From git at git.haskell.org Sat Nov 1 00:34:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 00:34:38 +0000 (UTC) Subject: [commit: ghc] master: Fix build via Haddock submodule update. (d15d704) Message-ID: <20141101003438.A8B683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d15d70447769c11d708e18078a475406f3b58491/ghc >--------------------------------------------------------------- commit d15d70447769c11d708e18078a475406f3b58491 Author: Austin Seipp Date: Fri Oct 31 19:34:56 2014 -0500 Fix build via Haddock submodule update. Signed-off-by: Austin Seipp >--------------------------------------------------------------- d15d70447769c11d708e18078a475406f3b58491 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 5a79e5b..199936a 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 5a79e5b25a1e628f7d1d9f4bf97ccd9e30242c6a +Subproject commit 199936af5bb902c81f822b2dc57308dc25e18cfc From git at git.haskell.org Sat Nov 1 04:09:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 04:09:41 +0000 (UTC) Subject: [commit: ghc] wip/T9732: In pattern synonym matchers, support unboxed results. (f48362b) Message-ID: <20141101040941.5E9603A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/f48362b961227778759c1baab66ce910abd2c400/ghc >--------------------------------------------------------------- commit f48362b961227778759c1baab66ce910abd2c400 Author: Dr. ERDI Gergo Date: Sat Nov 1 11:10:56 2014 +0800 In pattern synonym matchers, support unboxed results. This requires ensuring the continuations have arguments by adding a dummy Void# argument when needed. This is so that matching on a pattern synonym is lazy even when the result is unboxed, e.g. pattern P = () f P = 0# In this case, without dummy arguments, the generated matcher's type would be $mP :: forall (r :: ?). () -> r -> r -> r which is called in `f` at type `() -> Int# -> Int# -> Int#`, so it would be strict, in particular, in the failure continuation of `patError`. We work around this by making sure both continuations have arguments: $mP :: forall (r :: ?). () -> (Void# -> r) -> (Void# -> r) -> r Of course, if `P` (and thus, the success continuation) has any arguments, we are only adding the extra dummy argument to the failure continuation. >--------------------------------------------------------------- f48362b961227778759c1baab66ce910abd2c400 compiler/deSugar/DsUtils.lhs | 4 +++- compiler/typecheck/TcPatSyn.lhs | 19 ++++++++++++------- 2 files changed, 15 insertions(+), 8 deletions(-) diff --git a/compiler/deSugar/DsUtils.lhs b/compiler/deSugar/DsUtils.lhs index a269374..7e6ac43 100644 --- a/compiler/deSugar/DsUtils.lhs +++ b/compiler/deSugar/DsUtils.lhs @@ -348,13 +348,15 @@ mkPatSynCase var ty alt fail = do matcher <- dsLExpr $ mkLHsWrap wrapper $ nlHsTyApp matcher [ty] let MatchResult _ mkCont = match_result cont <- mkCoreLams bndrs <$> mkCont fail - return $ mkCoreAppsDs matcher [Var var, cont, fail] + return $ mkCoreAppsDs matcher [Var var, ensure_unstrict cont, make_unstrict fail] where MkCaseAlt{ alt_pat = psyn, alt_bndrs = bndrs, alt_wrapper = wrapper, alt_result = match_result} = alt matcher = patSynMatcher psyn + ensure_unstrict = if null bndrs then make_unstrict else id + make_unstrict = Lam voidArgId mkDataConCase :: Id -> Type -> [CaseAlt DataCon] -> MatchResult mkDataConCase _ _ [] = panic "mkDataConCase: no alternatives" diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 9b2b511..633abe2 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -30,6 +30,7 @@ import BasicTypes import TcSimplify import TcType import VarSet +import MkId #if __GLASGOW_HASKELL__ < 709 import Data.Monoid #endif @@ -124,13 +125,18 @@ tcPatSynMatcher :: Located Name -> TcM (Id, LHsBinds Id) -- See Note [Matchers and wrappers for pattern synonyms] in PatSyn tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_dicts prov_theta req_theta pat_ty - = do { res_tv <- zonkQuantifiedTyVar =<< newFlexiTyVar liftedTypeKind + = do { res_tv <- zonkQuantifiedTyVar =<< newFlexiTyVar openTypeKind + -- Zonking entails kind defaulting, which turns res_tv :: ? into res_tv :: *. + -- But here, we really do mean res_tv :: ?, so we reset it. + ; res_tv <- return $ setTyVarKind res_tv openTypeKind ; matcher_name <- newImplicitBinder name mkMatcherOcc ; let res_ty = TyVarTy res_tv + cont_args = if null args then [voidPrimId] else args cont_ty = mkSigmaTy ex_tvs prov_theta $ - mkFunTys (map varType args) res_ty + mkFunTys (map varType cont_args) res_ty + fail_ty = mkFunTy voidPrimTy res_ty - ; let matcher_tau = mkFunTys [pat_ty, cont_ty, res_ty] res_ty + ; let matcher_tau = mkFunTys [pat_ty, cont_ty, fail_ty] res_ty matcher_sigma = mkSigmaTy (res_tv:univ_tvs) req_theta matcher_tau matcher_id = mkExportedLocalId VanillaId matcher_name matcher_sigma @@ -139,10 +145,9 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; scrutinee <- mkId "scrut" pat_ty ; cont <- mkId "cont" cont_ty - ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ args) - ; fail <- mkId "fail" res_ty - ; let fail' = nlHsVar fail - + ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ cont_args) + ; fail <- mkId "fail" fail_ty + ; let fail' = nlHsApps fail [nlHsVar voidPrimId] ; let args = map nlVarPat [scrutinee, cont, fail] lwpat = noLoc $ WildPat pat_ty From git at git.haskell.org Sat Nov 1 04:09:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 04:09:43 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Add a dummy Void# argument to pattern synonym wrapper if it has no arguments and returns an unboxed type (see #9732) (5f77fa0) Message-ID: <20141101040943.E8DCE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/5f77fa06a17f0b3f23fb0f4c6902bacde9747a49/ghc >--------------------------------------------------------------- commit 5f77fa06a17f0b3f23fb0f4c6902bacde9747a49 Author: Dr. ERDI Gergo Date: Sat Nov 1 11:49:23 2014 +0800 Add a dummy Void# argument to pattern synonym wrapper if it has no arguments and returns an unboxed type (see #9732) >--------------------------------------------------------------- 5f77fa06a17f0b3f23fb0f4c6902bacde9747a49 compiler/typecheck/TcExpr.lhs | 36 ++++++++++++++-------- compiler/typecheck/TcPatSyn.lhs | 68 +++++++++++++++++++++-------------------- 2 files changed, 58 insertions(+), 46 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5f77fa06a17f0b3f23fb0f4c6902bacde9747a49 From git at git.haskell.org Sat Nov 1 04:09:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 04:09:46 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Binding things matched by an unboxed pattern synonym should require a bang (d800e75) Message-ID: <20141101040946.EFA243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/d800e75294626b134eabb99998863872a415a580/ghc >--------------------------------------------------------------- commit d800e75294626b134eabb99998863872a415a580 Author: Dr. ERDI Gergo Date: Sat Nov 1 12:00:19 2014 +0800 Binding things matched by an unboxed pattern synonym should require a bang >--------------------------------------------------------------- d800e75294626b134eabb99998863872a415a580 testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/all.T | 1 + testsuite/tests/patsyn/should_fail/unboxed-bind.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/unboxed-bind.stderr | 6 ++++++ 5 files changed, 28 insertions(+) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index d851bc3..94950a1 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -10,3 +10,4 @@ test('incomplete', normal, compile, ['']) test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) +test('unboxed-bind-bang', normal, compile, ['']) diff --git a/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs new file mode 100644 index 0000000..a972b21 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash, BangPatterns #-} +module ShouldCompile where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let !(P arg) = x in arg diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index bff6bdf..808e261 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -6,3 +6,4 @@ test('T8961', normal, multimod_compile_fail, ['T8961','']) test('as-pattern', normal, compile_fail, ['']) test('T9161-1', normal, compile_fail, ['']) test('T9161-2', normal, compile_fail, ['']) +test('unboxed-bind', normal, compile_fail, ['']) diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.hs b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs new file mode 100644 index 0000000..ef1b070 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module ShouldFail where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let P arg = x in arg diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr new file mode 100644 index 0000000..17ca7af --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr @@ -0,0 +1,6 @@ + +unboxed-bind.hs:10:11: + Pattern bindings containing unlifted types should use an outermost bang pattern: + P arg = x + In the expression: let P arg = x in arg + In an equation for ?f?: f x = let P arg = x in arg From git at git.haskell.org Sat Nov 1 04:09:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 04:09:50 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Test case for matching on unboxed pattern synonyms (5f22010) Message-ID: <20141101040950.071433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/5f22010b8367f87e6c4a924393a3cdca27219cf9/ghc >--------------------------------------------------------------- commit 5f22010b8367f87e6c4a924393a3cdca27219cf9 Author: Dr. ERDI Gergo Date: Sat Nov 1 12:00:42 2014 +0800 Test case for matching on unboxed pattern synonyms >--------------------------------------------------------------- 5f22010b8367f87e6c4a924393a3cdca27219cf9 testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_run/all.T | 1 + testsuite/tests/patsyn/should_run/match-unboxed.hs | 21 +++++++++++++++++++++ .../should_run/match-unboxed.stdout} | 2 ++ 4 files changed, 25 insertions(+) diff --git a/testsuite/.gitignore b/testsuite/.gitignore index e8b83e8..1893e69 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -1084,6 +1084,7 @@ mk/ghcconfig_*_inplace_bin_ghc-stage2.exe.mk /tests/patsyn/should_run/ex-prov /tests/patsyn/should_run/ex-prov-run /tests/patsyn/should_run/match +/tests/patsyn/should_run/match-unboxed /tests/perf/compiler/T1969.comp.stats /tests/perf/compiler/T3064.comp.stats /tests/perf/compiler/T3294.comp.stats diff --git a/testsuite/tests/patsyn/should_run/all.T b/testsuite/tests/patsyn/should_run/all.T index b3c6b74..442dd43 100644 --- a/testsuite/tests/patsyn/should_run/all.T +++ b/testsuite/tests/patsyn/should_run/all.T @@ -3,3 +3,4 @@ test('match', normal, compile_and_run, ['']) test('ex-prov-run', normal, compile_and_run, ['']) test('bidir-explicit', normal, compile_and_run, ['']) test('bidir-explicit-scope', normal, compile_and_run, ['']) +test('match-unboxed', normal, compile_and_run, ['']) diff --git a/testsuite/tests/patsyn/should_run/match-unboxed.hs b/testsuite/tests/patsyn/should_run/match-unboxed.hs new file mode 100644 index 0000000..ec6de0c --- /dev/null +++ b/testsuite/tests/patsyn/should_run/match-unboxed.hs @@ -0,0 +1,21 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module Main where + +import GHC.Base + +pattern P1 <- 0# +pattern P2 <- 1# + +f :: Int# -> Int# +f P1 = 42# +f P2 = 44# + +g :: Int# -> Int +g P1 = 42 +g P2 = 44 + +main = do + print $ I# (f 0#) + print $ I# (f 1#) + print $ g 0# + print $ g 1# diff --git a/testsuite/tests/array/should_run/arr020.stdout b/testsuite/tests/patsyn/should_run/match-unboxed.stdout similarity index 50% copy from testsuite/tests/array/should_run/arr020.stdout copy to testsuite/tests/patsyn/should_run/match-unboxed.stdout index daaac9e..da4a47e 100644 --- a/testsuite/tests/array/should_run/arr020.stdout +++ b/testsuite/tests/patsyn/should_run/match-unboxed.stdout @@ -1,2 +1,4 @@ 42 +44 42 +44 From git at git.haskell.org Sat Nov 1 04:09:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 04:09:53 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Test cases for bidirectional, unboxed pattern synonyms (caf582d) Message-ID: <20141101040953.0BB883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/caf582d1a41c0c0be32ff64cee6d6ca449440e30/ghc >--------------------------------------------------------------- commit caf582d1a41c0c0be32ff64cee6d6ca449440e30 Author: Dr. ERDI Gergo Date: Sat Nov 1 12:08:00 2014 +0800 Test cases for bidirectional, unboxed pattern synonyms >--------------------------------------------------------------- caf582d1a41c0c0be32ff64cee6d6ca449440e30 testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_fail/all.T | 1 + .../should_fail/{unboxed-bind.hs => unboxed-wrapper-naked.hs} | 6 ++---- testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.stderr | 3 +++ testsuite/tests/patsyn/should_run/all.T | 1 + testsuite/tests/patsyn/should_run/unboxed-wrapper.hs | 9 +++++++++ .../cgrun002.stdout => patsyn/should_run/unboxed-wrapper.stdout} | 0 7 files changed, 17 insertions(+), 4 deletions(-) diff --git a/testsuite/.gitignore b/testsuite/.gitignore index 1893e69..0d12434 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -1085,6 +1085,7 @@ mk/ghcconfig_*_inplace_bin_ghc-stage2.exe.mk /tests/patsyn/should_run/ex-prov-run /tests/patsyn/should_run/match /tests/patsyn/should_run/match-unboxed +/tests/patsyn/should_run/unboxed-wrapper /tests/perf/compiler/T1969.comp.stats /tests/perf/compiler/T3064.comp.stats /tests/perf/compiler/T3294.comp.stats diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index 808e261..5a26df5 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -7,3 +7,4 @@ test('as-pattern', normal, compile_fail, ['']) test('T9161-1', normal, compile_fail, ['']) test('T9161-2', normal, compile_fail, ['']) test('unboxed-bind', normal, compile_fail, ['']) +test('unboxed-wrapper-naked', normal, compile_fail, ['']) diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.hs b/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs similarity index 52% copy from testsuite/tests/patsyn/should_fail/unboxed-bind.hs copy to testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs index ef1b070..6e7cc94 100644 --- a/testsuite/tests/patsyn/should_fail/unboxed-bind.hs +++ b/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs @@ -3,8 +3,6 @@ module ShouldFail where import GHC.Base -data Foo = MkFoo Int# Int# +pattern P1 = 42# -pattern P x = MkFoo 0# x - -f x = let P arg = x in arg +x = P1 diff --git a/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.stderr b/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.stderr new file mode 100644 index 0000000..e8d8950 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.stderr @@ -0,0 +1,3 @@ + +unboxed-wrapper-naked.hs:8:1: + Top-level bindings for unlifted types aren't allowed: x = P1 diff --git a/testsuite/tests/patsyn/should_run/all.T b/testsuite/tests/patsyn/should_run/all.T index 442dd43..b557b3c 100644 --- a/testsuite/tests/patsyn/should_run/all.T +++ b/testsuite/tests/patsyn/should_run/all.T @@ -4,3 +4,4 @@ test('ex-prov-run', normal, compile_and_run, ['']) test('bidir-explicit', normal, compile_and_run, ['']) test('bidir-explicit-scope', normal, compile_and_run, ['']) test('match-unboxed', normal, compile_and_run, ['']) +test('unboxed-wrapper', normal, compile_and_run, ['']) diff --git a/testsuite/tests/patsyn/should_run/unboxed-wrapper.hs b/testsuite/tests/patsyn/should_run/unboxed-wrapper.hs new file mode 100644 index 0000000..367c8cc --- /dev/null +++ b/testsuite/tests/patsyn/should_run/unboxed-wrapper.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module Main where + +import GHC.Base + +pattern P1 = 42# + +main = do + print $ I# P1 diff --git a/testsuite/tests/codeGen/should_run/cgrun002.stdout b/testsuite/tests/patsyn/should_run/unboxed-wrapper.stdout similarity index 100% copy from testsuite/tests/codeGen/should_run/cgrun002.stdout copy to testsuite/tests/patsyn/should_run/unboxed-wrapper.stdout From git at git.haskell.org Sat Nov 1 04:16:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 04:16:27 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Add original bug report from #9732 as a test case (7d1505c) Message-ID: <20141101041627.7360E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/7d1505c5734f36de72ea3d9981ad715f254c8433/ghc >--------------------------------------------------------------- commit 7d1505c5734f36de72ea3d9981ad715f254c8433 Author: Dr. ERDI Gergo Date: Sat Nov 1 12:14:52 2014 +0800 Add original bug report from #9732 as a test case >--------------------------------------------------------------- 7d1505c5734f36de72ea3d9981ad715f254c8433 testsuite/tests/patsyn/should_compile/T9732.hs | 4 ++++ testsuite/tests/patsyn/should_compile/all.T | 1 + 2 files changed, 5 insertions(+) diff --git a/testsuite/tests/patsyn/should_compile/T9732.hs b/testsuite/tests/patsyn/should_compile/T9732.hs new file mode 100644 index 0000000..7fd0515 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T9732.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module ShouldCompile where + +pattern P = 0# diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index 94950a1..55e3b83 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -11,3 +11,4 @@ test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) test('unboxed-bind-bang', normal, compile, ['']) +test('T9732', normal, compile, ['']) From git at git.haskell.org Sat Nov 1 10:37:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 10:37:45 +0000 (UTC) Subject: [commit: ghc] master: Fix comment about dropWhileEndLE (6534686) Message-ID: <20141101103745.C05A23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/65346865f1177fc89767de09604376ffea45bd4d/ghc >--------------------------------------------------------------- commit 65346865f1177fc89767de09604376ffea45bd4d Author: Joachim Breitner Date: Sat Nov 1 11:37:53 2014 +0100 Fix comment about dropWhileEndLE >--------------------------------------------------------------- 65346865f1177fc89767de09604376ffea45bd4d utils/hpc/HpcUtils.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/hpc/HpcUtils.hs b/utils/hpc/HpcUtils.hs index 73d9cd3..4f98556 100644 --- a/utils/hpc/HpcUtils.hs +++ b/utils/hpc/HpcUtils.hs @@ -4,7 +4,7 @@ import Trace.Hpc.Util import qualified Data.Map as Map dropWhileEndLE :: (a -> Bool) -> [a] -> [a] --- Spec: dropWhileEndLE p = reverse . dropWhileEnd . reverse +-- Spec: dropWhileEndLE p = reverse . dropWhile p . reverse dropWhileEndLE p = foldr (\x r -> if null r && p x then [] else x:r) [] -- turns \n into ' ' From git at git.haskell.org Sat Nov 1 11:15:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 11:15:06 +0000 (UTC) Subject: [commit: ghc] wip/T9705: rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) (474843e) Message-ID: <20141101111506.69CEB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9705 Link : http://ghc.haskell.org/trac/ghc/changeset/474843ea6e62b00b7a65cba9790f4ac0df69aa9b/ghc >--------------------------------------------------------------- commit 474843ea6e62b00b7a65cba9790f4ac0df69aa9b Author: Dr. ERDI Gergo Date: Tue Oct 21 20:51:35 2014 +0800 rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) >--------------------------------------------------------------- 474843ea6e62b00b7a65cba9790f4ac0df69aa9b compiler/rename/RnBinds.lhs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index 96cb1aa..555d833 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -745,6 +745,11 @@ rnMethodBind _ _ (L loc bind@(PatBind {})) = do addErrAt loc (methodBindErr bind) return (emptyBag, emptyFVs) +-- Associated pattern synonyms are not implemented yet +rnMethodBind _ _ (L loc bind@(PatSynBind {})) = do + addErrAt loc $ methodPatSynErr bind + return (emptyBag, emptyFVs) + rnMethodBind _ _ b = pprPanic "rnMethodBind" (ppr b) \end{code} @@ -1061,6 +1066,11 @@ methodBindErr mbind = hang (ptext (sLit "Pattern bindings (except simple variables) not allowed in instance declarations")) 2 (ppr mbind) +methodPatSynErr :: HsBindLR RdrName RdrName -> SDoc +methodPatSynErr mbind + = hang (ptext (sLit "Pattern synonyms not allowed in instance declarations")) + 2 (ppr mbind) + bindsInHsBootFile :: LHsBindsLR Name RdrName -> SDoc bindsInHsBootFile mbinds = hang (ptext (sLit "Bindings in hs-boot files are not allowed")) From git at git.haskell.org Sat Nov 1 11:15:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 11:15:09 +0000 (UTC) Subject: [commit: ghc] wip/T9705: Add test case for T9705 (1cca652) Message-ID: <20141101111509.50D2A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9705 Link : http://ghc.haskell.org/trac/ghc/changeset/1cca652e8d4a8b87daf70bded87cddc39d973dab/ghc >--------------------------------------------------------------- commit 1cca652e8d4a8b87daf70bded87cddc39d973dab Author: Dr. ERDI Gergo Date: Tue Oct 21 20:51:55 2014 +0800 Add test case for T9705 >--------------------------------------------------------------- 1cca652e8d4a8b87daf70bded87cddc39d973dab testsuite/tests/patsyn/should_fail/T9705.hs | 3 +++ testsuite/tests/patsyn/should_fail/T9705.stderr | 4 ++++ testsuite/tests/patsyn/should_fail/all.T | 1 + 3 files changed, 8 insertions(+) diff --git a/testsuite/tests/patsyn/should_fail/T9705.hs b/testsuite/tests/patsyn/should_fail/T9705.hs new file mode 100644 index 0000000..54d1d00 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/T9705.hs @@ -0,0 +1,3 @@ +{-# LANGUAGE PatternSynonyms #-} +class C a where + pattern P = () diff --git a/testsuite/tests/patsyn/should_fail/T9705.stderr b/testsuite/tests/patsyn/should_fail/T9705.stderr new file mode 100644 index 0000000..d9a3a49 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/T9705.stderr @@ -0,0 +1,4 @@ + +T9705.hs:3:5: + Pattern synonyms not allowed in instance declarations + pattern P = () diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index bff6bdf..298f23b 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -6,3 +6,4 @@ test('T8961', normal, multimod_compile_fail, ['T8961','']) test('as-pattern', normal, compile_fail, ['']) test('T9161-1', normal, compile_fail, ['']) test('T9161-2', normal, compile_fail, ['']) +test('T9705', normal, compile_fail, ['']) From git at git.haskell.org Sat Nov 1 11:15:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 11:15:12 +0000 (UTC) Subject: [commit: ghc] wip/T9705's head updated: Add test case for T9705 (1cca652) Message-ID: <20141101111512.063FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9705' now includes: 5b9fe33 Indentation and non-semantic changes only. 4d90b53 Sync up `containers` submodule to latest `master`-tip 07da36b Revert "Fix typo in section name: no leading period." 0202b7c Revert "Check for staticclosures section in Windows linker." 89a8d81 Revert "Rename _closure to _static_closure, apply naming consistently." 126b0c4 Revert "Properly generate info tables for static closures in C--." a3860fc Revert "BC-breaking changes to C-- CLOSURE syntax." d5d6fb3 Revert "Place static closures in their own section." 47c4c91 Update Haddock submodule 07a99c1 Revert "rts/PrimOps.cmm: follow '_static_closure' update" f681c32 Test #9692 in th/T9692 2cd80ba Clarify location of Note. Comment change only. e319d6d Reify data family instances correctly. 710bc8d Update primitive, vector, and dph submodules. 27f7552 Make Applicative-Monad fixes for tests. 3687089 Updated testsuite/.gitignore to cover artifacts on Windows. 2cc2065 Use objdump instead of nm to derive constants on OpenBSD 9f29e03 ghc-prim: Use population count appropriate for platform d4fd168 Update to Unicode version 7.0 a5f4fb6 Remove extra period 3157127 Improve isDigit, isSpace, etc. ef2d027 Make findIndices fuse 1e269bf Make Data.List.concatMap fuse better 6825558 Add doctest examples for Data.Functor. 5211673 Fix typo in -XConstraintKinds docs 9c464f8 Add doctest examples for Data.Bool. c819958 Add release note about Unicode 7.0 69f6361 Fixes the ARM build 972ba12 Enabled warn on tabs by default (fixes #9230) 4faeecb [skip ci] rts: Detabify RtsMessages.c aa8d23d [skip ci] rts: Detabify RaiseAsync.h bb04867 [skip ci] rts: Detabify Capability.h 99edc35 [skip ci] rts: Detabify CheckUnload.c 6aa6ca8 [skip ci] rts: Detabify Profiling.c 570b339 [skip ci] rts: Detabify Threads.c 21eaaa1 [skip ci] rts: Detabify sm/Evac.c 9167d0e [skip ci] rts: Detabify sm/Scav.c 5bb8f14 [skip ci] rts: Detabify Stats.c 2dc21b9 [skip ci] rts: Detabify Schedule.h 1d12df3 [skip ci] rts: Detabify LdvProfile.h 3d0e695 [skip ci] rts: Detabify Proftimer.c 68c45b6 [skip ci] rts: Detabify Exception.cmm a7ab7d3 [skip ci] rts: Detabify HeapStackCheck.cmm 6811e53 [skip ci] rts: Detabify Capability.c beb5c2e [skip ci] rts: Detabify RaiseAsync.c e13478f [skip ci] rts: Detabify sm/GC.c faa3339 [skip ci] rts: Detabify sm/Sanity.c bc1609a [skip ci] rts: Detabify sm/Compact.c c8173d5 [skip ci] rts: Detabify sm/Compact.h 5106e20 [skip ci] rts: Detabify RetainerProfile.c 03c3e9a [skip ci] rts: Detabify ProfHeap.c 6abb34c [skip ci] rts: Detabify Schedule.c 9bfe602 rts: Detabify Interpreter.c df5c11a base: Mark WCsubst.c as generated for Phabricator 45cbe85 Flush stdout in T9692 aa641e5 Add forgotten import to T9692 a11f71e Fix a rare parallel GC bug 427925d More updates to Backpack manual [skip ci] 5bb73d7 Check in up-to-date PDF copies of Backpack docs. [skip ci] aa47995 Implementation of hsig (module signatures), per #9252 1addef8 Fix windows build failure. 73c7ea7 fix a typo in comments: normaliseFfiType 0855b24 Pass in CXX to libffi's configure script. 7b59db2 `M-x delete-trailing-whitespace` & `M-x untabify` a3312c3 testsuite: Fix outdated output for T5979/safePkg01 0a290ca Add new `Data.Bifunctor` module (re #9682) 9e2cb00 Optimise atomicModifyIORef' implementation (#8345) 0e1f0f7 Un-wire `Integer` type (re #9714) 0013613 Deactivate T3064 `max_bytes_used`-check 49b05d6 Improve performance of isSuffixOf (#9676) 1874501 Typo in comment aa2ceba Normalise package key hash to make tests less fragile. 63918e6 Add n-ary version of `two_normalisers` to testsuite lib 3d6422b testlib: Get rid of two_normalisers 98ed815 Make iterateFB inlineable 75979f3 base: Refactor/clean-up *List modules 5f69c8e Reorder GHC.List; fix performance regressions f109085 Update Haddock submodule for collapsible section support 64d0a19 Really fix fft2 regression. #9740 208a0c2 Fixed unused variable warning on mingw32/i686 in rts/Linker.c f9ca529 hsc2hs: Update submodule 322810e Convert GHCi sources from .lhs to .hs 257cbec Fix #9236 Error on read from closed handle 5ce1266 Use snwprintf instead of swprintf in rts/Linker.c. acb3295 Avoid setting -Werror=unused-but-set-variable on Windows. 45175e1 Extra CRs are now filtered out from the source file for :list. f10b67a Updated stale ghcpkg05.stderr-mingw32. 3d27f69 Do not use a relative path for echo in tests/ghci/prog013. c211f8e Add __GLASGOW_HASKELL_TH__=YES/NO to CPP definitions 93c776a Added mingw32-specific expected stdout files for tests/driver/sigof{01,02,03} 9de5240 Comments only c6d4ae6 Fix test driver python3 compatibility issues 578bc00 Add notes on change to hGetContents semantics 995ea1c Fixed missing trailing newline bug in pretty printer 1907e81 Updated testsuite/.gitignore to exclude some test artifacts on Windows. cbb20ab Drop deprecated `OverlappingInstances` from base 919e930 Fix comment typos 8ef4cf1 Add doctest examples for Data.Char bd6c6f6 Update Haddock submodule 54addb1 Clean-up `Data.Fixed` f12be5b Add changelog entry for recent Unicode 7.0 update d3a7126 Update doctest example style in `Data.Bool` 4667fb5 Split off stat (benchmark) test failures into a separate section in the test runner summary. 322c139 remove old .NET related code e466ea7 Remove legacy support for -optdef flags d15d704 Fix build via Haddock submodule update. 474843e rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) 1cca652 Add test case for T9705 From git at git.haskell.org Sat Nov 1 11:16:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 11:16:08 +0000 (UTC) Subject: [commit: ghc] wip/T9705: rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) (e5ba360) Message-ID: <20141101111608.165373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9705 Link : http://ghc.haskell.org/trac/ghc/changeset/e5ba36080d08791f44e3bed37721f702e242af96/ghc >--------------------------------------------------------------- commit e5ba36080d08791f44e3bed37721f702e242af96 Author: Dr. ERDI Gergo Date: Tue Oct 21 20:51:35 2014 +0800 rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) >--------------------------------------------------------------- e5ba36080d08791f44e3bed37721f702e242af96 compiler/rename/RnBinds.lhs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/T9705.hs | 3 +++ testsuite/tests/patsyn/should_fail/T9705.stderr | 4 ++++ testsuite/tests/patsyn/should_fail/all.T | 1 + 4 files changed, 18 insertions(+) diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index 96cb1aa..555d833 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -745,6 +745,11 @@ rnMethodBind _ _ (L loc bind@(PatBind {})) = do addErrAt loc (methodBindErr bind) return (emptyBag, emptyFVs) +-- Associated pattern synonyms are not implemented yet +rnMethodBind _ _ (L loc bind@(PatSynBind {})) = do + addErrAt loc $ methodPatSynErr bind + return (emptyBag, emptyFVs) + rnMethodBind _ _ b = pprPanic "rnMethodBind" (ppr b) \end{code} @@ -1061,6 +1066,11 @@ methodBindErr mbind = hang (ptext (sLit "Pattern bindings (except simple variables) not allowed in instance declarations")) 2 (ppr mbind) +methodPatSynErr :: HsBindLR RdrName RdrName -> SDoc +methodPatSynErr mbind + = hang (ptext (sLit "Pattern synonyms not allowed in instance declarations")) + 2 (ppr mbind) + bindsInHsBootFile :: LHsBindsLR Name RdrName -> SDoc bindsInHsBootFile mbinds = hang (ptext (sLit "Bindings in hs-boot files are not allowed")) diff --git a/testsuite/tests/patsyn/should_fail/T9705.hs b/testsuite/tests/patsyn/should_fail/T9705.hs new file mode 100644 index 0000000..54d1d00 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/T9705.hs @@ -0,0 +1,3 @@ +{-# LANGUAGE PatternSynonyms #-} +class C a where + pattern P = () diff --git a/testsuite/tests/patsyn/should_fail/T9705.stderr b/testsuite/tests/patsyn/should_fail/T9705.stderr new file mode 100644 index 0000000..d9a3a49 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/T9705.stderr @@ -0,0 +1,4 @@ + +T9705.hs:3:5: + Pattern synonyms not allowed in instance declarations + pattern P = () diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index bff6bdf..298f23b 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -6,3 +6,4 @@ test('T8961', normal, multimod_compile_fail, ['T8961','']) test('as-pattern', normal, compile_fail, ['']) test('T9161-1', normal, compile_fail, ['']) test('T9161-2', normal, compile_fail, ['']) +test('T9705', normal, compile_fail, ['']) From git at git.haskell.org Sat Nov 1 11:16:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 11:16:10 +0000 (UTC) Subject: [commit: ghc] wip/T9705's head updated: rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) (e5ba360) Message-ID: <20141101111610.4A6533A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9705' now includes: 6534686 Fix comment about dropWhileEndLE e5ba360 rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) From git at git.haskell.org Sat Nov 1 11:18:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 11:18:28 +0000 (UTC) Subject: [commit: ghc] master's head updated: rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) (e5ba360) Message-ID: <20141101111828.8E94E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: e5ba360 rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) From git at git.haskell.org Sat Nov 1 11:45:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 11:45:15 +0000 (UTC) Subject: [commit: ghc] wip/T9732: In pattern synonym matchers, support unboxed continuation results. (ce26212) Message-ID: <20141101114515.EE5993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/ce26212f3fbeff2fdc31a114a3fb1f5a66e4e661/ghc >--------------------------------------------------------------- commit ce26212f3fbeff2fdc31a114a3fb1f5a66e4e661 Author: Dr. ERDI Gergo Date: Sat Nov 1 11:10:56 2014 +0800 In pattern synonym matchers, support unboxed continuation results. This requires ensuring the continuations have arguments by adding a dummy Void# argument when needed. This is so that matching on a pattern synonym is lazy even when the result is unboxed, e.g. pattern P = () f P = 0# In this case, without dummy arguments, the generated matcher's type would be $mP :: forall (r :: ?). () -> r -> r -> r which is called in `f` at type `() -> Int# -> Int# -> Int#`, so it would be strict, in particular, in the failure continuation of `patError`. We work around this by making sure both continuations have arguments: $mP :: forall (r :: ?). () -> (Void# -> r) -> (Void# -> r) -> r Of course, if `P` (and thus, the success continuation) has any arguments, we are only adding the extra dummy argument to the failure continuation. >--------------------------------------------------------------- ce26212f3fbeff2fdc31a114a3fb1f5a66e4e661 compiler/deSugar/DsUtils.lhs | 4 +++- compiler/typecheck/TcPatSyn.lhs | 19 ++++++++++++------- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_run/all.T | 1 + testsuite/tests/patsyn/should_run/match-unboxed.hs | 21 +++++++++++++++++++++ .../should_run/match-unboxed.stdout} | 2 ++ 6 files changed, 40 insertions(+), 8 deletions(-) diff --git a/compiler/deSugar/DsUtils.lhs b/compiler/deSugar/DsUtils.lhs index a269374..7e6ac43 100644 --- a/compiler/deSugar/DsUtils.lhs +++ b/compiler/deSugar/DsUtils.lhs @@ -348,13 +348,15 @@ mkPatSynCase var ty alt fail = do matcher <- dsLExpr $ mkLHsWrap wrapper $ nlHsTyApp matcher [ty] let MatchResult _ mkCont = match_result cont <- mkCoreLams bndrs <$> mkCont fail - return $ mkCoreAppsDs matcher [Var var, cont, fail] + return $ mkCoreAppsDs matcher [Var var, ensure_unstrict cont, make_unstrict fail] where MkCaseAlt{ alt_pat = psyn, alt_bndrs = bndrs, alt_wrapper = wrapper, alt_result = match_result} = alt matcher = patSynMatcher psyn + ensure_unstrict = if null bndrs then make_unstrict else id + make_unstrict = Lam voidArgId mkDataConCase :: Id -> Type -> [CaseAlt DataCon] -> MatchResult mkDataConCase _ _ [] = panic "mkDataConCase: no alternatives" diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 9b2b511..633abe2 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -30,6 +30,7 @@ import BasicTypes import TcSimplify import TcType import VarSet +import MkId #if __GLASGOW_HASKELL__ < 709 import Data.Monoid #endif @@ -124,13 +125,18 @@ tcPatSynMatcher :: Located Name -> TcM (Id, LHsBinds Id) -- See Note [Matchers and wrappers for pattern synonyms] in PatSyn tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_dicts prov_theta req_theta pat_ty - = do { res_tv <- zonkQuantifiedTyVar =<< newFlexiTyVar liftedTypeKind + = do { res_tv <- zonkQuantifiedTyVar =<< newFlexiTyVar openTypeKind + -- Zonking entails kind defaulting, which turns res_tv :: ? into res_tv :: *. + -- But here, we really do mean res_tv :: ?, so we reset it. + ; res_tv <- return $ setTyVarKind res_tv openTypeKind ; matcher_name <- newImplicitBinder name mkMatcherOcc ; let res_ty = TyVarTy res_tv + cont_args = if null args then [voidPrimId] else args cont_ty = mkSigmaTy ex_tvs prov_theta $ - mkFunTys (map varType args) res_ty + mkFunTys (map varType cont_args) res_ty + fail_ty = mkFunTy voidPrimTy res_ty - ; let matcher_tau = mkFunTys [pat_ty, cont_ty, res_ty] res_ty + ; let matcher_tau = mkFunTys [pat_ty, cont_ty, fail_ty] res_ty matcher_sigma = mkSigmaTy (res_tv:univ_tvs) req_theta matcher_tau matcher_id = mkExportedLocalId VanillaId matcher_name matcher_sigma @@ -139,10 +145,9 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; scrutinee <- mkId "scrut" pat_ty ; cont <- mkId "cont" cont_ty - ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ args) - ; fail <- mkId "fail" res_ty - ; let fail' = nlHsVar fail - + ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ cont_args) + ; fail <- mkId "fail" fail_ty + ; let fail' = nlHsApps fail [nlHsVar voidPrimId] ; let args = map nlVarPat [scrutinee, cont, fail] lwpat = noLoc $ WildPat pat_ty diff --git a/testsuite/.gitignore b/testsuite/.gitignore index ce5c2c2..2423e15 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -1097,6 +1097,7 @@ mk/ghcconfig*_inplace_bin_ghc-stage2.exe.mk /tests/patsyn/should_run/ex-prov /tests/patsyn/should_run/ex-prov-run /tests/patsyn/should_run/match +/tests/patsyn/should_run/match-unboxed /tests/perf/compiler/T1969.comp.stats /tests/perf/compiler/T3064.comp.stats /tests/perf/compiler/T3294.comp.stats diff --git a/testsuite/tests/patsyn/should_run/all.T b/testsuite/tests/patsyn/should_run/all.T index b3c6b74..442dd43 100644 --- a/testsuite/tests/patsyn/should_run/all.T +++ b/testsuite/tests/patsyn/should_run/all.T @@ -3,3 +3,4 @@ test('match', normal, compile_and_run, ['']) test('ex-prov-run', normal, compile_and_run, ['']) test('bidir-explicit', normal, compile_and_run, ['']) test('bidir-explicit-scope', normal, compile_and_run, ['']) +test('match-unboxed', normal, compile_and_run, ['']) diff --git a/testsuite/tests/patsyn/should_run/match-unboxed.hs b/testsuite/tests/patsyn/should_run/match-unboxed.hs new file mode 100644 index 0000000..ec6de0c --- /dev/null +++ b/testsuite/tests/patsyn/should_run/match-unboxed.hs @@ -0,0 +1,21 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module Main where + +import GHC.Base + +pattern P1 <- 0# +pattern P2 <- 1# + +f :: Int# -> Int# +f P1 = 42# +f P2 = 44# + +g :: Int# -> Int +g P1 = 42 +g P2 = 44 + +main = do + print $ I# (f 0#) + print $ I# (f 1#) + print $ g 0# + print $ g 1# diff --git a/testsuite/tests/array/should_run/arr020.stdout b/testsuite/tests/patsyn/should_run/match-unboxed.stdout similarity index 50% copy from testsuite/tests/array/should_run/arr020.stdout copy to testsuite/tests/patsyn/should_run/match-unboxed.stdout index daaac9e..da4a47e 100644 --- a/testsuite/tests/array/should_run/arr020.stdout +++ b/testsuite/tests/patsyn/should_run/match-unboxed.stdout @@ -1,2 +1,4 @@ 42 +44 42 +44 From git at git.haskell.org Sat Nov 1 11:45:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 11:45:19 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Add a dummy Void# argument to pattern synonym wrapper if it has no arguments and returns an unboxed type (see #9732) (3dc8fb9) Message-ID: <20141101114519.20EC33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/3dc8fb9556215712cb2348a4a2a7f44a6dbafa28/ghc >--------------------------------------------------------------- commit 3dc8fb9556215712cb2348a4a2a7f44a6dbafa28 Author: Dr. ERDI Gergo Date: Sat Nov 1 11:49:23 2014 +0800 Add a dummy Void# argument to pattern synonym wrapper if it has no arguments and returns an unboxed type (see #9732) >--------------------------------------------------------------- 3dc8fb9556215712cb2348a4a2a7f44a6dbafa28 compiler/typecheck/TcExpr.lhs | 36 +++++++----- compiler/typecheck/TcPatSyn.lhs | 68 +++++++++++----------- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_compile/T9732.hs | 4 ++ testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_fail/all.T | 2 +- .../patsyn/should_fail/unboxed-wrapper-naked.hs | 8 +++ .../should_fail/unboxed-wrapper-naked.stderr | 3 + testsuite/tests/patsyn/should_run/all.T | 1 + .../tests/patsyn/should_run/unboxed-wrapper.hs | 9 +++ .../should_run/unboxed-wrapper.stdout} | 0 11 files changed, 86 insertions(+), 47 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3dc8fb9556215712cb2348a4a2a7f44a6dbafa28 From git at git.haskell.org Sat Nov 1 11:45:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 11:45:22 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Binding things matched by an unboxed pattern synonym should require a bang (a322501) Message-ID: <20141101114522.29DF23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/a322501d15e8bcf49300b5d3afcca5857adb78e8/ghc >--------------------------------------------------------------- commit a322501d15e8bcf49300b5d3afcca5857adb78e8 Author: Dr. ERDI Gergo Date: Sat Nov 1 12:00:19 2014 +0800 Binding things matched by an unboxed pattern synonym should require a bang >--------------------------------------------------------------- a322501d15e8bcf49300b5d3afcca5857adb78e8 testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/all.T | 1 + .../should_fail/{unboxed-wrapper-naked.hs => unboxed-bind.hs} | 6 ++++-- testsuite/tests/patsyn/should_fail/unboxed-bind.stderr | 6 ++++++ 5 files changed, 22 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index e8cfb60..97d4317 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -11,3 +11,4 @@ test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) test('T9732', normal, compile, ['']) +test('unboxed-bind-bang', normal, compile, ['']) diff --git a/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs new file mode 100644 index 0000000..a972b21 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash, BangPatterns #-} +module ShouldCompile where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let !(P arg) = x in arg diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index 00cf0d9..2eba0ff 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -7,3 +7,4 @@ test('T9161-1', normal, compile_fail, ['']) test('T9161-2', normal, compile_fail, ['']) test('T9705', normal, compile_fail, ['']) test('unboxed-wrapper-naked', normal, compile_fail, ['']) +test('unboxed-bind', normal, compile_fail, ['']) diff --git a/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs similarity index 52% copy from testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs copy to testsuite/tests/patsyn/should_fail/unboxed-bind.hs index 6e7cc94..ef1b070 100644 --- a/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs @@ -3,6 +3,8 @@ module ShouldFail where import GHC.Base -pattern P1 = 42# +data Foo = MkFoo Int# Int# -x = P1 +pattern P x = MkFoo 0# x + +f x = let P arg = x in arg diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr new file mode 100644 index 0000000..17ca7af --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr @@ -0,0 +1,6 @@ + +unboxed-bind.hs:10:11: + Pattern bindings containing unlifted types should use an outermost bang pattern: + P arg = x + In the expression: let P arg = x in arg + In an equation for ?f?: f x = let P arg = x in arg From git at git.haskell.org Sat Nov 1 11:45:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 11:45:24 +0000 (UTC) Subject: [commit: ghc] wip/T9732's head updated: Binding things matched by an unboxed pattern synonym should require a bang (a322501) Message-ID: <20141101114524.BCDAF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9732' now includes: 5b9fe33 Indentation and non-semantic changes only. 4d90b53 Sync up `containers` submodule to latest `master`-tip 07da36b Revert "Fix typo in section name: no leading period." 0202b7c Revert "Check for staticclosures section in Windows linker." 89a8d81 Revert "Rename _closure to _static_closure, apply naming consistently." 126b0c4 Revert "Properly generate info tables for static closures in C--." a3860fc Revert "BC-breaking changes to C-- CLOSURE syntax." d5d6fb3 Revert "Place static closures in their own section." 47c4c91 Update Haddock submodule 07a99c1 Revert "rts/PrimOps.cmm: follow '_static_closure' update" f681c32 Test #9692 in th/T9692 2cd80ba Clarify location of Note. Comment change only. e319d6d Reify data family instances correctly. 710bc8d Update primitive, vector, and dph submodules. 27f7552 Make Applicative-Monad fixes for tests. 3687089 Updated testsuite/.gitignore to cover artifacts on Windows. 2cc2065 Use objdump instead of nm to derive constants on OpenBSD 9f29e03 ghc-prim: Use population count appropriate for platform d4fd168 Update to Unicode version 7.0 a5f4fb6 Remove extra period 3157127 Improve isDigit, isSpace, etc. ef2d027 Make findIndices fuse 1e269bf Make Data.List.concatMap fuse better 6825558 Add doctest examples for Data.Functor. 5211673 Fix typo in -XConstraintKinds docs 9c464f8 Add doctest examples for Data.Bool. c819958 Add release note about Unicode 7.0 69f6361 Fixes the ARM build 972ba12 Enabled warn on tabs by default (fixes #9230) 4faeecb [skip ci] rts: Detabify RtsMessages.c aa8d23d [skip ci] rts: Detabify RaiseAsync.h bb04867 [skip ci] rts: Detabify Capability.h 99edc35 [skip ci] rts: Detabify CheckUnload.c 6aa6ca8 [skip ci] rts: Detabify Profiling.c 570b339 [skip ci] rts: Detabify Threads.c 21eaaa1 [skip ci] rts: Detabify sm/Evac.c 9167d0e [skip ci] rts: Detabify sm/Scav.c 5bb8f14 [skip ci] rts: Detabify Stats.c 2dc21b9 [skip ci] rts: Detabify Schedule.h 1d12df3 [skip ci] rts: Detabify LdvProfile.h 3d0e695 [skip ci] rts: Detabify Proftimer.c 68c45b6 [skip ci] rts: Detabify Exception.cmm a7ab7d3 [skip ci] rts: Detabify HeapStackCheck.cmm 6811e53 [skip ci] rts: Detabify Capability.c beb5c2e [skip ci] rts: Detabify RaiseAsync.c e13478f [skip ci] rts: Detabify sm/GC.c faa3339 [skip ci] rts: Detabify sm/Sanity.c bc1609a [skip ci] rts: Detabify sm/Compact.c c8173d5 [skip ci] rts: Detabify sm/Compact.h 5106e20 [skip ci] rts: Detabify RetainerProfile.c 03c3e9a [skip ci] rts: Detabify ProfHeap.c 6abb34c [skip ci] rts: Detabify Schedule.c 9bfe602 rts: Detabify Interpreter.c df5c11a base: Mark WCsubst.c as generated for Phabricator 45cbe85 Flush stdout in T9692 aa641e5 Add forgotten import to T9692 a11f71e Fix a rare parallel GC bug 427925d More updates to Backpack manual [skip ci] 5bb73d7 Check in up-to-date PDF copies of Backpack docs. [skip ci] aa47995 Implementation of hsig (module signatures), per #9252 1addef8 Fix windows build failure. 73c7ea7 fix a typo in comments: normaliseFfiType 0855b24 Pass in CXX to libffi's configure script. 7b59db2 `M-x delete-trailing-whitespace` & `M-x untabify` a3312c3 testsuite: Fix outdated output for T5979/safePkg01 0a290ca Add new `Data.Bifunctor` module (re #9682) 9e2cb00 Optimise atomicModifyIORef' implementation (#8345) 0e1f0f7 Un-wire `Integer` type (re #9714) 0013613 Deactivate T3064 `max_bytes_used`-check 49b05d6 Improve performance of isSuffixOf (#9676) 1874501 Typo in comment aa2ceba Normalise package key hash to make tests less fragile. 63918e6 Add n-ary version of `two_normalisers` to testsuite lib 3d6422b testlib: Get rid of two_normalisers 98ed815 Make iterateFB inlineable 75979f3 base: Refactor/clean-up *List modules 5f69c8e Reorder GHC.List; fix performance regressions f109085 Update Haddock submodule for collapsible section support 64d0a19 Really fix fft2 regression. #9740 208a0c2 Fixed unused variable warning on mingw32/i686 in rts/Linker.c f9ca529 hsc2hs: Update submodule 322810e Convert GHCi sources from .lhs to .hs 257cbec Fix #9236 Error on read from closed handle 5ce1266 Use snwprintf instead of swprintf in rts/Linker.c. acb3295 Avoid setting -Werror=unused-but-set-variable on Windows. 45175e1 Extra CRs are now filtered out from the source file for :list. f10b67a Updated stale ghcpkg05.stderr-mingw32. 3d27f69 Do not use a relative path for echo in tests/ghci/prog013. c211f8e Add __GLASGOW_HASKELL_TH__=YES/NO to CPP definitions 93c776a Added mingw32-specific expected stdout files for tests/driver/sigof{01,02,03} 9de5240 Comments only c6d4ae6 Fix test driver python3 compatibility issues 578bc00 Add notes on change to hGetContents semantics 995ea1c Fixed missing trailing newline bug in pretty printer 1907e81 Updated testsuite/.gitignore to exclude some test artifacts on Windows. cbb20ab Drop deprecated `OverlappingInstances` from base 919e930 Fix comment typos 8ef4cf1 Add doctest examples for Data.Char bd6c6f6 Update Haddock submodule 54addb1 Clean-up `Data.Fixed` f12be5b Add changelog entry for recent Unicode 7.0 update d3a7126 Update doctest example style in `Data.Bool` 4667fb5 Split off stat (benchmark) test failures into a separate section in the test runner summary. 322c139 remove old .NET related code e466ea7 Remove legacy support for -optdef flags d15d704 Fix build via Haddock submodule update. 6534686 Fix comment about dropWhileEndLE e5ba360 rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) ce26212 In pattern synonym matchers, support unboxed continuation results. 3dc8fb9 Add a dummy Void# argument to pattern synonym wrapper if it has no arguments and returns an unboxed type (see #9732) a322501 Binding things matched by an unboxed pattern synonym should require a bang From git at git.haskell.org Sat Nov 1 13:20:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Nov 2014 13:20:33 +0000 (UTC) Subject: [commit: ghc] master: Fixed T5435_dyn_asm on Windows. The test code was not in sync with the expected output. (a47ff8b) Message-ID: <20141101132033.287703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a47ff8be5aa78aff2eb80d5f91e294f52ea392e0/ghc >--------------------------------------------------------------- commit a47ff8be5aa78aff2eb80d5f91e294f52ea392e0 Author: Gintautas Miliauskas Date: Sat Nov 1 08:20:45 2014 -0500 Fixed T5435_dyn_asm on Windows. The test code was not in sync with the expected output. Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D403 GHC Trac Issues: #5435 >--------------------------------------------------------------- a47ff8be5aa78aff2eb80d5f91e294f52ea392e0 testsuite/tests/rts/all.T | 2 ++ 1 file changed, 2 insertions(+) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index 015a9c7..6d08594 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -142,6 +142,8 @@ def checkDynAsm(actual_file, normaliser): elif actual == ['ctors1', 'ctors2', 'initArray1', 'initArray2', 'success']: if_verbose(1, 'T5435_dyn_asm detected old-style dlopen, see #8458') return 1 + elif opsys('mingw32') and actual == ['ctors1', 'ctors2', 'success']: + return 1 else: if_verbose(1, 'T5435_dyn_asm failed with %s, see all.T for details' % actual) return 0 From git at git.haskell.org Sun Nov 2 03:53:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 03:53:20 +0000 (UTC) Subject: [commit: ghc] master: Test #9262 in th/T9262, and update other tests. (f688f03) Message-ID: <20141102035320.CDCEC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f688f0377e13e0762d422ed3a83e74b5d39b5e13/ghc >--------------------------------------------------------------- commit f688f0377e13e0762d422ed3a83e74b5d39b5e13 Author: Richard Eisenberg Date: Tue Oct 21 09:12:34 2014 -0400 Test #9262 in th/T9262, and update other tests. >--------------------------------------------------------------- f688f0377e13e0762d422ed3a83e74b5d39b5e13 testsuite/tests/th/T6114.hs | 13 ++++++------- testsuite/tests/th/T6114.stderr | 12 ------------ testsuite/tests/th/T9262.hs | 12 ++++++++++++ testsuite/tests/th/T9262.stderr | 1 + testsuite/tests/th/all.T | 3 ++- 5 files changed, 21 insertions(+), 20 deletions(-) diff --git a/testsuite/tests/th/T6114.hs b/testsuite/tests/th/T6114.hs index bea852c..c5278e3 100644 --- a/testsuite/tests/th/T6114.hs +++ b/testsuite/tests/th/T6114.hs @@ -1,11 +1,10 @@ {-# LANGUAGE TemplateHaskell #-} module T6114 where import Language.Haskell.TH -import Control.Monad.Instances () -instanceVar = $(do - xName <- newName "x" - instanceType <- [t| $(varT xName) |] - _ <- reifyInstances ''Eq [instanceType] - undefined - ) +$(do + xName <- newName "x" + instanceType <- [t| $(varT xName) |] + _ <- reifyInstances ''Eq [instanceType] + return [] + ) diff --git a/testsuite/tests/th/T6114.stderr b/testsuite/tests/th/T6114.stderr deleted file mode 100644 index 917b56f..0000000 --- a/testsuite/tests/th/T6114.stderr +++ /dev/null @@ -1,12 +0,0 @@ - -T6114.hs:6:17: - The exact Name ?x? is not in scope - Probable cause: you used a unique Template Haskell name (NameU), - perhaps via newName, but did not bind it - If that's it, then -ddump-splices might be useful - In the argument of reifyInstances: GHC.Classes.Eq x_0 - In the splice: - $(do { xName <- newName "x"; - instanceType <- [t| $(varT xName) |]; - _ <- reifyInstances ''Eq [instanceType]; - .... }) diff --git a/testsuite/tests/th/T9262.hs b/testsuite/tests/th/T9262.hs new file mode 100644 index 0000000..8a44603 --- /dev/null +++ b/testsuite/tests/th/T9262.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T9262 where + +import Language.Haskell.TH +import Language.Haskell.TH.Ppr +import System.IO + +$(do insts <- reifyInstances ''Eq [ListT `AppT` VarT (mkName "a")] + runIO $ putStrLn $ pprint insts + runIO $ hFlush stdout + return [] ) diff --git a/testsuite/tests/th/T9262.stderr b/testsuite/tests/th/T9262.stderr new file mode 100644 index 0000000..efdf5e3 --- /dev/null +++ b/testsuite/tests/th/T9262.stderr @@ -0,0 +1 @@ +instance GHC.Classes.Eq a_0 => GHC.Classes.Eq ([a_0]) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 2981202..d3ae4e4 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -251,7 +251,7 @@ test('T5795', normal, compile_fail, ['-v0']) test('T6005', normal, compile, ['-v0']) test('T6005a', normal, compile, ['-v0']) test('T5737', normal, compile, ['-v0']) -test('T6114', normal, compile_fail, ['-v0 -dsuppress-uniques']) +test('T6114', normal, compile, ['-v0']) test('TH_StringPrimL', normal, compile_and_run, ['']) test('T7064', extra_clean(['T7064a.hi', 'T7064a.o']), @@ -329,5 +329,6 @@ test('T8954', normal, compile, ['-v0']) test('T8932', normal, compile_fail, ['-v0']) test('T8987', normal, compile_fail, ['-v0']) test('T7241', normal, compile_fail, ['-v0']) +test('T9262', normal, compile, ['-v0']) test('T9199', normal, compile, ['-v0']) test('T9692', normal, compile, ['-v0']) From git at git.haskell.org Sun Nov 2 03:53:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 03:53:23 +0000 (UTC) Subject: [commit: ghc] master: Bring unbound tyvars into scope during reifyInstances. (2cc593d) Message-ID: <20141102035323.60E623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2cc593dd50197c252d87321280a04f04cc173dbc/ghc >--------------------------------------------------------------- commit 2cc593dd50197c252d87321280a04f04cc173dbc Author: Richard Eisenberg Date: Tue Oct 21 09:13:08 2014 -0400 Bring unbound tyvars into scope during reifyInstances. Fix #9262. >--------------------------------------------------------------- 2cc593dd50197c252d87321280a04f04cc173dbc compiler/rename/RnSplice.lhs | 7 +++++++ compiler/typecheck/TcSplice.lhs | 30 ++++++++++++++++-------------- 2 files changed, 23 insertions(+), 14 deletions(-) diff --git a/compiler/rename/RnSplice.lhs b/compiler/rename/RnSplice.lhs index c7b962e..94e3fc2 100644 --- a/compiler/rename/RnSplice.lhs +++ b/compiler/rename/RnSplice.lhs @@ -87,6 +87,13 @@ which is a bit inconsistent -- but there are a lot of them. We might thereby get some bogus unused-import warnings, but we won't crash the type checker. Not very satisfactory really. +Note [Renamer errors] +~~~~~~~~~~~~~~~~~~~~~ +It's important to wrap renamer calls in checkNoErrs, because the +renamer does not fail for out of scope variables etc. Instead it +returns a bogus term/type, so that it can report more than one error. +We don't want the type checker to see these bogus unbound variables. + \begin{code} rnSpliceGen :: Bool -- Typed splice? -> (HsSplice Name -> RnM (a, FreeVars)) -- Outside brackets, run splice diff --git a/compiler/typecheck/TcSplice.lhs b/compiler/typecheck/TcSplice.lhs index e952a27..aebf430 100644 --- a/compiler/typecheck/TcSplice.lhs +++ b/compiler/typecheck/TcSplice.lhs @@ -523,14 +523,6 @@ tcTopSpliceExpr isTypedSplice tc_action ; zonkTopLExpr (mkHsDictLet (EvBinds const_binds) expr') } \end{code} -Note [Renamer errors] -~~~~~~~~~~~~~~~~~~~~~ -It's important to wrap renamer calls in checkNoErrs, because the -renamer does not fail for out of scope variables etc. Instead it -returns a bogus term/type, so that it can report more than one error. -We don't want the type checker to see these bogus unbound variables. - - %************************************************************************ %* * Annotations @@ -1005,12 +997,22 @@ reifyInstances th_nm th_tys <+> ppr_th th_nm <+> sep (map ppr_th th_tys)) $ do { loc <- getSrcSpanM ; rdr_ty <- cvt loc (mkThAppTs (TH.ConT th_nm) th_tys) - ; (rn_ty, _fvs) <- checkNoErrs $ rnLHsType doc rdr_ty -- Rename to HsType Name - -- checkNoErrs: see Note [Renamer errors] - ; (ty, _kind) <- tcLHsType rn_ty - ; ty <- zonkTcTypeToType emptyZonkEnv ty -- Substitute out the meta type variables - -- In particular, the type might have kind - -- variables inside it (Trac #7477) + -- #9262 says to bring vars into scope, like in HsForAllTy case + -- of rnHsTyKi + ; let (kvs, tvs) = extractHsTyRdrTyVars rdr_ty + tv_bndrs = userHsTyVarBndrs loc tvs + hs_tvbs = mkHsQTvs tv_bndrs + -- Rename to HsType Name + ; ((rn_tvbs, rn_ty), _fvs) + <- bindHsTyVars doc Nothing kvs hs_tvbs $ \ rn_tvbs -> + do { (rn_ty, fvs) <- rnLHsType doc rdr_ty + ; return ((rn_tvbs, rn_ty), fvs) } + ; (ty, _kind) <- tcHsTyVarBndrs rn_tvbs $ \ _tvs -> + tcLHsType rn_ty + ; ty <- zonkTcTypeToType emptyZonkEnv ty + -- Substitute out the meta type variables + -- In particular, the type might have kind + -- variables inside it (Trac #7477) ; traceTc "reifyInstances" (ppr ty $$ ppr (typeKind ty)) ; case splitTyConApp_maybe ty of -- This expands any type synonyms From git at git.haskell.org Sun Nov 2 03:53:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 03:53:25 +0000 (UTC) Subject: [commit: ghc] master: Annotate reified poly-kinded tycons when necessary. (#8953) (593e8b9) Message-ID: <20141102035325.EE9233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/593e8b9adc3cb6b7364bedec4e4c626eea2fcd27/ghc >--------------------------------------------------------------- commit 593e8b9adc3cb6b7364bedec4e4c626eea2fcd27 Author: Richard Eisenberg Date: Tue Oct 21 10:58:05 2014 -0400 Annotate reified poly-kinded tycons when necessary. (#8953) >--------------------------------------------------------------- 593e8b9adc3cb6b7364bedec4e4c626eea2fcd27 compiler/typecheck/TcSplice.lhs | 72 +++++++++++++++++++++++++++++++++++++++-- 1 file changed, 69 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcSplice.lhs b/compiler/typecheck/TcSplice.lhs index 99deb0f..518deee 100644 --- a/compiler/typecheck/TcSplice.lhs +++ b/compiler/typecheck/TcSplice.lhs @@ -1441,12 +1441,52 @@ reifyTyVars tvs = mapM reify_tv $ filter isTypeVar tvs kind = tyVarKind tv name = reifyName tv +\end{code} + +Note [Kind annotations on TyConApps] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +A poly-kinded tycon sometimes needs a kind annotation to be unambiguous. +For example: + + type family F a :: k + type instance F Int = (Proxy :: * -> *) + type instance F Bool = (Proxy :: (* -> *) -> *) + +It's hard to figure out where these annotations should appear, so we do this: +Suppose the tycon is applied to n arguments. We strip off the first n +arguments of the tycon's kind. If there are any variables left in the result +kind, we put on a kind annotation. But we must be slightly careful: it's +possible that the tycon's kind will have fewer than n arguments, in the case +that the concrete application instantiates a result kind variable with an +arrow kind. So, if we run out of arguments, we conservatively put on a kind +annotation anyway. This should be a rare case, indeed. Here is an example: + + data T1 :: k1 -> k2 -> * + data T2 :: k1 -> k2 -> * + + type family G (a :: k) :: k + type instance G T1 = T2 + + type instance F Char = (G T1 Bool :: (* -> *) -> *) -- F from above + +Here G's kind is (forall k. k -> k), and the desugared RHS of that last +instance of F is (G (* -> (* -> *) -> *) (T1 * (* -> *)) Bool). According to +the algoritm above, there are 3 arguments to G so we should peel off 3 +arguments in G's kind. But G's kind has only two arguments. This is the +rare special case, and we conservatively choose to put the annotation +in. + +See #8953 and test th/T8953. + +\begin{code} + reify_tc_app :: TyCon -> [TypeRep.Type] -> TcM TH.Type reify_tc_app tc tys - = do { tys' <- reifyTypes (removeKinds (tyConKind tc) tys) - ; return (mkThAppTs r_tc tys') } + = do { tys' <- reifyTypes (removeKinds tc_kind tys) + ; maybe_sig_t (mkThAppTs r_tc tys') } where - arity = tyConArity tc + arity = tyConArity tc + tc_kind = tyConKind tc r_tc | isTupleTyCon tc = if isPromotedDataCon tc then TH.PromotedTupleT arity else TH.TupleT arity @@ -1455,6 +1495,32 @@ reify_tc_app tc tys | tc `hasKey` consDataConKey = TH.PromotedConsT | tc `hasKey` eqTyConKey = TH.EqualityT | otherwise = TH.ConT (reifyName tc) + + -- See Note [Kind annotations on TyConApps] + maybe_sig_t th_type + | needs_kind_sig + = do { let full_kind = typeKind (mkTyConApp tc tys) + ; th_full_kind <- reifyKind full_kind + ; return (TH.SigT th_type th_full_kind) } + | otherwise + = return th_type + + needs_kind_sig + | Just result_ki <- peel_off_n_args tc_kind (length tys) + = not $ isEmptyVarSet $ kiVarsOfKind result_ki + | otherwise + = True + + peel_off_n_args :: Kind -> Arity -> Maybe Kind + peel_off_n_args k 0 = Just k + peel_off_n_args k n + | Just (_, res_k) <- splitForAllTy_maybe k + = peel_off_n_args res_k (n-1) + | Just (_, res_k) <- splitFunTy_maybe k + = peel_off_n_args res_k (n-1) + | otherwise + = Nothing + removeKinds :: Kind -> [TypeRep.Type] -> [TypeRep.Type] removeKinds (FunTy k1 k2) (h:t) | isSuperKind k1 = removeKinds k2 t From git at git.haskell.org Sun Nov 2 03:53:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 03:53:28 +0000 (UTC) Subject: [commit: ghc] master: Testsuite wibbles from fixing #8953 (99882ba) Message-ID: <20141102035328.816D53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/99882babf9bb2d73b972330b1cfa9495a029855b/ghc >--------------------------------------------------------------- commit 99882babf9bb2d73b972330b1cfa9495a029855b Author: Richard Eisenberg Date: Tue Oct 28 10:42:32 2014 -0400 Testsuite wibbles from fixing #8953 >--------------------------------------------------------------- 99882babf9bb2d73b972330b1cfa9495a029855b testsuite/tests/th/T1835.stdout | 2 +- testsuite/tests/th/T4188.stderr | 15 ++++++++----- testsuite/tests/th/T8499.hs | 2 +- testsuite/tests/th/T8884.stderr | 2 +- testsuite/tests/th/T9692.stderr | 2 +- testsuite/tests/th/TH_reifyDecl1.stderr | 39 +++++++++++++++++---------------- testsuite/tests/th/TH_reifyDecl2.stderr | 3 ++- 7 files changed, 35 insertions(+), 30 deletions(-) diff --git a/testsuite/tests/th/T1835.stdout b/testsuite/tests/th/T1835.stdout index ba8e65f..5b21c03 100644 --- a/testsuite/tests/th/T1835.stdout +++ b/testsuite/tests/th/T1835.stdout @@ -1,4 +1,4 @@ -class GHC.Classes.Eq a_0 => Main.MyClass a_0 +class GHC.Classes.Eq a_0 => Main.MyClass (a_0 :: *) instance Main.MyClass Main.Foo instance Main.MyClass Main.Baz instance GHC.Classes.Eq a_1 => Main.MyClass (Main.Quux a_1) diff --git a/testsuite/tests/th/T4188.stderr b/testsuite/tests/th/T4188.stderr index 02b9977..bea2e80 100644 --- a/testsuite/tests/th/T4188.stderr +++ b/testsuite/tests/th/T4188.stderr @@ -1,6 +1,9 @@ -data T4188.T1 a_0 = forall b_1 . T4188.MkT1 a_0 b_1 -data T4188.T2 a_0 - = forall b_1 . (T4188.C a_0, T4188.C b_1) => T4188.MkT2 a_0 b_1 -data T4188.T3 x_0 - = forall x_1 y_2 . (x_0 ~ (x_1, y_2), T4188.C x_1, T4188.C y_2) => - T4188.MkT3 x_1 y_2 +data T4188.T1 (a_0 :: *) = forall (b_1 :: *) . T4188.MkT1 a_0 b_1 +data T4188.T2 (a_0 :: *) + = forall (b_1 :: *) . (T4188.C a_0, T4188.C b_1) => + T4188.MkT2 a_0 b_1 +data T4188.T3 (x_0 :: *) + = forall (x_1 :: *) (y_2 :: *) . (x_0 ~ (x_1, y_2), + T4188.C x_1, + T4188.C y_2) => + T4188.MkT3 x_1 y_2 diff --git a/testsuite/tests/th/T8499.hs b/testsuite/tests/th/T8499.hs index 353bb9f..7829e99 100644 --- a/testsuite/tests/th/T8499.hs +++ b/testsuite/tests/th/T8499.hs @@ -5,7 +5,7 @@ module T8499 where import Language.Haskell.TH -$( do TyConI (DataD _ _ [PlainTV tvb_a] _ _) <- reify ''Maybe +$( do TyConI (DataD _ _ [KindedTV tvb_a _] _ _) <- reify ''Maybe my_a <- newName "a" return [TySynD (mkName "SMaybe") [KindedTV my_a (AppT (ConT ''Maybe) (VarT tvb_a))] diff --git a/testsuite/tests/th/T8884.stderr b/testsuite/tests/th/T8884.stderr index 3c45d0e..24fc15a 100644 --- a/testsuite/tests/th/T8884.stderr +++ b/testsuite/tests/th/T8884.stderr @@ -1,3 +1,3 @@ type family T8884.Foo (a_0 :: k_1) :: k_1 where T8884.Foo x_2 = x_2 type family T8884.Baz (a_0 :: k_1) :: * -type instance T8884.Baz x_0 = x_0 +type instance T8884.Baz (x_0 :: *) = x_0 diff --git a/testsuite/tests/th/T9692.stderr b/testsuite/tests/th/T9692.stderr index e62c8c5..ffa5536 100644 --- a/testsuite/tests/th/T9692.stderr +++ b/testsuite/tests/th/T9692.stderr @@ -1,2 +1,2 @@ data family T9692.F (a_0 :: k_1) (b_2 :: k_3) :: * -data instance T9692.F GHC.Types.Int x_4 = T9692.FInt x_4 +data instance T9692.F GHC.Types.Int (x_4 :: *) = T9692.FInt x_4 diff --git a/testsuite/tests/th/TH_reifyDecl1.stderr b/testsuite/tests/th/TH_reifyDecl1.stderr index 9c3b6da..bf5a819 100644 --- a/testsuite/tests/th/TH_reifyDecl1.stderr +++ b/testsuite/tests/th/TH_reifyDecl1.stderr @@ -1,35 +1,36 @@ data TH_reifyDecl1.T = TH_reifyDecl1.A | TH_reifyDecl1.B -data TH_reifyDecl1.R a_0 = TH_reifyDecl1.C a_0 | TH_reifyDecl1.D -data TH_reifyDecl1.List a_0 +data TH_reifyDecl1.R (a_0 :: *) + = TH_reifyDecl1.C a_0 | TH_reifyDecl1.D +data TH_reifyDecl1.List (a_0 :: *) = TH_reifyDecl1.Nil | TH_reifyDecl1.Cons a_0 (TH_reifyDecl1.List a_0) -data TH_reifyDecl1.Tree a_0 +data TH_reifyDecl1.Tree (a_0 :: *) = TH_reifyDecl1.Leaf | (TH_reifyDecl1.Tree a_0) TH_reifyDecl1.:+: (TH_reifyDecl1.Tree a_0) type TH_reifyDecl1.IntList = [GHC.Types.Int] newtype TH_reifyDecl1.Length = TH_reifyDecl1.Length GHC.Types.Int -Constructor from TH_reifyDecl1.Tree: TH_reifyDecl1.Leaf :: forall a_0 . TH_reifyDecl1.Tree a_0 -Class op from TH_reifyDecl1.C1: TH_reifyDecl1.m1 :: forall a_0 . TH_reifyDecl1.C1 a_0 => - a_0 -> GHC.Types.Int +Constructor from TH_reifyDecl1.Tree: TH_reifyDecl1.Leaf :: forall (a_0 :: *) . TH_reifyDecl1.Tree a_0 +Class op from TH_reifyDecl1.C1: TH_reifyDecl1.m1 :: forall (a_0 :: *) . TH_reifyDecl1.C1 a_0 => + a_0 -> GHC.Types.Int infixl 3 TH_reifyDecl1.m1 -class TH_reifyDecl1.C1 a_0 - where TH_reifyDecl1.m1 :: forall a_0 . TH_reifyDecl1.C1 a_0 => - a_0 -> GHC.Types.Int -class TH_reifyDecl1.C2 a_0 - where TH_reifyDecl1.m2 :: forall a_0 . TH_reifyDecl1.C2 a_0 => - a_0 -> GHC.Types.Int +class TH_reifyDecl1.C1 (a_0 :: *) + where TH_reifyDecl1.m1 :: forall (a_0 :: *) . TH_reifyDecl1.C1 a_0 => + a_0 -> GHC.Types.Int +class TH_reifyDecl1.C2 (a_0 :: *) + where TH_reifyDecl1.m2 :: forall (a_0 :: *) . TH_reifyDecl1.C2 a_0 => + a_0 -> GHC.Types.Int instance TH_reifyDecl1.C2 GHC.Types.Int -class TH_reifyDecl1.C3 a_0 +class TH_reifyDecl1.C3 (a_0 :: *) instance TH_reifyDecl1.C3 GHC.Types.Int -type family TH_reifyDecl1.AT1 a_0 :: * +type family TH_reifyDecl1.AT1 (a_0 :: *) :: * type instance TH_reifyDecl1.AT1 GHC.Types.Int = GHC.Types.Bool -data family TH_reifyDecl1.AT2 a_0 :: * +data family TH_reifyDecl1.AT2 (a_0 :: *) :: * data instance TH_reifyDecl1.AT2 GHC.Types.Int = TH_reifyDecl1.AT2Int -type family TH_reifyDecl1.TF1 a_0 :: * -type family TH_reifyDecl1.TF2 a_0 :: * +type family TH_reifyDecl1.TF1 (a_0 :: *) :: * +type family TH_reifyDecl1.TF2 (a_0 :: *) :: * type instance TH_reifyDecl1.TF2 GHC.Types.Bool = GHC.Types.Bool -data family TH_reifyDecl1.DF1 a_0 :: * -data family TH_reifyDecl1.DF2 a_0 :: * +data family TH_reifyDecl1.DF1 (a_0 :: *) :: * +data family TH_reifyDecl1.DF2 (a_0 :: *) :: * data instance TH_reifyDecl1.DF2 GHC.Types.Bool = TH_reifyDecl1.DBool diff --git a/testsuite/tests/th/TH_reifyDecl2.stderr b/testsuite/tests/th/TH_reifyDecl2.stderr index 3711f8e..64436f8 100644 --- a/testsuite/tests/th/TH_reifyDecl2.stderr +++ b/testsuite/tests/th/TH_reifyDecl2.stderr @@ -1 +1,2 @@ -data GHC.Base.Maybe a_0 = GHC.Base.Nothing | GHC.Base.Just a_0 +data GHC.Base.Maybe (a_0 :: *) + = GHC.Base.Nothing | GHC.Base.Just a_0 From git at git.haskell.org Sun Nov 2 03:53:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 03:53:31 +0000 (UTC) Subject: [commit: ghc] master: Annotate poly-kinded type patterns in instance reification. (c3ecf06) Message-ID: <20141102035331.29C1F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c3ecf06018ee3d97a6536de57519af865976ce04/ghc >--------------------------------------------------------------- commit c3ecf06018ee3d97a6536de57519af865976ce04 Author: Richard Eisenberg Date: Tue Oct 21 11:27:16 2014 -0400 Annotate poly-kinded type patterns in instance reification. This should fix #8953. >--------------------------------------------------------------- c3ecf06018ee3d97a6536de57519af865976ce04 compiler/typecheck/TcSplice.lhs | 91 ++++++++++++++++++++++++++++++++--------- testsuite/tests/th/T5358.stderr | 2 +- 2 files changed, 73 insertions(+), 20 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c3ecf06018ee3d97a6536de57519af865976ce04 From git at git.haskell.org Sun Nov 2 03:53:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 03:53:33 +0000 (UTC) Subject: [commit: ghc] master: Always use KindedTV when reifying. (#8953) (9fd19f9) Message-ID: <20141102035333.B398A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9fd19f960f37b1369f8a3453b05c1805e0057232/ghc >--------------------------------------------------------------- commit 9fd19f960f37b1369f8a3453b05c1805e0057232 Author: Richard Eisenberg Date: Tue Oct 21 10:48:49 2014 -0400 Always use KindedTV when reifying. (#8953) >--------------------------------------------------------------- 9fd19f960f37b1369f8a3453b05c1805e0057232 compiler/typecheck/TcSplice.lhs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcSplice.lhs b/compiler/typecheck/TcSplice.lhs index aebf430..99deb0f 100644 --- a/compiler/typecheck/TcSplice.lhs +++ b/compiler/typecheck/TcSplice.lhs @@ -1433,9 +1433,10 @@ reifyTyVars :: [TyVar] -> TcM [TH.TyVarBndr] reifyTyVars tvs = mapM reify_tv $ filter isTypeVar tvs where - reify_tv tv | isLiftedTypeKind kind = return (TH.PlainTV name) - | otherwise = do kind' <- reifyKind kind - return (TH.KindedTV name kind') + -- even if the kind is *, we need to include a kind annotation, + -- in case a poly-kind would be inferred without the annotation. + -- See #8953 or test th/T8953 + reify_tv tv = TH.KindedTV name <$> reifyKind kind where kind = tyVarKind tv name = reifyName tv From git at git.haskell.org Sun Nov 2 03:53:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 03:53:36 +0000 (UTC) Subject: [commit: ghc] master: Test #8953 in th/T8953 (b174288) Message-ID: <20141102035336.87CA43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b174288b15300093a4356c853ce2ea0abb4876f5/ghc >--------------------------------------------------------------- commit b174288b15300093a4356c853ce2ea0abb4876f5 Author: Richard Eisenberg Date: Tue Oct 21 10:46:27 2014 -0400 Test #8953 in th/T8953 >--------------------------------------------------------------- b174288b15300093a4356c853ce2ea0abb4876f5 testsuite/tests/th/T8953.hs | 39 +++++++++++++++++++++++++++++++++++++++ testsuite/tests/th/T8953.stderr | 19 +++++++++++++++++++ testsuite/tests/th/all.T | 1 + 3 files changed, 59 insertions(+) diff --git a/testsuite/tests/th/T8953.hs b/testsuite/tests/th/T8953.hs new file mode 100644 index 0000000..ba5833d --- /dev/null +++ b/testsuite/tests/th/T8953.hs @@ -0,0 +1,39 @@ +{-# LANGUAGE DataKinds, PolyKinds, TypeFamilies, TemplateHaskell, + FlexibleInstances, UndecidableInstances #-} + +module T8953 where + +import Data.Proxy +import Language.Haskell.TH +import System.IO + +type family Poly (a :: k) :: * +type instance Poly (x :: Bool) = Int +type instance Poly (x :: Maybe k) = Double + +type family Silly :: k -> * +type instance Silly = (Proxy :: * -> *) +type instance Silly = (Proxy :: (* -> *) -> *) + +a :: Proxy (Proxy :: * -> *) +b :: Proxy (Proxy :: (* -> *) -> *) +a = undefined +b = undefined + +type StarProxy (a :: *) = Proxy a + +class PC (a :: k) +instance PC (a :: *) +instance PC (Proxy :: (k -> *) -> *) + +data T1 :: k1 -> k2 -> * +data T2 :: k1 -> k2 -> * +type family F a :: k +type family G (a :: k) :: k +type instance G T1 = T2 +type instance F Char = (G T1 Bool :: (* -> *) -> *) + +$( do infos <- mapM reify [''Poly, ''Silly, 'a, 'b, ''StarProxy, ''PC, ''F, ''G] + runIO $ mapM (putStrLn . pprint) infos + runIO $ hFlush stdout + return [] ) diff --git a/testsuite/tests/th/T8953.stderr b/testsuite/tests/th/T8953.stderr new file mode 100644 index 0000000..14db2b7 --- /dev/null +++ b/testsuite/tests/th/T8953.stderr @@ -0,0 +1,19 @@ +type family T8953.Poly (a_0 :: k_1) :: * +type instance T8953.Poly (x_2 :: GHC.Types.Bool) = GHC.Types.Int +type instance T8953.Poly (x_3 :: GHC.Base.Maybe k_4) = GHC.Types.Double +type family T8953.Silly :: k_0 -> * +type instance T8953.Silly = Data.Proxy.Proxy :: * -> * +type instance T8953.Silly = Data.Proxy.Proxy :: (* -> *) -> * +T8953.a :: Data.Proxy.Proxy (Data.Proxy.Proxy :: * -> *) +T8953.b :: Data.Proxy.Proxy (Data.Proxy.Proxy :: (* -> *) -> *) +type T8953.StarProxy (a_0 :: *) = Data.Proxy.Proxy a_0 +class T8953.PC (a_0 :: k_1) +instance T8953.PC (a_2 :: *) +instance T8953.PC (Data.Proxy.Proxy :: (k_3 -> *) -> *) +type family T8953.F (a_0 :: *) :: k_1 +type instance T8953.F GHC.Types.Char = T8953.G (T8953.T1 :: * -> + (* -> *) -> *) + GHC.Types.Bool :: (* -> *) -> * +type family T8953.G (a_0 :: k_1) :: k_1 +type instance T8953.G (T8953.T1 :: k_2 -> + k1_3 -> *) = T8953.T2 :: k_2 -> k1_3 -> * diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index d3ae4e4..28ae4fb 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -332,3 +332,4 @@ test('T7241', normal, compile_fail, ['-v0']) test('T9262', normal, compile, ['-v0']) test('T9199', normal, compile, ['-v0']) test('T9692', normal, compile, ['-v0']) +test('T8953', normal, compile, ['-v0']) From git at git.haskell.org Sun Nov 2 03:53:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 03:53:39 +0000 (UTC) Subject: [commit: ghc] master: Fix #9084 by calling notHandled when unknown bits are enountered. (03d61cc) Message-ID: <20141102035339.1EF2A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/03d61cce4d92a37a193cc1211eb7262149f22e3b/ghc >--------------------------------------------------------------- commit 03d61cce4d92a37a193cc1211eb7262149f22e3b Author: Richard Eisenberg Date: Tue Oct 28 13:21:34 2014 -0400 Fix #9084 by calling notHandled when unknown bits are enountered. >--------------------------------------------------------------- 03d61cce4d92a37a193cc1211eb7262149f22e3b compiler/deSugar/DsMeta.hs | 79 +++++++++++++++++++++++++++++++++++----------- 1 file changed, 60 insertions(+), 19 deletions(-) diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs index 28e6fef..186b74c 100644 --- a/compiler/deSugar/DsMeta.hs +++ b/compiler/deSugar/DsMeta.hs @@ -112,8 +112,20 @@ repTopP pat = do { ss <- mkGenSyms (collectPatBinders pat) ; wrapGenSyms ss pat' } repTopDs :: HsGroup Name -> DsM (Core (TH.Q [TH.Dec])) -repTopDs group - = do { let { tv_bndrs = hsSigTvBinders (hs_valds group) +repTopDs group@(HsGroup { hs_valds = valds + , hs_splcds = splcds + , hs_tyclds = tyclds + , hs_instds = instds + , hs_derivds = derivds + , hs_fixds = fixds + , hs_defds = defds + , hs_fords = fords + , hs_warnds = warnds + , hs_annds = annds + , hs_ruleds = ruleds + , hs_vects = vects + , hs_docs = docs }) + = do { let { tv_bndrs = hsSigTvBinders valds ; bndrs = tv_bndrs ++ hsGroupBinders group } ; ss <- mkGenSyms bndrs ; @@ -124,16 +136,24 @@ repTopDs group -- The other important reason is that the output must mention -- only "T", not "Foo:T" where Foo is the current module - decls <- addBinds ss (do { - fix_ds <- mapM repFixD (hs_fixds group) ; - val_ds <- rep_val_binds (hs_valds group) ; - tycl_ds <- mapM repTyClD (tyClGroupConcat (hs_tyclds group)) ; - role_ds <- mapM repRoleD (concatMap group_roles (hs_tyclds group)) ; - inst_ds <- mapM repInstD (hs_instds group) ; - rule_ds <- mapM repRuleD (hs_ruleds group) ; - for_ds <- mapM repForD (hs_fords group) ; + decls <- addBinds ss ( + do { val_ds <- rep_val_binds valds + ; _ <- mapM no_splice splcds + ; tycl_ds <- mapM repTyClD (tyClGroupConcat tyclds) + ; role_ds <- mapM repRoleD (concatMap group_roles tyclds) + ; inst_ds <- mapM repInstD instds + ; _ <- mapM no_standalone_deriv derivds + ; fix_ds <- mapM repFixD fixds + ; _ <- mapM no_default_decl defds + ; for_ds <- mapM repForD fords + ; _ <- mapM no_warn warnds + ; _ <- mapM no_ann annds + ; rule_ds <- mapM repRuleD ruleds + ; _ <- mapM no_vect vects + ; _ <- mapM no_doc docs + -- more needed - return (de_loc $ sort_by_loc $ + ; return (de_loc $ sort_by_loc $ val_ds ++ catMaybes tycl_ds ++ role_ds ++ fix_ds ++ inst_ds ++ rule_ds ++ for_ds) }) ; @@ -145,7 +165,22 @@ repTopDs group wrapGenSyms ss q_decs } - + where + no_splice (L loc _) + = notHandledL loc "Splices within declaration brackets" empty + no_standalone_deriv (L loc (DerivDecl { deriv_type = deriv_ty })) + = notHandledL loc "Standalone-deriving" (ppr deriv_ty) + no_default_decl (L loc decl) + = notHandledL loc "Default declarations" (ppr decl) + no_warn (L loc (Warning thing _)) + = notHandledL loc "WARNING and DEPRECATION pragmas" $ + text "Pragma for declaration of" <+> ppr thing + no_ann (L loc decl) + = notHandledL loc "ANN pragmas" (ppr decl) + no_vect (L loc decl) + = notHandledL loc "Vectorisation pragmas" (ppr decl) + no_doc (L loc _) + = notHandledL loc "Haddock documentation" empty hsSigTvBinders :: HsValBinds Name -> [Name] -- See Note [Scoped type variables in bindings] @@ -611,17 +646,16 @@ rep_sigs' sigs = do { sigs1 <- mapM rep_sig sigs ; return (concat sigs1) } rep_sig :: LSig Name -> DsM [(SrcSpan, Core TH.DecQ)] - -- Singleton => Ok - -- Empty => Too hard, signature ignored rep_sig (L loc (TypeSig nms ty)) = mapM (rep_ty_sig loc ty) nms -rep_sig (L _ (GenericSig nm _)) = failWithDs msg - where msg = vcat [ ptext (sLit "Illegal default signature for") <+> quotes (ppr nm) - , ptext (sLit "Default signatures are not supported by Template Haskell") ] - +rep_sig (L _ (PatSynSig {})) = notHandled "Pattern type signatures" empty +rep_sig (L _ (GenericSig nm _)) = notHandled "Default type signatures" msg + where msg = text "Illegal default signature for" <+> quotes (ppr nm) +rep_sig d@(L _ (IdSig {})) = pprPanic "rep_sig IdSig" (ppr d) +rep_sig (L _ (FixSig {})) = return [] -- fixity sigs at top level rep_sig (L loc (InlineSig nm ispec)) = rep_inline nm ispec loc rep_sig (L loc (SpecSig nm ty ispec)) = rep_specialise nm ty ispec loc rep_sig (L loc (SpecInstSig ty)) = rep_specialiseInst ty loc -rep_sig _ = return [] +rep_sig (L _ (MinimalSig {})) = notHandled "MINIMAL pragmas" empty rep_ty_sig :: SrcSpan -> LHsType Name -> Located Name -> DsM (SrcSpan, Core TH.DecQ) @@ -1984,6 +2018,13 @@ coreVar :: Id -> Core TH.Name -- The Id has type Name coreVar id = MkC (Var id) ----------------- Failure ----------------------- +notHandledL :: SrcSpan -> String -> SDoc -> DsM a +notHandledL loc what doc + | isGoodSrcSpan loc + = putSrcSpanDs loc $ notHandled what doc + | otherwise + = notHandled what doc + notHandled :: String -> SDoc -> DsM a notHandled what doc = failWithDs msg where From git at git.haskell.org Sun Nov 2 03:53:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 03:53:41 +0000 (UTC) Subject: [commit: ghc] master: Fix testsuite output from #9084. (17265c0) Message-ID: <20141102035341.A737E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/17265c033707a84fd59fec61b3a370c3a427ffa3/ghc >--------------------------------------------------------------- commit 17265c033707a84fd59fec61b3a370c3a427ffa3 Author: Richard Eisenberg Date: Tue Oct 28 15:15:02 2014 -0400 Fix testsuite output from #9084. >--------------------------------------------------------------- 17265c033707a84fd59fec61b3a370c3a427ffa3 testsuite/tests/th/TH_dataD1.stderr | 3 +++ testsuite/tests/th/all.T | 2 +- 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/th/TH_dataD1.stderr b/testsuite/tests/th/TH_dataD1.stderr index e69de29..51ae5b9 100644 --- a/testsuite/tests/th/TH_dataD1.stderr +++ b/testsuite/tests/th/TH_dataD1.stderr @@ -0,0 +1,3 @@ + +TH_dataD1.hs:7:6: + Splices within declaration brackets not (yet) handled by Template Haskell diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index d6aaa84..3c108a7 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -120,7 +120,7 @@ test('TH_dupdecl', normal, compile_fail, ['-v0']) test('TH_exn2', normal, compile_fail, ['-v0']) test('TH_recover', normal, compile_and_run, ['']) -test('TH_dataD1', normal, compile, ['-v0']) +test('TH_dataD1', normal, compile_fail, ['-v0']) test('TH_ppr1', normal, compile_and_run, ['']) From git at git.haskell.org Sun Nov 2 03:53:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 03:53:44 +0000 (UTC) Subject: [commit: ghc] master: Test #9084 in th/T9084. (862772b) Message-ID: <20141102035344.BED4D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/862772b7ecfce977ffe7090659da3bd923ef946a/ghc >--------------------------------------------------------------- commit 862772b7ecfce977ffe7090659da3bd923ef946a Author: Richard Eisenberg Date: Tue Oct 28 13:10:11 2014 -0400 Test #9084 in th/T9084. The patch includes errors for a whole host of pragmas. But, these are generated one at a time, and it doesn't seem like a good idea to add gobs of test-cases here. >--------------------------------------------------------------- 862772b7ecfce977ffe7090659da3bd923ef946a testsuite/tests/th/T9084.hs | 10 ++++++++++ testsuite/tests/th/T9084.stderr | 2 ++ testsuite/tests/th/all.T | 1 + 3 files changed, 13 insertions(+) diff --git a/testsuite/tests/th/T9084.hs b/testsuite/tests/th/T9084.hs new file mode 100644 index 0000000..6b1fe0d --- /dev/null +++ b/testsuite/tests/th/T9084.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T9084 where + +$([d| + class C a where + meth :: a -> a + meth = undefined -- give a (silly) default + {-# MINIMAL meth #-} + |]) diff --git a/testsuite/tests/th/T9084.stderr b/testsuite/tests/th/T9084.stderr new file mode 100644 index 0000000..ad90d1b --- /dev/null +++ b/testsuite/tests/th/T9084.stderr @@ -0,0 +1,2 @@ + +T9084.hs:5:3: MINIMAL pragmas not (yet) handled by Template Haskell diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 28ae4fb..d6aaa84 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -333,3 +333,4 @@ test('T9262', normal, compile, ['-v0']) test('T9199', normal, compile, ['-v0']) test('T9692', normal, compile, ['-v0']) test('T8953', normal, compile, ['-v0']) +test('T9084', normal, compile_fail, ['-v0']) From git at git.haskell.org Sun Nov 2 03:53:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 03:53:47 +0000 (UTC) Subject: [commit: ghc] master: Test #9738 in th/T9738 (752b5e2) Message-ID: <20141102035347.D07BA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/752b5e216963c0e8c06aa382b695ce2215869632/ghc >--------------------------------------------------------------- commit 752b5e216963c0e8c06aa382b695ce2215869632 Author: Richard Eisenberg Date: Tue Oct 28 14:53:59 2014 -0400 Test #9738 in th/T9738 >--------------------------------------------------------------- 752b5e216963c0e8c06aa382b695ce2215869632 testsuite/tests/th/T9738.hs | 16 ++++++++++++++++ testsuite/tests/th/T9738.stderr | 1 + testsuite/tests/th/all.T | 1 + 3 files changed, 18 insertions(+) diff --git a/testsuite/tests/th/T9738.hs b/testsuite/tests/th/T9738.hs new file mode 100644 index 0000000..7c5f020 --- /dev/null +++ b/testsuite/tests/th/T9738.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T9738 where + +import System.IO +import Language.Haskell.TH + +data Foo = MkFoo + +$( do decs <- [d| {-# ANN type Foo "hi" #-} + {-# ANN MkFoo "there" #-} + {-# ANN module "Charley" #-} + |] + runIO $ print decs + runIO $ hFlush stdout + return [] ) diff --git a/testsuite/tests/th/T9738.stderr b/testsuite/tests/th/T9738.stderr new file mode 100644 index 0000000..e4b97cb --- /dev/null +++ b/testsuite/tests/th/T9738.stderr @@ -0,0 +1 @@ +[PragmaD (AnnP (TypeAnnotation T9738.Foo) (LitE (StringL "hi"))),PragmaD (AnnP (ValueAnnotation T9738.MkFoo) (LitE (StringL "there"))),PragmaD (AnnP ModuleAnnotation (LitE (StringL "Charley")))] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 3c108a7..4409571 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -334,3 +334,4 @@ test('T9199', normal, compile, ['-v0']) test('T9692', normal, compile, ['-v0']) test('T8953', normal, compile, ['-v0']) test('T9084', normal, compile_fail, ['-v0']) +test('T9738', normal, compile, ['-v0']) From git at git.haskell.org Sun Nov 2 03:53:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 03:53:50 +0000 (UTC) Subject: [commit: ghc] master: Fix #9738, by handling {-# ANN ... #-} in DsMeta. (209baea) Message-ID: <20141102035350.6EB583A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/209baea8bc1f99b371b9ba49f5b81caa45bb34bf/ghc >--------------------------------------------------------------- commit 209baea8bc1f99b371b9ba49f5b81caa45bb34bf Author: Richard Eisenberg Date: Tue Oct 28 14:54:20 2014 -0400 Fix #9738, by handling {-# ANN ... #-} in DsMeta. >--------------------------------------------------------------- 209baea8bc1f99b371b9ba49f5b81caa45bb34bf compiler/deSugar/DsMeta.hs | 76 ++++++++++++++++------ .../template-haskell/Language/Haskell/TH/Lib.hs | 11 ++++ 2 files changed, 67 insertions(+), 20 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 209baea8bc1f99b371b9ba49f5b81caa45bb34bf From git at git.haskell.org Sun Nov 2 04:09:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 04:09:32 +0000 (UTC) Subject: [commit: ghc] master: Update release notes for #9262 #8953 #9084. (18a4a5d) Message-ID: <20141102040932.CF5E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/18a4a5dad3cbee3c8bb4005ec09edf401ebe294c/ghc >--------------------------------------------------------------- commit 18a4a5dad3cbee3c8bb4005ec09edf401ebe294c Author: Richard Eisenberg Date: Sun Nov 2 00:08:26 2014 -0400 Update release notes for #9262 #8953 #9084. >--------------------------------------------------------------- 18a4a5dad3cbee3c8bb4005ec09edf401ebe294c docs/users_guide/7.10.1-notes.xml | 28 ++++++++++++++++++++++++++++ 1 file changed, 28 insertions(+) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index fa7ad1a..95f581b 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -110,6 +110,34 @@ Added support for generating LINE pragma declarations (). + + + The type Pred (which stores a type + constraint) is now a synonym for Type, + in order to work with the ConstraintKinds + extension. This is a breaking change and may require + some rewriting of Template Haskell code. + + + + reifyInstances now treats unbound type + variables as univerally quantified, allowing lookup of, say, + the instance for Eq [a]. + + + + More kind annotations appear in reified types, in order to + disambiguate types that would otherwise be ambiguous in the + presence of PolyKinds. In particular, all + reified TyVarBndrs are now + KindedTVs. (This does not affect Template + Haskell quotations, just calls to reify.) + + + + Various features unsupported in quotations were previously + silently ignored. These now cause errors. + From git at git.haskell.org Sun Nov 2 06:07:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:07:57 +0000 (UTC) Subject: [commit: ghc] wip/T9705: Tweak the error message for pattern synonym methods, since they are disallowed both in class and instance declarations (ff3cc2f) Message-ID: <20141102060757.5026F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9705 Link : http://ghc.haskell.org/trac/ghc/changeset/ff3cc2f12181070702485321975ce00f38add96d/ghc >--------------------------------------------------------------- commit ff3cc2f12181070702485321975ce00f38add96d Author: Dr. ERDI Gergo Date: Sun Nov 2 14:06:24 2014 +0800 Tweak the error message for pattern synonym methods, since they are disallowed both in class and instance declarations >--------------------------------------------------------------- ff3cc2f12181070702485321975ce00f38add96d compiler/rename/RnBinds.lhs | 2 +- testsuite/tests/patsyn/should_fail/{T9705.hs => T9705-1.hs} | 0 testsuite/tests/patsyn/should_fail/T9705-1.stderr | 4 ++++ testsuite/tests/patsyn/should_fail/{T9705.hs => T9705-2.hs} | 3 +++ testsuite/tests/patsyn/should_fail/T9705-2.stderr | 4 ++++ testsuite/tests/patsyn/should_fail/T9705.stderr | 4 ---- testsuite/tests/patsyn/should_fail/all.T | 3 ++- 7 files changed, 14 insertions(+), 6 deletions(-) diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index 555d833..c2489cb 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -1068,7 +1068,7 @@ methodBindErr mbind methodPatSynErr :: HsBindLR RdrName RdrName -> SDoc methodPatSynErr mbind - = hang (ptext (sLit "Pattern synonyms not allowed in instance declarations")) + = hang (ptext (sLit "Pattern synonyms not allowed in class/instance declarations")) 2 (ppr mbind) bindsInHsBootFile :: LHsBindsLR Name RdrName -> SDoc diff --git a/testsuite/tests/patsyn/should_fail/T9705.hs b/testsuite/tests/patsyn/should_fail/T9705-1.hs similarity index 100% copy from testsuite/tests/patsyn/should_fail/T9705.hs copy to testsuite/tests/patsyn/should_fail/T9705-1.hs diff --git a/testsuite/tests/patsyn/should_fail/T9705-1.stderr b/testsuite/tests/patsyn/should_fail/T9705-1.stderr new file mode 100644 index 0000000..abe4fe6 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/T9705-1.stderr @@ -0,0 +1,4 @@ + +T9705-1.hs:3:5: + Pattern synonyms not allowed in class/instance declarations + pattern P = () diff --git a/testsuite/tests/patsyn/should_fail/T9705.hs b/testsuite/tests/patsyn/should_fail/T9705-2.hs similarity index 64% rename from testsuite/tests/patsyn/should_fail/T9705.hs rename to testsuite/tests/patsyn/should_fail/T9705-2.hs index 54d1d00..463c94b 100644 --- a/testsuite/tests/patsyn/should_fail/T9705.hs +++ b/testsuite/tests/patsyn/should_fail/T9705-2.hs @@ -1,3 +1,6 @@ {-# LANGUAGE PatternSynonyms #-} class C a where + method :: a + +instance C Int where pattern P = () diff --git a/testsuite/tests/patsyn/should_fail/T9705-2.stderr b/testsuite/tests/patsyn/should_fail/T9705-2.stderr new file mode 100644 index 0000000..23f85fa --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/T9705-2.stderr @@ -0,0 +1,4 @@ + +T9705-2.hs:6:5: + Pattern synonyms not allowed in class/instance declarations + pattern P = () diff --git a/testsuite/tests/patsyn/should_fail/T9705.stderr b/testsuite/tests/patsyn/should_fail/T9705.stderr deleted file mode 100644 index d9a3a49..0000000 --- a/testsuite/tests/patsyn/should_fail/T9705.stderr +++ /dev/null @@ -1,4 +0,0 @@ - -T9705.hs:3:5: - Pattern synonyms not allowed in instance declarations - pattern P = () diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index 298f23b..ea671dc 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -6,4 +6,5 @@ test('T8961', normal, multimod_compile_fail, ['T8961','']) test('as-pattern', normal, compile_fail, ['']) test('T9161-1', normal, compile_fail, ['']) test('T9161-2', normal, compile_fail, ['']) -test('T9705', normal, compile_fail, ['']) +test('T9705-1', normal, compile_fail, ['']) +test('T9705-2', normal, compile_fail, ['']) From git at git.haskell.org Sun Nov 2 06:11:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:11:54 +0000 (UTC) Subject: [commit: ghc] master: Tweak the error message for pattern synonym methods, since they are disallowed both in class and instance declarations (96c22d9) Message-ID: <20141102061154.072AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/96c22d9e3591d49a9435e7961563ccd55c0bec0f/ghc >--------------------------------------------------------------- commit 96c22d9e3591d49a9435e7961563ccd55c0bec0f Author: Dr. ERDI Gergo Date: Sun Nov 2 14:06:24 2014 +0800 Tweak the error message for pattern synonym methods, since they are disallowed both in class and instance declarations >--------------------------------------------------------------- 96c22d9e3591d49a9435e7961563ccd55c0bec0f compiler/rename/RnBinds.lhs | 2 +- testsuite/tests/patsyn/should_fail/{T9705.hs => T9705-1.hs} | 0 testsuite/tests/patsyn/should_fail/T9705-1.stderr | 4 ++++ testsuite/tests/patsyn/should_fail/{T9705.hs => T9705-2.hs} | 3 +++ testsuite/tests/patsyn/should_fail/T9705-2.stderr | 4 ++++ testsuite/tests/patsyn/should_fail/T9705.stderr | 4 ---- testsuite/tests/patsyn/should_fail/all.T | 3 ++- 7 files changed, 14 insertions(+), 6 deletions(-) diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index 555d833..c2489cb 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -1068,7 +1068,7 @@ methodBindErr mbind methodPatSynErr :: HsBindLR RdrName RdrName -> SDoc methodPatSynErr mbind - = hang (ptext (sLit "Pattern synonyms not allowed in instance declarations")) + = hang (ptext (sLit "Pattern synonyms not allowed in class/instance declarations")) 2 (ppr mbind) bindsInHsBootFile :: LHsBindsLR Name RdrName -> SDoc diff --git a/testsuite/tests/patsyn/should_fail/T9705.hs b/testsuite/tests/patsyn/should_fail/T9705-1.hs similarity index 100% copy from testsuite/tests/patsyn/should_fail/T9705.hs copy to testsuite/tests/patsyn/should_fail/T9705-1.hs diff --git a/testsuite/tests/patsyn/should_fail/T9705-1.stderr b/testsuite/tests/patsyn/should_fail/T9705-1.stderr new file mode 100644 index 0000000..abe4fe6 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/T9705-1.stderr @@ -0,0 +1,4 @@ + +T9705-1.hs:3:5: + Pattern synonyms not allowed in class/instance declarations + pattern P = () diff --git a/testsuite/tests/patsyn/should_fail/T9705.hs b/testsuite/tests/patsyn/should_fail/T9705-2.hs similarity index 64% rename from testsuite/tests/patsyn/should_fail/T9705.hs rename to testsuite/tests/patsyn/should_fail/T9705-2.hs index 54d1d00..463c94b 100644 --- a/testsuite/tests/patsyn/should_fail/T9705.hs +++ b/testsuite/tests/patsyn/should_fail/T9705-2.hs @@ -1,3 +1,6 @@ {-# LANGUAGE PatternSynonyms #-} class C a where + method :: a + +instance C Int where pattern P = () diff --git a/testsuite/tests/patsyn/should_fail/T9705-2.stderr b/testsuite/tests/patsyn/should_fail/T9705-2.stderr new file mode 100644 index 0000000..23f85fa --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/T9705-2.stderr @@ -0,0 +1,4 @@ + +T9705-2.hs:6:5: + Pattern synonyms not allowed in class/instance declarations + pattern P = () diff --git a/testsuite/tests/patsyn/should_fail/T9705.stderr b/testsuite/tests/patsyn/should_fail/T9705.stderr deleted file mode 100644 index d9a3a49..0000000 --- a/testsuite/tests/patsyn/should_fail/T9705.stderr +++ /dev/null @@ -1,4 +0,0 @@ - -T9705.hs:3:5: - Pattern synonyms not allowed in instance declarations - pattern P = () diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index 298f23b..ea671dc 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -6,4 +6,5 @@ test('T8961', normal, multimod_compile_fail, ['T8961','']) test('as-pattern', normal, compile_fail, ['']) test('T9161-1', normal, compile_fail, ['']) test('T9161-2', normal, compile_fail, ['']) -test('T9705', normal, compile_fail, ['']) +test('T9705-1', normal, compile_fail, ['']) +test('T9705-2', normal, compile_fail, ['']) From git at git.haskell.org Sun Nov 2 06:16:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:16:01 +0000 (UTC) Subject: [commit: ghc] wip/T9732: In pattern synonym matchers, support unboxed continuation results. (0f7fa84) Message-ID: <20141102061601.DE8303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/0f7fa84b909d2577b2d4ab04f90432321d72028c/ghc >--------------------------------------------------------------- commit 0f7fa84b909d2577b2d4ab04f90432321d72028c Author: Dr. ERDI Gergo Date: Sat Nov 1 11:10:56 2014 +0800 In pattern synonym matchers, support unboxed continuation results. This requires ensuring the continuations have arguments by adding a dummy Void# argument when needed. This is so that matching on a pattern synonym is lazy even when the result is unboxed, e.g. pattern P = () f P = 0# In this case, without dummy arguments, the generated matcher's type would be $mP :: forall (r :: ?). () -> r -> r -> r which is called in `f` at type `() -> Int# -> Int# -> Int#`, so it would be strict, in particular, in the failure continuation of `patError`. We work around this by making sure both continuations have arguments: $mP :: forall (r :: ?). () -> (Void# -> r) -> (Void# -> r) -> r Of course, if `P` (and thus, the success continuation) has any arguments, we are only adding the extra dummy argument to the failure continuation. >--------------------------------------------------------------- 0f7fa84b909d2577b2d4ab04f90432321d72028c compiler/deSugar/DsUtils.lhs | 4 +++- compiler/typecheck/TcPatSyn.lhs | 19 ++++++++++++------- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_run/all.T | 1 + testsuite/tests/patsyn/should_run/match-unboxed.hs | 21 +++++++++++++++++++++ .../should_run/match-unboxed.stdout} | 2 ++ 6 files changed, 40 insertions(+), 8 deletions(-) diff --git a/compiler/deSugar/DsUtils.lhs b/compiler/deSugar/DsUtils.lhs index a269374..7e6ac43 100644 --- a/compiler/deSugar/DsUtils.lhs +++ b/compiler/deSugar/DsUtils.lhs @@ -348,13 +348,15 @@ mkPatSynCase var ty alt fail = do matcher <- dsLExpr $ mkLHsWrap wrapper $ nlHsTyApp matcher [ty] let MatchResult _ mkCont = match_result cont <- mkCoreLams bndrs <$> mkCont fail - return $ mkCoreAppsDs matcher [Var var, cont, fail] + return $ mkCoreAppsDs matcher [Var var, ensure_unstrict cont, make_unstrict fail] where MkCaseAlt{ alt_pat = psyn, alt_bndrs = bndrs, alt_wrapper = wrapper, alt_result = match_result} = alt matcher = patSynMatcher psyn + ensure_unstrict = if null bndrs then make_unstrict else id + make_unstrict = Lam voidArgId mkDataConCase :: Id -> Type -> [CaseAlt DataCon] -> MatchResult mkDataConCase _ _ [] = panic "mkDataConCase: no alternatives" diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 9b2b511..633abe2 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -30,6 +30,7 @@ import BasicTypes import TcSimplify import TcType import VarSet +import MkId #if __GLASGOW_HASKELL__ < 709 import Data.Monoid #endif @@ -124,13 +125,18 @@ tcPatSynMatcher :: Located Name -> TcM (Id, LHsBinds Id) -- See Note [Matchers and wrappers for pattern synonyms] in PatSyn tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_dicts prov_theta req_theta pat_ty - = do { res_tv <- zonkQuantifiedTyVar =<< newFlexiTyVar liftedTypeKind + = do { res_tv <- zonkQuantifiedTyVar =<< newFlexiTyVar openTypeKind + -- Zonking entails kind defaulting, which turns res_tv :: ? into res_tv :: *. + -- But here, we really do mean res_tv :: ?, so we reset it. + ; res_tv <- return $ setTyVarKind res_tv openTypeKind ; matcher_name <- newImplicitBinder name mkMatcherOcc ; let res_ty = TyVarTy res_tv + cont_args = if null args then [voidPrimId] else args cont_ty = mkSigmaTy ex_tvs prov_theta $ - mkFunTys (map varType args) res_ty + mkFunTys (map varType cont_args) res_ty + fail_ty = mkFunTy voidPrimTy res_ty - ; let matcher_tau = mkFunTys [pat_ty, cont_ty, res_ty] res_ty + ; let matcher_tau = mkFunTys [pat_ty, cont_ty, fail_ty] res_ty matcher_sigma = mkSigmaTy (res_tv:univ_tvs) req_theta matcher_tau matcher_id = mkExportedLocalId VanillaId matcher_name matcher_sigma @@ -139,10 +145,9 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; scrutinee <- mkId "scrut" pat_ty ; cont <- mkId "cont" cont_ty - ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ args) - ; fail <- mkId "fail" res_ty - ; let fail' = nlHsVar fail - + ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ cont_args) + ; fail <- mkId "fail" fail_ty + ; let fail' = nlHsApps fail [nlHsVar voidPrimId] ; let args = map nlVarPat [scrutinee, cont, fail] lwpat = noLoc $ WildPat pat_ty diff --git a/testsuite/.gitignore b/testsuite/.gitignore index ce5c2c2..2423e15 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -1097,6 +1097,7 @@ mk/ghcconfig*_inplace_bin_ghc-stage2.exe.mk /tests/patsyn/should_run/ex-prov /tests/patsyn/should_run/ex-prov-run /tests/patsyn/should_run/match +/tests/patsyn/should_run/match-unboxed /tests/perf/compiler/T1969.comp.stats /tests/perf/compiler/T3064.comp.stats /tests/perf/compiler/T3294.comp.stats diff --git a/testsuite/tests/patsyn/should_run/all.T b/testsuite/tests/patsyn/should_run/all.T index b3c6b74..442dd43 100644 --- a/testsuite/tests/patsyn/should_run/all.T +++ b/testsuite/tests/patsyn/should_run/all.T @@ -3,3 +3,4 @@ test('match', normal, compile_and_run, ['']) test('ex-prov-run', normal, compile_and_run, ['']) test('bidir-explicit', normal, compile_and_run, ['']) test('bidir-explicit-scope', normal, compile_and_run, ['']) +test('match-unboxed', normal, compile_and_run, ['']) diff --git a/testsuite/tests/patsyn/should_run/match-unboxed.hs b/testsuite/tests/patsyn/should_run/match-unboxed.hs new file mode 100644 index 0000000..ec6de0c --- /dev/null +++ b/testsuite/tests/patsyn/should_run/match-unboxed.hs @@ -0,0 +1,21 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module Main where + +import GHC.Base + +pattern P1 <- 0# +pattern P2 <- 1# + +f :: Int# -> Int# +f P1 = 42# +f P2 = 44# + +g :: Int# -> Int +g P1 = 42 +g P2 = 44 + +main = do + print $ I# (f 0#) + print $ I# (f 1#) + print $ g 0# + print $ g 1# diff --git a/testsuite/tests/array/should_run/arr020.stdout b/testsuite/tests/patsyn/should_run/match-unboxed.stdout similarity index 50% copy from testsuite/tests/array/should_run/arr020.stdout copy to testsuite/tests/patsyn/should_run/match-unboxed.stdout index daaac9e..da4a47e 100644 --- a/testsuite/tests/array/should_run/arr020.stdout +++ b/testsuite/tests/patsyn/should_run/match-unboxed.stdout @@ -1,2 +1,4 @@ 42 +44 42 +44 From git at git.haskell.org Sun Nov 2 06:16:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:16:05 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Add a dummy Void# argument to pattern synonym wrapper if it has no arguments and returns an unboxed type (see #9732) (27419ee) Message-ID: <20141102061605.376AE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/27419ee6cd46135c25e2e8aad2ef88137cf9eca6/ghc >--------------------------------------------------------------- commit 27419ee6cd46135c25e2e8aad2ef88137cf9eca6 Author: Dr. ERDI Gergo Date: Sun Nov 2 14:13:20 2014 +0800 Add a dummy Void# argument to pattern synonym wrapper if it has no arguments and returns an unboxed type (see #9732) >--------------------------------------------------------------- 27419ee6cd46135c25e2e8aad2ef88137cf9eca6 compiler/typecheck/TcExpr.lhs | 36 +++++++----- compiler/typecheck/TcPatSyn.lhs | 68 +++++++++++----------- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_compile/T9732.hs | 4 ++ testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_fail/all.T | 2 +- .../patsyn/should_fail/unboxed-wrapper-naked.hs | 8 +++ .../should_fail/unboxed-wrapper-naked.stderr | 3 + testsuite/tests/patsyn/should_run/all.T | 1 + .../tests/patsyn/should_run/unboxed-wrapper.hs | 9 +++ .../should_run/unboxed-wrapper.stdout} | 0 11 files changed, 86 insertions(+), 47 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 27419ee6cd46135c25e2e8aad2ef88137cf9eca6 From git at git.haskell.org Sun Nov 2 06:16:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:16:08 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Binding things matched by an unboxed pattern synonym should require a bang (e5e18a7) Message-ID: <20141102061608.481013A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/e5e18a7779a7bf72182193ed93a687f6e559eaba/ghc >--------------------------------------------------------------- commit e5e18a7779a7bf72182193ed93a687f6e559eaba Author: Dr. ERDI Gergo Date: Sat Nov 1 12:00:19 2014 +0800 Binding things matched by an unboxed pattern synonym should require a bang >--------------------------------------------------------------- e5e18a7779a7bf72182193ed93a687f6e559eaba testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/all.T | 1 + .../should_fail/{unboxed-wrapper-naked.hs => unboxed-bind.hs} | 6 ++++-- testsuite/tests/patsyn/should_fail/unboxed-bind.stderr | 6 ++++++ 5 files changed, 22 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index e8cfb60..97d4317 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -11,3 +11,4 @@ test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) test('T9732', normal, compile, ['']) +test('unboxed-bind-bang', normal, compile, ['']) diff --git a/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs new file mode 100644 index 0000000..a972b21 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash, BangPatterns #-} +module ShouldCompile where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let !(P arg) = x in arg diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index 3979288..96cb097 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -8,3 +8,4 @@ test('T9161-2', normal, compile_fail, ['']) test('T9705-1', normal, compile_fail, ['']) test('T9705-2', normal, compile_fail, ['']) test('unboxed-wrapper-naked', normal, compile_fail, ['']) +test('unboxed-bind', normal, compile_fail, ['']) diff --git a/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs similarity index 52% copy from testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs copy to testsuite/tests/patsyn/should_fail/unboxed-bind.hs index 6e7cc94..ef1b070 100644 --- a/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs @@ -3,6 +3,8 @@ module ShouldFail where import GHC.Base -pattern P1 = 42# +data Foo = MkFoo Int# Int# -x = P1 +pattern P x = MkFoo 0# x + +f x = let P arg = x in arg diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr new file mode 100644 index 0000000..17ca7af --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr @@ -0,0 +1,6 @@ + +unboxed-bind.hs:10:11: + Pattern bindings containing unlifted types should use an outermost bang pattern: + P arg = x + In the expression: let P arg = x in arg + In an equation for ?f?: f x = let P arg = x in arg From git at git.haskell.org Sun Nov 2 06:16:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:16:10 +0000 (UTC) Subject: [commit: ghc] wip/T9732's head updated: Binding things matched by an unboxed pattern synonym should require a bang (e5e18a7) Message-ID: <20141102061610.677C43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9732' now includes: a47ff8b Fixed T5435_dyn_asm on Windows. The test code was not in sync with the expected output. f688f03 Test #9262 in th/T9262, and update other tests. 2cc593d Bring unbound tyvars into scope during reifyInstances. b174288 Test #8953 in th/T8953 9fd19f9 Always use KindedTV when reifying. (#8953) 593e8b9 Annotate reified poly-kinded tycons when necessary. (#8953) c3ecf06 Annotate poly-kinded type patterns in instance reification. 99882ba Testsuite wibbles from fixing #8953 862772b Test #9084 in th/T9084. 03d61cc Fix #9084 by calling notHandled when unknown bits are enountered. 17265c0 Fix testsuite output from #9084. 752b5e2 Test #9738 in th/T9738 209baea Fix #9738, by handling {-# ANN ... #-} in DsMeta. 18a4a5d Update release notes for #9262 #8953 #9084. 96c22d9 Tweak the error message for pattern synonym methods, since they are disallowed both in class and instance declarations 0f7fa84 In pattern synonym matchers, support unboxed continuation results. 27419ee Add a dummy Void# argument to pattern synonym wrapper if it has no arguments and returns an unboxed type (see #9732) e5e18a7 Binding things matched by an unboxed pattern synonym should require a bang From git at git.haskell.org Sun Nov 2 06:42:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:42:21 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Show foralls (when requested) in pattern synonym types (88f7f2e) Message-ID: <20141102064221.DE1303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/88f7f2e3482abc180f9e80d4c97b77312496a3ff/ghc >--------------------------------------------------------------- commit 88f7f2e3482abc180f9e80d4c97b77312496a3ff Author: Dr. ERDI Gergo Date: Sun Aug 3 15:26:13 2014 +0200 Show foralls (when requested) in pattern synonym types >--------------------------------------------------------------- 88f7f2e3482abc180f9e80d4c97b77312496a3ff compiler/hsSyn/HsBinds.lhs | 21 ++++++--------------- compiler/iface/IfaceSyn.lhs | 9 +++++---- 2 files changed, 11 insertions(+), 19 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index f75fa2e..5a45956 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -730,24 +730,18 @@ ppr_sig (SpecSig var ty inl) = pragBrackets (pprSpec (unLoc var) (ppr ty) i ppr_sig (InlineSig var inl) = pragBrackets (ppr inl <+> pprPrefixOcc (unLoc var)) ppr_sig (SpecInstSig ty) = pragBrackets (ptext (sLit "SPECIALIZE instance") <+> ppr ty) ppr_sig (MinimalSig bf) = pragBrackets (pprMinimalSig bf) -ppr_sig (PatSynSig name arg_tys ty (_, _, prov) (_, _, req)) +ppr_sig (PatSynSig name arg_tys ty prov req) = pprPatSynSig (unLoc name) False args (ppr ty) (pprCtx prov) (pprCtx req) where args = fmap ppr arg_tys - pprCtx lctx = case unLoc lctx of - [] -> Nothing - ctx -> Just (pprHsContextNoArrow ctx) + pprCtx (flag, tvs, lctx) = pprHsForAll flag tvs lctx pprPatSynSig :: (OutputableBndr a) - => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> Maybe SDoc -> Maybe SDoc -> SDoc -pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta - = sep [ ptext (sLit "pattern") - , ptext (sLit "type") - , thetaOpt prov_theta, name_and_args - , colon - , thetaOpt req_theta, rhs_ty - ] + => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> SDoc -> SDoc -> SDoc +pprPatSynSig ident is_bidir args rhs_ty prov req + = ptext (sLit "pattern type") <+> + prov <+> name_and_args <+> colon <+> req <+> rhs_ty where name_and_args = case args of PrefixPatSyn arg_tys -> @@ -755,9 +749,6 @@ pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta InfixPatSyn left_ty right_ty -> left_ty <+> pprInfixOcc ident <+> right_ty - -- TODO: support explicit foralls - thetaOpt = maybe empty (<+> darrow) - colon = if is_bidir then dcolon else dcolon -- TODO instance OutputableBndr name => Outputable (FixitySig name) where diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 7e2d6f2..d900875 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -761,11 +761,13 @@ pprIfaceDecl ss (IfaceSyn { ifName = tycon, ifTyVars = tyvars pprIfaceDecl _ (IfacePatSyn { ifName = name, ifPatWrapper = wrapper, ifPatIsInfix = is_infix, - ifPatUnivTvs = _univ_tvs, ifPatExTvs = _ex_tvs, + ifPatUnivTvs = univ_tvs, ifPatExTvs = ex_tvs, ifPatProvCtxt = prov_ctxt, ifPatReqCtxt = req_ctxt, ifPatArgs = args, ifPatTy = ty }) - = pprPatSynSig name has_wrap args' ty' (pprCtxt prov_ctxt) (pprCtxt req_ctxt) + = pprPatSynSig name has_wrap args' ty' + (pprCtxt ex_tvs prov_ctxt) + (pprCtxt univ_tvs req_ctxt) where has_wrap = isJust wrapper args' = case (is_infix, args) of @@ -776,8 +778,7 @@ pprIfaceDecl _ (IfacePatSyn { ifName = name, ifPatWrapper = wrapper, ty' = pprParendIfaceType ty - pprCtxt [] = Nothing - pprCtxt ctxt = Just $ pprIfaceContext ctxt + pprCtxt tvs ctxt = pprIfaceForAllPart tvs ctxt empty pprIfaceDecl ss (IfaceId { ifName = var, ifType = ty, ifIdDetails = details, ifIdInfo = info }) From git at git.haskell.org Sun Nov 2 06:42:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:42:24 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add TcPatSynInfo as a separate type (same pattern as PatSynBind being a separate type) (7150e3d) Message-ID: <20141102064224.7A7213A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/7150e3dc7ba2120087e67d64e2c11c48de82e4f0/ghc >--------------------------------------------------------------- commit 7150e3dc7ba2120087e67d64e2c11c48de82e4f0 Author: Dr. ERDI Gergo Date: Sun Aug 31 19:04:17 2014 +0800 Add TcPatSynInfo as a separate type (same pattern as PatSynBind being a separate type) >--------------------------------------------------------------- 7150e3dc7ba2120087e67d64e2c11c48de82e4f0 compiler/typecheck/TcBinds.lhs | 19 ++++++++++--------- compiler/typecheck/TcPat.lhs | 22 ++++++++++++++++------ compiler/typecheck/TcPatSyn.lhs | 11 ++++++----- compiler/typecheck/TcPatSyn.lhs-boot | 6 ++---- 4 files changed, 34 insertions(+), 24 deletions(-) diff --git a/compiler/typecheck/TcBinds.lhs b/compiler/typecheck/TcBinds.lhs index 68ce078..250e11d 100644 --- a/compiler/typecheck/TcBinds.lhs +++ b/compiler/typecheck/TcBinds.lhs @@ -431,11 +431,9 @@ tc_single _top_lvl sig_fn _prag_fn (L _ (PatSynBind psb at PSB{ psb_id = L _ name } } where tc_pat_syn_decl = case sig_fn name of - Nothing -> - tcInferPatSynDecl psb - Just TcPatSynInfo{ patsig_tau = tau, patsig_prov = prov, patsig_req = req } -> - tcCheckPatSynDecl psb tau prov req - Just _ -> panic "tc_single" + Nothing -> tcInferPatSynDecl psb + Just (TcPatSynInfo tpsi) -> tcCheckPatSynDecl psb tpsi + Just _ -> panic "tc_single" tc_single top_lvl sig_fn prag_fn lbind thing_inside = do { (binds1, ids, closed) <- tcPolyBinds top_lvl sig_fn prag_fn @@ -1320,10 +1318,13 @@ tcTySig (L loc (PatSynSig (L _ name) args ty (_, ex_tvs, prov) (_, univ_tvs, req InfixPatSyn ty1 ty2 -> [ty1, ty2] ; prov' <- tcHsContext prov ; traceTc "tcTySig" $ ppr ty' $$ ppr args' $$ ppr (ex_tvs', prov') $$ ppr (univ_tvs', req') - ; return [TcPatSynInfo{ patsig_name = name, - patsig_tau = mkFunTys args' ty', - patsig_prov = (ex_tvs', prov'), - patsig_req = (univ_tvs', req') }]}}} + ; let tpsi = TPSI{ patsig_name = name, + patsig_tau = mkFunTys args' ty', + patsig_ex = ex_tvs', + patsig_prov = prov', + patsig_univ = univ_tvs', + patsig_req = req' } + ; return [TcPatSynInfo tpsi]}}} tcTySig _ = return [] instTcTySigFromId :: SrcSpan -> Id -> TcM TcSigInfo diff --git a/compiler/typecheck/TcPat.lhs b/compiler/typecheck/TcPat.lhs index dcec057..e67aa57 100644 --- a/compiler/typecheck/TcPat.lhs +++ b/compiler/typecheck/TcPat.lhs @@ -9,7 +9,8 @@ TcPat: Typechecking patterns {-# LANGUAGE CPP, RankNTypes #-} module TcPat ( tcLetPat, TcSigFun, TcPragFun - , TcSigInfo(..), findScopedTyVars + , TcSigInfo(..), TcPatSynInfo(..) + , findScopedTyVars , LetBndrSpec(..), addInlinePrags, warnPrags , tcPat, tcPats, newNoSigLetBndr , addDataConStupidTheta, badFieldCon, polyPatSig ) where @@ -152,11 +153,16 @@ data TcSigInfo sig_loc :: SrcSpan -- The location of the signature } - | TcPatSynInfo { + | TcPatSynInfo TcPatSynInfo + +data TcPatSynInfo + = TPSI { patsig_name :: Name, patsig_tau :: TcSigmaType, - patsig_prov :: ([TcTyVar], TcThetaType), - patsig_req :: ([TcTyVar], TcThetaType) + patsig_ex :: [TcTyVar], + patsig_prov :: TcThetaType, + patsig_univ :: [TcTyVar], + patsig_req :: TcThetaType } findScopedTyVars -- See Note [Binding scoped type variables] @@ -179,13 +185,17 @@ findScopedTyVars hs_ty sig_ty inst_tvs instance NamedThing TcSigInfo where getName TcSigInfo{ sig_id = id } = idName id - getName TcPatSynInfo { patsig_name = name } = name + getName (TcPatSynInfo tpsi) = patsig_name tpsi instance Outputable TcSigInfo where ppr (TcSigInfo { sig_id = id, sig_tvs = tyvars, sig_theta = theta, sig_tau = tau}) = ppr id <+> dcolon <+> vcat [ pprSigmaType (mkSigmaTy (map snd tyvars) theta tau) , ppr (map fst tyvars) ] - ppr (TcPatSynInfo { patsig_name = name}) = text "TcPatSynInfo" <+> ppr name + ppr (TcPatSynInfo tpsi) = text "TcPatSynInfo" <+> ppr tpsi + +instance Outputable TcPatSynInfo where + ppr (TPSI{ patsig_name = name}) = ppr name + \end{code} Note [Binding scoped type variables] diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index c337845..3bdb9b3 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -94,14 +94,15 @@ tcInferPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; return (patSyn, matcher_bind) } tcCheckPatSynDecl :: PatSynBind Name Name - -> TcType - -> ([TyVar], ThetaType) -> ([TyVar], ThetaType) + -> TcPatSynInfo -> TcM (PatSyn, LHsBinds Id) tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, psb_def = lpat, psb_dir = dir } - tau (ex_tvs, prov_theta) (univ_tvs, req_theta) - = do { tcCheckPatSynPat lpat - + TPSI{ patsig_tau = tau, + patsig_ex = ex_tvs, patsig_univ = univ_tvs, + patsig_prov = prov_theta, patsig_req = req_theta } + = setSrcSpan loc $ + do { tcCheckPatSynPat lpat ; prov_dicts <- newEvVars prov_theta ; req_dicts <- newEvVars req_theta diff --git a/compiler/typecheck/TcPatSyn.lhs-boot b/compiler/typecheck/TcPatSyn.lhs-boot index 2129c33..1b2356a 100644 --- a/compiler/typecheck/TcPatSyn.lhs-boot +++ b/compiler/typecheck/TcPatSyn.lhs-boot @@ -6,15 +6,13 @@ import Id ( Id ) import HsSyn ( PatSynBind, LHsBinds ) import TcRnTypes ( TcM ) import PatSyn ( PatSyn ) -import TcType ( TcType, ThetaType ) -import Var ( TyVar ) +import TcPat ( TcPatSynInfo ) tcInferPatSynDecl :: PatSynBind Name Name -> TcM (PatSyn, LHsBinds Id) tcCheckPatSynDecl :: PatSynBind Name Name - -> TcType - -> ([TyVar], ThetaType) -> ([TyVar], ThetaType) + -> TcPatSynInfo -> TcM (PatSyn, LHsBinds Id) tcPatSynWrapper :: PatSynBind Name Name From git at git.haskell.org Sun Nov 2 06:42:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:42:27 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Renamer for PatSynSigs: handle type variable bindings (7502bf6) Message-ID: <20141102064227.09AD33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/7502bf63349f7978e9c3bad11d812f908565c084/ghc >--------------------------------------------------------------- commit 7502bf63349f7978e9c3bad11d812f908565c084 Author: Dr. ERDI Gergo Date: Tue Oct 21 21:19:21 2014 +0800 Renamer for PatSynSigs: handle type variable bindings >--------------------------------------------------------------- 7502bf63349f7978e9c3bad11d812f908565c084 compiler/rename/RnBinds.lhs | 50 ++++++++++++++++++++++++++++++--------------- 1 file changed, 33 insertions(+), 17 deletions(-) diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index c2489cb..906d441 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -30,7 +30,7 @@ import {-# SOURCE #-} RnExpr( rnLExpr, rnStmts ) import HsSyn import TcRnMonad import TcEvidence ( emptyTcEvBinds ) -import RnTypes ( bindSigTyVarsFV, rnHsSigType, rnLHsType, checkPrecMatch, rnContext ) +import RnTypes import RnPat import RnNames import RnEnv @@ -842,22 +842,38 @@ renameSig ctxt sig@(MinimalSig bf) return (MinimalSig new_bf, emptyFVs) renameSig ctxt sig@(PatSynSig v args ty prov req) - = do v' <- lookupSigOccRn ctxt sig v - let doc = quotes (ppr v) - rn_type = rnHsSigType doc - (ty', fvs1) <- rn_type ty - (args', fvs2) <- case args of - PrefixPatSyn tys -> - do (tys, fvs) <- unzip <$> mapM rn_type tys - return (PrefixPatSyn tys, plusFVs fvs) - InfixPatSyn left right -> - do (left', fvs1) <- rn_type left - (right', fvs2) <- rn_type right - return (InfixPatSyn left' right', fvs1 `plusFV` fvs2) - (prov', fvs3) <- rnContext (TypeSigCtx doc) prov - (req', fvs4) <- rnContext (TypeSigCtx doc) req - let fvs = plusFVs [fvs1, fvs2, fvs3, fvs4] - return (PatSynSig v' args' ty' prov' req', fvs) + = do { v' <- lookupSigOccRn ctxt sig v + ; let doc = TypeSigCtx $ quotes (ppr v) + ; loc <- getSrcSpanM + + ; let (ty_kvs, ty_tvs) = extractHsTysRdrTyVars (ty:unLoc req) + ; let ty_tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ ty_tvs + + ; bindHsTyVars doc Nothing ty_kvs ty_tv_bndrs $ \ _new_tyvars -> do + { (req', fvs1) <- rnContext doc req + ; (ty', fvs2) <- rnLHsType doc ty + + ; let (arg_tys, rnArgs) = case args of + PrefixPatSyn tys -> + let rnArgs = do + (tys', fvs) <- mapFvRn (rnLHsType doc) tys + return (PrefixPatSyn tys', fvs) + in (tys, rnArgs) + InfixPatSyn ty1 ty2 -> + let rnArgs = do + (ty1', fvs1) <- rnLHsType doc ty1 + (ty2', fvs2) <- rnLHsType doc ty2 + return (InfixPatSyn ty1' ty2', fvs1 `plusFV` fvs2) + in ([ty1, ty2], rnArgs) + ; let (arg_kvs, arg_tvs) = extractHsTysRdrTyVars (arg_tys ++ unLoc prov) + ; let arg_tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ arg_tvs + + ; bindHsTyVars doc Nothing arg_kvs arg_tv_bndrs $ \ _new_tyvars -> do + { (prov', fvs3) <- rnContext doc prov + ; (args', fvs4) <- rnArgs + + ; let fvs = plusFVs [fvs1, fvs2, fvs3, fvs4] + ; return (PatSynSig v' args' ty' prov' req', fvs) }}} ppr_sig_bndrs :: [Located RdrName] -> SDoc ppr_sig_bndrs bs = quotes (pprWithCommas ppr bs) From git at git.haskell.org Sun Nov 2 06:42:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:42:29 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add TcPatSynInfo to store the typechecked representation of a pattern synonym type signature (44c0215) Message-ID: <20141102064229.97CB53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/44c02158b9b7d4dca3838de100a1dd465bc64951/ghc >--------------------------------------------------------------- commit 44c02158b9b7d4dca3838de100a1dd465bc64951 Author: Dr. ERDI Gergo Date: Wed Jul 30 10:07:30 2014 +0200 Add TcPatSynInfo to store the typechecked representation of a pattern synonym type signature >--------------------------------------------------------------- 44c02158b9b7d4dca3838de100a1dd465bc64951 compiler/typecheck/TcBinds.lhs | 43 +++++++++++++--- compiler/typecheck/TcClassDcl.lhs | 4 +- compiler/typecheck/TcPat.lhs | 11 +++++ compiler/typecheck/TcPatSyn.lhs | 96 ++++++++++++++++++++++++++---------- compiler/typecheck/TcPatSyn.lhs-boot | 7 +++ 5 files changed, 127 insertions(+), 34 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 44c02158b9b7d4dca3838de100a1dd465bc64951 From git at git.haskell.org Sun Nov 2 06:42:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:42:32 +0000 (UTC) Subject: [commit: ghc] wip/T8584: universially-bound tyvars are in scope when renaming existentially-bound tyvars in a pattern synonym signature (ffc72bb) Message-ID: <20141102064232.2A4D63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/ffc72bb3e9193eb6335899430c5b80328d322ba1/ghc >--------------------------------------------------------------- commit ffc72bb3e9193eb6335899430c5b80328d322ba1 Author: Dr. ERDI Gergo Date: Mon Jul 28 16:42:30 2014 +0200 universially-bound tyvars are in scope when renaming existentially-bound tyvars in a pattern synonym signature >--------------------------------------------------------------- ffc72bb3e9193eb6335899430c5b80328d322ba1 compiler/rename/RnBinds.lhs | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index 7f715b6..4a98a35 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -50,6 +50,7 @@ import FastString import Data.List ( partition, sort ) import Maybes ( orElse ) import Control.Monad +import Util ( filterOut ) #if __GLASGOW_HASKELL__ < 709 import Data.Traversable ( traverse ) #endif @@ -865,10 +866,14 @@ renameSig ctxt sig@(PatSynSig v args ty (ex_flag, _ex_tvs, prov) (univ_flag, _un (ty2', fvs2) <- rnLHsType doc ty2 return (InfixPatSyn ty1' ty2', fvs1 `plusFV` fvs2) in ([ty1, ty2], rnArgs) + ; let (ex_kvs, ex_tvs) = extractHsTysRdrTyVars (arg_tys ++ unLoc prov) - ; let ex_tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ ex_tvs + ex_kvs' = filterOut (`elem` univ_kvs) ex_kvs + ex_tvs' = filterOut (`elem` univ_tvs) ex_tvs + + ; let ex_tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ ex_tvs' - ; bindHsTyVars doc Nothing ex_kvs ex_tv_bndrs $ \ ex_tyvars -> do + ; bindHsTyVars doc Nothing ex_kvs' ex_tv_bndrs $ \ ex_tyvars -> do { (prov', fvs3) <- rnContext doc prov ; (args', fvs4) <- rnArgs From git at git.haskell.org Sun Nov 2 06:42:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:42:34 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add parser for pattern synonym type signatures. Syntax is of the form (073941d) Message-ID: <20141102064234.B31EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/073941d65a117958fb543a6ae1c5451d02a51bf6/ghc >--------------------------------------------------------------- commit 073941d65a117958fb543a6ae1c5451d02a51bf6 Author: Dr. ERDI Gergo Date: Mon Jul 14 18:18:44 2014 +0800 Add parser for pattern synonym type signatures. Syntax is of the form pattern type Eq a => P a T b :: Num b => R a b which declares a pattern synonym called P, with argument types a, T, and b. >--------------------------------------------------------------- 073941d65a117958fb543a6ae1c5451d02a51bf6 compiler/hsSyn/HsBinds.lhs | 1 + compiler/hsSyn/HsTypes.lhs | 2 +- compiler/parser/Parser.y.pp | 9 +++++++-- compiler/parser/RdrHsSyn.lhs | 29 ++++++++++++++++++++++++++++- 4 files changed, 37 insertions(+), 4 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index bbf6bc2..91e60c7 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -743,6 +743,7 @@ pprPatSynSig :: (OutputableBndr a) => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> Maybe SDoc -> Maybe SDoc -> SDoc pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta = sep [ ptext (sLit "pattern") + , ptext (sLit "type") , thetaOpt prov_theta, name_and_args , colon , thetaOpt req_theta, rhs_ty diff --git a/compiler/hsSyn/HsTypes.lhs b/compiler/hsSyn/HsTypes.lhs index 9bd5845..9d35c91 100644 --- a/compiler/hsSyn/HsTypes.lhs +++ b/compiler/hsSyn/HsTypes.lhs @@ -39,7 +39,7 @@ module HsTypes ( hsLTyVarName, hsLTyVarNames, hsLTyVarLocName, hsLTyVarLocNames, splitLHsInstDeclTy_maybe, splitHsClassTy_maybe, splitLHsClassTy_maybe, - splitHsFunType, + splitHsFunType, splitLHsForAllTy, splitHsAppTys, hsTyGetAppHead_maybe, mkHsAppTys, mkHsOpTy, -- Printing diff --git a/compiler/parser/Parser.y.pp b/compiler/parser/Parser.y.pp index e0eaf4d..41ad6f0 100644 --- a/compiler/parser/Parser.y.pp +++ b/compiler/parser/Parser.y.pp @@ -856,8 +856,7 @@ role : VARID { L1 $ Just $ getVARID $1 } pattern_synonym_decl :: { LHsDecl RdrName } : 'pattern' pat '=' pat {% do { (name, args) <- splitPatSyn $2 - ; return $ LL . ValD $ mkPatSynBind name args $4 ImplicitBidirectional - }} + ; return $ LL . ValD $ mkPatSynBind name args $4 ImplicitBidirectional }} | 'pattern' pat '<-' pat {% do { (name, args) <- splitPatSyn $2 ; return $ LL . ValD $ mkPatSynBind name args $4 Unidirectional @@ -873,6 +872,11 @@ where_decls :: { Located (OrdList (LHsDecl RdrName)) } : 'where' '{' decls '}' { $3 } | 'where' vocurly decls close { $3 } +pattern_synonym_sig :: { LSig RdrName } + : 'pattern' 'type' ctype '::' ctype + {% do { (name, details, ty, prov, req) <- splitPatSynSig $3 $5 + ; return . LL $ PatSynSig name details ty prov req }} + vars0 :: { [Located RdrName] } : {- empty -} { [] } | varid vars0 { $1 : $2 } @@ -1484,6 +1488,7 @@ sigdecl :: { Located (OrdList (LHsDecl RdrName)) } { LL $ toOL [ LL $ SigD (TypeSig ($1 : reverse (unLoc $3)) $5) ] } | infix prec ops { LL $ toOL [ LL $ SigD (FixSig (FixitySig n (Fixity $2 (unLoc $1)))) | n <- unLoc $3 ] } + | pattern_synonym_sig { LL . unitOL $ LL . SigD . unLoc $ $1 } | '{-# INLINE' activation qvar '#-}' { LL $ unitOL (LL $ SigD (InlineSig $3 (mkInlinePragma (getINLINE $1) $2))) } | '{-# SPECIALISE' activation qvar '::' sigtypes1 '#-}' diff --git a/compiler/parser/RdrHsSyn.lhs b/compiler/parser/RdrHsSyn.lhs index e6969e7..3f2f4bf 100644 --- a/compiler/parser/RdrHsSyn.lhs +++ b/compiler/parser/RdrHsSyn.lhs @@ -18,7 +18,7 @@ module RdrHsSyn ( mkTyFamInst, mkFamDecl, splitCon, mkInlinePragma, - splitPatSyn, toPatSynMatchGroup, + splitPatSyn, splitPatSynSig, toPatSynMatchGroup, mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp mkTyClD, mkInstD, @@ -471,6 +471,33 @@ toPatSynMatchGroup (L _ patsyn_name) (L _ decls) = text "pattern synonym 'where' clause must bind the pattern synonym's name" <+> quotes (ppr patsyn_name) $$ ppr decl +-- Given two types like +-- Eq a => P a T b +-- and +-- Num b => R a b +-- +-- This returns +-- P as the name, +-- PrefixPatSyn [a, T, b] as the details, +-- R a b as the result type, +-- and (Eq a) and (Num b) as the provided and required thetas (respectively) +splitPatSynSig :: LHsType RdrName + -> LHsType RdrName + -> P (Located RdrName, HsPatSynDetails (LHsType RdrName), LHsType RdrName, LHsContext RdrName, LHsContext RdrName) +splitPatSynSig lty1 lty2 = do + (name, details) <- splitCon pat_ty + details' <- case details of + PrefixCon tys -> return $ PrefixPatSyn tys + InfixCon ty1 ty2 -> return $ InfixPatSyn ty1 ty2 + RecCon{} -> parseErrorSDoc (getLoc lty1) $ + text "record syntax not supported for pattern synonym declarations:" $$ ppr lty1 + return (name, details', res_ty, prov', req') + where + (_, prov, pat_ty) = splitLHsForAllTy lty1 + (_, req, res_ty) = splitLHsForAllTy lty2 + prov' = L (getLoc lty1) prov + req' = L (getLoc lty2) req + mkDeprecatedGadtRecordDecl :: SrcSpan -> Located RdrName -> [ConDeclField RdrName] From git at git.haskell.org Sun Nov 2 06:42:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:42:37 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Create SigTyVars for existentials under tcPat when typechecking a PatSyn with a type signature (02e083e) Message-ID: <20141102064237.5A1C53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/02e083e8b19120734d9acb1b6d81fcbc4f510f00/ghc >--------------------------------------------------------------- commit 02e083e8b19120734d9acb1b6d81fcbc4f510f00 Author: Dr. ERDI Gergo Date: Thu Oct 16 22:24:57 2014 +0800 Create SigTyVars for existentials under tcPat when typechecking a PatSyn with a type signature >--------------------------------------------------------------- 02e083e8b19120734d9acb1b6d81fcbc4f510f00 compiler/typecheck/TcPatSyn.lhs | 95 ++++++++++++++++++++++------------------- 1 file changed, 50 insertions(+), 45 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 02e083e8b19120734d9acb1b6d81fcbc4f510f00 From git at git.haskell.org Sun Nov 2 06:42:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:42:39 +0000 (UTC) Subject: [commit: ghc] wip/T8584: tcTySig for PatSynSigs: filter out universially-bound type variables from ex_tvs (f82848d) Message-ID: <20141102064239.E27963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/f82848dbe398556d84cd10eb3ac6edf9bba0b999/ghc >--------------------------------------------------------------- commit f82848dbe398556d84cd10eb3ac6edf9bba0b999 Author: Dr. ERDI Gergo Date: Thu Oct 16 22:17:08 2014 +0800 tcTySig for PatSynSigs: filter out universially-bound type variables from ex_tvs >--------------------------------------------------------------- f82848dbe398556d84cd10eb3ac6edf9bba0b999 compiler/typecheck/TcBinds.lhs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcBinds.lhs b/compiler/typecheck/TcBinds.lhs index 187d33b..68ce078 100644 --- a/compiler/typecheck/TcBinds.lhs +++ b/compiler/typecheck/TcBinds.lhs @@ -1314,7 +1314,8 @@ tcTySig (L loc (PatSynSig (L _ name) args ty (_, ex_tvs, prov) (_, univ_tvs, req { ty' <- tcHsSigType ctxt ty ; req' <- tcHsContext req ; tcHsTyVarBndrs ex_tvs $ \ ex_tvs' -> do - { args' <- mapM (tcHsSigType ctxt) $ case args of + { ex_tvs' <- return $ filter (`notElem` univ_tvs') ex_tvs' + ; args' <- mapM (tcHsSigType ctxt) $ case args of PrefixPatSyn tys -> tys InfixPatSyn ty1 ty2 -> [ty1, ty2] ; prov' <- tcHsContext prov From git at git.haskell.org Sun Nov 2 06:42:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:42:42 +0000 (UTC) Subject: [commit: ghc] wip/T8584: PatSynSig: Add type variable binders (c90c3dd) Message-ID: <20141102064242.7B1A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/c90c3dd1daa81c34ff07d775fa28e27f5fed5987/ghc >--------------------------------------------------------------- commit c90c3dd1daa81c34ff07d775fa28e27f5fed5987 Author: Dr. ERDI Gergo Date: Mon Jul 21 19:40:34 2014 +0800 PatSynSig: Add type variable binders >--------------------------------------------------------------- c90c3dd1daa81c34ff07d775fa28e27f5fed5987 compiler/hsSyn/HsBinds.lhs | 8 ++++---- compiler/hsSyn/HsTypes.lhs | 19 +++++++++++++------ compiler/parser/RdrHsSyn.lhs | 10 ++++++---- compiler/rename/RnBinds.lhs | 16 ++++++++-------- 4 files changed, 31 insertions(+), 22 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index 91e60c7..f75fa2e 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -568,12 +568,12 @@ data Sig name TypeSig [Located name] (LHsType name) -- | A pattern synonym type signature - -- @pattern (Eq b) => P a b :: (Num a) => T a + -- @pattern type forall b. (Eq b) => P a b :: forall a. (Num a) => T a | PatSynSig (Located name) (HsPatSynDetails (LHsType name)) (LHsType name) -- Type - (LHsContext name) -- Provided context - (LHsContext name) -- Required contex + (HsExplicitFlag, LHsTyVarBndrs name, LHsContext name) -- Provided context + (HsExplicitFlag, LHsTyVarBndrs name, LHsContext name) -- Required contex -- | A type signature for a default method inside a class -- @@ -730,7 +730,7 @@ ppr_sig (SpecSig var ty inl) = pragBrackets (pprSpec (unLoc var) (ppr ty) i ppr_sig (InlineSig var inl) = pragBrackets (ppr inl <+> pprPrefixOcc (unLoc var)) ppr_sig (SpecInstSig ty) = pragBrackets (ptext (sLit "SPECIALIZE instance") <+> ppr ty) ppr_sig (MinimalSig bf) = pragBrackets (pprMinimalSig bf) -ppr_sig (PatSynSig name arg_tys ty prov req) +ppr_sig (PatSynSig name arg_tys ty (_, _, prov) (_, _, req)) = pprPatSynSig (unLoc name) False args (ppr ty) (pprCtx prov) (pprCtx req) where args = fmap ppr arg_tys diff --git a/compiler/hsSyn/HsTypes.lhs b/compiler/hsSyn/HsTypes.lhs index 9d35c91..db4d976 100644 --- a/compiler/hsSyn/HsTypes.lhs +++ b/compiler/hsSyn/HsTypes.lhs @@ -39,7 +39,7 @@ module HsTypes ( hsLTyVarName, hsLTyVarNames, hsLTyVarLocName, hsLTyVarLocNames, splitLHsInstDeclTy_maybe, splitHsClassTy_maybe, splitLHsClassTy_maybe, - splitHsFunType, splitLHsForAllTy, + splitHsFunType, splitLHsForAllTyFlag, splitLHsForAllTy, splitHsAppTys, hsTyGetAppHead_maybe, mkHsAppTys, mkHsOpTy, -- Printing @@ -510,15 +510,22 @@ splitLHsInstDeclTy_maybe inst_ty = do (cls, tys) <- splitLHsClassTy_maybe ty return (tvs, cxt, cls, tys) +splitLHsForAllTyFlag + :: LHsType name + -> (HsExplicitFlag, LHsTyVarBndrs name, HsContext name, LHsType name) +splitLHsForAllTyFlag poly_ty + = case unLoc poly_ty of + HsParTy ty -> splitLHsForAllTyFlag ty + HsForAllTy flag tvs cxt ty -> (flag, tvs, unLoc cxt, ty) + _ -> (Implicit, emptyHsQTvs, [], poly_ty) + -- The type vars should have been computed by now, even if they were implicit + splitLHsForAllTy :: LHsType name -> (LHsTyVarBndrs name, HsContext name, LHsType name) splitLHsForAllTy poly_ty - = case unLoc poly_ty of - HsParTy ty -> splitLHsForAllTy ty - HsForAllTy _ tvs cxt ty -> (tvs, unLoc cxt, ty) - _ -> (emptyHsQTvs, [], poly_ty) - -- The type vars should have been computed by now, even if they were implicit + = let (_, tvs, cxt, ty) = splitLHsForAllTyFlag poly_ty + in (tvs, cxt, ty) splitHsClassTy_maybe :: HsType name -> Maybe (name, [LHsType name]) splitHsClassTy_maybe ty = fmap (\(L _ n, tys) -> (n, tys)) $ splitLHsClassTy_maybe (noLoc ty) diff --git a/compiler/parser/RdrHsSyn.lhs b/compiler/parser/RdrHsSyn.lhs index 3f2f4bf..3152642 100644 --- a/compiler/parser/RdrHsSyn.lhs +++ b/compiler/parser/RdrHsSyn.lhs @@ -483,7 +483,9 @@ toPatSynMatchGroup (L _ patsyn_name) (L _ decls) = -- and (Eq a) and (Num b) as the provided and required thetas (respectively) splitPatSynSig :: LHsType RdrName -> LHsType RdrName - -> P (Located RdrName, HsPatSynDetails (LHsType RdrName), LHsType RdrName, LHsContext RdrName, LHsContext RdrName) + -> P (Located RdrName, HsPatSynDetails (LHsType RdrName), LHsType RdrName, + (HsExplicitFlag, LHsTyVarBndrs RdrName, LHsContext RdrName), + (HsExplicitFlag, LHsTyVarBndrs RdrName, LHsContext RdrName)) splitPatSynSig lty1 lty2 = do (name, details) <- splitCon pat_ty details' <- case details of @@ -491,10 +493,10 @@ splitPatSynSig lty1 lty2 = do InfixCon ty1 ty2 -> return $ InfixPatSyn ty1 ty2 RecCon{} -> parseErrorSDoc (getLoc lty1) $ text "record syntax not supported for pattern synonym declarations:" $$ ppr lty1 - return (name, details', res_ty, prov', req') + return (name, details', res_ty, (ex_flag, ex_tvs, prov'), (univ_flag, univ_tvs, req')) where - (_, prov, pat_ty) = splitLHsForAllTy lty1 - (_, req, res_ty) = splitLHsForAllTy lty2 + (ex_flag, ex_tvs, prov, pat_ty) = splitLHsForAllTyFlag lty1 + (univ_flag, univ_tvs, req, res_ty) = splitLHsForAllTyFlag lty2 prov' = L (getLoc lty1) prov req' = L (getLoc lty2) req diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index 906d441..7f715b6 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -841,15 +841,15 @@ renameSig ctxt sig@(MinimalSig bf) = do new_bf <- traverse (lookupSigOccRn ctxt sig) bf return (MinimalSig new_bf, emptyFVs) -renameSig ctxt sig@(PatSynSig v args ty prov req) +renameSig ctxt sig@(PatSynSig v args ty (ex_flag, _ex_tvs, prov) (univ_flag, _univ_tvs, req)) = do { v' <- lookupSigOccRn ctxt sig v ; let doc = TypeSigCtx $ quotes (ppr v) ; loc <- getSrcSpanM - ; let (ty_kvs, ty_tvs) = extractHsTysRdrTyVars (ty:unLoc req) - ; let ty_tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ ty_tvs + ; let (univ_kvs, univ_tvs) = extractHsTysRdrTyVars (ty:unLoc req) + ; let univ_tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ univ_tvs - ; bindHsTyVars doc Nothing ty_kvs ty_tv_bndrs $ \ _new_tyvars -> do + ; bindHsTyVars doc Nothing univ_kvs univ_tv_bndrs $ \ univ_tyvars -> do { (req', fvs1) <- rnContext doc req ; (ty', fvs2) <- rnLHsType doc ty @@ -865,15 +865,15 @@ renameSig ctxt sig@(PatSynSig v args ty prov req) (ty2', fvs2) <- rnLHsType doc ty2 return (InfixPatSyn ty1' ty2', fvs1 `plusFV` fvs2) in ([ty1, ty2], rnArgs) - ; let (arg_kvs, arg_tvs) = extractHsTysRdrTyVars (arg_tys ++ unLoc prov) - ; let arg_tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ arg_tvs + ; let (ex_kvs, ex_tvs) = extractHsTysRdrTyVars (arg_tys ++ unLoc prov) + ; let ex_tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ ex_tvs - ; bindHsTyVars doc Nothing arg_kvs arg_tv_bndrs $ \ _new_tyvars -> do + ; bindHsTyVars doc Nothing ex_kvs ex_tv_bndrs $ \ ex_tyvars -> do { (prov', fvs3) <- rnContext doc prov ; (args', fvs4) <- rnArgs ; let fvs = plusFVs [fvs1, fvs2, fvs3, fvs4] - ; return (PatSynSig v' args' ty' prov' req', fvs) }}} + ; return (PatSynSig v' args' ty' (ex_flag, ex_tyvars, prov') (univ_flag, univ_tyvars, req'), fvs) }}} ppr_sig_bndrs :: [Located RdrName] -> SDoc ppr_sig_bndrs bs = quotes (pprWithCommas ppr bs) From git at git.haskell.org Sun Nov 2 06:42:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:42:45 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Update baseline shift/reduce conflict number (296eba6) Message-ID: <20141102064245.141AF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/296eba6607fb1d24573330953786a177f0ade9b2/ghc >--------------------------------------------------------------- commit 296eba6607fb1d24573330953786a177f0ade9b2 Author: Dr. ERDI Gergo Date: Wed Jul 2 19:18:43 2014 +0800 Update baseline shift/reduce conflict number >--------------------------------------------------------------- 296eba6607fb1d24573330953786a177f0ade9b2 compiler/parser/Parser.y.pp | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/compiler/parser/Parser.y.pp b/compiler/parser/Parser.y.pp index e33808d..e0eaf4d 100644 --- a/compiler/parser/Parser.y.pp +++ b/compiler/parser/Parser.y.pp @@ -72,6 +72,12 @@ import Control.Monad ( mplus ) {- ----------------------------------------------------------------------------- +25 June 2014 + +Conflicts: 47 shift/reduce + 1 reduce/reduce + +----------------------------------------------------------------------------- 12 October 2012 Conflicts: 43 shift/reduce From git at git.haskell.org Sun Nov 2 06:42:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:42:47 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Split tcPatSynDecl into inferring function and general workhorse function (b9f6912) Message-ID: <20141102064247.9CF0C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/b9f6912ea8d2c8c796c8f363ee2f3ea3630a866a/ghc >--------------------------------------------------------------- commit b9f6912ea8d2c8c796c8f363ee2f3ea3630a866a Author: Dr. ERDI Gergo Date: Sun Jul 27 14:10:34 2014 +0200 Split tcPatSynDecl into inferring function and general workhorse function >--------------------------------------------------------------- b9f6912ea8d2c8c796c8f363ee2f3ea3630a866a compiler/typecheck/TcBinds.lhs | 4 ++-- compiler/typecheck/TcPatSyn.lhs | 11 +++++++++-- compiler/typecheck/TcPatSyn.lhs-boot | 4 ++-- 3 files changed, 13 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcBinds.lhs b/compiler/typecheck/TcBinds.lhs index e96e0be..a94748f 100644 --- a/compiler/typecheck/TcBinds.lhs +++ b/compiler/typecheck/TcBinds.lhs @@ -16,7 +16,7 @@ module TcBinds ( tcLocalBinds, tcTopBinds, tcRecSelBinds, import {-# SOURCE #-} TcMatches ( tcGRHSsPat, tcMatchesFun ) import {-# SOURCE #-} TcExpr ( tcMonoExpr ) -import {-# SOURCE #-} TcPatSyn ( tcPatSynDecl, tcPatSynWrapper ) +import {-# SOURCE #-} TcPatSyn ( tcInferPatSynDecl, tcPatSynWrapper ) import DynFlags import HsSyn @@ -419,7 +419,7 @@ tc_single :: forall thing. -> LHsBind Name -> TcM thing -> TcM (LHsBinds TcId, thing) tc_single _top_lvl _sig_fn _prag_fn (L _ (PatSynBind psb)) thing_inside - = do { (pat_syn, aux_binds) <- tcPatSynDecl psb + = do { (pat_syn, aux_binds) <- tcInferPatSynDecl psb ; let tything = AConLike (PatSynCon pat_syn) implicit_ids = (patSynMatcher pat_syn) : diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 9b2b511..17ea802 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -7,7 +7,7 @@ \begin{code} {-# LANGUAGE CPP #-} -module TcPatSyn (tcPatSynDecl, tcPatSynWrapper) where +module TcPatSyn (tcInferPatSynDecl, tcPatSynWrapper) where import HsSyn import TcPat @@ -42,13 +42,20 @@ import TypeRep \end{code} \begin{code} +tcInferPatSynDecl :: PatSynBind Name Name + -> TcM (PatSyn, LHsBinds Id) +tcInferPatSynDecl psb + = do { pat_ty <- newFlexiTyVarTy openTypeKind + ; tcPatSynDecl psb pat_ty } + tcPatSynDecl :: PatSynBind Name Name + -> TcType -> TcM (PatSyn, LHsBinds Id) tcPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, psb_def = lpat, psb_dir = dir } + pat_ty = do { traceTc "tcPatSynDecl {" $ ppr name $$ ppr lpat ; tcCheckPatSynPat lpat - ; pat_ty <- newFlexiTyVarTy openTypeKind ; let (arg_names, is_infix) = case details of PrefixPatSyn names -> (map unLoc names, False) diff --git a/compiler/typecheck/TcPatSyn.lhs-boot b/compiler/typecheck/TcPatSyn.lhs-boot index 700137c..0f77400 100644 --- a/compiler/typecheck/TcPatSyn.lhs-boot +++ b/compiler/typecheck/TcPatSyn.lhs-boot @@ -7,8 +7,8 @@ import HsSyn ( PatSynBind, LHsBinds ) import TcRnTypes ( TcM ) import PatSyn ( PatSyn ) -tcPatSynDecl :: PatSynBind Name Name - -> TcM (PatSyn, LHsBinds Id) +tcInferPatSynDecl :: PatSynBind Name Name + -> TcM (PatSyn, LHsBinds Id) tcPatSynWrapper :: PatSynBind Name Name -> TcM (LHsBinds Id) From git at git.haskell.org Sun Nov 2 06:42:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:42:50 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add test case for T8968 (6706978) Message-ID: <20141102064250.8E1C63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/670697837e471c62e1d498d6fb2e8247b850be2d/ghc >--------------------------------------------------------------- commit 670697837e471c62e1d498d6fb2e8247b850be2d Author: Dr. ERDI Gergo Date: Sun Nov 2 14:35:49 2014 +0800 Add test case for T8968 >--------------------------------------------------------------- 670697837e471c62e1d498d6fb2e8247b850be2d testsuite/tests/patsyn/should_compile/T8968-1.hs | 8 ++++++++ testsuite/tests/patsyn/should_compile/all.T | 1 + 2 files changed, 9 insertions(+) diff --git a/testsuite/tests/patsyn/should_compile/T8968-1.hs b/testsuite/tests/patsyn/should_compile/T8968-1.hs new file mode 100644 index 0000000..f4a1dc4 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8968-1.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE GADTs, KindSignatures, PatternSynonyms #-} +module ShouldCompile where + +data X :: (* -> *) -> * -> * where + Y :: f a -> X f (Maybe a) + +pattern type C a :: X Maybe (Maybe a) +pattern C x = Y (Just x) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index d851bc3..3b7bf27 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -10,3 +10,4 @@ test('incomplete', normal, compile, ['']) test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) +test('T8968-1', normal, compile, ['']) From git at git.haskell.org Sun Nov 2 06:42:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:42:53 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Check provided constraints from pattern type signature (10d5a7b) Message-ID: <20141102064253.261F93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/10d5a7be074f65322aa384df62d20c2d9851eaa1/ghc >--------------------------------------------------------------- commit 10d5a7be074f65322aa384df62d20c2d9851eaa1 Author: Dr. ERDI Gergo Date: Wed Oct 22 18:06:50 2014 +0800 Check provided constraints from pattern type signature >--------------------------------------------------------------- 10d5a7be074f65322aa384df62d20c2d9851eaa1 compiler/typecheck/TcPatSyn.lhs | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 6a329ac..c0ef09b 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -39,7 +39,7 @@ import Bag import TcEvidence import BuildTyCl import TypeRep -import Control.Monad (forM) +import Control.Monad (forM, forM_) #include "HsVersions.h" \end{code} @@ -136,6 +136,15 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, ; let ex_tvs' = varSetElems ex_vars' prov_theta' = map evVarPred prov_dicts' + + ; checkConstraints skol_info ex_tvs' prov_dicts' $ do + ctLoc <- getCtLoc PatSigOrigin + forM_ prov_theta $ \pred -> do + let ctEv = CtWanted{ ctev_pred = pred + , ctev_evar = panic "ctev_evar" + , ctev_loc = ctLoc + } + emitFlat $ mkNonCanonical ctEv ; let (args', _wraps) = unzip arg_w_wraps -- wrap = foldr (<.>) idHsWrapper wraps wrap = idHsWrapper From git at git.haskell.org Sun Nov 2 06:42:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:42:56 +0000 (UTC) Subject: [commit: ghc] wip/T8584: #WIP #STASH (f216eec) Message-ID: <20141102064256.1F3C73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/f216eec563974cd6019b46a5c2c80391fc4d0a8b/ghc >--------------------------------------------------------------- commit f216eec563974cd6019b46a5c2c80391fc4d0a8b Author: Dr. ERDI Gergo Date: Sun Nov 2 14:37:43 2014 +0800 #WIP #STASH >--------------------------------------------------------------- f216eec563974cd6019b46a5c2c80391fc4d0a8b compiler/typecheck/TcPatSyn.lhs | 28 ++++++++++++++---------- testsuite/tests/patsyn/should_compile/T8584-1.hs | 10 +++++++++ testsuite/tests/patsyn/should_compile/all.T | 1 + 3 files changed, 27 insertions(+), 12 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index c0ef09b..9ca3e0f 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -74,9 +74,10 @@ tcInferPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; req_theta <- zonkTcThetaType req_theta ; pat_ty <- zonkTcType pat_ty ; args <- mapM zonkId args + ; let arg_w_wraps = zip args $ repeat idHsWrapper ; let theta = prov_theta ++ req_theta - ; (matcher_id, matcher_bind) <- tcPatSynMatcher lname lpat' args idHsWrapper + ; (matcher_id, matcher_bind) <- tcPatSynMatcher lname lpat' arg_w_wraps univ_tvs ex_tvs ev_binds prov_dicts req_dicts @@ -111,7 +112,7 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, ppr (univ_tvs, req_theta) $$ ppr tau - -- ; prov_dicts <- newEvVars prov_theta + ; _prov_dicts <- newEvVars prov_theta ; req_dicts <- newEvVars req_theta ; let skol_info = SigSkol (FunSigCtxt name) (mkFunTys arg_tys pat_ty) @@ -136,8 +137,11 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, ; let ex_tvs' = varSetElems ex_vars' prov_theta' = map evVarPred prov_dicts' + ; traceTc "prov_theta" $ ppr prov_theta + ; traceTc "prov_theta'" $ ppr prov_theta' + ; traceTc "prov_dicts'" $ ppr prov_dicts' - ; checkConstraints skol_info ex_tvs' prov_dicts' $ do + ; (ev_binds', _) <- checkConstraints skol_info ex_tvs' prov_dicts' $ do ctLoc <- getCtLoc PatSigOrigin forM_ prov_theta $ \pred -> do let ctEv = CtWanted{ ctev_pred = pred @@ -145,16 +149,15 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, , ctev_loc = ctLoc } emitFlat $ mkNonCanonical ctEv - ; let (args', _wraps) = unzip arg_w_wraps - -- wrap = foldr (<.>) idHsWrapper wraps - wrap = idHsWrapper ; ex_tvs' <- mapM zonkQuantifiedTyVar ex_tvs' - ; args' <- mapM zonkId args' + ; arg_w_wraps <- forM arg_w_wraps $ \(arg', wrap) -> do + arg' <- zonkId arg' + return (arg', wrap) ; (matcher_id, matcher_bind) <- tcPatSynMatcher lname lpat' - args' wrap + arg_w_wraps univ_tvs ex_tvs' - ev_binds + ev_binds' prov_dicts' req_dicts prov_theta' req_theta pat_ty @@ -180,7 +183,7 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, \begin{code} tcPatSynMatcher :: Located Name -> LPat Id - -> [Var] -> HsWrapper + -> [(Var, HsWrapper)] -> [TcTyVar] -> [TcTyVar] -> TcEvBinds -> [EvVar] -> [EvVar] @@ -188,7 +191,7 @@ tcPatSynMatcher :: Located Name -> TcType -> TcM (Id, LHsBinds Id) -- See Note [Matchers and wrappers for pattern synonyms] in PatSyn -tcPatSynMatcher (L loc name) lpat args wrap univ_tvs ex_tvs ev_binds prov_dicts req_dicts prov_theta req_theta pat_ty +tcPatSynMatcher (L loc name) lpat arg_w_wraps univ_tvs ex_tvs ev_binds prov_dicts req_dicts prov_theta req_theta pat_ty = do { res_tv <- zonkQuantifiedTyVar =<< newFlexiTyVar liftedTypeKind ; matcher_name <- newImplicitBinder name mkMatcherOcc ; let res_ty = TyVarTy res_tv @@ -204,7 +207,7 @@ tcPatSynMatcher (L loc name) lpat args wrap univ_tvs ex_tvs ev_binds prov_dicts ; scrutinee <- mkId "scrut" pat_ty ; cont <- mkId "cont" cont_ty - ; let cont' = mkLHsWrap wrap $ nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ args) + ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts) ++ [mkLHsWrap wrap $ nlHsVar arg | (arg, wrap) <- arg_w_wraps] ; fail <- mkId "fail" res_ty ; let fail' = nlHsVar fail @@ -253,6 +256,7 @@ tcPatSynMatcher (L loc name) lpat args wrap univ_tvs ex_tvs ev_binds prov_dicts mkId s ty = do name <- newName . mkVarOccFS . fsLit $ s return $ mkLocalId name ty + args = map fst arg_w_wraps isBidirectional :: HsPatSynDir a -> Bool isBidirectional Unidirectional = False diff --git a/testsuite/tests/patsyn/should_compile/T8584-1.hs b/testsuite/tests/patsyn/should_compile/T8584-1.hs new file mode 100644 index 0000000..7a017c8 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8584-1.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms #-} +module ShouldCompile where + +pattern type (Eq a) => Single a :: (Show a) => [a] +-- pattern type Single a :: (Eq a, Show a) => [a] +-- pattern type Single a :: [a] +pattern Single x = [x] + +-- f :: (Show a) => [a] -> a +foobar (Single x) = x diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index 3b7bf27..8896008 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -11,3 +11,4 @@ test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) test('T8968-1', normal, compile, ['']) +test('T8584-1', normal, compile, ['']) From git at git.haskell.org Sun Nov 2 06:42:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 06:42:58 +0000 (UTC) Subject: [commit: ghc] wip/T8584's head updated: #WIP #STASH (f216eec) Message-ID: <20141102064258.ED8763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T8584' now includes: 5b9fe33 Indentation and non-semantic changes only. 4d90b53 Sync up `containers` submodule to latest `master`-tip 07da36b Revert "Fix typo in section name: no leading period." 0202b7c Revert "Check for staticclosures section in Windows linker." 89a8d81 Revert "Rename _closure to _static_closure, apply naming consistently." 126b0c4 Revert "Properly generate info tables for static closures in C--." a3860fc Revert "BC-breaking changes to C-- CLOSURE syntax." d5d6fb3 Revert "Place static closures in their own section." 47c4c91 Update Haddock submodule 07a99c1 Revert "rts/PrimOps.cmm: follow '_static_closure' update" f681c32 Test #9692 in th/T9692 2cd80ba Clarify location of Note. Comment change only. e319d6d Reify data family instances correctly. 710bc8d Update primitive, vector, and dph submodules. 27f7552 Make Applicative-Monad fixes for tests. 3687089 Updated testsuite/.gitignore to cover artifacts on Windows. 2cc2065 Use objdump instead of nm to derive constants on OpenBSD 9f29e03 ghc-prim: Use population count appropriate for platform d4fd168 Update to Unicode version 7.0 a5f4fb6 Remove extra period 3157127 Improve isDigit, isSpace, etc. ef2d027 Make findIndices fuse 1e269bf Make Data.List.concatMap fuse better 6825558 Add doctest examples for Data.Functor. 5211673 Fix typo in -XConstraintKinds docs 9c464f8 Add doctest examples for Data.Bool. c819958 Add release note about Unicode 7.0 69f6361 Fixes the ARM build 972ba12 Enabled warn on tabs by default (fixes #9230) 4faeecb [skip ci] rts: Detabify RtsMessages.c aa8d23d [skip ci] rts: Detabify RaiseAsync.h bb04867 [skip ci] rts: Detabify Capability.h 99edc35 [skip ci] rts: Detabify CheckUnload.c 6aa6ca8 [skip ci] rts: Detabify Profiling.c 570b339 [skip ci] rts: Detabify Threads.c 21eaaa1 [skip ci] rts: Detabify sm/Evac.c 9167d0e [skip ci] rts: Detabify sm/Scav.c 5bb8f14 [skip ci] rts: Detabify Stats.c 2dc21b9 [skip ci] rts: Detabify Schedule.h 1d12df3 [skip ci] rts: Detabify LdvProfile.h 3d0e695 [skip ci] rts: Detabify Proftimer.c 68c45b6 [skip ci] rts: Detabify Exception.cmm a7ab7d3 [skip ci] rts: Detabify HeapStackCheck.cmm 6811e53 [skip ci] rts: Detabify Capability.c beb5c2e [skip ci] rts: Detabify RaiseAsync.c e13478f [skip ci] rts: Detabify sm/GC.c faa3339 [skip ci] rts: Detabify sm/Sanity.c bc1609a [skip ci] rts: Detabify sm/Compact.c c8173d5 [skip ci] rts: Detabify sm/Compact.h 5106e20 [skip ci] rts: Detabify RetainerProfile.c 03c3e9a [skip ci] rts: Detabify ProfHeap.c 6abb34c [skip ci] rts: Detabify Schedule.c 9bfe602 rts: Detabify Interpreter.c df5c11a base: Mark WCsubst.c as generated for Phabricator 45cbe85 Flush stdout in T9692 aa641e5 Add forgotten import to T9692 a11f71e Fix a rare parallel GC bug 427925d More updates to Backpack manual [skip ci] 5bb73d7 Check in up-to-date PDF copies of Backpack docs. [skip ci] aa47995 Implementation of hsig (module signatures), per #9252 1addef8 Fix windows build failure. 73c7ea7 fix a typo in comments: normaliseFfiType 0855b24 Pass in CXX to libffi's configure script. 7b59db2 `M-x delete-trailing-whitespace` & `M-x untabify` a3312c3 testsuite: Fix outdated output for T5979/safePkg01 0a290ca Add new `Data.Bifunctor` module (re #9682) 9e2cb00 Optimise atomicModifyIORef' implementation (#8345) 0e1f0f7 Un-wire `Integer` type (re #9714) 0013613 Deactivate T3064 `max_bytes_used`-check 49b05d6 Improve performance of isSuffixOf (#9676) 1874501 Typo in comment aa2ceba Normalise package key hash to make tests less fragile. 63918e6 Add n-ary version of `two_normalisers` to testsuite lib 3d6422b testlib: Get rid of two_normalisers 98ed815 Make iterateFB inlineable 75979f3 base: Refactor/clean-up *List modules 5f69c8e Reorder GHC.List; fix performance regressions f109085 Update Haddock submodule for collapsible section support 64d0a19 Really fix fft2 regression. #9740 208a0c2 Fixed unused variable warning on mingw32/i686 in rts/Linker.c f9ca529 hsc2hs: Update submodule 322810e Convert GHCi sources from .lhs to .hs 257cbec Fix #9236 Error on read from closed handle 5ce1266 Use snwprintf instead of swprintf in rts/Linker.c. acb3295 Avoid setting -Werror=unused-but-set-variable on Windows. 45175e1 Extra CRs are now filtered out from the source file for :list. f10b67a Updated stale ghcpkg05.stderr-mingw32. 3d27f69 Do not use a relative path for echo in tests/ghci/prog013. c211f8e Add __GLASGOW_HASKELL_TH__=YES/NO to CPP definitions 93c776a Added mingw32-specific expected stdout files for tests/driver/sigof{01,02,03} 9de5240 Comments only c6d4ae6 Fix test driver python3 compatibility issues 578bc00 Add notes on change to hGetContents semantics 995ea1c Fixed missing trailing newline bug in pretty printer 1907e81 Updated testsuite/.gitignore to exclude some test artifacts on Windows. cbb20ab Drop deprecated `OverlappingInstances` from base 919e930 Fix comment typos 8ef4cf1 Add doctest examples for Data.Char bd6c6f6 Update Haddock submodule 54addb1 Clean-up `Data.Fixed` f12be5b Add changelog entry for recent Unicode 7.0 update d3a7126 Update doctest example style in `Data.Bool` 4667fb5 Split off stat (benchmark) test failures into a separate section in the test runner summary. 322c139 remove old .NET related code e466ea7 Remove legacy support for -optdef flags d15d704 Fix build via Haddock submodule update. 6534686 Fix comment about dropWhileEndLE e5ba360 rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) a47ff8b Fixed T5435_dyn_asm on Windows. The test code was not in sync with the expected output. f688f03 Test #9262 in th/T9262, and update other tests. 2cc593d Bring unbound tyvars into scope during reifyInstances. b174288 Test #8953 in th/T8953 9fd19f9 Always use KindedTV when reifying. (#8953) 593e8b9 Annotate reified poly-kinded tycons when necessary. (#8953) c3ecf06 Annotate poly-kinded type patterns in instance reification. 99882ba Testsuite wibbles from fixing #8953 862772b Test #9084 in th/T9084. 03d61cc Fix #9084 by calling notHandled when unknown bits are enountered. 17265c0 Fix testsuite output from #9084. 752b5e2 Test #9738 in th/T9738 209baea Fix #9738, by handling {-# ANN ... #-} in DsMeta. 18a4a5d Update release notes for #9262 #8953 #9084. 96c22d9 Tweak the error message for pattern synonym methods, since they are disallowed both in class and instance declarations 296eba6 Update baseline shift/reduce conflict number 073941d Add parser for pattern synonym type signatures. Syntax is of the form 7502bf6 Renamer for PatSynSigs: handle type variable bindings c90c3dd PatSynSig: Add type variable binders b9f6912 Split tcPatSynDecl into inferring function and general workhorse function 44c0215 Add TcPatSynInfo to store the typechecked representation of a pattern synonym type signature ffc72bb universially-bound tyvars are in scope when renaming existentially-bound tyvars in a pattern synonym signature f82848d tcTySig for PatSynSigs: filter out universially-bound type variables from ex_tvs 88f7f2e Show foralls (when requested) in pattern synonym types 7150e3d Add TcPatSynInfo as a separate type (same pattern as PatSynBind being a separate type) 02e083e Create SigTyVars for existentials under tcPat when typechecking a PatSyn with a type signature 6706978 Add test case for T8968 10d5a7b Check provided constraints from pattern type signature f216eec #WIP #STASH From git at git.haskell.org Sun Nov 2 18:04:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 18:04:07 +0000 (UTC) Subject: [commit: ghc] branch 'wip/oneShot' deleted Message-ID: <20141102180407.975B33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/oneShot From git at git.haskell.org Sun Nov 2 18:04:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 18:04:10 +0000 (UTC) Subject: [commit: ghc] master: Put one-Shot info in the interface (c001bde) Message-ID: <20141102180410.3D7A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c001bde73e38904ed161b0b61b240f99a3b6f48d/ghc >--------------------------------------------------------------- commit c001bde73e38904ed161b0b61b240f99a3b6f48d Author: Joachim Breitner Date: Tue Oct 28 13:02:40 2014 +0100 Put one-Shot info in the interface Differential Revision: https://phabricator.haskell.org/D391 >--------------------------------------------------------------- c001bde73e38904ed161b0b61b240f99a3b6f48d compiler/coreSyn/CoreTidy.lhs | 13 +++++++++++++ compiler/iface/IfaceSyn.lhs | 30 ++++++++++++++++-------------- compiler/iface/IfaceType.lhs | 29 +++++++++++++++++++++++++++-- compiler/iface/MkIface.lhs | 9 ++++++++- compiler/iface/TcIface.lhs | 7 +++++-- 5 files changed, 69 insertions(+), 19 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c001bde73e38904ed161b0b61b240f99a3b6f48d From git at git.haskell.org Sun Nov 2 18:04:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 18:04:13 +0000 (UTC) Subject: [commit: ghc] master: Add GHC.Prim.oneShot (c271e32) Message-ID: <20141102180413.A14C23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c271e32eac65ee95ba1aacc72ed1b24b58ef17ad/ghc >--------------------------------------------------------------- commit c271e32eac65ee95ba1aacc72ed1b24b58ef17ad Author: Joachim Breitner Date: Sun Jan 26 11:36:23 2014 +0000 Add GHC.Prim.oneShot to allow the programer to explictitly set the oneShot flag. This helps with #7994 and will be used in left folds. Also see https://ghc.haskell.org/trac/ghc/wiki/OneShot This commit touches libraries/base/GHC/Event/Manager.hs (which used to have a local definition of the name oneShot) to avoid a shadowing error. Differential Revision: https://phabricator.haskell.org/D392 >--------------------------------------------------------------- c271e32eac65ee95ba1aacc72ed1b24b58ef17ad compiler/basicTypes/MkId.lhs | 42 ++++++++++++++++++++-- compiler/prelude/PrelNames.lhs | 3 +- libraries/base/GHC/Event/Manager.hs | 6 ++-- libraries/ghc-prim/GHC/Magic.hs | 11 +++++- testsuite/.gitignore | 1 + .../should_compile => simplCore/prog003}/Makefile | 0 testsuite/tests/simplCore/prog003/OneShot1.hs | 21 +++++++++++ testsuite/tests/simplCore/prog003/OneShot2.hs | 24 +++++++++++++ .../simplCore/prog003/simplCore.oneShot.stderr | 21 +++++++++++ .../simplCore/prog003/simplCore.oneShot.stdout | 1 + testsuite/tests/simplCore/prog003/test.T | 7 ++++ 11 files changed, 130 insertions(+), 7 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c271e32eac65ee95ba1aacc72ed1b24b58ef17ad From git at git.haskell.org Sun Nov 2 18:04:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 2 Nov 2014 18:04:16 +0000 (UTC) Subject: [commit: ghc] master: Use oneShot in the definition of foldl etc. (072259c) Message-ID: <20141102180416.3C2913A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/072259c78f77d6fe7c36755ebe0123e813c34457/ghc >--------------------------------------------------------------- commit 072259c78f77d6fe7c36755ebe0123e813c34457 Author: Joachim Breitner Date: Sat Oct 25 12:27:06 2014 +0200 Use oneShot in the definition of foldl etc. This increases the chance of good code after fusing a left fold. See ticket #7994 and the new Note [Left folds via right fold] Differential Revision: https://phabricator.haskell.org/D393 >--------------------------------------------------------------- 072259c78f77d6fe7c36755ebe0123e813c34457 libraries/base/Data/OldList.hs | 6 ++++-- libraries/base/GHC/List.lhs | 37 ++++++++++++++++++++++++++----------- 2 files changed, 30 insertions(+), 13 deletions(-) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index 00bc660..e1de19a 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -522,9 +522,11 @@ pairWithNil x = (x, []) mapAccumLF :: (acc -> x -> (acc, y)) -> x -> (acc -> (acc, [y])) -> acc -> (acc, [y]) {-# INLINE [0] mapAccumLF #-} -mapAccumLF f = \x r s -> let (s', y) = f s x +mapAccumLF f = \x r -> oneShot (\s -> + let (s', y) = f s x (s'', ys) = r s' - in (s'', y:ys) + in (s'', y:ys)) + -- See Note [Left folds via right fold] -- | The 'mapAccumR' function behaves like a combination of 'map' and diff --git a/libraries/base/GHC/List.lhs b/libraries/base/GHC/List.lhs index 6a93033..da4c386 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -187,10 +187,26 @@ filterFB c p x r | p x = x `c` r foldl :: forall a b. (b -> a -> b) -> b -> [a] -> b {-# INLINE foldl #-} foldl k z0 xs = - foldr (\(v::a) (fn::b->b) (z::b) -> fn (k z v)) (id :: b -> b) xs z0 --- Implementing foldl via foldr is only a good idea if the compiler can optimize --- the resulting code (eta-expand the recursive "go"), so this needs --- -fcall-arity! Also see #7994. + foldr (\(v::a) (fn::b->b) -> oneShot (\(z::b) -> fn (k z v))) (id :: b -> b) xs z0 + -- See Note [Left folds via right fold] + +{- +Note [Left folds via right fold] + +Implementing foldl et. al. via foldr is only a good idea if the compiler can +optimize the resulting code (eta-expand the recursive "go"). See #7994. +We hope that one of the two measure kick in: + + * Call Arity (-fcall-arity, enabled by default) eta-expands it if it can see + all calls and determine that the arity is large. + * The oneShot annotation gives a hint to the regular arity analysis that + it may assume that the lambda is called at most once. + See [One-shot lambdas] in CoreArity and especially [Eta expanding thunks] + in CoreArity. + +The oneShot annotations used in this module are correct, as we only use them in +argumets to foldr, where we know how the arguments are called. +-} -- ---------------------------------------------------------------------------- @@ -198,11 +214,8 @@ foldl k z0 xs = foldl' :: forall a b . (b -> a -> b) -> b -> [a] -> b {-# INLINE foldl' #-} foldl' k z0 xs = - foldr (\(v::a) (fn::b->b) (z::b) -> z `seq` fn (k z v)) (id :: b -> b) xs z0 - --- Implementing foldl' via foldr is only a good idea if the compiler can --- optimize the resulting code (eta-expand the recursive "go"), so this needs --- -fcall-arity! Also see #7994 + foldr (\(v::a) (fn::b->b) -> oneShot (\(z::b) -> z `seq` fn (k z v))) (id :: b -> b) xs z0 + -- See Note [Left folds via right fold] -- | 'foldl1' is a variant of 'foldl' that has no starting value argument, -- and thus must be applied to non-empty lists. @@ -258,7 +271,8 @@ scanl = scanlGo {-# INLINE [0] scanlFB #-} scanlFB :: (b -> a -> b) -> (b -> c -> c) -> a -> (b -> c) -> b -> c -scanlFB f c = \b g x -> let b' = f x b in b' `c` g b' +scanlFB f c = \b g -> oneShot (\x -> let b' = f x b in b' `c` g b') + -- See Note [Left folds via right fold] {-# INLINE [0] constScanl #-} constScanl :: a -> b -> a @@ -295,7 +309,8 @@ scanl' = scanlGo' {-# INLINE [0] scanlFB' #-} scanlFB' :: (b -> a -> b) -> (b -> c -> c) -> a -> (b -> c) -> b -> c -scanlFB' f c = \b g x -> let !b' = f x b in b' `c` g b' +scanlFB' f c = \b g -> oneShot (\x -> let !b' = f x b in b' `c` g b') + -- See Note [Left folds via right fold] {-# INLINE [0] flipSeqScanl' #-} flipSeqScanl' :: a -> b -> a From git at git.haskell.org Mon Nov 3 09:23:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 09:23:56 +0000 (UTC) Subject: [commit: ghc] master: Update expected profiling output for scc001 (063ae61) Message-ID: <20141103092356.85E213A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/063ae6141855184619e8aa36cab739d6a3fdecb2/ghc >--------------------------------------------------------------- commit 063ae6141855184619e8aa36cab739d6a3fdecb2 Author: Joachim Breitner Date: Mon Nov 3 10:24:10 2014 +0100 Update expected profiling output for scc001 >--------------------------------------------------------------- 063ae6141855184619e8aa36cab739d6a3fdecb2 .../tests/profiling/should_run/scc001.prof.sample | 41 ++++++++++++---------- 1 file changed, 23 insertions(+), 18 deletions(-) diff --git a/testsuite/tests/profiling/should_run/scc001.prof.sample b/testsuite/tests/profiling/should_run/scc001.prof.sample index da0cac9..1a4bec7 100644 --- a/testsuite/tests/profiling/should_run/scc001.prof.sample +++ b/testsuite/tests/profiling/should_run/scc001.prof.sample @@ -1,28 +1,33 @@ - Fri Oct 14 16:27 2011 Time and Allocation Profiling Report (Final) + Sun Nov 2 20:50 2014 Time and Allocation Profiling Report (Final) - scc001 +RTS -hc -p -RTS + scc001 +RTS -hc -p -RTS - total time = 0.00 secs (0 ticks @ 20 ms) - total alloc = 46,020 bytes (excludes profiling overheads) + total time = 0.00 secs (0 ticks @ 1000 us, 1 processor) + total alloc = 51,344 bytes (excludes profiling overheads) COST CENTRE MODULE %time %alloc -MAIN MAIN 0.0 23.0 -CAF GHC.IO.Encoding.Iconv 0.0 1.3 -CAF GHC.IO.Handle.FD 0.0 74.2 +MAIN MAIN 0.0 1.9 +CAF GHC.IO.Encoding 0.0 5.4 +CAF GHC.IO.Handle.FD 0.0 67.3 +CAF GHC.Conc.Signal 0.0 1.3 +main Main 0.0 22.8 individual inherited COST CENTRE MODULE no. entries %time %alloc %time %alloc -MAIN MAIN 101 0 0.0 23.0 0.0 100.0 - CAF GHC.Show 141 0 0.0 0.3 0.0 0.3 - CAF GHC.IO.Handle.FD 128 0 0.0 74.2 0.0 74.2 - CAF GHC.IO.Encoding.Iconv 120 0 0.0 1.3 0.0 1.3 - CAF GHC.Conc.Signal 110 0 0.0 0.7 0.0 0.7 - CAF Main 107 0 0.0 0.4 0.0 0.4 - (...) Main 206 1 0.0 0.0 0.0 0.0 - h Main 205 1 0.0 0.0 0.0 0.0 - main Main 202 1 0.0 0.0 0.0 0.0 - g Main 204 1 0.0 0.0 0.0 0.0 - f Main 203 1 0.0 0.0 0.0 0.0 +MAIN MAIN 44 0 0.0 1.9 0.0 100.0 + main Main 89 0 0.0 22.8 0.0 22.8 + g Main 91 1 0.0 0.0 0.0 0.0 + f Main 90 1 0.0 0.0 0.0 0.0 + CAF Main 87 0 0.0 0.1 0.0 0.1 + (...) Main 93 1 0.0 0.0 0.0 0.0 + h Main 92 1 0.0 0.0 0.0 0.0 + main Main 88 1 0.0 0.0 0.0 0.0 + CAF GHC.Show 84 0 0.0 0.6 0.0 0.6 + CAF GHC.Conc.Signal 82 0 0.0 1.3 0.0 1.3 + CAF GHC.IO.Handle.FD 80 0 0.0 67.3 0.0 67.3 + CAF GHC.IO.Handle.Text 79 0 0.0 0.2 0.0 0.2 + CAF GHC.IO.Encoding 75 0 0.0 5.4 0.0 5.4 + CAF GHC.IO.Encoding.Iconv 69 0 0.0 0.5 0.0 0.5 From git at git.haskell.org Mon Nov 3 13:23:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 13:23:31 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: Make Data.List.Inits fast (ae81f62) Message-ID: <20141103132331.C91283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/ae81f62edcade8f98709a124caf2fe72ad2f81b9/base >--------------------------------------------------------------- commit ae81f62edcade8f98709a124caf2fe72ad2f81b9 Author: David Feuer Date: Mon Nov 3 07:23:09 2014 -0600 Make Data.List.Inits fast Fixes #9345. Use a modified banker's queue to achieve amortized optimal performance for inits. The previous implementation was extremely slow. Reviewed By: nomeata, ekmett, austin Differential Revision: https://phabricator.haskell.org/D329 (cherry picked from cde3a77f9703966145cae481ee35f52dcca2cf7d) >--------------------------------------------------------------- ae81f62edcade8f98709a124caf2fe72ad2f81b9 Data/List.hs | 60 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++--- 1 file changed, 57 insertions(+), 3 deletions(-) diff --git a/Data/List.hs b/Data/List.hs index 130ceb2..8973464 100644 --- a/Data/List.hs +++ b/Data/List.hs @@ -206,6 +206,7 @@ module Data.List ) where import Data.Maybe +import Data.Bits ( (.&.) ) import Data.Char ( isSpace ) import GHC.Num @@ -746,11 +747,16 @@ groupBy eq (x:xs) = (x:ys) : groupBy eq zs -- > inits "abc" == ["","a","ab","abc"] -- -- Note that 'inits' has the following strictness property: +-- @inits (xs ++ _|_) = inits xs ++ _|_@ +-- +-- In particular, -- @inits _|_ = [] : _|_@ inits :: [a] -> [[a]] -inits xs = [] : case xs of - [] -> [] - x : xs' -> map (x :) (inits xs') +inits = map toListSB . scanl' snocSB emptySB +{-# NOINLINE inits #-} +-- We do not allow inits to inline, because it plays havoc with Call Arity +-- if it fuses with a consumer, and it would generally lead to serious +-- loss of sharing if allowed to fuse with a producer. -- | The 'tails' function returns all final segments of the argument, -- longest first. For example, @@ -1087,3 +1093,51 @@ unwords [] = "" unwords [w] = w unwords (w:ws) = w ++ ' ' : unwords ws #endif + +{- A "SnocBuilder" is a version of Chris Okasaki's banker's queue that supports +toListSB instead of uncons. In single-threaded use, its performance +characteristics are similar to John Hughes's functional difference lists, but +likely somewhat worse. In heavily persistent settings, however, it does much +better, because it takes advantage of sharing. The banker's queue guarantees +(amortized) O(1) snoc and O(1) uncons, meaning that we can think of toListSB as +an O(1) conversion to a list-like structure a constant factor slower than +normal lists--we pay the O(n) cost incrementally as we consume the list. Using +functional difference lists, on the other hand, we would have to pay the whole +cost up front for each output list. -} + +{- We store a front list, a rear list, and the length of the queue. Because we +only snoc onto the queue and never uncons, we know it's time to rotate when the +length of the queue plus 1 is a power of 2. Note that we rely on the value of +the length field only for performance. In the unlikely event of overflow, the +performance will suffer but the semantics will remain correct. -} + +data SnocBuilder a = SnocBuilder {-# UNPACK #-} !Word [a] [a] + +{- Smart constructor that rotates the builder when lp is one minus a power of +2. Does not rotate very small builders because doing so is not worth the +trouble. The lp < 255 test goes first because the power-of-2 test gives awful +branch prediction for very small n (there are 5 powers of 2 between 1 and +16). Putting the well-predicted lp < 255 test first avoids branching on the +power-of-2 test until powers of 2 have become sufficiently rare to be predicted +well. -} + +{-# INLINE sb #-} +sb :: Word -> [a] -> [a] -> SnocBuilder a +sb lp f r + | lp < 255 || (lp .&. (lp + 1)) /= 0 = SnocBuilder lp f r + | otherwise = SnocBuilder lp (f ++ reverse r) [] + +-- The empty builder + +emptySB :: SnocBuilder a +emptySB = SnocBuilder 0 [] [] + +-- Add an element to the end of a queue. + +snocSB :: SnocBuilder a -> a -> SnocBuilder a +snocSB (SnocBuilder lp f r) x = sb (lp + 1) f (x:r) + +-- Convert a builder to a list + +toListSB :: SnocBuilder a -> [a] +toListSB (SnocBuilder _ f r) = f ++ reverse r From git at git.haskell.org Mon Nov 3 13:25:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 13:25:22 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: testsuite: T7815 requires SMP support from ghc (a674a0d) Message-ID: <20141103132522.533683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/a674a0d874c45785af6a7a66fde402008b2504fc/ghc >--------------------------------------------------------------- commit a674a0d874c45785af6a7a66fde402008b2504fc Author: Sergei Trofimovich Date: Sat Aug 23 01:20:11 2014 +0300 testsuite: T7815 requires SMP support from ghc Signed-off-by: Sergei Trofimovich (cherry picked from commit ff9f4ad38521e54c5284f9bf4599c3baaefeb228) >--------------------------------------------------------------- a674a0d874c45785af6a7a66fde402008b2504fc testsuite/tests/rts/all.T | 1 + 1 file changed, 1 insertion(+) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index 920368a..58fcd4b 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -176,6 +176,7 @@ test('stablename001', expect_fail_for(['hpc']), compile_and_run, ['']) test('T7815', [ multi_cpu_race, extra_run_opts('50000 +RTS -N2 -RTS'), + req_smp, only_ways(['threaded1', 'threaded2']) ], compile_and_run, [''] ) # ignore_output because it contains a unique: From git at git.haskell.org Mon Nov 3 13:25:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 13:25:25 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: testsuite: disable gcc's warnings about casts of incompatible prototypes in UNREG (60d88fa) Message-ID: <20141103132525.009323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/60d88fabac11c4e2572692dc73d6842647cb59a7/ghc >--------------------------------------------------------------- commit 60d88fabac11c4e2572692dc73d6842647cb59a7 Author: Sergei Trofimovich Date: Sat Aug 23 11:01:16 2014 +0300 testsuite: disable gcc's warnings about casts of incompatible prototypes in UNREG Haskell's 'foreign import' declaraion does not have a way to extress exact C prototypes (it ignores 'const' modifiers, exact pointer types, etc.) which leads to warnings when C backend generates calls to such functions: /tmp/ghc32698_0/ghc32698_10.hc:52:5: warning: conflicting types for built-in function ?strlen? [enabled by default] EF_(strlen); ^ Patch disables builtin functions for UNREG build to workaround test failures due to stderr mismatch. Fixes the following test failures: TEST="safePkg01 T5423 T7574 T3736" Signed-off-by: Sergei Trofimovich (cherry picked from commit fcdd58d2ddcfd8d420adbcb3f20c1d666bc834e6) >--------------------------------------------------------------- 60d88fabac11c4e2572692dc73d6842647cb59a7 testsuite/mk/test.mk | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/testsuite/mk/test.mk b/testsuite/mk/test.mk index 0cc3f21..ab059bf 100644 --- a/testsuite/mk/test.mk +++ b/testsuite/mk/test.mk @@ -25,6 +25,13 @@ COMPILER = ghc CONFIGDIR = $(TOP)/config CONFIG = $(CONFIGDIR)/$(COMPILER) +ifeq "$(GhcUnregisterised)" "YES" + # Otherwise C backend generates many warnings about + # imcompatible proto casts for GCC's buitins: + # memcpy, printf, strlen. + EXTRA_HC_OPTS += -optc-fno-builtin +endif + # TEST_HC_OPTS is passed to every invocation of TEST_HC # in nested Makefiles TEST_HC_OPTS = -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output -no-user-$(GhcPackageDbFlag) -rtsopts $(EXTRA_HC_OPTS) From git at git.haskell.org Mon Nov 3 13:25:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 13:25:27 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: testsuite: mark testwsdeque mark as faulty on NOSMP builds (8a7c348) Message-ID: <20141103132527.A3C233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/8a7c3488b014367470fa157dd9dc69d930c25afa/ghc >--------------------------------------------------------------- commit 8a7c3488b014367470fa157dd9dc69d930c25afa Author: Sergei Trofimovich Date: Sat Aug 23 11:32:05 2014 +0300 testsuite: mark testwsdeque mark as faulty on NOSMP builds Signed-off-by: Sergei Trofimovich (cherry picked from commit 2fcb36e41f46f80f75e2f245a1a45457f0f7d6d2) >--------------------------------------------------------------- 8a7c3488b014367470fa157dd9dc69d930c25afa testsuite/tests/rts/all.T | 1 + 1 file changed, 1 insertion(+) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index 58fcd4b..1506f3c 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -49,6 +49,7 @@ test('T2783', [ omit_ways(['ghci']), exit_code(1) ], compile_and_run, ['']) # Test the work-stealing deque implementation. We run this test in # both threaded1 (-threaded -debug) and threaded2 (-threaded) ways. test('testwsdeque', [unless(in_tree_compiler(), skip), + req_smp, # needs atomic 'cas' c_src, only_ways(['threaded1', 'threaded2'])], compile_and_run, ['-I../../../rts']) From git at git.haskell.org Mon Nov 3 13:41:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 13:41:41 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Use correct precedence when printing contexts with class operators (d71f316) Message-ID: <20141103134141.4D6733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/d71f316ef4acb6a967a1f07bc4c1144e553a3ac9/ghc >--------------------------------------------------------------- commit d71f316ef4acb6a967a1f07bc4c1144e553a3ac9 Author: Simon Peyton Jones Date: Thu Oct 2 17:47:21 2014 +0100 Use correct precedence when printing contexts with class operators Fixes Trac #9658 (cherry picked from commit 48089ccf4f1f239b3268b2cb52b8aa0f7356485b) Conflicts: compiler/types/TypeRep.lhs testsuite/tests/ghci/scripts/all.T testsuite/tests/perf/compiler/T5837.stderr testsuite/tests/typecheck/should_fail/ContextStack2.stderr testsuite/tests/typecheck/should_fail/T8392a.stderr >--------------------------------------------------------------- d71f316ef4acb6a967a1f07bc4c1144e553a3ac9 compiler/types/TypeRep.lhs | 10 ++++++---- testsuite/tests/gadt/T7558.stderr | 2 +- testsuite/tests/ghci/scripts/Defer02.stderr | 8 ++++---- testsuite/tests/ghci/scripts/T9658.script | 4 ++++ testsuite/tests/ghci/scripts/T9658.stdout | 1 + testsuite/tests/ghci/scripts/all.T | 1 + testsuite/tests/indexed-types/should_compile/Simple14.stderr | 2 +- testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.stderr | 2 +- testsuite/tests/indexed-types/should_fail/SimpleFail15.stderr | 2 +- testsuite/tests/indexed-types/should_fail/T2239.stderr | 4 ++-- testsuite/tests/indexed-types/should_fail/T4093a.stderr | 4 ++-- testsuite/tests/perf/compiler/T5837.stderr | 4 ++-- testsuite/tests/polykinds/T7230.stderr | 3 ++- testsuite/tests/roles/should_compile/Roles3.stderr | 2 +- testsuite/tests/typecheck/should_fail/ContextStack2.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/FrozenErrorTests.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5858.stderr | 2 +- testsuite/tests/typecheck/should_fail/T7857.stderr | 2 +- testsuite/tests/typecheck/should_fail/T8392a.stderr | 6 +++--- 19 files changed, 37 insertions(+), 28 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d71f316ef4acb6a967a1f07bc4c1144e553a3ac9 From git at git.haskell.org Mon Nov 3 13:41:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 13:41:43 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Improve comments and tracing in SpecConstr (fcece34) Message-ID: <20141103134143.EAA493A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/fcece34760929d79dea3e9871462cb927f60aa5c/ghc >--------------------------------------------------------------- commit fcece34760929d79dea3e9871462cb927f60aa5c Author: Simon Peyton Jones Date: Mon May 5 08:50:51 2014 +0100 Improve comments and tracing in SpecConstr (cherry picked from commit 675c5478793ac8cede5daca4f70cd09846879837) >--------------------------------------------------------------- fcece34760929d79dea3e9871462cb927f60aa5c compiler/specialise/SpecConstr.lhs | 53 ++++++++++++++++++++++---------------- 1 file changed, 31 insertions(+), 22 deletions(-) diff --git a/compiler/specialise/SpecConstr.lhs b/compiler/specialise/SpecConstr.lhs index 060c705..faedb94 100644 --- a/compiler/specialise/SpecConstr.lhs +++ b/compiler/specialise/SpecConstr.lhs @@ -396,16 +396,19 @@ use the calls in the un-specialised RHS as seeds. We call these Note [Top-level recursive groups] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -If all the bindings in a top-level recursive group are not exported, -all the calls are in the rest of the top-level bindings. -This means we can specialise with those call patterns instead of with the RHSs -of the recursive group. +If all the bindings in a top-level recursive group are local (not +exported), then all the calls are in the rest of the top-level +bindings. This means we can specialise with those call patterns +instead of with the RHSs of the recursive group. -To get the call usage information, we work backwards through the top-level bindings -so we see the usage before we get to the binding of the function. -Before we can collect the usage though, we go through all the bindings and add them -to the environment. This is necessary because usage is only tracked for functions -in the environment. +(Question: maybe we should *also* use calls in the rest of the +top-level bindings as seeds? + +To get the call usage information, we work backwards through the +top-level bindings so we see the usage before we get to the binding of +the function. Before we can collect the usage though, we go through +all the bindings and add them to the environment. This is necessary +because usage is only tracked for functions in the environment. The actual seeding of the specialisation is very similar to Note [Local recursive group]. @@ -1323,16 +1326,14 @@ scTopBind env usage (Rec prs) = do { (rhs_usgs, rhss') <- mapAndUnzipM (scExpr env) rhss ; return (usage `combineUsage` (combineUsages rhs_usgs), Rec (bndrs `zip` rhss')) } | otherwise -- Do specialisation - = do { (rhs_usgs, rhs_infos) <- mapAndUnzipM (scRecRhs env) (bndrs `zip` rhss) + = do { (rhs_usgs, rhs_infos) <- mapAndUnzipM (scRecRhs env) prs -- ; pprTrace "scTopBind" (ppr bndrs $$ ppr (map (lookupVarEnv (scu_calls usage)) bndrs)) (return ()) -- Note [Top-level recursive groups] - ; let (usg,rest) = if all (not . isExportedId) bndrs - then -- pprTrace "scTopBind-T" (ppr bndrs $$ ppr (map (fmap (map snd) . lookupVarEnv (scu_calls usage)) bndrs)) - ( usage - , [SI [] 0 (Just us) | us <- rhs_usgs] ) - else ( combineUsages rhs_usgs - , [SI [] 0 Nothing | _ <- rhs_usgs] ) + ; let (usg,rest) | any isExportedId bndrs -- Seed from RHSs + = ( combineUsages rhs_usgs, [SI [] 0 Nothing | _ <- rhs_usgs] ) + | otherwise -- Seed from body only + = ( usage, [SI [] 0 (Just us) | us <- rhs_usgs] ) ; (usage', specs) <- specLoop (scForce env force_spec) (scu_calls usg) rhs_infos nullUsage rest @@ -1446,11 +1447,6 @@ specialise env bind_calls (RI fn _ arg_bndrs body arg_occs) , notNull arg_bndrs -- Only specialise functions , Just all_calls <- lookupVarEnv bind_calls fn = do { (boring_call, pats) <- callsToPats env specs arg_occs all_calls --- ; pprTrace "specialise" (vcat [ ppr fn <+> text "with" <+> int (length pats) <+> text "good patterns" --- , text "arg_occs" <+> ppr arg_occs --- , text "calls" <+> ppr all_calls --- , text "good pats" <+> ppr pats]) $ --- return () -- Bale out if too many specialisations ; let n_pats = length pats @@ -1473,12 +1469,25 @@ specialise env bind_calls (RI fn _ arg_bndrs body arg_occs) _normal_case -> do { - let spec_env = decreaseSpecCount env n_pats +-- ; if (not (null pats) || isJust mb_unspec) then +-- pprTrace "specialise" (vcat [ ppr fn <+> text "with" <+> int (length pats) <+> text "good patterns" +-- , text "mb_unspec" <+> ppr (isJust mb_unspec) +-- , text "arg_occs" <+> ppr arg_occs +-- , text "good pats" <+> ppr pats]) $ +-- return () +-- else return () + + ; let spec_env = decreaseSpecCount env n_pats ; (spec_usgs, new_specs) <- mapAndUnzipM (spec_one spec_env fn arg_bndrs body) (pats `zip` [spec_count..]) -- See Note [Specialise original body] ; let spec_usg = combineUsages spec_usgs + + -- If there were any boring calls among the seeds (= all_calls), then those + -- calls will call the un-specialised function. So we should use the seeds + -- from the _unspecialised_ function's RHS, which are in mb_unspec, by returning + -- then in new_usg. (new_usg, mb_unspec') = case mb_unspec of Just rhs_usg | boring_call -> (spec_usg `combineUsage` rhs_usg, Nothing) From git at git.haskell.org Mon Nov 3 13:41:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 13:41:46 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Introduce the Call data types (9622fca) Message-ID: <20141103134146.9A3203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/9622fcaf4a2bbe650a588dec4ffff85105b2bdcb/ghc >--------------------------------------------------------------- commit 9622fcaf4a2bbe650a588dec4ffff85105b2bdcb Author: Simon Peyton Jones Date: Mon Aug 25 12:24:55 2014 +0100 Introduce the Call data types This is just a small refactoring that makes the code a bit clearer, using a data type instead of a triple. We get better pretty-printing too. (cherry picked from commit c0fe1d9e7a9f23d050319c77f3a38264f3aa22f8) >--------------------------------------------------------------- 9622fcaf4a2bbe650a588dec4ffff85105b2bdcb compiler/specialise/SpecConstr.lhs | 19 ++++++++++++++++--- 1 file changed, 16 insertions(+), 3 deletions(-) diff --git a/compiler/specialise/SpecConstr.lhs b/compiler/specialise/SpecConstr.lhs index faedb94..609dcfd 100644 --- a/compiler/specialise/SpecConstr.lhs +++ b/compiler/specialise/SpecConstr.lhs @@ -33,6 +33,7 @@ import Rules import Type hiding ( substTy ) import TyCon ( isRecursiveTyCon, tyConName ) import Id +import PprCore ( pprParendExpr ) import MkCore ( mkImpossibleExpr ) import Var import VarEnv @@ -1017,15 +1018,27 @@ data ScUsage } -- The domain is OutIds type CallEnv = IdEnv [Call] -type Call = (ValueEnv, [CoreArg]) +data Call = Call Id [CoreArg] ValueEnv -- The arguments of the call, together with the -- env giving the constructor bindings at the call site + -- We keep the function mainly for debug output + +instance Outputable Call where + ppr (Call fn args _) = ppr fn <+> fsep (map pprParendExpr args) nullUsage :: ScUsage nullUsage = SCU { scu_calls = emptyVarEnv, scu_occs = emptyVarEnv } combineCalls :: CallEnv -> CallEnv -> CallEnv combineCalls = plusVarEnv_C (++) + where +-- plus cs ds | length res > 1 +-- = pprTrace "combineCalls" (vcat [ ptext (sLit "cs:") <+> ppr cs +-- , ptext (sLit "ds:") <+> ppr ds]) +-- res +-- | otherwise = res +-- where +-- res = cs ++ ds combineUsage :: ScUsage -> ScUsage -> ScUsage combineUsage u1 u2 = SCU { scu_calls = combineCalls (scu_calls u1) (scu_calls u2), @@ -1283,7 +1296,7 @@ scApp env (other_fn, args) mkVarUsage :: ScEnv -> Id -> [CoreExpr] -> ScUsage mkVarUsage env fn args = case lookupHowBound env fn of - Just RecFun -> SCU { scu_calls = unitVarEnv fn [(sc_vals env, args)] + Just RecFun -> SCU { scu_calls = unitVarEnv fn [Call fn args (sc_vals env)] , scu_occs = emptyVarEnv } Just RecArg -> SCU { scu_calls = emptyVarEnv , scu_occs = unitVarEnv fn arg_occ } @@ -1709,7 +1722,7 @@ callToPats :: ScEnv -> [ArgOcc] -> Call -> UniqSM (Maybe (CallPat, ValueEnv)) -- Type variables come first, since they may scope -- over the following term variables -- The [CoreExpr] are the argument patterns for the rule -callToPats env bndr_occs (con_env, args) +callToPats env bndr_occs (Call _ args con_env) | length args < length bndr_occs -- Check saturated = return Nothing | otherwise From git at git.haskell.org Mon Nov 3 13:41:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 13:41:49 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Do not duplicate call information in SpecConstr (Trac #8852) (01c48d8) Message-ID: <20141103134149.50E773A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/01c48d84d680957f07534fa6ab6218f78efcfb1f/ghc >--------------------------------------------------------------- commit 01c48d84d680957f07534fa6ab6218f78efcfb1f Author: Simon Peyton Jones Date: Mon Aug 25 12:28:44 2014 +0100 Do not duplicate call information in SpecConstr (Trac #8852) This long-standing and egregious bug meant that call information was being gratuitously copied, leading to an exponential blowup in the number of calls to be examined when function definitions are deeply nested. That is what has been causing the blowup in SpecConstr's running time, not (as I had previously supposed) generating very large code. See Note [spec_usg includes rhs_usg] (cherry picked from commit af4bc31c50c873344a2426d4be842f92edf17019) >--------------------------------------------------------------- 01c48d84d680957f07534fa6ab6218f78efcfb1f compiler/specialise/SpecConstr.lhs | 70 ++++++++++++++++++++++++++------------ 1 file changed, 48 insertions(+), 22 deletions(-) diff --git a/compiler/specialise/SpecConstr.lhs b/compiler/specialise/SpecConstr.lhs index 609dcfd..0b612ee 100644 --- a/compiler/specialise/SpecConstr.lhs +++ b/compiler/specialise/SpecConstr.lhs @@ -1209,7 +1209,7 @@ scExpr' env (Let (NonRec bndr rhs) body) (SI [] 0 (Just rhs_usg)) ; return (body_usg { scu_calls = scu_calls body_usg `delVarEnv` bndr' } - `combineUsage` rhs_usg `combineUsage` spec_usg, + `combineUsage` spec_usg, -- Note [spec_usg includes rhs_usg] mkLets [NonRec b r | (b,r) <- specInfoBinds rhs_info specs] body') } @@ -1233,8 +1233,7 @@ scExpr' env (Let (Rec prs) body) -- Instead use them only if we find an unspecialised call -- See Note [Local recursive groups] - ; let rhs_usg = combineUsages rhs_usgs - all_usg = spec_usg `combineUsage` rhs_usg `combineUsage` body_usg + ; let all_usg = spec_usg `combineUsage` body_usg -- Note [spec_usg includes rhs_usg] bind' = Rec (concat (zipWith specInfoBinds rhs_infos specs)) ; return (all_usg { scu_calls = scu_calls all_usg `delVarEnvList` bndrs' }, @@ -1331,34 +1330,35 @@ scTopBind _ usage _ = error "false" -} -scTopBind env usage (Rec prs) +scTopBind env body_usage (Rec prs) | Just threshold <- sc_size env , not force_spec , not (all (couldBeSmallEnoughToInline (sc_dflags env) threshold) rhss) -- No specialisation = do { (rhs_usgs, rhss') <- mapAndUnzipM (scExpr env) rhss - ; return (usage `combineUsage` (combineUsages rhs_usgs), Rec (bndrs `zip` rhss')) } + ; return (body_usage `combineUsage` combineUsages rhs_usgs, Rec (bndrs `zip` rhss')) } + | otherwise -- Do specialisation = do { (rhs_usgs, rhs_infos) <- mapAndUnzipM (scRecRhs env) prs - -- ; pprTrace "scTopBind" (ppr bndrs $$ ppr (map (lookupVarEnv (scu_calls usage)) bndrs)) (return ()) + -- ; pprTrace "scTopBind" (ppr bndrs $$ ppr (map (lookupVarEnv (scu_calls body_usage)) bndrs)) (return ()) -- Note [Top-level recursive groups] ; let (usg,rest) | any isExportedId bndrs -- Seed from RHSs = ( combineUsages rhs_usgs, [SI [] 0 Nothing | _ <- rhs_usgs] ) | otherwise -- Seed from body only - = ( usage, [SI [] 0 (Just us) | us <- rhs_usgs] ) + = ( body_usage, [SI [] 0 (Just us) | us <- rhs_usgs] ) - ; (usage', specs) <- specLoop (scForce env force_spec) - (scu_calls usg) rhs_infos nullUsage rest + ; (spec_usage, specs) <- specLoop (scForce env force_spec) + (scu_calls usg) rhs_infos nullUsage rest - ; return (usage `combineUsage` usage', + ; return (body_usage `combineUsage` spec_usage, Rec (concat (zipWith specInfoBinds rhs_infos specs))) } where (bndrs,rhss) = unzip prs force_spec = any (forceSpecBndr env) bndrs -- Note [Forcing specialisation] -scTopBind env usage (NonRec bndr rhs) +scTopBind env usage (NonRec bndr rhs) -- Oddly, we don't seem to specialise top-level non-rec functions = do { (rhs_usg', rhs') <- scExpr env rhs ; return (usage `combineUsage` rhs_usg', NonRec bndr rhs') } @@ -1415,6 +1415,7 @@ data SpecInfo = SI [OneSpec] -- The specialisations we have generated -- unleashed) -- Nothing => we have -- See Note [Local recursive groups] + -- See Note [spec_usg includes rhs_usg] -- One specialisation: Rule plus definition data OneSpec = OS CallPat -- Call pattern that generated this specialisation @@ -1441,10 +1442,12 @@ specLoop env all_calls rhs_infos usg_so_far specs_so_far specialise :: ScEnv - -> CallEnv -- Info on calls + -> CallEnv -- Info on newly-discovered calls to this function -> RhsInfo - -> SpecInfo -- Original RHS plus patterns dealt with - -> UniqSM (ScUsage, SpecInfo) -- New specialised versions and their usage + -> SpecInfo -- Original RHS plus patterns dealt with + -> UniqSM (ScUsage, SpecInfo) -- New specialised versions and their usage + +-- See Note [spec_usg includes rhs_usg] -- Note: this only generates *specialised* bindings -- The original binding is added by specInfoBinds @@ -1455,11 +1458,20 @@ specialise specialise env bind_calls (RI fn _ arg_bndrs body arg_occs) spec_info@(SI specs spec_count mb_unspec) - | not (isBottomingId fn) -- Note [Do not specialise diverging functions] - , not (isNeverActive (idInlineActivation fn)) -- See Note [Transfer activation] - , notNull arg_bndrs -- Only specialise functions - , Just all_calls <- lookupVarEnv bind_calls fn - = do { (boring_call, pats) <- callsToPats env specs arg_occs all_calls + | isBottomingId fn -- Note [Do not specialise diverging functions] + -- and do not generate specialisation seeds from its RHS + = return (nullUsage, spec_info) + + | isNeverActive (idInlineActivation fn) -- See Note [Transfer activation] + || null arg_bndrs -- Only specialise functions + = case mb_unspec of -- Behave as if there was a single, boring call + Just rhs_usg -> return (rhs_usg, SI specs spec_count Nothing) + -- See Note [spec_usg includes rhs_usg] + Nothing -> return (nullUsage, spec_info) + + | Just all_calls <- lookupVarEnv bind_calls fn + = -- pprTrace "specialise entry {" (ppr fn <+> ppr (length all_calls)) $ + do { (boring_call, pats) <- callsToPats env specs arg_occs all_calls -- Bale out if too many specialisations ; let n_pats = length pats @@ -1506,9 +1518,13 @@ specialise env bind_calls (RI fn _ arg_bndrs body arg_occs) Just rhs_usg | boring_call -> (spec_usg `combineUsage` rhs_usg, Nothing) _ -> (spec_usg, mb_unspec) - ; return (new_usg, SI (new_specs ++ specs) spec_count' mb_unspec') } } - | otherwise - = return (nullUsage, spec_info) -- The boring case +-- ; pprTrace "specialise return }" (ppr fn +-- <+> ppr (scu_calls new_usg)) + ; return (new_usg, SI (new_specs ++ specs) spec_count' mb_unspec') } } + + + | otherwise -- No new seeds, so return nullUsage + = return (nullUsage, spec_info) --------------------- @@ -1610,6 +1626,16 @@ calcSpecStrictness fn qvars pats go_one env _ _ = env \end{code} +Note [spec_usg includes rhs_usg] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +In calls to 'specialise', the returned ScUsage must include the rhs_usg in +the passed-in SpecInfo, unless there are no calls at all to the function. + +The caller can, indeed must, assume this. He should not combine in rhs_usg +himself, or he'll get rhs_usg twice -- and that can lead to an exponential +blowup of duplicates in the CallEnv. This is what gave rise to the massive +performace loss in Trac #8852. + Note [Specialise original body] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The RhsInfo for a binding keeps the *original* body of the binding. We From git at git.haskell.org Mon Nov 3 13:45:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 13:45:13 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: Filter out null bytes from trace, and warn accordingly, fixing #9395. (8dcd15c) Message-ID: <20141103134513.B4E0E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/8dcd15c0db12069aee0ab8193b03ccc5a0078c4b/base >--------------------------------------------------------------- commit 8dcd15c0db12069aee0ab8193b03ccc5a0078c4b Author: Edward Z. Yang Date: Mon Nov 3 07:45:11 2014 -0600 Filter out null bytes from trace, and warn accordingly, fixing #9395. Summary: Previously, if you ran trace "foo\0bar", the output was truncated so that everything after the null byte was omitted. This was terrible. Now we filter out null bytes, and emit an extra trace saying that null bytes were filtered out. NB: we CANNOT fix debugBelch, because all printf variants *always* respect null bytes, even if you're using string precision such as %.*s. The alternative would have been to introduce a new function debugRawBelch which did not use format strings and took an explicit string length, but I decided we generally should avoid putting null bytes in our trace messages, and warn the user. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: hvr, austin Subscribers: simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D121 GHC Trac Issues: #9395 >--------------------------------------------------------------- 8dcd15c0db12069aee0ab8193b03ccc5a0078c4b Debug/Trace.hs | 11 +++++++++-- tests/T9395.hs | 2 ++ tests/T9395.stderr | 2 ++ tests/all.T | 1 + 4 files changed, 14 insertions(+), 2 deletions(-) diff --git a/Debug/Trace.hs b/Debug/Trace.hs index eedacfa..92e5b20 100644 --- a/Debug/Trace.hs +++ b/Debug/Trace.hs @@ -52,6 +52,7 @@ import qualified GHC.Foreign import GHC.IO.Encoding import GHC.Ptr import GHC.Stack +import Data.List -- $tracing -- @@ -70,9 +71,15 @@ import GHC.Stack -- /Since: 4.5.0.0/ traceIO :: String -> IO () traceIO msg = do - withCString "%s\n" $ \cfmt -> - withCString msg $ \cmsg -> + withCString "%s\n" $ \cfmt -> do + -- NB: debugBelch can't deal with null bytes, so filter them + -- out so we don't accidentally truncate the message. See Trac #9395 + let (nulls, msg') = partition (=='\0') msg + withCString msg' $ \cmsg -> debugBelch cfmt cmsg + when (not (null nulls)) $ + withCString "WARNING: previous trace message had null bytes" $ \cmsg -> + debugBelch cfmt cmsg -- don't use debugBelch() directly, because we cannot call varargs functions -- using the FFI. diff --git a/tests/T9395.hs b/tests/T9395.hs new file mode 100644 index 0000000..c86b127 --- /dev/null +++ b/tests/T9395.hs @@ -0,0 +1,2 @@ +import Debug.Trace +main = trace "333\0UUUU" $ return () diff --git a/tests/T9395.stderr b/tests/T9395.stderr new file mode 100644 index 0000000..4a4fb3f --- /dev/null +++ b/tests/T9395.stderr @@ -0,0 +1,2 @@ +333UUUU +WARNING: previous trace message had null bytes diff --git a/tests/all.T b/tests/all.T index bec843f..5b2f40a 100644 --- a/tests/all.T +++ b/tests/all.T @@ -163,3 +163,4 @@ test('T8766', only_ways(['normal'])], compile_and_run, ['-O']) +test('T9395', normal, compile_and_run, ['']) From git at git.haskell.org Mon Nov 3 13:46:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 13:46:32 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) (df719cb) Message-ID: <20141103134632.825573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/df719cbfbc822bf77c5de884b37ef35597cd64ca/ghc >--------------------------------------------------------------- commit df719cbfbc822bf77c5de884b37ef35597cd64ca Author: Dr. ERDI Gergo Date: Tue Oct 21 20:51:35 2014 +0800 rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) (cherry picked from commit e5ba36080d08791f44e3bed37721f702e242af96) >--------------------------------------------------------------- df719cbfbc822bf77c5de884b37ef35597cd64ca compiler/rename/RnBinds.lhs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/T9705.hs | 3 +++ testsuite/tests/patsyn/should_fail/T9705.stderr | 4 ++++ testsuite/tests/patsyn/should_fail/all.T | 1 + 4 files changed, 18 insertions(+) diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index 7251492..3991e24 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -698,6 +698,11 @@ rnMethodBind _ _ (L loc bind@(PatBind {})) = do addErrAt loc (methodBindErr bind) return (emptyBag, emptyFVs) +-- Associated pattern synonyms are not implemented yet +rnMethodBind _ _ (L loc bind@(PatSynBind {})) = do + addErrAt loc $ methodPatSynErr bind + return (emptyBag, emptyFVs) + rnMethodBind _ _ b = pprPanic "rnMethodBind" (ppr b) \end{code} @@ -1012,6 +1017,11 @@ methodBindErr mbind = hang (ptext (sLit "Pattern bindings (except simple variables) not allowed in instance declarations")) 2 (ppr mbind) +methodPatSynErr :: HsBindLR RdrName RdrName -> SDoc +methodPatSynErr mbind + = hang (ptext (sLit "Pattern synonyms not allowed in instance declarations")) + 2 (ppr mbind) + bindsInHsBootFile :: LHsBindsLR Name RdrName -> SDoc bindsInHsBootFile mbinds = hang (ptext (sLit "Bindings in hs-boot files are not allowed")) diff --git a/testsuite/tests/patsyn/should_fail/T9705.hs b/testsuite/tests/patsyn/should_fail/T9705.hs new file mode 100644 index 0000000..54d1d00 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/T9705.hs @@ -0,0 +1,3 @@ +{-# LANGUAGE PatternSynonyms #-} +class C a where + pattern P = () diff --git a/testsuite/tests/patsyn/should_fail/T9705.stderr b/testsuite/tests/patsyn/should_fail/T9705.stderr new file mode 100644 index 0000000..d9a3a49 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/T9705.stderr @@ -0,0 +1,4 @@ + +T9705.hs:3:5: + Pattern synonyms not allowed in instance declarations + pattern P = () diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index bff6bdf..298f23b 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -6,3 +6,4 @@ test('T8961', normal, multimod_compile_fail, ['T8961','']) test('as-pattern', normal, compile_fail, ['']) test('T9161-1', normal, compile_fail, ['']) test('T9161-2', normal, compile_fail, ['']) +test('T9705', normal, compile_fail, ['']) From git at git.haskell.org Mon Nov 3 14:02:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 14:02:32 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Add skeleton 7.8.4 release notes (7d128ea) Message-ID: <20141103140232.298C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/7d128ea05cf91589ae78873294f63938af45b2b9/ghc >--------------------------------------------------------------- commit 7d128ea05cf91589ae78873294f63938af45b2b9 Author: Austin Seipp Date: Mon Nov 3 07:51:38 2014 -0600 Add skeleton 7.8.4 release notes Signed-off-by: Austin Seipp >--------------------------------------------------------------- 7d128ea05cf91589ae78873294f63938af45b2b9 docs/users_guide/7.8.4-notes.xml | 21 +++++++++++++++++++++ docs/users_guide/intro.xml | 1 + docs/users_guide/ug-ent.xml.in | 1 + 3 files changed, 23 insertions(+) diff --git a/docs/users_guide/7.8.4-notes.xml b/docs/users_guide/7.8.4-notes.xml new file mode 100644 index 0000000..075ffb6 --- /dev/null +++ b/docs/users_guide/7.8.4-notes.xml @@ -0,0 +1,21 @@ + + + Release notes for version 7.8.4 + + + The 7.8.4 release is a bugfix release. The major bugfixes relative + to 7.8.3 are listed below. + + + + GHC + + + + + Lorem ipsum... + + + + + diff --git a/docs/users_guide/intro.xml b/docs/users_guide/intro.xml index fb7116e..0bbc7ac 100644 --- a/docs/users_guide/intro.xml +++ b/docs/users_guide/intro.xml @@ -310,6 +310,7 @@ &relnotes1; &relnotes2; &relnotes3; +&relnotes4; diff --git a/docs/users_guide/ug-ent.xml.in b/docs/users_guide/ug-ent.xml.in index 5df3a04..ab5c54a 100644 --- a/docs/users_guide/ug-ent.xml.in +++ b/docs/users_guide/ug-ent.xml.in @@ -6,6 +6,7 @@ + From git at git.haskell.org Mon Nov 3 14:02:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 14:02:34 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Flesh out release notes. (ce30dae) Message-ID: <20141103140234.D82FE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/ce30dae684b91fd734cfdfc4d9f223f28f539f0a/ghc >--------------------------------------------------------------- commit ce30dae684b91fd734cfdfc4d9f223f28f539f0a Author: Austin Seipp Date: Mon Nov 3 08:02:55 2014 -0600 Flesh out release notes. Signed-off-by: Austin Seipp >--------------------------------------------------------------- ce30dae684b91fd734cfdfc4d9f223f28f539f0a docs/users_guide/7.8.4-notes.xml | 84 +++++++++++++++++++++++++++++++++++++++- 1 file changed, 83 insertions(+), 1 deletion(-) diff --git a/docs/users_guide/7.8.4-notes.xml b/docs/users_guide/7.8.4-notes.xml index 075ffb6..5d98063 100644 --- a/docs/users_guide/7.8.4-notes.xml +++ b/docs/users_guide/7.8.4-notes.xml @@ -13,7 +13,89 @@ - Lorem ipsum... + A critical bug in the LLVM backend which would cause the + compiler to generate incorrect code has been fixed (issue + #9439). + + + + + Several bugs in the code generator have been fixed for + unregisterised platforms, such as 64bit PowerPC (issue + #8819 and #8849). + + + + + A bug that could cause GHC's constructor specialization + pass (enabled by default at -O2, or via + -fspec-constr) to loop forever and + consume large amounts of memory has been fixed (issue + #8960). + + + + + A bug that would cause GHC to fail when attempting to + determine GCC's version information in non-english locales + has been fixed (issue #8825). + + + + + A minor bug that allowed GHC to seemingly import (but not + use) private data constructors has been fixed (issue + #9006). + + + + + A bug in the register allocator which would cause GHC to + crash during compilation has been fixed (issue #9303). + + + + + A bug that caused the compiler to panic on some input C-- + code has been fixed (issue #9329). + + + + + A few various minor deadlocks in the runtime system when + using forkProcess have been fixed. + + + + + A bug which made blocked STM transactions + non-interruptible has been fixed (issue #9379). + + + + + A bug in the compiler which broke pattern synonym imports + across modules in Haddock has been fixed (issue #9417). + + + + + A minor bug in the code generator in which the + popCnt16# did not zero-extend its + result has been fixed (issue #9435). + + + + + A minor bug in the compiler which made error messages emit + necessary parenthesis has been fixed (issue #9658). + + + + + A bug which caused the compiler to panic on pattern + synonyms inside a class declaration has been fixed (issue + #9705). From git at git.haskell.org Mon Nov 3 14:10:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 14:10:50 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix a typo in an error message (246c380) Message-ID: <20141103141050.E92173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/246c3807a71bfb7d4f982a1903c22e3c81d74d37/ghc >--------------------------------------------------------------- commit 246c3807a71bfb7d4f982a1903c22e3c81d74d37 Author: Gabor Greif Date: Tue Oct 7 10:20:08 2014 +0200 Fix a typo in an error message (cherry picked from commit 3c5648afff13e9f6e94dea4094cc3a3fb97baeea) >--------------------------------------------------------------- 246c3807a71bfb7d4f982a1903c22e3c81d74d37 compiler/typecheck/TcTyClsDecls.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcTyClsDecls.lhs b/compiler/typecheck/TcTyClsDecls.lhs index 1345696..f416067 100644 --- a/compiler/typecheck/TcTyClsDecls.lhs +++ b/compiler/typecheck/TcTyClsDecls.lhs @@ -1655,7 +1655,7 @@ checkFamFlag tc_name = do { idx_tys <- xoptM Opt_TypeFamilies ; checkTc idx_tys err_msg } where - err_msg = hang (ptext (sLit "Illegal family declaraion for") <+> quotes (ppr tc_name)) + err_msg = hang (ptext (sLit "Illegal family declaration for") <+> quotes (ppr tc_name)) 2 (ptext (sLit "Use TypeFamilies to allow indexed type families")) \end{code} From git at git.haskell.org Mon Nov 3 14:19:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 14:19:44 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Make Core Lint check for un-saturated type applications (b15432c) Message-ID: <20141103141944.44EE93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/b15432c826fdad27afc45be617c117876d9f3e08/ghc >--------------------------------------------------------------- commit b15432c826fdad27afc45be617c117876d9f3e08 Author: Simon Peyton Jones Date: Mon Aug 25 15:10:19 2014 +0100 Make Core Lint check for un-saturated type applications Un-saturated type-family and type-synonym applications are detected in the front end, but for some reason Lint wasn't looking for them. I came across this when wondering why Trac #9433 didn't give a Core Lint error (cherry picked from commit 8ff4671422090acf9146e3a90dd38e2c6f72aebb) >--------------------------------------------------------------- b15432c826fdad27afc45be617c117876d9f3e08 compiler/coreSyn/CoreLint.lhs | 15 +++++++++++---- 1 file changed, 11 insertions(+), 4 deletions(-) diff --git a/compiler/coreSyn/CoreLint.lhs b/compiler/coreSyn/CoreLint.lhs index 8665ec4..2689900 100644 --- a/compiler/coreSyn/CoreLint.lhs +++ b/compiler/coreSyn/CoreLint.lhs @@ -727,13 +727,20 @@ lintType ty@(FunTy t1 t2) -- (->) has two different rules, for types and kind ; lintArrow (ptext (sLit "type or kind") <+> quotes (ppr ty)) k1 k2 } lintType ty@(TyConApp tc tys) - | not (isUnLiftedTyCon tc) || tys `lengthIs` tyConArity tc - -- Check that primitive types are saturated + | Just ty' <- coreView ty + = lintType ty' -- Expand type synonyms, so that we do not bogusly complain + -- about un-saturated type synonyms + -- + + | isUnLiftedTyCon tc || isSynTyCon tc -- See Note [The kind invariant] in TypeRep + -- Also type synonyms and type families + , length tys < tyConArity tc + = failWithL (hang (ptext (sLit "Un-saturated type application")) 2 (ppr ty)) + + | otherwise = do { ks <- mapM lintType tys ; lint_ty_app ty (tyConKind tc) (tys `zip` ks) } - | otherwise - = failWithL (hang (ptext (sLit "Malformed type:")) 2 (ppr ty)) lintType (ForAllTy tv ty) = do { lintTyBndrKind tv From git at git.haskell.org Mon Nov 3 14:19:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 14:19:47 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Check for un-saturated type family applications (de53111) Message-ID: <20141103141947.5AFEA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/de531119362b343978c0a38d4fa75e80103baaa1/ghc >--------------------------------------------------------------- commit de531119362b343978c0a38d4fa75e80103baaa1 Author: Simon Peyton Jones Date: Mon Aug 25 15:13:02 2014 +0100 Check for un-saturated type family applications This patch corrects an egregious error introduced by: commit 022f8750edf6f413fba31293435dcc62600eab77 Author: Simon Peyton Jones Date: Thu May 15 16:07:04 2014 +0100 Refactoring around TyCon.isSynTyCon * Document isSynTyCon better * Add isTypeSyonymTyCon for regular H98 type synonyms * Use isTypeSynonymTyCon rather than isSynTyCon where the former is really intended At this particular spot in TcValidity we really do mean isSynTyCon and not isTypeSynonymTyCon. Fixes Trac #9433 (cherry picked from commit ee4501bbad6480509e8a60b5ff89c0b0b228b66d) Conflicts: testsuite/tests/indexed-types/should_fail/all.T >--------------------------------------------------------------- de531119362b343978c0a38d4fa75e80103baaa1 compiler/typecheck/TcValidity.lhs | 5 ++++- testsuite/tests/indexed-types/should_fail/T9433.hs | 15 +++++++++++++++ testsuite/tests/indexed-types/should_fail/T9433.stderr | 4 ++++ testsuite/tests/indexed-types/should_fail/all.T | 1 + 4 files changed, 24 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcValidity.lhs b/compiler/typecheck/TcValidity.lhs index ebb375d..7e73ee6 100644 --- a/compiler/typecheck/TcValidity.lhs +++ b/compiler/typecheck/TcValidity.lhs @@ -290,7 +290,7 @@ check_type ctxt rank (AppTy ty1 ty2) ; check_arg_type ctxt rank ty2 } check_type ctxt rank ty@(TyConApp tc tys) - | isTypeSynonymTyCon tc = check_syn_tc_app ctxt rank ty tc tys + | isSynTyCon tc = check_syn_tc_app ctxt rank ty tc tys | isUnboxedTupleTyCon tc = check_ubx_tuple ctxt ty tys | otherwise = mapM_ (check_arg_type ctxt rank) tys @@ -301,6 +301,9 @@ check_type _ _ ty = pprPanic "check_type" (ppr ty) ---------------------------------------- check_syn_tc_app :: UserTypeCtxt -> Rank -> KindOrType -> TyCon -> [KindOrType] -> TcM () +-- Used for type synonyms and type synonym families, +-- which must be saturated, +-- but not data families, which need not be saturated check_syn_tc_app ctxt rank ty tc tys | tc_arity <= n_args -- Saturated -- Check that the synonym has enough args diff --git a/testsuite/tests/indexed-types/should_fail/T9433.hs b/testsuite/tests/indexed-types/should_fail/T9433.hs new file mode 100644 index 0000000..c7b6161 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T9433.hs @@ -0,0 +1,15 @@ +{-# LANGUAGE + TypeFamilies + , KindSignatures + #-} + +module T9433 where + +type family Id x :: * +type instance Id a = a + +type family Map (f :: * -> *) x :: * +type instance Map f [a] = [f a] + +x :: Map Id [Bool] +x = [] diff --git a/testsuite/tests/indexed-types/should_fail/T9433.stderr b/testsuite/tests/indexed-types/should_fail/T9433.stderr new file mode 100644 index 0000000..0b17f57 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T9433.stderr @@ -0,0 +1,4 @@ + +T9433.hs:14:6: + Type synonym ?Id? should have 1 argument, but has been given none + In the type signature for ?x?: x :: Map Id [Bool] diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index 5340574..dde335d 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -120,3 +120,4 @@ test('T8368', normal, compile_fail, ['']) test('T8368a', normal, compile_fail, ['']) test('T8518', normal, compile_fail, ['']) test('T9160', normal, compile_fail, ['']) +test('T9433', normal, compile_fail, ['']) From git at git.haskell.org Mon Nov 3 14:26:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 14:26:31 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Release note blurb for #9433 (7b1d4c4) Message-ID: <20141103142631.2ABCD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/7b1d4c4d678fb41897cd6c89a95b526f32595c91/ghc >--------------------------------------------------------------- commit 7b1d4c4d678fb41897cd6c89a95b526f32595c91 Author: Austin Seipp Date: Mon Nov 3 08:26:57 2014 -0600 Release note blurb for #9433 Signed-off-by: Austin Seipp >--------------------------------------------------------------- 7b1d4c4d678fb41897cd6c89a95b526f32595c91 docs/users_guide/7.8.4-notes.xml | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/docs/users_guide/7.8.4-notes.xml b/docs/users_guide/7.8.4-notes.xml index 5d98063..7b75069 100644 --- a/docs/users_guide/7.8.4-notes.xml +++ b/docs/users_guide/7.8.4-notes.xml @@ -98,6 +98,12 @@ #9705). + + + A bug in the typechecker revolving around un-saturated + type family applications has been fixed (issue #9433). + + From git at git.haskell.org Mon Nov 3 16:22:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 16:22:15 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9066 in th/T9066 (187e090) Message-ID: <20141103162215.0CB013A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/187e090a7af1a1b192709a25d31d5df9071b0900/ghc >--------------------------------------------------------------- commit 187e090a7af1a1b192709a25d31d5df9071b0900 Author: Richard Eisenberg Date: Sun Nov 2 13:44:27 2014 -0500 Test #9066 in th/T9066 >--------------------------------------------------------------- 187e090a7af1a1b192709a25d31d5df9071b0900 testsuite/tests/th/T9066.hs | 10 ++++++++++ testsuite/tests/th/all.T | 1 + 2 files changed, 11 insertions(+) diff --git a/testsuite/tests/th/T9066.hs b/testsuite/tests/th/T9066.hs new file mode 100644 index 0000000..2e46fe5 --- /dev/null +++ b/testsuite/tests/th/T9066.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T9066 where + +$([d| data Blargh = (:<=>) Int Int + infix 4 :<=> + + type Foo a b = Either a b + infix 5 `Foo` + |]) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 4409571..132ef82 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -335,3 +335,4 @@ test('T9692', normal, compile, ['-v0']) test('T8953', normal, compile, ['-v0']) test('T9084', normal, compile_fail, ['-v0']) test('T9738', normal, compile, ['-v0']) +test('T9066', expect_broken(9066), compile, ['-v0']) From git at git.haskell.org Mon Nov 3 16:22:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 16:22:17 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9066. (c126f33) Message-ID: <20141103162217.9B0073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/c126f333eabe11bb47ffd9acb228124360b1b56c/ghc >--------------------------------------------------------------- commit c126f333eabe11bb47ffd9acb228124360b1b56c Author: Richard Eisenberg Date: Mon Nov 3 11:15:35 2014 -0500 Fix #9066. When splicing in a fixity declaration, look for both term-level things and type-level things. This requires some changes elsewhere in the code to allow for more flexibility when looking up Exact names, which can be assigned the wrong namespace during fixity declaration conversion. See the ticket for more info. >--------------------------------------------------------------- c126f333eabe11bb47ffd9acb228124360b1b56c compiler/basicTypes/RdrName.lhs | 11 +++++--- compiler/hsSyn/Convert.lhs | 17 +++++++++--- compiler/rename/RnEnv.lhs | 57 ++++++++++++++++++++++++++--------------- testsuite/tests/th/all.T | 2 +- 4 files changed, 58 insertions(+), 29 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c126f333eabe11bb47ffd9acb228124360b1b56c From git at git.haskell.org Mon Nov 3 16:22:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 16:22:20 +0000 (UTC) Subject: [commit: ghc] wip/rae's head updated: Fix #9066. (c126f33) Message-ID: <20141103162220.2CD883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/rae' now includes: 0013613 Deactivate T3064 `max_bytes_used`-check 49b05d6 Improve performance of isSuffixOf (#9676) 1874501 Typo in comment aa2ceba Normalise package key hash to make tests less fragile. 63918e6 Add n-ary version of `two_normalisers` to testsuite lib 3d6422b testlib: Get rid of two_normalisers 98ed815 Make iterateFB inlineable 75979f3 base: Refactor/clean-up *List modules 5f69c8e Reorder GHC.List; fix performance regressions f109085 Update Haddock submodule for collapsible section support 64d0a19 Really fix fft2 regression. #9740 208a0c2 Fixed unused variable warning on mingw32/i686 in rts/Linker.c f9ca529 hsc2hs: Update submodule 322810e Convert GHCi sources from .lhs to .hs 257cbec Fix #9236 Error on read from closed handle 5ce1266 Use snwprintf instead of swprintf in rts/Linker.c. acb3295 Avoid setting -Werror=unused-but-set-variable on Windows. 45175e1 Extra CRs are now filtered out from the source file for :list. f10b67a Updated stale ghcpkg05.stderr-mingw32. 3d27f69 Do not use a relative path for echo in tests/ghci/prog013. c211f8e Add __GLASGOW_HASKELL_TH__=YES/NO to CPP definitions 93c776a Added mingw32-specific expected stdout files for tests/driver/sigof{01,02,03} 9de5240 Comments only c6d4ae6 Fix test driver python3 compatibility issues 578bc00 Add notes on change to hGetContents semantics 995ea1c Fixed missing trailing newline bug in pretty printer 1907e81 Updated testsuite/.gitignore to exclude some test artifacts on Windows. cbb20ab Drop deprecated `OverlappingInstances` from base 919e930 Fix comment typos 8ef4cf1 Add doctest examples for Data.Char bd6c6f6 Update Haddock submodule 54addb1 Clean-up `Data.Fixed` f12be5b Add changelog entry for recent Unicode 7.0 update d3a7126 Update doctest example style in `Data.Bool` 4667fb5 Split off stat (benchmark) test failures into a separate section in the test runner summary. 322c139 remove old .NET related code e466ea7 Remove legacy support for -optdef flags d15d704 Fix build via Haddock submodule update. 6534686 Fix comment about dropWhileEndLE e5ba360 rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) a47ff8b Fixed T5435_dyn_asm on Windows. The test code was not in sync with the expected output. f688f03 Test #9262 in th/T9262, and update other tests. 2cc593d Bring unbound tyvars into scope during reifyInstances. b174288 Test #8953 in th/T8953 9fd19f9 Always use KindedTV when reifying. (#8953) 593e8b9 Annotate reified poly-kinded tycons when necessary. (#8953) c3ecf06 Annotate poly-kinded type patterns in instance reification. 99882ba Testsuite wibbles from fixing #8953 862772b Test #9084 in th/T9084. 03d61cc Fix #9084 by calling notHandled when unknown bits are enountered. 17265c0 Fix testsuite output from #9084. 752b5e2 Test #9738 in th/T9738 209baea Fix #9738, by handling {-# ANN ... #-} in DsMeta. 18a4a5d Update release notes for #9262 #8953 #9084. 96c22d9 Tweak the error message for pattern synonym methods, since they are disallowed both in class and instance declarations c001bde Put one-Shot info in the interface c271e32 Add GHC.Prim.oneShot 072259c Use oneShot in the definition of foldl etc. 187e090 Test #9066 in th/T9066 c126f33 Fix #9066. From git at git.haskell.org Mon Nov 3 17:23:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 17:23:46 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Compiler performance is much worse in for loopy givens (37785df) Message-ID: <20141103172346.714393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Oct14 Link : http://ghc.haskell.org/trac/ghc/changeset/37785df6febb50350bdc7967e7361eb68ee24425/ghc >--------------------------------------------------------------- commit 37785df6febb50350bdc7967e7361eb68ee24425 Author: Simon Peyton Jones Date: Mon Nov 3 10:37:59 2014 +0000 Compiler performance is much worse in for loopy givens This is a deliberate choice, to simplify code, invariants, and I think performance in typical cases. The "loopy givens" case is situations like [G] a ~ TF (a, Int) where TF is a type function with TF (a,b) = (TF a, TF b). See Note [An alternative story for the inert substitution] in TcFlatten. >--------------------------------------------------------------- 37785df6febb50350bdc7967e7361eb68ee24425 testsuite/tests/perf/compiler/T5837.hs | 40 +++++++++++++++++++++++++++++----- testsuite/tests/perf/compiler/all.T | 4 +++- 2 files changed, 38 insertions(+), 6 deletions(-) diff --git a/testsuite/tests/perf/compiler/T5837.hs b/testsuite/tests/perf/compiler/T5837.hs index 1dc3c33..6ebbd65 100644 --- a/testsuite/tests/perf/compiler/T5837.hs +++ b/testsuite/tests/perf/compiler/T5837.hs @@ -10,14 +10,44 @@ t = undefined {- - [G] a ~ TF (a,Int) + [G] a ~ TF (a,Int) -- a = a_am1 --> - TF (a,Int) ~ fsk - fsk ~ a + [G] TF (a,Int) ~ fsk -- fsk = fsk_am8 +inert [G] fsk ~ a + ---> - fsk ~ (TF a, TF Int) - fsk ~ a + [G] fsk ~ (TF a, TF Int) +inert [G] fsk ~ a + ---> a ~ (TF a, TF Int) +inert [G] fsk ~ a + +---> (attempting to flatten (TF a) so that it does not mention a + TF a ~ fsk2 +inert a ~ (fsk2, TF Int) +inert fsk ~ (fsk2, TF Int) + +---> (substitute for a) + TF (fsk2, TF Int) ~ fsk2 +inert a ~ (fsk2, TF Int) +inert fsk ~ (fsk2, TF Int) + +---> (top-level reduction, re-orient) + fsk2 ~ (TF fsk2, TF Int) +inert a ~ (fsk2, TF Int) +inert fsk ~ (fsk2, TF Int) + +---> (attempt to flatten (TF fsk2) to get rid of fsk2 + TF fsk2 ~ fsk3 + fsk2 ~ (fsk3, TF Int) +inert a ~ (fsk2, TF Int) +inert fsk ~ (fsk2, TF Int) + +---> + TF fsk2 ~ fsk3 +inert fsk2 ~ (fsk3, TF Int) +inert a ~ ((fsk3, TF Int), TF Int) +inert fsk ~ ((fsk3, TF Int), TF Int) -} \ No newline at end of file diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 1a9dfcb..3bce7ce 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -454,7 +454,7 @@ test('T5837', # 40000000 (x86/Linux) # 2013-11-13: 45520936 (x86/Windows, 64bit machine) # 2041-09-03: 37096484 (Windows laptop, w/w for INLINABLE things - (wordsize(64), 75765728, 10)]) + (wordsize(64), 651924880, 10)]) # sample: 3926235424 (amd64/Linux, 15/2/2012) # 2012-10-02 81879216 # 2012-09-20 87254264 amd64/Linux @@ -463,6 +463,8 @@ test('T5837', # for constraints solving # 2014-08-29 73639840 amd64/Linux, w/w for INLINABLE things # 2014-10-08 73639840 amd64/Linux, Burning Bridges and other small changes + # 2014-11-02 651924880 Linux, Accept big regression; + # See Note [An alternative story for the inert substitution] in TcFlatten ], compile_fail,['-ftype-function-depth=50']) From git at git.haskell.org Mon Nov 3 17:23:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 17:23:49 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Simon's major commit to re-engineer the constraint solver (78a0fcb) Message-ID: <20141103172349.C28CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Oct14 Link : http://ghc.haskell.org/trac/ghc/changeset/78a0fcb13046a86708d683350d844a77849f0ad5/ghc >--------------------------------------------------------------- commit 78a0fcb13046a86708d683350d844a77849f0ad5 Author: Simon Peyton Jones Date: Mon Nov 3 17:23:11 2014 +0000 Simon's major commit to re-engineer the constraint solver The driving change is this: * The canonical CFunEqCan constraints now have the form [G] F xis ~ fsk [W] F xis ~ fmv where fsk is a flatten-skolem, and fmv is a flatten-meta-variable Think of them as the name of the type-function application See Note [The flattening story] in TcFlatten. A flatten-meta-variable is distinguishable by its MetaInfo of FlatMetaTv This in turn led to an enormous cascade of other changes, which simplify and modularise the constraint solver. In particular: * Basic data types * I got rid of inert_solved_funeqs altogether. It serves no useful role that inert_flat_cache does not solve. * I added wl_implics to the WorkList, as a convenient place to accumulate newly-emitted implications; see Note [Residual implications] in TcSMonad. * I eliminated tcs_ty_binds altogether. These were the bindings for unification variables that we have now solved by unification. We kept them in a finite map and did the side-effecting unification later. But in cannonicalisation we had to look up in the side-effected mutable tyvars anyway, so nothing was being gained. Our original idea was that the solver would be pure, and would be a no-op if you discarded its results, but this was already not-true for implications since we update their evidence bindings in an imperative way. So rather than the uneasy compromise, it's now clearly imperative! * I split out the flatten/unflatten code into a new module, TcFlatten * I simplified and articulated explicitly the (rather hazy) invariants for the inert substitution inert_eqs. See Note [eqCanRewrite] and See Note [Applying the inert substitution] in TcFlatten * Unflattening is now done (by TcFlatten.unflatten) after solveFlats, before solving nested implications. This turned out to simplify a lot of code. Previously, unflattening was done as part of zonking, at the very very end. * Eager unflattening allowed me to remove the unpleasant ic_fsks field of an Implication (hurrah) * Eager unflattening made the TcSimplify.floatEqualities function much simpler (just float equalities looking like a ~ ty, where a is an untouchable meta-tyvar). * Likewise the idea of "pushing wanteds in as givens" could be completely eliminated. * I radically simplified the code that determines when there are 'given' equalities, and hence whether we can float 'wanted' equalies out. See TcSMonad.getNoGivenEqs, and Note [When does an implication have given equalities?]. This allowed me to get rid of the unpleasant inert_no_eqs flag in InertCans. * As part of this given-equality stuff, I fixed Trac #9211. See Note [Let-bound skolems] in TcSMonad * Orientation of tyvar/tyvar equalities (a ~ b) was partly done during canonicalisation, but then repeated in the spontaneous-solve stage (trySpontaneousSolveTwoWay). Now it is done exclusively during canonicalisation, which keeps all the code in one place. See Note [Canonical orientation for tyvar/tyvar equality constraints] in TcCanonical >--------------------------------------------------------------- 78a0fcb13046a86708d683350d844a77849f0ad5 compiler/ghc.cabal.in | 1 + compiler/typecheck/Flattening-notes | 13 +- compiler/typecheck/Inst.lhs | 19 +- compiler/typecheck/TcCanonical.lhs | 929 ++++++++------------------- compiler/typecheck/TcFlatten.lhs | 1147 +++++++++++++++++++++++++++++++++ compiler/typecheck/TcInteract.lhs | 895 +++++++++++++------------- compiler/typecheck/TcMType.lhs | 139 +--- compiler/typecheck/TcRnTypes.lhs | 185 +++--- compiler/typecheck/TcRules.lhs | 2 - compiler/typecheck/TcSMonad.lhs | 1205 ++++++++++++++++++----------------- compiler/typecheck/TcSimplify.lhs | 403 +++++------- compiler/typecheck/TcType.lhs | 107 +++- compiler/typecheck/TcUnify.lhs | 1 - 13 files changed, 2835 insertions(+), 2211 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 78a0fcb13046a86708d683350d844a77849f0ad5 From git at git.haskell.org Mon Nov 3 18:51:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 18:51:25 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9209 in th/T9209 (6f92ff8) Message-ID: <20141103185125.E23B53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/6f92ff847792d8482191ce2aab4218b89611f37c/ghc >--------------------------------------------------------------- commit 6f92ff847792d8482191ce2aab4218b89611f37c Author: Richard Eisenberg Date: Mon Nov 3 13:46:58 2014 -0500 Test #9209 in th/T9209 >--------------------------------------------------------------- 6f92ff847792d8482191ce2aab4218b89611f37c testsuite/tests/th/T9209.hs | 5 +++++ testsuite/tests/th/T9209.stderr | 4 ++++ testsuite/tests/th/all.T | 1 + 3 files changed, 10 insertions(+) diff --git a/testsuite/tests/th/T9209.hs b/testsuite/tests/th/T9209.hs new file mode 100644 index 0000000..46740ba --- /dev/null +++ b/testsuite/tests/th/T9209.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T9209 where + +foo = let $( [d| x = 5 |] ) in x diff --git a/testsuite/tests/th/T9209.stderr b/testsuite/tests/th/T9209.stderr new file mode 100644 index 0000000..1f4f3e7 --- /dev/null +++ b/testsuite/tests/th/T9209.stderr @@ -0,0 +1,4 @@ + +T9209.hs:5:11: + Declaration splices are allowed only at the top level: + $([d| x = 5 |]) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index c7045c4..5151fd7 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -336,3 +336,4 @@ test('T8953', normal, compile, ['-v0']) test('T9084', normal, compile_fail, ['-v0']) test('T9738', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) +test('T9209', expect_broken(9209), compile_fail, ['-v0']) From git at git.haskell.org Mon Nov 3 18:51:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 18:51:28 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9209, by reporting an error instead of panicking on bad splices. (e860bac) Message-ID: <20141103185128.8864B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/e860bacd80c385af5a2301f20937046935559ef8/ghc >--------------------------------------------------------------- commit e860bacd80c385af5a2301f20937046935559ef8 Author: Richard Eisenberg Date: Mon Nov 3 13:49:59 2014 -0500 Fix #9209, by reporting an error instead of panicking on bad splices. >--------------------------------------------------------------- e860bacd80c385af5a2301f20937046935559ef8 compiler/parser/Parser.y.pp | 15 ++++++------ compiler/parser/RdrHsSyn.lhs | 57 +++++++++++++++++++++++++------------------- testsuite/tests/th/all.T | 2 +- 3 files changed, 42 insertions(+), 32 deletions(-) diff --git a/compiler/parser/Parser.y.pp b/compiler/parser/Parser.y.pp index e33808d..98468d4 100644 --- a/compiler/parser/Parser.y.pp +++ b/compiler/parser/Parser.y.pp @@ -684,12 +684,12 @@ ty_decl :: { LTyClDecl RdrName } inst_decl :: { LInstDecl RdrName } : 'instance' overlap_pragma inst_type where_inst - { let (binds, sigs, _, ats, adts, _) = cvBindsAndSigs (unLoc $4) in - let cid = ClsInstDecl { cid_poly_ty = $3, cid_binds = binds - , cid_sigs = sigs, cid_tyfam_insts = ats - , cid_overlap_mode = $2 - , cid_datafam_insts = adts } - in L (comb3 $1 $3 $4) (ClsInstD { cid_inst = cid }) } + {% do { (binds, sigs, _, ats, adts, _) <- cvBindsAndSigs (unLoc $4) + ; let cid = ClsInstDecl { cid_poly_ty = $3, cid_binds = binds + , cid_sigs = sigs, cid_tyfam_insts = ats + , cid_overlap_mode = $2 + , cid_datafam_insts = adts } + ; return (L (comb3 $1 $3 $4) (ClsInstD { cid_inst = cid })) } } -- type instance declarations | 'type' 'instance' ty_fam_inst_eqn @@ -950,7 +950,8 @@ decllist :: { Located (OrdList (LHsDecl RdrName)) } -- binds :: { Located (HsLocalBinds RdrName) } -- May have implicit parameters -- No type declarations - : decllist { L1 (HsValBinds (cvBindGroup (unLoc $1))) } + : decllist {% do { val_binds <- cvBindGroup (unLoc $1) + ; return (L1 (HsValBinds val_binds)) } } | '{' dbinds '}' { LL (HsIPBinds (IPBinds (unLoc $2) emptyTcEvBinds)) } | vocurly dbinds close { L (getLoc $2) (HsIPBinds (IPBinds (unLoc $2) emptyTcEvBinds)) } diff --git a/compiler/parser/RdrHsSyn.lhs b/compiler/parser/RdrHsSyn.lhs index e6969e7..125bfa9 100644 --- a/compiler/parser/RdrHsSyn.lhs +++ b/compiler/parser/RdrHsSyn.lhs @@ -127,8 +127,8 @@ mkClassDecl :: SrcSpan -> P (LTyClDecl RdrName) mkClassDecl loc (L _ (mcxt, tycl_hdr)) fds where_cls - = do { let (binds, sigs, ats, at_insts, _, docs) = cvBindsAndSigs (unLoc where_cls) - cxt = fromMaybe (noLoc []) mcxt + = do { (binds, sigs, ats, at_insts, _, docs) <- cvBindsAndSigs (unLoc where_cls) + ; let cxt = fromMaybe (noLoc []) mcxt ; (cls, tparams) <- checkTyClHdr tycl_hdr ; tyvars <- checkTyVarsP (ptext (sLit "class")) whereDots cls tparams ; at_defs <- mapM (eitherToP . mkATDefault) at_insts @@ -308,36 +308,45 @@ cvTopDecls decls = go (fromOL decls) go (d : ds) = d : go ds -- Declaration list may only contain value bindings and signatures. -cvBindGroup :: OrdList (LHsDecl RdrName) -> HsValBinds RdrName +cvBindGroup :: OrdList (LHsDecl RdrName) -> P (HsValBinds RdrName) cvBindGroup binding - = case cvBindsAndSigs binding of - (mbs, sigs, fam_ds, tfam_insts, dfam_insts, _) - -> ASSERT( null fam_ds && null tfam_insts && null dfam_insts) - ValBindsIn mbs sigs + = do { (mbs, sigs, fam_ds, tfam_insts, dfam_insts, _) <- cvBindsAndSigs binding + ; ASSERT( null fam_ds && null tfam_insts && null dfam_insts) + return $ ValBindsIn mbs sigs } cvBindsAndSigs :: OrdList (LHsDecl RdrName) - -> (LHsBinds RdrName, [LSig RdrName], [LFamilyDecl RdrName] + -> P (LHsBinds RdrName, [LSig RdrName], [LFamilyDecl RdrName] , [LTyFamInstDecl RdrName], [LDataFamInstDecl RdrName], [LDocDecl]) -- Input decls contain just value bindings and signatures -- and in case of class or instance declarations also -- associated type declarations. They might also contain Haddock comments. -cvBindsAndSigs fb = go (fromOL fb) +cvBindsAndSigs fb = go (fromOL fb) where - go [] = (emptyBag, [], [], [], [], []) - go (L l (SigD s) : ds) = (bs, L l s : ss, ts, tfis, dfis, docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L l (ValD b) : ds) = (b' `consBag` bs, ss, ts, tfis, dfis, docs) - where (b', ds') = getMonoBind (L l b) ds - (bs, ss, ts, tfis, dfis, docs) = go ds' - go (L l (TyClD (FamDecl t)) : ds) = (bs, ss, L l t : ts, tfis, dfis, docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L l (InstD (TyFamInstD { tfid_inst = tfi })) : ds) = (bs, ss, ts, L l tfi : tfis, dfis, docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L l (InstD (DataFamInstD { dfid_inst = dfi })) : ds) = (bs, ss, ts, tfis, L l dfi : dfis, docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L l (DocD d) : ds) = (bs, ss, ts, tfis, dfis, (L l d) : docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L _ d : _) = pprPanic "cvBindsAndSigs" (ppr d) + go [] = return (emptyBag, [], [], [], [], []) + go (L l (ValD b) : ds) + = do { (bs, ss, ts, tfis, dfis, docs) <- go ds' + ; return (b' `consBag` bs, ss, ts, tfis, dfis, docs) } + where + (b', ds') = getMonoBind (L l b) ds + go (L l decl : ds) + = do { (bs, ss, ts, tfis, dfis, docs) <- go ds + ; case decl of + SigD s + -> return (bs, L l s : ss, ts, tfis, dfis, docs) + TyClD (FamDecl t) + -> return (bs, ss, L l t : ts, tfis, dfis, docs) + InstD (TyFamInstD { tfid_inst = tfi }) + -> return (bs, ss, ts, L l tfi : tfis, dfis, docs) + InstD (DataFamInstD { dfid_inst = dfi }) + -> return (bs, ss, ts, tfis, L l dfi : dfis, docs) + DocD d + -> return (bs, ss, ts, tfis, dfis, L l d : docs) + SpliceD d + -> parseErrorSDoc l $ + hang (text "Declaration splices are allowed only" <+> + text "at the top level:") + 2 (ppr d) + _ -> pprPanic "cvBindsAndSigs" (ppr decl) } ----------------------------------------------------------------------------- -- Group function bindings into equation groups diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 5151fd7..f72bf45 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -336,4 +336,4 @@ test('T8953', normal, compile, ['-v0']) test('T9084', normal, compile_fail, ['-v0']) test('T9738', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) -test('T9209', expect_broken(9209), compile_fail, ['-v0']) +test('T9209', normal, compile_fail, ['-v0']) From git at git.haskell.org Mon Nov 3 19:26:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 19:26:25 +0000 (UTC) Subject: [commit: ghc] master: Link to oneShot from the User's Guide (1c0b736) Message-ID: <20141103192625.6F9D33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1c0b7362068d05b68bd7e05c4d2ef51da9533bf7/ghc >--------------------------------------------------------------- commit 1c0b7362068d05b68bd7e05c4d2ef51da9533bf7 Author: Joachim Breitner Date: Mon Nov 3 20:26:25 2014 +0100 Link to oneShot from the User's Guide thanks to Jan for nudging. >--------------------------------------------------------------- 1c0b7362068d05b68bd7e05c4d2ef51da9533bf7 docs/users_guide/glasgow_exts.xml | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 7aff1a7..06c1b3b 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -11531,6 +11531,10 @@ allows control over inlining on a per-call-site basis. lazy restrains the strictness analyser. + +oneShot +gives a hint to the compiler about how often a function is being called. + From git at git.haskell.org Mon Nov 3 20:39:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 20:39:46 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #7484, checking for good binder names in Convert. (d8b3074) Message-ID: <20141103203946.28DFD3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/d8b3074c97f91df24abf2c86e541fe974e1d31d2/ghc >--------------------------------------------------------------- commit d8b3074c97f91df24abf2c86e541fe974e1d31d2 Author: Richard Eisenberg Date: Mon Nov 3 15:34:53 2014 -0500 Fix #7484, checking for good binder names in Convert. This includes a somewhat pedantic check against the code in Lexer.x to make sure that TH accepts the same set of names that the lexer does. Doing this unearthed a latent bug dealing with unicode identifiers in OccName. >--------------------------------------------------------------- d8b3074c97f91df24abf2c86e541fe974e1d31d2 compiler/basicTypes/OccName.lhs | 5 +- compiler/hsSyn/Convert.lhs | 123 +++++++++++++++++++++++++++++++++++++--- testsuite/tests/th/all.T | 2 +- 3 files changed, 121 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/OccName.lhs b/compiler/basicTypes/OccName.lhs index 0010ad3..dc86991 100644 --- a/compiler/basicTypes/OccName.lhs +++ b/compiler/basicTypes/OccName.lhs @@ -905,7 +905,10 @@ isLexVarSym fs -- Infix identifiers e.g. "+" startsVarSym, startsVarId, startsConSym, startsConId :: Char -> Bool startsVarSym c = isSymbolASCII c || (ord c > 0x7f && isSymbol c) -- Infix Ids startsConSym c = c == ':' -- Infix data constructors -startsVarId c = isLower c || c == '_' -- Ordinary Ids +startsVarId c = c == '_' || case generalCategory c of -- Ordinary Ids + LowercaseLetter -> True + OtherLetter -> True -- See #1103 + _ -> False startsConId c = isUpper c || c == '(' -- Ordinary type constructors and data constructors isSymbolASCII :: Char -> Bool diff --git a/compiler/hsSyn/Convert.lhs b/compiler/hsSyn/Convert.lhs index 6cff928..243903a 100644 --- a/compiler/hsSyn/Convert.lhs +++ b/compiler/hsSyn/Convert.lhs @@ -45,6 +45,8 @@ import Data.Maybe( catMaybes ) import Language.Haskell.TH as TH hiding (sigP) import Language.Haskell.TH.Syntax as TH import GHC.Exts +import Data.Char +import qualified Data.Set as Set ------------------------------------------------------------------- -- The external interface @@ -1109,13 +1111,120 @@ cvtName ctxt_ns (TH.Name occ flavour) occ_str = TH.occString occ okOcc :: OccName.NameSpace -> String -> Bool -okOcc _ [] = False -okOcc ns str@(c:_) - | OccName.isVarNameSpace ns = startsVarId c || startsVarSym c - | OccName.isDataConNameSpace ns = startsConId c || startsConSym c || str == "[]" - | otherwise = startsConId c || startsConSym c || - startsVarSym c || str == "[]" || str == "->" - -- allow type operators like "+" +okOcc ns str + | OccName.isVarNameSpace ns = okVarOcc str + | OccName.isDataConNameSpace ns = okConOcc str + | otherwise = okTcOcc str + +-- | Is this an acceptable variable name? +okVarOcc :: String -> Bool +okVarOcc str@(c:_) + | startsVarId c + = okVarIdOcc str + | startsVarSym c + = okVarSymOcc str +okVarOcc _ = False + +-- | Is this an acceptable alphanumeric variable name, assuming it starts +-- with an acceptable letter? +okVarIdOcc :: String -> Bool +okVarIdOcc str = all okIdChar str && + not (str `Set.member` reservedIds) + +-- | Is this an acceptable symbolic variable name, assuming it starts +-- with an acceptable character? +okVarSymOcc :: String -> Bool +okVarSymOcc str = all okSymChar str && + not (str `Set.member` reservedOps) && + not (isDashes str) + +-- | Is this an acceptable constructor name? +okConOcc :: String -> Bool +okConOcc str@(c:_) + | startsConId c + = okConIdOcc str + | startsConSym c + = okConSymOcc str + | str == "[]" + = True +okConOcc _ = False + +-- | Is this an acceptable alphanumeric constructor name, assuming it +-- starts with an acceptable letter? +okConIdOcc :: String -> Bool +okConIdOcc = all okIdChar + +-- | Is this an acceptable symbolic constructor name, assuming it +-- starts with an acceptable character? +okConSymOcc :: String -> Bool +okConSymOcc str = all okSymChar str && + not (str `Set.member` reservedOps) + +-- | Is this an acceptable type name? +okTcOcc :: String -> Bool +okTcOcc str@(c:_) + | startsConId c + = okConIdOcc str + | startsConSym c + = okConSymOcc str + | startsVarSym c + = okVarSymOcc str + | str == "[]" || str == "->" + = True +okTcOcc _ = False + +-- | Is this character acceptable in an identifier (after the first letter)? +-- See alexGetByte in Lexer.x +okIdChar :: Char -> Bool +okIdChar c = case generalCategory c of + UppercaseLetter -> True + LowercaseLetter -> True + OtherLetter -> True + TitlecaseLetter -> True + DecimalNumber -> True + OtherNumber -> True + _ -> c == '\'' || c == '_' + +-- | Is this character acceptable in a symbol (after the first char)? +-- See alexGetByte in Lexer.x +okSymChar :: Char -> Bool +okSymChar c + | c `elem` specialSymbols + = False + | c `elem` "_\"'" + = False + | otherwise + = case generalCategory c of + ConnectorPunctuation -> True + DashPunctuation -> True + OtherPunctuation -> True + MathSymbol -> True + CurrencySymbol -> True + ModifierSymbol -> True + OtherSymbol -> True + _ -> False + +-- | All reserved identifiers. Taken from section 2.4 of the 2010 Report. +reservedIds :: Set.Set String +reservedIds = Set.fromList [ "case", "class", "data", "default", "deriving" + , "do", "else", "foreign", "if", "import", "in" + , "infix", "infixl", "infixr", "instance", "let" + , "module", "newtype", "of", "then", "type", "where" + , "_" ] + +-- | All punctuation that cannot appear in symbols. See $special in Lexer.x. +specialSymbols :: [Char] +specialSymbols = "(),;[]`{}" + +-- | All reserved operators. Taken from section 2.4 of the 2010 Report. +reservedOps :: Set.Set String +reservedOps = Set.fromList [ "..", ":", "::", "=", "\\", "|", "<-", "->" + , "@", "~", "=>" ] + +-- | Does this string contain only dashes and has at least 2 of them? +isDashes :: String -> Bool +isDashes ('-' : '-' : rest) = all (== '-') rest +isDashes _ = False -- Determine the name space of a name in a type -- diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 4f71fd2..4fd131a 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -337,4 +337,4 @@ test('T9084', normal, compile_fail, ['-v0']) test('T9738', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) -test('T7484', expect_broken(7484), compile_fail, ['-v0']) +test('T7484', normal, compile_fail, ['-v0']) From git at git.haskell.org Mon Nov 3 20:39:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 20:39:43 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #7484 in th/T7484 (6b0d4d8) Message-ID: <20141103203943.969323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/6b0d4d8347caf7f2a5e89c1f3d648fa3469ac39d/ghc >--------------------------------------------------------------- commit 6b0d4d8347caf7f2a5e89c1f3d648fa3469ac39d Author: Richard Eisenberg Date: Mon Nov 3 15:33:51 2014 -0500 Test #7484 in th/T7484 >--------------------------------------------------------------- 6b0d4d8347caf7f2a5e89c1f3d648fa3469ac39d testsuite/tests/th/T7484.hs | 7 +++++++ testsuite/tests/th/T7484.stderr | 4 ++++ testsuite/tests/th/all.T | 1 + 3 files changed, 12 insertions(+) diff --git a/testsuite/tests/th/T7484.hs b/testsuite/tests/th/T7484.hs new file mode 100644 index 0000000..b1a9cba --- /dev/null +++ b/testsuite/tests/th/T7484.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T7484 where + +import Language.Haskell.TH + +$( return [ ValD (VarP (mkName "a ")) (NormalB (LitE (IntegerL 5))) [] ] ) diff --git a/testsuite/tests/th/T7484.stderr b/testsuite/tests/th/T7484.stderr new file mode 100644 index 0000000..3ffe123 --- /dev/null +++ b/testsuite/tests/th/T7484.stderr @@ -0,0 +1,4 @@ + +T7484.hs:7:4: + Illegal variable name: ?a ? + When splicing a TH declaration: a = 5 diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index f72bf45..4f71fd2 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -337,3 +337,4 @@ test('T9084', normal, compile_fail, ['-v0']) test('T9738', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) +test('T7484', expect_broken(7484), compile_fail, ['-v0']) From git at git.haskell.org Mon Nov 3 22:32:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 22:32:14 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData: More work (50e56bc) Message-ID: <20141103223214.058F43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData Link : http://ghc.haskell.org/trac/ghc/changeset/50e56bc8867c8ba17adfa06f9e513c77882072ee/ghc >--------------------------------------------------------------- commit 50e56bc8867c8ba17adfa06f9e513c77882072ee Author: Jose Pedro Magalhaes Date: Thu Oct 30 18:47:19 2014 +0000 More work >--------------------------------------------------------------- 50e56bc8867c8ba17adfa06f9e513c77882072ee compiler/prelude/PrelNames.lhs | 57 ++++--- compiler/typecheck/TcDeriv.lhs | 38 +---- compiler/typecheck/TcGenGenerics.lhs | 286 +++++--------------------------- libraries/base/Data/Monoid.hs | 1 + libraries/base/GHC/Generics.hs | 54 +++--- testsuite/tests/generics/GShow/GShow.hs | 1 + 6 files changed, 109 insertions(+), 328 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 50e56bc8867c8ba17adfa06f9e513c77882072ee From git at git.haskell.org Mon Nov 3 22:32:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 22:32:17 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData: Merge branch 'wip/new-flatten-skolems-Oct14' into wip/GenericsMetaData (7dba4dc) Message-ID: <20141103223217.689623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData Link : http://ghc.haskell.org/trac/ghc/changeset/7dba4dc7eabaeb3f93c31f7a31dd68cb3e7a16c1/ghc >--------------------------------------------------------------- commit 7dba4dc7eabaeb3f93c31f7a31dd68cb3e7a16c1 Merge: 50e56bc 78a0fcb Author: Jose Pedro Magalhaes Date: Mon Nov 3 22:30:29 2014 +0000 Merge branch 'wip/new-flatten-skolems-Oct14' into wip/GenericsMetaData Conflicts: compiler/typecheck/TcDeriv.lhs compiler/typecheck/TcGenGenerics.lhs >--------------------------------------------------------------- Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7dba4dc7eabaeb3f93c31f7a31dd68cb3e7a16c1 From git at git.haskell.org Mon Nov 3 22:32:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Nov 2014 22:32:20 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData's head updated: Merge branch 'wip/new-flatten-skolems-Oct14' into wip/GenericsMetaData (7dba4dc) Message-ID: <20141103223220.94D353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/GenericsMetaData' now includes: d6d5c12 Revert "Use dropWhileEndLE p instead of reverse . dropWhile p . reverse" 9bf5228 Use dropWhileEndLE p instead of reverse . dropWhile p . reverse eb191ab rts/PrimOps.cmm: follow '_static_closure' update eb35339 Really fix dropWhileEndLE commit 2b59c7a arclint: Don't complain about tabs unless it's inside the diff. 582217f Comments only (instances for Proxy are lazy) e4a597f Revert "Basic Python 3 support for testsuite driver (Trac #9184)" 4977efc Restore spaces instead of tabs, caused by revert of Python 3 2fc0c6c Check for staticclosures section in Windows linker. e8dac6d Fix typo in section name: no leading period. 2a8ea47 ghc.mk: fix list for dll-split on GHCi-less builds 3549c95 Implement `MIN_VERSION_GLASGOW_HASKELL()` macro cb0a503 rts: unrust 'libbfd' debug symbols parser 6a36636 testsuite: fix tcrun036 build against Prelude/Main 'traverse' clash a1b5391 testsuite: fix T5751 build failure (AMP) b30b185 testsuite: fix T1735_Help/State.hs build failure (AMP) 6ecf19c testsuite: fix seward-space-leak build aganst Prelude/Main 'traverse' clash 48089cc Use correct precedence when printing contexts with class operators 85aba49 Merge branch 'master' of http://git.haskell.org/ghc 3c5648a Fix a typo in an error message 460eebe Remove RAWCPP_FLAGS b3e5a7b Delete __GLASGOW_HASKELL__ ifdefs for stage0 < 7.6. 2ee2527 Remove unused hashName declaration adcb9db Add support for LINE pragma in template-haskell 1ec9113 Fix configure check for 9439 bug 1f92420 configure in base: add msys to windows check 9ebbdf3 Clean up and remove todo. 205b103 Fix closing parenthesis d45693a Make scanl fuse; add scanl' bdb0c43 Code size micro-optimizations in the X86 backend ffde9d2 testsuite: T5486 requires integer-gmp internals e87135c Bump haddock.base perf numbers 6f2eca1 Use Data.Map.mergeWithKey 21dff57 Initial commit of the Backpack manual [skip ci] 21389bc Update some out-of-date things in Backpack implementation doc [skip ci] d14d3f9 Make Data.List.takeWhile fuse: fix #9132 eb6b04c Update T4801 perf numbers 0ed9a27 Preemptive performance number updates 5300099 Make the linker more robust to errors 267ad95 Ignore exe files in base (from tests) 39666ae Update haddock submodule with lazy IO fix. d3f56ec Rewrite section 1 of the Backpack manual. [skip ci] 674c631 Name worker threads using pthread_setname_np 97b7593 rts: don't crash on 'hs_init(NULL, NULL)' in debug rts ad4a713 Remove a few redundant `.hs-boot` files 1032554 Fallback to `ctypes.cdll` if `ctypes.windll` unavailable 034b203 Extend windows detection in testsuite to recognize MSYS target 1942fd6 Refactor to avoid need for `Unicode.hs-boot` a36991b Fix build on some platforms c375de0 Update `time` submodule to address linker issue 05f962d Compiler performance benchmark for #9675 23da971 Adjust T9675 baseline numbers based on ghc-speed d9db81f seqDmdType needs to seq the DmdEnv as well 3575109 Update more performance numbers due to stricter seqDmdType f3ae936 T9675: Allow Much wider range of values f0af3d8 Actually put in new perf number for T4801 8376027 Fix comment typos: lll -> ll, THe -> The 4b69d96 Add a configure test for pthread_setname_np cde3a77 Make Data.List.Inits fast 7e73595 Make tails a good producer (#9670) d786781 Declare official GitHub home of libraries/deepseq a477e81 Avoid printing uniques in specialization rules 0e2bd03 Update T6056 output 1c35f9f rts: fix unused parameter warning 612f3d1 Implement optimized NCG `MO_Ctz W64` op for i386 (#9340) 7369d25 Remove obsolete Data.OldTypeable (#9639) ce23745 Generalise `Control.Monad.{foldM,foldM_}` to `Foldable` (#9586) abfbb0d Remove redundant explicit `Prelude` imports d576fc3 Python 3 support, second attempt (Trac #9184) b5930f8 Refactor module imports in base 5b9fe33 Indentation and non-semantic changes only. 4d90b53 Sync up `containers` submodule to latest `master`-tip 07da36b Revert "Fix typo in section name: no leading period." 0202b7c Revert "Check for staticclosures section in Windows linker." 89a8d81 Revert "Rename _closure to _static_closure, apply naming consistently." 126b0c4 Revert "Properly generate info tables for static closures in C--." a3860fc Revert "BC-breaking changes to C-- CLOSURE syntax." d5d6fb3 Revert "Place static closures in their own section." 47c4c91 Update Haddock submodule 07a99c1 Revert "rts/PrimOps.cmm: follow '_static_closure' update" f681c32 Test #9692 in th/T9692 2cd80ba Clarify location of Note. Comment change only. e319d6d Reify data family instances correctly. 710bc8d Update primitive, vector, and dph submodules. 27f7552 Make Applicative-Monad fixes for tests. 3687089 Updated testsuite/.gitignore to cover artifacts on Windows. 2cc2065 Use objdump instead of nm to derive constants on OpenBSD 9f29e03 ghc-prim: Use population count appropriate for platform d4fd168 Update to Unicode version 7.0 a5f4fb6 Remove extra period 3157127 Improve isDigit, isSpace, etc. ef2d027 Make findIndices fuse 1e269bf Make Data.List.concatMap fuse better 6825558 Add doctest examples for Data.Functor. 5211673 Fix typo in -XConstraintKinds docs 9c464f8 Add doctest examples for Data.Bool. c819958 Add release note about Unicode 7.0 69f6361 Fixes the ARM build 972ba12 Enabled warn on tabs by default (fixes #9230) 4faeecb [skip ci] rts: Detabify RtsMessages.c aa8d23d [skip ci] rts: Detabify RaiseAsync.h bb04867 [skip ci] rts: Detabify Capability.h 99edc35 [skip ci] rts: Detabify CheckUnload.c 6aa6ca8 [skip ci] rts: Detabify Profiling.c 570b339 [skip ci] rts: Detabify Threads.c 21eaaa1 [skip ci] rts: Detabify sm/Evac.c 9167d0e [skip ci] rts: Detabify sm/Scav.c 5bb8f14 [skip ci] rts: Detabify Stats.c 2dc21b9 [skip ci] rts: Detabify Schedule.h 1d12df3 [skip ci] rts: Detabify LdvProfile.h 3d0e695 [skip ci] rts: Detabify Proftimer.c 68c45b6 [skip ci] rts: Detabify Exception.cmm a7ab7d3 [skip ci] rts: Detabify HeapStackCheck.cmm 6811e53 [skip ci] rts: Detabify Capability.c beb5c2e [skip ci] rts: Detabify RaiseAsync.c e13478f [skip ci] rts: Detabify sm/GC.c faa3339 [skip ci] rts: Detabify sm/Sanity.c bc1609a [skip ci] rts: Detabify sm/Compact.c c8173d5 [skip ci] rts: Detabify sm/Compact.h 5106e20 [skip ci] rts: Detabify RetainerProfile.c 03c3e9a [skip ci] rts: Detabify ProfHeap.c 6abb34c [skip ci] rts: Detabify Schedule.c 9bfe602 rts: Detabify Interpreter.c df5c11a base: Mark WCsubst.c as generated for Phabricator 45cbe85 Flush stdout in T9692 aa641e5 Add forgotten import to T9692 a11f71e Fix a rare parallel GC bug 427925d More updates to Backpack manual [skip ci] 5bb73d7 Check in up-to-date PDF copies of Backpack docs. [skip ci] aa47995 Implementation of hsig (module signatures), per #9252 1addef8 Fix windows build failure. 73c7ea7 fix a typo in comments: normaliseFfiType 0855b24 Pass in CXX to libffi's configure script. 7b59db2 `M-x delete-trailing-whitespace` & `M-x untabify` a3312c3 testsuite: Fix outdated output for T5979/safePkg01 0a290ca Add new `Data.Bifunctor` module (re #9682) 9e2cb00 Optimise atomicModifyIORef' implementation (#8345) 0e1f0f7 Un-wire `Integer` type (re #9714) 0013613 Deactivate T3064 `max_bytes_used`-check 49b05d6 Improve performance of isSuffixOf (#9676) 1874501 Typo in comment aa2ceba Normalise package key hash to make tests less fragile. 63918e6 Add n-ary version of `two_normalisers` to testsuite lib 3d6422b testlib: Get rid of two_normalisers 98ed815 Make iterateFB inlineable 75979f3 base: Refactor/clean-up *List modules 5f69c8e Reorder GHC.List; fix performance regressions f109085 Update Haddock submodule for collapsible section support 64d0a19 Really fix fft2 regression. #9740 208a0c2 Fixed unused variable warning on mingw32/i686 in rts/Linker.c f9ca529 hsc2hs: Update submodule 322810e Convert GHCi sources from .lhs to .hs 257cbec Fix #9236 Error on read from closed handle 5ce1266 Use snwprintf instead of swprintf in rts/Linker.c. acb3295 Avoid setting -Werror=unused-but-set-variable on Windows. 45175e1 Extra CRs are now filtered out from the source file for :list. f10b67a Updated stale ghcpkg05.stderr-mingw32. 3d27f69 Do not use a relative path for echo in tests/ghci/prog013. c211f8e Add __GLASGOW_HASKELL_TH__=YES/NO to CPP definitions 93c776a Added mingw32-specific expected stdout files for tests/driver/sigof{01,02,03} 9de5240 Comments only 50e56bc More work b52c345 Tidy up pretty-printing of SrcLoc and SrcSpan fe60b78 Improve pretty-printing of type variables e4a0a3e Some refactoring around endPass and debug dumping 68d3377 Simplify the generation of superclass constraints in tcInstDecl2 e741075 Add the unfolding and inline-pragma for DFuns in DsBinds, not TcInstDcls 3c7eec4 White space only 54e5a43 Fix reduceTyFamApp_maybe 9b888dd Simplify the API for tcInstTyVars, and make it more consistent with other similar functions 7b3c742 Rename setRole_maybe to downgradeRole_maybe 4290bda Refactor skolemising, and newClsInst 0ce46e7 Refactor the treatment of lexically-scoped type variables for instance declarations 446ced2 Get the Untouchables level right in simplifyInfer 23600fb Normalise the type of an inferred let-binding ac31ee3 Typechecker debug tracing only 69cdebf When reporting the context of given constraints, stop when you find one that binds a variable mentioned in the wanted 394ca3b Only report "could not deduce s~t from ..." for givens that include equalities ec5be5fb Don't filter out allegedly-irrelevant bindings with -dppr-debug f61b89f Minor refactoring (no change in functionality) 697444d Define ctEvLoc and ctEvCoercion, and use them d60edce Test Trac #9211 8075e43 Test Trac #9708 8aa08f2 Improve error message for a handwritten Typeable instance bfadcaf Test Trac #9747 1ca7670 Add comments explaining ProbOneShot c140398 Test Trac #9739 87d89ea Fix the superclass-cycle detection code (Trac #9739) 9b82cfb Comments only b75d3e5 Testsuite error message changes 4fe6e76 Add flattening-notes a59bfa9 Make this test a bit simpler 37785df Compiler performance is much worse in for loopy givens 78a0fcb Simon's major commit to re-engineer the constraint solver 7dba4dc Merge branch 'wip/new-flatten-skolems-Oct14' into wip/GenericsMetaData From git at git.haskell.org Tue Nov 4 01:29:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 01:29:48 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #1476 in th/T1476 (225131d) Message-ID: <20141104012948.70EA63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/225131dcc2fe82616ba983f98e1af883b15113f5/ghc >--------------------------------------------------------------- commit 225131dcc2fe82616ba983f98e1af883b15113f5 Author: Richard Eisenberg Date: Mon Nov 3 20:26:14 2014 -0500 Test #1476 in th/T1476 >--------------------------------------------------------------- 225131dcc2fe82616ba983f98e1af883b15113f5 testsuite/tests/th/T1476.hs | 8 ++++++++ testsuite/tests/th/all.T | 1 + 2 files changed, 9 insertions(+) diff --git a/testsuite/tests/th/T1476.hs b/testsuite/tests/th/T1476.hs new file mode 100644 index 0000000..2554d9e --- /dev/null +++ b/testsuite/tests/th/T1476.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T1476 where + +import Language.Haskell.TH + +foo $( return $ VarP $ mkName "x" ) = x +bar $( [p| x |] ) = x diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 4fd131a..c9c0cbe 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -338,3 +338,4 @@ test('T9738', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) +test('T1476', expect_broken(1476), compile, ['-v0']) From git at git.haskell.org Tue Nov 4 01:29:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 01:29:51 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #1476 by allowing pattern splices to bind variables. (e08b457) Message-ID: <20141104012951.117463A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/e08b457f470aa74322ff9af70fb26f55d81b2481/ghc >--------------------------------------------------------------- commit e08b457f470aa74322ff9af70fb26f55d81b2481 Author: Richard Eisenberg Date: Mon Nov 3 20:20:41 2014 -0500 Fix #1476 by allowing pattern splices to bind variables. Operationally, this is quite simple: just rename the RHS of a pattern in the right scope, after running a pattern splice. Now that splices are run in the renamer, this is easy. From a coding standpoint, it's rather painful, because there's a moderate-sized impedance mismatch between the code in RnPat and RnSplice. The monads are different (CpsRn vs RnM) as are the callback types in a call to rnSpliceGen. Throw in the necessity of lhs-boot files, and it all gets a little ugly. Suggestions to make this less ugly are strongly encouraged. >--------------------------------------------------------------- e08b457f470aa74322ff9af70fb26f55d81b2481 compiler/rename/RnPat.lhs | 49 +++++++++++++++++++++++++++---- compiler/rename/RnSplice.lhs | 61 ++++++++++++++------------------------- compiler/rename/RnSplice.lhs-boot | 8 ++++- testsuite/tests/th/all.T | 2 +- 4 files changed, 72 insertions(+), 48 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e08b457f470aa74322ff9af70fb26f55d81b2481 From git at git.haskell.org Tue Nov 4 02:10:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 02:10:11 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #7484, checking for good binder names in Convert. (d10ec68) Message-ID: <20141104021011.5CDA13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/d10ec6831fca74e8e8f917ec32a89711f33e33db/ghc >--------------------------------------------------------------- commit d10ec6831fca74e8e8f917ec32a89711f33e33db Author: Richard Eisenberg Date: Mon Nov 3 15:34:53 2014 -0500 Fix #7484, checking for good binder names in Convert. This includes a somewhat pedantic check against the code in Lexer.x to make sure that TH accepts the same set of names that the lexer does. Doing this unearthed a latent bug dealing with unicode identifiers in OccName. >--------------------------------------------------------------- d10ec6831fca74e8e8f917ec32a89711f33e33db compiler/basicTypes/OccName.lhs | 5 +- compiler/hsSyn/Convert.lhs | 137 ++++++++++++++++++++++++++++++++++++++-- testsuite/tests/th/all.T | 2 +- 3 files changed, 135 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/OccName.lhs b/compiler/basicTypes/OccName.lhs index 0010ad3..dc86991 100644 --- a/compiler/basicTypes/OccName.lhs +++ b/compiler/basicTypes/OccName.lhs @@ -905,7 +905,10 @@ isLexVarSym fs -- Infix identifiers e.g. "+" startsVarSym, startsVarId, startsConSym, startsConId :: Char -> Bool startsVarSym c = isSymbolASCII c || (ord c > 0x7f && isSymbol c) -- Infix Ids startsConSym c = c == ':' -- Infix data constructors -startsVarId c = isLower c || c == '_' -- Ordinary Ids +startsVarId c = c == '_' || case generalCategory c of -- Ordinary Ids + LowercaseLetter -> True + OtherLetter -> True -- See #1103 + _ -> False startsConId c = isUpper c || c == '(' -- Ordinary type constructors and data constructors isSymbolASCII :: Char -> Bool diff --git a/compiler/hsSyn/Convert.lhs b/compiler/hsSyn/Convert.lhs index 6cff928..6f2b14d 100644 --- a/compiler/hsSyn/Convert.lhs +++ b/compiler/hsSyn/Convert.lhs @@ -45,6 +45,8 @@ import Data.Maybe( catMaybes ) import Language.Haskell.TH as TH hiding (sigP) import Language.Haskell.TH.Syntax as TH import GHC.Exts +import Data.Char +import qualified Data.Set as Set ------------------------------------------------------------------- -- The external interface @@ -1109,13 +1111,134 @@ cvtName ctxt_ns (TH.Name occ flavour) occ_str = TH.occString occ okOcc :: OccName.NameSpace -> String -> Bool -okOcc _ [] = False -okOcc ns str@(c:_) - | OccName.isVarNameSpace ns = startsVarId c || startsVarSym c - | OccName.isDataConNameSpace ns = startsConId c || startsConSym c || str == "[]" - | otherwise = startsConId c || startsConSym c || - startsVarSym c || str == "[]" || str == "->" - -- allow type operators like "+" +okOcc ns str + | OccName.isVarNameSpace ns = okVarOcc str + | OccName.isDataConNameSpace ns = okConOcc str + | otherwise = okTcOcc str + +-- | Is this an acceptable variable name? +okVarOcc :: String -> Bool +okVarOcc str@(c:_) + | startsVarId c + = okVarIdOcc str + | startsVarSym c + = okVarSymOcc str +okVarOcc _ = False + +-- | Is this an acceptable alphanumeric variable name, assuming it starts +-- with an acceptable letter? +okVarIdOcc :: String -> Bool +okVarIdOcc str = all okIdChar str && + not (str `Set.member` reservedIds) + +-- | Is this an acceptable symbolic variable name, assuming it starts +-- with an acceptable character? +okVarSymOcc :: String -> Bool +okVarSymOcc str = all okSymChar str && + not (str `Set.member` reservedOps) && + not (isDashes str) + +-- | Is this an acceptable constructor name? +okConOcc :: String -> Bool +okConOcc str@(c:_) + | startsConId c + = okConIdOcc str + | startsConSym c + = okConSymOcc str + | str == "[]" + = True +okConOcc _ = False + +-- | Is this an acceptable alphanumeric constructor name, assuming it +-- starts with an acceptable letter? +okConIdOcc :: String -> Bool +okConIdOcc str = all okIdChar str || + is_tuple_name1 str + where + -- check for tuple name, starting at the beginning + is_tuple_name1 ('(' : rest) = is_tuple_name2 rest + is_tuple_name1 _ = False + + -- check for tuple tail + is_tuple_name2 ")" = True + is_tuple_name2 (',' : rest) = is_tuple_name2 rest + is_tuple_name2 (ws : rest) + | isSpace ws = is_tuple_name2 rest + is_tuple_name2 _ = False + +-- | Is this an acceptable symbolic constructor name, assuming it +-- starts with an acceptable character? +okConSymOcc :: String -> Bool +okConSymOcc ":" = True +okConSymOcc str = all okSymChar str && + not (str `Set.member` reservedOps) + +-- | Is this an acceptable type name? +okTcOcc :: String -> Bool +okTcOcc "[]" = True +okTcOcc "->" = True +okTcOcc "~" = True +okTcOcc str@(c:_) + | startsConId c + = okConIdOcc str + | startsConSym c + = okConSymOcc str + | startsVarSym c + = okVarSymOcc str +okTcOcc _ = False + +-- | Is this character acceptable in an identifier (after the first letter)? +-- See alexGetByte in Lexer.x +okIdChar :: Char -> Bool +okIdChar c = case generalCategory c of + UppercaseLetter -> True + LowercaseLetter -> True + OtherLetter -> True + TitlecaseLetter -> True + DecimalNumber -> True + OtherNumber -> True + _ -> c == '\'' || c == '_' || c == '#' + +-- | Is this character acceptable in a symbol (after the first char)? +-- See alexGetByte in Lexer.x +okSymChar :: Char -> Bool +okSymChar c + | c `elem` specialSymbols + = False + | c `elem` "_\"'" + = False + | otherwise + = case generalCategory c of + ConnectorPunctuation -> True + DashPunctuation -> True + OtherPunctuation -> True + MathSymbol -> True + CurrencySymbol -> True + ModifierSymbol -> True + OtherSymbol -> True + _ -> False + +-- | All reserved identifiers. Taken from section 2.4 of the 2010 Report. +reservedIds :: Set.Set String +reservedIds = Set.fromList [ "case", "class", "data", "default", "deriving" + , "do", "else", "foreign", "if", "import", "in" + , "infix", "infixl", "infixr", "instance", "let" + , "module", "newtype", "of", "then", "type", "where" + , "_" ] + +-- | All punctuation that cannot appear in symbols. See $special in Lexer.x. +specialSymbols :: [Char] +specialSymbols = "(),;[]`{}" + +-- | All reserved operators. Taken from section 2.4 of the 2010 Report. +reservedOps :: Set.Set String +reservedOps = Set.fromList [ "..", ":", "::", "=", "\\", "|", "<-", "->" + , "@", "~", "=>" ] + +-- | Does this string contain only dashes and has at least 2 of them? +isDashes :: String -> Bool +isDashes ('-' : '-' : rest) = all (== '-') rest +isDashes _ = False -- Determine the name space of a name in a type -- diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 4f71fd2..4fd131a 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -337,4 +337,4 @@ test('T9084', normal, compile_fail, ['-v0']) test('T9738', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) -test('T7484', expect_broken(7484), compile_fail, ['-v0']) +test('T7484', normal, compile_fail, ['-v0']) From git at git.haskell.org Tue Nov 4 02:10:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 02:10:14 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #1476 in th/T1476 (fb001f9) Message-ID: <20141104021014.581623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/fb001f94f3731606f1aad2d4d89ddf05ca8e50aa/ghc >--------------------------------------------------------------- commit fb001f94f3731606f1aad2d4d89ddf05ca8e50aa Author: Richard Eisenberg Date: Mon Nov 3 20:26:14 2014 -0500 Test #1476 in th/T1476 >--------------------------------------------------------------- fb001f94f3731606f1aad2d4d89ddf05ca8e50aa testsuite/tests/th/T1476.hs | 8 ++++++++ testsuite/tests/th/all.T | 1 + 2 files changed, 9 insertions(+) diff --git a/testsuite/tests/th/T1476.hs b/testsuite/tests/th/T1476.hs new file mode 100644 index 0000000..2554d9e --- /dev/null +++ b/testsuite/tests/th/T1476.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T1476 where + +import Language.Haskell.TH + +foo $( return $ VarP $ mkName "x" ) = x +bar $( [p| x |] ) = x diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 4fd131a..c9c0cbe 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -338,3 +338,4 @@ test('T9738', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) +test('T1476', expect_broken(1476), compile, ['-v0']) From git at git.haskell.org Tue Nov 4 02:10:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 02:10:16 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #1476 by allowing pattern splices to bind variables. (f6a93f6) Message-ID: <20141104021016.EF3143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/f6a93f69d893fa343b1bb50e576299f9aeb07f5d/ghc >--------------------------------------------------------------- commit f6a93f69d893fa343b1bb50e576299f9aeb07f5d Author: Richard Eisenberg Date: Mon Nov 3 20:20:41 2014 -0500 Fix #1476 by allowing pattern splices to bind variables. Operationally, this is quite simple: just rename the RHS of a pattern in the right scope, after running a pattern splice. Now that splices are run in the renamer, this is easy. From a coding standpoint, it's rather painful, because there's a moderate-sized impedance mismatch between the code in RnPat and RnSplice. The monads are different (CpsRn vs RnM) as are the callback types in a call to rnSpliceGen. Throw in the necessity of lhs-boot files, and it all gets a little ugly. Suggestions to make this less ugly are strongly encouraged. >--------------------------------------------------------------- f6a93f69d893fa343b1bb50e576299f9aeb07f5d compiler/rename/RnPat.lhs | 49 +++++++++++++++++++++++++++---- compiler/rename/RnSplice.lhs | 61 ++++++++++++++------------------------- compiler/rename/RnSplice.lhs-boot | 8 ++++- testsuite/tests/th/all.T | 2 +- 4 files changed, 72 insertions(+), 48 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f6a93f69d893fa343b1bb50e576299f9aeb07f5d From git at git.haskell.org Tue Nov 4 09:07:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 09:07:04 +0000 (UTC) Subject: [commit: ghc] master: Make Foldable's foldr1 and foldl1 defaults lazier (6dd218e) Message-ID: <20141104090704.592373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6dd218e5f82f19523f9e7aa5371f5bd7beb19663/ghc >--------------------------------------------------------------- commit 6dd218e5f82f19523f9e7aa5371f5bd7beb19663 Author: David Feuer Date: Tue Nov 4 10:03:12 2014 +0100 Make Foldable's foldr1 and foldl1 defaults lazier Fixes #9742. Previously, `foldr1` as applied to a list-like structure would be strict in the spine, and `foldl1` would be strict in the spine of a snoc-list. See also https://www.haskell.org/pipermail/libraries/2014-October/024035.html Differential Revision: https://phabricator.haskell.org/D423 >--------------------------------------------------------------- 6dd218e5f82f19523f9e7aa5371f5bd7beb19663 libraries/base/Data/Foldable.hs | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs index 75460bb..a855090 100644 --- a/libraries/base/Data/Foldable.hs +++ b/libraries/base/Data/Foldable.hs @@ -130,8 +130,9 @@ class Foldable t where foldr1 f xs = fromMaybe (error "foldr1: empty structure") (foldr mf Nothing xs) where - mf x Nothing = Just x - mf x (Just y) = Just (f x y) + mf x m = Just (case m of + Nothing -> x + Just y -> f x y) -- | A variant of 'foldl' that has no base case, -- and thus may only be applied to non-empty structures. @@ -141,8 +142,9 @@ class Foldable t where foldl1 f xs = fromMaybe (error "foldl1: empty structure") (foldl mf Nothing xs) where - mf Nothing y = Just y - mf (Just x) y = Just (f x y) + mf m y = Just (case m of + Nothing -> y + Just x -> f x y) -- | List of elements of a structure. toList :: Foldable t => t a -> [a] From git at git.haskell.org Tue Nov 4 09:10:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 09:10:12 +0000 (UTC) Subject: [commit: ghc] master: Further relax T1969’s max_bytes range (ce03c4a) Message-ID: <20141104091012.D66403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ce03c4a628c7ed75138c95aff65d85ab01b69a66/ghc >--------------------------------------------------------------- commit ce03c4a628c7ed75138c95aff65d85ab01b69a66 Author: Joachim Breitner Date: Tue Nov 4 10:09:50 2014 +0100 Further relax T1969?s max_bytes range >--------------------------------------------------------------- ce03c4a628c7ed75138c95aff65d85ab01b69a66 testsuite/tests/perf/compiler/all.T | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 1a9dfcb..76aee35 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -55,14 +55,15 @@ test('T1969', # 2009-12-31 6149572 (x86/Linux) # 2014-01-22 6429864 (x86/Linux) # 2014-06-29 5949188 (x86/Linux) - (wordsize(64), 9684256, 10)]), + (wordsize(64), 10000000, 15)]), # 2014-09-10 10463640, 10 # post-AMP-update (somewhat stabelish) # looks like the peak is around ~10M, but we're # unlikely to GC exactly on the peak. # varies quite a lot with CLEANUP and BINDIST, # hence 10% range. # See Note [residency] to get an accurate view. - # 2014-09-14 9684256, 10 # try to lower it a bit more to match Phab's CI + # 2014-09-14 9684256, 10 # try to lower it a bit more to match Phab's CI + # 2014-11-03 10584344, # ghcspeed reports higher numbers consistently compiler_stats_num_field('bytes allocated', [(platform('i386-unknown-mingw32'), 301784492, 5), # 215582916 (x86/Windows) From git at git.haskell.org Tue Nov 4 09:33:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 09:33:17 +0000 (UTC) Subject: [commit: ghc] master: Add `Alternative` wrapper to Data.Monoid (49fde3b) Message-ID: <20141104093317.C11C43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/49fde3b6764d4b7bb149ef1c2c56d00cf0878ddb/ghc >--------------------------------------------------------------- commit 49fde3b6764d4b7bb149ef1c2c56d00cf0878ddb Author: David Feuer Date: Tue Nov 4 10:13:05 2014 +0100 Add `Alternative` wrapper to Data.Monoid Complete #9759. Use `coerce` to get nicer definitions of `Sum` and `Product`; update documentation for `First` and `Last`. Reviewed By: hvr Differential Revision: https://phabricator.haskell.org/D422 >--------------------------------------------------------------- 49fde3b6764d4b7bb149ef1c2c56d00cf0878ddb libraries/base/Data/Monoid.hs | 60 ++++++++++++++++++++++--------------------- libraries/base/changelog.md | 2 ++ 2 files changed, 33 insertions(+), 29 deletions(-) diff --git a/libraries/base/Data/Monoid.hs b/libraries/base/Data/Monoid.hs index 8b8c8e8..57ff498 100644 --- a/libraries/base/Data/Monoid.hs +++ b/libraries/base/Data/Monoid.hs @@ -4,6 +4,7 @@ {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE PolyKinds #-} +{-# LANGUAGE ScopedTypeVariables #-} ----------------------------------------------------------------------------- -- | @@ -36,7 +37,9 @@ module Data.Monoid ( -- * Maybe wrappers -- $MaybeExamples First(..), - Last(..) + Last(..), + -- * 'Alternative' wrapper + Alt (..) ) where -- Push down the module in the dependency hierarchy. @@ -102,7 +105,8 @@ newtype Sum a = Sum { getSum :: a } instance Num a => Monoid (Sum a) where mempty = Sum 0 - Sum x `mappend` Sum y = Sum (x + y) + mappend = coerce ((+) :: a -> a -> a) +-- Sum x `mappend` Sum y = Sum (x + y) -- | Monoid under multiplication. newtype Product a = Product { getProduct :: a } @@ -110,7 +114,8 @@ newtype Product a = Product { getProduct :: a } instance Num a => Monoid (Product a) where mempty = Product 1 - Product x `mappend` Product y = Product (x * y) + mappend = coerce ((*) :: a -> a -> a) +-- Product x `mappend` Product y = Product (x * y) -- $MaybeExamples -- To implement @find@ or @findLast@ on any 'Foldable': @@ -145,44 +150,41 @@ instance Num a => Monoid (Product a) where -- | Maybe monoid returning the leftmost non-Nothing value. +-- +-- @'First' a@ is isomorphic to @'Alt' 'Maybe' a@, but precedes it +-- historically. newtype First a = First { getFirst :: Maybe a } - deriving (Eq, Ord, Read, Show, Generic, Generic1) + deriving (Eq, Ord, Read, Show, Generic, Generic1, + Functor, Applicative, Monad) instance Monoid (First a) where mempty = First Nothing - r@(First (Just _)) `mappend` _ = r First Nothing `mappend` r = r - -instance Functor First where - fmap f (First x) = First (fmap f x) - -instance Applicative First where - pure x = First (Just x) - First x <*> First y = First (x <*> y) - -instance Monad First where - return x = First (Just x) - First x >>= m = First (x >>= getFirst . m) + l `mappend` _ = l -- | Maybe monoid returning the rightmost non-Nothing value. +-- +-- @'Last' a@ is isomorphic to @'Dual' ('First' a)@, and thus to +-- @'Dual' ('Alt' 'Maybe' a)@ newtype Last a = Last { getLast :: Maybe a } - deriving (Eq, Ord, Read, Show, Generic, Generic1) + deriving (Eq, Ord, Read, Show, Generic, Generic1, + Functor, Applicative, Monad) instance Monoid (Last a) where mempty = Last Nothing - _ `mappend` r@(Last (Just _)) = r - r `mappend` Last Nothing = r - -instance Functor Last where - fmap f (Last x) = Last (fmap f x) + l `mappend` Last Nothing = l + _ `mappend` r = r -instance Applicative Last where - pure x = Last (Just x) - Last x <*> Last y = Last (x <*> y) - -instance Monad Last where - return x = Last (Just x) - Last x >>= m = Last (x >>= getLast . m) +-- | Monoid under '<|>'. +-- +-- /Since: 4.8.0.0/ +newtype Alt f a = Alt {getAlt :: f a} + deriving (Generic, Generic1, Read, Show, Eq, Ord, Num, Enum, + Monad, MonadPlus, Applicative, Alternative, Functor) + +instance forall f a . Alternative f => Monoid (Alt f a) where + mempty = Alt empty + mappend = coerce ((<|>) :: f a -> f a -> f a) {- {-------------------------------------------------------------------- diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 0f89249..c3e1fa7 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -89,6 +89,8 @@ * Update Unicode class definitions to Unicode version 7.0 + * Add `Alt`, an `Alternative` wrapper, to `Data.Monoid`. (#9759) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 From git at git.haskell.org Tue Nov 4 10:06:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:06:51 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData: Remove some left-over stuff (8b2a3d5) Message-ID: <20141104100651.6C20A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData Link : http://ghc.haskell.org/trac/ghc/changeset/8b2a3d51ca6c1adaa9c9da3d73fab83e3defe84d/ghc >--------------------------------------------------------------- commit 8b2a3d51ca6c1adaa9c9da3d73fab83e3defe84d Author: Jose Pedro Magalhaes Date: Tue Nov 4 10:01:54 2014 +0000 Remove some left-over stuff >--------------------------------------------------------------- 8b2a3d51ca6c1adaa9c9da3d73fab83e3defe84d compiler/typecheck/TcDeriv.lhs | 25 ++++++------------------- compiler/typecheck/TcGenDeriv.lhs | 18 +++++++----------- compiler/typecheck/TcGenGenerics.lhs | 11 +++++------ 3 files changed, 18 insertions(+), 36 deletions(-) diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index 2cf5131..25314b7 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -35,7 +35,6 @@ import RnNames( extendGlobalRdrEnvRn ) import RnBinds import RnEnv import RnSource ( addTcgDUs ) -import HscTypes import Avail import Unify( tcUnifyTy ) @@ -358,11 +357,6 @@ tcDeriving tycl_decls inst_decls deriv_decls ; early_specs <- makeDerivSpecs is_boot tycl_decls inst_decls deriv_decls ; traceTc "tcDeriving 1" (ppr early_specs) - -- for each type, determine the auxliary declarations that are common - -- to multiple derivations involving that type (e.g. Generic and - -- Generic1 should use the same TcGenGenerics.MetaTyCons) - -- ; (commonAuxs, auxDerivStuff) <- commonAuxiliaries $ map forgetTheta early_specs - ; let (infer_specs, given_specs) = splitEarlyDerivSpec early_specs ; insts1 <- mapM genInst given_specs @@ -375,7 +369,7 @@ tcDeriving tycl_decls inst_decls deriv_decls ; let (inst_infos, deriv_stuff, maybe_fvs) = unzip3 (insts1 ++ insts2) ; loc <- getSrcSpanM - ; let (binds, newTyCons, famInsts, extraInstances) = + ; let (binds, famInsts, extraInstances) = genAuxBinds loc (unionManyBags deriv_stuff) ; (inst_info, rn_binds, rn_dus) <- @@ -384,29 +378,22 @@ tcDeriving tycl_decls inst_decls deriv_decls ; dflags <- getDynFlags ; unless (isEmptyBag inst_info) $ liftIO (dumpIfSet_dyn dflags Opt_D_dump_deriv "Derived instances" - (ddump_deriving inst_info rn_binds newTyCons famInsts)) + (ddump_deriving inst_info rn_binds famInsts)) - ; let all_tycons = map ATyCon (bagToList newTyCons) - ; gbl_env <- tcExtendGlobalEnv all_tycons $ - tcExtendGlobalEnvImplicit (concatMap implicitTyThings all_tycons) $ - tcExtendLocalFamInstEnv (bagToList famInsts) $ + ; gbl_env <- tcExtendLocalFamInstEnv (bagToList famInsts) $ tcExtendLocalInstEnv (map iSpec (bagToList inst_info)) getGblEnv ; let all_dus = rn_dus `plusDU` usesOnly (mkFVs $ catMaybes maybe_fvs) ; return (addTcgDUs gbl_env all_dus, inst_info, rn_binds) } where ddump_deriving :: Bag (InstInfo Name) -> HsValBinds Name - -> Bag TyCon -- ^ Empty data constructors -> Bag FamInst -- ^ Rep type family instances -> SDoc - ddump_deriving inst_infos extra_binds repMetaTys repFamInsts + ddump_deriving inst_infos extra_binds repFamInsts = hang (ptext (sLit "Derived instances:")) 2 (vcat (map (\i -> pprInstInfoDetails i $$ text "") (bagToList inst_infos)) $$ ppr extra_binds) - $$ hangP "Generic representation:" ( - hangP "Generated datatypes for meta-information:" - (vcat (map ppr (bagToList repMetaTys))) - $$ hangP "Representation types:" - (vcat (map pprRepTy (bagToList repFamInsts)))) + $$ hangP "GHC.Generics representation types:" + (vcat (map pprRepTy (bagToList repFamInsts))) hangP s x = text "" $$ hang (ptext (sLit s)) 2 x diff --git a/compiler/typecheck/TcGenDeriv.lhs b/compiler/typecheck/TcGenDeriv.lhs index 31e31ed..fd83301 100644 --- a/compiler/typecheck/TcGenDeriv.lhs +++ b/compiler/typecheck/TcGenDeriv.lhs @@ -84,7 +84,6 @@ data DerivStuff -- Please add this auxiliary stuff = DerivAuxBind AuxBindSpec -- Generics - | DerivTyCon TyCon -- New data types | DerivFamInst FamInst -- New type family instances -- New top-level auxiliary bindings @@ -1992,7 +1991,6 @@ genAuxBindSpec loc (DerivMaxTag tycon) type SeparateBagsDerivStuff = -- AuxBinds and SYB bindings ( Bag (LHsBind RdrName, LSig RdrName) -- Extra bindings (used by Generic only) - , Bag TyCon -- Extra top-level datatypes , Bag (FamInst) -- Extra family instances , Bag (InstInfo RdrName)) -- Extra instances @@ -2007,18 +2005,16 @@ genAuxBinds loc b = genAuxBinds' b2 where genAuxBinds' :: BagDerivStuff -> SeparateBagsDerivStuff genAuxBinds' = foldrBag f ( mapBag (genAuxBindSpec loc) (rm_dups b1) - , emptyBag, emptyBag, emptyBag) + , emptyBag, emptyBag) f :: DerivStuff -> SeparateBagsDerivStuff -> SeparateBagsDerivStuff f (DerivAuxBind _) = panic "genAuxBinds'" -- We have removed these before f (DerivHsBind b) = add1 b - f (DerivTyCon t) = add2 t - f (DerivFamInst t) = add3 t - f (DerivInst i) = add4 i - - add1 x (a,b,c,d) = (x `consBag` a,b,c,d) - add2 x (a,b,c,d) = (a,x `consBag` b,c,d) - add3 x (a,b,c,d) = (a,b,x `consBag` c,d) - add4 x (a,b,c,d) = (a,b,c,x `consBag` d) + f (DerivFamInst t) = add2 t + f (DerivInst i) = add3 i + + add1 x (a,b,c) = (x `consBag` a,b,c) + add2 x (a,b,c) = (a,x `consBag` b,c) + add3 x (a,b,c) = (a,b,x `consBag` c) mk_data_type_name :: TyCon -> RdrName -- "$tT" mk_data_type_name tycon = mkAuxBinderName (tyConName tycon) mkDataTOcc diff --git a/compiler/typecheck/TcGenGenerics.lhs b/compiler/typecheck/TcGenGenerics.lhs index 2362a8d..582b1f3 100644 --- a/compiler/typecheck/TcGenGenerics.lhs +++ b/compiler/typecheck/TcGenGenerics.lhs @@ -514,11 +514,11 @@ tc_mkRepTy gk_ tycon = (dataConFieldLabels a)] -- This field has no label -- mkS Nothing _ a = mkTyConApp s1 [mkTyConApp ms [mkTyConTy pNothing], a] - mkS Nothing a = mkTyConApp s1 [{- typeKind msel, -} msel, a] + mkS Nothing a = mkTyConApp s1 [msel, a] where msel = mkTyConApp ms [mkStrLitTy (mkFastString "")] -- This field has a label -- mkS (Just l) _ a = mkTyConApp s1 [mkTyConApp ms [mkTyConApp pJust [selName l]], a] - mkS (Just l) a = mkTyConApp s1 [{- typeKind msel, -} msel, a] + mkS (Just l) a = mkTyConApp s1 [msel, a] where msel = mkTyConApp ms [selName l] -- Sums and products are done in the same way for both Rep and Rep1 @@ -581,7 +581,6 @@ tc_mkRepTy gk_ tycon = metaConsTy c = mkTyConApp mc [ctName c, ctFix c, isRec c] -- metaSelTy s = mkTyConApp mc [ctName c, ctFix c, isRec c] - -- pprTrace "rep: " (ppr (metaDataTy, tycon, mkD tycon)) $ return (mkD tycon) -------------------------------------------------------------------------------- @@ -676,10 +675,10 @@ genLR_E i n e -------------------------------------------------------------------------------- -- Build a product expression -mkProd_E :: GenericKind_DC -- Generic or Generic1? - -> US -- Base for unique names +mkProd_E :: GenericKind_DC -- Generic or Generic1? + -> US -- Base for unique names -> [(RdrName, Type)] -- List of variables matched on the lhs and their types - -> LHsExpr RdrName -- Resulting product expression + -> LHsExpr RdrName -- Resulting product expression mkProd_E _ _ [] = mkM1_E (nlHsVar u1DataCon_RDR) mkProd_E gk_ _ varTys = mkM1_E (foldBal prod appVars) -- These M1s are meta-information for the constructor From git at git.haskell.org Tue Nov 4 10:06:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:06:54 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData: Update test output (d8e8996) Message-ID: <20141104100654.0A8B53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData Link : http://ghc.haskell.org/trac/ghc/changeset/d8e899686d7f3092af54932f46ab122dc8d3d373/ghc >--------------------------------------------------------------- commit d8e899686d7f3092af54932f46ab122dc8d3d373 Author: Jose Pedro Magalhaes Date: Tue Nov 4 10:02:17 2014 +0000 Update test output >--------------------------------------------------------------- d8e899686d7f3092af54932f46ab122dc8d3d373 testsuite/tests/generics/GenDerivOutput.stderr | 120 +++++----- testsuite/tests/generics/GenDerivOutput1_0.stderr | 48 ++-- testsuite/tests/generics/GenDerivOutput1_1.stderr | 254 ++++++++++------------ 3 files changed, 187 insertions(+), 235 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d8e899686d7f3092af54932f46ab122dc8d3d373 From git at git.haskell.org Tue Nov 4 10:17:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:17:27 +0000 (UTC) Subject: [commit: ghc] master: Minor Haddock markup improvement to Data.Monoid (4dbe433) Message-ID: <20141104101727.D2C523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4dbe4330e046c57c09feaa972a3fd513a55d601c/ghc >--------------------------------------------------------------- commit 4dbe4330e046c57c09feaa972a3fd513a55d601c Author: Herbert Valerio Riedel Date: Tue Nov 4 10:52:56 2014 +0100 Minor Haddock markup improvement to Data.Monoid [skip ci] >--------------------------------------------------------------- 4dbe4330e046c57c09feaa972a3fd513a55d601c libraries/base/Data/Monoid.hs | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/libraries/base/Data/Monoid.hs b/libraries/base/Data/Monoid.hs index 57ff498..288d71d 100644 --- a/libraries/base/Data/Monoid.hs +++ b/libraries/base/Data/Monoid.hs @@ -23,18 +23,18 @@ ----------------------------------------------------------------------------- module Data.Monoid ( - -- * Monoid typeclass + -- * 'Monoid' typeclass Monoid(..), (<>), Dual(..), Endo(..), - -- * Bool wrappers + -- * 'Bool' wrappers All(..), Any(..), - -- * Num wrappers + -- * 'Num' wrappers Sum(..), Product(..), - -- * Maybe wrappers + -- * 'Maybe' wrappers -- $MaybeExamples First(..), Last(..), @@ -67,7 +67,7 @@ infixr 6 <> -- Monoid instances. --- | The dual of a monoid, obtained by swapping the arguments of 'mappend'. +-- | The dual of a 'Monoid', obtained by swapping the arguments of 'mappend'. newtype Dual a = Dual { getDual :: a } deriving (Eq, Ord, Read, Show, Bounded, Generic, Generic1) @@ -83,7 +83,7 @@ instance Monoid (Endo a) where mempty = Endo id Endo f `mappend` Endo g = Endo (f . g) --- | Boolean monoid under conjunction. +-- | Boolean monoid under conjunction ('&&'). newtype All = All { getAll :: Bool } deriving (Eq, Ord, Read, Show, Bounded, Generic) @@ -91,7 +91,7 @@ instance Monoid All where mempty = All True All x `mappend` All y = All (x && y) --- | Boolean monoid under disjunction. +-- | Boolean monoid under disjunction ('||'). newtype Any = Any { getAny :: Bool } deriving (Eq, Ord, Read, Show, Bounded, Generic) From git at git.haskell.org Tue Nov 4 10:17:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:17:30 +0000 (UTC) Subject: [commit: ghc] master: Refactor Haddock comments in Data.Bits (828d724) Message-ID: <20141104101730.66F913A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/828d72489a8bad79e3675deed4b90807052ca0ee/ghc >--------------------------------------------------------------- commit 828d72489a8bad79e3675deed4b90807052ca0ee Author: Herbert Valerio Riedel Date: Tue Nov 4 11:06:53 2014 +0100 Refactor Haddock comments in Data.Bits This removes the redundant "Minimal complete definition"-block included in the Haddock comment since Haddock renders the `MINIMAL`-pragma as well (which has is moved to the start of `class` definition for better readability of the source code) Morever, the references to `testBitDefault`, `bitDefault`, and `popCountDefault` have been moved to the respective methods' Haddock strings for which they can be used. >--------------------------------------------------------------- 828d72489a8bad79e3675deed4b90807052ca0ee libraries/base/Data/Bits.hs | 35 ++++++++++++++++++----------------- 1 file changed, 18 insertions(+), 17 deletions(-) diff --git a/libraries/base/Data/Bits.hs b/libraries/base/Data/Bits.hs index cdef2fb..fead6fb 100644 --- a/libraries/base/Data/Bits.hs +++ b/libraries/base/Data/Bits.hs @@ -68,19 +68,16 @@ infixl 5 .|. {-# DEPRECATED bitSize "Use 'bitSizeMaybe' or 'finiteBitSize' instead" #-} -- deprecated in 7.8 -{-| -The 'Bits' class defines bitwise operations over integral types. - -* Bits are numbered from 0 with bit 0 being the least - significant bit. - -Minimal complete definition: '.&.', '.|.', 'xor', 'complement', -('shift' or ('shiftL' and 'shiftR')), ('rotate' or ('rotateL' and 'rotateR')), -'bitSize', 'isSigned', 'testBit', 'bit', and 'popCount'. The latter three can -be implemented using `testBitDefault', 'bitDefault', and 'popCountDefault', if - at a@ is also an instance of 'Num'. --} +-- | The 'Bits' class defines bitwise operations over integral types. +-- +-- * Bits are numbered from 0 with bit 0 being the least +-- significant bit. class Eq a => Bits a where + {-# MINIMAL (.&.), (.|.), xor, complement, + (shift | (shiftL, shiftR)), + (rotate | (rotateL, rotateR)), + bitSize, bitSizeMaybe, isSigned, testBit, bit, popCount #-} + -- | Bitwise \"and\" (.&.) :: a -> a -> a @@ -155,6 +152,9 @@ class Eq a => Bits a where -- | @bit /i/@ is a value with the @/i/@th bit set and all other bits clear. -- + -- Can be implemented using `bitDefault' if @a@ is also an + -- instance of 'Num'. + -- -- See also 'zeroBits'. bit :: Int -> a @@ -168,6 +168,9 @@ class Eq a => Bits a where complementBit :: a -> Int -> a -- | Return 'True' if the @n at th bit of the argument is 1 + -- + -- Can be implemented using `testBitDefault' if @a@ is also an + -- instance of 'Num'. testBit :: a -> Int -> Bool {-| Return the number of bits in the type of the argument. The actual @@ -268,14 +271,12 @@ class Eq a => Bits a where {-| Return the number of set bits in the argument. This number is known as the population count or the Hamming weight. + Can be implemented using `popCountDefault' if @a@ is also an + instance of 'Num'. + /Since: 4.5.0.0/ -} popCount :: a -> Int - {-# MINIMAL (.&.), (.|.), xor, complement, - (shift | (shiftL, shiftR)), - (rotate | (rotateL, rotateR)), - bitSize, bitSizeMaybe, isSigned, testBit, bit, popCount #-} - -- |The 'FiniteBits' class denotes types with a finite, fixed number of bits. -- -- /Since: 4.7.0.0/ From git at git.haskell.org Tue Nov 4 10:17:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:17:32 +0000 (UTC) Subject: [commit: ghc] master: Fix lost Haddock annotation for `class Monad m` (c7fa0ba) Message-ID: <20141104101732.F19873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c7fa0ba69c1d28e874d811535447838910810c6f/ghc >--------------------------------------------------------------- commit c7fa0ba69c1d28e874d811535447838910810c6f Author: Herbert Valerio Riedel Date: Tue Nov 4 11:15:51 2014 +0100 Fix lost Haddock annotation for `class Monad m` This was broken in d94de87252d0fe2ae97341d186b03a2fbe136b04 when `join` was inserted between `Monad`'s Haddock string and the `class Monad m` definition thereby breaking the association. >--------------------------------------------------------------- c7fa0ba69c1d28e874d811535447838910810c6f libraries/base/GHC/Base.lhs | 13 ++++++------- 1 file changed, 6 insertions(+), 7 deletions(-) diff --git a/libraries/base/GHC/Base.lhs b/libraries/base/GHC/Base.lhs index f9d01b5..d395935 100644 --- a/libraries/base/GHC/Base.lhs +++ b/libraries/base/GHC/Base.lhs @@ -416,6 +416,12 @@ liftA2 f a b = (fmap f a) <*> b liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d liftA3 f a b c = (fmap f a) <*> b <*> c +-- | The 'join' function is the conventional monad join operator. It +-- is used to remove one level of monadic structure, projecting its +-- bound argument into the outer level. +join :: (Monad m) => m (m a) -> m a +join x = x >>= id + {- | The 'Monad' class defines the basic operations over a /monad/, a concept from a branch of mathematics known as /category theory/. From the perspective of a Haskell programmer, however, it is best to @@ -438,13 +444,6 @@ Instances of both 'Monad' and 'Functor' should additionally satisfy the law: The instances of 'Monad' for lists, 'Data.Maybe.Maybe' and 'System.IO.IO' defined in the "Prelude" satisfy these laws. -} - --- | The 'join' function is the conventional monad join operator. It --- is used to remove one level of monadic structure, projecting its --- bound argument into the outer level. -join :: (Monad m) => m (m a) -> m a -join x = x >>= id - class Applicative m => Monad m where -- | Sequentially compose two actions, passing any value produced -- by the first as an argument to the second. From git at git.haskell.org Tue Nov 4 10:37:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:37:53 +0000 (UTC) Subject: [commit: ghc] master: Tidy up pretty-printing of SrcLoc and SrcSpan (1d6124d) Message-ID: <20141104103753.347583A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1d6124de4e7ee97447e9e2fff6beca617b4d694b/ghc >--------------------------------------------------------------- commit 1d6124de4e7ee97447e9e2fff6beca617b4d694b Author: Simon Peyton Jones Date: Wed Oct 29 15:13:41 2014 +0000 Tidy up pretty-printing of SrcLoc and SrcSpan >--------------------------------------------------------------- 1d6124de4e7ee97447e9e2fff6beca617b4d694b compiler/basicTypes/SrcLoc.lhs | 101 ++++++++++++++++++++++------------------- 1 file changed, 55 insertions(+), 46 deletions(-) diff --git a/compiler/basicTypes/SrcLoc.lhs b/compiler/basicTypes/SrcLoc.lhs index ab58a4f..6b46454 100644 --- a/compiler/basicTypes/SrcLoc.lhs +++ b/compiler/basicTypes/SrcLoc.lhs @@ -83,7 +83,6 @@ import Data.Bits import Data.Data import Data.List import Data.Ord -import System.FilePath \end{code} %************************************************************************ @@ -191,15 +190,19 @@ cmpRealSrcLoc (SrcLoc s1 l1 c1) (SrcLoc s2 l2 c2) instance Outputable RealSrcLoc where ppr (SrcLoc src_path src_line src_col) - = getPprStyle $ \ sty -> - if userStyle sty || debugStyle sty then - hcat [ pprFastFilePath src_path, char ':', - int src_line, - char ':', int src_col - ] - else - hcat [text "{-# LINE ", int src_line, space, - char '\"', pprFastFilePath src_path, text " #-}"] + = hcat [ pprFastFilePath src_path <> colon + , int src_line <> colon + , int src_col ] + +-- I don't know why there is this style-based difference +-- if userStyle sty || debugStyle sty then +-- hcat [ pprFastFilePath src_path, char ':', +-- int src_line, +-- char ':', int src_col +-- ] +-- else +-- hcat [text "{-# LINE ", int src_line, space, +-- char '\"', pprFastFilePath src_path, text " #-}"] instance Outputable SrcLoc where ppr (RealSrcLoc l) = ppr l @@ -432,50 +435,56 @@ instance Ord SrcSpan where instance Outputable RealSrcSpan where - ppr span - = getPprStyle $ \ sty -> - if userStyle sty || debugStyle sty then - text (showUserRealSpan True span) - else - hcat [text "{-# LINE ", int (srcSpanStartLine span), space, - char '\"', pprFastFilePath $ srcSpanFile span, text " #-}"] + ppr span = pprUserRealSpan True span + +-- I don't know why there is this style-based difference +-- = getPprStyle $ \ sty -> +-- if userStyle sty || debugStyle sty then +-- text (showUserRealSpan True span) +-- else +-- hcat [text "{-# LINE ", int (srcSpanStartLine span), space, +-- char '\"', pprFastFilePath $ srcSpanFile span, text " #-}"] instance Outputable SrcSpan where - ppr span - = getPprStyle $ \ sty -> - if userStyle sty || debugStyle sty then - pprUserSpan True span - else - case span of - UnhelpfulSpan _ -> panic "Outputable UnhelpfulSpan" - RealSrcSpan s -> ppr s + ppr span = pprUserSpan True span -pprUserSpan :: Bool -> SrcSpan -> SDoc -pprUserSpan _ (UnhelpfulSpan s) = ftext s -pprUserSpan show_path (RealSrcSpan s) = text (showUserRealSpan show_path s) +-- I don't know why there is this style-based difference +-- = getPprStyle $ \ sty -> +-- if userStyle sty || debugStyle sty then +-- pprUserSpan True span +-- else +-- case span of +-- UnhelpfulSpan _ -> panic "Outputable UnhelpfulSpan" +-- RealSrcSpan s -> ppr s showUserSpan :: Bool -> SrcSpan -> String -showUserSpan _ (UnhelpfulSpan s) = unpackFS s -showUserSpan show_path (RealSrcSpan s) = showUserRealSpan show_path s - -showUserRealSpan :: Bool -> RealSrcSpan -> String -showUserRealSpan show_path (SrcSpanOneLine src_path line start_col end_col) - = (if show_path then normalise (unpackFS src_path) ++ ":" else "") - ++ show line ++ ":" ++ show start_col - ++ (if end_col - start_col <= 1 then "" else '-' : show (end_col - 1)) +showUserSpan show_path span = showSDocSimple (pprUserSpan show_path span) + +pprUserSpan :: Bool -> SrcSpan -> SDoc +pprUserSpan _ (UnhelpfulSpan s) = ftext s +pprUserSpan show_path (RealSrcSpan s) = pprUserRealSpan show_path s + +pprUserRealSpan :: Bool -> RealSrcSpan -> SDoc +pprUserRealSpan show_path (SrcSpanOneLine src_path line start_col end_col) + = hcat [ ppWhen show_path (pprFastFilePath src_path <> colon) + , int line <> colon + , int start_col + , ppUnless (end_col - start_col <= 1) (char '-' <> int (end_col - 1)) ] -- For single-character or point spans, we just -- output the starting column number -showUserRealSpan show_path (SrcSpanMultiLine src_path sline scol eline ecol) - = (if show_path then normalise (unpackFS src_path) ++ ":" else "") - ++ "(" ++ show sline ++ "," ++ show scol ++ ")" - ++ "-" - ++ "(" ++ show eline ++ "," ++ show ecol' ++ ")" - where ecol' = if ecol == 0 then ecol else ecol - 1 - -showUserRealSpan show_path (SrcSpanPoint src_path line col) - = (if show_path then normalise (unpackFS src_path) ++ ":" else "") - ++ show line ++ ":" ++ show col +pprUserRealSpan show_path (SrcSpanMultiLine src_path sline scol eline ecol) + = hcat [ ppWhen show_path (pprFastFilePath src_path <> colon) + , parens (int sline <> comma <> int scol) + , char '-' + , parens (int eline <> comma <> int ecol') ] + where + ecol' = if ecol == 0 then ecol else ecol - 1 + +pprUserRealSpan show_path (SrcSpanPoint src_path line col) + = hcat [ ppWhen show_path (pprFastFilePath src_path <> colon) + , int line <> colon + , int col ] \end{code} %************************************************************************ From git at git.haskell.org Tue Nov 4 10:37:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:37:55 +0000 (UTC) Subject: [commit: ghc] master: Improve pretty-printing of type variables (27ba070) Message-ID: <20141104103755.C1AAD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/27ba070c56fa6c583a34dc9eaede0083530f1dbe/ghc >--------------------------------------------------------------- commit 27ba070c56fa6c583a34dc9eaede0083530f1dbe Author: Simon Peyton Jones Date: Wed Oct 29 15:15:38 2014 +0000 Improve pretty-printing of type variables In particular, print a bit of debug info in debug-style and dump-style Otherwise distinct type variables look the same >--------------------------------------------------------------- 27ba070c56fa6c583a34dc9eaede0083530f1dbe compiler/basicTypes/Var.lhs | 20 ++++++++++---------- 1 file changed, 10 insertions(+), 10 deletions(-) diff --git a/compiler/basicTypes/Var.lhs b/compiler/basicTypes/Var.lhs index f7e5f67..62253c8 100644 --- a/compiler/basicTypes/Var.lhs +++ b/compiler/basicTypes/Var.lhs @@ -206,16 +206,16 @@ After CoreTidy, top-level LocalIds are turned into GlobalIds \begin{code} instance Outputable Var where - ppr var = ppr (varName var) <+> ifPprDebug (brackets (ppr_debug var)) --- Printing the type on every occurrence is too much! --- <+> if (not (gopt Opt_SuppressVarKinds dflags)) --- then ifPprDebug (text "::" <+> ppr (tyVarKind var) <+> text ")") --- else empty - -ppr_debug :: Var -> SDoc -ppr_debug (TyVar {}) = ptext (sLit "tv") -ppr_debug (TcTyVar {tc_tv_details = d}) = pprTcTyVarDetails d -ppr_debug (Id { idScope = s, id_details = d }) = ppr_id_scope s <> pprIdDetails d + ppr var = ppr (varName var) <> getPprStyle (ppr_debug var) + +ppr_debug :: Var -> PprStyle -> SDoc +ppr_debug (TyVar {}) sty + | debugStyle sty = brackets (ptext (sLit "tv")) +ppr_debug (TcTyVar {tc_tv_details = d}) sty + | dumpStyle sty || debugStyle sty = brackets (pprTcTyVarDetails d) +ppr_debug (Id { idScope = s, id_details = d }) sty + | debugStyle sty = brackets (ppr_id_scope s <> pprIdDetails d) +ppr_debug _ _ = empty ppr_id_scope :: IdScope -> SDoc ppr_id_scope GlobalId = ptext (sLit "gid") From git at git.haskell.org Tue Nov 4 10:37:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:37:58 +0000 (UTC) Subject: [commit: ghc] master: Some refactoring around endPass and debug dumping (c8c18a1) Message-ID: <20141104103758.782013A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c8c18a106458c80ec0eb5108d11b4ed9e2bc7478/ghc >--------------------------------------------------------------- commit c8c18a106458c80ec0eb5108d11b4ed9e2bc7478 Author: Simon Peyton Jones Date: Wed Oct 29 15:23:14 2014 +0000 Some refactoring around endPass and debug dumping I forget all the details, but I spent some time trying to understand the current setup, and tried to simplify it a bit >--------------------------------------------------------------- c8c18a106458c80ec0eb5108d11b4ed9e2bc7478 compiler/coreSyn/CorePrep.lhs | 4 +- compiler/deSugar/Desugar.lhs | 7 ++-- compiler/ghci/Debugger.hs | 1 + compiler/main/DynFlags.hs | 12 ------ compiler/main/ErrUtils.lhs | 61 +++++++++++++++++------------ compiler/main/TidyPgm.lhs | 8 ++-- compiler/nativeGen/AsmCodeGen.lhs | 8 ++-- compiler/simplCore/CoreMonad.lhs | 47 ++++++++++++++++------- compiler/simplCore/SimplCore.lhs | 33 ++++++++-------- compiler/simplCore/SimplMonad.lhs | 1 + compiler/simplCore/Simplify.lhs | 5 ++- compiler/typecheck/TcDeriv.lhs | 4 +- compiler/utils/Outputable.lhs | 81 ++++++++++++++++++++++----------------- 13 files changed, 156 insertions(+), 116 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c8c18a106458c80ec0eb5108d11b4ed9e2bc7478 From git at git.haskell.org Tue Nov 4 10:38:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:01 +0000 (UTC) Subject: [commit: ghc] master: Simplify the generation of superclass constraints in tcInstDecl2 (7251798) Message-ID: <20141104103801.23FA53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/725179875b1d7c9d42291ac338ab317ab6597c0d/ghc >--------------------------------------------------------------- commit 725179875b1d7c9d42291ac338ab317ab6597c0d Author: Simon Peyton Jones Date: Wed Oct 29 15:34:14 2014 +0000 Simplify the generation of superclass constraints in tcInstDecl2 The simplified function is tcSuperClasses; no need for an implication constraint here >--------------------------------------------------------------- 725179875b1d7c9d42291ac338ab317ab6597c0d compiler/typecheck/TcInstDcls.lhs | 19 ++++++++++--------- 1 file changed, 10 insertions(+), 9 deletions(-) diff --git a/compiler/typecheck/TcInstDcls.lhs b/compiler/typecheck/TcInstDcls.lhs index b986fa8..a471e11 100644 --- a/compiler/typecheck/TcInstDcls.lhs +++ b/compiler/typecheck/TcInstDcls.lhs @@ -840,7 +840,7 @@ tcInstDecl2 (InstInfo { iSpec = ispec, iBinds = ibinds }) ; dfun_ev_vars <- newEvVars dfun_theta - ; (sc_binds, sc_ev_vars) <- tcSuperClasses dfun_id inst_tyvars dfun_ev_vars sc_theta' + ; sc_ev_vars <- tcSuperClasses dfun_id inst_tyvars dfun_ev_vars sc_theta' -- Deal with 'SPECIALISE instance' pragmas -- See Note [SPECIALISE instance pragmas] @@ -908,7 +908,7 @@ tcInstDecl2 (InstInfo { iSpec = ispec, iBinds = ibinds }) main_bind = AbsBinds { abs_tvs = inst_tyvars , abs_ev_vars = dfun_ev_vars , abs_exports = [export] - , abs_ev_binds = sc_binds + , abs_ev_binds = emptyTcEvBinds , abs_binds = unitBag dict_bind } ; return (unitBag (L loc main_bind) `unionBags` @@ -920,22 +920,23 @@ tcInstDecl2 (InstInfo { iSpec = ispec, iBinds = ibinds }) ------------------------------ tcSuperClasses :: DFunId -> [TcTyVar] -> [EvVar] -> TcThetaType - -> TcM (TcEvBinds, [EvVar]) + -> TcM [EvVar] -- See Note [Silent superclass arguments] tcSuperClasses dfun_id inst_tyvars dfun_ev_vars sc_theta + | null inst_tyvars && null dfun_ev_vars + = emitWanteds ScOrigin sc_theta + + | otherwise = do { -- Check that all superclasses can be deduced from -- the originally-specified dfun arguments - ; (sc_binds, sc_evs) <- checkConstraints InstSkol inst_tyvars orig_ev_vars $ - emitWanteds ScOrigin sc_theta + ; _ <- checkConstraints InstSkol inst_tyvars orig_ev_vars $ + emitWanteds ScOrigin sc_theta - ; if null inst_tyvars && null dfun_ev_vars - then return (sc_binds, sc_evs) - else return (emptyTcEvBinds, sc_lam_args) } + ; return (map (find dfun_ev_vars) sc_theta) } where n_silent = dfunNSilent dfun_id orig_ev_vars = drop n_silent dfun_ev_vars - sc_lam_args = map (find dfun_ev_vars) sc_theta find [] pred = pprPanic "tcInstDecl2" (ppr dfun_id $$ ppr (idType dfun_id) $$ ppr pred) find (ev:evs) pred From git at git.haskell.org Tue Nov 4 10:38:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:03 +0000 (UTC) Subject: [commit: ghc] master: Add the unfolding and inline-pragma for DFuns in DsBinds, not TcInstDcls (d153e40) Message-ID: <20141104103803.C78FA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d153e4020e5e7c07bbe616381a97c760509ad3fa/ghc >--------------------------------------------------------------- commit d153e4020e5e7c07bbe616381a97c760509ad3fa Author: Simon Peyton Jones Date: Wed Oct 29 15:36:28 2014 +0000 Add the unfolding and inline-pragma for DFuns in DsBinds, not TcInstDcls This is a straight refactoring that puts the generation of unfolding info in one place, which is a lot tidier >--------------------------------------------------------------- d153e4020e5e7c07bbe616381a97c760509ad3fa compiler/deSugar/DsBinds.lhs | 20 ++++++++++++++++++++ compiler/typecheck/TcInstDcls.lhs | 31 ++++++++----------------------- 2 files changed, 28 insertions(+), 23 deletions(-) diff --git a/compiler/deSugar/DsBinds.lhs b/compiler/deSugar/DsBinds.lhs index 8c2541c..a3aac1b 100644 --- a/compiler/deSugar/DsBinds.lhs +++ b/compiler/deSugar/DsBinds.lhs @@ -51,6 +51,7 @@ import Class import DataCon ( dataConWorkId ) import Name import MkId ( seqId ) +import IdInfo ( IdDetails(..) ) import Var import VarSet import Rules @@ -214,6 +215,9 @@ makeCorePair dflags gbl_id is_default_method dict_arity rhs | is_default_method -- Default methods are *always* inlined = (gbl_id `setIdUnfolding` mkCompulsoryUnfolding rhs, rhs) + | DFunId _ is_newtype <- idDetails gbl_id + = (mk_dfun_w_stuff is_newtype, rhs) + | otherwise = case inlinePragmaSpec inline_prag of EmptyInlineSpec -> (gbl_id, rhs) @@ -237,6 +241,22 @@ makeCorePair dflags gbl_id is_default_method dict_arity rhs = pprTrace "makeCorePair: arity missing" (ppr gbl_id) $ (gbl_id `setIdUnfolding` mkInlineUnfolding Nothing rhs, rhs) + -- See Note [ClassOp/DFun selection] in TcInstDcls + -- See Note [Single-method classes] in TcInstDcls + mk_dfun_w_stuff is_newtype + | is_newtype + = gbl_id `setIdUnfolding` mkInlineUnfolding (Just 0) rhs + `setInlinePragma` alwaysInlinePragma { inl_sat = Just 0 } + | otherwise + = gbl_id `setIdUnfolding` mkDFunUnfolding dfun_bndrs dfun_constr dfun_args + `setInlinePragma` dfunInlinePragma + (dfun_bndrs, dfun_body) = collectBinders (simpleOptExpr rhs) + (dfun_con, dfun_args) = collectArgs dfun_body + dfun_constr | Var id <- dfun_con + , DataConWorkId con <- idDetails id + = con + | otherwise = pprPanic "makeCorePair: dfun" (ppr rhs) + dictArity :: [Var] -> Arity -- Don't count coercion variables in arity diff --git a/compiler/typecheck/TcInstDcls.lhs b/compiler/typecheck/TcInstDcls.lhs index a471e11..f135fe5 100644 --- a/compiler/typecheck/TcInstDcls.lhs +++ b/compiler/typecheck/TcInstDcls.lhs @@ -43,10 +43,7 @@ import Class import Var import VarEnv import VarSet -import CoreUnfold ( mkDFunUnfolding ) -import CoreSyn ( Expr(Var, Type), CoreExpr, mkTyApps, mkVarApps ) -import PrelNames ( tYPEABLE_INTERNAL, typeableClassName, - genericClassNames ) +import PrelNames ( tYPEABLE_INTERNAL, typeableClassName, genericClassNames ) import Bag import BasicTypes import DynFlags @@ -883,26 +880,14 @@ tcInstDecl2 (InstInfo { iSpec = ispec, iBinds = ibinds }) arg_wrapper = mkWpEvVarApps dfun_ev_vars <.> mkWpTyApps inst_tv_tys -- Do not inline the dfun; instead give it a magic DFunFunfolding - -- See Note [ClassOp/DFun selection] - -- See also note [Single-method classes] - (dfun_id_w_fun, dfun_spec_prags) - | isNewTyCon class_tc - = ( dfun_id `setInlinePragma` alwaysInlinePragma { inl_sat = Just 0 } - , SpecPrags [] ) -- Newtype dfuns just inline unconditionally, - -- so don't attempt to specialise them + dfun_spec_prags + | isNewTyCon class_tc = SpecPrags [] + -- Newtype dfuns just inline unconditionally, + -- so don't attempt to specialise them | otherwise - = ( dfun_id `setIdUnfolding` mkDFunUnfolding (inst_tyvars ++ dfun_ev_vars) - dict_constr dfun_args - `setInlinePragma` dfunInlinePragma - , SpecPrags spec_inst_prags ) - - dfun_args :: [CoreExpr] - dfun_args = map Type inst_tys ++ - map Var sc_ev_vars ++ - map mk_meth_app meth_ids - mk_meth_app meth_id = Var meth_id `mkTyApps` inst_tv_tys `mkVarApps` dfun_ev_vars - - export = ABE { abe_wrap = idHsWrapper, abe_poly = dfun_id_w_fun + = SpecPrags spec_inst_prags + + export = ABE { abe_wrap = idHsWrapper, abe_poly = dfun_id , abe_mono = self_dict, abe_prags = dfun_spec_prags } -- NB: see Note [SPECIALISE instance pragmas] main_bind = AbsBinds { abs_tvs = inst_tyvars From git at git.haskell.org Tue Nov 4 10:38:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:06 +0000 (UTC) Subject: [commit: ghc] master: Fix reduceTyFamApp_maybe (fd46acf) Message-ID: <20141104103806.664563A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fd46acf1c30d81ce0ac676c5ca7ffe6e3c82ad25/ghc >--------------------------------------------------------------- commit fd46acf1c30d81ce0ac676c5ca7ffe6e3c82ad25 Author: Simon Peyton Jones Date: Wed Oct 29 16:30:05 2014 +0000 Fix reduceTyFamApp_maybe This function previously would expand *data* families even when it was asked for a *Nominal* coercion. This patch fixes it, and adds comments. >--------------------------------------------------------------- fd46acf1c30d81ce0ac676c5ca7ffe6e3c82ad25 compiler/types/FamInstEnv.lhs | 46 ++++++++++++++++++++++++++++++++----------- 1 file changed, 34 insertions(+), 12 deletions(-) diff --git a/compiler/types/FamInstEnv.lhs b/compiler/types/FamInstEnv.lhs index 7fe35ff..bc21e2e 100644 --- a/compiler/types/FamInstEnv.lhs +++ b/compiler/types/FamInstEnv.lhs @@ -361,7 +361,8 @@ extendFamInstEnvList :: FamInstEnv -> [FamInst] -> FamInstEnv extendFamInstEnvList inst_env fis = foldl extendFamInstEnv inst_env fis extendFamInstEnv :: FamInstEnv -> FamInst -> FamInstEnv -extendFamInstEnv inst_env ins_item@(FamInst {fi_fam = cls_nm}) +extendFamInstEnv inst_env + ins_item@(FamInst {fi_fam = cls_nm}) = addToUFM_C add inst_env cls_nm (FamIE [ins_item]) where add (FamIE items) _ = FamIE (ins_item:items) @@ -789,18 +790,33 @@ The lookupFamInstEnv function does a nice job for *open* type families, but we also need to handle closed ones when normalising a type: \begin{code} -reduceTyFamApp_maybe :: FamInstEnvs -> Role -> TyCon -> [Type] -> Maybe (Coercion, Type) +reduceTyFamApp_maybe :: FamInstEnvs + -> Role -- Desired role of result coercion + -> TyCon -> [Type] + -> Maybe (Coercion, Type) -- Attempt to do a *one-step* reduction of a type-family application +-- but *not* newtypes +-- Works on type-synonym families always; data-families only if +-- the role we seek is representational -- It first normalises the type arguments, wrt functions but *not* newtypes, --- to be sure that nested calls like --- F (G Int) --- are correctly reduced +-- to be sure that nested calls like +-- F (G Int) +-- are correctly reduced -- -- The TyCon can be oversaturated. -- Works on both open and closed families reduceTyFamApp_maybe envs role tc tys - | isOpenFamilyTyCon tc + | Phantom <- role + = Nothing + + | case role of + Representational -> isOpenFamilyTyCon tc + _ -> isOpenSynFamilyTyCon tc + -- If we seek a representational coercion + -- (e.g. the call in topNormaliseType_maybe) then we can + -- unwrap data families as well as type-synonym families; + -- otherwise only type-synonym families , [FamInstMatch { fim_instance = fam_inst , fim_tys = inst_tys }] <- lookupFamInstEnv envs tc ntys = let ax = famInstAxiom fam_inst @@ -927,12 +943,18 @@ topNormaliseType_maybe env ty --------------- normaliseTcApp :: FamInstEnvs -> Role -> TyCon -> [Type] -> (Coercion, Type) +-- See comments on normaliseType for the arguments of this function normaliseTcApp env role tc tys + | isTypeSynonymTyCon tc + , (co1, ntys) <- normaliseTcArgs env role tc tys + , Just (tenv, rhs, ntys') <- tcExpandTyCon_maybe tc ntys + , (co2, ninst_rhs) <- normaliseType env role (Type.substTy (mkTopTvSubst tenv) rhs) + = if isReflCo co2 then (co1, mkTyConApp tc ntys) + else (co1 `mkTransCo` co2, mkAppTys ninst_rhs ntys') + | Just (first_co, ty') <- reduceTyFamApp_maybe env role tc tys - = let -- A reduction is possible - (rest_co,nty) = normaliseType env role ty' - in - (first_co `mkTransCo` rest_co, nty) + , (rest_co,nty) <- normaliseType env role ty' + = (first_co `mkTransCo` rest_co, nty) | otherwise -- No unique matching family instance exists; -- we do not do anything @@ -958,10 +980,10 @@ normaliseType :: FamInstEnvs -- environment with family instances -> (Coercion, Type) -- (coercion,new type), where -- co :: old-type ~ new_type -- Normalise the input type, by eliminating *all* type-function redexes +-- but *not* newtypes (which are visible to the programmer) -- Returns with Refl if nothing happens +-- Try to not to disturb type syonyms if possible -normaliseType env role ty - | Just ty' <- coreView ty = normaliseType env role ty' normaliseType env role (TyConApp tc tys) = normaliseTcApp env role tc tys normaliseType _env role ty@(LitTy {}) = (Refl role ty, ty) From git at git.haskell.org Tue Nov 4 10:38:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:08 +0000 (UTC) Subject: [commit: ghc] master: White space only (bdbb595) Message-ID: <20141104103808.F03DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bdbb595cf5fbb871a8d4d19ce1b9400adefa0b1b/ghc >--------------------------------------------------------------- commit bdbb595cf5fbb871a8d4d19ce1b9400adefa0b1b Author: Simon Peyton Jones Date: Wed Oct 29 16:27:50 2014 +0000 White space only >--------------------------------------------------------------- bdbb595cf5fbb871a8d4d19ce1b9400adefa0b1b compiler/main/PprTyThing.hs | 2 +- compiler/typecheck/Inst.lhs | 96 +++++++++++++++++++++------------------ compiler/typecheck/TcDeriv.lhs | 6 +-- compiler/typecheck/TcGenDeriv.lhs | 2 +- compiler/types/InstEnv.lhs | 4 +- 5 files changed, 59 insertions(+), 51 deletions(-) diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs index eed4671..240e63b 100644 --- a/compiler/main/PprTyThing.hs +++ b/compiler/main/PprTyThing.hs @@ -128,7 +128,7 @@ pprTyThingInContextLoc tyThing ------------------------ ppr_ty_thing :: Bool -> [OccName] -> TyThing -> SDoc -- We pretty-print 'TyThing' via 'IfaceDecl' --- See Note [Pretty-pringint TyThings] +-- See Note [Pretty-printing TyThings] ppr_ty_thing hdr_only path ty_thing = pprIfaceDecl ss (tyThingToIfaceDecl ty_thing) where diff --git a/compiler/typecheck/Inst.lhs b/compiler/typecheck/Inst.lhs index 3405fd4..89955bf 100644 --- a/compiler/typecheck/Inst.lhs +++ b/compiler/typecheck/Inst.lhs @@ -473,52 +473,60 @@ addLocalInst (home_ie, my_insts) ispec dupInstErr ispec (head dups) ; return (extendInstEnv home_ie' ispec, ispec:my_insts') } +\end{code} + +Note [Signature files and type class instances] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Instances in signature files do not have an effect when compiling: +when you compile a signature against an implementation, you will +see the instances WHETHER OR NOT the instance is declared in +the file (this is because the signatures go in the EPS and we +can't filter them out easily.) This is also why we cannot +place the instance in the hi file: it would show up as a duplicate, +and we don't have instance reexports anyway. + +However, you might find them useful when typechecking against +a signature: the instance is a way of indicating to GHC that +some instance exists, in case downstream code uses it. + +Implementing this is a little tricky. Consider the following +situation (sigof03): + + module A where + instance C T where ... + + module ASig where + instance C T + +When compiling ASig, A.hi is loaded, which brings its instances +into the EPS. When we process the instance declaration in ASig, +we should ignore it for the purpose of doing a duplicate check, +since it's not actually a duplicate. But don't skip the check +entirely, we still want this to fail (tcfail221): + + module ASig where + instance C T + instance C T --- Note [Signature files and type class instances] --- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --- Instances in signature files do not have an effect when compiling: --- when you compile a signature against an implementation, you will --- see the instances WHETHER OR NOT the instance is declared in --- the file (this is because the signatures go in the EPS and we --- can't filter them out easily.) This is also why we cannot --- place the instance in the hi file: it would show up as a duplicate, --- and we don't have instance reexports anyway. --- --- However, you might find them useful when typechecking against --- a signature: the instance is a way of indicating to GHC that --- some instance exists, in case downstream code uses it. --- --- Implementing this is a little tricky. Consider the following --- situation (sigof03): --- --- module A where --- instance C T where ... --- --- module ASig where --- instance C T --- --- When compiling ASig, A.hi is loaded, which brings its instances --- into the EPS. When we process the instance declaration in ASig, --- we should ignore it for the purpose of doing a duplicate check, --- since it's not actually a duplicate. But don't skip the check --- entirely, we still want this to fail (tcfail221): --- --- module ASig where --- instance C T --- instance C T --- --- Note that in some situations, the interface containing the type --- class instances may not have been loaded yet at all. The usual --- situation when A imports another module which provides the --- instances (sigof02m): --- --- module A(module B) where --- import B --- --- See also Note [Signature lazy interface loading]. We can't --- rely on this, however, since sometimes we'll have spurious --- type class instances in the EPS, see #9422 (sigof02dm) +Note that in some situations, the interface containing the type +class instances may not have been loaded yet at all. The usual +situation when A imports another module which provides the +instances (sigof02m): + module A(module B) where + import B + +See also Note [Signature lazy interface loading]. We can't +rely on this, however, since sometimes we'll have spurious +type class instances in the EPS, see #9422 (sigof02dm) + +%************************************************************************ +%* * + Errors and tracing +%* * +%************************************************************************ + +\begin{code} traceDFuns :: [ClsInst] -> TcRn () traceDFuns ispecs = traceTc "Adding instances:" (vcat (map pp ispecs)) diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index 1ef3ab4..b39739d 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -402,8 +402,8 @@ tcDeriving tycl_decls inst_decls deriv_decls ; return (addTcgDUs gbl_env all_dus, inst_info, rn_binds) } where ddump_deriving :: Bag (InstInfo Name) -> HsValBinds Name - -> Bag TyCon -- ^ Empty data constructors - -> Bag (FamInst) -- ^ Rep type family instances + -> Bag TyCon -- ^ Empty data constructors + -> Bag FamInst -- ^ Rep type family instances -> SDoc ddump_deriving inst_infos extra_binds repMetaTys repFamInsts = hang (ptext (sLit "Derived instances:")) @@ -2041,7 +2041,7 @@ genDerivStuff loc clas dfun_name tycon comaux_maybe Just metaTyCons = comaux_maybe -- well-guarded by commonAuxiliaries and genInst in do (binds, faminst) <- gen_Generic_binds gk tycon metaTyCons (nameModule dfun_name) - return (binds, DerivFamInst faminst `consBag` emptyBag) + return (binds, unitBag (DerivFamInst faminst)) | otherwise -- Non-monadic generators = do dflags <- getDynFlags diff --git a/compiler/typecheck/TcGenDeriv.lhs b/compiler/typecheck/TcGenDeriv.lhs index e416aaf..31e31ed 100644 --- a/compiler/typecheck/TcGenDeriv.lhs +++ b/compiler/typecheck/TcGenDeriv.lhs @@ -85,7 +85,7 @@ data DerivStuff -- Please add this auxiliary stuff -- Generics | DerivTyCon TyCon -- New data types - | DerivFamInst (FamInst) -- New type family instances + | DerivFamInst FamInst -- New type family instances -- New top-level auxiliary bindings | DerivHsBind (LHsBind RdrName, LSig RdrName) -- Also used for SYB diff --git a/compiler/types/InstEnv.lhs b/compiler/types/InstEnv.lhs index 1e7e023..6d03fbe 100644 --- a/compiler/types/InstEnv.lhs +++ b/compiler/types/InstEnv.lhs @@ -161,8 +161,8 @@ pprInstance :: ClsInst -> SDoc -- Prints the ClsInst as an instance declaration pprInstance ispec = hang (pprInstanceHdr ispec) - 2 (vcat [ ptext (sLit "--") <+> pprDefinedAt (getName ispec) - , ifPprDebug (ppr (is_dfun ispec)) ]) + 2 (vcat [ ptext (sLit "--") <+> pprDefinedAt (getName ispec) + , ifPprDebug (ppr (is_dfun ispec)) ]) -- * pprInstanceHdr is used in VStudio to populate the ClassView tree pprInstanceHdr :: ClsInst -> SDoc From git at git.haskell.org Tue Nov 4 10:38:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:11 +0000 (UTC) Subject: [commit: ghc] master: Simplify the API for tcInstTyVars, and make it more consistent with other similar functions (33dcb81) Message-ID: <20141104103811.8D5143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/33dcb810c72e448c8db74decce8f1acef5e9295e/ghc >--------------------------------------------------------------- commit 33dcb810c72e448c8db74decce8f1acef5e9295e Author: Simon Peyton Jones Date: Wed Oct 29 16:34:05 2014 +0000 Simplify the API for tcInstTyVars, and make it more consistent with other similar functions >--------------------------------------------------------------- 33dcb810c72e448c8db74decce8f1acef5e9295e compiler/ghci/RtClosureInspect.hs | 10 +++++----- compiler/typecheck/Inst.lhs | 9 +++++++-- compiler/typecheck/TcExpr.lhs | 18 ++++++++++-------- compiler/typecheck/TcMType.lhs | 10 ++-------- compiler/typecheck/TcPat.lhs | 17 +++++++++-------- 5 files changed, 33 insertions(+), 31 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 33dcb810c72e448c8db74decce8f1acef5e9295e From git at git.haskell.org Tue Nov 4 10:38:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:14 +0000 (UTC) Subject: [commit: ghc] master: Refactor skolemising, and newClsInst (54f9188) Message-ID: <20141104103814.291863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/54f91886aa2562c0ae0386030b2d012c2f84707b/ghc >--------------------------------------------------------------- commit 54f91886aa2562c0ae0386030b2d012c2f84707b Author: Simon Peyton Jones Date: Wed Oct 29 16:26:53 2014 +0000 Refactor skolemising, and newClsInst This makes newClsInst (was mkInstance) look more like newFamInst, and simplifies the plumbing of the overlap flag, and ensures that freshening (required by the InstEnv stuff) happens in one place. On the way I also tided up the rather ragged family of tcInstSkolTyVars and friends. The result at least has more uniform naming. >--------------------------------------------------------------- 54f91886aa2562c0ae0386030b2d012c2f84707b compiler/typecheck/FamInst.lhs | 14 ++--- compiler/typecheck/Inst.lhs | 32 +++++++++-- compiler/typecheck/TcDeriv.lhs | 43 ++++++-------- compiler/typecheck/TcInstDcls.lhs | 11 +--- compiler/typecheck/TcMType.lhs | 116 ++++++++++++++++++++++---------------- 5 files changed, 115 insertions(+), 101 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 54f91886aa2562c0ae0386030b2d012c2f84707b From git at git.haskell.org Tue Nov 4 10:38:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:16 +0000 (UTC) Subject: [commit: ghc] master: Rename setRole_maybe to downgradeRole_maybe (9c81db4) Message-ID: <20141104103816.B451F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9c81db45b098b2a44b1cad3d1043fba49aa070a7/ghc >--------------------------------------------------------------- commit 9c81db45b098b2a44b1cad3d1043fba49aa070a7 Author: Simon Peyton Jones Date: Wed Oct 29 16:35:19 2014 +0000 Rename setRole_maybe to downgradeRole_maybe This change is just for naming uniformity with the existing downgradeRole >--------------------------------------------------------------- 9c81db45b098b2a44b1cad3d1043fba49aa070a7 compiler/types/Coercion.lhs | 36 ++++++++++++++++++------------------ 1 file changed, 18 insertions(+), 18 deletions(-) diff --git a/compiler/types/Coercion.lhs b/compiler/types/Coercion.lhs index 36eb711..dc0a7d0 100644 --- a/compiler/types/Coercion.lhs +++ b/compiler/types/Coercion.lhs @@ -844,7 +844,7 @@ mkSubCo: Requires a nominal input coercion and always produces a representational output. This is used when you (the programmer) are sure you know exactly that role you have and what you want. -setRole_maybe: This function takes both the input role and the output role +downgradeRole_maybe: This function takes both the input role and the output role as parameters. (The *output* role comes first!) It can only *downgrade* a role -- that is, change it from N to R or P, or from R to P. This one-way behavior is why there is the "_maybe". If an upgrade is requested, this @@ -853,10 +853,10 @@ coercion, but you're not sure (as you're writing the code) of which roles are involved. This function could have been written using coercionRole to ascertain the role -of the input. But, that function is recursive, and the caller of setRole_maybe +of the input. But, that function is recursive, and the caller of downgradeRole_maybe often knows the input role. So, this is more efficient. -downgradeRole: This is just like setRole_maybe, but it panics if the conversion +downgradeRole: This is just like downgradeRole_maybe, but it panics if the conversion isn't a downgrade. setNominalRole_maybe: This is the only function that can *upgrade* a coercion. The result @@ -880,7 +880,7 @@ API, as he was decomposing Core casts. The Core casts use representational coerc as they must, but his use case required nominal coercions (he was building a GADT). So, that's why this function is exported from this module. -One might ask: shouldn't setRole_maybe just use setNominalRole_maybe as appropriate? +One might ask: shouldn't downgradeRole_maybe just use setNominalRole_maybe as appropriate? I (Richard E.) have decided not to do this, because upgrading a role is bizarre and a caller should have to ask for this behavior explicitly. @@ -1081,15 +1081,15 @@ mkSubCo co = ASSERT2( coercionRole co == Nominal, ppr co <+> ppr (coercionRole c SubCo co -- only *downgrades* a role. See Note [Role twiddling functions] -setRole_maybe :: Role -- desired role - -> Role -- current role - -> Coercion -> Maybe Coercion -setRole_maybe Representational Nominal = Just . mkSubCo -setRole_maybe Nominal Representational = const Nothing -setRole_maybe Phantom Phantom = Just -setRole_maybe Phantom _ = Just . mkPhantomCo -setRole_maybe _ Phantom = const Nothing -setRole_maybe _ _ = Just +downgradeRole_maybe :: Role -- desired role + -> Role -- current role + -> Coercion -> Maybe Coercion +downgradeRole_maybe Representational Nominal co = Just (mkSubCo co) +downgradeRole_maybe Nominal Representational _ = Nothing +downgradeRole_maybe Phantom Phantom co = Just co +downgradeRole_maybe Phantom _ co = Just (mkPhantomCo co) +downgradeRole_maybe _ Phantom _ = Nothing +downgradeRole_maybe _ _ co = Just co -- panics if the requested conversion is not a downgrade. -- See also Note [Role twiddling functions] @@ -1097,7 +1097,7 @@ downgradeRole :: Role -- desired role -> Role -- current role -> Coercion -> Coercion downgradeRole r1 r2 co - = case setRole_maybe r1 r2 co of + = case downgradeRole_maybe r1 r2 co of Just co' -> co' Nothing -> pprPanic "downgradeRole" (ppr co) @@ -1158,8 +1158,9 @@ nthRole Phantom _ _ = Phantom nthRole Representational tc n = (tyConRolesX Representational tc) !! n --- is one role "less" than another? ltRole :: Role -> Role -> Bool +-- Is one role "less" than another? +-- Nominal < Representational < Phantom ltRole Phantom _ = False ltRole Representational Phantom = True ltRole Representational _ = False @@ -1619,17 +1620,16 @@ failing for reason 2) is fine. matchAxiom is trying to find a set of coercions that match, but it may fail, and this is healthy behavior. Bottom line: if you find that liftCoSubst is doing weird things (like leaving out-of-scope variables lying around), disable coercion optimization (bypassing matchAxiom) -and use downgradeRole instead of setRole_maybe. The panic will then happen, +and use downgradeRole instead of downgradeRole_maybe. The panic will then happen, and you may learn something useful. \begin{code} - liftCoSubstTyVar :: LiftCoSubst -> Role -> TyVar -> Maybe Coercion liftCoSubstTyVar (LCS _ cenv) r tv = do { co <- lookupVarEnv cenv tv ; let co_role = coercionRole co -- could theoretically take this as -- a parameter, but painful - ; setRole_maybe r co_role co } -- see Note [liftCoSubstTyVar] + ; downgradeRole_maybe r co_role co } -- see Note [liftCoSubstTyVar] liftCoSubstTyVarBndr :: LiftCoSubst -> TyVar -> (LiftCoSubst, TyVar) liftCoSubstTyVarBndr subst@(LCS in_scope cenv) old_var From git at git.haskell.org Tue Nov 4 10:38:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:19 +0000 (UTC) Subject: [commit: ghc] master: Get the Untouchables level right in simplifyInfer (e11e1b8) Message-ID: <20141104103819.65C4E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e11e1b80324cd165f5439132384b56dd72355718/ghc >--------------------------------------------------------------- commit e11e1b80324cd165f5439132384b56dd72355718 Author: Simon Peyton Jones Date: Wed Oct 29 17:18:33 2014 +0000 Get the Untouchables level right in simplifyInfer Previously we could get constraints in which the untouchables-level did not strictly increase, which is one of the main invariants! This patch also simplifies and modularises the tricky case of generalising an inferred let-binding >--------------------------------------------------------------- e11e1b80324cd165f5439132384b56dd72355718 compiler/typecheck/FunDeps.lhs | 42 +------ compiler/typecheck/TcBinds.lhs | 7 +- compiler/typecheck/TcPatSyn.lhs | 17 ++- compiler/typecheck/TcSimplify.lhs | 233 +++++++++++++++++++++++++----------- compiler/typecheck/TcTyClsDecls.lhs | 2 +- 5 files changed, 177 insertions(+), 124 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e11e1b80324cd165f5439132384b56dd72355718 From git at git.haskell.org Tue Nov 4 10:38:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:22 +0000 (UTC) Subject: [commit: ghc] master: Refactor the treatment of lexically-scoped type variables for instance declarations (2bfc653) Message-ID: <20141104103822.0798E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2bfc65303e0d6f2ee25a565d0998d6c00aab24d5/ghc >--------------------------------------------------------------- commit 2bfc65303e0d6f2ee25a565d0998d6c00aab24d5 Author: Simon Peyton Jones Date: Wed Oct 29 16:54:47 2014 +0000 Refactor the treatment of lexically-scoped type variables for instance declarations Previously the univerally-quantified variables of the DFun were also (bizarrely) used as the lexically-scoped variables of the instance declaration. So, for example, the DFun's type could not be alpha-renamed. This was an odd restriction, which has bitten me several times. This patch does the Right Thing, by adding an ib_tyvars field to the InstBindings record, which captures the lexically scoped variables. Easy, robust, nice. (I think this record probably didn't exist originally, hence the hack.) >--------------------------------------------------------------- 2bfc65303e0d6f2ee25a565d0998d6c00aab24d5 compiler/typecheck/TcDeriv.lhs | 20 ++++++++++---------- compiler/typecheck/TcEnv.lhs | 13 +++++++++---- compiler/typecheck/TcGenGenerics.lhs | 3 +++ compiler/typecheck/TcInstDcls.lhs | 13 ++++++------- 4 files changed, 28 insertions(+), 21 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2bfc65303e0d6f2ee25a565d0998d6c00aab24d5 From git at git.haskell.org Tue Nov 4 10:38:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:24 +0000 (UTC) Subject: [commit: ghc] master: Typechecker debug tracing only (e840d85) Message-ID: <20141104103824.9B1D13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e840d85309ba1de954dad6ad3acfdddafc5d5ac6/ghc >--------------------------------------------------------------- commit e840d85309ba1de954dad6ad3acfdddafc5d5ac6 Author: Simon Peyton Jones Date: Wed Oct 29 17:22:57 2014 +0000 Typechecker debug tracing only >--------------------------------------------------------------- e840d85309ba1de954dad6ad3acfdddafc5d5ac6 compiler/typecheck/TcErrors.lhs | 1 + compiler/typecheck/TcHsType.lhs | 9 ++++--- compiler/typecheck/TcRnDriver.lhs | 2 +- compiler/typecheck/TcRnMonad.lhs | 57 ++++++++++++++++++++------------------- 4 files changed, 38 insertions(+), 31 deletions(-) diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs index 210bd79..72fe9fa 100644 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@ -606,6 +606,7 @@ mkEqErr1 ctxt ct ; (env1, tidy_orig) <- zonkTidyOrigin (cec_tidy ctxt) (ctLocOrigin loc) ; let (is_oriented, wanted_msg) = mk_wanted_extra tidy_orig ; dflags <- getDynFlags + ; traceTc "mkEqErr1" (ppr ct $$ pprCtOrigin (ctLocOrigin loc) $$ pprCtOrigin tidy_orig) ; mkEqErr_help dflags (ctxt {cec_tidy = env1}) (wanted_msg $$ binds_msg) ct is_oriented ty1 ty2 } diff --git a/compiler/typecheck/TcHsType.lhs b/compiler/typecheck/TcHsType.lhs index c9f0e2f..d6f237f 100644 --- a/compiler/typecheck/TcHsType.lhs +++ b/compiler/typecheck/TcHsType.lhs @@ -425,9 +425,11 @@ tc_hs_type hs_ty@(HsPArrTy elt_ty) exp_kind tc_hs_type hs_ty@(HsTupleTy HsBoxedOrConstraintTuple hs_tys) exp_kind@(EK exp_k _ctxt) -- (NB: not zonking before looking at exp_k, to avoid left-right bias) | Just tup_sort <- tupKindSort_maybe exp_k - = tc_tuple hs_ty tup_sort hs_tys exp_kind + = traceTc "tc_hs_type tuple" (ppr hs_tys) >> + tc_tuple hs_ty tup_sort hs_tys exp_kind | otherwise - = do { (tys, kinds) <- mapAndUnzipM tc_infer_lhs_type hs_tys + = do { traceTc "tc_hs_type tuple 2" (ppr hs_tys) + ; (tys, kinds) <- mapAndUnzipM tc_infer_lhs_type hs_tys ; kinds <- mapM zonkTcKind kinds -- Infer each arg type separately, because errors can be -- confusing if we give them a shared kind. Eg Trac #7410 @@ -554,7 +556,8 @@ tc_tuple hs_ty tup_sort tys exp_kind finish_tuple :: HsType Name -> TupleSort -> [TcType] -> ExpKind -> TcM TcType finish_tuple hs_ty tup_sort tau_tys exp_kind - = do { checkExpectedKind hs_ty res_kind exp_kind + = do { traceTc "finish_tuple" (ppr res_kind $$ ppr exp_kind $$ ppr exp_kind) + ; checkExpectedKind hs_ty res_kind exp_kind ; checkWiredInTyCon tycon ; return (mkTyConApp tycon tau_tys) } where diff --git a/compiler/typecheck/TcRnDriver.lhs b/compiler/typecheck/TcRnDriver.lhs index e6f7824..9ac01ed 100644 --- a/compiler/typecheck/TcRnDriver.lhs +++ b/compiler/typecheck/TcRnDriver.lhs @@ -1916,7 +1916,7 @@ tcDump env -- Dump short output if -ddump-types or -ddump-tc when (dopt Opt_D_dump_types dflags || dopt Opt_D_dump_tc dflags) - (dumpTcRn short_dump) ; + (printForUserTcRn short_dump) ; -- Dump bindings if -ddump-tc dumpOptTcRn Opt_D_dump_tc (mkDumpDoc "Typechecker" full_dump) diff --git a/compiler/typecheck/TcRnMonad.lhs b/compiler/typecheck/TcRnMonad.lhs index bd6218c..dce4b49 100644 --- a/compiler/typecheck/TcRnMonad.lhs +++ b/compiler/typecheck/TcRnMonad.lhs @@ -192,8 +192,7 @@ initTc hsc_env hsc_src keep_rn_syntax mod do_this lie <- readIORef lie_var ; if isEmptyWC lie then return () - else pprPanic "initTc: unsolved constraints" - (pprWantedsWithLocs lie) ; + else pprPanic "initTc: unsolved constraints" (ppr lie) ; -- Collect any error messages msgs <- readIORef errs_var ; @@ -487,25 +486,35 @@ traceIf = traceOptIf Opt_D_dump_if_trace traceHiDiffs = traceOptIf Opt_D_dump_hi_diffs -traceOptIf :: DumpFlag -> SDoc -> TcRnIf m n () -- No RdrEnv available, so qualify everything -traceOptIf flag doc = whenDOptM flag $ - do dflags <- getDynFlags - liftIO (printInfoForUser dflags alwaysQualify doc) +traceOptIf :: DumpFlag -> SDoc -> TcRnIf m n () +traceOptIf flag doc + = whenDOptM flag $ -- No RdrEnv available, so qualify everything + do { dflags <- getDynFlags + ; liftIO (putMsg dflags doc) } traceOptTcRn :: DumpFlag -> SDoc -> TcRn () -- Output the message, with current location if opt_PprStyle_Debug -traceOptTcRn flag doc = whenDOptM flag $ do - { loc <- getSrcSpanM - ; let real_doc - | opt_PprStyle_Debug = mkLocMessage SevInfo loc doc - | otherwise = doc -- The full location is - -- usually way too much - ; dumpTcRn real_doc } +traceOptTcRn flag doc + = whenDOptM flag $ + do { loc <- getSrcSpanM + ; let real_doc + | opt_PprStyle_Debug = mkLocMessage SevInfo loc doc + | otherwise = doc -- The full location is + -- usually way too much + ; dumpTcRn real_doc } dumpTcRn :: SDoc -> TcRn () -dumpTcRn doc = do { rdr_env <- getGlobalRdrEnv - ; dflags <- getDynFlags - ; liftIO (printInfoForUser dflags (mkPrintUnqualified dflags rdr_env) doc) } +dumpTcRn doc + = do { dflags <- getDynFlags + ; rdr_env <- getGlobalRdrEnv + ; liftIO (logInfo dflags (mkDumpStyle (mkPrintUnqualified dflags rdr_env)) doc) } + +printForUserTcRn :: SDoc -> TcRn () +-- Like dumpTcRn, but for user consumption +printForUserTcRn doc + = do { dflags <- getDynFlags + ; rdr_env <- getGlobalRdrEnv + ; liftIO (printInfoForUser dflags (mkPrintUnqualified dflags rdr_env) doc) } debugDumpTcRn :: SDoc -> TcRn () debugDumpTcRn doc | opt_NoDebugOutput = return () @@ -698,14 +707,6 @@ reportWarning warn errs_var <- getErrsVar ; (warns, errs) <- readTcRef errs_var ; writeTcRef errs_var (warns `snocBag` warn, errs) } - -dumpDerivingInfo :: SDoc -> TcM () -dumpDerivingInfo doc - = do { dflags <- getDynFlags - ; when (dopt Opt_D_dump_deriv dflags) $ do - { rdr_env <- getGlobalRdrEnv - ; let unqual = mkPrintUnqualified dflags rdr_env - ; liftIO (putMsgWith dflags unqual doc) } } \end{code} @@ -1052,9 +1053,11 @@ newTcEvBinds = do { ref <- newTcRef emptyEvBindMap addTcEvBind :: EvBindsVar -> EvVar -> EvTerm -> TcM () -- Add a binding to the TcEvBinds by side effect -addTcEvBind (EvBindsVar ev_ref _) var t - = do { bnds <- readTcRef ev_ref - ; writeTcRef ev_ref (extendEvBinds bnds var t) } +addTcEvBind (EvBindsVar ev_ref _) ev_id ev_tm + = do { traceTc "addTcEvBind" $ vcat [ text "ev_id =" <+> ppr ev_id + , text "ev_tm =" <+> ppr ev_tm ] + ; bnds <- readTcRef ev_ref + ; writeTcRef ev_ref (extendEvBinds bnds ev_id ev_tm) } getTcEvBinds :: EvBindsVar -> TcM (Bag EvBind) getTcEvBinds (EvBindsVar ev_ref _) From git at git.haskell.org Tue Nov 4 10:38:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:27 +0000 (UTC) Subject: [commit: ghc] master: Normalise the type of an inferred let-binding (a6e7654) Message-ID: <20141104103827.3B4A43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a6e7654b495f68adcdcf3ffe920d5aa1b5a9b7dc/ghc >--------------------------------------------------------------- commit a6e7654b495f68adcdcf3ffe920d5aa1b5a9b7dc Author: Simon Peyton Jones Date: Wed Oct 29 17:21:05 2014 +0000 Normalise the type of an inferred let-binding With the new constraint solver, we don't guarantee to fully-normalise all constraints (if doing so is not necessary to solve them). So we may end up with an inferred type like f :: [F Int] -> Bool which could be simplifed to f :: [Char] -> Bool if there is a suitable family instance declaration. This patch does this normalisation, in TcBinds.mkExport >--------------------------------------------------------------- a6e7654b495f68adcdcf3ffe920d5aa1b5a9b7dc compiler/typecheck/TcBinds.lhs | 26 +++++++++++++++++--------- compiler/typecheck/TcRnDriver.lhs | 7 ++++--- 2 files changed, 21 insertions(+), 12 deletions(-) diff --git a/compiler/typecheck/TcBinds.lhs b/compiler/typecheck/TcBinds.lhs index 9f3576d..3741273 100644 --- a/compiler/typecheck/TcBinds.lhs +++ b/compiler/typecheck/TcBinds.lhs @@ -31,8 +31,9 @@ import TcPat import TcMType import PatSyn import ConLike +import FamInstEnv( normaliseType ) +import FamInst( tcGetFamInstEnvs ) import Type( tidyOpenType ) -import FunDeps( growThetaTyVars ) import TyCon import TcType import TysPrim @@ -678,15 +679,22 @@ mkInferredPolyId :: Name -> [TyVar] -> TcThetaType -> TcType -> TcM Id -- the right type variables and theta to quantify over -- See Note [Validity of inferred types] mkInferredPolyId poly_name qtvs theta mono_ty - = addErrCtxtM (mk_bind_msg True False poly_name inferred_poly_ty) $ - do { checkValidType (InfSigCtxt poly_name) inferred_poly_ty - ; return (mkLocalId poly_name inferred_poly_ty) } - where - my_tvs2 = closeOverKinds (growThetaTyVars theta (tyVarsOfType mono_ty)) + = do { fam_envs <- tcGetFamInstEnvs + + ; let (_co, norm_mono_ty) = normaliseType fam_envs Nominal mono_ty + -- Unification may not have normalised the type, so do it + -- here to make it as uncomplicated as possible. + -- Example: f :: [F Int] -> Bool + -- should be rewritten to f :: [Char] -> Bool, if possible + my_tvs2 = closeOverKinds (growThetaTyVars theta (tyVarsOfType norm_mono_ty)) -- Include kind variables! Trac #7916 - my_tvs = filter (`elemVarSet` my_tvs2) qtvs -- Maintain original order - my_theta = filter (quantifyPred my_tvs2) theta - inferred_poly_ty = mkSigmaTy my_tvs my_theta mono_ty + my_tvs = filter (`elemVarSet` my_tvs2) qtvs -- Maintain original order + my_theta = filter (quantifyPred my_tvs2) theta + inferred_poly_ty = mkSigmaTy my_tvs my_theta norm_mono_ty + + ; addErrCtxtM (mk_bind_msg True False poly_name inferred_poly_ty) $ + checkValidType (InfSigCtxt poly_name) inferred_poly_ty + ; return (mkLocalId poly_name inferred_poly_ty) } mk_bind_msg :: Bool -> Bool -> Name -> TcType -> TidyEnv -> TcM (TidyEnv, SDoc) mk_bind_msg inferred want_ambig poly_name poly_ty tidy_env diff --git a/compiler/typecheck/TcRnDriver.lhs b/compiler/typecheck/TcRnDriver.lhs index b628591..e6f7824 100644 --- a/compiler/typecheck/TcRnDriver.lhs +++ b/compiler/typecheck/TcRnDriver.lhs @@ -1641,11 +1641,12 @@ tcRnExpr hsc_env rdr_expr -- it might have a rank-2 type (e.g. :t runST) uniq <- newUnique ; let { fresh_it = itName uniq (getLoc rdr_expr) } ; - ((_tc_expr, res_ty), lie) <- captureConstraints $ - tcInferRho rn_expr ; + (((_tc_expr, res_ty), untch), lie) <- captureConstraints $ + captureUntouchables $ + tcInferRho rn_expr ; ((qtvs, dicts, _, _), lie_top) <- captureConstraints $ {-# SCC "simplifyInfer" #-} - simplifyInfer True {- Free vars are closed -} + simplifyInfer untch False {- No MR for now -} [(fresh_it, res_ty)] lie ; From git at git.haskell.org Tue Nov 4 10:38:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:29 +0000 (UTC) Subject: [commit: ghc] master: Don't filter out allegedly-irrelevant bindings with -dppr-debug (f054822) Message-ID: <20141104103829.C08943A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f054822c0c977922860bedfc937f2a75e04fa797/ghc >--------------------------------------------------------------- commit f054822c0c977922860bedfc937f2a75e04fa797 Author: Simon Peyton Jones Date: Wed Oct 29 17:50:44 2014 +0000 Don't filter out allegedly-irrelevant bindings with -dppr-debug >--------------------------------------------------------------- f054822c0c977922860bedfc937f2a75e04fa797 compiler/typecheck/TcErrors.lhs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs index 0596e0c..d2d8133 100644 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@ -40,6 +40,7 @@ import FastString import Outputable import SrcLoc import DynFlags +import StaticFlags ( opt_PprStyle_Debug ) import ListSetOps ( equivClasses ) import Data.Maybe @@ -1422,7 +1423,8 @@ relevantBindings want_filtering ctxt ct <+> ppr (getSrcLoc id)))] new_seen = tvs_seen `unionVarSet` id_tvs - ; if (want_filtering && id_tvs `disjointVarSet` ct_tvs) + ; if (want_filtering && not opt_PprStyle_Debug + && id_tvs `disjointVarSet` ct_tvs) -- We want to filter out this binding anyway -- so discard it silently then go tidy_env n_left tvs_seen docs discards tc_bndrs From git at git.haskell.org Tue Nov 4 10:38:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:32 +0000 (UTC) Subject: [commit: ghc] master: Only report "could not deduce s~t from ..." for givens that include equalities (15131ec) Message-ID: <20141104103832.568863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/15131ecbdac503af15d45c2e4463ac2018d6603b/ghc >--------------------------------------------------------------- commit 15131ecbdac503af15d45c2e4463ac2018d6603b Author: Simon Peyton Jones Date: Wed Oct 29 17:49:34 2014 +0000 Only report "could not deduce s~t from ..." for givens that include equalities This just simplifies the error message in cases where there are no useful equalities in the context >--------------------------------------------------------------- 15131ecbdac503af15d45c2e4463ac2018d6603b compiler/typecheck/TcErrors.lhs | 14 ++++++++------ 1 file changed, 8 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs index 9a6b31f..0596e0c 100644 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@ -424,14 +424,15 @@ mkErrorMsg ctxt ct msg ; err_info <- mkErrInfo (cec_tidy ctxt) (tcl_ctxt tcl_env) ; mkLongErrAt (tcl_loc tcl_env) msg err_info } -type UserGiven = ([EvVar], SkolemInfo, SrcSpan) +type UserGiven = ([EvVar], SkolemInfo, Bool, SrcSpan) getUserGivens :: ReportErrCtxt -> [UserGiven] -- One item for each enclosing implication getUserGivens (CEC {cec_encl = ctxt}) = reverse $ - [ (givens, info, tcl_loc env) - | Implic {ic_given = givens, ic_env = env, ic_info = info } <- ctxt + [ (givens, info, no_eqs, tcl_loc env) + | Implic { ic_given = givens, ic_env = env + , ic_no_eqs = no_eqs, ic_info = info } <- ctxt , not (null givens) ] \end{code} @@ -795,7 +796,8 @@ misMatchOrCND ctxt ct oriented ty1 ty2 | otherwise = couldNotDeduce givens ([mkTcEqPred ty1 ty2], orig) where - givens = getUserGivens ctxt + givens = [ given | given@(_, _, no_eqs, _) <- getUserGivens ctxt, not no_eqs] + -- Keep only UserGivens that have some equalities orig = TypeEqOrigin { uo_actual = ty1, uo_expected = ty2 } couldNotDeduce :: [UserGiven] -> (ThetaType, CtOrigin) -> SDoc @@ -810,7 +812,7 @@ pp_givens givens (g:gs) -> ppr_given (ptext (sLit "from the context")) g : map (ppr_given (ptext (sLit "or from"))) gs where - ppr_given herald (gs, skol_info, loc) + ppr_given herald (gs, skol_info, _, loc) = hang (herald <+> pprEvVarTheta gs) 2 (sep [ ptext (sLit "bound by") <+> ppr skol_info , ptext (sLit "at") <+> ppr loc]) @@ -1135,7 +1137,7 @@ mk_dict_err fam_envs ctxt (ct, (matches, unifiers, safe_haskell)) givens = getUserGivens ctxt matching_givens = mapMaybe matchable givens - matchable (evvars,skol_info,loc) + matchable (evvars,skol_info,_,loc) = case ev_vars_matching of [] -> Nothing _ -> Just $ hang (pprTheta ev_vars_matching) From git at git.haskell.org Tue Nov 4 10:38:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:34 +0000 (UTC) Subject: [commit: ghc] master: When reporting the context of given constraints, stop when you find one that binds a variable mentioned in the wanted (c64539c) Message-ID: <20141104103834.E5AEC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c64539cdea1ba9ac3ab2613e0f320e74859a37ff/ghc >--------------------------------------------------------------- commit c64539cdea1ba9ac3ab2613e0f320e74859a37ff Author: Simon Peyton Jones Date: Wed Oct 29 17:45:34 2014 +0000 When reporting the context of given constraints, stop when you find one that binds a variable mentioned in the wanted There is really no point in reporting ones further out; they can't be useful >--------------------------------------------------------------- c64539cdea1ba9ac3ab2613e0f320e74859a37ff compiler/typecheck/TcErrors.lhs | 23 +++++++++++++++++------ 1 file changed, 17 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs index 72fe9fa..9a6b31f 100644 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@ -1068,7 +1068,7 @@ mk_dict_err fam_envs ctxt (ct, (matches, unifiers, safe_haskell)) add_to_ctxt_fixes has_ambig_tvs | not has_ambig_tvs && all_tyvars - , (orig:origs) <- mapMaybe get_good_orig (cec_encl ctxt) + , (orig:origs) <- usefulContext ctxt pred = [sep [ ptext (sLit "add") <+> pprParendType pred <+> ptext (sLit "to the context of") , nest 2 $ ppr_skol orig $$ @@ -1079,11 +1079,6 @@ mk_dict_err fam_envs ctxt (ct, (matches, unifiers, safe_haskell)) ppr_skol (PatSkol dc _) = ptext (sLit "the data constructor") <+> quotes (ppr dc) ppr_skol skol_info = ppr skol_info - -- Do not suggest adding constraints to an *inferred* type signature! - get_good_orig ic = case ic_info ic of - SigSkol (InfSigCtxt {}) _ -> Nothing - origin -> Just origin - no_inst_msg | clas == coercibleClass = let (ty1, ty2) = getEqPredTys pred @@ -1218,6 +1213,22 @@ mk_dict_err fam_envs ctxt (ct, (matches, unifiers, safe_haskell)) , ptext (sLit "is not in scope") ]) | otherwise = Nothing +usefulContext :: ReportErrCtxt -> TcPredType -> [SkolemInfo] +usefulContext ctxt pred + = go (cec_encl ctxt) + where + pred_tvs = tyVarsOfType pred + go [] = [] + go (ic : ics) + = case ic_info ic of + -- Do not suggest adding constraints to an *inferred* type signature! + SigSkol (InfSigCtxt {}) _ -> rest + info -> info : rest + where + -- Stop when the context binds a variable free in the predicate + rest | any (`elemVarSet` pred_tvs) (ic_skols ic) = [] + | otherwise = go ics + show_fixes :: [SDoc] -> SDoc show_fixes [] = empty show_fixes (f:fs) = sep [ ptext (sLit "Possible fix:") From git at git.haskell.org Tue Nov 4 10:38:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:37 +0000 (UTC) Subject: [commit: ghc] master: Define ctEvLoc and ctEvCoercion, and use them (c1a85b3) Message-ID: <20141104103837.76E313A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c1a85b321768d3e13adbbfaa5413bcff310ffb2e/ghc >--------------------------------------------------------------- commit c1a85b321768d3e13adbbfaa5413bcff310ffb2e Author: Simon Peyton Jones Date: Thu Oct 30 09:08:23 2014 +0000 Define ctEvLoc and ctEvCoercion, and use them >--------------------------------------------------------------- c1a85b321768d3e13adbbfaa5413bcff310ffb2e compiler/typecheck/TcErrors.lhs | 4 ++-- compiler/typecheck/TcRnTypes.lhs | 16 +++++++++++++--- 2 files changed, 15 insertions(+), 5 deletions(-) diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs index 927f522..9e9e551 100644 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@ -614,7 +614,7 @@ mkEqErr1 ctxt ct ct is_oriented ty1 ty2 } where ev = ctEvidence ct - loc = ctev_loc ev + loc = ctEvLoc ev (ty1, ty2) = getEqPredTys (ctEvPred ev) mk_given :: [Implication] -> (CtLoc, SDoc) @@ -1480,7 +1480,7 @@ solverDepthErrorTcS cnt ev tidy_pred = tidyType tidy_env pred ; failWithTcM (tidy_env, hang (msg cnt) 2 (ppr tidy_pred)) } where - loc = ctev_loc ev + loc = ctEvLoc ev depth = ctLocDepth loc value = subGoalCounterValue cnt depth msg CountConstraints = diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index 86475e0..7e80906 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -52,7 +52,7 @@ module TcRnTypes( isGivenCt, isHoleCt, ctEvidence, ctLoc, ctPred, mkNonCanonical, mkNonCanonicalCt, - ctEvPred, ctEvTerm, ctEvId, ctEvCheckDepth, + ctEvPred, ctEvLoc, ctEvTerm, ctEvCoercion, ctEvId, ctEvCheckDepth, WantedConstraints(..), insolubleWC, emptyWC, isEmptyWC, andWC, unionsWC, addFlats, addImplics, mkFlatWC, addInsols, @@ -1114,7 +1114,7 @@ ctEvidence :: Ct -> CtEvidence ctEvidence = cc_ev ctLoc :: Ct -> CtLoc -ctLoc = ctev_loc . cc_ev +ctLoc = ctEvLoc . ctEvidence ctPred :: Ct -> PredType -- See Note [Ct/evidence invariant] @@ -1480,16 +1480,26 @@ ctEvPred :: CtEvidence -> TcPredType -- The predicate of a flavor ctEvPred = ctev_pred +ctEvLoc :: CtEvidence -> CtLoc +ctEvLoc = ctev_loc + ctEvTerm :: CtEvidence -> EvTerm ctEvTerm (CtGiven { ctev_evtm = tm }) = tm ctEvTerm (CtWanted { ctev_evar = ev }) = EvId ev ctEvTerm ctev@(CtDerived {}) = pprPanic "ctEvTerm: derived constraint cannot have id" (ppr ctev) +ctEvCoercion :: CtEvidence -> TcCoercion +-- ctEvCoercion ev = evTermCoercion (ctEvTerm ev) +ctEvCoercion (CtGiven { ctev_evtm = tm }) = evTermCoercion tm +ctEvCoercion (CtWanted { ctev_evar = v }) = mkTcCoVarCo v +ctEvCoercion ctev@(CtDerived {}) = pprPanic "ctEvCoercion: derived constraint cannot have id" + (ppr ctev) + -- | Checks whether the evidence can be used to solve a goal with the given minimum depth ctEvCheckDepth :: SubGoalDepth -> CtEvidence -> Bool ctEvCheckDepth _ (CtGiven {}) = True -- Given evidence has infinite depth -ctEvCheckDepth min ev@(CtWanted {}) = min <= ctLocDepth (ctev_loc ev) +ctEvCheckDepth min ev@(CtWanted {}) = min <= ctLocDepth (ctEvLoc ev) ctEvCheckDepth _ ev@(CtDerived {}) = pprPanic "ctEvCheckDepth: cannot consider derived evidence" (ppr ev) ctEvId :: CtEvidence -> TcId From git at git.haskell.org Tue Nov 4 10:38:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:40 +0000 (UTC) Subject: [commit: ghc] master: Minor refactoring (no change in functionality) (84d9ef0) Message-ID: <20141104103840.0FA923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/84d9ef0f38a11ef9bcfbdc82cbf5bd39c6fc473a/ghc >--------------------------------------------------------------- commit 84d9ef0f38a11ef9bcfbdc82cbf5bd39c6fc473a Author: Simon Peyton Jones Date: Wed Oct 29 17:51:41 2014 +0000 Minor refactoring (no change in functionality) >--------------------------------------------------------------- 84d9ef0f38a11ef9bcfbdc82cbf5bd39c6fc473a compiler/typecheck/TcErrors.lhs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs index d2d8133..927f522 100644 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@ -989,7 +989,9 @@ mkDictErr ctxt cts = ASSERT( not (null cts) ) do { inst_envs <- tcGetInstEnvs ; fam_envs <- tcGetFamInstEnvs - ; lookups <- mapM (lookup_cls_inst inst_envs) cts + ; let (ct1:_) = cts -- ct1 just for its location + min_cts = elim_superclasses cts + ; lookups <- mapM (lookup_cls_inst inst_envs) min_cts ; let (no_inst_cts, overlap_cts) = partition is_no_inst lookups -- Report definite no-instance errors, @@ -1000,8 +1002,6 @@ mkDictErr ctxt cts ; (ctxt, err) <- mk_dict_err fam_envs ctxt (head (no_inst_cts ++ overlap_cts)) ; mkErrorMsg ctxt ct1 err } where - ct1:_ = elim_superclasses cts - no_givens = null (getUserGivens ctxt) is_no_inst (ct, (matches, unifiers, _)) From git at git.haskell.org Tue Nov 4 10:38:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:43 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #9708 (f861fc6) Message-ID: <20141104103843.2E4C43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f861fc6ad8e5504a4fecfc9bb0945fe2d313687c/ghc >--------------------------------------------------------------- commit f861fc6ad8e5504a4fecfc9bb0945fe2d313687c Author: Simon Peyton Jones Date: Thu Oct 30 11:39:39 2014 +0000 Test Trac #9708 >--------------------------------------------------------------- f861fc6ad8e5504a4fecfc9bb0945fe2d313687c testsuite/tests/typecheck/should_compile/T9708.hs | 10 ++++++++++ testsuite/tests/typecheck/should_compile/T9708.stderr | 17 +++++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 28 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T9708.hs b/testsuite/tests/typecheck/should_compile/T9708.hs new file mode 100644 index 0000000..fa6deb2 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9708.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE DataKinds, TypeOperators, TypeFamilies #-} +module TcTypeNatSimple where + +import GHC.TypeLits +import Data.Proxy + +type family SomeFun (n :: Nat) + +ti7 :: (x <= y, y <= x) => Proxy (SomeFun x) -> Proxy y -> () +ti7 _ _ = () diff --git a/testsuite/tests/typecheck/should_compile/T9708.stderr b/testsuite/tests/typecheck/should_compile/T9708.stderr new file mode 100644 index 0000000..fca5df7 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9708.stderr @@ -0,0 +1,17 @@ + +T9708.hs:9:8: + Could not deduce (SomeFun x ~ SomeFun y) + from the context (x <= y, y <= x) + bound by the type signature for + ti7 :: (x <= y, y <= x) => Proxy (SomeFun x) -> Proxy y -> () + at T9708.hs:9:8-61 + NB: ?SomeFun? is a type function, and may not be injective + Expected type: Proxy (SomeFun x) -> Proxy y -> () + Actual type: Proxy (SomeFun y) -> Proxy y -> () + In the ambiguity check for: + forall (x :: Nat) (y :: Nat). + (x <= y, y <= x) => + Proxy (SomeFun x) -> Proxy y -> () + To defer the ambiguity check to use sites, enable AllowAmbiguousTypes + In the type signature for ?ti7?: + ti7 :: (x <= y, y <= x) => Proxy (SomeFun x) -> Proxy y -> () diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 8b8155d..a6cb78a 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -421,3 +421,4 @@ test('MutRec', normal, compile, ['']) test('T8856', normal, compile, ['']) test('T9117', normal, compile, ['']) test('T9117_2', expect_broken('9117'), compile, ['']) +test('T9708', normal, compile_fail, ['']) From git at git.haskell.org Tue Nov 4 10:38:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:46 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #9211 (4723a0e) Message-ID: <20141104103846.246793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4723a0e39b5eb7a47457696aceb67f8e230a42e6/ghc >--------------------------------------------------------------- commit 4723a0e39b5eb7a47457696aceb67f8e230a42e6 Author: Simon Peyton Jones Date: Thu Oct 30 11:37:39 2014 +0000 Test Trac #9211 >--------------------------------------------------------------- 4723a0e39b5eb7a47457696aceb67f8e230a42e6 testsuite/tests/indexed-types/should_compile/T9211.hs | 10 ++++++++++ testsuite/tests/indexed-types/should_compile/all.T | 1 + 2 files changed, 11 insertions(+) diff --git a/testsuite/tests/indexed-types/should_compile/T9211.hs b/testsuite/tests/indexed-types/should_compile/T9211.hs new file mode 100644 index 0000000..6ba0af4 --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T9211.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE TypeFamilies #-} + +module T9211 where + +-- foo :: (forall f g. (Functor f) => f a -> f b) -> [a] -> [b] +foo :: (forall f g. (Functor f, g ~ f) => g a -> g b) -> [a] -> [b] +foo tr x = tr x + +t = foo (fmap not) [True] diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index ff45df2..32c42d1 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -247,3 +247,4 @@ test('T9085', normal, compile, ['']) test('T9316', normal, compile, ['']) test('red-black-delete', normal, compile, ['']) test('Sock', normal, compile, ['']) +test('T9211', normal, compile, ['']) From git at git.haskell.org Tue Nov 4 10:38:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:49 +0000 (UTC) Subject: [commit: ghc] master: Improve error message for a handwritten Typeable instance (6d1ac96) Message-ID: <20141104103849.30A8E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6d1ac963d87b83f1cac85c18729cfbc29c390383/ghc >--------------------------------------------------------------- commit 6d1ac963d87b83f1cac85c18729cfbc29c390383 Author: Simon Peyton Jones Date: Thu Oct 30 16:33:34 2014 +0000 Improve error message for a handwritten Typeable instance >--------------------------------------------------------------- 6d1ac963d87b83f1cac85c18729cfbc29c390383 compiler/typecheck/TcInstDcls.lhs | 42 ++++++++++++---------- testsuite/tests/deriving/should_fail/T9687.hs | 4 +++ testsuite/tests/deriving/should_fail/T9687.stderr | 5 +++ .../should_fail/T9730.stderr} | 0 testsuite/tests/deriving/should_fail/all.T | 1 + 5 files changed, 34 insertions(+), 18 deletions(-) diff --git a/compiler/typecheck/TcInstDcls.lhs b/compiler/typecheck/TcInstDcls.lhs index 10bc466..d22938e 100644 --- a/compiler/typecheck/TcInstDcls.lhs +++ b/compiler/typecheck/TcInstDcls.lhs @@ -61,7 +61,7 @@ import BooleanFormula ( isUnsatisfied, pprBooleanFormulaNice ) import Control.Monad import Maybes ( isNothing, isJust, whenIsJust ) -import Data.List ( mapAccumL ) +import Data.List ( mapAccumL, partition ) \end{code} Typechecking instance declarations is done in two passes. The first @@ -378,7 +378,8 @@ tcInstDecls1 tycl_decls inst_decls deriv_decls local_infos' = concat local_infos_s -- Handwritten instances of the poly-kinded Typeable class are -- forbidden, so we handle those separately - (typeable_instances, local_infos) = splitTypeable env local_infos' + (typeable_instances, local_infos) + = partition (bad_typeable_instance env) local_infos' ; addClsInsts local_infos $ addFamInsts fam_insts $ @@ -400,7 +401,7 @@ tcInstDecls1 tycl_decls inst_decls deriv_decls else tcDeriving tycl_decls inst_decls deriv_decls -- Fail if there are any handwritten instance of poly-kinded Typeable - ; mapM_ (failWithTc . instMsg) typeable_instances + ; mapM_ typeable_err typeable_instances -- Check that if the module is compiled with -XSafe, there are no -- hand written instances of old Typeable as then unsafe casts could be @@ -422,18 +423,14 @@ tcInstDecls1 tycl_decls inst_decls deriv_decls }} where -- Separate the Typeable instances from the rest - splitTypeable _ [] = ([],[]) - splitTypeable env (i:is) = - let (typeableInsts, otherInsts) = splitTypeable env is - in if -- We will filter out instances of Typeable - (typeableClassName == is_cls_nm (iSpec i)) - -- but not those that come from Data.Typeable.Internal - && tcg_mod env /= tYPEABLE_INTERNAL - -- nor those from an .hs-boot or .hsig file - -- (deriving can't be used there) - && not (isHsBootOrSig (tcg_src env)) - then (i:typeableInsts, otherInsts) - else (typeableInsts, i:otherInsts) + bad_typeable_instance env i + = -- Class name is Typeable + typeableClassName == is_cls_nm (iSpec i) + -- but not those that come from Data.Typeable.Internal + && tcg_mod env /= tYPEABLE_INTERNAL + -- nor those from an .hs-boot or .hsig file + -- (deriving can't be used there) + && not (isHsBootOrSig (tcg_src env)) overlapCheck ty = overlapMode (is_flag $ iSpec ty) `elem` [Overlappable, Overlapping, Overlaps] @@ -443,9 +440,18 @@ tcInstDecls1 tycl_decls inst_decls deriv_decls ptext (sLit "Replace the following instance:")) 2 (pprInstanceHdr (iSpec i)) - instMsg i = hang (ptext (sLit $ "Typeable instances can only be derived; replace " - ++ "the following instance:")) - 2 (pprInstance (iSpec i)) + typeable_err i + = setSrcSpan (getSrcSpan ispec) $ + addErrTc $ hang (ptext (sLit "Typeable instances can only be derived")) + 2 (vcat [ ptext (sLit "Try") <+> quotes (ptext (sLit "deriving instance Typeable") + <+> pp_tc) + , ptext (sLit "(requires StandaloneDeriving)") ]) + where + ispec = iSpec i + pp_tc | [_kind, ty] <- is_tys ispec + , Just (tc,_) <- tcSplitTyConApp_maybe ty + = ppr tc + | otherwise = ptext (sLit "") addClsInsts :: [InstInfo Name] -> TcM a -> TcM a addClsInsts infos thing_inside diff --git a/testsuite/tests/deriving/should_fail/T9687.hs b/testsuite/tests/deriving/should_fail/T9687.hs new file mode 100644 index 0000000..818878b --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T9687.hs @@ -0,0 +1,4 @@ +module T9687 where +import Data.Typeable + +instance Typeable (a,b,c,d,e,f,g,h) diff --git a/testsuite/tests/deriving/should_fail/T9687.stderr b/testsuite/tests/deriving/should_fail/T9687.stderr new file mode 100644 index 0000000..10619a6 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T9687.stderr @@ -0,0 +1,5 @@ + +T9687.hs:4:10: + Typeable instances can only be derived + Try ?deriving instance Typeable (,,,,,,,)? + (requires StandaloneDeriving) diff --git a/testsuite/tests/deSugar/should_run/T5472.stdout b/testsuite/tests/deriving/should_fail/T9730.stderr similarity index 100% copy from testsuite/tests/deSugar/should_run/T5472.stdout copy to testsuite/tests/deriving/should_fail/T9730.stderr diff --git a/testsuite/tests/deriving/should_fail/all.T b/testsuite/tests/deriving/should_fail/all.T index 7700d62..54a6f95 100644 --- a/testsuite/tests/deriving/should_fail/all.T +++ b/testsuite/tests/deriving/should_fail/all.T @@ -51,4 +51,5 @@ test('T6147', normal, compile_fail, ['']) test('T8851', normal, compile_fail, ['']) test('T9071', normal, multimod_compile_fail, ['T9071','']) test('T9071_2', normal, compile_fail, ['']) +test('T9687', normal, compile_fail, ['']) From git at git.haskell.org Tue Nov 4 10:38:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:51 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #9747 (dbbffb7) Message-ID: <20141104103851.F2C303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dbbffb7bd59c2c0d098afacad7c88c53588f0faa/ghc >--------------------------------------------------------------- commit dbbffb7bd59c2c0d098afacad7c88c53588f0faa Author: Simon Peyton Jones Date: Fri Oct 31 08:53:52 2014 +0000 Test Trac #9747 >--------------------------------------------------------------- dbbffb7bd59c2c0d098afacad7c88c53588f0faa .../tests/indexed-types/should_compile/T9747.hs | 39 ++++++++++++++++++++++ testsuite/tests/indexed-types/should_compile/all.T | 1 + 2 files changed, 40 insertions(+) diff --git a/testsuite/tests/indexed-types/should_compile/T9747.hs b/testsuite/tests/indexed-types/should_compile/T9747.hs new file mode 100644 index 0000000..05b4397 --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T9747.hs @@ -0,0 +1,39 @@ +{-# LANGUAGE ConstraintKinds, DataKinds, GADTs, TypeFamilies, TypeOperators #-} +module T9747 where +import Data.List (intercalate) +import Data.Proxy +import GHC.Prim (Constraint) + +data HList :: [*] -> * where + Nil :: HList '[] + Cons :: a -> HList as -> HList (a ': as) + +type family HListAll (c :: * -> Constraint) (ts :: [*]) :: Constraint where + HListAll c '[] = () + HListAll c (t ': ts) = (c t, HListAll c ts) + +showHList :: HListAll Show ts => HList ts -> String +showHList = ("[" ++ ) . (++"]") . intercalate ", " . go + where + go :: HListAll Show ts => HList ts -> [String] + go Nil = [] + go (Cons x xs) = show x : go xs + +-- Things work okay up to this point +test :: String +test = showHList (Cons (2::Int) + (Cons (3.1 :: Float) + (Cons 'c' Nil))) + +type family ConFun (t :: *) :: * -> Constraint +data Tag +type instance ConFun Tag = Group + +class (Show a, Eq a, Ord a) => Group a + +-- This is notionally similar to showHList +bar :: HListAll (ConFun l) ts => Proxy l -> HList ts -> () +bar _ _ = () + +baz :: (ConFun l a, ConFun l b) => Proxy l -> HList [a,b] -> () +baz = bar diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index 32c42d1..445804a 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -248,3 +248,4 @@ test('T9316', normal, compile, ['']) test('red-black-delete', normal, compile, ['']) test('Sock', normal, compile, ['']) test('T9211', normal, compile, ['']) +test('T9747', normal, compile, ['']) From git at git.haskell.org Tue Nov 4 10:38:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:55 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #9739 (c639560) Message-ID: <20141104103855.244963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c639560d8ad969415033b19201d9626b1a0638bf/ghc >--------------------------------------------------------------- commit c639560d8ad969415033b19201d9626b1a0638bf Author: Simon Peyton Jones Date: Fri Oct 31 11:11:50 2014 +0000 Test Trac #9739 >--------------------------------------------------------------- c639560d8ad969415033b19201d9626b1a0638bf testsuite/tests/typecheck/should_fail/T9739.hs | 6 ++++++ testsuite/tests/typecheck/should_fail/T9739.stderr | 10 ++++++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 17 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T9739.hs b/testsuite/tests/typecheck/should_fail/T9739.hs new file mode 100644 index 0000000..4b7869d --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9739.hs @@ -0,0 +1,6 @@ +module T9739 where + +class Class2 a => Class1 a where + class3 :: (Class2 a) => b + +class (Class1 a) => Class2 a where diff --git a/testsuite/tests/typecheck/should_fail/T9739.stderr b/testsuite/tests/typecheck/should_fail/T9739.stderr new file mode 100644 index 0000000..95fcf6a --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9739.stderr @@ -0,0 +1,10 @@ + +T9739.hs:3:1: + Cycle in class declaration (via superclasses): + Class1 -> Class2 -> Class1 + In the class declaration for ?Class1? + +T9739.hs:6:1: + Cycle in class declaration (via superclasses): + Class2 -> Class1 -> Class2 + In the class declaration for ?Class2? diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 2738e81..e9dd289 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -341,3 +341,4 @@ test('T9323', normal, compile_fail, ['']) test('T9415', normal, compile_fail, ['']) test('T9612', normal, compile_fail, ['']) test('T9634', normal, compile_fail, ['']) +test('T9739', normal, compile_fail, ['']) From git at git.haskell.org Tue Nov 4 10:38:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:38:57 +0000 (UTC) Subject: [commit: ghc] master: Add comments explaining ProbOneShot (abfbdd1) Message-ID: <20141104103857.B53A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/abfbdd1c639c0c60bcc20bde81d61a9ad3e786fa/ghc >--------------------------------------------------------------- commit abfbdd1c639c0c60bcc20bde81d61a9ad3e786fa Author: Simon Peyton Jones Date: Fri Oct 31 11:13:37 2014 +0000 Add comments explaining ProbOneShot >--------------------------------------------------------------- abfbdd1c639c0c60bcc20bde81d61a9ad3e786fa compiler/basicTypes/BasicTypes.lhs | 8 ++- compiler/basicTypes/Demand.lhs | 110 ++++++++++++++++++++++++------------- compiler/simplCore/OccurAnal.lhs | 0 compiler/simplCore/SetLevels.lhs | 1 + 4 files changed, 77 insertions(+), 42 deletions(-) diff --git a/compiler/basicTypes/BasicTypes.lhs b/compiler/basicTypes/BasicTypes.lhs index 2f86db7..4fbfb60 100644 --- a/compiler/basicTypes/BasicTypes.lhs +++ b/compiler/basicTypes/BasicTypes.lhs @@ -155,9 +155,11 @@ type Alignment = Int -- align to next N-byte boundary (N must be a power of 2). -- This information may be useful in optimisation, as computations may -- safely be floated inside such a lambda without risk of duplicating -- work. -data OneShotInfo = NoOneShotInfo -- ^ No information - | ProbOneShot -- ^ The lambda is probably applied at most once - | OneShotLam -- ^ The lambda is applied at most once. +data OneShotInfo + = NoOneShotInfo -- ^ No information + | ProbOneShot -- ^ The lambda is probably applied at most once + -- See Note [Computing one-shot info, and ProbOneShot] in OccurAnl + | OneShotLam -- ^ The lambda is applied at most once. -- | It is always safe to assume that an 'Id' has no lambda-bound variable information noOneShotInfo :: OneShotInfo diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 2aa25ce..f553fc2 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1493,6 +1493,11 @@ newtype StrictSig = StrictSig DmdType instance Outputable StrictSig where ppr (StrictSig ty) = ppr ty +-- Used for printing top-level strictness pragmas in interface files +pprIfaceStrictSig :: StrictSig -> SDoc +pprIfaceStrictSig (StrictSig (DmdType _ dmds res)) + = hcat (map ppr dmds) <> ppr res + mkStrictSig :: DmdType -> StrictSig mkStrictSig dmd_ty = StrictSig dmd_ty @@ -1520,29 +1525,8 @@ botSig = StrictSig botDmdType cprProdSig :: Arity -> StrictSig cprProdSig arity = StrictSig (cprProdDmdType arity) -argsOneShots :: StrictSig -> Arity -> [[OneShotInfo]] -argsOneShots (StrictSig (DmdType _ arg_ds _)) n_val_args - = go arg_ds - where - good_one_shot - | arg_ds `lengthExceeds` n_val_args = ProbOneShot - | otherwise = OneShotLam - - go [] = [] - go (arg_d : arg_ds) = argOneShots good_one_shot arg_d `cons` go arg_ds - - cons [] [] = [] - cons a as = a:as - -argOneShots :: OneShotInfo -> JointDmd -> [OneShotInfo] -argOneShots one_shot_info (JD { absd = usg }) - = case usg of - Use _ arg_usg -> go arg_usg - _ -> [] - where - go (UCall One u) = one_shot_info : go u - go (UCall Many u) = NoOneShotInfo : go u - go _ = [] +seqStrictSig :: StrictSig -> () +seqStrictSig (StrictSig ty) = seqDmdType ty dmdTransformSig :: StrictSig -> CleanDemand -> DmdType -- (dmdTransformSig fun_sig dmd) considers a call to a function whose @@ -1617,31 +1601,79 @@ you might do strictness analysis, but there is no inlining for the class op. This is weird, so I'm not worried about whether this optimises brilliantly; but it should not fall over. -Note [Non-full application] -~~~~~~~~~~~~~~~~~~~~~~~~~~~ -If a function having bottom as its demand result is applied to a less -number of arguments than its syntactic arity, we cannot say for sure -that it is going to diverge. This is the reason why we use the -function appIsBottom, which, given a strictness signature and a number -of arguments, says conservatively if the function is going to diverge -or not. +\begin{code} +argsOneShots :: StrictSig -> Arity -> [[OneShotInfo]] +-- See Note [Computing one-shot info, and ProbOneShot] +argsOneShots (StrictSig (DmdType _ arg_ds _)) n_val_args + = go arg_ds + where + unsaturated_call = arg_ds `lengthExceeds` n_val_args + good_one_shot + | unsaturated_call = ProbOneShot + | otherwise = OneShotLam + + go [] = [] + go (arg_d : arg_ds) = argOneShots good_one_shot arg_d `cons` go arg_ds + + -- Avoid list tail like [ [], [], [] ] + cons [] [] = [] + cons a as = a:as + +argOneShots :: OneShotInfo -> JointDmd -> [OneShotInfo] +argOneShots one_shot_info (JD { absd = usg }) + = case usg of + Use _ arg_usg -> go arg_usg + _ -> [] + where + go (UCall One u) = one_shot_info : go u + go (UCall Many u) = NoOneShotInfo : go u + go _ = [] +\end{code} + +Note [Computing one-shot info, and ProbOneShot] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider a call + f (\pqr. e1) (\xyz. e2) e3 +where f has usage signature + C1(C(C1(U))) C1(U) U +Then argsOneShots returns a [[OneShotInfo]] of + [[OneShot,NoOneShotInfo,OneShot], [OneShot]] +The occurrence analyser propagates this one-shot infor to the +binders \pqr and \xyz; see Note [Use one-shot information] in OccurAnal. + +But suppose f was not saturated, so the call looks like + f (\pqr. e1) (\xyz. e2) +The in principle this partial application might be shared, and +the (\prq.e1) abstraction might be called more than once. So +we can't mark them OneShot. But instead we return + [[ProbOneShot,NoOneShotInfo,ProbOneShot], [ProbOneShot]] +The occurrence analyser propagates this to the \pqr and \xyz +binders. + +How is it used? Well, it's quite likely that the partial application +of f is not shared, so the float-out pass (in SetLevels.lvlLamBndrs) +does not float MFEs out of a ProbOneShot lambda. That currently is +the only way that ProbOneShot is used. + \begin{code} -- appIsBottom returns true if an application to n args would diverge +-- See Note [Unsaturated applications] appIsBottom :: StrictSig -> Int -> Bool appIsBottom (StrictSig (DmdType _ ds res)) n | isBotRes res = not $ lengthExceeds ds n appIsBottom _ _ = False - -seqStrictSig :: StrictSig -> () -seqStrictSig (StrictSig ty) = seqDmdType ty - --- Used for printing top-level strictness pragmas in interface files -pprIfaceStrictSig :: StrictSig -> SDoc -pprIfaceStrictSig (StrictSig (DmdType _ dmds res)) - = hcat (map ppr dmds) <> ppr res \end{code} +Note [Unsaturated applications] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +If a function having bottom as its demand result is applied to a less +number of arguments than its syntactic arity, we cannot say for sure +that it is going to diverge. This is the reason why we use the +function appIsBottom, which, given a strictness signature and a number +of arguments, says conservatively if the function is going to diverge +or not. + Zap absence or one-shot information, under control of flags \begin{code} diff --git a/compiler/simplCore/SetLevels.lhs b/compiler/simplCore/SetLevels.lhs index e5cd42e..b8726d9 100644 --- a/compiler/simplCore/SetLevels.lhs +++ b/compiler/simplCore/SetLevels.lhs @@ -827,6 +827,7 @@ lvlLamBndrs env lvl bndrs is_major bndr = isId bndr && not (isProbablyOneShotLambda bndr) -- The "probably" part says "don't float things out of a -- probable one-shot lambda" + -- See Note [Computing one-shot info] in Demand.lhs lvlBndrs :: LevelEnv -> Level -> [CoreBndr] -> (LevelEnv, [LevelledBndr]) From git at git.haskell.org Tue Nov 4 10:39:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:39:00 +0000 (UTC) Subject: [commit: ghc] master: Fix the superclass-cycle detection code (Trac #9739) (7c79633) Message-ID: <20141104103900.6CE0B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7c79633688238086ad60e1d23e0a424bb4eb325f/ghc >--------------------------------------------------------------- commit 7c79633688238086ad60e1d23e0a424bb4eb325f Author: Simon Peyton Jones Date: Fri Oct 31 12:31:59 2014 +0000 Fix the superclass-cycle detection code (Trac #9739) We were falling into an infinite loop when doing the ambiguity check on a class method, even though we had previously detected a superclass cycle. There was code to deal with this, but it wasn't right. >--------------------------------------------------------------- 7c79633688238086ad60e1d23e0a424bb4eb325f compiler/typecheck/TcRnMonad.lhs | 3 ++ compiler/typecheck/TcTyClsDecls.lhs | 39 +++++++++++----------- testsuite/tests/typecheck/should_fail/T9739.hs | 9 +++-- testsuite/tests/typecheck/should_fail/T9739.stderr | 10 +++--- 4 files changed, 34 insertions(+), 27 deletions(-) diff --git a/compiler/typecheck/TcRnMonad.lhs b/compiler/typecheck/TcRnMonad.lhs index dce4b49..cd41499 100644 --- a/compiler/typecheck/TcRnMonad.lhs +++ b/compiler/typecheck/TcRnMonad.lhs @@ -825,6 +825,9 @@ checkNoErrs main Just val -> return val } +whenNoErrs :: TcM () -> TcM () +whenNoErrs thing = ifErrsM (return ()) thing + ifErrsM :: TcRn r -> TcRn r -> TcRn r -- ifErrsM bale_out normal -- does 'bale_out' if there are errors in errors collection diff --git a/compiler/typecheck/TcTyClsDecls.lhs b/compiler/typecheck/TcTyClsDecls.lhs index fd3c8f8..e08f269 100644 --- a/compiler/typecheck/TcTyClsDecls.lhs +++ b/compiler/typecheck/TcTyClsDecls.lhs @@ -1357,25 +1357,9 @@ since GADTs are not kind indexed. Validity checking is done once the mutually-recursive knot has been tied, so we can look at things freely. -Note [Abort when superclass cycle is detected] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We must avoid doing the ambiguity check when there are already errors accumulated. -This is because one of the errors may be a superclass cycle, and superclass cycles -cause canonicalization to loop. Here is a representative example: - - class D a => C a where - meth :: D a => () - class C a => D a - -This fixes Trac #9415. - \begin{code} checkClassCycleErrs :: Class -> TcM () -checkClassCycleErrs cls - = unless (null cls_cycles) $ - do { mapM_ recClsErr cls_cycles - ; failM } -- See Note [Abort when superclass cycle is detected] - where cls_cycles = calcClassCycles cls +checkClassCycleErrs cls = mapM_ recClsErr (calcClassCycles cls) checkValidTyCl :: TyThing -> TcM () checkValidTyCl thing @@ -1628,8 +1612,11 @@ checkValidClass cls -- If there are superclass cycles, checkClassCycleErrs bails. ; checkClassCycleErrs cls - -- Check the class operations - ; mapM_ (check_op constrained_class_methods) op_stuff + -- Check the class operations. + -- But only if there have been no earlier errors + -- See Note [Abort when superclass cycle is detected] + ; whenNoErrs $ + mapM_ (check_op constrained_class_methods) op_stuff -- Check the associated type defaults are well-formed and instantiated ; mapM_ check_at_defs at_stuff } @@ -1695,6 +1682,20 @@ checkFamFlag tc_name 2 (ptext (sLit "Use TypeFamilies to allow indexed type families")) \end{code} +Note [Abort when superclass cycle is detected] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +We must avoid doing the ambiguity check for the methods (in +checkValidClass.check_op) when there are already errors accumulated. +This is because one of the errors may be a superclass cycle, and +superclass cycles cause canonicalization to loop. Here is a +representative example: + + class D a => C a where + meth :: D a => () + class C a => D a + +This fixes Trac #9415, #9739 + %************************************************************************ %* * Checking role validity diff --git a/testsuite/tests/typecheck/should_fail/T9739.hs b/testsuite/tests/typecheck/should_fail/T9739.hs index 4b7869d..18df797 100644 --- a/testsuite/tests/typecheck/should_fail/T9739.hs +++ b/testsuite/tests/typecheck/should_fail/T9739.hs @@ -1,6 +1,9 @@ +{-# LANGUAGE MultiParamTypeClasses #-} module T9739 where -class Class2 a => Class1 a where - class3 :: (Class2 a) => b +class Class3 a => Class1 a where -class (Class1 a) => Class2 a where +class Class2 t a where + class2 :: (Class3 t) => a -> m + +class (Class1 t, Class2 t t) => Class3 t where diff --git a/testsuite/tests/typecheck/should_fail/T9739.stderr b/testsuite/tests/typecheck/should_fail/T9739.stderr index 95fcf6a..34e2f11 100644 --- a/testsuite/tests/typecheck/should_fail/T9739.stderr +++ b/testsuite/tests/typecheck/should_fail/T9739.stderr @@ -1,10 +1,10 @@ -T9739.hs:3:1: +T9739.hs:4:1: Cycle in class declaration (via superclasses): - Class1 -> Class2 -> Class1 + Class1 -> Class3 -> Class1 In the class declaration for ?Class1? -T9739.hs:6:1: +T9739.hs:9:1: Cycle in class declaration (via superclasses): - Class2 -> Class1 -> Class2 - In the class declaration for ?Class2? + Class3 -> Class1 -> Class3 + In the class declaration for ?Class3? From git at git.haskell.org Tue Nov 4 10:39:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:39:03 +0000 (UTC) Subject: [commit: ghc] master: Comments only (66658ee) Message-ID: <20141104103903.01B273A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/66658eedf0aa51de37ff6d2d009a2f37208985ca/ghc >--------------------------------------------------------------- commit 66658eedf0aa51de37ff6d2d009a2f37208985ca Author: Simon Peyton Jones Date: Fri Oct 31 12:32:36 2014 +0000 Comments only >--------------------------------------------------------------- 66658eedf0aa51de37ff6d2d009a2f37208985ca compiler/stranal/WwLib.lhs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index 11f97ea..1f1fbdf 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -528,7 +528,8 @@ can still be specialised by the type-class specialiser, something like BUT if f is strict in the Ord dictionary, we might unpack it, to get fw :: (a->a->Bool) -> [a] -> Int# -> a -and the type-class specialiser can't specialise that. +and the type-class specialiser can't specialise that. An example is +Trac #6056. Moreover, dictinoaries can have a lot of fields, so unpacking them can increase closure sizes. From git at git.haskell.org Tue Nov 4 10:39:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:39:06 +0000 (UTC) Subject: [commit: ghc] master: Testsuite error message changes (5479ae0) Message-ID: <20141104103906.085253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5479ae0a0ff6d5df2da4f6208ce747f669c6d492/ghc >--------------------------------------------------------------- commit 5479ae0a0ff6d5df2da4f6208ce747f669c6d492 Author: Simon Peyton Jones Date: Thu Oct 30 11:41:17 2014 +0000 Testsuite error message changes >--------------------------------------------------------------- 5479ae0a0ff6d5df2da4f6208ce747f669c6d492 .../tests/deSugar/should_compile/T2431.stderr | 9 +- testsuite/tests/deriving/should_fail/T9071.stderr | 2 +- .../tests/deriving/should_fail/T9071_2.stderr | 2 +- testsuite/tests/gadt/T3169.stderr | 4 +- testsuite/tests/gadt/T7293.stderr | 2 +- testsuite/tests/gadt/T7294.stderr | 2 +- testsuite/tests/gadt/gadt21.stderr | 7 +- .../tests/ghc-api/apirecomp001/apirecomp001.stderr | 12 +- .../tests/ghci.debugger/scripts/break026.stdout | 40 +-- .../should_compile/IndTypesPerfMerge.hs | 8 + .../should_compile/PushInAsGivens.stderr} | 0 .../should_compile/PushedInAsGivens.hs | 9 +- .../should_compile/PushedInAsGivens.stderr | 27 ++ .../tests/indexed-types/should_compile/Simple13.hs | 30 ++ .../tests/indexed-types/should_compile/Simple8.hs | 2 +- .../indexed-types/should_compile/T3017.stderr | 2 +- .../indexed-types/should_compile/T3208b.stderr | 13 +- .../tests/indexed-types/should_compile/T3826.hs | 56 +++- .../tests/indexed-types/should_compile/T4494.hs | 20 ++ .../tests/indexed-types/should_compile/T7804.hs | 12 + testsuite/tests/indexed-types/should_compile/all.T | 2 +- .../indexed-types/should_fail/ExtraTcsUntch.hs | 27 +- .../indexed-types/should_fail/ExtraTcsUntch.stderr | 22 +- .../tests/indexed-types/should_fail/GADTwrong1.hs | 30 +- .../indexed-types/should_fail/GADTwrong1.stderr | 21 +- .../indexed-types/should_fail/NoMatchErr.stderr | 5 +- .../indexed-types/should_fail/Overlap9.stderr | 5 +- .../tests/indexed-types/should_fail/T1897b.stderr | 8 +- .../tests/indexed-types/should_fail/T1900.stderr | 5 +- testsuite/tests/indexed-types/should_fail/T2544.hs | 13 + .../tests/indexed-types/should_fail/T2544.stderr | 8 +- .../tests/indexed-types/should_fail/T2627b.hs | 10 +- testsuite/tests/indexed-types/should_fail/T2664.hs | 17 ++ .../tests/indexed-types/should_fail/T2664.stderr | 22 +- .../tests/indexed-types/should_fail/T2693.stderr | 12 +- .../tests/indexed-types/should_fail/T4093a.hs | 31 +++ .../tests/indexed-types/should_fail/T4093a.stderr | 17 +- .../tests/indexed-types/should_fail/T4174.stderr | 27 +- .../tests/indexed-types/should_fail/T4179.stderr | 11 +- .../tests/indexed-types/should_fail/T4272.stderr | 6 +- .../tests/indexed-types/should_fail/T5439.stderr | 3 +- .../tests/indexed-types/should_fail/T5934.stderr | 3 +- .../tests/indexed-types/should_fail/T7010.stderr | 2 +- .../tests/indexed-types/should_fail/T7729.stderr | 8 +- .../tests/indexed-types/should_fail/T7729a.hs | 41 +++ .../tests/indexed-types/should_fail/T7729a.stderr | 8 +- testsuite/tests/indexed-types/should_fail/T7786.hs | 2 +- .../tests/indexed-types/should_fail/T8129.stdout | 4 +- testsuite/tests/indexed-types/should_fail/T8227.hs | 23 +- .../tests/indexed-types/should_fail/T8227.stderr | 20 +- .../tests/indexed-types/should_fail/T8518.stderr | 26 +- .../tests/indexed-types/should_fail/T9036.stderr | 4 +- .../tests/numeric/should_compile/T7116.stdout | 28 +- testsuite/tests/parser/should_compile/T2245.stderr | 10 +- testsuite/tests/perf/compiler/T5837.hs | 14 + testsuite/tests/perf/compiler/T5837.stderr | 310 ++++++++++----------- testsuite/tests/polykinds/T7438.stderr | 0 testsuite/tests/polykinds/T8132.stderr | 7 +- testsuite/tests/rebindable/rebindable6.stderr | 12 +- .../tests/roles/should_compile/Roles13.stderr | 14 +- testsuite/tests/roles/should_compile/T8958.stderr | 15 +- .../tests/simplCore/should_compile/EvalTest.stdout | 2 +- .../tests/simplCore/should_compile/T3717.stderr | 8 +- .../tests/simplCore/should_compile/T3772.stdout | 13 +- .../tests/simplCore/should_compile/T4201.stdout | 2 +- .../tests/simplCore/should_compile/T4306.stdout | 2 +- .../tests/simplCore/should_compile/T4908.stderr | 41 +-- .../tests/simplCore/should_compile/T4918.stdout | 4 +- .../tests/simplCore/should_compile/T4930.stderr | 28 +- .../tests/simplCore/should_compile/T5366.stdout | 2 +- .../tests/simplCore/should_compile/T6056.stderr | 3 +- .../tests/simplCore/should_compile/T7360.stderr | 20 +- .../tests/simplCore/should_compile/T7865.stdout | 8 +- .../tests/simplCore/should_compile/T8832.stdout | 20 +- .../simplCore/should_compile/T8832.stdout-ws-32 | 16 +- .../tests/simplCore/should_compile/T9400.stderr | 30 +- .../tests/simplCore/should_compile/rule2.stderr | 2 +- .../simplCore/should_compile/spec-inline.stderr | 87 +++--- testsuite/tests/th/T3319.stderr | 0 testsuite/tests/th/T3600.stderr | 0 testsuite/tests/th/T5217.stderr | 18 +- testsuite/tests/th/all.T | 6 +- .../tests/typecheck/should_compile/FD1.stderr | 6 +- .../tests/typecheck/should_compile/FD2.stderr | 13 +- testsuite/tests/typecheck/should_compile/T3346.hs | 4 +- testsuite/tests/typecheck/should_compile/T8474.hs | 2 + .../typecheck/should_compile/TcTypeNatSimple.hs | 11 +- testsuite/tests/typecheck/should_compile/tc231.hs | 2 +- .../tests/typecheck/should_compile/tc231.stderr | 2 +- .../tests/typecheck/should_fail/ContextStack2.hs | 44 +++ .../typecheck/should_fail/ContextStack2.stderr | 6 +- .../typecheck/should_fail/FDsFromGivens.stderr | 6 +- .../typecheck/should_fail/FrozenErrorTests.stderr | 4 +- testsuite/tests/typecheck/should_fail/T1899.stderr | 10 +- testsuite/tests/typecheck/should_fail/T2688.stderr | 5 +- testsuite/tests/typecheck/should_fail/T5236.stderr | 4 +- testsuite/tests/typecheck/should_fail/T5300.stderr | 4 +- testsuite/tests/typecheck/should_fail/T5684.stderr | 88 +++++- testsuite/tests/typecheck/should_fail/T5853.stderr | 2 +- .../tests/typecheck/should_fail/T7748a.stderr | 11 +- testsuite/tests/typecheck/should_fail/T8142.stderr | 28 +- testsuite/tests/typecheck/should_fail/T8450.hs | 3 + testsuite/tests/typecheck/should_fail/T8450.stderr | 8 +- testsuite/tests/typecheck/should_fail/T8883.stderr | 2 +- testsuite/tests/typecheck/should_fail/T9305.stderr | 2 +- testsuite/tests/typecheck/should_fail/mc21.stderr | 4 +- testsuite/tests/typecheck/should_fail/mc22.stderr | 17 +- testsuite/tests/typecheck/should_fail/mc25.stderr | 14 +- .../tests/typecheck/should_fail/tcfail019.stderr | 2 +- .../tests/typecheck/should_fail/tcfail067.stderr | 4 +- testsuite/tests/typecheck/should_fail/tcfail068.hs | 2 +- .../tests/typecheck/should_fail/tcfail068.stderr | 35 +-- .../tests/typecheck/should_fail/tcfail072.stderr | 4 +- .../tests/typecheck/should_fail/tcfail131.stderr | 5 +- .../tests/typecheck/should_fail/tcfail143.stderr | 4 +- .../tests/typecheck/should_fail/tcfail171.stderr | 4 +- .../tests/typecheck/should_fail/tcfail186.stderr | 0 .../tests/typecheck/should_fail/tcfail201.stderr | 9 +- .../tests/typecheck/should_fail/tcfail204.stderr | 7 +- testsuite/tests/typecheck/should_run/T5751.hs | 0 testsuite/tests/typecheck/should_run/tcrun036.hs | 12 +- 121 files changed, 1054 insertions(+), 760 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5479ae0a0ff6d5df2da4f6208ce747f669c6d492 From git at git.haskell.org Tue Nov 4 10:39:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:39:08 +0000 (UTC) Subject: [commit: ghc] master: Add flattening-notes (652a5ef) Message-ID: <20141104103908.D82E13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/652a5efe774adf2d1d502df2f1670f500fddd038/ghc >--------------------------------------------------------------- commit 652a5efe774adf2d1d502df2f1670f500fddd038 Author: Simon Peyton Jones Date: Thu Oct 30 12:11:27 2014 +0000 Add flattening-notes >--------------------------------------------------------------- 652a5efe774adf2d1d502df2f1670f500fddd038 compiler/typecheck/Flattening-notes | 49 +++++++++++++++++++++++++++++++++++++ 1 file changed, 49 insertions(+) diff --git a/compiler/typecheck/Flattening-notes b/compiler/typecheck/Flattening-notes new file mode 100644 index 0000000..5f6fd14 --- /dev/null +++ b/compiler/typecheck/Flattening-notes @@ -0,0 +1,49 @@ +ToDo: + +* get rid of getEvTerm? + +* Float only CTyEqCans. kind-incompatible things should be CNonCanonical, + so they won't float and generate a duplicate kind-unify message + + Then we can stop disabling floating when there are insolubles, + and that will improve mc21 etc + +* Note [Do not add duplicate derived isols] + This mostly doesn't apply now, except for the fundeps + +* inert_funeqs, inert_eqs: keep only the CtEvidence. + They are all CFunEqCans, CTyEqCans + +* remove/rewrite TcMType Note [Unflattening while zonking] + +* Consider individual data tpyes for CFunEqCan etc + +Remaining errors +============================ +Unexpected failures: + generics GenDerivOutput1_1 [stderr mismatch] (normal) + +ghcirun002: internal error: ASSERTION FAILED: file rts/Interpreter.c, line 773 + ghci/should_run ghcirun002 [bad exit code] (ghci) + +-package dependencies: array-0.5.0.1 at array_GX4NwjS8xZkC2ZPtjgwhnz ++package dependencies: array-0.5.0.1 base-4.8.0.0 + safeHaskell/check/pkg01 safePkg01 [bad stdout] (normal) + + +Wierd looking pattern synonym thing + ghci/scripts T8776 [bad stdout] (ghci) + patsyn/should_fail mono [stderr mismatch] (normal) + +Derived equalities fmv1 ~ Maybe a, fmv2 ~ Maybe b + indexed-types/should_fail T4093a [stderr mismatch] (normal) + +Not sure + indexed-types/should_fail ExtraTcsUntch [stderr mismatch] (normal) + +Order of finding iprovements + typecheck/should_compile TcTypeNatSimple [exit code non-0] (normal) + + + +----------------- From git at git.haskell.org Tue Nov 4 10:39:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:39:11 +0000 (UTC) Subject: [commit: ghc] master: Make this test a bit simpler (f02c915) Message-ID: <20141104103911.77F1C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f02c915c1583e40d614dfd97047d5117a9b8a9a5/ghc >--------------------------------------------------------------- commit f02c915c1583e40d614dfd97047d5117a9b8a9a5 Author: Simon Peyton Jones Date: Fri Oct 31 12:28:42 2014 +0000 Make this test a bit simpler There were two unrelated functions, and the `-ddump-rule-firings` output was coming in a non-deterministic order as a result. So now there is just one function. >--------------------------------------------------------------- f02c915c1583e40d614dfd97047d5117a9b8a9a5 testsuite/tests/simplCore/should_compile/T6056.hs | 6 ++---- testsuite/tests/simplCore/should_compile/T6056.stderr | 7 ------- 2 files changed, 2 insertions(+), 11 deletions(-) diff --git a/testsuite/tests/simplCore/should_compile/T6056.hs b/testsuite/tests/simplCore/should_compile/T6056.hs index e24631d..d2d8349 100644 --- a/testsuite/tests/simplCore/should_compile/T6056.hs +++ b/testsuite/tests/simplCore/should_compile/T6056.hs @@ -1,8 +1,6 @@ module T6056 where import T6056a -foo1 :: Int -> (Maybe Int, [Int]) -foo1 x = smallerAndRest x [x] +foo :: Int -> (Maybe Int, [Int]) +foo x = smallerAndRest x [x] -foo2 :: Integer -> (Maybe Integer, [Integer]) -foo2 x = smallerAndRest x [x] diff --git a/testsuite/tests/simplCore/should_compile/T6056.stderr b/testsuite/tests/simplCore/should_compile/T6056.stderr index d9d4193..5695bd5 100644 --- a/testsuite/tests/simplCore/should_compile/T6056.stderr +++ b/testsuite/tests/simplCore/should_compile/T6056.stderr @@ -1,13 +1,6 @@ Rule fired: foldr/nil -Rule fired: foldr/nil -Rule fired: SPEC/T6056 $wsmallerAndRest @ Integer Rule fired: SPEC/T6056 $wsmallerAndRest @ Int Rule fired: Class op < -Rule fired: Class op < -Rule fired: SPEC/T6056 $wsmallerAndRest @ Integer -Rule fired: SPEC/T6056 $wsmallerAndRest @ Integer Rule fired: SPEC/T6056 $wsmallerAndRest @ Int Rule fired: SPEC/T6056 $wsmallerAndRest @ Int Rule fired: SPEC/T6056 $wsmallerAndRest @ Int -Rule fired: SPEC/T6056 $wsmallerAndRest @ Integer - From git at git.haskell.org Tue Nov 4 10:39:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:39:14 +0000 (UTC) Subject: [commit: ghc] master: Compiler performance is much worse in for loopy givens (ce9d6f2) Message-ID: <20141104103914.1003A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ce9d6f251f9764f769f5ebd8c6130809b6b0d159/ghc >--------------------------------------------------------------- commit ce9d6f251f9764f769f5ebd8c6130809b6b0d159 Author: Simon Peyton Jones Date: Mon Nov 3 10:37:59 2014 +0000 Compiler performance is much worse in for loopy givens This is a deliberate choice, to simplify code, invariants, and I think performance in typical cases. The "loopy givens" case is situations like [G] a ~ TF (a, Int) where TF is a type function with TF (a,b) = (TF a, TF b). See Note [An alternative story for the inert substitution] in TcFlatten. >--------------------------------------------------------------- ce9d6f251f9764f769f5ebd8c6130809b6b0d159 testsuite/tests/perf/compiler/T5837.hs | 40 +++++++++++++++++++++++++++++----- testsuite/tests/perf/compiler/all.T | 4 +++- 2 files changed, 38 insertions(+), 6 deletions(-) diff --git a/testsuite/tests/perf/compiler/T5837.hs b/testsuite/tests/perf/compiler/T5837.hs index 1dc3c33..6ebbd65 100644 --- a/testsuite/tests/perf/compiler/T5837.hs +++ b/testsuite/tests/perf/compiler/T5837.hs @@ -10,14 +10,44 @@ t = undefined {- - [G] a ~ TF (a,Int) + [G] a ~ TF (a,Int) -- a = a_am1 --> - TF (a,Int) ~ fsk - fsk ~ a + [G] TF (a,Int) ~ fsk -- fsk = fsk_am8 +inert [G] fsk ~ a + ---> - fsk ~ (TF a, TF Int) - fsk ~ a + [G] fsk ~ (TF a, TF Int) +inert [G] fsk ~ a + ---> a ~ (TF a, TF Int) +inert [G] fsk ~ a + +---> (attempting to flatten (TF a) so that it does not mention a + TF a ~ fsk2 +inert a ~ (fsk2, TF Int) +inert fsk ~ (fsk2, TF Int) + +---> (substitute for a) + TF (fsk2, TF Int) ~ fsk2 +inert a ~ (fsk2, TF Int) +inert fsk ~ (fsk2, TF Int) + +---> (top-level reduction, re-orient) + fsk2 ~ (TF fsk2, TF Int) +inert a ~ (fsk2, TF Int) +inert fsk ~ (fsk2, TF Int) + +---> (attempt to flatten (TF fsk2) to get rid of fsk2 + TF fsk2 ~ fsk3 + fsk2 ~ (fsk3, TF Int) +inert a ~ (fsk2, TF Int) +inert fsk ~ (fsk2, TF Int) + +---> + TF fsk2 ~ fsk3 +inert fsk2 ~ (fsk3, TF Int) +inert a ~ ((fsk3, TF Int), TF Int) +inert fsk ~ ((fsk3, TF Int), TF Int) -} \ No newline at end of file diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 76aee35..6df8210 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -455,7 +455,7 @@ test('T5837', # 40000000 (x86/Linux) # 2013-11-13: 45520936 (x86/Windows, 64bit machine) # 2041-09-03: 37096484 (Windows laptop, w/w for INLINABLE things - (wordsize(64), 75765728, 10)]) + (wordsize(64), 651924880, 10)]) # sample: 3926235424 (amd64/Linux, 15/2/2012) # 2012-10-02 81879216 # 2012-09-20 87254264 amd64/Linux @@ -464,6 +464,8 @@ test('T5837', # for constraints solving # 2014-08-29 73639840 amd64/Linux, w/w for INLINABLE things # 2014-10-08 73639840 amd64/Linux, Burning Bridges and other small changes + # 2014-11-02 651924880 Linux, Accept big regression; + # See Note [An alternative story for the inert substitution] in TcFlatten ], compile_fail,['-ftype-function-depth=50']) From git at git.haskell.org Tue Nov 4 10:39:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:39:17 +0000 (UTC) Subject: [commit: ghc] master: Simon's major commit to re-engineer the constraint solver (5770029) Message-ID: <20141104103917.68CE83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5770029a1f8509a673b2277287fc8fe90b9b6002/ghc >--------------------------------------------------------------- commit 5770029a1f8509a673b2277287fc8fe90b9b6002 Author: Simon Peyton Jones Date: Mon Nov 3 17:23:11 2014 +0000 Simon's major commit to re-engineer the constraint solver The driving change is this: * The canonical CFunEqCan constraints now have the form [G] F xis ~ fsk [W] F xis ~ fmv where fsk is a flatten-skolem, and fmv is a flatten-meta-variable Think of them as the name of the type-function application See Note [The flattening story] in TcFlatten. A flatten-meta-variable is distinguishable by its MetaInfo of FlatMetaTv This in turn led to an enormous cascade of other changes, which simplify and modularise the constraint solver. In particular: * Basic data types * I got rid of inert_solved_funeqs altogether. It serves no useful role that inert_flat_cache does not solve. * I added wl_implics to the WorkList, as a convenient place to accumulate newly-emitted implications; see Note [Residual implications] in TcSMonad. * I eliminated tcs_ty_binds altogether. These were the bindings for unification variables that we have now solved by unification. We kept them in a finite map and did the side-effecting unification later. But in cannonicalisation we had to look up in the side-effected mutable tyvars anyway, so nothing was being gained. Our original idea was that the solver would be pure, and would be a no-op if you discarded its results, but this was already not-true for implications since we update their evidence bindings in an imperative way. So rather than the uneasy compromise, it's now clearly imperative! * I split out the flatten/unflatten code into a new module, TcFlatten * I simplified and articulated explicitly the (rather hazy) invariants for the inert substitution inert_eqs. See Note [eqCanRewrite] and See Note [Applying the inert substitution] in TcFlatten * Unflattening is now done (by TcFlatten.unflatten) after solveFlats, before solving nested implications. This turned out to simplify a lot of code. Previously, unflattening was done as part of zonking, at the very very end. * Eager unflattening allowed me to remove the unpleasant ic_fsks field of an Implication (hurrah) * Eager unflattening made the TcSimplify.floatEqualities function much simpler (just float equalities looking like a ~ ty, where a is an untouchable meta-tyvar). * Likewise the idea of "pushing wanteds in as givens" could be completely eliminated. * I radically simplified the code that determines when there are 'given' equalities, and hence whether we can float 'wanted' equalies out. See TcSMonad.getNoGivenEqs, and Note [When does an implication have given equalities?]. This allowed me to get rid of the unpleasant inert_no_eqs flag in InertCans. * As part of this given-equality stuff, I fixed Trac #9211. See Note [Let-bound skolems] in TcSMonad * Orientation of tyvar/tyvar equalities (a ~ b) was partly done during canonicalisation, but then repeated in the spontaneous-solve stage (trySpontaneousSolveTwoWay). Now it is done exclusively during canonicalisation, which keeps all the code in one place. See Note [Canonical orientation for tyvar/tyvar equality constraints] in TcCanonical >--------------------------------------------------------------- 5770029a1f8509a673b2277287fc8fe90b9b6002 compiler/ghc.cabal.in | 1 + compiler/typecheck/Flattening-notes | 13 +- compiler/typecheck/Inst.lhs | 19 +- compiler/typecheck/TcCanonical.lhs | 929 ++++++++------------------- compiler/typecheck/TcFlatten.lhs | 1147 +++++++++++++++++++++++++++++++++ compiler/typecheck/TcInteract.lhs | 895 +++++++++++++------------- compiler/typecheck/TcMType.lhs | 139 +--- compiler/typecheck/TcRnTypes.lhs | 185 +++--- compiler/typecheck/TcRules.lhs | 2 - compiler/typecheck/TcSMonad.lhs | 1205 ++++++++++++++++++----------------- compiler/typecheck/TcSimplify.lhs | 403 +++++------- compiler/typecheck/TcType.lhs | 107 +++- compiler/typecheck/TcUnify.lhs | 1 - 13 files changed, 2835 insertions(+), 2211 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5770029a1f8509a673b2277287fc8fe90b9b6002 From git at git.haskell.org Tue Nov 4 10:39:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:39:19 +0000 (UTC) Subject: [commit: ghc] master: Updates to safePkg01 under Edward's guidance (2f0d841) Message-ID: <20141104103919.EF5893A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2f0d84164006665cd7c89cc77c1c1896a6ff0bcf/ghc >--------------------------------------------------------------- commit 2f0d84164006665cd7c89cc77c1c1896a6ff0bcf Author: Simon Peyton Jones Date: Tue Nov 4 08:36:17 2014 +0000 Updates to safePkg01 under Edward's guidance >--------------------------------------------------------------- 2f0d84164006665cd7c89cc77c1c1896a6ff0bcf testsuite/tests/safeHaskell/check/pkg01/Makefile | 17 +++++++++-------- testsuite/tests/safeHaskell/check/pkg01/all.T | 4 ---- .../tests/safeHaskell/check/pkg01/safePkg01.stdout | 16 ++++++++-------- 3 files changed, 17 insertions(+), 20 deletions(-) diff --git a/testsuite/tests/safeHaskell/check/pkg01/Makefile b/testsuite/tests/safeHaskell/check/pkg01/Makefile index 19e1106..a53b4e6 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/Makefile +++ b/testsuite/tests/safeHaskell/check/pkg01/Makefile @@ -36,6 +36,7 @@ mkPackageDatabase.%: safePkg01_GHC_PKG = '$(GHC_PKG)' --no-user-package-db -f pdb.safePkg01/local.db +SHOW_IFACE=-dppr-cols999 --show-iface safePkg01: '$(MAKE)' mkPackageDatabase.safePkg01 @@ -43,28 +44,28 @@ safePkg01: $(safePkg01_GHC_PKG) field safePkg01-1.0 trusted echo echo 'M_SafePkg' - '$(TEST_HC)' --show-iface pdb.safePkg01/dist/build/M_SafePkg.$(HI_SUF) | grep -E '^package dependencies:|^trusted:|^require own pkg trusted:' + '$(TEST_HC)' $(SHOW_IFACE) pdb.safePkg01/dist/build/M_SafePkg.$(HI_SUF) | grep -E '^package dependencies:|^trusted:|^require own pkg trusted:' echo echo 'M_SafePkg2' - '$(TEST_HC)' --show-iface pdb.safePkg01/dist/build/M_SafePkg2.$(HI_SUF) | grep -E '^package dependencies:|^trusted:|^require own pkg trusted:' + '$(TEST_HC)' $(SHOW_IFACE) pdb.safePkg01/dist/build/M_SafePkg2.$(HI_SUF) | grep -E '^package dependencies:|^trusted:|^require own pkg trusted:' echo echo 'M_SafePkg3' - '$(TEST_HC)' --show-iface pdb.safePkg01/dist/build/M_SafePkg3.$(HI_SUF) | grep -E '^package dependencies:|^trusted:|^require own pkg trusted:' + '$(TEST_HC)' $(SHOW_IFACE) pdb.safePkg01/dist/build/M_SafePkg3.$(HI_SUF) | grep -E '^package dependencies:|^trusted:|^require own pkg trusted:' echo echo 'M_SafePkg4' - '$(TEST_HC)' --show-iface pdb.safePkg01/dist/build/M_SafePkg4.$(HI_SUF) | grep -E '^package dependencies:|^trusted:|^require own pkg trusted:' + '$(TEST_HC)' $(SHOW_IFACE) pdb.safePkg01/dist/build/M_SafePkg4.$(HI_SUF) | grep -E '^package dependencies:|^trusted:|^require own pkg trusted:' echo echo 'M_SafePkg5' - '$(TEST_HC)' --show-iface pdb.safePkg01/dist/build/M_SafePkg5.$(HI_SUF) | grep -E '^package dependencies:|^trusted:|^require own pkg trusted:' + '$(TEST_HC)' $(SHOW_IFACE) pdb.safePkg01/dist/build/M_SafePkg5.$(HI_SUF) | grep -E '^package dependencies:|^trusted:|^require own pkg trusted:' echo echo 'M_SafePkg6' - '$(TEST_HC)' --show-iface pdb.safePkg01/dist/build/M_SafePkg6.$(HI_SUF) | grep -E '^package dependencies:|^trusted:|^require own pkg trusted:' + '$(TEST_HC)' $(SHOW_IFACE) pdb.safePkg01/dist/build/M_SafePkg6.$(HI_SUF) | grep -E '^package dependencies:|^trusted:|^require own pkg trusted:' echo echo 'M_SafePkg7' - '$(TEST_HC)' --show-iface pdb.safePkg01/dist/build/M_SafePkg7.$(HI_SUF) | grep -E '^package dependencies:|^trusted:|^require own pkg trusted:' + '$(TEST_HC)' $(SHOW_IFACE) pdb.safePkg01/dist/build/M_SafePkg7.$(HI_SUF) | grep -E '^package dependencies:|^trusted:|^require own pkg trusted:' echo echo 'M_SafePkg8' - '$(TEST_HC)' --show-iface pdb.safePkg01/dist/build/M_SafePkg8.$(HI_SUF) | grep -E '^package dependencies:|^trusted:|^require own pkg trusted:' + '$(TEST_HC)' $(SHOW_IFACE) pdb.safePkg01/dist/build/M_SafePkg8.$(HI_SUF) | grep -E '^package dependencies:|^trusted:|^require own pkg trusted:' echo echo 'Testing setting trust' $(safePkg01_GHC_PKG) trust safePkg01-1.0 diff --git a/testsuite/tests/safeHaskell/check/pkg01/all.T b/testsuite/tests/safeHaskell/check/pkg01/all.T index 732f6fb..604a5cc 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/all.T +++ b/testsuite/tests/safeHaskell/check/pkg01/all.T @@ -11,9 +11,6 @@ def normaliseBytestringPackage(str): def normaliseIntegerPackage(str): return re.sub('integer-(gmp|simple)-[0-9.]+', 'integer--', str) -def normaliseArrayPackageKey(str): - return re.sub('array_[A-Za-z0-9]+', 'array_', str) - def ignoreLdOutput(str): return re.sub('Creating library file: pdb.safePkg01/dist.build.libHSsafePkg01-1.0-ghc[0-9.]*.dll.a\n', '', str) @@ -43,7 +40,6 @@ test('safePkg01', normalise_errmsg_fun(ignoreLdOutput), normalise_fun( normaliseArrayPackage, - normaliseArrayPackageKey, normaliseBytestringPackage)], run_command, ['$MAKE -s --no-print-directory safePkg01 ' + make_args]) diff --git a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout index 62074de..44ea89f 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout +++ b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout @@ -4,42 +4,42 @@ pdb.safePkg01/local.db: trusted: False M_SafePkg -package dependencies: base-4.8.0.0* ghc-prim-0.3.1.0 +package dependencies: base-4.8.0.0* ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 trusted: safe require own pkg trusted: False M_SafePkg2 -package dependencies: base-4.8.0.0 ghc-prim-0.3.1.0 +package dependencies: base-4.8.0.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 trusted: trustworthy require own pkg trusted: False M_SafePkg3 -package dependencies: base-4.8.0.0* ghc-prim-0.3.1.0 +package dependencies: base-4.8.0.0* ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 trusted: safe require own pkg trusted: True M_SafePkg4 -package dependencies: base-4.8.0.0* ghc-prim-0.3.1.0 +package dependencies: base-4.8.0.0* ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 trusted: safe require own pkg trusted: True M_SafePkg5 -package dependencies: base-4.8.0.0* ghc-prim-0.3.1.0 +package dependencies: base-4.8.0.0* ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 trusted: safe require own pkg trusted: True M_SafePkg6 -package dependencies: array-0.5.0.1 at array_ +package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.4.0* deepseq-1.3.0.3 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 trusted: trustworthy require own pkg trusted: False M_SafePkg7 -package dependencies: array-0.5.0.1 at array_ +package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.4.0* deepseq-1.3.0.3 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 trusted: safe require own pkg trusted: False M_SafePkg8 -package dependencies: array-0.5.0.1 at array_ +package dependencies: array-0.5.0.1 base-4.8.0.0 bytestring-0.10.4.0* deepseq-1.3.0.3 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 trusted: trustworthy require own pkg trusted: False From git at git.haskell.org Tue Nov 4 10:39:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:39:22 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #9750 (fe178b2) Message-ID: <20141104103922.C56533A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fe178b2729bb044b401b3fe670d12bcd3d14ad71/ghc >--------------------------------------------------------------- commit fe178b2729bb044b401b3fe670d12bcd3d14ad71 Author: Simon Peyton Jones Date: Tue Nov 4 10:37:38 2014 +0000 Test Trac #9750 >--------------------------------------------------------------- fe178b2729bb044b401b3fe670d12bcd3d14ad71 testsuite/tests/polykinds/T9750.hs | 34 ++++++++++++++++++++++++++++++++++ testsuite/tests/polykinds/all.T | 1 + 2 files changed, 35 insertions(+) diff --git a/testsuite/tests/polykinds/T9750.hs b/testsuite/tests/polykinds/T9750.hs new file mode 100644 index 0000000..9d865d0 --- /dev/null +++ b/testsuite/tests/polykinds/T9750.hs @@ -0,0 +1,34 @@ +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE ScopedTypeVariables #-} + +module T9750 where + +import GHC.TypeLits ( Symbol, KnownSymbol ) + +-------------------------------------------------------------------------------- + +data Meta = MetaCons Symbol +data M1 (c :: Meta) = M1 + +class Generic a where + type Rep a :: * + from :: a -> Rep a + +-------------------------------------------------------------------------------- + +data A = A1 + +instance Generic A where + type Rep A = M1 ('MetaCons "test") + from A1 = M1 + +class GShow' f where + gshowsPrec' :: f -> ShowS + +instance (KnownSymbol c) => GShow' (M1 ('MetaCons c)) where + gshowsPrec' = error "urk" + +instance GShow' A where + gshowsPrec' = gshowsPrec' . from diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index 5b02dda..48b0e61 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -108,3 +108,4 @@ test('T9263', normal, run_command, ['$MAKE -s --no-print-directory T9263']) test('T9063', normal, compile, ['']) test('T9200', normal, compile, ['']) test('T9200b', normal, compile_fail, ['']) +test('T9750', normal, compile, ['']) From git at git.haskell.org Tue Nov 4 10:39:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 10:39:25 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #9081 (09aac7d) Message-ID: <20141104103925.C012E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/09aac7dafc2905603283b6028e4ce7416716bcd6/ghc >--------------------------------------------------------------- commit 09aac7dafc2905603283b6028e4ce7416716bcd6 Author: Simon Peyton Jones Date: Tue Nov 4 10:35:05 2014 +0000 Test Trac #9081 >--------------------------------------------------------------- 09aac7dafc2905603283b6028e4ce7416716bcd6 testsuite/tests/th/T9081.hs | 10 ++++++++++ testsuite/tests/th/all.T | 1 + 2 files changed, 11 insertions(+) diff --git a/testsuite/tests/th/T9081.hs b/testsuite/tests/th/T9081.hs new file mode 100644 index 0000000..1fa2b83 --- /dev/null +++ b/testsuite/tests/th/T9081.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell, DataKinds, PolyKinds, TypeFamilies #-} + +module T9081 where + +import Data.Proxy + +$( [d| + class kproxy ~ 'KProxy => C (kproxy :: KProxy a) where + type TF (x :: a) :: Bool + |]) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 5e65875..a35e126 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -335,3 +335,4 @@ test('T9692', normal, compile, ['-v0']) test('T8953', normal, compile, ['-v0']) test('T9084', normal, compile_fail, ['-v0']) test('T9738', normal, compile, ['-v0']) +test('T9081', normal, compile, ['-v0']) From git at git.haskell.org Tue Nov 4 11:33:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 11:33:47 +0000 (UTC) Subject: [commit: ghc] master: Remove redundant "Minimal complete definition"-comments (1408c8d) Message-ID: <20141104113347.2B70B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1408c8dcd4ccf3c4f418ca8dd13516efb604922f/ghc >--------------------------------------------------------------- commit 1408c8dcd4ccf3c4f418ca8dd13516efb604922f Author: Herbert Valerio Riedel Date: Tue Nov 4 11:43:29 2014 +0100 Remove redundant "Minimal complete definition"-comments Those manual descriptions in Haddock strings have become redundant since Haddock gained the ability to print the minimal complete definition as specified via `{-# MINIMAL #-}` annotation (or otherwise inferred by GHC). Moreover, this commit moves all `{-# MINIMAL #-}` annotations in `base` to the start of the respective `class` definitions, as this is more readable and matches more closely the way Haddock renders that information. >--------------------------------------------------------------- 1408c8dcd4ccf3c4f418ca8dd13516efb604922f libraries/base/Control/Arrow.hs | 4 ++-- libraries/base/Control/Monad/Zip.hs | 2 +- libraries/base/Data/Foldable.hs | 2 -- libraries/base/Data/Traversable.hs | 5 ++--- libraries/base/Foreign/Storable.hs | 11 +++-------- libraries/base/GHC/Base.lhs | 6 ------ libraries/base/GHC/Float.lhs | 7 ------- libraries/base/GHC/Num.lhs | 5 ++--- libraries/base/GHC/Read.lhs | 5 ++--- libraries/base/GHC/Real.lhs | 9 ++------- libraries/base/GHC/Show.lhs | 5 ++--- 11 files changed, 16 insertions(+), 45 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1408c8dcd4ccf3c4f418ca8dd13516efb604922f From git at git.haskell.org Tue Nov 4 11:42:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 11:42:27 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData: Merge branch 'master' into wip/GenericsMetaData (3744afb) Message-ID: <20141104114227.147B63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData Link : http://ghc.haskell.org/trac/ghc/changeset/3744afb5d91ebbe235230b7e9a03e1918ed4aa2c/ghc >--------------------------------------------------------------- commit 3744afb5d91ebbe235230b7e9a03e1918ed4aa2c Merge: d8e8996 d3a7126 Author: Jose Pedro Magalhaes Date: Tue Nov 4 11:10:27 2014 +0000 Merge branch 'master' into wip/GenericsMetaData >--------------------------------------------------------------- 3744afb5d91ebbe235230b7e9a03e1918ed4aa2c compiler/simplCore/CallArity.hs | 4 +- compiler/simplCore/SetLevels.lhs | 2 +- docs/users_guide/7.10.1-notes.xml | 22 +- libraries/base/Data/Bool.hs | 40 ++-- libraries/base/Data/Char.hs | 341 +++++++++++++++++++++++++++++-- libraries/base/Data/Fixed.hs | 25 +-- libraries/base/Data/Typeable.hs | 21 +- libraries/base/Data/Typeable/Internal.hs | 27 ++- libraries/base/GHC/Show.lhs | 1 + libraries/base/base.cabal | 1 - libraries/base/changelog.md | 2 + libraries/base/tests/T9681.hs | 3 + libraries/base/tests/T9681.stderr | 5 + libraries/base/tests/all.T | 1 + testsuite/.gitignore | 4 +- testsuite/driver/testlib.py | 10 +- utils/haddock | 2 +- 17 files changed, 413 insertions(+), 98 deletions(-) From git at git.haskell.org Tue Nov 4 11:42:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 11:42:29 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData's head updated: Merge branch 'master' into wip/GenericsMetaData (3744afb) Message-ID: <20141104114229.51F623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/GenericsMetaData' now includes: c6d4ae6 Fix test driver python3 compatibility issues 578bc00 Add notes on change to hGetContents semantics 995ea1c Fixed missing trailing newline bug in pretty printer 1907e81 Updated testsuite/.gitignore to exclude some test artifacts on Windows. cbb20ab Drop deprecated `OverlappingInstances` from base 919e930 Fix comment typos 8ef4cf1 Add doctest examples for Data.Char bd6c6f6 Update Haddock submodule 54addb1 Clean-up `Data.Fixed` f12be5b Add changelog entry for recent Unicode 7.0 update d3a7126 Update doctest example style in `Data.Bool` 3744afb Merge branch 'master' into wip/GenericsMetaData From git at git.haskell.org Tue Nov 4 14:18:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 14:18:44 +0000 (UTC) Subject: [commit: ghc] branch 'wip/GenericsMetaData2' created Message-ID: <20141104141844.910403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/GenericsMetaData2 Referencing: fcc4ad391432ea1f8faf7d076218f468ed426ace From git at git.haskell.org Tue Nov 4 14:18:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 14:18:47 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData2: Use TypeLits in the meta-data encoding of GHC.Generics (8fa0e5c) Message-ID: <20141104141847.5164F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData2 Link : http://ghc.haskell.org/trac/ghc/changeset/8fa0e5c1a4de2c9761dc2aa2f141b5fa6a9e6660/ghc >--------------------------------------------------------------- commit 8fa0e5c1a4de2c9761dc2aa2f141b5fa6a9e6660 Author: Jose Pedro Magalhaes Date: Thu Oct 2 08:38:05 2014 +0100 Use TypeLits in the meta-data encoding of GHC.Generics The following wiki page contains more information about this: https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/GenericDeriving#Amoreconservativefirstapproachtothisproblem >--------------------------------------------------------------- 8fa0e5c1a4de2c9761dc2aa2f141b5fa6a9e6660 compiler/prelude/PrelNames.lhs | 71 ++++++-- compiler/typecheck/TcDeriv.lhs | 64 ++----- compiler/typecheck/TcGenDeriv.lhs | 18 +- compiler/typecheck/TcGenGenerics.lhs | 308 +++++++++----------------------- libraries/base/Data/Monoid.hs | 1 + libraries/base/GHC/Generics.hs | 190 ++++++++++++++++---- testsuite/tests/generics/GShow/GShow.hs | 1 + 7 files changed, 314 insertions(+), 339 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8fa0e5c1a4de2c9761dc2aa2f141b5fa6a9e6660 From git at git.haskell.org Tue Nov 4 14:18:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 14:18:49 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData2: Update test output (fcc4ad3) Message-ID: <20141104141849.ED5113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData2 Link : http://ghc.haskell.org/trac/ghc/changeset/fcc4ad391432ea1f8faf7d076218f468ed426ace/ghc >--------------------------------------------------------------- commit fcc4ad391432ea1f8faf7d076218f468ed426ace Author: Jose Pedro Magalhaes Date: Tue Nov 4 10:02:17 2014 +0000 Update test output >--------------------------------------------------------------- fcc4ad391432ea1f8faf7d076218f468ed426ace testsuite/tests/generics/GenDerivOutput.stderr | 120 +++++----- testsuite/tests/generics/GenDerivOutput1_0.stderr | 48 ++-- testsuite/tests/generics/GenDerivOutput1_1.stderr | 254 ++++++++++------------ 3 files changed, 187 insertions(+), 235 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fcc4ad391432ea1f8faf7d076218f468ed426ace From git at git.haskell.org Tue Nov 4 14:27:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 14:27:50 +0000 (UTC) Subject: [commit: ghc] master: Re-center perf-numbers for T5631 (64dc4d1) Message-ID: <20141104142750.293253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/64dc4d1085a7db375f6532362bf7e23fac3a25eb/ghc >--------------------------------------------------------------- commit 64dc4d1085a7db375f6532362bf7e23fac3a25eb Author: Herbert Valerio Riedel Date: Tue Nov 4 15:27:17 2014 +0100 Re-center perf-numbers for T5631 >--------------------------------------------------------------- 64dc4d1085a7db375f6532362bf7e23fac3a25eb testsuite/tests/perf/compiler/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 6df8210..58c3891 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -333,11 +333,12 @@ test('T5631', [(wordsize(32), 346389856, 10), # expected value: 392904228 (x86/Linux) # 2014-04-04: 346389856 (x86 Windows, 64 bit machine) - (wordsize(64), 739704712, 5)]), + (wordsize(64), 776121120, 5)]), # expected value: 774595008 (amd64/Linux): # expected value: 735486328 (amd64/Linux) 2012/12/12: # expected value: 690742040 (amd64/Linux) Call Arity improvements # 2014-09-09: 739704712 (amd64/Linux) AMP changes + # 2014-11-04: 776121120 (amd64/Linux) new-flatten-skolems only_ways(['normal']) ], compile, From git at git.haskell.org Tue Nov 4 14:58:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 14:58:07 +0000 (UTC) Subject: [commit: ghc] master: A little refactoring of HsSplice and friends (6a1c05f) Message-ID: <20141104145807.0A5C13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6a1c05f01429511984b63c49e6d802673ca5f4a1/ghc >--------------------------------------------------------------- commit 6a1c05f01429511984b63c49e6d802673ca5f4a1 Author: Simon Peyton Jones Date: Tue Nov 4 14:58:13 2014 +0000 A little refactoring of HsSplice and friends Plus adding comments. The most substantive change is that PendingTcSplice becomes a proper data type rather than a pair; and PendingRnSplice uses it >--------------------------------------------------------------- 6a1c05f01429511984b63c49e6d802673ca5f4a1 compiler/deSugar/DsMeta.hs | 2 +- compiler/hsSyn/HsExpr.lhs | 140 ++++++++++++++++++++++++--------------- compiler/hsSyn/HsUtils.lhs | 8 +-- compiler/rename/RnSplice.lhs | 45 +++++++------ compiler/typecheck/TcExpr.lhs | 3 +- compiler/typecheck/TcHsSyn.lhs | 4 +- compiler/typecheck/TcRnTypes.lhs | 4 +- compiler/typecheck/TcSplice.lhs | 16 +++-- 8 files changed, 130 insertions(+), 92 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6a1c05f01429511984b63c49e6d802673ca5f4a1 From git at git.haskell.org Tue Nov 4 16:36:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 16:36:26 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9066 in th/T9066 (ba147ac) Message-ID: <20141104163626.394513A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/ba147ac1556b8024ff580825752cc64311593226/ghc >--------------------------------------------------------------- commit ba147ac1556b8024ff580825752cc64311593226 Author: Richard Eisenberg Date: Sun Nov 2 13:44:27 2014 -0500 Test #9066 in th/T9066 >--------------------------------------------------------------- ba147ac1556b8024ff580825752cc64311593226 testsuite/tests/th/T9066.hs | 10 ++++++++++ testsuite/tests/th/all.T | 2 ++ 2 files changed, 12 insertions(+) diff --git a/testsuite/tests/th/T9066.hs b/testsuite/tests/th/T9066.hs new file mode 100644 index 0000000..2e46fe5 --- /dev/null +++ b/testsuite/tests/th/T9066.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T9066 where + +$([d| data Blargh = (:<=>) Int Int + infix 4 :<=> + + type Foo a b = Either a b + infix 5 `Foo` + |]) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index a35e126..3d64060 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -336,3 +336,5 @@ test('T8953', normal, compile, ['-v0']) test('T9084', normal, compile_fail, ['-v0']) test('T9738', normal, compile, ['-v0']) test('T9081', normal, compile, ['-v0']) +test('T9066', expect_broken(9066), compile, ['-v0']) + From git at git.haskell.org Tue Nov 4 16:36:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 16:36:28 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9066. (c00f6e7) Message-ID: <20141104163628.E42663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/c00f6e7670f06a9c89dd77a18c2288949688c70f/ghc >--------------------------------------------------------------- commit c00f6e7670f06a9c89dd77a18c2288949688c70f Author: Richard Eisenberg Date: Mon Nov 3 11:15:35 2014 -0500 Fix #9066. When splicing in a fixity declaration, look for both term-level things and type-level things. This requires some changes elsewhere in the code to allow for more flexibility when looking up Exact names, which can be assigned the wrong namespace during fixity declaration conversion. See the ticket for more info. >--------------------------------------------------------------- c00f6e7670f06a9c89dd77a18c2288949688c70f compiler/basicTypes/RdrName.lhs | 11 +++++--- compiler/hsSyn/Convert.lhs | 17 +++++++++--- compiler/rename/RnEnv.lhs | 57 ++++++++++++++++++++++++++--------------- testsuite/tests/th/all.T | 3 +-- 4 files changed, 58 insertions(+), 30 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c00f6e7670f06a9c89dd77a18c2288949688c70f From git at git.haskell.org Tue Nov 4 16:36:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 16:36:31 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9209, by reporting an error instead of panicking on bad splices. (20e1bb1) Message-ID: <20141104163631.895D93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/20e1bb1c582bd7b884bea624fee8699f3e2ec3d3/ghc >--------------------------------------------------------------- commit 20e1bb1c582bd7b884bea624fee8699f3e2ec3d3 Author: Richard Eisenberg Date: Mon Nov 3 13:49:59 2014 -0500 Fix #9209, by reporting an error instead of panicking on bad splices. >--------------------------------------------------------------- 20e1bb1c582bd7b884bea624fee8699f3e2ec3d3 compiler/parser/Parser.y.pp | 15 ++++++------ compiler/parser/RdrHsSyn.lhs | 57 +++++++++++++++++++++++++------------------- testsuite/tests/th/all.T | 2 +- 3 files changed, 42 insertions(+), 32 deletions(-) diff --git a/compiler/parser/Parser.y.pp b/compiler/parser/Parser.y.pp index e33808d..98468d4 100644 --- a/compiler/parser/Parser.y.pp +++ b/compiler/parser/Parser.y.pp @@ -684,12 +684,12 @@ ty_decl :: { LTyClDecl RdrName } inst_decl :: { LInstDecl RdrName } : 'instance' overlap_pragma inst_type where_inst - { let (binds, sigs, _, ats, adts, _) = cvBindsAndSigs (unLoc $4) in - let cid = ClsInstDecl { cid_poly_ty = $3, cid_binds = binds - , cid_sigs = sigs, cid_tyfam_insts = ats - , cid_overlap_mode = $2 - , cid_datafam_insts = adts } - in L (comb3 $1 $3 $4) (ClsInstD { cid_inst = cid }) } + {% do { (binds, sigs, _, ats, adts, _) <- cvBindsAndSigs (unLoc $4) + ; let cid = ClsInstDecl { cid_poly_ty = $3, cid_binds = binds + , cid_sigs = sigs, cid_tyfam_insts = ats + , cid_overlap_mode = $2 + , cid_datafam_insts = adts } + ; return (L (comb3 $1 $3 $4) (ClsInstD { cid_inst = cid })) } } -- type instance declarations | 'type' 'instance' ty_fam_inst_eqn @@ -950,7 +950,8 @@ decllist :: { Located (OrdList (LHsDecl RdrName)) } -- binds :: { Located (HsLocalBinds RdrName) } -- May have implicit parameters -- No type declarations - : decllist { L1 (HsValBinds (cvBindGroup (unLoc $1))) } + : decllist {% do { val_binds <- cvBindGroup (unLoc $1) + ; return (L1 (HsValBinds val_binds)) } } | '{' dbinds '}' { LL (HsIPBinds (IPBinds (unLoc $2) emptyTcEvBinds)) } | vocurly dbinds close { L (getLoc $2) (HsIPBinds (IPBinds (unLoc $2) emptyTcEvBinds)) } diff --git a/compiler/parser/RdrHsSyn.lhs b/compiler/parser/RdrHsSyn.lhs index e6969e7..125bfa9 100644 --- a/compiler/parser/RdrHsSyn.lhs +++ b/compiler/parser/RdrHsSyn.lhs @@ -127,8 +127,8 @@ mkClassDecl :: SrcSpan -> P (LTyClDecl RdrName) mkClassDecl loc (L _ (mcxt, tycl_hdr)) fds where_cls - = do { let (binds, sigs, ats, at_insts, _, docs) = cvBindsAndSigs (unLoc where_cls) - cxt = fromMaybe (noLoc []) mcxt + = do { (binds, sigs, ats, at_insts, _, docs) <- cvBindsAndSigs (unLoc where_cls) + ; let cxt = fromMaybe (noLoc []) mcxt ; (cls, tparams) <- checkTyClHdr tycl_hdr ; tyvars <- checkTyVarsP (ptext (sLit "class")) whereDots cls tparams ; at_defs <- mapM (eitherToP . mkATDefault) at_insts @@ -308,36 +308,45 @@ cvTopDecls decls = go (fromOL decls) go (d : ds) = d : go ds -- Declaration list may only contain value bindings and signatures. -cvBindGroup :: OrdList (LHsDecl RdrName) -> HsValBinds RdrName +cvBindGroup :: OrdList (LHsDecl RdrName) -> P (HsValBinds RdrName) cvBindGroup binding - = case cvBindsAndSigs binding of - (mbs, sigs, fam_ds, tfam_insts, dfam_insts, _) - -> ASSERT( null fam_ds && null tfam_insts && null dfam_insts) - ValBindsIn mbs sigs + = do { (mbs, sigs, fam_ds, tfam_insts, dfam_insts, _) <- cvBindsAndSigs binding + ; ASSERT( null fam_ds && null tfam_insts && null dfam_insts) + return $ ValBindsIn mbs sigs } cvBindsAndSigs :: OrdList (LHsDecl RdrName) - -> (LHsBinds RdrName, [LSig RdrName], [LFamilyDecl RdrName] + -> P (LHsBinds RdrName, [LSig RdrName], [LFamilyDecl RdrName] , [LTyFamInstDecl RdrName], [LDataFamInstDecl RdrName], [LDocDecl]) -- Input decls contain just value bindings and signatures -- and in case of class or instance declarations also -- associated type declarations. They might also contain Haddock comments. -cvBindsAndSigs fb = go (fromOL fb) +cvBindsAndSigs fb = go (fromOL fb) where - go [] = (emptyBag, [], [], [], [], []) - go (L l (SigD s) : ds) = (bs, L l s : ss, ts, tfis, dfis, docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L l (ValD b) : ds) = (b' `consBag` bs, ss, ts, tfis, dfis, docs) - where (b', ds') = getMonoBind (L l b) ds - (bs, ss, ts, tfis, dfis, docs) = go ds' - go (L l (TyClD (FamDecl t)) : ds) = (bs, ss, L l t : ts, tfis, dfis, docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L l (InstD (TyFamInstD { tfid_inst = tfi })) : ds) = (bs, ss, ts, L l tfi : tfis, dfis, docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L l (InstD (DataFamInstD { dfid_inst = dfi })) : ds) = (bs, ss, ts, tfis, L l dfi : dfis, docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L l (DocD d) : ds) = (bs, ss, ts, tfis, dfis, (L l d) : docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L _ d : _) = pprPanic "cvBindsAndSigs" (ppr d) + go [] = return (emptyBag, [], [], [], [], []) + go (L l (ValD b) : ds) + = do { (bs, ss, ts, tfis, dfis, docs) <- go ds' + ; return (b' `consBag` bs, ss, ts, tfis, dfis, docs) } + where + (b', ds') = getMonoBind (L l b) ds + go (L l decl : ds) + = do { (bs, ss, ts, tfis, dfis, docs) <- go ds + ; case decl of + SigD s + -> return (bs, L l s : ss, ts, tfis, dfis, docs) + TyClD (FamDecl t) + -> return (bs, ss, L l t : ts, tfis, dfis, docs) + InstD (TyFamInstD { tfid_inst = tfi }) + -> return (bs, ss, ts, L l tfi : tfis, dfis, docs) + InstD (DataFamInstD { dfid_inst = dfi }) + -> return (bs, ss, ts, tfis, L l dfi : dfis, docs) + DocD d + -> return (bs, ss, ts, tfis, dfis, L l d : docs) + SpliceD d + -> parseErrorSDoc l $ + hang (text "Declaration splices are allowed only" <+> + text "at the top level:") + 2 (ppr d) + _ -> pprPanic "cvBindsAndSigs" (ppr decl) } ----------------------------------------------------------------------------- -- Group function bindings into equation groups diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 8d55bf7..bb8734e 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -337,4 +337,4 @@ test('T9084', normal, compile_fail, ['-v0']) test('T9738', normal, compile, ['-v0']) test('T9081', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) -test('T9209', expect_broken(9209), compile_fail, ['-v0']) +test('T9209', normal, compile_fail, ['-v0']) From git at git.haskell.org Tue Nov 4 16:36:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 16:36:34 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9209 in th/T9209 (fa05d66) Message-ID: <20141104163634.8F51F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/fa05d66e102138a7bb40fba7b8ab49bf2d5c2b33/ghc >--------------------------------------------------------------- commit fa05d66e102138a7bb40fba7b8ab49bf2d5c2b33 Author: Richard Eisenberg Date: Mon Nov 3 13:46:58 2014 -0500 Test #9209 in th/T9209 >--------------------------------------------------------------- fa05d66e102138a7bb40fba7b8ab49bf2d5c2b33 testsuite/tests/th/T9209.hs | 5 +++++ testsuite/tests/th/T9209.stderr | 4 ++++ testsuite/tests/th/all.T | 1 + 3 files changed, 10 insertions(+) diff --git a/testsuite/tests/th/T9209.hs b/testsuite/tests/th/T9209.hs new file mode 100644 index 0000000..46740ba --- /dev/null +++ b/testsuite/tests/th/T9209.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T9209 where + +foo = let $( [d| x = 5 |] ) in x diff --git a/testsuite/tests/th/T9209.stderr b/testsuite/tests/th/T9209.stderr new file mode 100644 index 0000000..1f4f3e7 --- /dev/null +++ b/testsuite/tests/th/T9209.stderr @@ -0,0 +1,4 @@ + +T9209.hs:5:11: + Declaration splices are allowed only at the top level: + $([d| x = 5 |]) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 342f5e3..8d55bf7 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -337,3 +337,4 @@ test('T9084', normal, compile_fail, ['-v0']) test('T9738', normal, compile, ['-v0']) test('T9081', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) +test('T9209', expect_broken(9209), compile_fail, ['-v0']) From git at git.haskell.org Tue Nov 4 16:36:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 16:36:37 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #7484 in th/T7484 (89b963f) Message-ID: <20141104163637.AEF1E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/89b963f2ec7e116ea34632fec54b174bfbd111ff/ghc >--------------------------------------------------------------- commit 89b963f2ec7e116ea34632fec54b174bfbd111ff Author: Richard Eisenberg Date: Mon Nov 3 15:33:51 2014 -0500 Test #7484 in th/T7484 >--------------------------------------------------------------- 89b963f2ec7e116ea34632fec54b174bfbd111ff testsuite/tests/th/T7484.hs | 7 +++++++ testsuite/tests/th/T7484.stderr | 4 ++++ testsuite/tests/th/all.T | 1 + 3 files changed, 12 insertions(+) diff --git a/testsuite/tests/th/T7484.hs b/testsuite/tests/th/T7484.hs new file mode 100644 index 0000000..b1a9cba --- /dev/null +++ b/testsuite/tests/th/T7484.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T7484 where + +import Language.Haskell.TH + +$( return [ ValD (VarP (mkName "a ")) (NormalB (LitE (IntegerL 5))) [] ] ) diff --git a/testsuite/tests/th/T7484.stderr b/testsuite/tests/th/T7484.stderr new file mode 100644 index 0000000..3ffe123 --- /dev/null +++ b/testsuite/tests/th/T7484.stderr @@ -0,0 +1,4 @@ + +T7484.hs:7:4: + Illegal variable name: ?a ? + When splicing a TH declaration: a = 5 diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index bb8734e..db41e19 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -338,3 +338,4 @@ test('T9738', normal, compile, ['-v0']) test('T9081', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) +test('T7484', expect_broken(7484), compile_fail, ['-v0']) From git at git.haskell.org Tue Nov 4 16:36:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 16:36:40 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #7484, checking for good binder names in Convert. (eed503f) Message-ID: <20141104163640.5A3CB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/eed503f49e4abcd3d6838c6d7892eb3ab77837d2/ghc >--------------------------------------------------------------- commit eed503f49e4abcd3d6838c6d7892eb3ab77837d2 Author: Richard Eisenberg Date: Mon Nov 3 15:34:53 2014 -0500 Fix #7484, checking for good binder names in Convert. This includes a somewhat pedantic check against the code in Lexer.x to make sure that TH accepts the same set of names that the lexer does. Doing this unearthed a latent bug dealing with unicode identifiers in OccName. >--------------------------------------------------------------- eed503f49e4abcd3d6838c6d7892eb3ab77837d2 compiler/basicTypes/OccName.lhs | 5 +- compiler/hsSyn/Convert.lhs | 137 ++++++++++++++++++++++++++++++++++++++-- testsuite/tests/th/all.T | 2 +- 3 files changed, 135 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/OccName.lhs b/compiler/basicTypes/OccName.lhs index 0010ad3..dc86991 100644 --- a/compiler/basicTypes/OccName.lhs +++ b/compiler/basicTypes/OccName.lhs @@ -905,7 +905,10 @@ isLexVarSym fs -- Infix identifiers e.g. "+" startsVarSym, startsVarId, startsConSym, startsConId :: Char -> Bool startsVarSym c = isSymbolASCII c || (ord c > 0x7f && isSymbol c) -- Infix Ids startsConSym c = c == ':' -- Infix data constructors -startsVarId c = isLower c || c == '_' -- Ordinary Ids +startsVarId c = c == '_' || case generalCategory c of -- Ordinary Ids + LowercaseLetter -> True + OtherLetter -> True -- See #1103 + _ -> False startsConId c = isUpper c || c == '(' -- Ordinary type constructors and data constructors isSymbolASCII :: Char -> Bool diff --git a/compiler/hsSyn/Convert.lhs b/compiler/hsSyn/Convert.lhs index 6cff928..6f2b14d 100644 --- a/compiler/hsSyn/Convert.lhs +++ b/compiler/hsSyn/Convert.lhs @@ -45,6 +45,8 @@ import Data.Maybe( catMaybes ) import Language.Haskell.TH as TH hiding (sigP) import Language.Haskell.TH.Syntax as TH import GHC.Exts +import Data.Char +import qualified Data.Set as Set ------------------------------------------------------------------- -- The external interface @@ -1109,13 +1111,134 @@ cvtName ctxt_ns (TH.Name occ flavour) occ_str = TH.occString occ okOcc :: OccName.NameSpace -> String -> Bool -okOcc _ [] = False -okOcc ns str@(c:_) - | OccName.isVarNameSpace ns = startsVarId c || startsVarSym c - | OccName.isDataConNameSpace ns = startsConId c || startsConSym c || str == "[]" - | otherwise = startsConId c || startsConSym c || - startsVarSym c || str == "[]" || str == "->" - -- allow type operators like "+" +okOcc ns str + | OccName.isVarNameSpace ns = okVarOcc str + | OccName.isDataConNameSpace ns = okConOcc str + | otherwise = okTcOcc str + +-- | Is this an acceptable variable name? +okVarOcc :: String -> Bool +okVarOcc str@(c:_) + | startsVarId c + = okVarIdOcc str + | startsVarSym c + = okVarSymOcc str +okVarOcc _ = False + +-- | Is this an acceptable alphanumeric variable name, assuming it starts +-- with an acceptable letter? +okVarIdOcc :: String -> Bool +okVarIdOcc str = all okIdChar str && + not (str `Set.member` reservedIds) + +-- | Is this an acceptable symbolic variable name, assuming it starts +-- with an acceptable character? +okVarSymOcc :: String -> Bool +okVarSymOcc str = all okSymChar str && + not (str `Set.member` reservedOps) && + not (isDashes str) + +-- | Is this an acceptable constructor name? +okConOcc :: String -> Bool +okConOcc str@(c:_) + | startsConId c + = okConIdOcc str + | startsConSym c + = okConSymOcc str + | str == "[]" + = True +okConOcc _ = False + +-- | Is this an acceptable alphanumeric constructor name, assuming it +-- starts with an acceptable letter? +okConIdOcc :: String -> Bool +okConIdOcc str = all okIdChar str || + is_tuple_name1 str + where + -- check for tuple name, starting at the beginning + is_tuple_name1 ('(' : rest) = is_tuple_name2 rest + is_tuple_name1 _ = False + + -- check for tuple tail + is_tuple_name2 ")" = True + is_tuple_name2 (',' : rest) = is_tuple_name2 rest + is_tuple_name2 (ws : rest) + | isSpace ws = is_tuple_name2 rest + is_tuple_name2 _ = False + +-- | Is this an acceptable symbolic constructor name, assuming it +-- starts with an acceptable character? +okConSymOcc :: String -> Bool +okConSymOcc ":" = True +okConSymOcc str = all okSymChar str && + not (str `Set.member` reservedOps) + +-- | Is this an acceptable type name? +okTcOcc :: String -> Bool +okTcOcc "[]" = True +okTcOcc "->" = True +okTcOcc "~" = True +okTcOcc str@(c:_) + | startsConId c + = okConIdOcc str + | startsConSym c + = okConSymOcc str + | startsVarSym c + = okVarSymOcc str +okTcOcc _ = False + +-- | Is this character acceptable in an identifier (after the first letter)? +-- See alexGetByte in Lexer.x +okIdChar :: Char -> Bool +okIdChar c = case generalCategory c of + UppercaseLetter -> True + LowercaseLetter -> True + OtherLetter -> True + TitlecaseLetter -> True + DecimalNumber -> True + OtherNumber -> True + _ -> c == '\'' || c == '_' || c == '#' + +-- | Is this character acceptable in a symbol (after the first char)? +-- See alexGetByte in Lexer.x +okSymChar :: Char -> Bool +okSymChar c + | c `elem` specialSymbols + = False + | c `elem` "_\"'" + = False + | otherwise + = case generalCategory c of + ConnectorPunctuation -> True + DashPunctuation -> True + OtherPunctuation -> True + MathSymbol -> True + CurrencySymbol -> True + ModifierSymbol -> True + OtherSymbol -> True + _ -> False + +-- | All reserved identifiers. Taken from section 2.4 of the 2010 Report. +reservedIds :: Set.Set String +reservedIds = Set.fromList [ "case", "class", "data", "default", "deriving" + , "do", "else", "foreign", "if", "import", "in" + , "infix", "infixl", "infixr", "instance", "let" + , "module", "newtype", "of", "then", "type", "where" + , "_" ] + +-- | All punctuation that cannot appear in symbols. See $special in Lexer.x. +specialSymbols :: [Char] +specialSymbols = "(),;[]`{}" + +-- | All reserved operators. Taken from section 2.4 of the 2010 Report. +reservedOps :: Set.Set String +reservedOps = Set.fromList [ "..", ":", "::", "=", "\\", "|", "<-", "->" + , "@", "~", "=>" ] + +-- | Does this string contain only dashes and has at least 2 of them? +isDashes :: String -> Bool +isDashes ('-' : '-' : rest) = all (== '-') rest +isDashes _ = False -- Determine the name space of a name in a type -- diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index db41e19..1c17829 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -338,4 +338,4 @@ test('T9738', normal, compile, ['-v0']) test('T9081', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) -test('T7484', expect_broken(7484), compile_fail, ['-v0']) +test('T7484', normal, compile_fail, ['-v0']) From git at git.haskell.org Tue Nov 4 16:36:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 16:36:43 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #1476 in th/T1476 (6af3b8e) Message-ID: <20141104163643.765CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/6af3b8ed2a413c1bbf8abce36df11040d528415c/ghc >--------------------------------------------------------------- commit 6af3b8ed2a413c1bbf8abce36df11040d528415c Author: Richard Eisenberg Date: Mon Nov 3 20:26:14 2014 -0500 Test #1476 in th/T1476 >--------------------------------------------------------------- 6af3b8ed2a413c1bbf8abce36df11040d528415c testsuite/tests/th/T1476.hs | 10 ++++++++++ testsuite/tests/th/all.T | 1 + 2 files changed, 11 insertions(+) diff --git a/testsuite/tests/th/T1476.hs b/testsuite/tests/th/T1476.hs new file mode 100644 index 0000000..4beebae --- /dev/null +++ b/testsuite/tests/th/T1476.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T1476 where + +import Language.Haskell.TH + +foo $( return $ VarP $ mkName "x" ) = x +bar $( [p| x |] ) = x + +baz = [| \ $( return $ VarP $ mkName "x" ) -> x |] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 1c17829..72c1a75 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -339,3 +339,4 @@ test('T9081', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) +test('T1476', expect_broken(1476), compile, ['-v0']) From git at git.haskell.org Tue Nov 4 16:36:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 16:36:46 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #1476 by making splice patterns work. (b7a4f49) Message-ID: <20141104163646.1CB673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/b7a4f49615f528913ef38dc377471e1603c5acd4/ghc >--------------------------------------------------------------- commit b7a4f49615f528913ef38dc377471e1603c5acd4 Author: Richard Eisenberg Date: Tue Nov 4 11:34:53 2014 -0500 Fix #1476 by making splice patterns work. Unfortunately, splice patterns in brackets still do not work because we don't run splices in brackets. Without running a pattern splice, we can't know what variables it binds, so we're stuck. This is still a substantial improvement, and it may be the best we can do. Still must document new behavior. >--------------------------------------------------------------- b7a4f49615f528913ef38dc377471e1603c5acd4 compiler/rename/RnPat.lhs | 10 ++++++---- compiler/rename/RnSplice.lhs | 38 +++++++++++++++++++++++++++++++------- compiler/rename/RnSplice.lhs-boot | 3 ++- 3 files changed, 39 insertions(+), 12 deletions(-) diff --git a/compiler/rename/RnPat.lhs b/compiler/rename/RnPat.lhs index aa41361..634c99c 100644 --- a/compiler/rename/RnPat.lhs +++ b/compiler/rename/RnPat.lhs @@ -440,10 +440,12 @@ rnPatAndThen mk (TuplePat pats boxed _) ; pats' <- rnLPatsAndThen mk pats ; return (TuplePat pats' boxed []) } -rnPatAndThen _ (SplicePat splice) - = do { -- XXX How to deal with free variables? - ; (pat, _) <- liftCps $ rnSplicePat splice - ; return pat } +rnPatAndThen mk (SplicePat splice) + = do { eith <- liftCpsFV $ rnSplicePat splice + ; case eith of -- See Note [rnSplicePat] in RnSplice + Left not_yet_renamed -> rnPatAndThen mk not_yet_renamed + Right already_renamed -> return already_renamed } + rnPatAndThen mk (QuasiQuotePat qq) = do { pat <- liftCps $ runQuasiQuotePat qq -- Wrap the result of the quasi-quoter in parens so that we don't diff --git a/compiler/rename/RnSplice.lhs b/compiler/rename/RnSplice.lhs index 59c8c62..8918e39 100644 --- a/compiler/rename/RnSplice.lhs +++ b/compiler/rename/RnSplice.lhs @@ -206,13 +206,40 @@ rnSpliceType splice k } ; return (unLoc hs_ty3, fvs) } ----------------------- -rnSplicePat :: HsSplice RdrName -> RnM (Pat Name, FreeVars) +\end{code} + +Note [rnSplicePat] +~~~~~~~~~~~~~~~~~~ +Renaming a pattern splice is a bit tricky, because we need the variables +bound in the pattern to be in scope in the RHS of the pattern. This scope +management is effectively done by using continuation-passing style in +RnPat, through the CpsRn monad. We don't wish to be in that monad here +(it would create import cycles and generally conflict with renaming other +splices), so we really want to return a (Pat RdrName) -- the result of +running the splice -- which can then be further renamed in RnPat, in +the CpsRn monad. + +The problem is that if we're renaming a splice within a bracket, we +*don't* want to run the splice now. We really do just want to rename +it to an HsSplice Name. Of course, then we can't know what variables +are bound within the splice, so pattern splices within brackets aren't +all that useful. + +In any case, when we're done in rnSplicePat, we'll either have a +Pat RdrName (the result of running a top-level splice) or a Pat Name +(the renamed nested splice). Thus, the awkward return type of +rnSplicePat. + +\begin{code} + +-- | Rename a splice pattern. See Note [rnSplicePat] +rnSplicePat :: HsSplice RdrName -> RnM ( Either (Pat RdrName) (Pat Name) + , FreeVars) rnSplicePat splice = rnSpliceGen False run_pat_splice pend_pat_splice splice where pend_pat_splice rn_splice@(HsSplice n e) - = (PendingRnPatSplice (PendSplice n e), SplicePat rn_splice) + = (PendingRnPatSplice (PendSplice n e), Right $ SplicePat rn_splice) run_pat_splice (HsSplice _ expr') = do { expr <- getHooked runRnSpliceHook return >>= ($ expr') @@ -227,10 +254,7 @@ rnSplicePat splice ; pat <- runMetaP zonked_q_expr ; showSplice "pattern" expr (ppr pat) - ; (pat', fvs) <- checkNoErrs $ - rnPat ThPatSplice pat $ \pat' -> return (pat', emptyFVs) - - ; return (unLoc pat', fvs) } + ; return (Left $ unLoc pat, emptyFVs) } ---------------------- rnSpliceDecl :: SpliceDecl RdrName -> RnM (SpliceDecl Name, FreeVars) diff --git a/compiler/rename/RnSplice.lhs-boot b/compiler/rename/RnSplice.lhs-boot index 45a2a10..de6da77 100644 --- a/compiler/rename/RnSplice.lhs-boot +++ b/compiler/rename/RnSplice.lhs-boot @@ -11,6 +11,7 @@ import Kind rnSpliceType :: HsSplice RdrName -> PostTc Name Kind -> RnM (HsType Name, FreeVars) -rnSplicePat :: HsSplice RdrName -> RnM (Pat Name, FreeVars) +rnSplicePat :: HsSplice RdrName -> RnM ( Either (Pat RdrName) (Pat Name) + , FreeVars ) rnSpliceDecl :: SpliceDecl RdrName -> RnM (SpliceDecl Name, FreeVars) \end{code} From git at git.haskell.org Tue Nov 4 16:36:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 16:36:48 +0000 (UTC) Subject: [commit: ghc] wip/rae's head updated: Fix #1476 by making splice patterns work. (b7a4f49) Message-ID: <20141104163648.A1E563A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/rae' now includes: 063ae61 Update expected profiling output for scc001 1c0b736 Link to oneShot from the User's Guide 6dd218e Make Foldable's foldr1 and foldl1 defaults lazier ce03c4a Further relax T1969?s max_bytes range 49fde3b Add `Alternative` wrapper to Data.Monoid 4dbe433 Minor Haddock markup improvement to Data.Monoid 828d724 Refactor Haddock comments in Data.Bits c7fa0ba Fix lost Haddock annotation for `class Monad m` 1d6124d Tidy up pretty-printing of SrcLoc and SrcSpan 27ba070 Improve pretty-printing of type variables c8c18a1 Some refactoring around endPass and debug dumping 7251798 Simplify the generation of superclass constraints in tcInstDecl2 d153e40 Add the unfolding and inline-pragma for DFuns in DsBinds, not TcInstDcls bdbb595 White space only fd46acf Fix reduceTyFamApp_maybe 33dcb81 Simplify the API for tcInstTyVars, and make it more consistent with other similar functions 9c81db4 Rename setRole_maybe to downgradeRole_maybe 54f9188 Refactor skolemising, and newClsInst 2bfc653 Refactor the treatment of lexically-scoped type variables for instance declarations e11e1b8 Get the Untouchables level right in simplifyInfer a6e7654 Normalise the type of an inferred let-binding e840d85 Typechecker debug tracing only c64539c When reporting the context of given constraints, stop when you find one that binds a variable mentioned in the wanted 15131ec Only report "could not deduce s~t from ..." for givens that include equalities f054822 Don't filter out allegedly-irrelevant bindings with -dppr-debug 84d9ef0 Minor refactoring (no change in functionality) c1a85b3 Define ctEvLoc and ctEvCoercion, and use them 4723a0e Test Trac #9211 f861fc6 Test Trac #9708 6d1ac96 Improve error message for a handwritten Typeable instance dbbffb7 Test Trac #9747 abfbdd1 Add comments explaining ProbOneShot c639560 Test Trac #9739 7c79633 Fix the superclass-cycle detection code (Trac #9739) 66658ee Comments only 5479ae0 Testsuite error message changes 652a5ef Add flattening-notes f02c915 Make this test a bit simpler ce9d6f2 Compiler performance is much worse in for loopy givens 5770029 Simon's major commit to re-engineer the constraint solver 2f0d841 Updates to safePkg01 under Edward's guidance 09aac7d Test Trac #9081 fe178b2 Test Trac #9750 1408c8d Remove redundant "Minimal complete definition"-comments 64dc4d1 Re-center perf-numbers for T5631 6a1c05f A little refactoring of HsSplice and friends ba147ac Test #9066 in th/T9066 c00f6e7 Fix #9066. fa05d66 Test #9209 in th/T9209 20e1bb1 Fix #9209, by reporting an error instead of panicking on bad splices. 89b963f Test #7484 in th/T7484 eed503f Fix #7484, checking for good binder names in Convert. 6af3b8e Test #1476 in th/T1476 b7a4f49 Fix #1476 by making splice patterns work. From git at git.haskell.org Tue Nov 4 17:33:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 17:33:50 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #1476 in th/T1476 (5c0a560) Message-ID: <20141104173350.1C99A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/5c0a560888662fb7ca3c220509a6ccaff897c480/ghc >--------------------------------------------------------------- commit 5c0a560888662fb7ca3c220509a6ccaff897c480 Author: Richard Eisenberg Date: Mon Nov 3 20:26:14 2014 -0500 Test #1476 in th/T1476 >--------------------------------------------------------------- 5c0a560888662fb7ca3c220509a6ccaff897c480 testsuite/tests/th/T1476.hs | 10 ++++++++++ testsuite/tests/th/all.T | 1 + 2 files changed, 11 insertions(+) diff --git a/testsuite/tests/th/T1476.hs b/testsuite/tests/th/T1476.hs new file mode 100644 index 0000000..4beebae --- /dev/null +++ b/testsuite/tests/th/T1476.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T1476 where + +import Language.Haskell.TH + +foo $( return $ VarP $ mkName "x" ) = x +bar $( [p| x |] ) = x + +baz = [| \ $( return $ VarP $ mkName "x" ) -> x |] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 1c17829..72c1a75 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -339,3 +339,4 @@ test('T9081', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) +test('T1476', expect_broken(1476), compile, ['-v0']) From git at git.haskell.org Tue Nov 4 17:33:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 17:33:52 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #7484, checking for good binder names in Convert. (16f0ea8) Message-ID: <20141104173352.B00A93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/16f0ea81efa4386f821095b7d293a2dad614c1c6/ghc >--------------------------------------------------------------- commit 16f0ea81efa4386f821095b7d293a2dad614c1c6 Author: Richard Eisenberg Date: Mon Nov 3 15:34:53 2014 -0500 Fix #7484, checking for good binder names in Convert. This includes a somewhat pedantic check against the code in Lexer.x to make sure that TH accepts the same set of names that the lexer does. Doing this unearthed a latent bug dealing with unicode identifiers in OccName. >--------------------------------------------------------------- 16f0ea81efa4386f821095b7d293a2dad614c1c6 compiler/basicTypes/OccName.lhs | 11 +-- compiler/hsSyn/Convert.lhs | 145 ++++++++++++++++++++++++++++++++++++++-- testsuite/tests/th/all.T | 2 +- 3 files changed, 146 insertions(+), 12 deletions(-) diff --git a/compiler/basicTypes/OccName.lhs b/compiler/basicTypes/OccName.lhs index 0010ad3..182e563 100644 --- a/compiler/basicTypes/OccName.lhs +++ b/compiler/basicTypes/OccName.lhs @@ -903,13 +903,16 @@ isLexVarSym fs -- Infix identifiers e.g. "+" ------------- startsVarSym, startsVarId, startsConSym, startsConId :: Char -> Bool -startsVarSym c = isSymbolASCII c || (ord c > 0x7f && isSymbol c) -- Infix Ids +startsVarSym c = startsVarSymASCII c || (ord c > 0x7f && isSymbol c) -- Infix Ids startsConSym c = c == ':' -- Infix data constructors -startsVarId c = isLower c || c == '_' -- Ordinary Ids +startsVarId c = c == '_' || case generalCategory c of -- Ordinary Ids + LowercaseLetter -> True + OtherLetter -> True -- See #1103 + _ -> False startsConId c = isUpper c || c == '(' -- Ordinary type constructors and data constructors -isSymbolASCII :: Char -> Bool -isSymbolASCII c = c `elem` "!#$%&*+./<=>?@\\^|~-" +startsVarSymASCII :: Char -> Bool +startsVarSymASCII c = c `elem` "!#$%&*+./<=>?@\\^|~-" isVarSymChar :: Char -> Bool isVarSymChar c = c == ':' || startsVarSym c diff --git a/compiler/hsSyn/Convert.lhs b/compiler/hsSyn/Convert.lhs index 6cff928..cf26cf7 100644 --- a/compiler/hsSyn/Convert.lhs +++ b/compiler/hsSyn/Convert.lhs @@ -45,6 +45,8 @@ import Data.Maybe( catMaybes ) import Language.Haskell.TH as TH hiding (sigP) import Language.Haskell.TH.Syntax as TH import GHC.Exts +import Data.Char +import qualified Data.Set as Set ------------------------------------------------------------------- -- The external interface @@ -1109,13 +1111,142 @@ cvtName ctxt_ns (TH.Name occ flavour) occ_str = TH.occString occ okOcc :: OccName.NameSpace -> String -> Bool -okOcc _ [] = False -okOcc ns str@(c:_) - | OccName.isVarNameSpace ns = startsVarId c || startsVarSym c - | OccName.isDataConNameSpace ns = startsConId c || startsConSym c || str == "[]" - | otherwise = startsConId c || startsConSym c || - startsVarSym c || str == "[]" || str == "->" - -- allow type operators like "+" +okOcc ns str + | OccName.isVarNameSpace ns = okVarOcc str + | OccName.isDataConNameSpace ns = okConOcc str + | otherwise = okTcOcc str + +-- | Is this an acceptable variable name? +okVarOcc :: String -> Bool +okVarOcc str@(c:_) + | startsVarId c + = okVarIdOcc str + | startsVarSym c + = okVarSymOcc str +okVarOcc _ = False + +-- | Is this an acceptable alphanumeric variable name, assuming it starts +-- with an acceptable letter? +okVarIdOcc :: String -> Bool +okVarIdOcc str = okIdOcc str && + not (str `Set.member` reservedIds) + +-- | Is this an acceptable symbolic variable name, assuming it starts +-- with an acceptable character? +okVarSymOcc :: String -> Bool +okVarSymOcc str = all okSymChar str && + not (str `Set.member` reservedOps) && + not (isDashes str) + +-- | Is this an acceptable constructor name? +okConOcc :: String -> Bool +okConOcc str@(c:_) + | startsConId c + = okConIdOcc str + | startsConSym c + = okConSymOcc str + | str == "[]" + = True +okConOcc _ = False + +-- | Is this an acceptable alphanumeric constructor name, assuming it +-- starts with an acceptable letter? +okConIdOcc :: String -> Bool +okConIdOcc str = okIdOcc str || + is_tuple_name1 str + where + -- check for tuple name, starting at the beginning + is_tuple_name1 ('(' : rest) = is_tuple_name2 rest + is_tuple_name1 _ = False + + -- check for tuple tail + is_tuple_name2 ")" = True + is_tuple_name2 (',' : rest) = is_tuple_name2 rest + is_tuple_name2 (ws : rest) + | isSpace ws = is_tuple_name2 rest + is_tuple_name2 _ = False + +-- | Is this an acceptable symbolic constructor name, assuming it +-- starts with an acceptable character? +okConSymOcc :: String -> Bool +okConSymOcc ":" = True +okConSymOcc str = all okSymChar str && + not (str `Set.member` reservedOps) + +-- | Is this an acceptable type name? +okTcOcc :: String -> Bool +okTcOcc "[]" = True +okTcOcc "->" = True +okTcOcc "~" = True +okTcOcc str@(c:_) + | startsConId c + = okConIdOcc str + | startsConSym c + = okConSymOcc str + | startsVarSym c + = okVarSymOcc str +okTcOcc _ = False + +-- | Is this string an acceptable id, possibly with a suffix of hashes, +-- but not worrying about case or clashing with reserved words? +okIdOcc :: String -> Bool +okIdOcc str + = let hashes = dropWhile okIdChar str in + all (== '#') hashes -- -XMagicHash allows a suffix of hashes + -- of course, `all` says "True" to an empty list + +-- | Is this character acceptable in an identifier (after the first letter)? +-- See alexGetByte in Lexer.x +okIdChar :: Char -> Bool +okIdChar c = case generalCategory c of + UppercaseLetter -> True + LowercaseLetter -> True + OtherLetter -> True + TitlecaseLetter -> True + DecimalNumber -> True + OtherNumber -> True + _ -> c == '\'' || c == '_' + +-- | Is this character acceptable in a symbol (after the first char)? +-- See alexGetByte in Lexer.x +okSymChar :: Char -> Bool +okSymChar c + | c `elem` specialSymbols + = False + | c `elem` "_\"'" + = False + | otherwise + = case generalCategory c of + ConnectorPunctuation -> True + DashPunctuation -> True + OtherPunctuation -> True + MathSymbol -> True + CurrencySymbol -> True + ModifierSymbol -> True + OtherSymbol -> True + _ -> False + +-- | All reserved identifiers. Taken from section 2.4 of the 2010 Report. +reservedIds :: Set.Set String +reservedIds = Set.fromList [ "case", "class", "data", "default", "deriving" + , "do", "else", "foreign", "if", "import", "in" + , "infix", "infixl", "infixr", "instance", "let" + , "module", "newtype", "of", "then", "type", "where" + , "_" ] + +-- | All punctuation that cannot appear in symbols. See $special in Lexer.x. +specialSymbols :: [Char] +specialSymbols = "(),;[]`{}" + +-- | All reserved operators. Taken from section 2.4 of the 2010 Report. +reservedOps :: Set.Set String +reservedOps = Set.fromList [ "..", ":", "::", "=", "\\", "|", "<-", "->" + , "@", "~", "=>" ] + +-- | Does this string contain only dashes and has at least 2 of them? +isDashes :: String -> Bool +isDashes ('-' : '-' : rest) = all (== '-') rest +isDashes _ = False -- Determine the name space of a name in a type -- diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index db41e19..1c17829 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -338,4 +338,4 @@ test('T9738', normal, compile, ['-v0']) test('T9081', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) -test('T7484', expect_broken(7484), compile_fail, ['-v0']) +test('T7484', normal, compile_fail, ['-v0']) From git at git.haskell.org Tue Nov 4 17:33:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 17:33:55 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #1476 by making splice patterns work. (a470acf) Message-ID: <20141104173355.5251C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/a470acf697d66ee3f9552a495c9ca510d2b6518d/ghc >--------------------------------------------------------------- commit a470acf697d66ee3f9552a495c9ca510d2b6518d Author: Richard Eisenberg Date: Tue Nov 4 11:34:53 2014 -0500 Fix #1476 by making splice patterns work. Unfortunately, splice patterns in brackets still do not work because we don't run splices in brackets. Without running a pattern splice, we can't know what variables it binds, so we're stuck. This is still a substantial improvement, and it may be the best we can do. Still must document new behavior. >--------------------------------------------------------------- a470acf697d66ee3f9552a495c9ca510d2b6518d compiler/rename/RnPat.lhs | 10 ++++++---- compiler/rename/RnSplice.lhs | 38 +++++++++++++++++++++++++++++++------- compiler/rename/RnSplice.lhs-boot | 3 ++- 3 files changed, 39 insertions(+), 12 deletions(-) diff --git a/compiler/rename/RnPat.lhs b/compiler/rename/RnPat.lhs index aa41361..634c99c 100644 --- a/compiler/rename/RnPat.lhs +++ b/compiler/rename/RnPat.lhs @@ -440,10 +440,12 @@ rnPatAndThen mk (TuplePat pats boxed _) ; pats' <- rnLPatsAndThen mk pats ; return (TuplePat pats' boxed []) } -rnPatAndThen _ (SplicePat splice) - = do { -- XXX How to deal with free variables? - ; (pat, _) <- liftCps $ rnSplicePat splice - ; return pat } +rnPatAndThen mk (SplicePat splice) + = do { eith <- liftCpsFV $ rnSplicePat splice + ; case eith of -- See Note [rnSplicePat] in RnSplice + Left not_yet_renamed -> rnPatAndThen mk not_yet_renamed + Right already_renamed -> return already_renamed } + rnPatAndThen mk (QuasiQuotePat qq) = do { pat <- liftCps $ runQuasiQuotePat qq -- Wrap the result of the quasi-quoter in parens so that we don't diff --git a/compiler/rename/RnSplice.lhs b/compiler/rename/RnSplice.lhs index 59c8c62..8918e39 100644 --- a/compiler/rename/RnSplice.lhs +++ b/compiler/rename/RnSplice.lhs @@ -206,13 +206,40 @@ rnSpliceType splice k } ; return (unLoc hs_ty3, fvs) } ----------------------- -rnSplicePat :: HsSplice RdrName -> RnM (Pat Name, FreeVars) +\end{code} + +Note [rnSplicePat] +~~~~~~~~~~~~~~~~~~ +Renaming a pattern splice is a bit tricky, because we need the variables +bound in the pattern to be in scope in the RHS of the pattern. This scope +management is effectively done by using continuation-passing style in +RnPat, through the CpsRn monad. We don't wish to be in that monad here +(it would create import cycles and generally conflict with renaming other +splices), so we really want to return a (Pat RdrName) -- the result of +running the splice -- which can then be further renamed in RnPat, in +the CpsRn monad. + +The problem is that if we're renaming a splice within a bracket, we +*don't* want to run the splice now. We really do just want to rename +it to an HsSplice Name. Of course, then we can't know what variables +are bound within the splice, so pattern splices within brackets aren't +all that useful. + +In any case, when we're done in rnSplicePat, we'll either have a +Pat RdrName (the result of running a top-level splice) or a Pat Name +(the renamed nested splice). Thus, the awkward return type of +rnSplicePat. + +\begin{code} + +-- | Rename a splice pattern. See Note [rnSplicePat] +rnSplicePat :: HsSplice RdrName -> RnM ( Either (Pat RdrName) (Pat Name) + , FreeVars) rnSplicePat splice = rnSpliceGen False run_pat_splice pend_pat_splice splice where pend_pat_splice rn_splice@(HsSplice n e) - = (PendingRnPatSplice (PendSplice n e), SplicePat rn_splice) + = (PendingRnPatSplice (PendSplice n e), Right $ SplicePat rn_splice) run_pat_splice (HsSplice _ expr') = do { expr <- getHooked runRnSpliceHook return >>= ($ expr') @@ -227,10 +254,7 @@ rnSplicePat splice ; pat <- runMetaP zonked_q_expr ; showSplice "pattern" expr (ppr pat) - ; (pat', fvs) <- checkNoErrs $ - rnPat ThPatSplice pat $ \pat' -> return (pat', emptyFVs) - - ; return (unLoc pat', fvs) } + ; return (Left $ unLoc pat, emptyFVs) } ---------------------- rnSpliceDecl :: SpliceDecl RdrName -> RnM (SpliceDecl Name, FreeVars) diff --git a/compiler/rename/RnSplice.lhs-boot b/compiler/rename/RnSplice.lhs-boot index 45a2a10..de6da77 100644 --- a/compiler/rename/RnSplice.lhs-boot +++ b/compiler/rename/RnSplice.lhs-boot @@ -11,6 +11,7 @@ import Kind rnSpliceType :: HsSplice RdrName -> PostTc Name Kind -> RnM (HsType Name, FreeVars) -rnSplicePat :: HsSplice RdrName -> RnM (Pat Name, FreeVars) +rnSplicePat :: HsSplice RdrName -> RnM ( Either (Pat RdrName) (Pat Name) + , FreeVars ) rnSpliceDecl :: SpliceDecl RdrName -> RnM (SpliceDecl Name, FreeVars) \end{code} From git at git.haskell.org Tue Nov 4 17:33:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 17:33:57 +0000 (UTC) Subject: [commit: ghc] wip/rae: Release notes for #1476, #7484. (361004a) Message-ID: <20141104173357.D9E133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/361004a6ebac8e7cc5a0bf90d840ffef3997e66a/ghc >--------------------------------------------------------------- commit 361004a6ebac8e7cc5a0bf90d840ffef3997e66a Author: Richard Eisenberg Date: Tue Nov 4 12:20:25 2014 -0500 Release notes for #1476, #7484. >--------------------------------------------------------------- 361004a6ebac8e7cc5a0bf90d840ffef3997e66a docs/users_guide/7.10.1-notes.xml | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 95f581b..b197406 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -120,6 +120,10 @@ + Pattern splices now work. + + + reifyInstances now treats unbound type variables as univerally quantified, allowing lookup of, say, the instance for Eq [a]. @@ -138,6 +142,13 @@ Various features unsupported in quotations were previously silently ignored. These now cause errors. + + + Template Haskell is now more pedantic about splicing in + bogus variable names, like "a ". If you + use bogus names in your Template Haskell code, this may break + your program. + From git at git.haskell.org Tue Nov 4 18:58:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 18:58:33 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #1476 in th/T1476 (e76a653) Message-ID: <20141104185833.3DCDD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/e76a653a66c1fa01d7d46185d2d7855cd29a4da7/ghc >--------------------------------------------------------------- commit e76a653a66c1fa01d7d46185d2d7855cd29a4da7 Author: Richard Eisenberg Date: Mon Nov 3 20:26:14 2014 -0500 Test #1476 in th/T1476 >--------------------------------------------------------------- e76a653a66c1fa01d7d46185d2d7855cd29a4da7 testsuite/tests/th/T1476.hs | 10 ++++++++++ testsuite/tests/th/all.T | 1 + 2 files changed, 11 insertions(+) diff --git a/testsuite/tests/th/T1476.hs b/testsuite/tests/th/T1476.hs new file mode 100644 index 0000000..7e3a192 --- /dev/null +++ b/testsuite/tests/th/T1476.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T1476 where + +import Language.Haskell.TH + +foo $( return $ VarP $ mkName "x" ) = x +bar $( [p| x |] ) = x + +baz = [| \ $( return $ VarP $ mkName "x" ) -> $(dyn "x") |] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 1c17829..72c1a75 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -339,3 +339,4 @@ test('T9081', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) +test('T1476', expect_broken(1476), compile, ['-v0']) From git at git.haskell.org Tue Nov 4 18:58:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 18:58:36 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test that nested pattern splices don't scope (#1476). (87af99c) Message-ID: <20141104185836.74CFD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/87af99c6f96b0950145e2a37da6406bd93cbbcef/ghc >--------------------------------------------------------------- commit 87af99c6f96b0950145e2a37da6406bd93cbbcef Author: Richard Eisenberg Date: Tue Nov 4 13:06:56 2014 -0500 Test that nested pattern splices don't scope (#1476). Test case: th/T1476b. >--------------------------------------------------------------- 87af99c6f96b0950145e2a37da6406bd93cbbcef testsuite/tests/th/T1476b.hs | 10 ++++++++++ testsuite/tests/th/T1476b.stderr | 5 +++++ testsuite/tests/th/all.T | 1 + 3 files changed, 16 insertions(+) diff --git a/testsuite/tests/th/T1476b.hs b/testsuite/tests/th/T1476b.hs new file mode 100644 index 0000000..918a397 --- /dev/null +++ b/testsuite/tests/th/T1476b.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T1476b where + +import Language.Haskell.TH + +baz = [| \ $( return $ VarP $ mkName "x" ) -> x |] + +-- If this test starts passing, nested pattern splices scope correctly. +-- Good for you! Now, update the TH manual accordingly. diff --git a/testsuite/tests/th/T1476b.stderr b/testsuite/tests/th/T1476b.stderr new file mode 100644 index 0000000..65b0814 --- /dev/null +++ b/testsuite/tests/th/T1476b.stderr @@ -0,0 +1,5 @@ + +T1476b.hs:7:47: + Not in scope: ?x? + In the Template Haskell quotation + [| \ $(return $ VarP $ mkName "x") -> x |] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 72c1a75..0e0d500 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -340,3 +340,4 @@ test('T9066', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) test('T1476', expect_broken(1476), compile, ['-v0']) +test('T1476b', normal, compile_fail, ['-v0']) From git at git.haskell.org Tue Nov 4 18:58:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 18:58:39 +0000 (UTC) Subject: [commit: ghc] wip/rae: Release notes for #1476, #7484. (757fabc) Message-ID: <20141104185839.1EB463A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/757fabcfd0868c7d7f0e19f53dd8533a5aa8988c/ghc >--------------------------------------------------------------- commit 757fabcfd0868c7d7f0e19f53dd8533a5aa8988c Author: Richard Eisenberg Date: Tue Nov 4 12:20:25 2014 -0500 Release notes for #1476, #7484. >--------------------------------------------------------------- 757fabcfd0868c7d7f0e19f53dd8533a5aa8988c docs/users_guide/7.10.1-notes.xml | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 95f581b..fc88c5d 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -120,6 +120,10 @@ + Pattern splices now work. + + + reifyInstances now treats unbound type variables as univerally quantified, allowing lookup of, say, the instance for Eq [a]. @@ -138,6 +142,13 @@ Various features unsupported in quotations were previously silently ignored. These now cause errors. + + + Template Haskell is now more pedantic about splicing in + bogus variable names, like those containing whitespace. If you + use bogus names in your Template Haskell code, this may break + your program. + From git at git.haskell.org Tue Nov 4 18:58:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 18:58:41 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #1476 by making splice patterns work. (eb257c3) Message-ID: <20141104185841.A69913A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/eb257c32abd254c8f28f3b127746dadcfee91461/ghc >--------------------------------------------------------------- commit eb257c32abd254c8f28f3b127746dadcfee91461 Author: Richard Eisenberg Date: Tue Nov 4 11:34:53 2014 -0500 Fix #1476 by making splice patterns work. Unfortunately, splice patterns in brackets still do not work because we don't run splices in brackets. Without running a pattern splice, we can't know what variables it binds, so we're stuck. This is still a substantial improvement, and it may be the best we can do. Still must document new behavior. >--------------------------------------------------------------- eb257c32abd254c8f28f3b127746dadcfee91461 compiler/rename/RnPat.lhs | 10 ++++++---- compiler/rename/RnSplice.lhs | 38 +++++++++++++++++++++++++++++++------- compiler/rename/RnSplice.lhs-boot | 3 ++- testsuite/tests/th/all.T | 2 +- 4 files changed, 40 insertions(+), 13 deletions(-) diff --git a/compiler/rename/RnPat.lhs b/compiler/rename/RnPat.lhs index aa41361..634c99c 100644 --- a/compiler/rename/RnPat.lhs +++ b/compiler/rename/RnPat.lhs @@ -440,10 +440,12 @@ rnPatAndThen mk (TuplePat pats boxed _) ; pats' <- rnLPatsAndThen mk pats ; return (TuplePat pats' boxed []) } -rnPatAndThen _ (SplicePat splice) - = do { -- XXX How to deal with free variables? - ; (pat, _) <- liftCps $ rnSplicePat splice - ; return pat } +rnPatAndThen mk (SplicePat splice) + = do { eith <- liftCpsFV $ rnSplicePat splice + ; case eith of -- See Note [rnSplicePat] in RnSplice + Left not_yet_renamed -> rnPatAndThen mk not_yet_renamed + Right already_renamed -> return already_renamed } + rnPatAndThen mk (QuasiQuotePat qq) = do { pat <- liftCps $ runQuasiQuotePat qq -- Wrap the result of the quasi-quoter in parens so that we don't diff --git a/compiler/rename/RnSplice.lhs b/compiler/rename/RnSplice.lhs index 59c8c62..8918e39 100644 --- a/compiler/rename/RnSplice.lhs +++ b/compiler/rename/RnSplice.lhs @@ -206,13 +206,40 @@ rnSpliceType splice k } ; return (unLoc hs_ty3, fvs) } ----------------------- -rnSplicePat :: HsSplice RdrName -> RnM (Pat Name, FreeVars) +\end{code} + +Note [rnSplicePat] +~~~~~~~~~~~~~~~~~~ +Renaming a pattern splice is a bit tricky, because we need the variables +bound in the pattern to be in scope in the RHS of the pattern. This scope +management is effectively done by using continuation-passing style in +RnPat, through the CpsRn monad. We don't wish to be in that monad here +(it would create import cycles and generally conflict with renaming other +splices), so we really want to return a (Pat RdrName) -- the result of +running the splice -- which can then be further renamed in RnPat, in +the CpsRn monad. + +The problem is that if we're renaming a splice within a bracket, we +*don't* want to run the splice now. We really do just want to rename +it to an HsSplice Name. Of course, then we can't know what variables +are bound within the splice, so pattern splices within brackets aren't +all that useful. + +In any case, when we're done in rnSplicePat, we'll either have a +Pat RdrName (the result of running a top-level splice) or a Pat Name +(the renamed nested splice). Thus, the awkward return type of +rnSplicePat. + +\begin{code} + +-- | Rename a splice pattern. See Note [rnSplicePat] +rnSplicePat :: HsSplice RdrName -> RnM ( Either (Pat RdrName) (Pat Name) + , FreeVars) rnSplicePat splice = rnSpliceGen False run_pat_splice pend_pat_splice splice where pend_pat_splice rn_splice@(HsSplice n e) - = (PendingRnPatSplice (PendSplice n e), SplicePat rn_splice) + = (PendingRnPatSplice (PendSplice n e), Right $ SplicePat rn_splice) run_pat_splice (HsSplice _ expr') = do { expr <- getHooked runRnSpliceHook return >>= ($ expr') @@ -227,10 +254,7 @@ rnSplicePat splice ; pat <- runMetaP zonked_q_expr ; showSplice "pattern" expr (ppr pat) - ; (pat', fvs) <- checkNoErrs $ - rnPat ThPatSplice pat $ \pat' -> return (pat', emptyFVs) - - ; return (unLoc pat', fvs) } + ; return (Left $ unLoc pat, emptyFVs) } ---------------------- rnSpliceDecl :: SpliceDecl RdrName -> RnM (SpliceDecl Name, FreeVars) diff --git a/compiler/rename/RnSplice.lhs-boot b/compiler/rename/RnSplice.lhs-boot index 45a2a10..de6da77 100644 --- a/compiler/rename/RnSplice.lhs-boot +++ b/compiler/rename/RnSplice.lhs-boot @@ -11,6 +11,7 @@ import Kind rnSpliceType :: HsSplice RdrName -> PostTc Name Kind -> RnM (HsType Name, FreeVars) -rnSplicePat :: HsSplice RdrName -> RnM (Pat Name, FreeVars) +rnSplicePat :: HsSplice RdrName -> RnM ( Either (Pat RdrName) (Pat Name) + , FreeVars ) rnSpliceDecl :: SpliceDecl RdrName -> RnM (SpliceDecl Name, FreeVars) \end{code} diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 0e0d500..9c6dc12 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -339,5 +339,5 @@ test('T9081', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) -test('T1476', expect_broken(1476), compile, ['-v0']) +test('T1476', normal, compile, ['-v0']) test('T1476b', normal, compile_fail, ['-v0']) From git at git.haskell.org Tue Nov 4 18:58:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 18:58:44 +0000 (UTC) Subject: [commit: ghc] wip/rae: Remove unboxed Int# fields from NameFlavour (#9527) (8fdf085) Message-ID: <20141104185844.470003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/8fdf08515a788ad011c4460dab15f1e194715b63/ghc >--------------------------------------------------------------- commit 8fdf08515a788ad011c4460dab15f1e194715b63 Author: Richard Eisenberg Date: Tue Nov 4 13:03:48 2014 -0500 Remove unboxed Int# fields from NameFlavour (#9527) >--------------------------------------------------------------- 8fdf08515a788ad011c4460dab15f1e194715b63 .../template-haskell/Language/Haskell/TH/PprLib.hs | 6 +- .../template-haskell/Language/Haskell/TH/Syntax.hs | 107 +++------------------ 2 files changed, 18 insertions(+), 95 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8fdf08515a788ad011c4460dab15f1e194715b63 From git at git.haskell.org Tue Nov 4 18:58:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 18:58:46 +0000 (UTC) Subject: [commit: ghc] wip/rae: Derive Generic for TH types (#9527) (804fd18) Message-ID: <20141104185846.F21133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/804fd1808e865761b4be7aa27f0b561ecf231e16/ghc >--------------------------------------------------------------- commit 804fd1808e865761b4be7aa27f0b561ecf231e16 Author: Richard Eisenberg Date: Tue Nov 4 13:21:57 2014 -0500 Derive Generic for TH types (#9527) >--------------------------------------------------------------- 804fd1808e865761b4be7aa27f0b561ecf231e16 .../template-haskell/Language/Haskell/TH/Syntax.hs | 83 +++++++++++----------- 1 file changed, 42 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 804fd1808e865761b4be7aa27f0b561ecf231e16 From git at git.haskell.org Tue Nov 4 18:58:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 18:58:49 +0000 (UTC) Subject: [commit: ghc] wip/rae: Untabify template-haskell. (6cc1f46) Message-ID: <20141104185849.972E33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/6cc1f465cdb308a7d27a13b12f8573a677c15139/ghc >--------------------------------------------------------------- commit 6cc1f465cdb308a7d27a13b12f8573a677c15139 Author: Richard Eisenberg Date: Tue Nov 4 13:43:17 2014 -0500 Untabify template-haskell. >--------------------------------------------------------------- 6cc1f465cdb308a7d27a13b12f8573a677c15139 libraries/template-haskell/Language/Haskell/TH.hs | 8 +-- .../template-haskell/Language/Haskell/TH/Lib.hs | 2 +- .../template-haskell/Language/Haskell/TH/Ppr.hs | 24 ++++---- .../template-haskell/Language/Haskell/TH/PprLib.hs | 66 +++++++++++----------- .../template-haskell/Language/Haskell/TH/Quote.hs | 2 +- 5 files changed, 51 insertions(+), 51 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6cc1f465cdb308a7d27a13b12f8573a677c15139 From git at git.haskell.org Tue Nov 4 18:58:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 18:58:52 +0000 (UTC) Subject: [commit: ghc] wip/rae: Remove unused import from TH/PprLib (fe4d1ba) Message-ID: <20141104185852.397AF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/fe4d1bab9b12e4b56c7a7bcdee87749718676c87/ghc >--------------------------------------------------------------- commit fe4d1bab9b12e4b56c7a7bcdee87749718676c87 Author: Richard Eisenberg Date: Tue Nov 4 13:45:19 2014 -0500 Remove unused import from TH/PprLib >--------------------------------------------------------------- fe4d1bab9b12e4b56c7a7bcdee87749718676c87 libraries/template-haskell/Language/Haskell/TH/PprLib.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/PprLib.hs b/libraries/template-haskell/Language/Haskell/TH/PprLib.hs index af386d2..a6b923c 100644 --- a/libraries/template-haskell/Language/Haskell/TH/PprLib.hs +++ b/libraries/template-haskell/Language/Haskell/TH/PprLib.hs @@ -41,7 +41,6 @@ import qualified Text.PrettyPrint as HPJ import Control.Monad (liftM, liftM2, ap) import Language.Haskell.TH.Lib.Map ( Map ) import qualified Language.Haskell.TH.Lib.Map as Map ( lookup, insert, empty ) -import GHC.Base (Int(..)) infixl 6 <> infixl 6 <+> From git at git.haskell.org Tue Nov 4 20:33:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 20:33:19 +0000 (UTC) Subject: [commit: ghc] wip/T5462: Merge branch 'master' into wip/T5462 (d43b9bd) Message-ID: <20141104203319.AF08C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T5462 Link : http://ghc.haskell.org/trac/ghc/changeset/d43b9bd62f54c0d64d29c506f2dd43395bb42760/ghc >--------------------------------------------------------------- commit d43b9bd62f54c0d64d29c506f2dd43395bb42760 Merge: 7a4cdef 3567207 Author: Jose Pedro Magalhaes Date: Fri Oct 3 14:22:32 2014 +0100 Merge branch 'master' into wip/T5462 >--------------------------------------------------------------- Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d43b9bd62f54c0d64d29c506f2dd43395bb42760 From git at git.haskell.org Tue Nov 4 20:33:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 20:33:24 +0000 (UTC) Subject: [commit: ghc] wip/T5462: Merge branch 'master' into wip/T5462 (a7f1bb9) Message-ID: <20141104203324.1776E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T5462 Link : http://ghc.haskell.org/trac/ghc/changeset/a7f1bb90beb44a0bb665f74629137ef5721c07bb/ghc >--------------------------------------------------------------- commit a7f1bb90beb44a0bb665f74629137ef5721c07bb Merge: d43b9bd 1408c8d Author: Jose Pedro Magalhaes Date: Tue Nov 4 17:24:50 2014 +0000 Merge branch 'master' into wip/T5462 >--------------------------------------------------------------- Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a7f1bb90beb44a0bb665f74629137ef5721c07bb From git at git.haskell.org Tue Nov 4 20:33:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Nov 2014 20:33:27 +0000 (UTC) Subject: [commit: ghc] wip/T5462's head updated: Merge branch 'master' into wip/T5462 (a7f1bb9) Message-ID: <20141104203327.7E3673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T5462' now includes: ee15686 Fixup nofib submodule to cope with e5cca4ab246ca2 e97234d bugfix: EventCapsetID should be EventThreadID aeb9c93 Document that -dynamic is needed for loading compiled code into GHCi 7371d7e Revert "rts: add Emacs 'Local Variables' to every .c file" 23bb904 Add emacs indentation/line-length settings 5d16c4d Update hsc2hs submodule 8d04eb2 Fix bogus comment 04ded40 Comments about the let/app invariant 1c10b4f Don't use newSysLocal etc for Coercible 864bed7 Update Win32 submodule to avoid potential -Werror failure 488e95b Make foldr2 a bit more strict 4e1dfc3 Make scanr a good producer and consumer d41dd03 Make mapAccumL a good consumer 7893210 Fusion rule for "foldr k z (x:build g)" 96a4062 Make filterM a good consumer 93b8d0f Simplify mergeSATInfo by using zipWith bcbb045 First stab at making ./validate less verbose 15f661c update cabal submodule to fix build failure on Solaris f3b5e16 rts/includes: Fix up .dir-locals.el 3a549ba [ci skip] compiler: Kill last remaining tabs in CallArity ca3089d [ci skip] Kill tabs in md5.h 53a2d46 [ci skip] Kill unused count_bytes script 2a88568 Use dropWhileEndLE p instead of reverse . dropWhile p . reverse 084d241 Basic Python 3 support for testsuite driver (Trac #9184) 644c76a Use LinkerInternals.h for exitLinker. b23ba2a Place static closures in their own section. 3b5a840 BC-breaking changes to C-- CLOSURE syntax. 178eb90 Properly generate info tables for static closures in C--. 3567207 Rename _closure to _static_closure, apply naming consistently. d6d5c12 Revert "Use dropWhileEndLE p instead of reverse . dropWhile p . reverse" 9bf5228 Use dropWhileEndLE p instead of reverse . dropWhile p . reverse eb191ab rts/PrimOps.cmm: follow '_static_closure' update eb35339 Really fix dropWhileEndLE commit 2b59c7a arclint: Don't complain about tabs unless it's inside the diff. 582217f Comments only (instances for Proxy are lazy) d43b9bd Merge branch 'master' into wip/T5462 e4a597f Revert "Basic Python 3 support for testsuite driver (Trac #9184)" 4977efc Restore spaces instead of tabs, caused by revert of Python 3 2fc0c6c Check for staticclosures section in Windows linker. e8dac6d Fix typo in section name: no leading period. 2a8ea47 ghc.mk: fix list for dll-split on GHCi-less builds 3549c95 Implement `MIN_VERSION_GLASGOW_HASKELL()` macro cb0a503 rts: unrust 'libbfd' debug symbols parser 6a36636 testsuite: fix tcrun036 build against Prelude/Main 'traverse' clash a1b5391 testsuite: fix T5751 build failure (AMP) b30b185 testsuite: fix T1735_Help/State.hs build failure (AMP) 6ecf19c testsuite: fix seward-space-leak build aganst Prelude/Main 'traverse' clash 48089cc Use correct precedence when printing contexts with class operators 85aba49 Merge branch 'master' of http://git.haskell.org/ghc 3c5648a Fix a typo in an error message 460eebe Remove RAWCPP_FLAGS b3e5a7b Delete __GLASGOW_HASKELL__ ifdefs for stage0 < 7.6. 2ee2527 Remove unused hashName declaration adcb9db Add support for LINE pragma in template-haskell 1ec9113 Fix configure check for 9439 bug 1f92420 configure in base: add msys to windows check 9ebbdf3 Clean up and remove todo. 205b103 Fix closing parenthesis d45693a Make scanl fuse; add scanl' bdb0c43 Code size micro-optimizations in the X86 backend ffde9d2 testsuite: T5486 requires integer-gmp internals e87135c Bump haddock.base perf numbers 6f2eca1 Use Data.Map.mergeWithKey 21dff57 Initial commit of the Backpack manual [skip ci] 21389bc Update some out-of-date things in Backpack implementation doc [skip ci] d14d3f9 Make Data.List.takeWhile fuse: fix #9132 eb6b04c Update T4801 perf numbers 0ed9a27 Preemptive performance number updates 5300099 Make the linker more robust to errors 267ad95 Ignore exe files in base (from tests) 39666ae Update haddock submodule with lazy IO fix. d3f56ec Rewrite section 1 of the Backpack manual. [skip ci] 674c631 Name worker threads using pthread_setname_np 97b7593 rts: don't crash on 'hs_init(NULL, NULL)' in debug rts ad4a713 Remove a few redundant `.hs-boot` files 1032554 Fallback to `ctypes.cdll` if `ctypes.windll` unavailable 034b203 Extend windows detection in testsuite to recognize MSYS target 1942fd6 Refactor to avoid need for `Unicode.hs-boot` a36991b Fix build on some platforms c375de0 Update `time` submodule to address linker issue 05f962d Compiler performance benchmark for #9675 23da971 Adjust T9675 baseline numbers based on ghc-speed d9db81f seqDmdType needs to seq the DmdEnv as well 3575109 Update more performance numbers due to stricter seqDmdType f3ae936 T9675: Allow Much wider range of values f0af3d8 Actually put in new perf number for T4801 8376027 Fix comment typos: lll -> ll, THe -> The 4b69d96 Add a configure test for pthread_setname_np cde3a77 Make Data.List.Inits fast 7e73595 Make tails a good producer (#9670) d786781 Declare official GitHub home of libraries/deepseq a477e81 Avoid printing uniques in specialization rules 0e2bd03 Update T6056 output 1c35f9f rts: fix unused parameter warning 612f3d1 Implement optimized NCG `MO_Ctz W64` op for i386 (#9340) 7369d25 Remove obsolete Data.OldTypeable (#9639) ce23745 Generalise `Control.Monad.{foldM,foldM_}` to `Foldable` (#9586) abfbb0d Remove redundant explicit `Prelude` imports d576fc3 Python 3 support, second attempt (Trac #9184) b5930f8 Refactor module imports in base 5b9fe33 Indentation and non-semantic changes only. 4d90b53 Sync up `containers` submodule to latest `master`-tip 07da36b Revert "Fix typo in section name: no leading period." 0202b7c Revert "Check for staticclosures section in Windows linker." 89a8d81 Revert "Rename _closure to _static_closure, apply naming consistently." 126b0c4 Revert "Properly generate info tables for static closures in C--." a3860fc Revert "BC-breaking changes to C-- CLOSURE syntax." d5d6fb3 Revert "Place static closures in their own section." 47c4c91 Update Haddock submodule 07a99c1 Revert "rts/PrimOps.cmm: follow '_static_closure' update" f681c32 Test #9692 in th/T9692 2cd80ba Clarify location of Note. Comment change only. e319d6d Reify data family instances correctly. 710bc8d Update primitive, vector, and dph submodules. 27f7552 Make Applicative-Monad fixes for tests. 3687089 Updated testsuite/.gitignore to cover artifacts on Windows. 2cc2065 Use objdump instead of nm to derive constants on OpenBSD 9f29e03 ghc-prim: Use population count appropriate for platform d4fd168 Update to Unicode version 7.0 a5f4fb6 Remove extra period 3157127 Improve isDigit, isSpace, etc. ef2d027 Make findIndices fuse 1e269bf Make Data.List.concatMap fuse better 6825558 Add doctest examples for Data.Functor. 5211673 Fix typo in -XConstraintKinds docs 9c464f8 Add doctest examples for Data.Bool. c819958 Add release note about Unicode 7.0 69f6361 Fixes the ARM build 972ba12 Enabled warn on tabs by default (fixes #9230) 4faeecb [skip ci] rts: Detabify RtsMessages.c aa8d23d [skip ci] rts: Detabify RaiseAsync.h bb04867 [skip ci] rts: Detabify Capability.h 99edc35 [skip ci] rts: Detabify CheckUnload.c 6aa6ca8 [skip ci] rts: Detabify Profiling.c 570b339 [skip ci] rts: Detabify Threads.c 21eaaa1 [skip ci] rts: Detabify sm/Evac.c 9167d0e [skip ci] rts: Detabify sm/Scav.c 5bb8f14 [skip ci] rts: Detabify Stats.c 2dc21b9 [skip ci] rts: Detabify Schedule.h 1d12df3 [skip ci] rts: Detabify LdvProfile.h 3d0e695 [skip ci] rts: Detabify Proftimer.c 68c45b6 [skip ci] rts: Detabify Exception.cmm a7ab7d3 [skip ci] rts: Detabify HeapStackCheck.cmm 6811e53 [skip ci] rts: Detabify Capability.c beb5c2e [skip ci] rts: Detabify RaiseAsync.c e13478f [skip ci] rts: Detabify sm/GC.c faa3339 [skip ci] rts: Detabify sm/Sanity.c bc1609a [skip ci] rts: Detabify sm/Compact.c c8173d5 [skip ci] rts: Detabify sm/Compact.h 5106e20 [skip ci] rts: Detabify RetainerProfile.c 03c3e9a [skip ci] rts: Detabify ProfHeap.c 6abb34c [skip ci] rts: Detabify Schedule.c 9bfe602 rts: Detabify Interpreter.c df5c11a base: Mark WCsubst.c as generated for Phabricator 45cbe85 Flush stdout in T9692 aa641e5 Add forgotten import to T9692 a11f71e Fix a rare parallel GC bug 427925d More updates to Backpack manual [skip ci] 5bb73d7 Check in up-to-date PDF copies of Backpack docs. [skip ci] aa47995 Implementation of hsig (module signatures), per #9252 1addef8 Fix windows build failure. 73c7ea7 fix a typo in comments: normaliseFfiType 0855b24 Pass in CXX to libffi's configure script. 7b59db2 `M-x delete-trailing-whitespace` & `M-x untabify` a3312c3 testsuite: Fix outdated output for T5979/safePkg01 0a290ca Add new `Data.Bifunctor` module (re #9682) 9e2cb00 Optimise atomicModifyIORef' implementation (#8345) 0e1f0f7 Un-wire `Integer` type (re #9714) 0013613 Deactivate T3064 `max_bytes_used`-check 49b05d6 Improve performance of isSuffixOf (#9676) 1874501 Typo in comment aa2ceba Normalise package key hash to make tests less fragile. 63918e6 Add n-ary version of `two_normalisers` to testsuite lib 3d6422b testlib: Get rid of two_normalisers 98ed815 Make iterateFB inlineable 75979f3 base: Refactor/clean-up *List modules 5f69c8e Reorder GHC.List; fix performance regressions f109085 Update Haddock submodule for collapsible section support 64d0a19 Really fix fft2 regression. #9740 208a0c2 Fixed unused variable warning on mingw32/i686 in rts/Linker.c f9ca529 hsc2hs: Update submodule 322810e Convert GHCi sources from .lhs to .hs 257cbec Fix #9236 Error on read from closed handle 5ce1266 Use snwprintf instead of swprintf in rts/Linker.c. acb3295 Avoid setting -Werror=unused-but-set-variable on Windows. 45175e1 Extra CRs are now filtered out from the source file for :list. f10b67a Updated stale ghcpkg05.stderr-mingw32. 3d27f69 Do not use a relative path for echo in tests/ghci/prog013. c211f8e Add __GLASGOW_HASKELL_TH__=YES/NO to CPP definitions 93c776a Added mingw32-specific expected stdout files for tests/driver/sigof{01,02,03} 9de5240 Comments only c6d4ae6 Fix test driver python3 compatibility issues 578bc00 Add notes on change to hGetContents semantics 995ea1c Fixed missing trailing newline bug in pretty printer 1907e81 Updated testsuite/.gitignore to exclude some test artifacts on Windows. cbb20ab Drop deprecated `OverlappingInstances` from base 919e930 Fix comment typos 8ef4cf1 Add doctest examples for Data.Char bd6c6f6 Update Haddock submodule 54addb1 Clean-up `Data.Fixed` f12be5b Add changelog entry for recent Unicode 7.0 update d3a7126 Update doctest example style in `Data.Bool` 4667fb5 Split off stat (benchmark) test failures into a separate section in the test runner summary. 322c139 remove old .NET related code e466ea7 Remove legacy support for -optdef flags d15d704 Fix build via Haddock submodule update. 6534686 Fix comment about dropWhileEndLE e5ba360 rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) a47ff8b Fixed T5435_dyn_asm on Windows. The test code was not in sync with the expected output. f688f03 Test #9262 in th/T9262, and update other tests. 2cc593d Bring unbound tyvars into scope during reifyInstances. b174288 Test #8953 in th/T8953 9fd19f9 Always use KindedTV when reifying. (#8953) 593e8b9 Annotate reified poly-kinded tycons when necessary. (#8953) c3ecf06 Annotate poly-kinded type patterns in instance reification. 99882ba Testsuite wibbles from fixing #8953 862772b Test #9084 in th/T9084. 03d61cc Fix #9084 by calling notHandled when unknown bits are enountered. 17265c0 Fix testsuite output from #9084. 752b5e2 Test #9738 in th/T9738 209baea Fix #9738, by handling {-# ANN ... #-} in DsMeta. 18a4a5d Update release notes for #9262 #8953 #9084. 96c22d9 Tweak the error message for pattern synonym methods, since they are disallowed both in class and instance declarations c001bde Put one-Shot info in the interface c271e32 Add GHC.Prim.oneShot 072259c Use oneShot in the definition of foldl etc. 063ae61 Update expected profiling output for scc001 1c0b736 Link to oneShot from the User's Guide 6dd218e Make Foldable's foldr1 and foldl1 defaults lazier ce03c4a Further relax T1969?s max_bytes range 49fde3b Add `Alternative` wrapper to Data.Monoid 4dbe433 Minor Haddock markup improvement to Data.Monoid 828d724 Refactor Haddock comments in Data.Bits c7fa0ba Fix lost Haddock annotation for `class Monad m` 1d6124d Tidy up pretty-printing of SrcLoc and SrcSpan 27ba070 Improve pretty-printing of type variables c8c18a1 Some refactoring around endPass and debug dumping 7251798 Simplify the generation of superclass constraints in tcInstDecl2 d153e40 Add the unfolding and inline-pragma for DFuns in DsBinds, not TcInstDcls bdbb595 White space only fd46acf Fix reduceTyFamApp_maybe 33dcb81 Simplify the API for tcInstTyVars, and make it more consistent with other similar functions 9c81db4 Rename setRole_maybe to downgradeRole_maybe 54f9188 Refactor skolemising, and newClsInst 2bfc653 Refactor the treatment of lexically-scoped type variables for instance declarations e11e1b8 Get the Untouchables level right in simplifyInfer a6e7654 Normalise the type of an inferred let-binding e840d85 Typechecker debug tracing only c64539c When reporting the context of given constraints, stop when you find one that binds a variable mentioned in the wanted 15131ec Only report "could not deduce s~t from ..." for givens that include equalities f054822 Don't filter out allegedly-irrelevant bindings with -dppr-debug 84d9ef0 Minor refactoring (no change in functionality) c1a85b3 Define ctEvLoc and ctEvCoercion, and use them 4723a0e Test Trac #9211 f861fc6 Test Trac #9708 6d1ac96 Improve error message for a handwritten Typeable instance dbbffb7 Test Trac #9747 abfbdd1 Add comments explaining ProbOneShot c639560 Test Trac #9739 7c79633 Fix the superclass-cycle detection code (Trac #9739) 66658ee Comments only 5479ae0 Testsuite error message changes 652a5ef Add flattening-notes f02c915 Make this test a bit simpler ce9d6f2 Compiler performance is much worse in for loopy givens 5770029 Simon's major commit to re-engineer the constraint solver 2f0d841 Updates to safePkg01 under Edward's guidance 09aac7d Test Trac #9081 fe178b2 Test Trac #9750 1408c8d Remove redundant "Minimal complete definition"-comments a7f1bb9 Merge branch 'master' into wip/T5462 From simonpj at microsoft.com Tue Nov 4 21:05:53 2014 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 4 Nov 2014 21:05:53 +0000 Subject: [commit: ghc] wip/rae: Fix #1476 by making splice patterns work. (eb257c3) In-Reply-To: <20141104185841.A69913A300@ghc.haskell.org> References: <20141104185841.A69913A300@ghc.haskell.org> Message-ID: <618BE556AADD624C9C918AA5D5911BEF3F39233D@DB3PRD3001MB020.064d.mgd.msft.net> | Unfortunately, splice patterns in brackets still do not work | because we don't run splices in brackets. Without running a pattern | splice, we can't know what variables it binds, so we're stuck. Not just "don't" but "can't"!! This isn't a compiler deficiency: the code is not there to run! Simon From git at git.haskell.org Wed Nov 5 07:41:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 07:41:28 +0000 (UTC) Subject: [commit: ghc] master: Temporarily disable T3064 (see #9771) (77f8221) Message-ID: <20141105074128.C8E673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/77f8221103a98b38384edd8c2caae6cc2c4ffd72/ghc >--------------------------------------------------------------- commit 77f8221103a98b38384edd8c2caae6cc2c4ffd72 Author: Herbert Valerio Riedel Date: Wed Nov 5 08:39:10 2014 +0100 Temporarily disable T3064 (see #9771) This disables T3064 temporarily as it puts a strain on buildbots during validation exhausting all available memory. >--------------------------------------------------------------- 77f8221103a98b38384edd8c2caae6cc2c4ffd72 testsuite/tests/perf/compiler/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 58c3891..f79f173 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -293,7 +293,8 @@ test('T3064', # # (amd64/Linux) (19/09/2014): 18744992, unknown # # (amd64/Linux) 2014-10-13: 13251728, Stricter seqDmdType - only_ways(['normal']) + ### TEMPORARILY DISABLED due to https://ghc.haskell.org/trac/ghc/ticket/9771 + only_ways([]) # only_ways(['normal']) ], compile, ['']) From git at git.haskell.org Wed Nov 5 08:09:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 08:09:53 +0000 (UTC) Subject: [commit: ghc] master: Remove redundant contexts from Foldable methods (0a8e899) Message-ID: <20141105080953.D45BA3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0a8e8995fd31dd46fa9bdbc7f65984b51c8c13dc/ghc >--------------------------------------------------------------- commit 0a8e8995fd31dd46fa9bdbc7f65984b51c8c13dc Author: David Feuer Date: Wed Nov 5 08:42:59 2014 +0100 Remove redundant contexts from Foldable methods New `Foldable` methods accidentally had `Foldable` contexts, which led to type roles being assigned incorrectly and preventing GND from deriving `Foldable` instances. Removing those fixes #9761. Moreover, this patch takes advantage of this fix by deriving `Foldable` (and `Eq`) for `UniqFM`. Differential Revision: https://phabricator.haskell.org/D425 >--------------------------------------------------------------- 0a8e8995fd31dd46fa9bdbc7f65984b51c8c13dc compiler/utils/UniqFM.lhs | 20 +++----------------- libraries/base/Data/Foldable.hs | 14 +++++++------- testsuite/tests/ghci/scripts/ghci025.stdout | 3 +-- 3 files changed, 11 insertions(+), 26 deletions(-) diff --git a/compiler/utils/UniqFM.lhs b/compiler/utils/UniqFM.lhs index 3ea97e4..f0f9035 100644 --- a/compiler/utils/UniqFM.lhs +++ b/compiler/utils/UniqFM.lhs @@ -72,7 +72,6 @@ import Outputable import Compiler.Hoopl hiding (Unique) -import Data.Function (on) import qualified Data.IntMap as M import qualified Data.IntSet as S import qualified Data.Foldable as Foldable @@ -212,22 +211,9 @@ instance Monoid (UniqFM a) where %************************************************************************ \begin{code} -newtype UniqFM ele = UFM { unUFM :: M.IntMap ele } - deriving (Typeable,Data, Traversable.Traversable, Functor) - -instance Eq ele => Eq (UniqFM ele) where - (==) = (==) `on` unUFM - -{- -instance Functor UniqFM where - fmap f = fmap f . unUFM - -instance Traversable.Traversable UniqFM where - traverse f = Traversable.traverse f . unUFM --} - -instance Foldable.Foldable UniqFM where - foldMap f = Foldable.foldMap f . unUFM +newtype UniqFM ele = UFM (M.IntMap ele) + deriving (Data, Eq, Foldable.Foldable, Functor, Traversable.Traversable, + Typeable) emptyUFM = UFM M.empty isNullUFM (UFM m) = M.null m diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs index 9d26f86..4167b92 100644 --- a/libraries/base/Data/Foldable.hs +++ b/libraries/base/Data/Foldable.hs @@ -145,28 +145,28 @@ class Foldable t where Just x -> f x y) -- | List of elements of a structure. - toList :: Foldable t => t a -> [a] + toList :: t a -> [a] {-# INLINE toList #-} toList t = build (\ c n -> foldr c n t) -- | Test whether the structure is empty. - null :: Foldable t => t a -> Bool + null :: t a -> Bool null = foldr (\_ _ -> False) True -- | Returns the size/length of a finite structure as an 'Int'. - length :: Foldable t => t a -> Int + length :: t a -> Int length = foldl' (\c _ -> c+1) 0 -- | Does the element occur in the structure? - elem :: (Foldable t, Eq a) => a -> t a -> Bool + elem :: Eq a => a -> t a -> Bool elem = any . (==) -- | The largest element of a non-empty structure. - maximum :: (Foldable t, Ord a) => t a -> a + maximum :: Ord a => t a -> a maximum = foldr1 max -- | The least element of a non-empty structure. - minimum :: (Foldable t, Ord a) => t a -> a + minimum :: Ord a => t a -> a minimum = foldr1 min -- | The 'sum' function computes the sum of the numbers of a structure. @@ -175,7 +175,7 @@ class Foldable t where -- | The 'product' function computes the product of the numbers of a -- structure. - product :: (Foldable t, Num a) => t a -> a + product :: Num a => t a -> a product = getProduct . foldMap Product -- instances for Prelude types diff --git a/testsuite/tests/ghci/scripts/ghci025.stdout b/testsuite/tests/ghci/scripts/ghci025.stdout index 4d21c5f..e5654b3 100644 --- a/testsuite/tests/ghci/scripts/ghci025.stdout +++ b/testsuite/tests/ghci/scripts/ghci025.stdout @@ -53,8 +53,7 @@ class Eq a where (GHC.Classes./=) :: a -> a -> GHC.Types.Bool -- imported via Prelude, T Prelude.length :: - Data.Foldable.Foldable t => - forall a. Data.Foldable.Foldable t => t a -> GHC.Types.Int + Data.Foldable.Foldable t => forall a. t a -> GHC.Types.Int -- imported via T data T.Integer = integer-gmp-0.5.1.0:GHC.Integer.Type.S# GHC.Prim.Int# From git at git.haskell.org Wed Nov 5 11:21:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 11:21:17 +0000 (UTC) Subject: [commit: ghc] master: Clean-up Haddock in `Data.Functor` (ac0915b) Message-ID: <20141105112117.E12ED3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ac0915b8f2b6f5b73f0a6d7e7739abe96c3745eb/ghc >--------------------------------------------------------------- commit ac0915b8f2b6f5b73f0a6d7e7739abe96c3745eb Author: Herbert Valerio Riedel Date: Wed Nov 5 12:19:13 2014 +0100 Clean-up Haddock in `Data.Functor` This mostly cleans up irregularities introduced in 68255588f89462e542c502f6f92548712808032f (re D352) as well as making sure Haddock is able to resolve all references. >--------------------------------------------------------------- ac0915b8f2b6f5b73f0a6d7e7739abe96c3745eb libraries/base/Data/Functor.hs | 131 ++++++++++++++++++++--------------------- 1 file changed, 65 insertions(+), 66 deletions(-) diff --git a/libraries/base/Data/Functor.hs b/libraries/base/Data/Functor.hs index 0896947..64692cf 100644 --- a/libraries/base/Data/Functor.hs +++ b/libraries/base/Data/Functor.hs @@ -12,7 +12,7 @@ -- Portability : portable -- -- Functors: uniform action over a parameterized type, generalizing the --- 'map' function on lists. +-- 'Data.List.map' function on lists. module Data.Functor ( @@ -33,33 +33,32 @@ infixl 4 <$> -- | An infix synonym for 'fmap'. -- --- ==== __Examples__ +-- ==== __Examples__ -- --- Convert from a 'Maybe' 'Int' to a 'Maybe' 'String' using 'show': +-- Convert from a @'Maybe' 'Int'@ to a @'Maybe' 'String'@ using 'show': -- --- >>> show <$> Nothing --- Nothing --- >>> show <$> Just 3 --- Just "3" +-- >>> show <$> Nothing +-- Nothing +-- >>> show <$> Just 3 +-- Just "3" -- --- Convert from an 'Either' 'Int' 'Int' to an 'Either' 'Int' --- 'String' using 'show': +-- Convert from an @'Either' 'Int' 'Int'@ to an @'Either' 'Int'@ +-- 'String' using 'show': -- --- >>> show <$> Left 17 --- Left 17 --- >>> show <$> Right 17 --- Right "17" +-- >>> show <$> Left 17 +-- Left 17 +-- >>> show <$> Right 17 +-- Right "17" -- --- Double each element of a list: +-- Double each element of a list: -- --- >>> (*2) <$> [1,2,3] --- [2,4,6] +-- >>> (*2) <$> [1,2,3] +-- [2,4,6] -- --- Apply 'even' to the second element of a pair: --- --- >>> even <$> (2,2) --- (2,True) +-- Apply 'even' to the second element of a pair: -- +-- >>> even <$> (2,2) +-- (2,True) -- (<$>) :: Functor f => (a -> b) -> f a -> f b (<$>) = fmap @@ -68,77 +67,77 @@ infixl 4 $> -- | Flipped version of '<$'. -- --- /Since: 4.7.0.0/ +-- /Since: 4.7.0.0/ -- --- ==== __Examples__ +-- ==== __Examples__ -- --- Replace the contents of a 'Maybe' 'Int' with a constant 'String': +-- Replace the contents of a @'Maybe' 'Int'@ with a constant 'String': -- --- >>> Nothing $> "foo" --- Nothing --- >>> Just 90210 $> "foo" --- Just "foo" +-- >>> Nothing $> "foo" +-- Nothing +-- >>> Just 90210 $> "foo" +-- Just "foo" -- --- Replace the contents of an 'Either' 'Int' 'Int' with a constant --- 'String', resulting in an 'Either' 'Int' 'String': +-- Replace the contents of an @'Either' 'Int' 'Int'@ with a constant +-- 'String', resulting in an @'Either' 'Int' 'String'@: -- --- >>> Left 8675309 $> "foo" --- Left 8675309 --- >>> Right 8675309 $> "foo" --- Right "foo" +-- >>> Left 8675309 $> "foo" +-- Left 8675309 +-- >>> Right 8675309 $> "foo" +-- Right "foo" -- --- Replace each element of a list with a constant 'String': +-- Replace each element of a list with a constant 'String': -- --- >>> [1,2,3] $> "foo" --- ["foo","foo","foo"] +-- >>> [1,2,3] $> "foo" +-- ["foo","foo","foo"] -- --- Replace the second element of a pair with a constant 'String': +-- Replace the second element of a pair with a constant 'String': -- --- >>> (1,2) $> "foo" --- (1,"foo") +-- >>> (1,2) $> "foo" +-- (1,"foo") -- ($>) :: Functor f => f a -> b -> f b ($>) = flip (<$) -- | @'void' value@ discards or ignores the result of evaluation, such --- as the return value of an 'IO' action. +-- as the return value of an 'System.IO.IO' action. -- --- ==== __Examples__ +-- ==== __Examples__ -- --- Replace the contents of a 'Maybe' 'Int' with unit: +-- Replace the contents of a @'Maybe' 'Int'@ with unit: -- --- >>> void Nothing --- Nothing --- >>> void (Just 3) --- Just () +-- >>> void Nothing +-- Nothing +-- >>> void (Just 3) +-- Just () -- --- Replace the contents of an 'Either' 'Int' 'Int' with unit, --- resulting in an 'Either' 'Int' '()': +-- Replace the contents of an @'Either' 'Int' 'Int'@ with unit, +-- resulting in an @'Either' 'Int' '()'@: -- --- >>> void (Left 8675309) --- Left 8675309 --- >>> void (Right 8675309) --- Right () +-- >>> void (Left 8675309) +-- Left 8675309 +-- >>> void (Right 8675309) +-- Right () -- --- Replace every element of a list with unit: +-- Replace every element of a list with unit: -- --- >>> void [1,2,3] --- [(),(),()] +-- >>> void [1,2,3] +-- [(),(),()] -- --- Replace the second element of a pair with unit: +-- Replace the second element of a pair with unit: -- --- >>> void (1,2) --- (1,()) +-- >>> void (1,2) +-- (1,()) -- --- Discard the result of an 'IO' action: +-- Discard the result of an 'System.IO.IO' action: -- --- >>> mapM print [1,2] --- 1 --- 2 --- [(),()] --- >>> void $ mapM print [1,2] --- 1 --- 2 +-- >>> mapM print [1,2] +-- 1 +-- 2 +-- [(),()] +-- >>> void $ mapM print [1,2] +-- 1 +-- 2 -- void :: Functor f => f a -> f () void = fmap (const ()) From git at git.haskell.org Wed Nov 5 11:42:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 11:42:57 +0000 (UTC) Subject: [commit: ghc] master: Add `isSubsequenceOf` to Data.List (#9767) (40b1ee4) Message-ID: <20141105114257.56A063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/40b1ee4043fefdd19ff6614a63939002840c6d97/ghc >--------------------------------------------------------------- commit 40b1ee4043fefdd19ff6614a63939002840c6d97 Author: Alexander Berntsen Date: Wed Nov 5 12:32:06 2014 +0100 Add `isSubsequenceOf` to Data.List (#9767) Niklas Hamb?chen suggested that we add the dual of `subsequences`, isSubsequenceOf (like `isPrefixOf` to `inits` & `isSuffixOf` to `tails`). It was a simple and noncontroversial proposal which passed unanimously. For more details see the original proposal discussion at https://www.haskell.org/pipermail/libraries/2014-November/024063.html Differential Revision: https://phabricator.haskell.org/D435 Signed-off-by: Alexander Berntsen >--------------------------------------------------------------- 40b1ee4043fefdd19ff6614a63939002840c6d97 libraries/base/Data/List.hs | 24 ++++++++++++++++++++++++ libraries/base/changelog.md | 2 ++ 2 files changed, 26 insertions(+) diff --git a/libraries/base/Data/List.hs b/libraries/base/Data/List.hs index 193ebbc..4f99926 100644 --- a/libraries/base/Data/List.hs +++ b/libraries/base/Data/List.hs @@ -106,6 +106,7 @@ module Data.List , isPrefixOf , isSuffixOf , isInfixOf + , isSubsequenceOf -- * Searching lists @@ -214,3 +215,26 @@ import Data.OldList hiding ( all, and, any, concat, concatMap, elem, find, foldl, foldl1, foldl', foldr, foldr1, mapAccumL, mapAccumR, maximum, maximumBy, minimum, minimumBy, length, notElem, null, or, product, sum ) + +import GHC.Base ( Bool(..), Eq((==)), otherwise ) + +-- | The 'isSubsequenceOf' function takes two lists and returns 'True' if the +-- first list is a subsequence of the second list. +-- +-- @'isSubsequenceOf' x y@ is equivalent to @'elem' x ('subsequences' y)@. +-- +-- /Since: 4.8.0.0/ +-- +-- ==== __Examples__ +-- +-- >>> isSubsequenceOf "GHC" "The Glorious Haskell Compiler" +-- True +-- >>> isSubsequenceOf ['a','d'..'z'] ['a'..'z'] +-- True +-- >>> isSubsequenceOf [1..10] [10,9..0] +-- False +isSubsequenceOf :: (Eq a) => [a] -> [a] -> Bool +isSubsequenceOf [] _ = True +isSubsequenceOf _ [] = False +isSubsequenceOf a@(x:a') (y:b) | x == y = isSubsequenceOf a' b + | otherwise = isSubsequenceOf a b diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index c3e1fa7..86595d6 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -91,6 +91,8 @@ * Add `Alt`, an `Alternative` wrapper, to `Data.Monoid`. (#9759) + * Add `isSubsequenceOf` to `Data.List` (#9767) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 From git at git.haskell.org Wed Nov 5 13:07:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 13:07:08 +0000 (UTC) Subject: [commit: ghc] master: Fix typo in testsuite Makefile (32237f0) Message-ID: <20141105130708.3AC9C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/32237f0d9024b2e1ab7cc637a79584bb07a10268/ghc >--------------------------------------------------------------- commit 32237f0d9024b2e1ab7cc637a79584bb07a10268 Author: Herbert Valerio Riedel Date: Wed Nov 5 14:05:48 2014 +0100 Fix typo in testsuite Makefile This is introduced in aa4799534225e3fc6bbde0d5e5eeab8868cc3111 and would cause indeterministic testsuite failures in `sigof02dmt` >--------------------------------------------------------------- 32237f0d9024b2e1ab7cc637a79584bb07a10268 testsuite/tests/driver/sigof02/Makefile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/driver/sigof02/Makefile b/testsuite/tests/driver/sigof02/Makefile index b61fe61..9a64ec2 100644 --- a/testsuite/tests/driver/sigof02/Makefile +++ b/testsuite/tests/driver/sigof02/Makefile @@ -72,4 +72,4 @@ sigof02dmt: rm -rf tmp_sigof02dmt mkdir tmp_sigof02dmt # doesn't typecheck due to lack of alias - ! '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -outputdir tmp_sigof02dmt -fno-code -fwrite-interface --make Double.hs -o tmp_sigof02dm/Double + ! '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -outputdir tmp_sigof02dmt -fno-code -fwrite-interface --make Double.hs -o tmp_sigof02dmt/Double From git at git.haskell.org Wed Nov 5 13:39:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 13:39:53 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Pass two sets of evidence bindings to tcPatSynMatcher (ca2923f) Message-ID: <20141105133953.A3A5D3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/ca2923f88a5e910f4703fbc5a482d0098ba553fd/ghc >--------------------------------------------------------------- commit ca2923f88a5e910f4703fbc5a482d0098ba553fd Author: Dr. ERDI Gergo Date: Wed Nov 5 21:38:14 2014 +0800 Pass two sets of evidence bindings to tcPatSynMatcher >--------------------------------------------------------------- ca2923f88a5e910f4703fbc5a482d0098ba553fd compiler/typecheck/TcPatSyn.lhs | 49 +++++++++++++++++++++-------------------- 1 file changed, 25 insertions(+), 24 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index cd60f0a..905a66e 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -61,7 +61,7 @@ tcInferPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, mapM tcLookupId arg_names ; let named_taus = (name, pat_ty):map (\arg -> (getName arg, varType arg)) args - ; (qtvs, req_dicts, _mr_bites, ev_binds) <- simplifyInfer True False named_taus wanted + ; (qtvs, req_dicts, _mr_bites, req_ev_binds) <- simplifyInfer True False named_taus wanted ; (ex_vars, prov_dicts) <- tcCollectEx lpat' ; let univ_tvs = filter (not . (`elemVarSet` ex_vars)) qtvs @@ -71,18 +71,19 @@ tcInferPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; univ_tvs <- mapM zonkQuantifiedTyVar univ_tvs ; ex_tvs <- mapM zonkQuantifiedTyVar ex_tvs + ; prov_theta <- zonkTcThetaType prov_theta ; req_theta <- zonkTcThetaType req_theta + ; pat_ty <- zonkTcType pat_ty ; args <- mapM zonkId args ; let arg_w_wraps = zip args $ repeat idHsWrapper ; let theta = prov_theta ++ req_theta - ; (matcher_id, matcher_bind) <- tcPatSynMatcher lname lpat' arg_w_wraps - univ_tvs ex_tvs - ev_binds - prov_dicts req_dicts - prov_theta req_theta + ; (matcher_id, matcher_bind) <- tcPatSynMatcher lname lpat' + (univ_tvs, req_theta, req_ev_binds, req_dicts) + (ex_tvs, prov_theta, emptyTcEvBinds, prov_dicts) + arg_w_wraps pat_ty ; wrapper_id <- if isBidirectional dir then fmap Just $ mkPatSynWrapperId lname (map varType args) univ_tvs ex_tvs theta pat_ty @@ -113,7 +114,6 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, ppr (univ_tvs, req_theta) $$ ppr tau - ; prov_dicts <- newEvVars prov_theta ; req_dicts <- newEvVars req_theta ; let skol_info = SigSkol (FunSigCtxt name) (mkFunTys arg_tys pat_ty) @@ -122,7 +122,7 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, PrefixPatSyn names -> (map unLoc names, False) InfixPatSyn name1 name2 -> (map unLoc [name1, name2], True) - ; (ev_binds, (lpat', arg_w_wraps)) <- + ; (req_ev_binds, (lpat', arg_w_wraps)) <- checkConstraints skol_info univ_tvs req_dicts $ tcPat PatSyn lpat pat_ty $ do { ex_sigtvs <- mapM (\tv -> newSigTyVar (getName tv) (tyVarKind tv)) ex_tvs @@ -134,25 +134,24 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, ; coi <- unifyType (varType arg) arg_ty ; return (setVarType arg arg_ty, coToHsWrapper coi) }} - ; (ex_vars', prov_dicts') <- tcCollectEx lpat' - ; let ex_tvs' = varSetElems ex_vars' - prov_theta' = map evVarPred prov_dicts' + ; (ex_vars_rhs, prov_dicts_rhs) <- tcCollectEx lpat' + ; let ex_tvs_rhs = varSetElems ex_vars_rhs - ; (ev_binds', _) <- checkConstraints skol_info ex_tvs' prov_dicts' $ do + ; (prov_ev_binds, prov_dicts) <- checkConstraints skol_info ex_tvs_rhs prov_dicts_rhs $ do ctLoc <- getCtLoc PatSigOrigin - forM_ prov_theta $ \pred -> do + forM prov_theta $ \pred -> do + evar <- newEvVar pred let ctEv = CtWanted{ ctev_pred = pred - , ctev_evar = panic "ctev_evar" + , ctev_evar = evar , ctev_loc = ctLoc } emitFlat $ mkNonCanonical ctEv + return evar ; (matcher_id, matcher_bind) <- tcPatSynMatcher lname lpat' + (univ_tvs, req_theta, req_ev_binds, req_dicts) + (ex_tvs, prov_theta, prov_ev_binds, prov_dicts) arg_w_wraps - univ_tvs ex_tvs - ev_binds - prov_dicts req_dicts - prov_theta req_theta pat_ty ; wrapper_id <- if isBidirectional dir @@ -176,15 +175,16 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, \begin{code} tcPatSynMatcher :: Located Name -> LPat Id + -> ([TcTyVar], ThetaType, TcEvBinds, [EvVar]) + -> ([TcTyVar], ThetaType, TcEvBinds, [EvVar]) -> [(Var, HsWrapper)] - -> [TcTyVar] -> [TcTyVar] - -> TcEvBinds - -> [EvVar] -> [EvVar] - -> ThetaType -> ThetaType -> TcType -> TcM (Id, LHsBinds Id) -- See Note [Matchers and wrappers for pattern synonyms] in PatSyn -tcPatSynMatcher (L loc name) lpat arg_w_wraps univ_tvs ex_tvs ev_binds prov_dicts req_dicts prov_theta req_theta pat_ty +tcPatSynMatcher (L loc name) lpat + (univ_tvs, req_theta, req_ev_binds, req_dicts) + (ex_tvs, prov_theta, prov_ev_binds, prov_dicts) + arg_w_wraps pat_ty = do { res_tv <- zonkQuantifiedTyVar =<< newFlexiTyVar liftedTypeKind ; matcher_name <- newImplicitBinder name mkMatcherOcc ; let res_ty = TyVarTy res_tv @@ -201,6 +201,7 @@ tcPatSynMatcher (L loc name) lpat arg_w_wraps univ_tvs ex_tvs ev_binds prov_dict ; scrutinee <- mkId "scrut" pat_ty ; cont <- mkId "cont" cont_ty ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts) ++ [mkLHsWrap wrap $ nlHsVar arg | (arg, wrap) <- arg_w_wraps] + ; cont' <- return $ mkLHsWrap (mkWpLet prov_ev_binds) cont' ; fail <- mkId "fail" res_ty ; let fail' = nlHsVar fail @@ -211,7 +212,7 @@ tcPatSynMatcher (L loc name) lpat arg_w_wraps univ_tvs ex_tvs ev_binds prov_dict then [mkSimpleHsAlt lpat cont'] else [mkSimpleHsAlt lpat cont', mkSimpleHsAlt lwpat fail'] - body = mkLHsWrap (mkWpLet ev_binds) $ + body = mkLHsWrap (mkWpLet req_ev_binds) $ L (getLoc lpat) $ HsCase (nlHsVar scrutinee) $ MG{ mg_alts = cases From git at git.haskell.org Wed Nov 5 13:39:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 13:39:51 +0000 (UTC) Subject: [commit: ghc] wip/T8584: #WIP #STASH (0feb654) Message-ID: <20141105133951.19ED83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/0feb654e77fa7a369ec35c17f740b4f84a21fda4/ghc >--------------------------------------------------------------- commit 0feb654e77fa7a369ec35c17f740b4f84a21fda4 Author: Dr. ERDI Gergo Date: Wed Nov 5 21:37:56 2014 +0800 #WIP #STASH >--------------------------------------------------------------- 0feb654e77fa7a369ec35c17f740b4f84a21fda4 compiler/typecheck/TcPatSyn.lhs | 35 +++++++++++------------- testsuite/tests/patsyn/should_compile/T8584-1.hs | 10 +++++++ testsuite/tests/patsyn/should_compile/all.T | 1 + 3 files changed, 27 insertions(+), 19 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index c0ef09b..cd60f0a 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -49,7 +49,8 @@ tcInferPatSynDecl :: PatSynBind Name Name -> TcM (PatSyn, LHsBinds Id) tcInferPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, psb_def = lpat, psb_dir = dir } - = do { pat_ty <- newFlexiTyVarTy openTypeKind + = do { traceTc "tcPatSynDecl {" $ ppr name + ; pat_ty <- newFlexiTyVarTy openTypeKind ; tcCheckPatSynPat lpat ; let (arg_names, is_infix) = case details of @@ -74,9 +75,10 @@ tcInferPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; req_theta <- zonkTcThetaType req_theta ; pat_ty <- zonkTcType pat_ty ; args <- mapM zonkId args + ; let arg_w_wraps = zip args $ repeat idHsWrapper ; let theta = prov_theta ++ req_theta - ; (matcher_id, matcher_bind) <- tcPatSynMatcher lname lpat' args idHsWrapper + ; (matcher_id, matcher_bind) <- tcPatSynMatcher lname lpat' arg_w_wraps univ_tvs ex_tvs ev_binds prov_dicts req_dicts @@ -111,7 +113,7 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, ppr (univ_tvs, req_theta) $$ ppr tau - -- ; prov_dicts <- newEvVars prov_theta + ; prov_dicts <- newEvVars prov_theta ; req_dicts <- newEvVars req_theta ; let skol_info = SigSkol (FunSigCtxt name) (mkFunTys arg_tys pat_ty) @@ -130,14 +132,13 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, ; forM (zip arg_names arg_tys') $ \(arg_name, arg_ty) -> do { arg <- tcLookupId arg_name ; coi <- unifyType (varType arg) arg_ty - ; return (setVarType arg arg_ty, mkWpCast coi) }} + ; return (setVarType arg arg_ty, coToHsWrapper coi) }} ; (ex_vars', prov_dicts') <- tcCollectEx lpat' ; let ex_tvs' = varSetElems ex_vars' prov_theta' = map evVarPred prov_dicts' - - ; checkConstraints skol_info ex_tvs' prov_dicts' $ do + ; (ev_binds', _) <- checkConstraints skol_info ex_tvs' prov_dicts' $ do ctLoc <- getCtLoc PatSigOrigin forM_ prov_theta $ \pred -> do let ctEv = CtWanted{ ctev_pred = pred @@ -145,18 +146,13 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, , ctev_loc = ctLoc } emitFlat $ mkNonCanonical ctEv - ; let (args', _wraps) = unzip arg_w_wraps - -- wrap = foldr (<.>) idHsWrapper wraps - wrap = idHsWrapper - ; ex_tvs' <- mapM zonkQuantifiedTyVar ex_tvs' - ; args' <- mapM zonkId args' ; (matcher_id, matcher_bind) <- tcPatSynMatcher lname lpat' - args' wrap - univ_tvs ex_tvs' + arg_w_wraps + univ_tvs ex_tvs ev_binds - prov_dicts' req_dicts - prov_theta' req_theta + prov_dicts req_dicts + prov_theta req_theta pat_ty ; wrapper_id <- if isBidirectional dir @@ -166,7 +162,7 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, ; traceTc "tcPatSynDecl }" $ ppr name ; let patSyn = mkPatSyn name is_infix arg_tys - univ_tvs ex_tvs' + univ_tvs ex_tvs prov_theta req_theta pat_ty matcher_id wrapper_id @@ -180,7 +176,7 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, \begin{code} tcPatSynMatcher :: Located Name -> LPat Id - -> [Var] -> HsWrapper + -> [(Var, HsWrapper)] -> [TcTyVar] -> [TcTyVar] -> TcEvBinds -> [EvVar] -> [EvVar] @@ -188,7 +184,7 @@ tcPatSynMatcher :: Located Name -> TcType -> TcM (Id, LHsBinds Id) -- See Note [Matchers and wrappers for pattern synonyms] in PatSyn -tcPatSynMatcher (L loc name) lpat args wrap univ_tvs ex_tvs ev_binds prov_dicts req_dicts prov_theta req_theta pat_ty +tcPatSynMatcher (L loc name) lpat arg_w_wraps univ_tvs ex_tvs ev_binds prov_dicts req_dicts prov_theta req_theta pat_ty = do { res_tv <- zonkQuantifiedTyVar =<< newFlexiTyVar liftedTypeKind ; matcher_name <- newImplicitBinder name mkMatcherOcc ; let res_ty = TyVarTy res_tv @@ -204,7 +200,7 @@ tcPatSynMatcher (L loc name) lpat args wrap univ_tvs ex_tvs ev_binds prov_dicts ; scrutinee <- mkId "scrut" pat_ty ; cont <- mkId "cont" cont_ty - ; let cont' = mkLHsWrap wrap $ nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ args) + ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts) ++ [mkLHsWrap wrap $ nlHsVar arg | (arg, wrap) <- arg_w_wraps] ; fail <- mkId "fail" res_ty ; let fail' = nlHsVar fail @@ -253,6 +249,7 @@ tcPatSynMatcher (L loc name) lpat args wrap univ_tvs ex_tvs ev_binds prov_dicts mkId s ty = do name <- newName . mkVarOccFS . fsLit $ s return $ mkLocalId name ty + args = map fst arg_w_wraps isBidirectional :: HsPatSynDir a -> Bool isBidirectional Unidirectional = False diff --git a/testsuite/tests/patsyn/should_compile/T8584-1.hs b/testsuite/tests/patsyn/should_compile/T8584-1.hs new file mode 100644 index 0000000..7a017c8 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8584-1.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms #-} +module ShouldCompile where + +pattern type (Eq a) => Single a :: (Show a) => [a] +-- pattern type Single a :: (Eq a, Show a) => [a] +-- pattern type Single a :: [a] +pattern Single x = [x] + +-- f :: (Show a) => [a] -> a +foobar (Single x) = x diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index 3b7bf27..8896008 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -11,3 +11,4 @@ test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) test('T8968-1', normal, compile, ['']) +test('T8584-1', normal, compile, ['']) From git at git.haskell.org Wed Nov 5 13:48:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 13:48:42 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Cosmetics (f424727) Message-ID: <20141105134842.727003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/f4247275cd9d192e23a0af6f8272eba8bdf87c49/ghc >--------------------------------------------------------------- commit f4247275cd9d192e23a0af6f8272eba8bdf87c49 Author: Dr. ERDI Gergo Date: Wed Nov 5 21:47:08 2014 +0800 Cosmetics >--------------------------------------------------------------- f4247275cd9d192e23a0af6f8272eba8bdf87c49 compiler/basicTypes/PatSyn.lhs | 27 ++++++++++++++------------- compiler/iface/BuildTyCl.lhs | 23 ++++++++++------------- compiler/iface/TcIface.lhs | 3 ++- compiler/typecheck/TcPatSyn.lhs | 15 ++++++++------- 4 files changed, 34 insertions(+), 34 deletions(-) diff --git a/compiler/basicTypes/PatSyn.lhs b/compiler/basicTypes/PatSyn.lhs index 2081b5a..9efd69d 100644 --- a/compiler/basicTypes/PatSyn.lhs +++ b/compiler/basicTypes/PatSyn.lhs @@ -123,9 +123,9 @@ data PatSyn psInfix :: Bool, -- True <=> declared infix psUnivTyVars :: [TyVar], -- Universially-quantified type variables + psReqTheta :: ThetaType, -- Required dictionaries psExTyVars :: [TyVar], -- Existentially-quantified type vars psProvTheta :: ThetaType, -- Provided dictionaries - psReqTheta :: ThetaType, -- Required dictionaries psOrigResTy :: Type, -- Mentions only psUnivTyVars -- See Note [Matchers and wrappers for pattern synonyms] @@ -194,19 +194,20 @@ instance Data.Data PatSyn where \begin{code} -- | Build a new pattern synonym mkPatSyn :: Name - -> Bool -- ^ Is the pattern synonym declared infix? - -> [Type] -- ^ Original arguments - -> [TyVar] -- ^ Universially-quantified type variables - -> [TyVar] -- ^ Existentially-quantified type variables - -> ThetaType -- ^ Wanted dicts - -> ThetaType -- ^ Given dicts - -> Type -- ^ Original result type - -> Id -- ^ Name of matcher - -> Maybe Id -- ^ Name of wrapper + -> Bool -- ^ Is the pattern synonym declared infix? + -> ([TyVar], ThetaType) -- ^ Universially-quantified type variables + -- and required dicts + -> ([TyVar], ThetaType) -- ^ Existentially-quantified type variables + -- and provided dicts + -> [Type] -- ^ Original arguments + -> Type -- ^ Original result type + -> Id -- ^ Name of matcher + -> Maybe Id -- ^ Name of wrapper -> PatSyn -mkPatSyn name declared_infix orig_args - univ_tvs ex_tvs - prov_theta req_theta +mkPatSyn name declared_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) + orig_args orig_res_ty matcher wrapper = MkPatSyn {psName = name, psUnique = getUnique name, diff --git a/compiler/iface/BuildTyCl.lhs b/compiler/iface/BuildTyCl.lhs index 2a66de2..d90e63c 100644 --- a/compiler/iface/BuildTyCl.lhs +++ b/compiler/iface/BuildTyCl.lhs @@ -180,32 +180,29 @@ mkDataConStupidTheta tycon arg_tys univ_tvs ------------------------------------------------------ buildPatSyn :: Name -> Bool -> Id -> Maybe Id - -> [Type] - -> [TyVar] -> [TyVar] -- Univ and ext - -> ThetaType -> ThetaType -- Prov and req - -> Type -- Result type + -> ([TyVar], ThetaType) -- ^ Univ and req + -> ([TyVar], ThetaType) -- ^ Ex and prov + -> [Type] -- ^ Argument types + -> Type -- ^ Result type -> PatSyn buildPatSyn src_name declared_infix matcher wrapper - args univ_tvs ex_tvs prov_theta req_theta pat_ty + (univ_tvs, req_theta) (ex_tvs, prov_theta) arg_tys pat_ty = ASSERT((and [ univ_tvs == univ_tvs' , ex_tvs == ex_tvs' , pat_ty `eqType` pat_ty' , prov_theta `eqTypes` prov_theta' , req_theta `eqTypes` req_theta' - , args `eqTypes` args' + , arg_tys `eqTypes` arg_tys' ])) mkPatSyn src_name declared_infix - args - univ_tvs ex_tvs - prov_theta req_theta - pat_ty - matcher - wrapper + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty + matcher wrapper where ((_:univ_tvs'), req_theta', tau) = tcSplitSigmaTy $ idType matcher ([pat_ty', cont_sigma, _], _) = tcSplitFunTys tau (ex_tvs', prov_theta', cont_tau) = tcSplitSigmaTy cont_sigma - (args', _) = tcSplitFunTys cont_tau + (arg_tys', _) = tcSplitFunTys cont_tau \end{code} diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index 424a46c..9dd5864 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -605,7 +605,8 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name ; pat_ty <- tcIfaceType pat_ty ; arg_tys <- mapM tcIfaceType args ; return $ buildPatSyn name is_infix matcher wrapper - arg_tys univ_tvs ex_tvs prov_theta req_theta pat_ty } + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty } ; return $ AConLike . PatSynCon $ patsyn }}} where mk_doc n = ptext (sLit "Pattern synonym") <+> ppr n diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 905a66e..3704265 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -49,9 +49,9 @@ tcInferPatSynDecl :: PatSynBind Name Name -> TcM (PatSyn, LHsBinds Id) tcInferPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, psb_def = lpat, psb_dir = dir } - = do { traceTc "tcPatSynDecl {" $ ppr name + = do { tcCheckPatSynPat lpat + ; traceTc "tcPatSynDecl {" $ ppr name ; pat_ty <- newFlexiTyVarTy openTypeKind - ; tcCheckPatSynPat lpat ; let (arg_names, is_infix) = case details of PrefixPatSyn names -> (map unLoc names, False) @@ -91,9 +91,9 @@ tcInferPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; traceTc "tcPatSynDecl }" $ ppr name ; let patSyn = mkPatSyn name is_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) (map varType args) - univ_tvs ex_tvs - prov_theta req_theta pat_ty matcher_id wrapper_id ; return (patSyn, matcher_bind) } @@ -109,7 +109,8 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, = setSrcSpan loc $ do { tcCheckPatSynPat lpat - ; traceTc "tcCheckPatSynDecl" $ + ; traceTc "tcCheckPatSynDecl {" $ + ppr name $$ ppr (ex_tvs, prov_theta) $$ ppr (univ_tvs, req_theta) $$ ppr tau @@ -160,9 +161,9 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, ; traceTc "tcPatSynDecl }" $ ppr name ; let patSyn = mkPatSyn name is_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) arg_tys - univ_tvs ex_tvs - prov_theta req_theta pat_ty matcher_id wrapper_id ; return (patSyn, matcher_bind) } From git at git.haskell.org Wed Nov 5 14:10:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 14:10:57 +0000 (UTC) Subject: [commit: ghc] wip/T8584: moar cleanup (45622b3) Message-ID: <20141105141057.B8ACB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/45622b352e27837fd3742a4878dda6a144354475/ghc >--------------------------------------------------------------- commit 45622b352e27837fd3742a4878dda6a144354475 Author: Dr. ERDI Gergo Date: Wed Nov 5 21:51:07 2014 +0800 moar cleanup >--------------------------------------------------------------- 45622b352e27837fd3742a4878dda6a144354475 compiler/typecheck/TcPatSyn.lhs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 3704265..2e93e7c 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -79,12 +79,13 @@ tcInferPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; args <- mapM zonkId args ; let arg_w_wraps = zip args $ repeat idHsWrapper - ; let theta = prov_theta ++ req_theta ; (matcher_id, matcher_bind) <- tcPatSynMatcher lname lpat' (univ_tvs, req_theta, req_ev_binds, req_dicts) (ex_tvs, prov_theta, emptyTcEvBinds, prov_dicts) arg_w_wraps pat_ty + + ; let theta = prov_theta ++ req_theta ; wrapper_id <- if isBidirectional dir then fmap Just $ mkPatSynWrapperId lname (map varType args) univ_tvs ex_tvs theta pat_ty else return Nothing @@ -155,6 +156,7 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, arg_w_wraps pat_ty + ; let theta = prov_theta ++ req_theta ; wrapper_id <- if isBidirectional dir then fmap Just $ mkPatSynWrapperId lname arg_tys univ_tvs ex_tvs theta pat_ty else return Nothing @@ -168,7 +170,6 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, matcher_id wrapper_id ; return (patSyn, matcher_bind) } where - theta = prov_theta ++ req_theta (arg_tys, pat_ty) = tcSplitFunTys tau \end{code} From git at git.haskell.org Wed Nov 5 14:11:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 14:11:00 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Finishing touches (28052d1) Message-ID: <20141105141100.4AF973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/28052d12c995fe40cb944dd8830cc98e3e031cb5/ghc >--------------------------------------------------------------- commit 28052d12c995fe40cb944dd8830cc98e3e031cb5 Author: Dr. ERDI Gergo Date: Wed Nov 5 22:07:17 2014 +0800 Finishing touches >--------------------------------------------------------------- 28052d12c995fe40cb944dd8830cc98e3e031cb5 compiler/typecheck/TcPatSyn.lhs | 107 ++++++++++++++++++++++------------------ 1 file changed, 59 insertions(+), 48 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 2e93e7c..2bb905b 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -30,14 +30,15 @@ import BasicTypes import TcSimplify import TcUnify import TcType +import TcEvidence +import BuildTyCl import VarSet import VarEnv #if __GLASGOW_HASKELL__ < 709 import Data.Monoid #endif import Bag -import TcEvidence -import BuildTyCl +import Util import TypeRep import Control.Monad (forM, forM_) @@ -50,7 +51,7 @@ tcInferPatSynDecl :: PatSynBind Name Name tcInferPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, psb_def = lpat, psb_dir = dir } = do { tcCheckPatSynPat lpat - ; traceTc "tcPatSynDecl {" $ ppr name + ; traceTc "tcInferPatSynDecl {" $ ppr name ; pat_ty <- newFlexiTyVarTy openTypeKind ; let (arg_names, is_infix) = case details of @@ -61,7 +62,7 @@ tcInferPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, mapM tcLookupId arg_names ; let named_taus = (name, pat_ty):map (\arg -> (getName arg, varType arg)) args - ; (qtvs, req_dicts, _mr_bites, req_ev_binds) <- simplifyInfer True False named_taus wanted + ; (qtvs, req_dicts, _mr_bites, ev_binds) <- simplifyInfer True False named_taus wanted ; (ex_vars, prov_dicts) <- tcCollectEx lpat' ; let univ_tvs = filter (not . (`elemVarSet` ex_vars)) qtvs @@ -77,27 +78,14 @@ tcInferPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; pat_ty <- zonkTcType pat_ty ; args <- mapM zonkId args - ; let arg_w_wraps = zip args $ repeat idHsWrapper - - ; (matcher_id, matcher_bind) <- tcPatSynMatcher lname lpat' - (univ_tvs, req_theta, req_ev_binds, req_dicts) - (ex_tvs, prov_theta, emptyTcEvBinds, prov_dicts) - arg_w_wraps - pat_ty + ; let wrapped_args = zip args $ repeat idHsWrapper - ; let theta = prov_theta ++ req_theta - ; wrapper_id <- if isBidirectional dir - then fmap Just $ mkPatSynWrapperId lname (map varType args) univ_tvs ex_tvs theta pat_ty - else return Nothing - - ; traceTc "tcPatSynDecl }" $ ppr name - ; let patSyn = mkPatSyn name is_infix - (univ_tvs, req_theta) - (ex_tvs, prov_theta) - (map varType args) - pat_ty - matcher_id wrapper_id - ; return (patSyn, matcher_bind) } + ; traceTc "tcInferPatSynDecl }" $ ppr name + ; tc_patsyn_finish lname dir is_infix lpat' + (univ_tvs, req_theta, ev_binds, req_dicts) + (ex_tvs, prov_theta, emptyTcEvBinds, prov_dicts) + (zip args $ repeat idHsWrapper) + pat_ty } tcCheckPatSynDecl :: PatSynBind Name Name -> TcPatSynInfo @@ -124,53 +112,76 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, PrefixPatSyn names -> (map unLoc names, False) InfixPatSyn name1 name2 -> (map unLoc [name1, name2], True) - ; (req_ev_binds, (lpat', arg_w_wraps)) <- + ; (req_ev_binds, (lpat', wrapped_args)) <- checkConstraints skol_info univ_tvs req_dicts $ tcPat PatSyn lpat pat_ty $ do { ex_sigtvs <- mapM (\tv -> newSigTyVar (getName tv) (tyVarKind tv)) ex_tvs ; let subst = mkTvSubst (mkInScopeSet (zipVarEnv ex_sigtvs ex_sigtvs)) $ zipTyEnv ex_tvs (map mkTyVarTy ex_sigtvs) arg_tys' = substTys subst arg_tys - ; forM (zip arg_names arg_tys') $ \(arg_name, arg_ty) -> - do { arg <- tcLookupId arg_name - ; coi <- unifyType (varType arg) arg_ty - ; return (setVarType arg arg_ty, coToHsWrapper coi) }} + ; forM (zipEqual "tcCheckPatSynDecl" arg_names arg_tys') $ \(arg_name, arg_ty) -> do + { arg <- tcLookupId arg_name + ; coi <- unifyType (varType arg) arg_ty + ; return (setVarType arg arg_ty, coToHsWrapper coi) }} ; (ex_vars_rhs, prov_dicts_rhs) <- tcCollectEx lpat' ; let ex_tvs_rhs = varSetElems ex_vars_rhs - ; (prov_ev_binds, prov_dicts) <- checkConstraints skol_info ex_tvs_rhs prov_dicts_rhs $ do - ctLoc <- getCtLoc PatSigOrigin - forM prov_theta $ \pred -> do - evar <- newEvVar pred - let ctEv = CtWanted{ ctev_pred = pred - , ctev_evar = evar - , ctev_loc = ctLoc - } - emitFlat $ mkNonCanonical ctEv - return evar - - ; (matcher_id, matcher_bind) <- tcPatSynMatcher lname lpat' + ; (prov_ev_binds, prov_dicts) <- + checkConstraints skol_info ex_tvs_rhs prov_dicts_rhs $ do + { ctLoc <- getCtLoc PatSigOrigin + ; forM prov_theta $ \pred -> do + { evar <- newEvVar pred + ; let ctEv = CtWanted{ ctev_pred = pred + , ctev_evar = evar + , ctev_loc = ctLoc + } + ; emitFlat $ mkNonCanonical ctEv + ; return evar }} + + ; traceTc "tcCheckPatSynDecl }" $ ppr name + ; tc_patsyn_finish lname dir is_infix lpat' + (univ_tvs, req_theta, req_ev_binds, req_dicts) + (ex_tvs, prov_theta, prov_ev_binds, prov_dicts) + wrapped_args + pat_ty } + where + (arg_tys, pat_ty) = tcSplitFunTys tau + +tc_patsyn_finish :: Located Name + -> HsPatSynDir Name + -> Bool + -> LPat Id + -> ([TcTyVar], [PredType], TcEvBinds, [EvVar]) + -> ([TcTyVar], [PredType], TcEvBinds, [EvVar]) + -> [(Var, HsWrapper)] + -> TcType + -> TcM (PatSyn, LHsBinds Id) +tc_patsyn_finish lname dir is_infix lpat' + (univ_tvs, req_theta, req_ev_binds, req_dicts) + (ex_tvs, prov_theta, prov_ev_binds, prov_dicts) + wrapped_args + pat_ty + = do { (matcher_id, matcher_bind) <- tcPatSynMatcher lname lpat' (univ_tvs, req_theta, req_ev_binds, req_dicts) (ex_tvs, prov_theta, prov_ev_binds, prov_dicts) - arg_w_wraps + wrapped_args pat_ty - ; let theta = prov_theta ++ req_theta ; wrapper_id <- if isBidirectional dir - then fmap Just $ mkPatSynWrapperId lname arg_tys univ_tvs ex_tvs theta pat_ty + then fmap Just $ mkPatSynWrapperId lname (map varType args) univ_tvs ex_tvs theta pat_ty else return Nothing - ; traceTc "tcPatSynDecl }" $ ppr name - ; let patSyn = mkPatSyn name is_infix + ; let patSyn = mkPatSyn (unLoc lname) is_infix (univ_tvs, req_theta) (ex_tvs, prov_theta) - arg_tys + (map varType args) pat_ty matcher_id wrapper_id ; return (patSyn, matcher_bind) } where - (arg_tys, pat_ty) = tcSplitFunTys tau + theta = prov_theta ++ req_theta + args = map fst wrapped_args \end{code} From git at git.haskell.org Wed Nov 5 15:53:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 15:53:40 +0000 (UTC) Subject: [commit: ghc] wip/rae: Untabify template-haskell. (f270281) Message-ID: <20141105155340.0E96A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/f270281218e693ebdad30de6d6cb70383b0980e8/ghc >--------------------------------------------------------------- commit f270281218e693ebdad30de6d6cb70383b0980e8 Author: Richard Eisenberg Date: Tue Nov 4 13:43:17 2014 -0500 Untabify template-haskell. >--------------------------------------------------------------- f270281218e693ebdad30de6d6cb70383b0980e8 libraries/template-haskell/Language/Haskell/TH.hs | 8 +-- .../template-haskell/Language/Haskell/TH/Lib.hs | 2 +- .../template-haskell/Language/Haskell/TH/Ppr.hs | 24 ++++---- .../template-haskell/Language/Haskell/TH/PprLib.hs | 66 +++++++++++----------- .../template-haskell/Language/Haskell/TH/Quote.hs | 2 +- 5 files changed, 51 insertions(+), 51 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f270281218e693ebdad30de6d6cb70383b0980e8 From git at git.haskell.org Wed Nov 5 15:53:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 15:53:42 +0000 (UTC) Subject: [commit: ghc] wip/rae: Derive Generic for TH types (#9527) (f45e81d) Message-ID: <20141105155342.997593A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/f45e81dbf0f6d5d42306ee072465f1893fe0ff44/ghc >--------------------------------------------------------------- commit f45e81dbf0f6d5d42306ee072465f1893fe0ff44 Author: Richard Eisenberg Date: Tue Nov 4 13:21:57 2014 -0500 Derive Generic for TH types (#9527) >--------------------------------------------------------------- f45e81dbf0f6d5d42306ee072465f1893fe0ff44 .../template-haskell/Language/Haskell/TH/Syntax.hs | 83 +++++++++++----------- 1 file changed, 42 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f45e81dbf0f6d5d42306ee072465f1893fe0ff44 From git at git.haskell.org Wed Nov 5 15:53:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 15:53:45 +0000 (UTC) Subject: [commit: ghc] wip/rae: Remove unboxed Int# fields from NameFlavour (#9527) (4ec297d) Message-ID: <20141105155345.33F3F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/4ec297dea453925058178002104866fa5e82b667/ghc >--------------------------------------------------------------- commit 4ec297dea453925058178002104866fa5e82b667 Author: Richard Eisenberg Date: Tue Nov 4 13:03:48 2014 -0500 Remove unboxed Int# fields from NameFlavour (#9527) >--------------------------------------------------------------- 4ec297dea453925058178002104866fa5e82b667 compiler/hsSyn/Convert.lhs | 6 +- .../template-haskell/Language/Haskell/TH/PprLib.hs | 7 +- .../template-haskell/Language/Haskell/TH/Syntax.hs | 110 +++------------------ 3 files changed, 21 insertions(+), 102 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4ec297dea453925058178002104866fa5e82b667 From git at git.haskell.org Wed Nov 5 15:53:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 15:53:48 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9064 in th/T9064 (c9f633a) Message-ID: <20141105155348.21C7D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/c9f633a968bab06e9c59720508821024c2794bce/ghc >--------------------------------------------------------------- commit c9f633a968bab06e9c59720508821024c2794bce Author: Richard Eisenberg Date: Tue Nov 4 15:28:40 2014 -0500 Test #9064 in th/T9064 >--------------------------------------------------------------- c9f633a968bab06e9c59720508821024c2794bce testsuite/tests/th/T9064.hs | 23 +++++++++++++++++++++++ testsuite/tests/th/T9064.stderr | 7 +++++++ testsuite/tests/th/all.T | 1 + 3 files changed, 31 insertions(+) diff --git a/testsuite/tests/th/T9064.hs b/testsuite/tests/th/T9064.hs new file mode 100644 index 0000000..3451e2e --- /dev/null +++ b/testsuite/tests/th/T9064.hs @@ -0,0 +1,23 @@ +{-# LANGUAGE TemplateHaskell, DefaultSignatures #-} + +module T9064 where + +import Language.Haskell.TH +import System.IO + +$( [d| class C a where + foo :: a -> String + default foo :: Show a => a -> String + foo = show |] ) + +data Bar = Bar deriving Show +instance C Bar + +x :: Bar -> String +x = foo + +$( do info <- reify ''C + runIO $ do + putStrLn $ pprint info + hFlush stdout + return [] ) diff --git a/testsuite/tests/th/T9064.stderr b/testsuite/tests/th/T9064.stderr new file mode 100644 index 0000000..f9c1716 --- /dev/null +++ b/testsuite/tests/th/T9064.stderr @@ -0,0 +1,7 @@ +class T9064.C (a_0 :: *) + where T9064.foo :: forall (a_0 :: *) . T9064.C a_0 => + a_0 -> GHC.Base.String + default T9064.foo :: forall (a_0 :: *) . (T9064.C a_0, + GHC.Show.Show a_0) => + a_0 -> GHC.Base.String +instance T9064.C T9064.Bar diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index d9783bb..ac0d2f5 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -342,3 +342,4 @@ test('T7484', normal, compile_fail, ['-v0']) test('T1476', normal, compile, ['-v0']) test('T1476b', normal, compile_fail, ['-v0']) test('T8100', normal, compile, ['-v0']) +test('T9064', expect_broken(9064), compile, ['-v0']) From git at git.haskell.org Wed Nov 5 15:53:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 15:53:50 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #8100, by adding StandaloneDerivD to TH's Dec type. (c0eaaa6) Message-ID: <20141105155350.B32A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/c0eaaa6d98a128f05cd76022f86fa4960776ecd2/ghc >--------------------------------------------------------------- commit c0eaaa6d98a128f05cd76022f86fa4960776ecd2 Author: Richard Eisenberg Date: Tue Nov 4 15:24:33 2014 -0500 Fix #8100, by adding StandaloneDerivD to TH's Dec type. >--------------------------------------------------------------- c0eaaa6d98a128f05cd76022f86fa4960776ecd2 compiler/deSugar/DsMeta.hs | 56 ++++++++++++++-------- compiler/hsSyn/Convert.lhs | 7 +++ libraries/template-haskell/Language/Haskell/TH.hs | 2 +- .../template-haskell/Language/Haskell/TH/Lib.hs | 7 +++ .../template-haskell/Language/Haskell/TH/Ppr.hs | 3 ++ .../template-haskell/Language/Haskell/TH/Syntax.hs | 1 + testsuite/tests/th/all.T | 2 +- 7 files changed, 56 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c0eaaa6d98a128f05cd76022f86fa4960776ecd2 From git at git.haskell.org Wed Nov 5 15:53:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 15:53:53 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #8100 in th/T8100 (0b15e8a) Message-ID: <20141105155353.B291A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/0b15e8a048a8f7f466984c685b80a44c0a3543e9/ghc >--------------------------------------------------------------- commit 0b15e8a048a8f7f466984c685b80a44c0a3543e9 Author: Richard Eisenberg Date: Tue Nov 4 15:15:56 2014 -0500 Test #8100 in th/T8100 >--------------------------------------------------------------- 0b15e8a048a8f7f466984c685b80a44c0a3543e9 testsuite/tests/th/T8100.hs | 20 ++++++++++++++++++++ testsuite/tests/th/all.T | 1 + 2 files changed, 21 insertions(+) diff --git a/testsuite/tests/th/T8100.hs b/testsuite/tests/th/T8100.hs new file mode 100644 index 0000000..debc2f7 --- /dev/null +++ b/testsuite/tests/th/T8100.hs @@ -0,0 +1,20 @@ +{-# LANGUAGE TemplateHaskell, StandaloneDeriving #-} + +module T8100 where + +import Language.Haskell.TH + +data Foo a = Foo a +data Bar = Bar Int + +$( do decs <- [d| deriving instance Eq a => Eq (Foo a) + deriving instance Ord a => Ord (Foo a) |] + return ( StandaloneDerivD [] (ConT ''Eq `AppT` ConT ''Bar) + : StandaloneDerivD [] (ConT ''Ord `AppT` ConT ''Bar) + : decs ) ) + +blah :: Ord a => Foo a -> Foo a -> Ordering +blah = compare + +buzz :: Bar -> Bar -> Ordering +buzz = compare diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 9c6dc12..a340be3 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -341,3 +341,4 @@ test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) test('T1476', normal, compile, ['-v0']) test('T1476b', normal, compile_fail, ['-v0']) +test('T8100', expect_broken(8100), compile, ['-v0']) From git at git.haskell.org Wed Nov 5 15:53:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 15:53:56 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9064 by adding support for generic default signatures to TH. (72f228e) Message-ID: <20141105155356.52C023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/72f228e201669384fe9b0c0c54ad917ae104cb2c/ghc >--------------------------------------------------------------- commit 72f228e201669384fe9b0c0c54ad917ae104cb2c Author: Richard Eisenberg Date: Tue Nov 4 16:38:22 2014 -0500 Fix #9064 by adding support for generic default signatures to TH. >--------------------------------------------------------------- 72f228e201669384fe9b0c0c54ad917ae104cb2c compiler/deSugar/DsMeta.hs | 24 +++++++++++----------- compiler/hsSyn/Convert.lhs | 5 +++++ compiler/typecheck/TcSplice.lhs | 13 +++++++++--- libraries/template-haskell/Language/Haskell/TH.hs | 2 +- .../template-haskell/Language/Haskell/TH/Lib.hs | 6 ++++++ .../template-haskell/Language/Haskell/TH/Ppr.hs | 3 +++ .../template-haskell/Language/Haskell/TH/Syntax.hs | 1 + testsuite/tests/th/all.T | 2 +- 8 files changed, 39 insertions(+), 17 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 72f228e201669384fe9b0c0c54ad917ae104cb2c From git at git.haskell.org Wed Nov 5 15:53:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 15:53:59 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9204 in roles/should_fail/T9204 (aa8a3a6) Message-ID: <20141105155359.258633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/aa8a3a649c2cea47f845f3180985b096954ff172/ghc >--------------------------------------------------------------- commit aa8a3a649c2cea47f845f3180985b096954ff172 Author: Richard Eisenberg Date: Tue Nov 4 17:40:06 2014 -0500 Test #9204 in roles/should_fail/T9204 >--------------------------------------------------------------- aa8a3a649c2cea47f845f3180985b096954ff172 testsuite/tests/roles/should_fail/Makefile | 4 ++++ testsuite/tests/roles/should_fail/T9204.hs | 6 ++++++ testsuite/tests/roles/should_fail/T9204.hs-boot | 4 ++++ testsuite/tests/roles/should_fail/all.T | 2 ++ 4 files changed, 16 insertions(+) diff --git a/testsuite/tests/roles/should_fail/Makefile b/testsuite/tests/roles/should_fail/Makefile index 8f80de3..14d6720 100644 --- a/testsuite/tests/roles/should_fail/Makefile +++ b/testsuite/tests/roles/should_fail/Makefile @@ -7,3 +7,7 @@ include $(TOP)/mk/test.mk Roles12: '$(TEST_HC)' $(TEST_HC_OPTS) -c Roles12.hs-boot -'$(TEST_HC)' $(TEST_HC_OPTS) -c Roles12.hs + +T9204: + '$(TEST_HC)' $(TEST_HC_OPTS) -c T9204.hs-boot + -'$(TEST_HC)' $(TEST_HC_OPTS) -c T9204.hs diff --git a/testsuite/tests/roles/should_fail/T9204.hs b/testsuite/tests/roles/should_fail/T9204.hs new file mode 100644 index 0000000..e2351a2 --- /dev/null +++ b/testsuite/tests/roles/should_fail/T9204.hs @@ -0,0 +1,6 @@ + +module T9204 where + +import {-# SOURCE #-} T9204 + +data D a diff --git a/testsuite/tests/roles/should_fail/T9204.hs-boot b/testsuite/tests/roles/should_fail/T9204.hs-boot new file mode 100644 index 0000000..7ee0f1d --- /dev/null +++ b/testsuite/tests/roles/should_fail/T9204.hs-boot @@ -0,0 +1,4 @@ + +module T9204 where + +data D a diff --git a/testsuite/tests/roles/should_fail/all.T b/testsuite/tests/roles/should_fail/all.T index d0d5c4d..bb90fee 100644 --- a/testsuite/tests/roles/should_fail/all.T +++ b/testsuite/tests/roles/should_fail/all.T @@ -8,3 +8,5 @@ test('Roles12', extra_clean(['Roles12.o-boot', 'Roles12.hi-boot']), run_command, ['$MAKE --no-print-directory -s Roles12']) test('T8773', normal, compile_fail, ['']) +test('T9204', [ expect_broken(9204), extra_clean(['T9204.o-boot', 'T9204.hi-boot']) ], + run_command, ['$MAKE --no-print-directory -s T9204']) From git at git.haskell.org Wed Nov 5 15:54:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 15:54:01 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9204 by outputting extra info on boot file mismatch. [skip ci] (36fb083) Message-ID: <20141105155401.C29CE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/36fb0836a541e28af41a4c9b4f54288515c3fc60/ghc >--------------------------------------------------------------- commit 36fb0836a541e28af41a4c9b4f54288515c3fc60 Author: Richard Eisenberg Date: Wed Nov 5 10:52:57 2014 -0500 Fix #9204 by outputting extra info on boot file mismatch. [skip ci] (still in progress) >--------------------------------------------------------------- 36fb0836a541e28af41a4c9b4f54288515c3fc60 compiler/typecheck/TcRnDriver.lhs | 138 +++++++++++++++++++++++++++++--------- 1 file changed, 105 insertions(+), 33 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 36fb0836a541e28af41a4c9b4f54288515c3fc60 From git at git.haskell.org Wed Nov 5 16:23:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 16:23:21 +0000 (UTC) Subject: [commit: ghc] wip/T5462: Merge branch 'master' into wip/T5462 (7452b6a) Message-ID: <20141105162321.9D7DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T5462 Link : http://ghc.haskell.org/trac/ghc/changeset/7452b6a74ffd45930b3207c98a95205ec8171f85/ghc >--------------------------------------------------------------- commit 7452b6a74ffd45930b3207c98a95205ec8171f85 Merge: a7f1bb9 0a8e899 Author: Jose Pedro Magalhaes Date: Wed Nov 5 09:06:12 2014 +0000 Merge branch 'master' into wip/T5462 >--------------------------------------------------------------- 7452b6a74ffd45930b3207c98a95205ec8171f85 compiler/deSugar/DsMeta.hs | 2 +- compiler/hsSyn/HsExpr.lhs | 140 +++++++++++++++++----------- compiler/hsSyn/HsUtils.lhs | 8 +- compiler/rename/RnSplice.lhs | 45 ++++----- compiler/typecheck/TcExpr.lhs | 3 +- compiler/typecheck/TcHsSyn.lhs | 4 +- compiler/typecheck/TcRnTypes.lhs | 4 +- compiler/typecheck/TcSplice.lhs | 16 ++-- compiler/utils/UniqFM.lhs | 20 +--- libraries/base/Data/Foldable.hs | 14 +-- testsuite/tests/ghci/scripts/ghci025.stdout | 3 +- testsuite/tests/perf/compiler/all.T | 6 +- 12 files changed, 145 insertions(+), 120 deletions(-) From git at git.haskell.org Wed Nov 5 16:23:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 16:23:24 +0000 (UTC) Subject: [commit: ghc] wip/T5462: Use MINIMAL to decide whether we can derive or not, and do not reject newtypes (a8e5cd9) Message-ID: <20141105162324.44E2E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T5462 Link : http://ghc.haskell.org/trac/ghc/changeset/a8e5cd9352d4926749b59667bbeb9395d9c21250/ghc >--------------------------------------------------------------- commit a8e5cd9352d4926749b59667bbeb9395d9c21250 Author: Jose Pedro Magalhaes Date: Wed Nov 5 16:25:25 2014 +0000 Use MINIMAL to decide whether we can derive or not, and do not reject newtypes >--------------------------------------------------------------- a8e5cd9352d4926749b59667bbeb9395d9c21250 compiler/typecheck/TcDeriv.lhs | 7 +++---- compiler/typecheck/TcGenDeriv.lhs | 14 +++++++++----- 2 files changed, 12 insertions(+), 9 deletions(-) diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index 231f928..ef12d55 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -1568,7 +1568,6 @@ mkNewTypeEqn dflags overlap_mode tvs , ds_newtype = True } | otherwise = case checkSideConditions dflags mtheta cls cls_tys rep_tycon rep_tc_args of - CanDerive -> go_for_it -- Use the standard H98 method DerivableClassError msg -- Error with standard class | might_derive_via_coercible -> bale_out (msg $$ suggest_nd) | otherwise -> bale_out msg @@ -1577,7 +1576,7 @@ mkNewTypeEqn dflags overlap_mode tvs | might_derive_via_coercible -> bale_out (non_std $$ suggest_nd) -- Try newtype deriving! | derivingViaGenerics -> bale_out msg | otherwise -> bale_out non_std - DerivableViaGenerics -> panicGenericsNewtype + _ -> go_for_it -- CanDerive/DerivableViaGenerics where newtype_deriving = xopt Opt_GeneralizedNewtypeDeriving dflags derivingViaGenerics = xopt Opt_DerivingViaGenerics dflags @@ -1586,8 +1585,8 @@ mkNewTypeEqn dflags overlap_mode tvs non_std = nonStdErr cls suggest_nd = ptext (sLit "Try GeneralizedNewtypeDeriving for GHC's newtype-deriving extension") - panicGenericsNewtype = pprPanic "mkNewTypeEqn: DerivableViaGenerics" - (ppr (cls, rep_tycon)) + -- panicGenericsNewtype = pprPanic "mkNewTypeEqn: DerivableViaGenerics" + -- (ppr (cls, rep_tycon)) -- Here is the plan for newtype derivings. We see -- newtype T a1...an = MkT (t ak+1...an) deriving (.., C s1 .. sm, ...) diff --git a/compiler/typecheck/TcGenDeriv.lhs b/compiler/typecheck/TcGenDeriv.lhs index 88c2929..232bfe8 100644 --- a/compiler/typecheck/TcGenDeriv.lhs +++ b/compiler/typecheck/TcGenDeriv.lhs @@ -69,6 +69,7 @@ import TcEnv (InstInfo) import ListSetOps ( assocMaybe ) import Data.List ( partition, intersperse ) import Data.Maybe ( isNothing ) +import BooleanFormula ( isTrue ) \end{code} \begin{code} @@ -132,7 +133,7 @@ genDerivedBinds dflags fix_env clas loc tycon -- We can derive a given class via Generics iff canDeriveViaGenerics :: DynFlags -> TyCon -> Class -> Maybe SDoc canDeriveViaGenerics dflags tycon clas = - let dfs = map (defMethSpecOfDefMeth . snd) . classOpItems $ clas + let _dfs = map (defMethSpecOfDefMeth . snd) . classOpItems $ clas b `orElse` s = if b then Nothing else Just (ptext (sLit s)) Just m <> _ = Just m Nothing <> n = n @@ -141,11 +142,14 @@ canDeriveViaGenerics dflags tycon clas = -- 2) Opt_DerivingViaGenerics is on <> (xopt Opt_DerivingViaGenerics dflags `orElse` "Try enabling DerivingViaGenerics") -- 3) It has no non-default methods - <> (all (/= NoDM) dfs `orElse` "There are methods without a default definition") + -- <> (all (/= NoDM) dfs `orElse` "There are methods without a default definition") -- 4) It has at least one generic default method - <> (any (== GenericDM) dfs `orElse` "There must be at least one method with a default signature") - -- 5) It's not a newtype (that conflicts with GeneralizedNewtypeDeriving) - <> (not (isNewTyCon tycon) `orElse` "DerivingViaGenerics is not supported for newtypes") + -- <> (any (== GenericDM) dfs `orElse` "There must be at least one method with a default signature") + -- 3/4) Its MINIMAL set is empty + <> (isTrue (classMinimalDef clas) `orElse` "because its MINIMAL set is not empty") + -- 5) It a newtype and GND is enabled + <> (not (isNewTyCon tycon && xopt Opt_GeneralizedNewtypeDeriving dflags) + `orElse` "I don't know whether to use DerivingViaGenerics or GeneralizedNewtypeDeriving") -- Nothing: we can derive it via Generics -- Just s: we can't, reason s \end{code} From git at git.haskell.org Wed Nov 5 16:23:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 16:23:26 +0000 (UTC) Subject: [commit: ghc] wip/T5462's head updated: Use MINIMAL to decide whether we can derive or not, and do not reject newtypes (a8e5cd9) Message-ID: <20141105162326.561A03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T5462' now includes: 64dc4d1 Re-center perf-numbers for T5631 6a1c05f A little refactoring of HsSplice and friends 77f8221 Temporarily disable T3064 (see #9771) 0a8e899 Remove redundant contexts from Foldable methods 7452b6a Merge branch 'master' into wip/T5462 a8e5cd9 Use MINIMAL to decide whether we can derive or not, and do not reject newtypes From git at git.haskell.org Wed Nov 5 18:15:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 18:15:40 +0000 (UTC) Subject: [commit: ghc] master: Disable an assertion; see comment (e6b3829) Message-ID: <20141105181540.E78D53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e6b38294512896cf55f2d05d09d742d82313f598/ghc >--------------------------------------------------------------- commit e6b38294512896cf55f2d05d09d742d82313f598 Author: Simon Marlow Date: Tue Nov 4 21:32:12 2014 +0000 Disable an assertion; see comment >--------------------------------------------------------------- e6b38294512896cf55f2d05d09d742d82313f598 rts/Interpreter.c | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/rts/Interpreter.c b/rts/Interpreter.c index 501cc4f..8a608ec 100644 --- a/rts/Interpreter.c +++ b/rts/Interpreter.c @@ -80,9 +80,15 @@ SpLim = tso_SpLim(cap->r.rCurrentTSO); #define SAVE_STACK_POINTERS \ - ASSERT(Sp > SpLim); \ cap->r.rCurrentTSO->stackobj->sp = Sp +// Note [Not true: ASSERT(Sp > SpLim)] +// +// SpLim has some headroom (RESERVED_STACK_WORDS) to allow for saving +// any necessary state on the stack when returning to the scheduler +// when a stack check fails.. The upshot of this is that Sp could be +// less than SpLim both when leaving to return to the scheduler. + #define RETURN_TO_SCHEDULER(todo,retcode) \ SAVE_STACK_POINTERS; \ cap->r.rCurrentTSO->what_next = (todo); \ From git at git.haskell.org Wed Nov 5 18:15:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 18:15:43 +0000 (UTC) Subject: [commit: ghc] master: Add a comment about stack checks (081ef2f) Message-ID: <20141105181543.825C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/081ef2fb351831081bf6851fd3907679b1b98405/ghc >--------------------------------------------------------------- commit 081ef2fb351831081bf6851fd3907679b1b98405 Author: Simon Marlow Date: Tue Nov 4 21:32:26 2014 +0000 Add a comment about stack checks >--------------------------------------------------------------- 081ef2fb351831081bf6851fd3907679b1b98405 rts/StgMiscClosures.cmm | 2 ++ 1 file changed, 2 insertions(+) diff --git a/rts/StgMiscClosures.cmm b/rts/StgMiscClosures.cmm index 42ef39e..f57fc04 100644 --- a/rts/StgMiscClosures.cmm +++ b/rts/StgMiscClosures.cmm @@ -199,6 +199,8 @@ INFO_TABLE_FUN( stg_BCO, 4, 0, BCO, "BCO", "BCO", ARG_BCO ) { /* entering a BCO means "apply it", same as a function */ Sp_adj(-2); + // Skip the stack check; the interpreter will do one before using + // the stack anyway. Sp(1) = R1; Sp(0) = stg_apply_interp_info; jump stg_yield_to_interpreter []; From git at git.haskell.org Wed Nov 5 18:15:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 18:15:46 +0000 (UTC) Subject: [commit: ghc] master: Fix bugs in debug printing (4cd277b) Message-ID: <20141105181546.1DC6D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4cd277b4dcb91c6c6aa7e071ef0364570566de37/ghc >--------------------------------------------------------------- commit 4cd277b4dcb91c6c6aa7e071ef0364570566de37 Author: Simon Marlow Date: Tue Nov 4 15:52:23 2014 +0000 Fix bugs in debug printing >--------------------------------------------------------------- 4cd277b4dcb91c6c6aa7e071ef0364570566de37 rts/Disassembler.c | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/rts/Disassembler.c b/rts/Disassembler.c index 6b7fa82..f6e2c93 100644 --- a/rts/Disassembler.c +++ b/rts/Disassembler.c @@ -288,7 +288,7 @@ void disassemble( StgBCO *bco ) debugBelch("BCO\n" ); pc = 0; - while (pc <= nbcs) { + while (pc < nbcs) { debugBelch("\t%2d: ", pc ); pc = disInstr ( bco, pc ); } @@ -312,7 +312,6 @@ void disassemble( StgBCO *bco ) debugBelch("\n"); debugBelch("\n"); - ASSERT(pc == nbcs+1); } #endif /* DEBUG */ From git at git.haskell.org Wed Nov 5 18:15:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 18:15:48 +0000 (UTC) Subject: [commit: ghc] master: Fix a couple of bugs in the way info tables are generated for 64-bit platforms (83cf31e) Message-ID: <20141105181548.AB82A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/83cf31e42e87e93eda3e576bc5935509959c2f49/ghc >--------------------------------------------------------------- commit 83cf31e42e87e93eda3e576bc5935509959c2f49 Author: Simon Marlow Date: Tue Nov 4 15:51:56 2014 +0000 Fix a couple of bugs in the way info tables are generated for 64-bit platforms 1. The offset was a full word, but it should actually be a 32-bit offset on 64-bit platforms. 2. The con_desc string was allocated separately, which meant that it might be out of range for a 32-bit offset. These bugs meant that +RTS -Di (interpreter debugging) would sometimes crash on 64-bit. >--------------------------------------------------------------- 83cf31e42e87e93eda3e576bc5935509959c2f49 compiler/ghci/ByteCodeItbls.hs | 38 ++++++++++++++++++++++++-------------- compiler/ghci/DebuggerUtils.hs | 2 +- 2 files changed, 25 insertions(+), 15 deletions(-) diff --git a/compiler/ghci/ByteCodeItbls.hs b/compiler/ghci/ByteCodeItbls.hs index 3288281..d6399ba 100644 --- a/compiler/ghci/ByteCodeItbls.hs +++ b/compiler/ghci/ByteCodeItbls.hs @@ -110,14 +110,10 @@ make_constr_itbls dflags cons then Just code' else Nothing } - qNameCString <- newArray0 0 $ dataConIdentity dcon - let conInfoTbl = StgConInfoTable { - conDesc = qNameCString, - infoTable = itbl - } + -- Make a piece of code to jump to "entry_label". -- This is the only arch-dependent bit. - addrCon <- newExecConItbl dflags conInfoTbl + addrCon <- newExecConItbl dflags itbl (dataConIdentity dcon) --putStrLn ("SIZE of itbl is " ++ show (sizeOf itbl)) --putStrLn ("# ptrs of itbl is " ++ show ptrs) --putStrLn ("# nptrs of itbl is " ++ show nptrs_really) @@ -273,12 +269,17 @@ sizeOfConItbl dflags conInfoTable = sum [ fieldSz conDesc conInfoTable , sizeOfItbl dflags (infoTable conInfoTable) ] -pokeConItbl :: DynFlags -> Ptr StgConInfoTable -> Ptr StgConInfoTable -> StgConInfoTable +pokeConItbl :: DynFlags -> Ptr StgConInfoTable -> Ptr StgConInfoTable + -> StgConInfoTable -> IO () pokeConItbl dflags wr_ptr ex_ptr itbl = flip evalStateT (castPtr wr_ptr) $ do - when ghciTablesNextToCode $ - store (conDesc itbl `minusPtr` (ex_ptr `plusPtr` conInfoTableSizeB dflags)) + when ghciTablesNextToCode $ do + let con_desc = conDesc itbl `minusPtr` + (ex_ptr `plusPtr` conInfoTableSizeB dflags) + store (fromIntegral con_desc :: Word32) + when (wORD_SIZE dflags == 8) $ + store (fromIntegral con_desc :: Word32) store' (sizeOfItbl dflags) (pokeItbl dflags) (infoTable itbl) unless ghciTablesNextToCode $ store (conDesc itbl) @@ -380,13 +381,22 @@ load :: Storable a => PtrIO a load = do addr <- advance lift (peek addr) -newExecConItbl :: DynFlags -> StgConInfoTable -> IO (FunPtr ()) -newExecConItbl dflags obj +newExecConItbl :: DynFlags -> StgInfoTable -> [Word8] -> IO (FunPtr ()) +newExecConItbl dflags obj con_desc = alloca $ \pcode -> do - let sz = fromIntegral (sizeOfConItbl dflags obj) - wr_ptr <- _allocateExec sz pcode + let lcon_desc = length con_desc + 1{- null terminator -} + dummy_cinfo = StgConInfoTable { conDesc = nullPtr, infoTable = obj } + sz = fromIntegral (sizeOfConItbl dflags dummy_cinfo) + -- Note: we need to allocate the conDesc string next to the info + -- table, because on a 64-bit platform we reference this string + -- with a 32-bit offset relative to the info table, so if we + -- allocated the string separately it might be out of range. + wr_ptr <- _allocateExec (sz + fromIntegral lcon_desc) pcode ex_ptr <- peek pcode - pokeConItbl dflags wr_ptr ex_ptr obj + let cinfo = StgConInfoTable { conDesc = ex_ptr `plusPtr` fromIntegral sz + , infoTable = obj } + pokeConItbl dflags wr_ptr ex_ptr cinfo + pokeArray0 0 (castPtr wr_ptr `plusPtr` fromIntegral sz) con_desc _flushExec sz ex_ptr -- Cache flush (if needed) return (castPtrToFunPtr ex_ptr) diff --git a/compiler/ghci/DebuggerUtils.hs b/compiler/ghci/DebuggerUtils.hs index 9ccb113..cafc375 100644 --- a/compiler/ghci/DebuggerUtils.hs +++ b/compiler/ghci/DebuggerUtils.hs @@ -103,7 +103,7 @@ dataConInfoPtrToName x = do 4 -> do w <- peek ptr' return (fromIntegral (w :: Word32)) 8 -> do w <- peek ptr' - return (fromIntegral (w :: Word64)) + return (fromIntegral (w :: Word32)) w -> panic ("getConDescAddress: Unknown platformWordSize: " ++ show w) return $ (ptr `plusPtr` stdInfoTableSizeB dflags) `plusPtr` offsetToString | otherwise = From git at git.haskell.org Wed Nov 5 18:15:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 18:15:51 +0000 (UTC) Subject: [commit: ghc] master: Fix a couple of inaccurate stack checks (3bebf3c) Message-ID: <20141105181551.49A673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3bebf3c2d92e6defc6d17ffa237cc4a9cad71dcf/ghc >--------------------------------------------------------------- commit 3bebf3c2d92e6defc6d17ffa237cc4a9cad71dcf Author: Simon Marlow Date: Tue Nov 4 21:31:00 2014 +0000 Fix a couple of inaccurate stack checks >--------------------------------------------------------------- 3bebf3c2d92e6defc6d17ffa237cc4a9cad71dcf rts/Apply.cmm | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/rts/Apply.cmm b/rts/Apply.cmm index 9d18e95..149a320 100644 --- a/rts/Apply.cmm +++ b/rts/Apply.cmm @@ -70,7 +70,7 @@ stg_PAP_apply /* no args => explicit stack */ // We have a hand-rolled stack check fragment here, because none of // the canned ones suit this situation. // - if ((Sp - WDS(Words)) < SpLim) { + if (Sp - (WDS(Words) + 2/* see ARG_BCO below */) < SpLim) { // there is a return address in R2 in the event of a // stack check failure. The various stg_apply functions arrange // this before calling stg_PAP_entry. @@ -168,7 +168,9 @@ INFO_TABLE(stg_AP,/*special layout*/0,0,AP,"AP","AP") * closure, in which case we must enter the blackhole on return rather * than continuing to evaluate the now-defunct closure. */ - STK_CHK_ENTER(WDS(Words) + SIZEOF_StgUpdateFrame, R1); + STK_CHK_ENTER(WDS(Words) + + SIZEOF_StgUpdateFrame + + 2/* see ARG_BCO below */, R1); PUSH_UPD_FRAME(Sp - SIZEOF_StgUpdateFrame, R1); Sp = Sp - SIZEOF_StgUpdateFrame - WDS(Words); @@ -239,7 +241,8 @@ INFO_TABLE(stg_AP_NOUPD,/*special layout*/0,0,AP,"AP_NOUPD","AP_NOUPD") * closure, in which case we must enter the blackhole on return rather * than continuing to evaluate the now-defunct closure. */ - STK_CHK_ENTER(WDS(Words), R1); + STK_CHK_ENTER(WDS(Words) + + 2/* see ARG_BCO below */, R1); Sp = Sp - WDS(Words); TICK_ENT_AP(); From git at git.haskell.org Wed Nov 5 19:00:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 19:00:02 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9204 in roles/should_fail/T9204 (9a42c0e) Message-ID: <20141105190002.8E5D03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/9a42c0e1d042e250be393bbca16a56355f0e90d8/ghc >--------------------------------------------------------------- commit 9a42c0e1d042e250be393bbca16a56355f0e90d8 Author: Richard Eisenberg Date: Tue Nov 4 17:40:06 2014 -0500 Test #9204 in roles/should_fail/T9204 >--------------------------------------------------------------- 9a42c0e1d042e250be393bbca16a56355f0e90d8 testsuite/tests/roles/should_fail/Makefile | 4 ++++ testsuite/tests/roles/should_fail/T9204.hs | 6 ++++++ testsuite/tests/roles/should_fail/T9204.hs-boot | 4 ++++ testsuite/tests/roles/should_fail/T9204.stderr | 9 +++++++++ testsuite/tests/roles/should_fail/all.T | 2 ++ 5 files changed, 25 insertions(+) diff --git a/testsuite/tests/roles/should_fail/Makefile b/testsuite/tests/roles/should_fail/Makefile index 8f80de3..14d6720 100644 --- a/testsuite/tests/roles/should_fail/Makefile +++ b/testsuite/tests/roles/should_fail/Makefile @@ -7,3 +7,7 @@ include $(TOP)/mk/test.mk Roles12: '$(TEST_HC)' $(TEST_HC_OPTS) -c Roles12.hs-boot -'$(TEST_HC)' $(TEST_HC_OPTS) -c Roles12.hs + +T9204: + '$(TEST_HC)' $(TEST_HC_OPTS) -c T9204.hs-boot + -'$(TEST_HC)' $(TEST_HC_OPTS) -c T9204.hs diff --git a/testsuite/tests/roles/should_fail/T9204.hs b/testsuite/tests/roles/should_fail/T9204.hs new file mode 100644 index 0000000..e2351a2 --- /dev/null +++ b/testsuite/tests/roles/should_fail/T9204.hs @@ -0,0 +1,6 @@ + +module T9204 where + +import {-# SOURCE #-} T9204 + +data D a diff --git a/testsuite/tests/roles/should_fail/T9204.hs-boot b/testsuite/tests/roles/should_fail/T9204.hs-boot new file mode 100644 index 0000000..7ee0f1d --- /dev/null +++ b/testsuite/tests/roles/should_fail/T9204.hs-boot @@ -0,0 +1,4 @@ + +module T9204 where + +data D a diff --git a/testsuite/tests/roles/should_fail/T9204.stderr b/testsuite/tests/roles/should_fail/T9204.stderr new file mode 100644 index 0000000..aa2f558 --- /dev/null +++ b/testsuite/tests/roles/should_fail/T9204.stderr @@ -0,0 +1,9 @@ + +T9204.hs:6:1: + Type constructor ?D? has conflicting definitions in the module + and its hs-boot file + Main module: type role D phantom + data D a + Boot file: abstract D a + The roles do not match. + Roles default to ?representational? in boot files diff --git a/testsuite/tests/roles/should_fail/all.T b/testsuite/tests/roles/should_fail/all.T index d0d5c4d..bb90fee 100644 --- a/testsuite/tests/roles/should_fail/all.T +++ b/testsuite/tests/roles/should_fail/all.T @@ -8,3 +8,5 @@ test('Roles12', extra_clean(['Roles12.o-boot', 'Roles12.hi-boot']), run_command, ['$MAKE --no-print-directory -s Roles12']) test('T8773', normal, compile_fail, ['']) +test('T9204', [ expect_broken(9204), extra_clean(['T9204.o-boot', 'T9204.hi-boot']) ], + run_command, ['$MAKE --no-print-directory -s T9204']) From git at git.haskell.org Wed Nov 5 19:00:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 19:00:05 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9204 by outputting extra info on boot file mismatch. (185b323) Message-ID: <20141105190005.589A93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/185b323c3944666bd21dc1dc1dcb86b9c1cb177e/ghc >--------------------------------------------------------------- commit 185b323c3944666bd21dc1dc1dcb86b9c1cb177e Author: Richard Eisenberg Date: Wed Nov 5 10:52:57 2014 -0500 Fix #9204 by outputting extra info on boot file mismatch. >--------------------------------------------------------------- 185b323c3944666bd21dc1dc1dcb86b9c1cb177e compiler/typecheck/TcRnDriver.lhs | 183 +++++++++++++++++++++++--------- testsuite/tests/roles/should_fail/all.T | 2 +- 2 files changed, 136 insertions(+), 49 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 185b323c3944666bd21dc1dc1dcb86b9c1cb177e From git at git.haskell.org Wed Nov 5 19:02:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 19:02:25 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Revert "Revert "rts/base: Fix #9423"" and resolve issue that caused the revert. (55d2522) Message-ID: <20141105190225.1B38A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/55d2522bd0c48e4c5dac1526cdf53459270baf96/ghc >--------------------------------------------------------------- commit 55d2522bd0c48e4c5dac1526cdf53459270baf96 Author: Andreas Voellmy Date: Wed Nov 5 13:02:20 2014 -0600 Revert "Revert "rts/base: Fix #9423"" and resolve issue that caused the revert. Summary: This reverts commit 4748f5936fe72d96edfa17b153dbfd84f2c4c053. The fix for #9423 was reverted because this commit introduced a C function setIOManagerControlFd() (defined in Schedule.c) defined for all OS types, while the prototype (in includes/rts/IOManager.h) was only included when mingw32_HOST_OS is not defined. This broke Windows builds. This commit reverts the original commit and resolves the problem by only defining setIOManagerControlFd() when mingw32_HOST_OS is defined. Hence the missing prototype error should not occur on Windows. In addition, since the io_manager_control_wr_fd field of the Capability struct is only usd by the setIOManagerControlFd, this commit includes the io_manager_control_wr_fd field in the Capability struct only when mingw32_HOST_OS is not defined. Test Plan: Try to compile successfully on all platforms. Reviewers: austin Reviewed By: austin Subscribers: simonmar, ezyang, carter Differential Revision: https://phabricator.haskell.org/D174 (commit cherry picked from 7e658bc14e2dd6baf208deebbdab9e1285ce4c72) >--------------------------------------------------------------- 55d2522bd0c48e4c5dac1526cdf53459270baf96 includes/rts/IOManager.h | 3 +- rts/Capability.c | 19 +++++++++++ rts/Capability.h | 4 +++ rts/Linker.c | 1 + rts/posix/Signals.c | 86 +++++++++++++++++++++++++++++------------------- 5 files changed, 79 insertions(+), 34 deletions(-) diff --git a/includes/rts/IOManager.h b/includes/rts/IOManager.h index 1c331b9..7bf2cdf 100644 --- a/includes/rts/IOManager.h +++ b/includes/rts/IOManager.h @@ -26,7 +26,8 @@ void sendIOManagerEvent (HsWord32 event); #else -void setIOManagerControlFd (int fd); +void setIOManagerControlFd (nat cap_no, int fd); +void setTimerManagerControlFd(int fd); void setIOManagerWakeupFd (int fd); #endif diff --git a/rts/Capability.c b/rts/Capability.c index 16b71b7..87c5950 100644 --- a/rts/Capability.c +++ b/rts/Capability.c @@ -27,6 +27,10 @@ #include "STM.h" #include "RtsUtils.h" +#if !defined(mingw32_HOST_OS) +#include "rts/IOManager.h" // for setIOManagerControlFd() +#endif + #include // one global capability, this is the Capability for non-threaded @@ -255,6 +259,9 @@ initCapability( Capability *cap, nat i ) cap->spark_stats.converted = 0; cap->spark_stats.gcd = 0; cap->spark_stats.fizzled = 0; +#if !defined(mingw32_HOST_OS) + cap->io_manager_control_wr_fd = -1; +#endif #endif cap->total_allocated = 0; @@ -1073,3 +1080,15 @@ rtsBool checkSparkCountInvariant (void) } #endif + +#if !defined(mingw32_HOST_OS) +void setIOManagerControlFd(nat cap_no USED_IF_THREADS, int fd USED_IF_THREADS) { +#if defined(THREADED_RTS) + if (cap_no < n_capabilities) { + capabilities[cap_no]->io_manager_control_wr_fd = fd; + } else { + errorBelch("warning: setIOManagerControlFd called with illegal capability number."); + } +#endif +} +#endif diff --git a/rts/Capability.h b/rts/Capability.h index f342d92..fc2bdb0 100644 --- a/rts/Capability.h +++ b/rts/Capability.h @@ -121,6 +121,10 @@ struct Capability_ { // Stats on spark creation/conversion SparkCounters spark_stats; +#if !defined(mingw32_HOST_OS) + // IO manager for this cap + int io_manager_control_wr_fd; +#endif #endif // Total words allocated by this cap since rts start W_ total_allocated; diff --git a/rts/Linker.c b/rts/Linker.c index ceb6a4f..124f6cc 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -858,6 +858,7 @@ typedef struct _RtsSymbolVal { #if !defined(mingw32_HOST_OS) #define RTS_USER_SIGNALS_SYMBOLS \ SymI_HasProto(setIOManagerControlFd) \ + SymI_HasProto(setTimerManagerControlFd) \ SymI_HasProto(setIOManagerWakeupFd) \ SymI_HasProto(ioManagerWakeup) \ SymI_HasProto(blockUserSignals) \ diff --git a/rts/posix/Signals.c b/rts/posix/Signals.c index f4a8341..a6978e6 100644 --- a/rts/posix/Signals.c +++ b/rts/posix/Signals.c @@ -124,28 +124,27 @@ more_handlers(int sig) // Here's the pipe into which we will send our signals static int io_manager_wakeup_fd = -1; -static int io_manager_control_fd = -1; +static int timer_manager_control_wr_fd = -1; #define IO_MANAGER_WAKEUP 0xff #define IO_MANAGER_DIE 0xfe #define IO_MANAGER_SYNC 0xfd -void -setIOManagerWakeupFd (int fd) -{ - // only called when THREADED_RTS, but unconditionally - // compiled here because GHC.Event.Control depends on it. - io_manager_wakeup_fd = fd; +void setTimerManagerControlFd(int fd) { + timer_manager_control_wr_fd = fd; } void -setIOManagerControlFd (int fd) +setIOManagerWakeupFd (int fd) { // only called when THREADED_RTS, but unconditionally // compiled here because GHC.Event.Control depends on it. - io_manager_control_fd = fd; + io_manager_wakeup_fd = fd; } +/* ----------------------------------------------------------------------------- + * Wake up at least one IO or timer manager HS thread. + * -------------------------------------------------------------------------- */ void ioManagerWakeup (void) { @@ -167,14 +166,24 @@ ioManagerWakeup (void) void ioManagerDie (void) { + StgWord8 byte = (StgWord8)IO_MANAGER_DIE; + nat i; + int fd; int r; - // Ask the IO Manager thread to exit - if (io_manager_control_fd >= 0) { - StgWord8 byte = (StgWord8)IO_MANAGER_DIE; - r = write(io_manager_control_fd, &byte, 1); + + if (0 <= timer_manager_control_wr_fd) { + r = write(timer_manager_control_wr_fd, &byte, 1); if (r == -1) { sysErrorBelch("ioManagerDie: write"); } - io_manager_control_fd = -1; - io_manager_wakeup_fd = -1; + timer_manager_control_wr_fd = -1; + } + + for (i=0; i < n_capabilities; i++) { + fd = capabilities[i]->io_manager_control_wr_fd; + if (0 <= fd) { + r = write(fd, &byte, 1); + if (r == -1) { sysErrorBelch("ioManagerDie: write"); } + capabilities[i]->io_manager_control_wr_fd = -1; + } } } @@ -189,10 +198,10 @@ ioManagerStart (void) { // Make sure the IO manager thread is running Capability *cap; - if (io_manager_control_fd < 0 || io_manager_wakeup_fd < 0) { - cap = rts_lock(); + if (timer_manager_control_wr_fd < 0 || io_manager_wakeup_fd < 0) { + cap = rts_lock(); ioManagerStartCap(&cap); - rts_unlock(cap); + rts_unlock(cap); } } #endif @@ -220,26 +229,37 @@ generic_handler(int sig USED_IF_THREADS, { #if defined(THREADED_RTS) - if (io_manager_control_fd != -1) - { - StgWord8 buf[sizeof(siginfo_t) + 1]; - int r; - - buf[0] = sig; + StgWord8 buf[sizeof(siginfo_t) + 1]; + int r; - if (info == NULL) { - // info may be NULL on Solaris (see #3790) - memset(buf+1, 0, sizeof(siginfo_t)); - } else { - memcpy(buf+1, info, sizeof(siginfo_t)); - } + buf[0] = sig; + if (info == NULL) { + // info may be NULL on Solaris (see #3790) + memset(buf+1, 0, sizeof(siginfo_t)); + } else { + memcpy(buf+1, info, sizeof(siginfo_t)); + } - r = write(io_manager_control_fd, buf, sizeof(siginfo_t)+1); - if (r == -1 && errno == EAGAIN) - { + if (0 <= timer_manager_control_wr_fd) + { + r = write(timer_manager_control_wr_fd, buf, sizeof(siginfo_t)+1); + if (r == -1 && errno == EAGAIN) { errorBelch("lost signal due to full pipe: %d\n", sig); } } + + nat i; + int fd; + for (i=0; i < n_capabilities; i++) { + fd = capabilities[i]->io_manager_control_wr_fd; + if (0 <= fd) { + r = write(fd, buf, sizeof(siginfo_t)+1); + if (r == -1 && errno == EAGAIN) { + errorBelch("lost signal due to full pipe: %d\n", sig); + } + } + } + // If the IO manager hasn't told us what the FD of the write end // of its pipe is, there's not much we can do here, so just ignore // the signal.. From git at git.haskell.org Wed Nov 5 19:02:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 19:02:35 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: Fix base component of #9423 (fb2cbec) Message-ID: <20141105190235.5C7743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/fb2cbec8ff8eb21690345aa5673c1936bf560fca/base >--------------------------------------------------------------- commit fb2cbec8ff8eb21690345aa5673c1936bf560fca Author: Andreas Voellmy Date: Mon Nov 3 09:57:33 2014 -0600 Fix base component of #9423 Signed-off-by: Austin Seipp >--------------------------------------------------------------- fb2cbec8ff8eb21690345aa5673c1936bf560fca GHC/Event/Control.hs | 8 ++------ GHC/Event/Manager.hs | 1 + GHC/Event/Thread.hs | 35 +++++++++++++++++++++-------------- GHC/Event/TimerManager.hs | 1 + 4 files changed, 25 insertions(+), 20 deletions(-) diff --git a/GHC/Event/Control.hs b/GHC/Event/Control.hs index 2951a6a..53a9bc8 100644 --- a/GHC/Event/Control.hs +++ b/GHC/Event/Control.hs @@ -17,6 +17,7 @@ module GHC.Event.Control , readControlMessage -- *** File descriptors , controlReadFd + , controlWriteFd , wakeupReadFd -- ** Control message sending , sendWakeup @@ -91,7 +92,6 @@ newControl shouldRegister = allocaArray 2 $ \fds -> do setCloseOnExec wr return (rd, wr) (ctrl_rd, ctrl_wr) <- createPipe - when shouldRegister $ c_setIOManagerControlFd ctrl_wr #if defined(HAVE_EVENTFD) ev <- throwErrnoIfMinus1 "eventfd" $ c_eventfd 0 0 setNonBlockingFD ev True @@ -200,9 +200,5 @@ foreign import ccall unsafe "sys/eventfd.h eventfd_write" c_eventfd_write :: CInt -> CULLong -> IO CInt #endif --- Used to tell the RTS how it can send messages to the I/O manager. -foreign import ccall "setIOManagerControlFd" - c_setIOManagerControlFd :: CInt -> IO () - -foreign import ccall "setIOManagerWakeupFd" +foreign import ccall unsafe "setIOManagerWakeupFd" c_setIOManagerWakeupFd :: CInt -> IO () diff --git a/GHC/Event/Manager.hs b/GHC/Event/Manager.hs index 14f7098..e474dc3 100644 --- a/GHC/Event/Manager.hs +++ b/GHC/Event/Manager.hs @@ -27,6 +27,7 @@ module GHC.Event.Manager -- * State , callbackTableVar + , emControl -- * Registering interest in I/O events , Event diff --git a/GHC/Event/Thread.hs b/GHC/Event/Thread.hs index c599047..c054742 100644 --- a/GHC/Event/Thread.hs +++ b/GHC/Event/Thread.hs @@ -21,6 +21,7 @@ import Data.List (zipWith3) import Data.Maybe (Maybe(..)) import Data.Tuple (snd) import Foreign.C.Error (eBADF, errnoToIOError) +import Foreign.C.Types (CInt(..), CUInt(..)) import Foreign.Ptr (Ptr) import GHC.Base import GHC.Conc.Sync (TVar, ThreadId, ThreadStatus(..), atomically, forkIO, @@ -32,12 +33,14 @@ import GHC.IO.Exception (ioError) import GHC.IOArray (IOArray, newIOArray, readIOArray, writeIOArray, boundsIOArray) import GHC.MVar (MVar, newEmptyMVar, newMVar, putMVar, takeMVar) +import GHC.Event.Control (controlWriteFd) import GHC.Event.Internal (eventIs, evtClose) import GHC.Event.Manager (Event, EventManager, evtRead, evtWrite, loop, new, registerFd, unregisterFd_) import qualified GHC.Event.Manager as M import qualified GHC.Event.TimerManager as TM import GHC.Num ((-), (+)) +import GHC.Real (fromIntegral) import System.IO.Unsafe (unsafePerformIO) import System.Posix.Types (Fd) @@ -253,7 +256,11 @@ startIOManagerThread :: IOArray Int (Maybe (ThreadId, EventManager)) startIOManagerThread eventManagerArray i = do let create = do !mgr <- new True - !t <- forkOn i $ loop mgr + !t <- forkOn i $ do + c_setIOManagerControlFd + (fromIntegral i) + (fromIntegral $ controlWriteFd $ M.emControl mgr) + loop mgr labelThread t "IOManager" writeIOArray eventManagerArray i (Just (t,mgr)) old <- readIOArray eventManagerArray i @@ -269,6 +276,7 @@ startIOManagerThread eventManagerArray i = do -- the fork, for example. In this case we should clean up -- open pipes and everything else related to the event manager. -- See #4449 + c_setIOManagerControlFd (fromIntegral i) (-1) M.cleanup em create _other -> return () @@ -277,8 +285,10 @@ startTimerManagerThread :: IO () startTimerManagerThread = modifyMVar_ timerManagerThreadVar $ \old -> do let create = do !mgr <- TM.new + c_setTimerManagerControlFd + (fromIntegral $ controlWriteFd $ TM.emControl mgr) writeIORef timerManager $ Just mgr - !t <- forkIO $ TM.loop mgr `finally` shutdownManagers + !t <- forkIO $ TM.loop mgr labelThread t "TimerManager" return $ Just t case old of @@ -296,21 +306,11 @@ startTimerManagerThread = modifyMVar_ timerManagerThreadVar $ \old -> do mem <- readIORef timerManager _ <- case mem of Nothing -> return () - Just em -> TM.cleanup em + Just em -> do c_setTimerManagerControlFd (-1) + TM.cleanup em create _other -> return st -shutdownManagers :: IO () -shutdownManagers = - withMVar ioManagerLock $ \_ -> do - eventManagerArray <- readIORef eventManager - let (_, high) = boundsIOArray eventManagerArray - forM_ [0..high] $ \i -> do - mmgr <- readIOArray eventManagerArray i - case mmgr of - Nothing -> return () - Just (_,mgr) -> M.shutdown mgr - foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool ioManagerCapabilitiesChanged :: IO () @@ -344,3 +344,10 @@ ioManagerCapabilitiesChanged = do Just (_,mgr) <- readIOArray eventManagerArray i tid <- restartPollLoop mgr i writeIOArray eventManagerArray i (Just (tid,mgr)) + +-- Used to tell the RTS how it can send messages to the I/O manager. +foreign import ccall unsafe "setIOManagerControlFd" + c_setIOManagerControlFd :: CUInt -> CInt -> IO () + +foreign import ccall unsafe "setTimerManagerControlFd" + c_setTimerManagerControlFd :: CInt -> IO () diff --git a/GHC/Event/TimerManager.hs b/GHC/Event/TimerManager.hs index e52f1a0..d8498aa 100644 --- a/GHC/Event/TimerManager.hs +++ b/GHC/Event/TimerManager.hs @@ -15,6 +15,7 @@ module GHC.Event.TimerManager , new , newWith , newDefaultBackend + , emControl -- * Running , finished From git at git.haskell.org Wed Nov 5 21:31:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 21:31:09 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Update release notes (48bc811) Message-ID: <20141105213109.651FC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/48bc8114f711729d437eebe474b19b0fbf3e84f0/ghc >--------------------------------------------------------------- commit 48bc8114f711729d437eebe474b19b0fbf3e84f0 Author: Austin Seipp Date: Wed Nov 5 13:04:51 2014 -0600 Update release notes Signed-off-by: Austin Seipp >--------------------------------------------------------------- 48bc8114f711729d437eebe474b19b0fbf3e84f0 docs/users_guide/7.8.4-notes.xml | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/docs/users_guide/7.8.4-notes.xml b/docs/users_guide/7.8.4-notes.xml index 7b75069..c497334 100644 --- a/docs/users_guide/7.8.4-notes.xml +++ b/docs/users_guide/7.8.4-notes.xml @@ -104,6 +104,13 @@ type family applications has been fixed (issue #9433). + + + A bug in the IO manager that could cause deadlocks in + combination with forkProcess has been + fixed (issues #9377 and #9284). + + From git at git.haskell.org Wed Nov 5 21:31:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 21:31:12 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Revert "Use correct precedence when printing contexts with class operators" (e05f78e) Message-ID: <20141105213112.0D43F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/e05f78ed5e909850b3c86c7ab75862cca50727e3/ghc >--------------------------------------------------------------- commit e05f78ed5e909850b3c86c7ab75862cca50727e3 Author: Austin Seipp Date: Wed Nov 5 15:30:18 2014 -0600 Revert "Use correct precedence when printing contexts with class operators" This breaks the build because I am a nincompoop and TyOpPrec doesn't exit here. This reverts commit d71f316ef4acb6a967a1f07bc4c1144e553a3ac9. >--------------------------------------------------------------- e05f78ed5e909850b3c86c7ab75862cca50727e3 compiler/types/TypeRep.lhs | 10 ++++------ testsuite/tests/gadt/T7558.stderr | 2 +- testsuite/tests/ghci/scripts/Defer02.stderr | 8 ++++---- testsuite/tests/ghci/scripts/T9658.script | 4 ---- testsuite/tests/ghci/scripts/T9658.stdout | 1 - testsuite/tests/ghci/scripts/all.T | 1 - testsuite/tests/indexed-types/should_compile/Simple14.stderr | 2 +- testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.stderr | 2 +- testsuite/tests/indexed-types/should_fail/SimpleFail15.stderr | 2 +- testsuite/tests/indexed-types/should_fail/T2239.stderr | 4 ++-- testsuite/tests/indexed-types/should_fail/T4093a.stderr | 4 ++-- testsuite/tests/perf/compiler/T5837.stderr | 4 ++-- testsuite/tests/polykinds/T7230.stderr | 3 +-- testsuite/tests/roles/should_compile/Roles3.stderr | 2 +- testsuite/tests/typecheck/should_fail/ContextStack2.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/FrozenErrorTests.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5858.stderr | 2 +- testsuite/tests/typecheck/should_fail/T7857.stderr | 2 +- testsuite/tests/typecheck/should_fail/T8392a.stderr | 6 +++--- 19 files changed, 28 insertions(+), 37 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e05f78ed5e909850b3c86c7ab75862cca50727e3 From git at git.haskell.org Wed Nov 5 21:31:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 21:31:14 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Undo release notes (re: precedence fix) (c7bc910) Message-ID: <20141105213114.B7B083A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/c7bc91083b3a76ee8e5652fd60a7d07338601ded/ghc >--------------------------------------------------------------- commit c7bc91083b3a76ee8e5652fd60a7d07338601ded Author: Austin Seipp Date: Wed Nov 5 15:31:29 2014 -0600 Undo release notes (re: precedence fix) Signed-off-by: Austin Seipp >--------------------------------------------------------------- c7bc91083b3a76ee8e5652fd60a7d07338601ded docs/users_guide/7.8.4-notes.xml | 6 ------ 1 file changed, 6 deletions(-) diff --git a/docs/users_guide/7.8.4-notes.xml b/docs/users_guide/7.8.4-notes.xml index c497334..f6fd304 100644 --- a/docs/users_guide/7.8.4-notes.xml +++ b/docs/users_guide/7.8.4-notes.xml @@ -87,12 +87,6 @@ - A minor bug in the compiler which made error messages emit - necessary parenthesis has been fixed (issue #9658). - - - - A bug which caused the compiler to panic on pattern synonyms inside a class declaration has been fixed (issue #9705). From git at git.haskell.org Wed Nov 5 22:45:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Nov 2014 22:45:21 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: Fix build due to missing scanl' (416ef66) Message-ID: <20141105224521.28B7B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/416ef6644ca26ecbebc8dfa5af1963e47e0b2e06/base >--------------------------------------------------------------- commit 416ef6644ca26ecbebc8dfa5af1963e47e0b2e06 Author: Austin Seipp Date: Wed Nov 5 16:07:08 2014 -0600 Fix build due to missing scanl' This was sitting in my working tree, and I forgot to commit it. Oops. This is not exported by Data.List, since it's only needed by 'inits' Signed-off-by: Austin Seipp >--------------------------------------------------------------- 416ef6644ca26ecbebc8dfa5af1963e47e0b2e06 Data/List.hs | 15 ++++++++++++++- 1 file changed, 14 insertions(+), 1 deletion(-) diff --git a/Data/List.hs b/Data/List.hs index 8973464..0b484e0 100644 --- a/Data/List.hs +++ b/Data/List.hs @@ -1,5 +1,5 @@ {-# LANGUAGE Trustworthy #-} -{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-} +{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, BangPatterns #-} ----------------------------------------------------------------------------- -- | @@ -754,10 +754,23 @@ groupBy eq (x:xs) = (x:ys) : groupBy eq zs inits :: [a] -> [[a]] inits = map toListSB . scanl' snocSB emptySB {-# NOINLINE inits #-} + -- We do not allow inits to inline, because it plays havoc with Call Arity -- if it fuses with a consumer, and it would generally lead to serious -- loss of sharing if allowed to fuse with a producer. +-- | A strictly accumulating version of 'scanl' +{-# NOINLINE [1] scanl' #-} +scanl' :: (b -> a -> b) -> b -> [a] -> [b] +-- This peculiar form is needed to prevent scanl' from being rewritten +-- in its own right hand side. +scanl' = scanlGo' + where + scanlGo' :: (b -> a -> b) -> b -> [a] -> [b] + scanlGo' f !q ls = q : (case ls of + [] -> [] + x:xs -> scanlGo' f (f q x) xs) + -- | The 'tails' function returns all final segments of the argument, -- longest first. For example, -- From git at git.haskell.org Thu Nov 6 07:56:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 07:56:33 +0000 (UTC) Subject: [commit: ghc] master: Add doctest examples for Data.Either (d14312f) Message-ID: <20141106075633.94B7A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d14312fcb4c7d3c2a35e086acdac6127ff1a4c60/ghc >--------------------------------------------------------------- commit d14312fcb4c7d3c2a35e086acdac6127ff1a4c60 Author: Michael Orlitzky Date: Thu Nov 6 08:29:26 2014 +0100 Add doctest examples for Data.Either Add doctest examples for every data type and function in `Data.Either` Differential Revision: https://phabricator.haskell.org/D443 >--------------------------------------------------------------- d14312fcb4c7d3c2a35e086acdac6127ff1a4c60 libraries/base/Data/Either.hs | 181 ++++++++++++++++++++++++++++++++++++++++-- 1 file changed, 175 insertions(+), 6 deletions(-) diff --git a/libraries/base/Data/Either.hs b/libraries/base/Data/Either.hs index efa9328..bd85b8f 100644 --- a/libraries/base/Data/Either.hs +++ b/libraries/base/Data/Either.hs @@ -34,6 +34,10 @@ import GHC.Read import Data.Typeable import Data.Type.Equality +-- $setup +-- Allow the use of some Prelude functions in doctests. +-- >>> import Prelude ( (+), (*), length, putStrLn ) + {- -- just for testing import Test.QuickCheck @@ -48,6 +52,75 @@ The 'Either' type is sometimes used to represent a value which is either correct or an error; by convention, the 'Left' constructor is used to hold an error value and the 'Right' constructor is used to hold a correct value (mnemonic: \"right\" also means \"correct\"). + +==== __Examples__ + +The type @'Either' 'String' 'Int'@ is the type of values which can be either +a 'String' or an 'Int'. The 'Left' constructor can be used only on +'String's, and the 'Right' constructor can be used only on 'Int's: + +>>> let s = Left "foo" :: Either String Int +>>> s +Left "foo" +>>> let n = Right 3 :: Either String Int +>>> n +Right 3 +>>> :type s +s :: Either String Int +>>> :type n +n :: Either String Int + +The 'fmap' from our 'Functor' instance will ignore 'Left' values, but +will apply the supplied function to values contained in a 'Right': + +>>> let s = Left "foo" :: Either String Int +>>> let n = Right 3 :: Either String Int +>>> fmap (*2) s +Left "foo" +>>> fmap (*2) n +Right 6 + +The 'Monad' instance for 'Either' allows us to chain together multiple +actions which may fail, and fail overall if any of the individual +steps failed. First we'll write a function that can either parse an +'Int' from a 'Char', or fail. + +>>> import Data.Char ( digitToInt, isDigit ) +>>> :{ + let parseEither :: Char -> Either String Int + parseEither c + | isDigit c = Right (digitToInt c) + | otherwise = Left "parse error" +>>> :} + +The following should work, since both @\'1\'@ and @\'2\'@ can be +parsed as 'Int's. + +>>> :{ + let parseMultiple :: Either String Int + parseMultiple = do + x <- parseEither '1' + y <- parseEither '2' + return (x + y) +>>> :} + +>>> parseMultiple +Right 3 + +But the following should fail overall, since the first operation where +we attempt to parse @\'m\'@ as an 'Int' will fail: + +>>> :{ + let parseMultiple :: Either String Int + parseMultiple = do + x <- parseEither 'm' + y <- parseEither '2' + return (x + y) +>>> :} + +>>> parseMultiple +Left "parse error" + -} data Either a b = Left a | Right b deriving (Eq, Ord, Read, Show, Typeable) @@ -69,27 +142,74 @@ instance Monad (Either e) where -- | Case analysis for the 'Either' type. -- If the value is @'Left' a@, apply the first function to @a@; -- if it is @'Right' b@, apply the second function to @b at . +-- +-- ==== __Examples__ +-- +-- We create two values of type @'Either' 'String' 'Int'@, one using the +-- 'Left' constructor and another using the 'Right' constructor. Then +-- we apply \"either\" the 'length' function (if we have a 'String') +-- or the \"times-two\" function (if we have an 'Int'): +-- +-- >>> let s = Left "foo" :: Either String Int +-- >>> let n = Right 3 :: Either String Int +-- >>> either length (*2) s +-- 3 +-- >>> either length (*2) n +-- 6 +-- either :: (a -> c) -> (b -> c) -> Either a b -> c either f _ (Left x) = f x either _ g (Right y) = g y --- | Extracts from a list of 'Either' all the 'Left' elements --- All the 'Left' elements are extracted in order. +-- | Extracts from a list of 'Either' all the 'Left' elements. +-- All the 'Left' elements are extracted in order. +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ] +-- >>> lefts list +-- ["foo","bar","baz"] +-- lefts :: [Either a b] -> [a] lefts x = [a | Left a <- x] --- | Extracts from a list of 'Either' all the 'Right' elements +-- | Extracts from a list of 'Either' all the 'Right' elements. -- All the 'Right' elements are extracted in order. - +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ] +-- >>> rights list +-- [3,7] +-- rights :: [Either a b] -> [b] rights x = [a | Right a <- x] --- | Partitions a list of 'Either' into two lists +-- | Partitions a list of 'Either' into two lists. -- All the 'Left' elements are extracted, in order, to the first -- component of the output. Similarly the 'Right' elements are extracted -- to the second component of the output. - +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ] +-- >>> partitionEithers list +-- (["foo","bar","baz"],[3,7]) +-- +-- The pair returned by @'partitionEithers' x@ should be the same +-- pair as @('lefts' x, 'rights' x)@: +-- +-- >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ] +-- >>> partitionEithers list == (lefts list, rights list) +-- True +-- partitionEithers :: [Either a b] -> ([a],[b]) partitionEithers = foldr (either left right) ([],[]) where @@ -99,6 +219,31 @@ partitionEithers = foldr (either left right) ([],[]) -- | Return `True` if the given value is a `Left`-value, `False` otherwise. -- -- /Since: 4.7.0.0/ +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> isLeft (Left "foo") +-- True +-- >>> isLeft (Right 3) +-- False +-- +-- Assuming a 'Left' value signifies some sort of error, we can use +-- 'isLeft' to write a very simple error-reporting function that does +-- absolutely nothing in the case of success, and outputs \"ERROR\" if +-- any error occurred. +-- +-- This example shows how 'isLeft' might be used to avoid pattern +-- matching when one does not care about the value contained in the +-- constructor: +-- +-- >>> import Control.Monad ( when ) +-- >>> let report e = when (isLeft e) $ putStrLn "ERROR" +-- >>> report (Right 1) +-- >>> report (Left "parse error") +-- ERROR +-- isLeft :: Either a b -> Bool isLeft (Left _) = True isLeft (Right _) = False @@ -106,6 +251,30 @@ isLeft (Right _) = False -- | Return `True` if the given value is a `Right`-value, `False` otherwise. -- -- /Since: 4.7.0.0/ +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> isRight (Left "foo") +-- False +-- >>> isRight (Right 3) +-- True +-- +-- Assuming a 'Left' value signifies some sort of error, we can use +-- 'isRight' to write a very simple reporting function that only +-- outputs \"SUCCESS\" when a computation has succeeded. +-- +-- This example shows how 'isRight' might be used to avoid pattern +-- matching when one does not care about the value contained in the +-- constructor: +-- +-- >>> import Control.Monad ( when ) +-- >>> let report e = when (isRight e) $ putStrLn "SUCCESS" +-- >>> report (Left "parse error") +-- >>> report (Right 1) +-- SUCCESS +-- isRight :: Either a b -> Bool isRight (Left _) = False isRight (Right _) = True From git at git.haskell.org Thu Nov 6 12:05:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 12:05:01 +0000 (UTC) Subject: [commit: ghc] master: Clarify confusing notice from `make maintainer-clean` (d0d9dc0) Message-ID: <20141106120501.622053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d0d9dc040b54cfd9ced12c5c260ae143fe4e7ec0/ghc >--------------------------------------------------------------- commit d0d9dc040b54cfd9ced12c5c260ae143fe4e7ec0 Author: Jan Stolarek Date: Wed Nov 5 09:39:50 2014 +0100 Clarify confusing notice from `make maintainer-clean` >--------------------------------------------------------------- d0d9dc040b54cfd9ced12c5c260ae143fe4e7ec0 testsuite/Makefile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/Makefile b/testsuite/Makefile index 65d9e9a..401e30a 100644 --- a/testsuite/Makefile +++ b/testsuite/Makefile @@ -32,5 +32,5 @@ clean distclean maintainer-clean: $(RM) -f mk/ghc-config mk/ghc-config.exe $(RM) -f driver/*.pyc @echo - @echo "NOTICE: To clean up test files, try running 'make CLEANUP=1 CLEAN_ONLY=YES'" + @echo "NOTICE: To clean up test files, try running 'make CLEANUP=1 CLEAN_ONLY=YES' in the testsuite directory" @echo From git at git.haskell.org Thu Nov 6 12:05:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 12:05:03 +0000 (UTC) Subject: [commit: ghc] master: Remove -ddump-core-pipeline flag (c0a2354) Message-ID: <20141106120503.F25453A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c0a235424a7a1963dddef6101da4edd3321b0002/ghc >--------------------------------------------------------------- commit c0a235424a7a1963dddef6101da4edd3321b0002 Author: Jan Stolarek Date: Wed Nov 5 13:43:48 2014 +0100 Remove -ddump-core-pipeline flag >--------------------------------------------------------------- c0a235424a7a1963dddef6101da4edd3321b0002 compiler/main/DynFlags.hs | 2 -- compiler/simplCore/CoreMonad.lhs | 2 +- compiler/simplCore/SimplCore.lhs | 4 ---- docs/users_guide/7.10.1-notes.xml | 6 ++++++ 4 files changed, 7 insertions(+), 7 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 495f000..d5362f3 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -237,7 +237,6 @@ data DumpFlag | Opt_D_dump_occur_anal | Opt_D_dump_parsed | Opt_D_dump_rn - | Opt_D_dump_core_pipeline -- TODO FIXME: dump after simplifier stats | Opt_D_dump_simpl | Opt_D_dump_simpl_iterations | Opt_D_dump_spec @@ -2360,7 +2359,6 @@ dynamic_flags = [ , Flag "ddump-occur-anal" (setDumpFlag Opt_D_dump_occur_anal) , Flag "ddump-parsed" (setDumpFlag Opt_D_dump_parsed) , Flag "ddump-rn" (setDumpFlag Opt_D_dump_rn) - , Flag "ddump-core-pipeline" (setDumpFlag Opt_D_dump_core_pipeline) , Flag "ddump-simpl" (setDumpFlag Opt_D_dump_simpl) , Flag "ddump-simpl-iterations" (setDumpFlag Opt_D_dump_simpl_iterations) , Flag "ddump-spec" (setDumpFlag Opt_D_dump_spec) diff --git a/compiler/simplCore/CoreMonad.lhs b/compiler/simplCore/CoreMonad.lhs index b5479ec..04782f1 100644 --- a/compiler/simplCore/CoreMonad.lhs +++ b/compiler/simplCore/CoreMonad.lhs @@ -336,7 +336,7 @@ data CoreToDo -- These are diff core-to-core passes, \begin{code} coreDumpFlag :: CoreToDo -> Maybe DumpFlag coreDumpFlag (CoreDoSimplify {}) = Just Opt_D_verbose_core2core -coreDumpFlag (CoreDoPluginPass {}) = Just Opt_D_dump_core_pipeline +coreDumpFlag (CoreDoPluginPass {}) = Just Opt_D_verbose_core2core coreDumpFlag CoreDoFloatInwards = Just Opt_D_verbose_core2core coreDumpFlag (CoreDoFloatOutwards {}) = Just Opt_D_verbose_core2core coreDumpFlag CoreLiberateCase = Just Opt_D_verbose_core2core diff --git a/compiler/simplCore/SimplCore.lhs b/compiler/simplCore/SimplCore.lhs index 4456f6e..1d3b233 100644 --- a/compiler/simplCore/SimplCore.lhs +++ b/compiler/simplCore/SimplCore.lhs @@ -80,10 +80,6 @@ core2core hsc_env guts do { all_passes <- addPluginPasses dflags builtin_passes ; runCorePasses all_passes guts } -{-- - ; Err.dumpIfSet_dyn dflags Opt_D_dump_core_pipeline - "Plugin information" "" -- TODO FIXME: dump plugin info ---} ; Err.dumpIfSet_dyn dflags Opt_D_dump_simpl_stats "Grand total simplifier statistics" (pprSimplCount stats) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 95f581b..c7954a7 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -88,6 +88,12 @@ specifying flag. + + + and + flags have been removed. + + From git at git.haskell.org Thu Nov 6 12:05:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 12:05:06 +0000 (UTC) Subject: [commit: ghc] master: Remove -ddump-simpl-phases flag (ad8457f) Message-ID: <20141106120506.948D33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ad8457f93807e3b7a9a24867ed69dc93662a29e3/ghc >--------------------------------------------------------------- commit ad8457f93807e3b7a9a24867ed69dc93662a29e3 Author: Jan Stolarek Date: Wed Nov 5 13:37:25 2014 +0100 Remove -ddump-simpl-phases flag >--------------------------------------------------------------- ad8457f93807e3b7a9a24867ed69dc93662a29e3 compiler/main/DynFlags.hs | 15 +++------------ compiler/simplCore/CoreMonad.lhs | 40 ++++++---------------------------------- compiler/simplCore/SimplCore.lhs | 9 +++++---- docs/users_guide/debugging.xml | 11 ----------- docs/users_guide/flags.xml | 6 ------ 5 files changed, 14 insertions(+), 67 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ad8457f93807e3b7a9a24867ed69dc93662a29e3 From git at git.haskell.org Thu Nov 6 12:05:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 12:05:09 +0000 (UTC) Subject: [commit: ghc] master: Update User's Guide, cleanup DynFlags (303776a) Message-ID: <20141106120509.378723A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/303776ab1ff8e192fe42374c8547b7c77305796e/ghc >--------------------------------------------------------------- commit 303776ab1ff8e192fe42374c8547b7c77305796e Author: Jan Stolarek Date: Wed Nov 5 13:44:32 2014 +0100 Update User's Guide, cleanup DynFlags >--------------------------------------------------------------- 303776ab1ff8e192fe42374c8547b7c77305796e compiler/cmm/CmmCallConv.hs | 2 +- compiler/main/DynFlags.hs | 539 ++++++++++++++------------ compiler/main/StaticFlags.hs | 6 +- docs/users_guide/7.10.1-notes.xml | 2 + docs/users_guide/flags.xml | 423 +++++++++++++-------- docs/users_guide/using.xml | 562 +++++++++++++++++++++------- testsuite/tests/ghci/scripts/ghci057.stdout | 18 +- 7 files changed, 1002 insertions(+), 550 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 303776ab1ff8e192fe42374c8547b7c77305796e From johan.tibell at gmail.com Thu Nov 6 12:30:13 2014 From: johan.tibell at gmail.com (Johan Tibell) Date: Thu, 6 Nov 2014 13:30:13 +0100 Subject: [commit: ghc] master: Remove -ddump-simpl-phases flag (ad8457f) In-Reply-To: <20141106120506.948D33A300@ghc.haskell.org> References: <20141106120506.948D33A300@ghc.haskell.org> Message-ID: I think this flag is useful for debugging e.g. why something didn't optimize the way you thought. On Nov 6, 2014 1:05 PM, wrote: > Repository : ssh://git at git.haskell.org/ghc > > On branch : master > Link : > http://ghc.haskell.org/trac/ghc/changeset/ad8457f93807e3b7a9a24867ed69dc93662a29e3/ghc > > >--------------------------------------------------------------- > > commit ad8457f93807e3b7a9a24867ed69dc93662a29e3 > Author: Jan Stolarek > Date: Wed Nov 5 13:37:25 2014 +0100 > > Remove -ddump-simpl-phases flag > > > >--------------------------------------------------------------- > > ad8457f93807e3b7a9a24867ed69dc93662a29e3 > compiler/main/DynFlags.hs | 15 +++------------ > compiler/simplCore/CoreMonad.lhs | 40 > ++++++---------------------------------- > compiler/simplCore/SimplCore.lhs | 9 +++++---- > docs/users_guide/debugging.xml | 11 ----------- > docs/users_guide/flags.xml | 6 ------ > 5 files changed, 14 insertions(+), 67 deletions(-) > > Diff suppressed because of size. To see it, use: > > git diff-tree --root --patch-with-stat --no-color --find-copies-harder > --ignore-space-at-eol --cc ad8457f93807e3b7a9a24867ed69dc93662a29e3 > _______________________________________________ > ghc-commits mailing list > ghc-commits at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-commits > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jan.stolarek at p.lodz.pl Thu Nov 6 13:10:02 2014 From: jan.stolarek at p.lodz.pl (Jan Stolarek) Date: Thu, 6 Nov 2014 14:10:02 +0100 Subject: [commit: ghc] master: Remove -ddump-simpl-phases flag (ad8457f) In-Reply-To: References: <20141106120506.948D33A300@ghc.haskell.org> Message-ID: <201411061410.02495.jan.stolarek@p.lodz.pl> Simon Marlow wrote: > isn't -ddump-simpl-phases useful? ?what's the other way to do that? -dverbose-core2core + -ddump-simple-stats Johan Tibell wrote: > I think this flag is useful for debugging e.g. why something didn't > optimize the way you thought. Well, you can get that information using flags mentioned above. It seemed that -ddump-simpl-phases is not used and can be safely removed. It wasn't documented at all, so the only way to figure out how it works was to look hard at the code. The output itself was rather cryptic - no information about the phase for which the stats are displayed. Again, the only way to make sense of that output was looking at the code to figure out the precise ordering of Core optimisations. With -dverbose-core2core the output makes a lot more sense because it directly follows the output of the phase. Simon PJ and Austin spoke in favour of removing that flag, so I went ahead and did that. But if indeed was used by someone to do their work we could revert that. Janek From git at git.haskell.org Thu Nov 6 13:10:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 13:10:54 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Fix typo in panic message (75237a9) Message-ID: <20141106131054.E1F9A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/75237a922e7b4a75b90252d2b68709625a9e1a47/ghc >--------------------------------------------------------------- commit 75237a922e7b4a75b90252d2b68709625a9e1a47 Author: Dr. ERDI Gergo Date: Thu Nov 6 19:38:40 2014 +0800 Fix typo in panic message >--------------------------------------------------------------- 75237a922e7b4a75b90252d2b68709625a9e1a47 compiler/main/TidyPgm.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs index 02db8ef..7d3752a 100644 --- a/compiler/main/TidyPgm.lhs +++ b/compiler/main/TidyPgm.lhs @@ -419,7 +419,7 @@ lookup_aux_id :: TypeEnv -> Var -> Id lookup_aux_id type_env id = case lookupTypeEnv type_env (idName id) of Just (AnId id') -> id' - _other -> pprPanic "lookup_axu_id" (ppr id) + _other -> pprPanic "lookup_aux_id" (ppr id) \end{code} From git at git.haskell.org Thu Nov 6 13:10:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 13:10:58 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Add a dummy Void# argument to pattern synonym wrapper if it has no arguments and returns an unboxed type (see #9732) (cb12825) Message-ID: <20141106131058.291713A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/cb128254b6ea33f85b2b0e31fb151b477c8a3c53/ghc >--------------------------------------------------------------- commit cb128254b6ea33f85b2b0e31fb151b477c8a3c53 Author: Dr. ERDI Gergo Date: Thu Nov 6 18:07:31 2014 +0800 Add a dummy Void# argument to pattern synonym wrapper if it has no arguments and returns an unboxed type (see #9732) >--------------------------------------------------------------- cb128254b6ea33f85b2b0e31fb151b477c8a3c53 compiler/typecheck/TcPatSyn.lhs | 68 +++++++++++----------- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_compile/T9732.hs | 4 ++ testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_fail/all.T | 2 +- .../patsyn/should_fail/unboxed-wrapper-naked.hs | 8 +++ .../should_fail/unboxed-wrapper-naked.stderr | 3 + testsuite/tests/patsyn/should_run/all.T | 1 + .../tests/patsyn/should_run/unboxed-wrapper.hs | 9 +++ .../should_run/unboxed-wrapper.stdout} | 0 10 files changed, 63 insertions(+), 34 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc cb128254b6ea33f85b2b0e31fb151b477c8a3c53 From git at git.haskell.org Thu Nov 6 13:11:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 13:11:01 +0000 (UTC) Subject: [commit: ghc] wip/T9732: In pattern synonym matchers, support unboxed continuation results. (6b68c8c) Message-ID: <20141106131101.22E193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/6b68c8ccbb08e815b281f4f5ed139311c1e04e27/ghc >--------------------------------------------------------------- commit 6b68c8ccbb08e815b281f4f5ed139311c1e04e27 Author: Dr. ERDI Gergo Date: Sat Nov 1 11:10:56 2014 +0800 In pattern synonym matchers, support unboxed continuation results. This requires ensuring the continuations have arguments by adding a dummy Void# argument when needed. This is so that matching on a pattern synonym is lazy even when the result is unboxed, e.g. pattern P = () f P = 0# In this case, without dummy arguments, the generated matcher's type would be $mP :: forall (r :: ?). () -> r -> r -> r which is called in `f` at type `() -> Int# -> Int# -> Int#`, so it would be strict, in particular, in the failure continuation of `patError`. We work around this by making sure both continuations have arguments: $mP :: forall (r :: ?). () -> (Void# -> r) -> (Void# -> r) -> r Of course, if `P` (and thus, the success continuation) has any arguments, we are only adding the extra dummy argument to the failure continuation. >--------------------------------------------------------------- 6b68c8ccbb08e815b281f4f5ed139311c1e04e27 compiler/deSugar/DsUtils.lhs | 4 +++- compiler/typecheck/TcPatSyn.lhs | 19 ++++++++++++------- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_run/all.T | 1 + testsuite/tests/patsyn/should_run/match-unboxed.hs | 21 +++++++++++++++++++++ .../should_run/match-unboxed.stdout} | 2 ++ 6 files changed, 40 insertions(+), 8 deletions(-) diff --git a/compiler/deSugar/DsUtils.lhs b/compiler/deSugar/DsUtils.lhs index a269374..d36e4c9 100644 --- a/compiler/deSugar/DsUtils.lhs +++ b/compiler/deSugar/DsUtils.lhs @@ -348,13 +348,15 @@ mkPatSynCase var ty alt fail = do matcher <- dsLExpr $ mkLHsWrap wrapper $ nlHsTyApp matcher [ty] let MatchResult _ mkCont = match_result cont <- mkCoreLams bndrs <$> mkCont fail - return $ mkCoreAppsDs matcher [Var var, cont, fail] + return $ mkCoreAppsDs matcher [Var var, ensure_unstrict cont, make_unstrict fail] where MkCaseAlt{ alt_pat = psyn, alt_bndrs = bndrs, alt_wrapper = wrapper, alt_result = match_result} = alt matcher = patSynMatcher psyn + ensure_unstrict = if null (patSynArgs psyn) then make_unstrict else id + make_unstrict = Lam voidArgId mkDataConCase :: Id -> Type -> [CaseAlt DataCon] -> MatchResult mkDataConCase _ _ [] = panic "mkDataConCase: no alternatives" diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 9b2b511..56342f0 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -30,6 +30,7 @@ import BasicTypes import TcSimplify import TcType import VarSet +import MkId #if __GLASGOW_HASKELL__ < 709 import Data.Monoid #endif @@ -124,13 +125,18 @@ tcPatSynMatcher :: Located Name -> TcM (Id, LHsBinds Id) -- See Note [Matchers and wrappers for pattern synonyms] in PatSyn tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_dicts prov_theta req_theta pat_ty - = do { res_tv <- zonkQuantifiedTyVar =<< newFlexiTyVar liftedTypeKind + = do { res_tv <- do + { uniq <- newUnique + ; let tv_name = mkInternalName uniq (mkTyVarOcc "r") loc + ; return $ mkTcTyVar tv_name openTypeKind (SkolemTv False) } ; matcher_name <- newImplicitBinder name mkMatcherOcc ; let res_ty = TyVarTy res_tv + cont_args = if null args then [voidPrimId] else args cont_ty = mkSigmaTy ex_tvs prov_theta $ - mkFunTys (map varType args) res_ty + mkFunTys (map varType cont_args) res_ty + fail_ty = mkFunTy voidPrimTy res_ty - ; let matcher_tau = mkFunTys [pat_ty, cont_ty, res_ty] res_ty + ; let matcher_tau = mkFunTys [pat_ty, cont_ty, fail_ty] res_ty matcher_sigma = mkSigmaTy (res_tv:univ_tvs) req_theta matcher_tau matcher_id = mkExportedLocalId VanillaId matcher_name matcher_sigma @@ -139,10 +145,9 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; scrutinee <- mkId "scrut" pat_ty ; cont <- mkId "cont" cont_ty - ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ args) - ; fail <- mkId "fail" res_ty - ; let fail' = nlHsVar fail - + ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ cont_args) + ; fail <- mkId "fail" fail_ty + ; let fail' = nlHsApps fail [nlHsVar voidPrimId] ; let args = map nlVarPat [scrutinee, cont, fail] lwpat = noLoc $ WildPat pat_ty diff --git a/testsuite/.gitignore b/testsuite/.gitignore index ce5c2c2..2423e15 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -1097,6 +1097,7 @@ mk/ghcconfig*_inplace_bin_ghc-stage2.exe.mk /tests/patsyn/should_run/ex-prov /tests/patsyn/should_run/ex-prov-run /tests/patsyn/should_run/match +/tests/patsyn/should_run/match-unboxed /tests/perf/compiler/T1969.comp.stats /tests/perf/compiler/T3064.comp.stats /tests/perf/compiler/T3294.comp.stats diff --git a/testsuite/tests/patsyn/should_run/all.T b/testsuite/tests/patsyn/should_run/all.T index b3c6b74..442dd43 100644 --- a/testsuite/tests/patsyn/should_run/all.T +++ b/testsuite/tests/patsyn/should_run/all.T @@ -3,3 +3,4 @@ test('match', normal, compile_and_run, ['']) test('ex-prov-run', normal, compile_and_run, ['']) test('bidir-explicit', normal, compile_and_run, ['']) test('bidir-explicit-scope', normal, compile_and_run, ['']) +test('match-unboxed', normal, compile_and_run, ['']) diff --git a/testsuite/tests/patsyn/should_run/match-unboxed.hs b/testsuite/tests/patsyn/should_run/match-unboxed.hs new file mode 100644 index 0000000..ec6de0c --- /dev/null +++ b/testsuite/tests/patsyn/should_run/match-unboxed.hs @@ -0,0 +1,21 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module Main where + +import GHC.Base + +pattern P1 <- 0# +pattern P2 <- 1# + +f :: Int# -> Int# +f P1 = 42# +f P2 = 44# + +g :: Int# -> Int +g P1 = 42 +g P2 = 44 + +main = do + print $ I# (f 0#) + print $ I# (f 1#) + print $ g 0# + print $ g 1# diff --git a/testsuite/tests/array/should_run/arr020.stdout b/testsuite/tests/patsyn/should_run/match-unboxed.stdout similarity index 50% copy from testsuite/tests/array/should_run/arr020.stdout copy to testsuite/tests/patsyn/should_run/match-unboxed.stdout index daaac9e..da4a47e 100644 --- a/testsuite/tests/array/should_run/arr020.stdout +++ b/testsuite/tests/patsyn/should_run/match-unboxed.stdout @@ -1,2 +1,4 @@ 42 +44 42 +44 From git at git.haskell.org Thu Nov 6 13:11:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 13:11:04 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Binding things matched by an unboxed pattern synonym should require a bang (ba1a59c) Message-ID: <20141106131104.2F5813A302@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/ba1a59cd6bcf9b1e04000907bedec1b1572d8c5a/ghc >--------------------------------------------------------------- commit ba1a59cd6bcf9b1e04000907bedec1b1572d8c5a Author: Dr. ERDI Gergo Date: Sat Nov 1 12:00:19 2014 +0800 Binding things matched by an unboxed pattern synonym should require a bang >--------------------------------------------------------------- ba1a59cd6bcf9b1e04000907bedec1b1572d8c5a testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/all.T | 1 + .../should_fail/{unboxed-wrapper-naked.hs => unboxed-bind.hs} | 6 ++++-- testsuite/tests/patsyn/should_fail/unboxed-bind.stderr | 6 ++++++ 5 files changed, 22 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index e8cfb60..97d4317 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -11,3 +11,4 @@ test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) test('T9732', normal, compile, ['']) +test('unboxed-bind-bang', normal, compile, ['']) diff --git a/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs new file mode 100644 index 0000000..a972b21 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash, BangPatterns #-} +module ShouldCompile where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let !(P arg) = x in arg diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index 3979288..96cb097 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -8,3 +8,4 @@ test('T9161-2', normal, compile_fail, ['']) test('T9705-1', normal, compile_fail, ['']) test('T9705-2', normal, compile_fail, ['']) test('unboxed-wrapper-naked', normal, compile_fail, ['']) +test('unboxed-bind', normal, compile_fail, ['']) diff --git a/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs similarity index 52% copy from testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs copy to testsuite/tests/patsyn/should_fail/unboxed-bind.hs index 6e7cc94..ef1b070 100644 --- a/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs @@ -3,6 +3,8 @@ module ShouldFail where import GHC.Base -pattern P1 = 42# +data Foo = MkFoo Int# Int# -x = P1 +pattern P x = MkFoo 0# x + +f x = let P arg = x in arg diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr new file mode 100644 index 0000000..17ca7af --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr @@ -0,0 +1,6 @@ + +unboxed-bind.hs:10:11: + Pattern bindings containing unlifted types should use an outermost bang pattern: + P arg = x + In the expression: let P arg = x in arg + In an equation for ?f?: f x = let P arg = x in arg From git at git.haskell.org Thu Nov 6 13:11:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 13:11:14 +0000 (UTC) Subject: [commit: ghc] wip/T9732: #WIP #STASH (515574e) Message-ID: <20141106131114.813403A339@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/515574e34d1fa3d3c08267c95fca740ae2586fe9/ghc >--------------------------------------------------------------- commit 515574e34d1fa3d3c08267c95fca740ae2586fe9 Author: Dr. ERDI Gergo Date: Thu Nov 6 21:09:08 2014 +0800 #WIP #STASH >--------------------------------------------------------------- 515574e34d1fa3d3c08267c95fca740ae2586fe9 compiler/basicTypes/PatSyn.lhs | 29 ++++++++++---- compiler/iface/BuildTyCl.lhs | 6 +-- compiler/iface/IfaceSyn.lhs | 15 ++++--- compiler/iface/MkIface.lhs | 10 +++-- compiler/iface/TcIface.lhs | 16 ++++---- compiler/typecheck/TcBinds.lhs | 8 +++- compiler/typecheck/TcPatSyn.lhs | 89 +++++++++++++++++++++++++++-------------- 7 files changed, 112 insertions(+), 61 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 515574e34d1fa3d3c08267c95fca740ae2586fe9 From git at git.haskell.org Thu Nov 6 13:11:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 13:11:09 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Simplify creation of IDs (7da3053) Message-ID: <20141106131109.5488C3A337@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/7da3053d3fbf6f3dcc12dd5df709083aed9cdfed/ghc >--------------------------------------------------------------- commit 7da3053d3fbf6f3dcc12dd5df709083aed9cdfed Author: Dr. ERDI Gergo Date: Thu Nov 6 20:27:54 2014 +0800 Simplify creation of IDs >--------------------------------------------------------------- 7da3053d3fbf6f3dcc12dd5df709083aed9cdfed compiler/typecheck/TcPatSyn.lhs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 398acca..afab369 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -24,7 +24,6 @@ import Outputable import FastString import Var import Id -import IdInfo( IdDetails( VanillaId ) ) import TcBinds import BasicTypes import TcSimplify @@ -138,7 +137,7 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; let matcher_tau = mkFunTys [pat_ty, cont_ty, fail_ty] res_ty matcher_sigma = mkSigmaTy (res_tv:univ_tvs) req_theta matcher_tau - matcher_id = mkExportedLocalId VanillaId matcher_name matcher_sigma + matcher_id = mkVanillaGlobal matcher_name matcher_sigma ; traceTc "tcPatSynMatcher" (ppr name $$ ppr (idType matcher_id)) ; let matcher_lid = L loc matcher_id @@ -190,9 +189,7 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; return (matcher_id, matcher_bind) } where - mkId s ty = do - name <- newName . mkVarOccFS . fsLit $ s - return $ mkLocalId name ty + mkId s ty = mkSysLocalM (fsLit s) ty isBidirectional :: HsPatSynDir a -> Bool isBidirectional Unidirectional = False @@ -233,7 +230,7 @@ mkPatSynWrapperId (L _ name) args univ_tvs ex_tvs theta pat_ty wrapper_sigma = mkSigmaTy wrapper_tvs wrapper_theta wrapper_tau ; wrapper_name <- newImplicitBinder name mkDataConWrapperOcc - ; return $ mkExportedLocalId VanillaId wrapper_name wrapper_sigma } + ; return $ mkVanillaGlobal wrapper_name wrapper_sigma } mkPatSynWrapper :: Located Name -> MatchGroup Name (LHsExpr Name) From git at git.haskell.org Thu Nov 6 13:11:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 13:11:11 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Update documentation of matcher type (bbbd75c) Message-ID: <20141106131111.E19223A338@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/bbbd75c6b7d26c04c00daecc5dfe63736aedf88c/ghc >--------------------------------------------------------------- commit bbbd75c6b7d26c04c00daecc5dfe63736aedf88c Author: Dr. ERDI Gergo Date: Thu Nov 6 20:31:03 2014 +0800 Update documentation of matcher type >--------------------------------------------------------------- bbbd75c6b7d26c04c00daecc5dfe63736aedf88c compiler/basicTypes/PatSyn.lhs | 18 +++++++++++++----- 1 file changed, 13 insertions(+), 5 deletions(-) diff --git a/compiler/basicTypes/PatSyn.lhs b/compiler/basicTypes/PatSyn.lhs index 9efd69d..af77d36 100644 --- a/compiler/basicTypes/PatSyn.lhs +++ b/compiler/basicTypes/PatSyn.lhs @@ -130,11 +130,19 @@ data PatSyn -- See Note [Matchers and wrappers for pattern synonyms] psMatcher :: Id, - -- Matcher function, of type - -- forall r univ_tvs. req_theta - -- => res_ty - -- -> (forall ex_tvs. prov_theta -> arg_tys -> r) - -- -> r -> r + -- Matcher function. If psArgs is empty, then it has type + -- forall (r :: ?) univ_tvs. req_theta + -- => res_ty + -- -> (forall ex_tvs. prov_theta -> Void# -> r) + -- -> (Void# -> r) + -- -> r + -- + -- Otherwise: + -- forall (r :: ?) univ_tvs. req_theta + -- => res_ty + -- -> (forall ex_tvs. prov_theta -> arg_tys -> r) + -- -> (Void# -> r) + -- -> r psWrapper :: Maybe Id -- Nothing => uni-directional pattern synonym From git at git.haskell.org Thu Nov 6 13:11:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 13:11:06 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Group PatSyn req/prov arguments together so that they're not all over the place (f2c683c) Message-ID: <20141106131106.BE3473A303@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/f2c683c8719d24ba16846245978ef1e980e27bca/ghc >--------------------------------------------------------------- commit f2c683c8719d24ba16846245978ef1e980e27bca Author: Dr. ERDI Gergo Date: Thu Nov 6 19:01:38 2014 +0800 Group PatSyn req/prov arguments together so that they're not all over the place >--------------------------------------------------------------- f2c683c8719d24ba16846245978ef1e980e27bca compiler/basicTypes/PatSyn.lhs | 27 ++++++++++++++------------- compiler/iface/BuildTyCl.lhs | 23 ++++++++++------------- compiler/iface/TcIface.lhs | 3 ++- compiler/typecheck/TcPatSyn.lhs | 4 ++-- 4 files changed, 28 insertions(+), 29 deletions(-) diff --git a/compiler/basicTypes/PatSyn.lhs b/compiler/basicTypes/PatSyn.lhs index 2081b5a..9efd69d 100644 --- a/compiler/basicTypes/PatSyn.lhs +++ b/compiler/basicTypes/PatSyn.lhs @@ -123,9 +123,9 @@ data PatSyn psInfix :: Bool, -- True <=> declared infix psUnivTyVars :: [TyVar], -- Universially-quantified type variables + psReqTheta :: ThetaType, -- Required dictionaries psExTyVars :: [TyVar], -- Existentially-quantified type vars psProvTheta :: ThetaType, -- Provided dictionaries - psReqTheta :: ThetaType, -- Required dictionaries psOrigResTy :: Type, -- Mentions only psUnivTyVars -- See Note [Matchers and wrappers for pattern synonyms] @@ -194,19 +194,20 @@ instance Data.Data PatSyn where \begin{code} -- | Build a new pattern synonym mkPatSyn :: Name - -> Bool -- ^ Is the pattern synonym declared infix? - -> [Type] -- ^ Original arguments - -> [TyVar] -- ^ Universially-quantified type variables - -> [TyVar] -- ^ Existentially-quantified type variables - -> ThetaType -- ^ Wanted dicts - -> ThetaType -- ^ Given dicts - -> Type -- ^ Original result type - -> Id -- ^ Name of matcher - -> Maybe Id -- ^ Name of wrapper + -> Bool -- ^ Is the pattern synonym declared infix? + -> ([TyVar], ThetaType) -- ^ Universially-quantified type variables + -- and required dicts + -> ([TyVar], ThetaType) -- ^ Existentially-quantified type variables + -- and provided dicts + -> [Type] -- ^ Original arguments + -> Type -- ^ Original result type + -> Id -- ^ Name of matcher + -> Maybe Id -- ^ Name of wrapper -> PatSyn -mkPatSyn name declared_infix orig_args - univ_tvs ex_tvs - prov_theta req_theta +mkPatSyn name declared_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) + orig_args orig_res_ty matcher wrapper = MkPatSyn {psName = name, psUnique = getUnique name, diff --git a/compiler/iface/BuildTyCl.lhs b/compiler/iface/BuildTyCl.lhs index 2a66de2..d90e63c 100644 --- a/compiler/iface/BuildTyCl.lhs +++ b/compiler/iface/BuildTyCl.lhs @@ -180,32 +180,29 @@ mkDataConStupidTheta tycon arg_tys univ_tvs ------------------------------------------------------ buildPatSyn :: Name -> Bool -> Id -> Maybe Id - -> [Type] - -> [TyVar] -> [TyVar] -- Univ and ext - -> ThetaType -> ThetaType -- Prov and req - -> Type -- Result type + -> ([TyVar], ThetaType) -- ^ Univ and req + -> ([TyVar], ThetaType) -- ^ Ex and prov + -> [Type] -- ^ Argument types + -> Type -- ^ Result type -> PatSyn buildPatSyn src_name declared_infix matcher wrapper - args univ_tvs ex_tvs prov_theta req_theta pat_ty + (univ_tvs, req_theta) (ex_tvs, prov_theta) arg_tys pat_ty = ASSERT((and [ univ_tvs == univ_tvs' , ex_tvs == ex_tvs' , pat_ty `eqType` pat_ty' , prov_theta `eqTypes` prov_theta' , req_theta `eqTypes` req_theta' - , args `eqTypes` args' + , arg_tys `eqTypes` arg_tys' ])) mkPatSyn src_name declared_infix - args - univ_tvs ex_tvs - prov_theta req_theta - pat_ty - matcher - wrapper + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty + matcher wrapper where ((_:univ_tvs'), req_theta', tau) = tcSplitSigmaTy $ idType matcher ([pat_ty', cont_sigma, _], _) = tcSplitFunTys tau (ex_tvs', prov_theta', cont_tau) = tcSplitSigmaTy cont_sigma - (args', _) = tcSplitFunTys cont_tau + (arg_tys', _) = tcSplitFunTys cont_tau \end{code} diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index 424a46c..9dd5864 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -605,7 +605,8 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name ; pat_ty <- tcIfaceType pat_ty ; arg_tys <- mapM tcIfaceType args ; return $ buildPatSyn name is_infix matcher wrapper - arg_tys univ_tvs ex_tvs prov_theta req_theta pat_ty } + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty } ; return $ AConLike . PatSynCon $ patsyn }}} where mk_doc n = ptext (sLit "Pattern synonym") <+> ppr n diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index e2334d0..398acca 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -103,9 +103,9 @@ tcPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; traceTc "tcPatSynDecl }" $ ppr name ; let patSyn = mkPatSyn name is_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) (map varType args) - univ_tvs ex_tvs - prov_theta req_theta pat_ty matcher_id wrapper_id ; return (patSyn, matcher_bind) } From git at git.haskell.org Thu Nov 6 13:14:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 13:14:00 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Add a dummy Void# argument to pattern synonym wrapper if it has no arguments and returns an unboxed type (see #9732) (49c3a2e) Message-ID: <20141106131400.C551C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/49c3a2e80308f9680d4b1f1c9aef25adf6eb11bc/ghc >--------------------------------------------------------------- commit 49c3a2e80308f9680d4b1f1c9aef25adf6eb11bc Author: Dr. ERDI Gergo Date: Thu Nov 6 18:07:31 2014 +0800 Add a dummy Void# argument to pattern synonym wrapper if it has no arguments and returns an unboxed type (see #9732) >--------------------------------------------------------------- 49c3a2e80308f9680d4b1f1c9aef25adf6eb11bc compiler/typecheck/TcPatSyn.lhs | 68 +++++++++++----------- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_compile/T9732.hs | 4 ++ testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_fail/all.T | 2 +- .../patsyn/should_fail/unboxed-wrapper-naked.hs | 8 +++ .../should_fail/unboxed-wrapper-naked.stderr | 3 + testsuite/tests/patsyn/should_run/all.T | 1 + .../tests/patsyn/should_run/unboxed-wrapper.hs | 9 +++ .../should_run/unboxed-wrapper.stdout} | 0 10 files changed, 63 insertions(+), 34 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 49c3a2e80308f9680d4b1f1c9aef25adf6eb11bc From git at git.haskell.org Thu Nov 6 13:14:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 13:14:03 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Group PatSyn req/prov arguments together so that they're not all over the place (e52869c) Message-ID: <20141106131403.5A9813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/e52869cfed4f5a40497ba46b472905b65388c83f/ghc >--------------------------------------------------------------- commit e52869cfed4f5a40497ba46b472905b65388c83f Author: Dr. ERDI Gergo Date: Thu Nov 6 19:01:38 2014 +0800 Group PatSyn req/prov arguments together so that they're not all over the place >--------------------------------------------------------------- e52869cfed4f5a40497ba46b472905b65388c83f compiler/basicTypes/PatSyn.lhs | 27 ++++++++++++++------------- compiler/iface/BuildTyCl.lhs | 23 ++++++++++------------- compiler/iface/TcIface.lhs | 3 ++- compiler/typecheck/TcPatSyn.lhs | 4 ++-- 4 files changed, 28 insertions(+), 29 deletions(-) diff --git a/compiler/basicTypes/PatSyn.lhs b/compiler/basicTypes/PatSyn.lhs index 1b78dac..af77d36 100644 --- a/compiler/basicTypes/PatSyn.lhs +++ b/compiler/basicTypes/PatSyn.lhs @@ -123,9 +123,9 @@ data PatSyn psInfix :: Bool, -- True <=> declared infix psUnivTyVars :: [TyVar], -- Universially-quantified type variables + psReqTheta :: ThetaType, -- Required dictionaries psExTyVars :: [TyVar], -- Existentially-quantified type vars psProvTheta :: ThetaType, -- Provided dictionaries - psReqTheta :: ThetaType, -- Required dictionaries psOrigResTy :: Type, -- Mentions only psUnivTyVars -- See Note [Matchers and wrappers for pattern synonyms] @@ -202,19 +202,20 @@ instance Data.Data PatSyn where \begin{code} -- | Build a new pattern synonym mkPatSyn :: Name - -> Bool -- ^ Is the pattern synonym declared infix? - -> [Type] -- ^ Original arguments - -> [TyVar] -- ^ Universially-quantified type variables - -> [TyVar] -- ^ Existentially-quantified type variables - -> ThetaType -- ^ Wanted dicts - -> ThetaType -- ^ Given dicts - -> Type -- ^ Original result type - -> Id -- ^ Name of matcher - -> Maybe Id -- ^ Name of wrapper + -> Bool -- ^ Is the pattern synonym declared infix? + -> ([TyVar], ThetaType) -- ^ Universially-quantified type variables + -- and required dicts + -> ([TyVar], ThetaType) -- ^ Existentially-quantified type variables + -- and provided dicts + -> [Type] -- ^ Original arguments + -> Type -- ^ Original result type + -> Id -- ^ Name of matcher + -> Maybe Id -- ^ Name of wrapper -> PatSyn -mkPatSyn name declared_infix orig_args - univ_tvs ex_tvs - prov_theta req_theta +mkPatSyn name declared_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) + orig_args orig_res_ty matcher wrapper = MkPatSyn {psName = name, psUnique = getUnique name, diff --git a/compiler/iface/BuildTyCl.lhs b/compiler/iface/BuildTyCl.lhs index 2a66de2..d90e63c 100644 --- a/compiler/iface/BuildTyCl.lhs +++ b/compiler/iface/BuildTyCl.lhs @@ -180,32 +180,29 @@ mkDataConStupidTheta tycon arg_tys univ_tvs ------------------------------------------------------ buildPatSyn :: Name -> Bool -> Id -> Maybe Id - -> [Type] - -> [TyVar] -> [TyVar] -- Univ and ext - -> ThetaType -> ThetaType -- Prov and req - -> Type -- Result type + -> ([TyVar], ThetaType) -- ^ Univ and req + -> ([TyVar], ThetaType) -- ^ Ex and prov + -> [Type] -- ^ Argument types + -> Type -- ^ Result type -> PatSyn buildPatSyn src_name declared_infix matcher wrapper - args univ_tvs ex_tvs prov_theta req_theta pat_ty + (univ_tvs, req_theta) (ex_tvs, prov_theta) arg_tys pat_ty = ASSERT((and [ univ_tvs == univ_tvs' , ex_tvs == ex_tvs' , pat_ty `eqType` pat_ty' , prov_theta `eqTypes` prov_theta' , req_theta `eqTypes` req_theta' - , args `eqTypes` args' + , arg_tys `eqTypes` arg_tys' ])) mkPatSyn src_name declared_infix - args - univ_tvs ex_tvs - prov_theta req_theta - pat_ty - matcher - wrapper + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty + matcher wrapper where ((_:univ_tvs'), req_theta', tau) = tcSplitSigmaTy $ idType matcher ([pat_ty', cont_sigma, _], _) = tcSplitFunTys tau (ex_tvs', prov_theta', cont_tau) = tcSplitSigmaTy cont_sigma - (args', _) = tcSplitFunTys cont_tau + (arg_tys', _) = tcSplitFunTys cont_tau \end{code} diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index 424a46c..9dd5864 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -605,7 +605,8 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name ; pat_ty <- tcIfaceType pat_ty ; arg_tys <- mapM tcIfaceType args ; return $ buildPatSyn name is_infix matcher wrapper - arg_tys univ_tvs ex_tvs prov_theta req_theta pat_ty } + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty } ; return $ AConLike . PatSynCon $ patsyn }}} where mk_doc n = ptext (sLit "Pattern synonym") <+> ppr n diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 1e58300..afab369 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -102,9 +102,9 @@ tcPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; traceTc "tcPatSynDecl }" $ ppr name ; let patSyn = mkPatSyn name is_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) (map varType args) - univ_tvs ex_tvs - prov_theta req_theta pat_ty matcher_id wrapper_id ; return (patSyn, matcher_bind) } From git at git.haskell.org Thu Nov 6 13:14:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 13:14:06 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Binding things matched by an unboxed pattern synonym should require a bang (6ce514b) Message-ID: <20141106131406.67C0B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/6ce514bfd9e787500bcc2f106f3c34a0cd0b95df/ghc >--------------------------------------------------------------- commit 6ce514bfd9e787500bcc2f106f3c34a0cd0b95df Author: Dr. ERDI Gergo Date: Sat Nov 1 12:00:19 2014 +0800 Binding things matched by an unboxed pattern synonym should require a bang >--------------------------------------------------------------- 6ce514bfd9e787500bcc2f106f3c34a0cd0b95df testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/all.T | 1 + .../should_fail/{unboxed-wrapper-naked.hs => unboxed-bind.hs} | 6 ++++-- testsuite/tests/patsyn/should_fail/unboxed-bind.stderr | 6 ++++++ 5 files changed, 22 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index e8cfb60..97d4317 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -11,3 +11,4 @@ test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) test('T9732', normal, compile, ['']) +test('unboxed-bind-bang', normal, compile, ['']) diff --git a/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs new file mode 100644 index 0000000..a972b21 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash, BangPatterns #-} +module ShouldCompile where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let !(P arg) = x in arg diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index 3979288..96cb097 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -8,3 +8,4 @@ test('T9161-2', normal, compile_fail, ['']) test('T9705-1', normal, compile_fail, ['']) test('T9705-2', normal, compile_fail, ['']) test('unboxed-wrapper-naked', normal, compile_fail, ['']) +test('unboxed-bind', normal, compile_fail, ['']) diff --git a/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs similarity index 52% copy from testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs copy to testsuite/tests/patsyn/should_fail/unboxed-bind.hs index 6e7cc94..ef1b070 100644 --- a/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs @@ -3,6 +3,8 @@ module ShouldFail where import GHC.Base -pattern P1 = 42# +data Foo = MkFoo Int# Int# -x = P1 +pattern P x = MkFoo 0# x + +f x = let P arg = x in arg diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr new file mode 100644 index 0000000..17ca7af --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr @@ -0,0 +1,6 @@ + +unboxed-bind.hs:10:11: + Pattern bindings containing unlifted types should use an outermost bang pattern: + P arg = x + In the expression: let P arg = x in arg + In an equation for ?f?: f x = let P arg = x in arg From git at git.haskell.org Thu Nov 6 13:14:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 13:14:09 +0000 (UTC) Subject: [commit: ghc] wip/T9732: #WIP #STASH (dbad3a3) Message-ID: <20141106131409.05D973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/dbad3a3d58b312248ad2f236028d89c6eaa598ba/ghc >--------------------------------------------------------------- commit dbad3a3d58b312248ad2f236028d89c6eaa598ba Author: Dr. ERDI Gergo Date: Thu Nov 6 21:09:08 2014 +0800 #WIP #STASH >--------------------------------------------------------------- dbad3a3d58b312248ad2f236028d89c6eaa598ba compiler/basicTypes/PatSyn.lhs | 29 ++++++++++---- compiler/iface/BuildTyCl.lhs | 6 +-- compiler/iface/IfaceSyn.lhs | 15 ++++--- compiler/iface/MkIface.lhs | 10 +++-- compiler/iface/TcIface.lhs | 16 ++++---- compiler/typecheck/TcBinds.lhs | 8 +++- compiler/typecheck/TcPatSyn.lhs | 89 +++++++++++++++++++++++++++-------------- 7 files changed, 112 insertions(+), 61 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc dbad3a3d58b312248ad2f236028d89c6eaa598ba From git at git.haskell.org Thu Nov 6 13:14:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 13:14:12 +0000 (UTC) Subject: [commit: ghc] wip/T9732: In pattern synonym matchers, support unboxed continuation results. (1567a8f) Message-ID: <20141106131412.0A0193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/1567a8f87303f1833ebf1eb253b3add974bc4ae3/ghc >--------------------------------------------------------------- commit 1567a8f87303f1833ebf1eb253b3add974bc4ae3 Author: Dr. ERDI Gergo Date: Sat Nov 1 11:10:56 2014 +0800 In pattern synonym matchers, support unboxed continuation results. This requires ensuring the continuations have arguments by adding a dummy Void# argument when needed. This is so that matching on a pattern synonym is lazy even when the result is unboxed, e.g. pattern P = () f P = 0# In this case, without dummy arguments, the generated matcher's type would be $mP :: forall (r :: ?). () -> r -> r -> r which is called in `f` at type `() -> Int# -> Int# -> Int#`, so it would be strict, in particular, in the failure continuation of `patError`. We work around this by making sure both continuations have arguments: $mP :: forall (r :: ?). () -> (Void# -> r) -> (Void# -> r) -> r Of course, if `P` (and thus, the success continuation) has any arguments, we are only adding the extra dummy argument to the failure continuation. >--------------------------------------------------------------- 1567a8f87303f1833ebf1eb253b3add974bc4ae3 compiler/basicTypes/PatSyn.lhs | 18 ++++++++++---- compiler/deSugar/DsUtils.lhs | 4 +++- compiler/typecheck/TcPatSyn.lhs | 28 ++++++++++++---------- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_run/all.T | 1 + testsuite/tests/patsyn/should_run/match-unboxed.hs | 21 ++++++++++++++++ .../should_run/match-unboxed.stdout} | 2 ++ 7 files changed, 56 insertions(+), 19 deletions(-) diff --git a/compiler/basicTypes/PatSyn.lhs b/compiler/basicTypes/PatSyn.lhs index 2081b5a..1b78dac 100644 --- a/compiler/basicTypes/PatSyn.lhs +++ b/compiler/basicTypes/PatSyn.lhs @@ -130,11 +130,19 @@ data PatSyn -- See Note [Matchers and wrappers for pattern synonyms] psMatcher :: Id, - -- Matcher function, of type - -- forall r univ_tvs. req_theta - -- => res_ty - -- -> (forall ex_tvs. prov_theta -> arg_tys -> r) - -- -> r -> r + -- Matcher function. If psArgs is empty, then it has type + -- forall (r :: ?) univ_tvs. req_theta + -- => res_ty + -- -> (forall ex_tvs. prov_theta -> Void# -> r) + -- -> (Void# -> r) + -- -> r + -- + -- Otherwise: + -- forall (r :: ?) univ_tvs. req_theta + -- => res_ty + -- -> (forall ex_tvs. prov_theta -> arg_tys -> r) + -- -> (Void# -> r) + -- -> r psWrapper :: Maybe Id -- Nothing => uni-directional pattern synonym diff --git a/compiler/deSugar/DsUtils.lhs b/compiler/deSugar/DsUtils.lhs index a269374..d36e4c9 100644 --- a/compiler/deSugar/DsUtils.lhs +++ b/compiler/deSugar/DsUtils.lhs @@ -348,13 +348,15 @@ mkPatSynCase var ty alt fail = do matcher <- dsLExpr $ mkLHsWrap wrapper $ nlHsTyApp matcher [ty] let MatchResult _ mkCont = match_result cont <- mkCoreLams bndrs <$> mkCont fail - return $ mkCoreAppsDs matcher [Var var, cont, fail] + return $ mkCoreAppsDs matcher [Var var, ensure_unstrict cont, make_unstrict fail] where MkCaseAlt{ alt_pat = psyn, alt_bndrs = bndrs, alt_wrapper = wrapper, alt_result = match_result} = alt matcher = patSynMatcher psyn + ensure_unstrict = if null (patSynArgs psyn) then make_unstrict else id + make_unstrict = Lam voidArgId mkDataConCase :: Id -> Type -> [CaseAlt DataCon] -> MatchResult mkDataConCase _ _ [] = panic "mkDataConCase: no alternatives" diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 9b2b511..2372a1b 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -24,12 +24,12 @@ import Outputable import FastString import Var import Id -import IdInfo( IdDetails( VanillaId ) ) import TcBinds import BasicTypes import TcSimplify import TcType import VarSet +import MkId #if __GLASGOW_HASKELL__ < 709 import Data.Monoid #endif @@ -124,25 +124,29 @@ tcPatSynMatcher :: Located Name -> TcM (Id, LHsBinds Id) -- See Note [Matchers and wrappers for pattern synonyms] in PatSyn tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_dicts prov_theta req_theta pat_ty - = do { res_tv <- zonkQuantifiedTyVar =<< newFlexiTyVar liftedTypeKind + = do { res_tv <- do + { uniq <- newUnique + ; let tv_name = mkInternalName uniq (mkTyVarOcc "r") loc + ; return $ mkTcTyVar tv_name openTypeKind (SkolemTv False) } ; matcher_name <- newImplicitBinder name mkMatcherOcc ; let res_ty = TyVarTy res_tv + cont_args = if null args then [voidPrimId] else args cont_ty = mkSigmaTy ex_tvs prov_theta $ - mkFunTys (map varType args) res_ty + mkFunTys (map varType cont_args) res_ty + fail_ty = mkFunTy voidPrimTy res_ty - ; let matcher_tau = mkFunTys [pat_ty, cont_ty, res_ty] res_ty + ; let matcher_tau = mkFunTys [pat_ty, cont_ty, fail_ty] res_ty matcher_sigma = mkSigmaTy (res_tv:univ_tvs) req_theta matcher_tau - matcher_id = mkExportedLocalId VanillaId matcher_name matcher_sigma + matcher_id = mkVanillaGlobal matcher_name matcher_sigma ; traceTc "tcPatSynMatcher" (ppr name $$ ppr (idType matcher_id)) ; let matcher_lid = L loc matcher_id ; scrutinee <- mkId "scrut" pat_ty ; cont <- mkId "cont" cont_ty - ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ args) - ; fail <- mkId "fail" res_ty - ; let fail' = nlHsVar fail - + ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ cont_args) + ; fail <- mkId "fail" fail_ty + ; let fail' = nlHsApps fail [nlHsVar voidPrimId] ; let args = map nlVarPat [scrutinee, cont, fail] lwpat = noLoc $ WildPat pat_ty @@ -185,9 +189,7 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; return (matcher_id, matcher_bind) } where - mkId s ty = do - name <- newName . mkVarOccFS . fsLit $ s - return $ mkLocalId name ty + mkId s ty = mkSysLocalM (fsLit s) ty isBidirectional :: HsPatSynDir a -> Bool isBidirectional Unidirectional = False @@ -243,7 +245,7 @@ mkPatSynWrapperId (L _ name) args univ_tvs ex_tvs theta pat_ty wrapper_sigma = mkSigmaTy wrapper_tvs wrapper_theta wrapper_tau ; wrapper_name <- newImplicitBinder name mkDataConWrapperOcc - ; return $ mkExportedLocalId VanillaId wrapper_name wrapper_sigma } + ; return $ mkVanillaGlobal wrapper_name wrapper_sigma } mkPatSynWrapper :: Id -> HsBind Name diff --git a/testsuite/.gitignore b/testsuite/.gitignore index ce5c2c2..2423e15 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -1097,6 +1097,7 @@ mk/ghcconfig*_inplace_bin_ghc-stage2.exe.mk /tests/patsyn/should_run/ex-prov /tests/patsyn/should_run/ex-prov-run /tests/patsyn/should_run/match +/tests/patsyn/should_run/match-unboxed /tests/perf/compiler/T1969.comp.stats /tests/perf/compiler/T3064.comp.stats /tests/perf/compiler/T3294.comp.stats diff --git a/testsuite/tests/patsyn/should_run/all.T b/testsuite/tests/patsyn/should_run/all.T index b3c6b74..442dd43 100644 --- a/testsuite/tests/patsyn/should_run/all.T +++ b/testsuite/tests/patsyn/should_run/all.T @@ -3,3 +3,4 @@ test('match', normal, compile_and_run, ['']) test('ex-prov-run', normal, compile_and_run, ['']) test('bidir-explicit', normal, compile_and_run, ['']) test('bidir-explicit-scope', normal, compile_and_run, ['']) +test('match-unboxed', normal, compile_and_run, ['']) diff --git a/testsuite/tests/patsyn/should_run/match-unboxed.hs b/testsuite/tests/patsyn/should_run/match-unboxed.hs new file mode 100644 index 0000000..ec6de0c --- /dev/null +++ b/testsuite/tests/patsyn/should_run/match-unboxed.hs @@ -0,0 +1,21 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module Main where + +import GHC.Base + +pattern P1 <- 0# +pattern P2 <- 1# + +f :: Int# -> Int# +f P1 = 42# +f P2 = 44# + +g :: Int# -> Int +g P1 = 42 +g P2 = 44 + +main = do + print $ I# (f 0#) + print $ I# (f 1#) + print $ g 0# + print $ g 1# diff --git a/testsuite/tests/array/should_run/arr020.stdout b/testsuite/tests/patsyn/should_run/match-unboxed.stdout similarity index 50% copy from testsuite/tests/array/should_run/arr020.stdout copy to testsuite/tests/patsyn/should_run/match-unboxed.stdout index daaac9e..da4a47e 100644 --- a/testsuite/tests/array/should_run/arr020.stdout +++ b/testsuite/tests/patsyn/should_run/match-unboxed.stdout @@ -1,2 +1,4 @@ 42 +44 42 +44 From git at git.haskell.org Thu Nov 6 13:46:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 13:46:22 +0000 (UTC) Subject: [commit: ghc] wip/T9732: #WIP #STASH (0b718e5) Message-ID: <20141106134622.68C693A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/0b718e5e600d6988a3937eeccaf416e30f276348/ghc >--------------------------------------------------------------- commit 0b718e5e600d6988a3937eeccaf416e30f276348 Author: Dr. ERDI Gergo Date: Thu Nov 6 21:44:44 2014 +0800 #WIP #STASH >--------------------------------------------------------------- 0b718e5e600d6988a3937eeccaf416e30f276348 compiler/basicTypes/PatSyn.lhs | 29 ++++++++++---- compiler/iface/BuildTyCl.lhs | 6 +-- compiler/iface/IfaceSyn.lhs | 15 ++++--- compiler/iface/MkIface.lhs | 12 +++--- compiler/iface/TcIface.lhs | 16 ++++---- compiler/typecheck/TcBinds.lhs | 8 +++- compiler/typecheck/TcPatSyn.lhs | 89 +++++++++++++++++++++++++++-------------- 7 files changed, 113 insertions(+), 62 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0b718e5e600d6988a3937eeccaf416e30f276348 From git at git.haskell.org Thu Nov 6 14:01:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 14:01:19 +0000 (UTC) Subject: [commit: ghc] master: Move expansion of 'assert' from renamer to typechecker (0f930ba) Message-ID: <20141106140119.6B73B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0f930ba2039e28d0083780a58adb37ff01a92019/ghc >--------------------------------------------------------------- commit 0f930ba2039e28d0083780a58adb37ff01a92019 Author: Simon Peyton Jones Date: Thu Nov 6 13:59:42 2014 +0000 Move expansion of 'assert' from renamer to typechecker This improves error messages when there is a type error, fixing Trac #9774 >--------------------------------------------------------------- 0f930ba2039e28d0083780a58adb37ff01a92019 compiler/rename/RnExpr.lhs | 38 +--------- compiler/typecheck/TcExpr.lhs | 86 +++++++++++++++------- testsuite/tests/typecheck/should_fail/T9774.hs | 5 ++ testsuite/tests/typecheck/should_fail/T9774.stderr | 8 ++ testsuite/tests/typecheck/should_fail/all.T | 1 + 5 files changed, 74 insertions(+), 64 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0f930ba2039e28d0083780a58adb37ff01a92019 From git at git.haskell.org Thu Nov 6 15:42:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 15:42:34 +0000 (UTC) Subject: [commit: ghc] master: Remove unused tyConsOfDataCon (030abf9) Message-ID: <20141106154234.E52403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/030abf9e059cb1382df14c878a74e6709d744c17/ghc >--------------------------------------------------------------- commit 030abf9e059cb1382df14c878a74e6709d744c17 Author: Simon Peyton Jones Date: Thu Nov 6 13:16:20 2014 +0000 Remove unused tyConsOfDataCon >--------------------------------------------------------------- 030abf9e059cb1382df14c878a74e6709d744c17 compiler/basicTypes/DataCon.lhs | 14 -------------- compiler/vectorise/Vectorise/Type/Classify.hs | 2 +- 2 files changed, 1 insertion(+), 15 deletions(-) diff --git a/compiler/basicTypes/DataCon.lhs b/compiler/basicTypes/DataCon.lhs index fa9e2e9..95969df 100644 --- a/compiler/basicTypes/DataCon.lhs +++ b/compiler/basicTypes/DataCon.lhs @@ -34,8 +34,6 @@ module DataCon ( splitDataProductType_maybe, - tyConsOfTyCon, - -- ** Predicates on DataCons isNullarySrcDataCon, isNullaryRepDataCon, isTupleDataCon, isUnboxedTupleCon, isVanillaDataCon, classDataCon, dataConCannotMatch, @@ -67,7 +65,6 @@ import BasicTypes import FastString import Module import VarEnv -import NameEnv import qualified Data.Data as Data import qualified Data.Typeable @@ -1126,15 +1123,4 @@ splitDataProductType_maybe ty = Just (tycon, ty_args, con, dataConInstArgTys con ty_args) | otherwise = Nothing - --- | All type constructors used in the definition of this type constructor, --- recursively. This is used to find out all the type constructors whose data --- constructors need to be in scope to be allowed to safely coerce under this --- type constructor in Safe Haskell mode. -tyConsOfTyCon :: TyCon -> [TyCon] -tyConsOfTyCon tc = nameEnvElts (add tc emptyNameEnv) - where - go env tc = foldr add env (tyConDataCons tc >>= dataConOrigArgTys >>= tyConsOfType) - add tc env | tyConName tc `elemNameEnv` env = env - | otherwise = go (extendNameEnv env (tyConName tc) tc) tc \end{code} diff --git a/compiler/vectorise/Vectorise/Type/Classify.hs b/compiler/vectorise/Vectorise/Type/Classify.hs index 56b8da5..dcc41dd 100644 --- a/compiler/vectorise/Vectorise/Type/Classify.hs +++ b/compiler/vectorise/Vectorise/Type/Classify.hs @@ -21,7 +21,7 @@ where import NameSet import UniqSet import UniqFM -import DataCon hiding (tyConsOfTyCon) +import DataCon import TyCon import TypeRep import Type hiding (tyConsOfType) From git at git.haskell.org Thu Nov 6 15:42:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 15:42:37 +0000 (UTC) Subject: [commit: ghc] master: Make tyConsOfType return a (NameEnv TyCon) rather than [TyCon] (e7523fe) Message-ID: <20141106154237.8CCA83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e7523fe73e938956aa31ad07a97e9f8ef87a4e0c/ghc >--------------------------------------------------------------- commit e7523fe73e938956aa31ad07a97e9f8ef87a4e0c Author: Simon Peyton Jones Date: Thu Nov 6 13:18:16 2014 +0000 Make tyConsOfType return a (NameEnv TyCon) rather than [TyCon] A little refactoring >--------------------------------------------------------------- e7523fe73e938956aa31ad07a97e9f8ef87a4e0c compiler/basicTypes/NameEnv.lhs | 8 ++++++-- compiler/typecheck/TcFlatten.lhs | 2 +- compiler/typecheck/TcTyDecls.lhs | 13 +++++-------- compiler/types/Type.lhs | 4 ++-- 4 files changed, 14 insertions(+), 13 deletions(-) diff --git a/compiler/basicTypes/NameEnv.lhs b/compiler/basicTypes/NameEnv.lhs index 1fe908b..f86e174 100644 --- a/compiler/basicTypes/NameEnv.lhs +++ b/compiler/basicTypes/NameEnv.lhs @@ -15,10 +15,10 @@ module NameEnv ( emptyNameEnv, unitNameEnv, nameEnvElts, nameEnvUniqueElts, extendNameEnv_C, extendNameEnv_Acc, extendNameEnv, extendNameEnvList, extendNameEnvList_C, - foldNameEnv, filterNameEnv, + foldNameEnv, filterNameEnv, anyNameEnv, plusNameEnv, plusNameEnv_C, alterNameEnv, lookupNameEnv, lookupNameEnv_NF, delFromNameEnv, delListFromNameEnv, - elemNameEnv, mapNameEnv, + elemNameEnv, mapNameEnv, disjointNameEnv, -- ** Dependency analysis depAnal @@ -88,7 +88,9 @@ lookupNameEnv :: NameEnv a -> Name -> Maybe a lookupNameEnv_NF :: NameEnv a -> Name -> a foldNameEnv :: (a -> b -> b) -> b -> NameEnv a -> b filterNameEnv :: (elt -> Bool) -> NameEnv elt -> NameEnv elt +anyNameEnv :: (elt -> Bool) -> NameEnv elt -> Bool mapNameEnv :: (elt1 -> elt2) -> NameEnv elt1 -> NameEnv elt2 +disjointNameEnv :: NameEnv a -> NameEnv a -> Bool nameEnvElts x = eltsUFM x emptyNameEnv = emptyUFM @@ -110,6 +112,8 @@ extendNameEnvList_C x y z = addListToUFM_C x y z delFromNameEnv x y = delFromUFM x y delListFromNameEnv x y = delListFromUFM x y filterNameEnv x y = filterUFM x y +anyNameEnv f x = foldUFM ((||) . f) False x +disjointNameEnv x y = isNullUFM (intersectUFM x y) lookupNameEnv_NF env n = expectJust "lookupNameEnv_NF" (lookupNameEnv env n) \end{code} diff --git a/compiler/typecheck/TcFlatten.lhs b/compiler/typecheck/TcFlatten.lhs index 02783a9..dcfdd1b 100644 --- a/compiler/typecheck/TcFlatten.lhs +++ b/compiler/typecheck/TcFlatten.lhs @@ -626,7 +626,7 @@ flatten fmode (TyConApp tc tys) | Just (tenv, rhs, tys') <- tcExpandTyCon_maybe tc tys , let expanded_ty = mkAppTys (substTy (mkTopTvSubst tenv) rhs) tys' = case fe_mode fmode of - FM_FlattenAll | any isSynFamilyTyCon (tyConsOfType rhs) + FM_FlattenAll | anyNameEnv isSynFamilyTyCon (tyConsOfType rhs) -> flatten fmode expanded_ty | otherwise -> flattenTyConApp fmode tc tys diff --git a/compiler/typecheck/TcTyDecls.lhs b/compiler/typecheck/TcTyDecls.lhs index ee26641..f2c2395 100644 --- a/compiler/typecheck/TcTyDecls.lhs +++ b/compiler/typecheck/TcTyDecls.lhs @@ -422,14 +422,11 @@ calcRecFlags boot_details is_boot mrole_env tyclss nt_edges = [(t, mk_nt_edges t) | t <- new_tycons] mk_nt_edges nt -- Invariant: nt is a newtype - = concatMap (mk_nt_edges1 nt) (tyConsOfType (new_tc_rhs nt)) + = [ tc | tc <- nameEnvElts (tyConsOfType (new_tc_rhs nt)) -- tyConsOfType looks through synonyms - - mk_nt_edges1 _ tc - | tc `elem` new_tycons = [tc] -- Loop - -- At this point we know that either it's a local *data* type, - -- or it's imported. Either way, it can't form part of a newtype cycle - | otherwise = [] + , tc `elem` new_tycons ] + -- If not (tc `elem` new_tycons) we know that either it's a local *data* type, + -- or it's imported. Either way, it can't form part of a newtype cycle --------------- Product types ---------------------- prod_loop_breakers = mkNameSet (findLoopBreakers prod_edges) @@ -439,7 +436,7 @@ calcRecFlags boot_details is_boot mrole_env tyclss mk_prod_edges tc -- Invariant: tc is a product tycon = concatMap (mk_prod_edges1 tc) (dataConOrigArgTys (head (tyConDataCons tc))) - mk_prod_edges1 ptc ty = concatMap (mk_prod_edges2 ptc) (tyConsOfType ty) + mk_prod_edges1 ptc ty = concatMap (mk_prod_edges2 ptc) (nameEnvElts (tyConsOfType ty)) mk_prod_edges2 ptc tc | tc `elem` prod_tycons = [tc] -- Local product diff --git a/compiler/types/Type.lhs b/compiler/types/Type.lhs index 8cad95e..01ec26c 100644 --- a/compiler/types/Type.lhs +++ b/compiler/types/Type.lhs @@ -662,9 +662,9 @@ repType ty -- | All type constructors occurring in the type; looking through type -- synonyms, but not newtypes. -- When it finds a Class, it returns the class TyCon. -tyConsOfType :: Type -> [TyCon] +tyConsOfType :: Type -> NameEnv TyCon tyConsOfType ty - = nameEnvElts (go ty) + = go ty where go :: Type -> NameEnv TyCon -- The NameEnv does duplicate elim go ty | Just ty' <- tcView ty = go ty' From git at git.haskell.org Thu Nov 6 15:42:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 15:42:40 +0000 (UTC) Subject: [commit: ghc] master: Comments and white space only (f81f82e) Message-ID: <20141106154240.586613A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f81f82eec0123e16bfa8677117107c3f3c4f0fe0/ghc >--------------------------------------------------------------- commit f81f82eec0123e16bfa8677117107c3f3c4f0fe0 Author: Simon Peyton Jones Date: Thu Nov 6 13:34:25 2014 +0000 Comments and white space only >--------------------------------------------------------------- f81f82eec0123e16bfa8677117107c3f3c4f0fe0 compiler/typecheck/TcRnTypes.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index 83f9a40..db326d6 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -1624,7 +1624,7 @@ subGoalDepthExceeded (SubGoalDepth mc mf) (SubGoalDepth c f) \end{code} Note [Preventing recursive dictionaries] - +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We have some classes where it is not very useful to build recursive dictionaries (Coercible, at the moment). So we need the constraint solver to prevent that. We conservatively ensure this property using the subgoal depth of From git at git.haskell.org Thu Nov 6 15:42:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 15:42:42 +0000 (UTC) Subject: [commit: ghc] master: Give T3064 the right module name (just tidying up) (528cbd7) Message-ID: <20141106154242.EB0743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/528cbd72d4d15886c3e675d8280cbb0fe91413bd/ghc >--------------------------------------------------------------- commit 528cbd72d4d15886c3e675d8280cbb0fe91413bd Author: Simon Peyton Jones Date: Thu Nov 6 13:35:09 2014 +0000 Give T3064 the right module name (just tidying up) >--------------------------------------------------------------- 528cbd72d4d15886c3e675d8280cbb0fe91413bd testsuite/tests/perf/compiler/T3064.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/T3064.hs b/testsuite/tests/perf/compiler/T3064.hs index d3cdea3..39a51de 100644 --- a/testsuite/tests/perf/compiler/T3064.hs +++ b/testsuite/tests/perf/compiler/T3064.hs @@ -1,6 +1,6 @@ {-# LANGUAGE Rank2Types, TypeSynonymInstances, FlexibleInstances #-} {-# LANGUAGE TypeFamilies, GeneralizedNewtypeDeriving #-} -module Bug2 where +module T3064 where import Control.Applicative newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a } From git at git.haskell.org Thu Nov 6 15:42:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 15:42:45 +0000 (UTC) Subject: [commit: ghc] master: Switch off lazy flattening (fix Trac #3064) (096b7e6) Message-ID: <20141106154245.9496A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/096b7e664351d102cc9e15f3aa226a976af5dae2/ghc >--------------------------------------------------------------- commit 096b7e664351d102cc9e15f3aa226a976af5dae2 Author: Simon Peyton Jones Date: Thu Nov 6 13:46:47 2014 +0000 Switch off lazy flattening (fix Trac #3064) See Note [Lazy flattening] in TcFlatten. Lazy flattening was an apparently good idea which actually made the type inference engine go a LOTS slower in T3064. So I switched it off again. >--------------------------------------------------------------- 096b7e664351d102cc9e15f3aa226a976af5dae2 compiler/typecheck/TcBinds.lhs | 5 ++- compiler/typecheck/TcCanonical.lhs | 4 +- compiler/typecheck/TcFlatten.lhs | 43 ++++++++++++++++++---- .../tests/indexed-types/should_fail/T2664.stderr | 18 +++++---- .../tests/indexed-types/should_fail/T7010.stderr | 2 +- .../tests/indexed-types/should_fail/T8518.stderr | 15 ++++++++ testsuite/tests/perf/compiler/all.T | 8 ++-- 7 files changed, 72 insertions(+), 23 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 096b7e664351d102cc9e15f3aa226a976af5dae2 From git at git.haskell.org Thu Nov 6 15:42:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 15:42:48 +0000 (UTC) Subject: [commit: ghc] master: Minor refacoring and trace-message printing (cb6ccad) Message-ID: <20141106154248.3C1703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cb6ccadf78eba0a36742d4f99eda41c1464fbec6/ghc >--------------------------------------------------------------- commit cb6ccadf78eba0a36742d4f99eda41c1464fbec6 Author: Simon Peyton Jones Date: Thu Nov 6 13:48:48 2014 +0000 Minor refacoring and trace-message printing >--------------------------------------------------------------- cb6ccadf78eba0a36742d4f99eda41c1464fbec6 compiler/typecheck/TcInteract.lhs | 5 ++--- compiler/typecheck/TcSMonad.lhs | 44 ++++++++++++++++++++------------------- 2 files changed, 25 insertions(+), 24 deletions(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 4884f1f..6947569 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -128,8 +128,7 @@ solveFlatGivens loc givens solveFlatWanteds :: Cts -> TcS WantedConstraints solveFlatWanteds wanteds = do { solveFlats wanteds - ; unsolved_implics <- getWorkListImplics - ; (tv_eqs, fun_eqs, insols, others) <- getUnsolvedInerts + ; (implics, tv_eqs, fun_eqs, insols, others) <- getUnsolvedInerts ; unflattened_eqs <- unflatten tv_eqs fun_eqs -- See Note [Unflatten after solving the flat wanteds] @@ -137,7 +136,7 @@ solveFlatWanteds wanteds -- Postcondition is that the wl_flats are zonked ; return (WC { wc_flat = zonked , wc_insol = insols - , wc_impl = unsolved_implics }) } + , wc_impl = implics }) } -- The main solver loop implements Note [Basic Simplifier Plan] --------------------------------------------------------------- diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index 4d910d9..c539c1e 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -12,7 +12,7 @@ module TcSMonad ( extendWorkListCts, appendWorkList, selectWorkItem, workListSize, - updWorkListTcS, updWorkListTcS_return, getWorkListImplics, + updWorkListTcS, updWorkListTcS_return, updInertCans, updInertDicts, updInertIrreds, updInertFunEqs, @@ -49,7 +49,7 @@ module TcSMonad ( maybeSym, newTcEvBinds, newWantedEvVar, newWantedEvVarNC, newWantedEvVarNonrec, - newEvVar, newGivenEvVar, newDerived, + newEvVar, newGivenEvVar, emitNewDerived, emitNewDerivedEq, instDFunConstraints, @@ -292,7 +292,7 @@ instance Outputable WorkList where , ppUnless (isEmptyDeque feqs) $ ptext (sLit "Funeqs =") <+> vcat (map ppr (dequeList feqs)) , ppUnless (null rest) $ - ptext (sLit "Eqs =") <+> vcat (map ppr rest) + ptext (sLit "Non-eqs =") <+> vcat (map ppr rest) , ppUnless (isEmptyBag implics) $ ptext (sLit "Implics =") <+> vcat (map ppr (bagToList implics)) ]) @@ -440,20 +440,21 @@ data InertSet \begin{code} instance Outputable InertCans where ppr ics = vcat [ ptext (sLit "Equalities:") - <+> vcat (map ppr (varEnvElts (inert_eqs ics))) + <+> pprCts (foldVarEnv (\eqs rest -> listToBag eqs `andCts` rest) + emptyCts (inert_eqs ics)) , ptext (sLit "Type-function equalities:") - <+> vcat (map ppr (funEqsToList (inert_funeqs ics))) + <+> pprCts (funEqsToBag (inert_funeqs ics)) , ptext (sLit "Dictionaries:") - <+> vcat (map ppr (Bag.bagToList $ dictsToBag (inert_dicts ics))) + <+> pprCts (dictsToBag (inert_dicts ics)) , ptext (sLit "Irreds:") - <+> vcat (map ppr (Bag.bagToList $ inert_irreds ics)) + <+> pprCts (inert_irreds ics) , text "Insolubles =" <+> -- Clearly print frozen errors braces (vcat (map ppr (Bag.bagToList $ inert_insols ics))) ] instance Outputable InertSet where ppr is = vcat [ ppr $ inert_cans is - , text "Solved dicts" <+> int (sizeDictMap (inert_solved_dicts is)) ] + , text "Solved dicts" <+> vcat (map ppr (bagToList (dictsToBag (inert_solved_dicts is)))) ] emptyInert :: InertSet emptyInert @@ -605,7 +606,8 @@ getInertEqs :: TcS (TyVarEnv EqualCtList) getInertEqs = do { inert <- getTcSInerts ; return (inert_eqs (inert_cans inert)) } -getUnsolvedInerts :: TcS ( Cts -- Tyvar eqs: a ~ ty +getUnsolvedInerts :: TcS ( Bag Implication + , Cts -- Tyvar eqs: a ~ ty , Cts -- Fun eqs: F a ~ ty , Cts -- Insoluble , Cts ) -- All others @@ -621,7 +623,9 @@ getUnsolvedInerts unsolved_dicts = foldDicts add_if_unsolved idicts emptyCts others = unsolved_irreds `unionBags` unsolved_dicts - ; return ( unsolved_tv_eqs, unsolved_fun_eqs, insols, others) } + ; implics <- getWorkListImplics + + ; return ( implics, unsolved_tv_eqs, unsolved_fun_eqs, insols, others) } -- Keep even the given insolubles -- so that we can report dead GADT pattern match branches where @@ -856,8 +860,8 @@ type DictMap a = TcAppMap a emptyDictMap :: DictMap a emptyDictMap = emptyTcAppMap -sizeDictMap :: DictMap a -> Int -sizeDictMap m = foldDicts (\ _ x -> x+1) m 0 +-- sizeDictMap :: DictMap a -> Int +-- sizeDictMap m = foldDicts (\ _ x -> x+1) m 0 findDict :: DictMap a -> Class -> [Type] -> Maybe a findDict m cls tys = findTcApp m (getUnique cls) tys @@ -916,8 +920,8 @@ findFunEq m tc tys = findTcApp m (getUnique tc) tys findFunEqs :: FunEqMap a -> TyCon -> [Type] -> Maybe a findFunEqs m tc tys = findTcApp m (getUnique tc) tys -funEqsToList :: FunEqMap a -> [a] -funEqsToList m = foldTcAppMap (:) m [] +funEqsToBag :: FunEqMap a -> Bag a +funEqsToBag m = foldTcAppMap consBag m emptyBag findFunEqsByTyCon :: FunEqMap a -> TyCon -> [a] -- Get inert function equation constraints that have the given tycon @@ -1582,13 +1586,11 @@ emitNewDerivedEq loc (Pair ty1 ty2) emitNewDerived :: CtLoc -> TcPredType -> TcS () -- Create new Derived and put it in the work list emitNewDerived loc pred - = do { mb_ct <- lookupInInerts pred - ; case mb_ct of - Just {} -> return () - Nothing -> do { traceTcS "Emitting [D]" (ppr der_ct) - ; updWorkListTcS (extendWorkListCt der_ct) } } - where - der_ct = mkNonCanonical (CtDerived { ctev_pred = pred, ctev_loc = loc }) + = do { mb_ev <- newDerived loc pred + ; case mb_ev of + Nothing -> return () + Just ev -> do { traceTcS "Emitting [D]" (ppr ev) + ; updWorkListTcS (extendWorkListCt (mkNonCanonical ev)) } } newDerived :: CtLoc -> TcPredType -> TcS (Maybe CtEvidence) -- Returns Nothing if cached, From git at git.haskell.org Thu Nov 6 15:42:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 15:42:50 +0000 (UTC) Subject: [commit: ghc] master: Wibbles to notes (ec38deb) Message-ID: <20141106154250.D87153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ec38deb243671216aea3fef9aaa2decb8e02f6b0/ghc >--------------------------------------------------------------- commit ec38deb243671216aea3fef9aaa2decb8e02f6b0 Author: Simon Peyton Jones Date: Thu Nov 6 13:55:05 2014 +0000 Wibbles to notes >--------------------------------------------------------------- ec38deb243671216aea3fef9aaa2decb8e02f6b0 compiler/typecheck/Flattening-notes | 35 ++--------------------------------- 1 file changed, 2 insertions(+), 33 deletions(-) diff --git a/compiler/typecheck/Flattening-notes b/compiler/typecheck/Flattening-notes index ec4565c..499a757 100644 --- a/compiler/typecheck/Flattening-notes +++ b/compiler/typecheck/Flattening-notes @@ -1,40 +1,9 @@ ToDo: -* get rid of getEvTerm? - * inert_funeqs, inert_eqs: keep only the CtEvidence. They are all CFunEqCans, CTyEqCans -* Consider individual data tpyes for CFunEqCan etc - -* Collapes CNonCanonical and CIrredCan - -Remaining errors -============================ -Unexpected failures: - generics GenDerivOutput1_1 [stderr mismatch] (normal) - -ghcirun002: internal error: ASSERTION FAILED: file rts/Interpreter.c, line 773 - ghci/should_run ghcirun002 [bad exit code] (ghci) - --package dependencies: array-0.5.0.1 at array_GX4NwjS8xZkC2ZPtjgwhnz -+package dependencies: array-0.5.0.1 base-4.8.0.0 - safeHaskell/check/pkg01 safePkg01 [bad stdout] (normal) - - -Wierd looking pattern synonym thing - ghci/scripts T8776 [bad stdout] (ghci) - patsyn/should_fail mono [stderr mismatch] (normal) - -Derived equalities fmv1 ~ Maybe a, fmv2 ~ Maybe b - indexed-types/should_fail T4093a [stderr mismatch] (normal) - -Not sure - indexed-types/should_fail ExtraTcsUntch [stderr mismatch] (normal) - -Order of finding iprovements - typecheck/should_compile TcTypeNatSimple [exit code non-0] (normal) - +* Consider individual data types for CFunEqCan etc +* Collapse CNonCanonical and CIrredCan ------------------ From git at git.haskell.org Thu Nov 6 15:42:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 15:42:53 +0000 (UTC) Subject: [commit: ghc] master: Allow the solved dictionaries to propagate from outside in (c945477) Message-ID: <20141106154253.86A843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c945477fba81b541b5a9c59d982447b862f601f4/ghc >--------------------------------------------------------------- commit c945477fba81b541b5a9c59d982447b862f601f4 Author: Simon Peyton Jones Date: Thu Nov 6 13:54:20 2014 +0000 Allow the solved dictionaries to propagate from outside in See Note [Propagate solved dictionaries] in TcSMonad. This can signficantly reduce the number of solver steps. >--------------------------------------------------------------- c945477fba81b541b5a9c59d982447b862f601f4 compiler/typecheck/TcSMonad.lhs | 29 ++++++++++++++++++++++++++--- 1 file changed, 26 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index c539c1e..0b3b9d8 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -1165,8 +1165,9 @@ recoverTcS (TcS recovery_code) (TcS thing_inside) nestTcS :: TcS a -> TcS a -- Use the current untouchables, augmenting the current --- evidence bindings, and solved caches --- But have no effect on the InertCans or insolubles +-- evidence bindings, and solved dictionaries +-- But have no effect on the InertCans, or on the inert_flat_cache +-- (the latter because the thing inside a nestTcS does unflattening) nestTcS (TcS thing_inside) = TcS $ \ env@(TcSEnv { tcs_inerts = inerts_var }) -> do { inerts <- TcM.readTcRef inerts_var @@ -1174,7 +1175,14 @@ nestTcS (TcS thing_inside) ; new_wl_var <- TcM.newTcRef emptyWorkList ; let nest_env = env { tcs_inerts = new_inert_var , tcs_worklist = new_wl_var } - ; thing_inside nest_env } + + ; res <- thing_inside nest_env + + ; new_inerts <- TcM.readTcRef new_inert_var + ; TcM.writeTcRef inerts_var -- See Note [Propagate the solved dictionaries] + (inerts { inert_solved_dicts = inert_solved_dicts new_inerts }) + + ; return res } tryTcS :: TcS a -> TcS a -- Like runTcS, but from within the TcS monad @@ -1191,7 +1199,21 @@ tryTcS (TcS thing_inside) , tcs_inerts = is_var , tcs_worklist = wl_var } ; thing_inside nest_env } +\end{code} + +Note [Propagate the solved dictionaries] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +It's really quite important that nestTcS does not discard the solved +dictionaries from the thing_inside. +Consider + Eq [a] + forall b. empty => Eq [a] +We solve the flat (Eq [a]), under nestTcS, and then turn our attention to +the implications. It's definitely fine to use the solved dictionaries on +the inner implications, and it can make a signficant performance difference +if you do so. +\begin{code} -- Getters and setters of TcEnv fields -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1365,6 +1387,7 @@ zonkFlats :: Cts -> TcS Cts zonkFlats cts = wrapTcS (TcM.zonkFlats cts) \end{code} + Note [Do not add duplicate derived insolubles] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ In general we *must* add an insoluble (Int ~ Bool) even if there is From git at git.haskell.org Thu Nov 6 15:42:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 15:42:56 +0000 (UTC) Subject: [commit: ghc] master: Refactor the code that prevents recursion among Coercible constraints (203cf0e) Message-ID: <20141106154256.449AC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/203cf0e46b1cd0880db81d1129d27b18460359c3/ghc >--------------------------------------------------------------- commit 203cf0e46b1cd0880db81d1129d27b18460359c3 Author: Simon Peyton Jones Date: Thu Nov 6 15:41:50 2014 +0000 Refactor the code that prevents recursion among Coercible constraints The main description is in Note [Preventing recursive dictionaries] in TcRnTypes, which applies only to Coercible dictionaries. But it was a bit of a mess: - It wasn't applied consistently - It was being applied to non-Coercible dictionaries in some places This patch tidies it up. This hack will largely go away when Richard starts treating Coercible constraints more like equalities than like dictionaries. >--------------------------------------------------------------- 203cf0e46b1cd0880db81d1129d27b18460359c3 compiler/typecheck/TcInteract.lhs | 8 +++--- compiler/typecheck/TcRnTypes.lhs | 29 ++++++++++++--------- compiler/typecheck/TcSMonad.lhs | 53 ++++++++++++++++++--------------------- 3 files changed, 44 insertions(+), 46 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 203cf0e46b1cd0880db81d1129d27b18460359c3 From git at git.haskell.org Thu Nov 6 15:45:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 15:45:53 +0000 (UTC) Subject: [commit: ghc] master: Re-enable T3064, which works now (c79cbac) Message-ID: <20141106154553.86DD83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c79cbacb6d9161c529ac13685ff29ac058a3ebfa/ghc >--------------------------------------------------------------- commit c79cbacb6d9161c529ac13685ff29ac058a3ebfa Author: Simon Peyton Jones Date: Thu Nov 6 15:46:11 2014 +0000 Re-enable T3064, which works now >--------------------------------------------------------------- c79cbacb6d9161c529ac13685ff29ac058a3ebfa testsuite/tests/perf/compiler/all.T | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index be2a12f..368753a 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -293,8 +293,7 @@ test('T3064', # # (amd64/Linux) (19/09/2014): 18744992, unknown # # (amd64/Linux) 2014-10-13: 13251728, Stricter seqDmdType - ### TEMPORARILY DISABLED due to https://ghc.haskell.org/trac/ghc/ticket/9771 - only_ways([]) # only_ways(['normal']) + only_ways(['normal']) ], compile, ['']) From git at git.haskell.org Thu Nov 6 19:20:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 19:20:50 +0000 (UTC) Subject: [commit: ghc] master: Better error messages for new per-instance overlap flags and Safe Haskell. (91c15d6) Message-ID: <20141106192050.54CDE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/91c15d65187c98bf7be5e71a247501f97611867a/ghc >--------------------------------------------------------------- commit 91c15d65187c98bf7be5e71a247501f97611867a Author: David Terei Date: Mon Aug 4 12:49:07 2014 -0400 Better error messages for new per-instance overlap flags and Safe Haskell. >--------------------------------------------------------------- 91c15d65187c98bf7be5e71a247501f97611867a compiler/main/HscMain.hs | 10 +++++++++- .../tests/safeHaskell/safeInfered/UnsafeInfered13.stderr | 2 ++ .../tests/safeHaskell/safeInfered/UnsafeInfered14.stderr | 2 ++ .../tests/safeHaskell/safeInfered/UnsafeInfered15.stderr | 2 ++ .../safeInfered/{UnsafeInfered15.hs => UnsafeInfered16.hs} | 6 ++++++ .../tests/safeHaskell/safeInfered/UnsafeInfered16.stderr | 13 +++++++++++++ testsuite/tests/safeHaskell/safeInfered/all.T | 1 + 7 files changed, 35 insertions(+), 1 deletion(-) diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index 3f4af8d..bec66f8 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -1025,13 +1025,21 @@ markUnsafe tcg_env whyUnsafe = do whyUnsafe' df = vcat [ quotes pprMod <+> text "has been inferred as unsafe!" , text "Reason:" , nest 4 $ (vcat $ badFlags df) $+$ - (vcat $ pprErrMsgBagWithLoc whyUnsafe) + (vcat $ pprErrMsgBagWithLoc whyUnsafe) $+$ + (vcat $ badInsts $ tcg_insts tcg_env) ] badFlags df = concat $ map (badFlag df) unsafeFlagsForInfer badFlag df (str,loc,on,_) | on df = [mkLocMessage SevOutput (loc df) $ text str <+> text "is not allowed in Safe Haskell"] | otherwise = [] + badInsts insts = concat $ map badInst insts + badInst ins | overlapMode (is_flag ins) /= NoOverlap + = [mkLocMessage SevOutput (nameSrcSpan $ getName $ is_dfun ins) $ + ppr (overlapMode $ is_flag ins) <+> + text "overlap mode isn't allowed in Safe Haskell"] + | otherwise = [] + -- | Figure out the final correct safe haskell mode hscGetSafeMode :: TcGblEnv -> Hsc SafeHaskellMode diff --git a/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered13.stderr b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered13.stderr index c545d40..30be0ec 100644 --- a/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered13.stderr +++ b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered13.stderr @@ -2,6 +2,8 @@ UnsafeInfered13.hs:1:16: Warning: ?UnsafeInfered13? has been inferred as unsafe! Reason: + UnsafeInfered13.hs:8:27: + [overlap ok] overlap mode isn't allowed in Safe Haskell : Failing due to -Werror. diff --git a/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered14.stderr b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered14.stderr index b7c41ac..80d9526 100644 --- a/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered14.stderr +++ b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered14.stderr @@ -2,6 +2,8 @@ UnsafeInfered14.hs:1:16: Warning: ?UnsafeInfered14? has been inferred as unsafe! Reason: + UnsafeInfered14.hs:8:31: + [overlappable] overlap mode isn't allowed in Safe Haskell : Failing due to -Werror. diff --git a/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered15.stderr b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered15.stderr index dbf2094..44a0202 100644 --- a/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered15.stderr +++ b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered15.stderr @@ -2,6 +2,8 @@ UnsafeInfered15.hs:1:16: Warning: ?UnsafeInfered15? has been inferred as unsafe! Reason: + UnsafeInfered15.hs:8:30: + [overlapping] overlap mode isn't allowed in Safe Haskell : Failing due to -Werror. diff --git a/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered15.hs b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered16.hs similarity index 63% copy from testsuite/tests/safeHaskell/safeInfered/UnsafeInfered15.hs copy to testsuite/tests/safeHaskell/safeInfered/UnsafeInfered16.hs index 427c97b..2df6576 100644 --- a/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered15.hs +++ b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered16.hs @@ -8,3 +8,9 @@ class C a where instance {-# OVERLAPPING #-} C a where f _ = "a" +instance {-# OVERLAPS #-} C Int where + f _ = "Int" + +instance {-# OVERLAPPABLE #-} C Bool where + f _ = "Bool" + diff --git a/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered16.stderr b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered16.stderr new file mode 100644 index 0000000..21674c4 --- /dev/null +++ b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered16.stderr @@ -0,0 +1,13 @@ + +UnsafeInfered16.hs:1:16: Warning: + ?UnsafeInfered15? has been inferred as unsafe! + Reason: + UnsafeInfered16.hs:8:30: + [overlapping] overlap mode isn't allowed in Safe Haskell + UnsafeInfered16.hs:11:27: + [overlap ok] overlap mode isn't allowed in Safe Haskell + UnsafeInfered16.hs:14:31: + [overlappable] overlap mode isn't allowed in Safe Haskell + +: +Failing due to -Werror. diff --git a/testsuite/tests/safeHaskell/safeInfered/all.T b/testsuite/tests/safeHaskell/safeInfered/all.T index 887ff68..a9600fa 100644 --- a/testsuite/tests/safeHaskell/safeInfered/all.T +++ b/testsuite/tests/safeHaskell/safeInfered/all.T @@ -63,6 +63,7 @@ test('UnsafeInfered12', normal, compile_fail, ['']) test('UnsafeInfered13', normal, compile_fail, ['']) test('UnsafeInfered14', normal, compile_fail, ['']) test('UnsafeInfered15', normal, compile_fail, ['']) +test('UnsafeInfered16', normal, compile_fail, ['']) # Mixed tests test('Mixed01', normal, compile_fail, ['']) From git at git.haskell.org Thu Nov 6 19:20:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 19:20:57 +0000 (UTC) Subject: [commit: ghc] master: Warn for Safe Haskell when -XOverlappingInstances or -XIncoherentInstances turned on. (f4ead30) Message-ID: <20141106192057.0100E3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f4ead30b96aa8faaf4d23815cc32f7adfadd28df/ghc >--------------------------------------------------------------- commit f4ead30b96aa8faaf4d23815cc32f7adfadd28df Author: David Terei Date: Mon Aug 4 17:43:09 2014 -0400 Warn for Safe Haskell when -XOverlappingInstances or -XIncoherentInstances turned on. >--------------------------------------------------------------- f4ead30b96aa8faaf4d23815cc32f7adfadd28df compiler/main/DynFlags.hs | 43 ++++++++++++++++------ compiler/typecheck/TcInstDcls.lhs | 3 +- .../safeHaskell/safeInfered/UnsafeInfered16.hs | 2 +- .../safeHaskell/safeInfered/UnsafeInfered16.stderr | 2 +- .../safeHaskell/safeInfered/UnsafeInfered17.hs | 2 +- .../safeHaskell/safeInfered/UnsafeInfered17.stderr | 2 +- .../safeHaskell/safeInfered/UnsafeInfered18.hs | 11 ++++++ .../safeHaskell/safeInfered/UnsafeInfered18.stderr | 11 ++++++ .../{UnsafeInfered14.hs => UnsafeInfered19.hs} | 5 ++- .../safeHaskell/safeInfered/UnsafeInfered19.stderr | 11 ++++++ testsuite/tests/safeHaskell/safeInfered/all.T | 2 + 11 files changed, 74 insertions(+), 20 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f4ead30b96aa8faaf4d23815cc32f7adfadd28df From git at git.haskell.org Thu Nov 6 19:20:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Nov 2014 19:20:53 +0000 (UTC) Subject: [commit: ghc] master: Add in Incoherent Instances test for Safe Haskell. (c96a613) Message-ID: <20141106192053.8BAA03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c96a613c98d07fab4facc77bdd0701b7a17d332a/ghc >--------------------------------------------------------------- commit c96a613c98d07fab4facc77bdd0701b7a17d332a Author: David Terei Date: Mon Aug 4 17:41:54 2014 -0400 Add in Incoherent Instances test for Safe Haskell. >--------------------------------------------------------------- c96a613c98d07fab4facc77bdd0701b7a17d332a .../safeInfered/{UnsafeInfered15.hs => UnsafeInfered17.hs} | 2 +- .../tests/safeHaskell/safeInfered/UnsafeInfered17.stderr | 9 +++++++++ testsuite/tests/safeHaskell/safeInfered/all.T | 1 + .../safeLanguage/{SafeLang10.hs => SafeLang17.hs} | 4 ++-- .../safeLanguage/{SafeLang10.stderr => SafeLang17.stderr} | 14 +++++++------- .../safeLanguage/{SafeLang10_A.hs => SafeLang17_A.hs} | 5 ++--- .../safeLanguage/{SafeLang09_B.hs => SafeLang17_B.hs} | 7 ++++--- testsuite/tests/safeHaskell/safeLanguage/all.T | 5 +++++ 8 files changed, 31 insertions(+), 16 deletions(-) diff --git a/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered15.hs b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered17.hs similarity index 80% copy from testsuite/tests/safeHaskell/safeInfered/UnsafeInfered15.hs copy to testsuite/tests/safeHaskell/safeInfered/UnsafeInfered17.hs index 427c97b..04591b5 100644 --- a/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered15.hs +++ b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered17.hs @@ -5,6 +5,6 @@ module UnsafeInfered15 where class C a where f :: a -> String -instance {-# OVERLAPPING #-} C a where +instance {-# INCOHERENT #-} C a where f _ = "a" diff --git a/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered17.stderr b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered17.stderr new file mode 100644 index 0000000..415e9a1 --- /dev/null +++ b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered17.stderr @@ -0,0 +1,9 @@ + +UnsafeInfered17.hs:1:16: Warning: + ?UnsafeInfered15? has been inferred as unsafe! + Reason: + UnsafeInfered17.hs:8:29: + [incoherent] overlap mode isn't allowed in Safe Haskell + +: +Failing due to -Werror. diff --git a/testsuite/tests/safeHaskell/safeInfered/all.T b/testsuite/tests/safeHaskell/safeInfered/all.T index a9600fa..4fc9fce 100644 --- a/testsuite/tests/safeHaskell/safeInfered/all.T +++ b/testsuite/tests/safeHaskell/safeInfered/all.T @@ -64,6 +64,7 @@ test('UnsafeInfered13', normal, compile_fail, ['']) test('UnsafeInfered14', normal, compile_fail, ['']) test('UnsafeInfered15', normal, compile_fail, ['']) test('UnsafeInfered16', normal, compile_fail, ['']) +test('UnsafeInfered17', normal, compile_fail, ['']) # Mixed tests test('Mixed01', normal, compile_fail, ['']) diff --git a/testsuite/tests/safeHaskell/safeLanguage/SafeLang10.hs b/testsuite/tests/safeHaskell/safeLanguage/SafeLang17.hs similarity index 66% copy from testsuite/tests/safeHaskell/safeLanguage/SafeLang10.hs copy to testsuite/tests/safeHaskell/safeLanguage/SafeLang17.hs index 5c88d39..411addd 100644 --- a/testsuite/tests/safeHaskell/safeLanguage/SafeLang10.hs +++ b/testsuite/tests/safeHaskell/safeLanguage/SafeLang17.hs @@ -1,8 +1,8 @@ {-# LANGUAGE Trustworthy #-} module Main where -import safe SafeLang10_A -- trusted lib -import safe SafeLang10_B -- untrusted plugin +import SafeLang17_A -- trusted lib +import SafeLang17_B -- untrusted plugin main = do let r = res [(1::Int)] diff --git a/testsuite/tests/safeHaskell/safeLanguage/SafeLang10.stderr b/testsuite/tests/safeHaskell/safeLanguage/SafeLang17.stderr similarity index 58% copy from testsuite/tests/safeHaskell/safeLanguage/SafeLang10.stderr copy to testsuite/tests/safeHaskell/safeLanguage/SafeLang17.stderr index d0c5c68..c59f866 100644 --- a/testsuite/tests/safeHaskell/safeLanguage/SafeLang10.stderr +++ b/testsuite/tests/safeHaskell/safeLanguage/SafeLang17.stderr @@ -1,17 +1,17 @@ -[1 of 3] Compiling SafeLang10_A ( SafeLang10_A.hs, SafeLang10_A.o ) -[2 of 3] Compiling SafeLang10_B ( SafeLang10_B.hs, SafeLang10_B.o ) -[3 of 3] Compiling Main ( SafeLang10.hs, SafeLang10.o ) +[1 of 3] Compiling SafeLang17_A ( SafeLang17_A.hs, SafeLang17_A.o ) +[2 of 3] Compiling SafeLang17_B ( SafeLang17_B.hs, SafeLang17_B.o ) +[3 of 3] Compiling Main ( SafeLang17.hs, SafeLang17.o ) -SafeLang10.hs:8:13: +SafeLang17.hs:8:13: Unsafe overlapping instances for Pos [Int] arising from a use of ?res? The matching instance is: - instance [overlapping] [safe] Pos [Int] - -- Defined at SafeLang10_B.hs:13:30 + instance [incoherent] [safe] Pos [Int] + -- Defined at SafeLang17_B.hs:14:10 It is compiled in a Safe module and as such can only overlap instances from the same module, however it overlaps the following instances from different modules: - instance Pos [a] -- Defined at SafeLang10_A.hs:13:10 + instance Pos [a] -- Defined at SafeLang17_A.hs:13:10 In the expression: res [(1 :: Int)] In an equation for ?r?: r = res [(1 :: Int)] In the expression: diff --git a/testsuite/tests/safeHaskell/safeLanguage/SafeLang10_A.hs b/testsuite/tests/safeHaskell/safeLanguage/SafeLang17_A.hs similarity index 92% copy from testsuite/tests/safeHaskell/safeLanguage/SafeLang10_A.hs copy to testsuite/tests/safeHaskell/safeLanguage/SafeLang17_A.hs index 7be17b5..0ce2bdf 100644 --- a/testsuite/tests/safeHaskell/safeLanguage/SafeLang10_A.hs +++ b/testsuite/tests/safeHaskell/safeLanguage/SafeLang17_A.hs @@ -1,8 +1,8 @@ -{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE Trustworthy #-} +{-# LANGUAGE FlexibleInstances #-} -- | Trusted library that unsafe plugins can use -module SafeLang10_A where +module SafeLang17_A where class Pos a where res :: a -> Bool @@ -13,4 +13,3 @@ class Pos a where instance Pos [a] where res _ = True - diff --git a/testsuite/tests/safeHaskell/safeLanguage/SafeLang09_B.hs b/testsuite/tests/safeHaskell/safeLanguage/SafeLang17_B.hs similarity index 70% copy from testsuite/tests/safeHaskell/safeLanguage/SafeLang09_B.hs copy to testsuite/tests/safeHaskell/safeLanguage/SafeLang17_B.hs index d03a629..2059f01 100644 --- a/testsuite/tests/safeHaskell/safeLanguage/SafeLang09_B.hs +++ b/testsuite/tests/safeHaskell/safeLanguage/SafeLang17_B.hs @@ -1,11 +1,12 @@ +{-# LANGUAGE Safe #-} {-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE OverlappingInstances #-} +{-# LANGUAGE IncoherentInstances #-} -- Untrusted plugin! Don't wan't it changing behaviour of our -- trusted code -module SafeLang09_B where +module SafeLang17_B where -import SafeLang09_A +import SafeLang17_A instance Pos a where res _ = False diff --git a/testsuite/tests/safeHaskell/safeLanguage/all.T b/testsuite/tests/safeHaskell/safeLanguage/all.T index 131778b..926c576 100644 --- a/testsuite/tests/safeHaskell/safeLanguage/all.T +++ b/testsuite/tests/safeHaskell/safeLanguage/all.T @@ -45,6 +45,11 @@ test('SafeLang15', multimod_compile_and_run, ['SafeLang15', '-XSafe']) test('SafeLang16', normal, compile, ['']) +test('SafeLang17', + extra_clean(['SafeLang17_A.o', 'SafeLang17_A.hi', + 'SafeLang17_B.o', 'SafeLang17_B.hi']), + multimod_compile_fail, + ['SafeLang17', '']) # Test building a package, that trust values are set correctly # and can be changed correctly From git at git.haskell.org Fri Nov 7 07:38:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 07:38:31 +0000 (UTC) Subject: [commit: ghc] master: Improve Applicative definitions (abba381) Message-ID: <20141107073831.155283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/abba3812e657a5267bba406d2c877c1cb5d978f9/ghc >--------------------------------------------------------------- commit abba3812e657a5267bba406d2c877c1cb5d978f9 Author: David Feuer Date: Fri Nov 7 08:12:21 2014 +0100 Improve Applicative definitions Generally clean up things relating to Applicative and Monad in `GHC.Base` and `Control.Applicative` to make `Applicative` feel like a bit more of a first-class citizen rather than just playing second fiddle to `Monad`. Use `coerce` and GND to improve performance and clarity. Change the default definition of `(*>)` to use `(<$)`, in case the `Functor` instance optimizes that. Moreover, some manually written instances are made into compiler-derived instances. Finally, this also adds a few AMP-related laws to the `Applicative` docstring. NOTE: These changes result in a 13% decrease in allocation for T9020 Reviewed By: ekmett, hvr Differential Revision: https://phabricator.haskell.org/D432 >--------------------------------------------------------------- abba3812e657a5267bba406d2c877c1cb5d978f9 compiler/basicTypes/UniqSupply.lhs | 1 + compiler/simplCore/SimplMonad.lhs | 3 +- libraries/base/Control/Applicative.hs | 28 ++++----- libraries/base/GHC/Base.lhs | 69 +++++++++++++++------- testsuite/tests/perf/compiler/all.T | 3 +- .../tests/simplCore/should_compile/T8848.stderr | 7 +-- 6 files changed, 67 insertions(+), 44 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc abba3812e657a5267bba406d2c877c1cb5d978f9 From git at git.haskell.org Fri Nov 7 12:02:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 12:02:17 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Renamer for PatSynSigs: handle type variable bindings (70ab25f) Message-ID: <20141107120217.57EE43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/70ab25f124c4b5bfaca121a3fb849e23d6f83a17/ghc >--------------------------------------------------------------- commit 70ab25f124c4b5bfaca121a3fb849e23d6f83a17 Author: Dr. ERDI Gergo Date: Fri Nov 7 19:29:06 2014 +0800 Renamer for PatSynSigs: handle type variable bindings >--------------------------------------------------------------- 70ab25f124c4b5bfaca121a3fb849e23d6f83a17 compiler/hsSyn/HsBinds.lhs | 8 +++---- compiler/rename/RnBinds.lhs | 57 +++++++++++++++++++++++++++++++-------------- 2 files changed, 43 insertions(+), 22 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index bbf6bc2..23534cf 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -568,12 +568,12 @@ data Sig name TypeSig [Located name] (LHsType name) -- | A pattern synonym type signature - -- @pattern (Eq b) => P a b :: (Num a) => T a + -- @pattern type forall b. (Eq b) => P a b :: forall a. (Num a) => T a | PatSynSig (Located name) (HsPatSynDetails (LHsType name)) (LHsType name) -- Type - (LHsContext name) -- Provided context - (LHsContext name) -- Required contex + (HsExplicitFlag, LHsTyVarBndrs name, LHsContext name) -- Provided context + (HsExplicitFlag, LHsTyVarBndrs name, LHsContext name) -- Required contex -- | A type signature for a default method inside a class -- @@ -730,7 +730,7 @@ ppr_sig (SpecSig var ty inl) = pragBrackets (pprSpec (unLoc var) (ppr ty) i ppr_sig (InlineSig var inl) = pragBrackets (ppr inl <+> pprPrefixOcc (unLoc var)) ppr_sig (SpecInstSig ty) = pragBrackets (ptext (sLit "SPECIALIZE instance") <+> ppr ty) ppr_sig (MinimalSig bf) = pragBrackets (pprMinimalSig bf) -ppr_sig (PatSynSig name arg_tys ty prov req) +ppr_sig (PatSynSig name arg_tys ty (_, _, prov) (_, _, req)) = pprPatSynSig (unLoc name) False args (ppr ty) (pprCtx prov) (pprCtx req) where args = fmap ppr arg_tys diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index c2489cb..4a98a35 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -30,7 +30,7 @@ import {-# SOURCE #-} RnExpr( rnLExpr, rnStmts ) import HsSyn import TcRnMonad import TcEvidence ( emptyTcEvBinds ) -import RnTypes ( bindSigTyVarsFV, rnHsSigType, rnLHsType, checkPrecMatch, rnContext ) +import RnTypes import RnPat import RnNames import RnEnv @@ -50,6 +50,7 @@ import FastString import Data.List ( partition, sort ) import Maybes ( orElse ) import Control.Monad +import Util ( filterOut ) #if __GLASGOW_HASKELL__ < 709 import Data.Traversable ( traverse ) #endif @@ -841,23 +842,43 @@ renameSig ctxt sig@(MinimalSig bf) = do new_bf <- traverse (lookupSigOccRn ctxt sig) bf return (MinimalSig new_bf, emptyFVs) -renameSig ctxt sig@(PatSynSig v args ty prov req) - = do v' <- lookupSigOccRn ctxt sig v - let doc = quotes (ppr v) - rn_type = rnHsSigType doc - (ty', fvs1) <- rn_type ty - (args', fvs2) <- case args of - PrefixPatSyn tys -> - do (tys, fvs) <- unzip <$> mapM rn_type tys - return (PrefixPatSyn tys, plusFVs fvs) - InfixPatSyn left right -> - do (left', fvs1) <- rn_type left - (right', fvs2) <- rn_type right - return (InfixPatSyn left' right', fvs1 `plusFV` fvs2) - (prov', fvs3) <- rnContext (TypeSigCtx doc) prov - (req', fvs4) <- rnContext (TypeSigCtx doc) req - let fvs = plusFVs [fvs1, fvs2, fvs3, fvs4] - return (PatSynSig v' args' ty' prov' req', fvs) +renameSig ctxt sig@(PatSynSig v args ty (ex_flag, _ex_tvs, prov) (univ_flag, _univ_tvs, req)) + = do { v' <- lookupSigOccRn ctxt sig v + ; let doc = TypeSigCtx $ quotes (ppr v) + ; loc <- getSrcSpanM + + ; let (univ_kvs, univ_tvs) = extractHsTysRdrTyVars (ty:unLoc req) + ; let univ_tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ univ_tvs + + ; bindHsTyVars doc Nothing univ_kvs univ_tv_bndrs $ \ univ_tyvars -> do + { (req', fvs1) <- rnContext doc req + ; (ty', fvs2) <- rnLHsType doc ty + + ; let (arg_tys, rnArgs) = case args of + PrefixPatSyn tys -> + let rnArgs = do + (tys', fvs) <- mapFvRn (rnLHsType doc) tys + return (PrefixPatSyn tys', fvs) + in (tys, rnArgs) + InfixPatSyn ty1 ty2 -> + let rnArgs = do + (ty1', fvs1) <- rnLHsType doc ty1 + (ty2', fvs2) <- rnLHsType doc ty2 + return (InfixPatSyn ty1' ty2', fvs1 `plusFV` fvs2) + in ([ty1, ty2], rnArgs) + + ; let (ex_kvs, ex_tvs) = extractHsTysRdrTyVars (arg_tys ++ unLoc prov) + ex_kvs' = filterOut (`elem` univ_kvs) ex_kvs + ex_tvs' = filterOut (`elem` univ_tvs) ex_tvs + + ; let ex_tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ ex_tvs' + + ; bindHsTyVars doc Nothing ex_kvs' ex_tv_bndrs $ \ ex_tyvars -> do + { (prov', fvs3) <- rnContext doc prov + ; (args', fvs4) <- rnArgs + + ; let fvs = plusFVs [fvs1, fvs2, fvs3, fvs4] + ; return (PatSynSig v' args' ty' (ex_flag, ex_tyvars, prov') (univ_flag, univ_tyvars, req'), fvs) }}} ppr_sig_bndrs :: [Located RdrName] -> SDoc ppr_sig_bndrs bs = quotes (pprWithCommas ppr bs) From git at git.haskell.org Fri Nov 7 12:02:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 12:02:19 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Group PatSyn req/prov arguments together so that they're not all over the place (dc91392) Message-ID: <20141107120219.EC4F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/dc9139230968ce848fdf3fc4ea6e3a01a28a8a75/ghc >--------------------------------------------------------------- commit dc9139230968ce848fdf3fc4ea6e3a01a28a8a75 Author: Dr. ERDI Gergo Date: Thu Nov 6 19:01:38 2014 +0800 Group PatSyn req/prov arguments together so that they're not all over the place >--------------------------------------------------------------- dc9139230968ce848fdf3fc4ea6e3a01a28a8a75 compiler/basicTypes/PatSyn.lhs | 27 ++++++++++++++------------- compiler/iface/BuildTyCl.lhs | 23 ++++++++++------------- compiler/iface/TcIface.lhs | 3 ++- compiler/typecheck/TcPatSyn.lhs | 4 ++-- 4 files changed, 28 insertions(+), 29 deletions(-) diff --git a/compiler/basicTypes/PatSyn.lhs b/compiler/basicTypes/PatSyn.lhs index 2081b5a..9efd69d 100644 --- a/compiler/basicTypes/PatSyn.lhs +++ b/compiler/basicTypes/PatSyn.lhs @@ -123,9 +123,9 @@ data PatSyn psInfix :: Bool, -- True <=> declared infix psUnivTyVars :: [TyVar], -- Universially-quantified type variables + psReqTheta :: ThetaType, -- Required dictionaries psExTyVars :: [TyVar], -- Existentially-quantified type vars psProvTheta :: ThetaType, -- Provided dictionaries - psReqTheta :: ThetaType, -- Required dictionaries psOrigResTy :: Type, -- Mentions only psUnivTyVars -- See Note [Matchers and wrappers for pattern synonyms] @@ -194,19 +194,20 @@ instance Data.Data PatSyn where \begin{code} -- | Build a new pattern synonym mkPatSyn :: Name - -> Bool -- ^ Is the pattern synonym declared infix? - -> [Type] -- ^ Original arguments - -> [TyVar] -- ^ Universially-quantified type variables - -> [TyVar] -- ^ Existentially-quantified type variables - -> ThetaType -- ^ Wanted dicts - -> ThetaType -- ^ Given dicts - -> Type -- ^ Original result type - -> Id -- ^ Name of matcher - -> Maybe Id -- ^ Name of wrapper + -> Bool -- ^ Is the pattern synonym declared infix? + -> ([TyVar], ThetaType) -- ^ Universially-quantified type variables + -- and required dicts + -> ([TyVar], ThetaType) -- ^ Existentially-quantified type variables + -- and provided dicts + -> [Type] -- ^ Original arguments + -> Type -- ^ Original result type + -> Id -- ^ Name of matcher + -> Maybe Id -- ^ Name of wrapper -> PatSyn -mkPatSyn name declared_infix orig_args - univ_tvs ex_tvs - prov_theta req_theta +mkPatSyn name declared_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) + orig_args orig_res_ty matcher wrapper = MkPatSyn {psName = name, psUnique = getUnique name, diff --git a/compiler/iface/BuildTyCl.lhs b/compiler/iface/BuildTyCl.lhs index 2a66de2..d90e63c 100644 --- a/compiler/iface/BuildTyCl.lhs +++ b/compiler/iface/BuildTyCl.lhs @@ -180,32 +180,29 @@ mkDataConStupidTheta tycon arg_tys univ_tvs ------------------------------------------------------ buildPatSyn :: Name -> Bool -> Id -> Maybe Id - -> [Type] - -> [TyVar] -> [TyVar] -- Univ and ext - -> ThetaType -> ThetaType -- Prov and req - -> Type -- Result type + -> ([TyVar], ThetaType) -- ^ Univ and req + -> ([TyVar], ThetaType) -- ^ Ex and prov + -> [Type] -- ^ Argument types + -> Type -- ^ Result type -> PatSyn buildPatSyn src_name declared_infix matcher wrapper - args univ_tvs ex_tvs prov_theta req_theta pat_ty + (univ_tvs, req_theta) (ex_tvs, prov_theta) arg_tys pat_ty = ASSERT((and [ univ_tvs == univ_tvs' , ex_tvs == ex_tvs' , pat_ty `eqType` pat_ty' , prov_theta `eqTypes` prov_theta' , req_theta `eqTypes` req_theta' - , args `eqTypes` args' + , arg_tys `eqTypes` arg_tys' ])) mkPatSyn src_name declared_infix - args - univ_tvs ex_tvs - prov_theta req_theta - pat_ty - matcher - wrapper + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty + matcher wrapper where ((_:univ_tvs'), req_theta', tau) = tcSplitSigmaTy $ idType matcher ([pat_ty', cont_sigma, _], _) = tcSplitFunTys tau (ex_tvs', prov_theta', cont_tau) = tcSplitSigmaTy cont_sigma - (args', _) = tcSplitFunTys cont_tau + (arg_tys', _) = tcSplitFunTys cont_tau \end{code} diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index 424a46c..9dd5864 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -605,7 +605,8 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name ; pat_ty <- tcIfaceType pat_ty ; arg_tys <- mapM tcIfaceType args ; return $ buildPatSyn name is_infix matcher wrapper - arg_tys univ_tvs ex_tvs prov_theta req_theta pat_ty } + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty } ; return $ AConLike . PatSynCon $ patsyn }}} where mk_doc n = ptext (sLit "Pattern synonym") <+> ppr n diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 9b2b511..6293077 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -102,9 +102,9 @@ tcPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; traceTc "tcPatSynDecl }" $ ppr name ; let patSyn = mkPatSyn name is_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) (map varType args) - univ_tvs ex_tvs - prov_theta req_theta pat_ty matcher_id wrapper_id ; return (patSyn, matcher_bind) } From git at git.haskell.org Fri Nov 7 12:02:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 12:02:22 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Update baseline shift/reduce conflict number (9346723) Message-ID: <20141107120222.9440E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/93467234320888bf311405e7c3d90a374cfefcea/ghc >--------------------------------------------------------------- commit 93467234320888bf311405e7c3d90a374cfefcea Author: Dr. ERDI Gergo Date: Wed Jul 2 19:18:43 2014 +0800 Update baseline shift/reduce conflict number >--------------------------------------------------------------- 93467234320888bf311405e7c3d90a374cfefcea compiler/parser/Parser.y.pp | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/compiler/parser/Parser.y.pp b/compiler/parser/Parser.y.pp index e33808d..e0eaf4d 100644 --- a/compiler/parser/Parser.y.pp +++ b/compiler/parser/Parser.y.pp @@ -72,6 +72,12 @@ import Control.Monad ( mplus ) {- ----------------------------------------------------------------------------- +25 June 2014 + +Conflicts: 47 shift/reduce + 1 reduce/reduce + +----------------------------------------------------------------------------- 12 October 2012 Conflicts: 43 shift/reduce From git at git.haskell.org Fri Nov 7 12:02:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 12:02:25 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Show foralls (when requested) in pattern synonym types (a362bfa) Message-ID: <20141107120225.2A9233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/a362bfac4969be05c91b0c5cf02eff2d280914aa/ghc >--------------------------------------------------------------- commit a362bfac4969be05c91b0c5cf02eff2d280914aa Author: Dr. ERDI Gergo Date: Sun Aug 3 15:26:13 2014 +0200 Show foralls (when requested) in pattern synonym types >--------------------------------------------------------------- a362bfac4969be05c91b0c5cf02eff2d280914aa compiler/hsSyn/HsBinds.lhs | 21 ++++++--------------- compiler/iface/IfaceSyn.lhs | 9 +++++---- 2 files changed, 11 insertions(+), 19 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index f75fa2e..5a45956 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -730,24 +730,18 @@ ppr_sig (SpecSig var ty inl) = pragBrackets (pprSpec (unLoc var) (ppr ty) i ppr_sig (InlineSig var inl) = pragBrackets (ppr inl <+> pprPrefixOcc (unLoc var)) ppr_sig (SpecInstSig ty) = pragBrackets (ptext (sLit "SPECIALIZE instance") <+> ppr ty) ppr_sig (MinimalSig bf) = pragBrackets (pprMinimalSig bf) -ppr_sig (PatSynSig name arg_tys ty (_, _, prov) (_, _, req)) +ppr_sig (PatSynSig name arg_tys ty prov req) = pprPatSynSig (unLoc name) False args (ppr ty) (pprCtx prov) (pprCtx req) where args = fmap ppr arg_tys - pprCtx lctx = case unLoc lctx of - [] -> Nothing - ctx -> Just (pprHsContextNoArrow ctx) + pprCtx (flag, tvs, lctx) = pprHsForAll flag tvs lctx pprPatSynSig :: (OutputableBndr a) - => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> Maybe SDoc -> Maybe SDoc -> SDoc -pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta - = sep [ ptext (sLit "pattern") - , ptext (sLit "type") - , thetaOpt prov_theta, name_and_args - , colon - , thetaOpt req_theta, rhs_ty - ] + => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> SDoc -> SDoc -> SDoc +pprPatSynSig ident is_bidir args rhs_ty prov req + = ptext (sLit "pattern type") <+> + prov <+> name_and_args <+> colon <+> req <+> rhs_ty where name_and_args = case args of PrefixPatSyn arg_tys -> @@ -755,9 +749,6 @@ pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta InfixPatSyn left_ty right_ty -> left_ty <+> pprInfixOcc ident <+> right_ty - -- TODO: support explicit foralls - thetaOpt = maybe empty (<+> darrow) - colon = if is_bidir then dcolon else dcolon -- TODO instance OutputableBndr name => Outputable (FixitySig name) where diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 7e2d6f2..d900875 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -761,11 +761,13 @@ pprIfaceDecl ss (IfaceSyn { ifName = tycon, ifTyVars = tyvars pprIfaceDecl _ (IfacePatSyn { ifName = name, ifPatWrapper = wrapper, ifPatIsInfix = is_infix, - ifPatUnivTvs = _univ_tvs, ifPatExTvs = _ex_tvs, + ifPatUnivTvs = univ_tvs, ifPatExTvs = ex_tvs, ifPatProvCtxt = prov_ctxt, ifPatReqCtxt = req_ctxt, ifPatArgs = args, ifPatTy = ty }) - = pprPatSynSig name has_wrap args' ty' (pprCtxt prov_ctxt) (pprCtxt req_ctxt) + = pprPatSynSig name has_wrap args' ty' + (pprCtxt ex_tvs prov_ctxt) + (pprCtxt univ_tvs req_ctxt) where has_wrap = isJust wrapper args' = case (is_infix, args) of @@ -776,8 +778,7 @@ pprIfaceDecl _ (IfacePatSyn { ifName = name, ifPatWrapper = wrapper, ty' = pprParendIfaceType ty - pprCtxt [] = Nothing - pprCtxt ctxt = Just $ pprIfaceContext ctxt + pprCtxt tvs ctxt = pprIfaceForAllPart tvs ctxt empty pprIfaceDecl ss (IfaceId { ifName = var, ifType = ty, ifIdDetails = details, ifIdInfo = info }) From git at git.haskell.org Fri Nov 7 12:02:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 12:02:27 +0000 (UTC) Subject: [commit: ghc] wip/T8584: tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures (952a2f4) Message-ID: <20141107120227.B81923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/952a2f46c6c8b7df2805c5bb768853cd1ea7e081/ghc >--------------------------------------------------------------- commit 952a2f46c6c8b7df2805c5bb768853cd1ea7e081 Author: Dr. ERDI Gergo Date: Sun Jul 27 14:10:34 2014 +0200 tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures >--------------------------------------------------------------- 952a2f46c6c8b7df2805c5bb768853cd1ea7e081 compiler/typecheck/TcBinds.lhs | 45 ++++++++-- compiler/typecheck/TcClassDcl.lhs | 4 +- compiler/typecheck/TcPat.lhs | 23 ++++- compiler/typecheck/TcPatSyn.lhs | 166 +++++++++++++++++++++++++---------- compiler/typecheck/TcPatSyn.lhs-boot | 9 +- 5 files changed, 191 insertions(+), 56 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 952a2f46c6c8b7df2805c5bb768853cd1ea7e081 From git at git.haskell.org Fri Nov 7 12:02:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 12:02:30 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add parser for pattern synonym type signatures. Syntax is of the form (aae1236) Message-ID: <20141107120230.6B3A43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/aae123636e18c3b09c137a43046f4333f5333651/ghc >--------------------------------------------------------------- commit aae123636e18c3b09c137a43046f4333f5333651 Author: Dr. ERDI Gergo Date: Mon Jul 14 18:18:44 2014 +0800 Add parser for pattern synonym type signatures. Syntax is of the form pattern type Eq a => P a T b :: Num b => R a b which declares a pattern synonym called P, with argument types a, T, and b. >--------------------------------------------------------------- aae123636e18c3b09c137a43046f4333f5333651 compiler/hsSyn/HsBinds.lhs | 1 + compiler/hsSyn/HsTypes.lhs | 19 +++++++++++++------ compiler/parser/Parser.y.pp | 9 +++++++-- compiler/parser/RdrHsSyn.lhs | 31 ++++++++++++++++++++++++++++++- 4 files changed, 51 insertions(+), 9 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index 23534cf..f75fa2e 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -743,6 +743,7 @@ pprPatSynSig :: (OutputableBndr a) => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> Maybe SDoc -> Maybe SDoc -> SDoc pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta = sep [ ptext (sLit "pattern") + , ptext (sLit "type") , thetaOpt prov_theta, name_and_args , colon , thetaOpt req_theta, rhs_ty diff --git a/compiler/hsSyn/HsTypes.lhs b/compiler/hsSyn/HsTypes.lhs index 9bd5845..db4d976 100644 --- a/compiler/hsSyn/HsTypes.lhs +++ b/compiler/hsSyn/HsTypes.lhs @@ -39,7 +39,7 @@ module HsTypes ( hsLTyVarName, hsLTyVarNames, hsLTyVarLocName, hsLTyVarLocNames, splitLHsInstDeclTy_maybe, splitHsClassTy_maybe, splitLHsClassTy_maybe, - splitHsFunType, + splitHsFunType, splitLHsForAllTyFlag, splitLHsForAllTy, splitHsAppTys, hsTyGetAppHead_maybe, mkHsAppTys, mkHsOpTy, -- Printing @@ -510,15 +510,22 @@ splitLHsInstDeclTy_maybe inst_ty = do (cls, tys) <- splitLHsClassTy_maybe ty return (tvs, cxt, cls, tys) +splitLHsForAllTyFlag + :: LHsType name + -> (HsExplicitFlag, LHsTyVarBndrs name, HsContext name, LHsType name) +splitLHsForAllTyFlag poly_ty + = case unLoc poly_ty of + HsParTy ty -> splitLHsForAllTyFlag ty + HsForAllTy flag tvs cxt ty -> (flag, tvs, unLoc cxt, ty) + _ -> (Implicit, emptyHsQTvs, [], poly_ty) + -- The type vars should have been computed by now, even if they were implicit + splitLHsForAllTy :: LHsType name -> (LHsTyVarBndrs name, HsContext name, LHsType name) splitLHsForAllTy poly_ty - = case unLoc poly_ty of - HsParTy ty -> splitLHsForAllTy ty - HsForAllTy _ tvs cxt ty -> (tvs, unLoc cxt, ty) - _ -> (emptyHsQTvs, [], poly_ty) - -- The type vars should have been computed by now, even if they were implicit + = let (_, tvs, cxt, ty) = splitLHsForAllTyFlag poly_ty + in (tvs, cxt, ty) splitHsClassTy_maybe :: HsType name -> Maybe (name, [LHsType name]) splitHsClassTy_maybe ty = fmap (\(L _ n, tys) -> (n, tys)) $ splitLHsClassTy_maybe (noLoc ty) diff --git a/compiler/parser/Parser.y.pp b/compiler/parser/Parser.y.pp index e0eaf4d..41ad6f0 100644 --- a/compiler/parser/Parser.y.pp +++ b/compiler/parser/Parser.y.pp @@ -856,8 +856,7 @@ role : VARID { L1 $ Just $ getVARID $1 } pattern_synonym_decl :: { LHsDecl RdrName } : 'pattern' pat '=' pat {% do { (name, args) <- splitPatSyn $2 - ; return $ LL . ValD $ mkPatSynBind name args $4 ImplicitBidirectional - }} + ; return $ LL . ValD $ mkPatSynBind name args $4 ImplicitBidirectional }} | 'pattern' pat '<-' pat {% do { (name, args) <- splitPatSyn $2 ; return $ LL . ValD $ mkPatSynBind name args $4 Unidirectional @@ -873,6 +872,11 @@ where_decls :: { Located (OrdList (LHsDecl RdrName)) } : 'where' '{' decls '}' { $3 } | 'where' vocurly decls close { $3 } +pattern_synonym_sig :: { LSig RdrName } + : 'pattern' 'type' ctype '::' ctype + {% do { (name, details, ty, prov, req) <- splitPatSynSig $3 $5 + ; return . LL $ PatSynSig name details ty prov req }} + vars0 :: { [Located RdrName] } : {- empty -} { [] } | varid vars0 { $1 : $2 } @@ -1484,6 +1488,7 @@ sigdecl :: { Located (OrdList (LHsDecl RdrName)) } { LL $ toOL [ LL $ SigD (TypeSig ($1 : reverse (unLoc $3)) $5) ] } | infix prec ops { LL $ toOL [ LL $ SigD (FixSig (FixitySig n (Fixity $2 (unLoc $1)))) | n <- unLoc $3 ] } + | pattern_synonym_sig { LL . unitOL $ LL . SigD . unLoc $ $1 } | '{-# INLINE' activation qvar '#-}' { LL $ unitOL (LL $ SigD (InlineSig $3 (mkInlinePragma (getINLINE $1) $2))) } | '{-# SPECIALISE' activation qvar '::' sigtypes1 '#-}' diff --git a/compiler/parser/RdrHsSyn.lhs b/compiler/parser/RdrHsSyn.lhs index e6969e7..3152642 100644 --- a/compiler/parser/RdrHsSyn.lhs +++ b/compiler/parser/RdrHsSyn.lhs @@ -18,7 +18,7 @@ module RdrHsSyn ( mkTyFamInst, mkFamDecl, splitCon, mkInlinePragma, - splitPatSyn, toPatSynMatchGroup, + splitPatSyn, splitPatSynSig, toPatSynMatchGroup, mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp mkTyClD, mkInstD, @@ -471,6 +471,35 @@ toPatSynMatchGroup (L _ patsyn_name) (L _ decls) = text "pattern synonym 'where' clause must bind the pattern synonym's name" <+> quotes (ppr patsyn_name) $$ ppr decl +-- Given two types like +-- Eq a => P a T b +-- and +-- Num b => R a b +-- +-- This returns +-- P as the name, +-- PrefixPatSyn [a, T, b] as the details, +-- R a b as the result type, +-- and (Eq a) and (Num b) as the provided and required thetas (respectively) +splitPatSynSig :: LHsType RdrName + -> LHsType RdrName + -> P (Located RdrName, HsPatSynDetails (LHsType RdrName), LHsType RdrName, + (HsExplicitFlag, LHsTyVarBndrs RdrName, LHsContext RdrName), + (HsExplicitFlag, LHsTyVarBndrs RdrName, LHsContext RdrName)) +splitPatSynSig lty1 lty2 = do + (name, details) <- splitCon pat_ty + details' <- case details of + PrefixCon tys -> return $ PrefixPatSyn tys + InfixCon ty1 ty2 -> return $ InfixPatSyn ty1 ty2 + RecCon{} -> parseErrorSDoc (getLoc lty1) $ + text "record syntax not supported for pattern synonym declarations:" $$ ppr lty1 + return (name, details', res_ty, (ex_flag, ex_tvs, prov'), (univ_flag, univ_tvs, req')) + where + (ex_flag, ex_tvs, prov, pat_ty) = splitLHsForAllTyFlag lty1 + (univ_flag, univ_tvs, req, res_ty) = splitLHsForAllTyFlag lty2 + prov' = L (getLoc lty1) prov + req' = L (getLoc lty2) req + mkDeprecatedGadtRecordDecl :: SrcSpan -> Located RdrName -> [ConDeclField RdrName] From git at git.haskell.org Fri Nov 7 12:02:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 12:02:33 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add test cases (6c7e835) Message-ID: <20141107120233.6138B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/6c7e8353af5c6a1e823e1b05037e5bc0369545a0/ghc >--------------------------------------------------------------- commit 6c7e8353af5c6a1e823e1b05037e5bc0369545a0 Author: Dr. ERDI Gergo Date: Sun Nov 2 14:35:49 2014 +0800 Add test cases >--------------------------------------------------------------- 6c7e8353af5c6a1e823e1b05037e5bc0369545a0 testsuite/tests/patsyn/should_compile/T8584-1.hs | 10 ++++++++++ testsuite/tests/patsyn/should_compile/T8968-1.hs | 8 ++++++++ testsuite/tests/patsyn/should_compile/all.T | 2 ++ 3 files changed, 20 insertions(+) diff --git a/testsuite/tests/patsyn/should_compile/T8584-1.hs b/testsuite/tests/patsyn/should_compile/T8584-1.hs new file mode 100644 index 0000000..7a017c8 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8584-1.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms #-} +module ShouldCompile where + +pattern type (Eq a) => Single a :: (Show a) => [a] +-- pattern type Single a :: (Eq a, Show a) => [a] +-- pattern type Single a :: [a] +pattern Single x = [x] + +-- f :: (Show a) => [a] -> a +foobar (Single x) = x diff --git a/testsuite/tests/patsyn/should_compile/T8968-1.hs b/testsuite/tests/patsyn/should_compile/T8968-1.hs new file mode 100644 index 0000000..f4a1dc4 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8968-1.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE GADTs, KindSignatures, PatternSynonyms #-} +module ShouldCompile where + +data X :: (* -> *) -> * -> * where + Y :: f a -> X f (Maybe a) + +pattern type C a :: X Maybe (Maybe a) +pattern C x = Y (Just x) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index d851bc3..8896008 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -10,3 +10,5 @@ test('incomplete', normal, compile, ['']) test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) +test('T8968-1', normal, compile, ['']) +test('T8584-1', normal, compile, ['']) From git at git.haskell.org Fri Nov 7 13:19:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 13:19:47 +0000 (UTC) Subject: [commit: ghc] master: Make getTag use a bang pattern instead of seq (dc5fa80) Message-ID: <20141107131947.6BD053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dc5fa804c604fa73494d97f1f1b0fef649731481/ghc >--------------------------------------------------------------- commit dc5fa804c604fa73494d97f1f1b0fef649731481 Author: David Feuer Date: Fri Nov 7 14:19:18 2014 +0100 Make getTag use a bang pattern instead of seq It's prettier that way, and there's less risk of anything going sideways. Reviewed By: hvr, simonpj Differential Revision: https://phabricator.haskell.org/D450 >--------------------------------------------------------------- dc5fa804c604fa73494d97f1f1b0fef649731481 libraries/base/GHC/Base.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/GHC/Base.lhs b/libraries/base/GHC/Base.lhs index 495a6b2..217f6ad 100644 --- a/libraries/base/GHC/Base.lhs +++ b/libraries/base/GHC/Base.lhs @@ -1121,7 +1121,7 @@ in the case when the argument is already known to be evaluated. \begin{code} {-# INLINE getTag #-} getTag :: a -> Int# -getTag x = x `seq` dataToTag# x +getTag !x = dataToTag# x \end{code} %********************************************************* From git at git.haskell.org Fri Nov 7 13:32:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 13:32:45 +0000 (UTC) Subject: [commit: ghc] master: Update .gitignore to properly ignore emacs temp files (b0e8e34) Message-ID: <20141107133245.E20A83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b0e8e34ac1b4dcab2e4ec92d00440e047d260562/ghc >--------------------------------------------------------------- commit b0e8e34ac1b4dcab2e4ec92d00440e047d260562 Author: Austin Seipp Date: Fri Nov 7 07:30:53 2014 -0600 Update .gitignore to properly ignore emacs temp files Signed-off-by: Austin Seipp >--------------------------------------------------------------- b0e8e34ac1b4dcab2e4ec92d00440e047d260562 .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index 19b55b2..5a58ed2 100644 --- a/.gitignore +++ b/.gitignore @@ -5,6 +5,7 @@ Thumbs.db .DS_Store *~ +*# #*# *.bak *.BAK From git at git.haskell.org Fri Nov 7 13:32:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 13:32:48 +0000 (UTC) Subject: [commit: ghc] master: *Really*, really fix RTS crash due to bad coercion. (24e05f4) Message-ID: <20141107133248.B669D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/24e05f48f3a3a1130ecd5a46e3089b76ee5a2304/ghc >--------------------------------------------------------------- commit 24e05f48f3a3a1130ecd5a46e3089b76ee5a2304 Author: Merijn Verstraaten Date: Fri Nov 7 07:32:18 2014 -0600 *Really*, really fix RTS crash due to bad coercion. Summary: My previous attempt to fix the new coercion bug introduced by my fix actually just reverted back to the *old* bug. This time it should properly handle all three size scenarios. Signed-off-by: Merijn Verstraaten Test Plan: validate Reviewers: dfeuer, austin, hvr Reviewed By: austin, hvr Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D407 GHC Trac Issues: #8089 >--------------------------------------------------------------- 24e05f48f3a3a1130ecd5a46e3089b76ee5a2304 libraries/base/GHC/Event/Poll.hsc | 14 +++++++++----- libraries/base/tests/T8089.hs | 32 ++++++++++++++++++++++++++++++++ libraries/base/tests/all.T | 1 + rts/posix/Select.c | 25 ++++++++++++++++++++++++- 4 files changed, 66 insertions(+), 6 deletions(-) diff --git a/libraries/base/GHC/Event/Poll.hsc b/libraries/base/GHC/Event/Poll.hsc index b8f8c02..6cbe143 100644 --- a/libraries/base/GHC/Event/Poll.hsc +++ b/libraries/base/GHC/Event/Poll.hsc @@ -112,12 +112,17 @@ poll p mtout f = do -- expired) OR the full timeout has passed. c_pollLoop :: Ptr PollFd -> (#type nfds_t) -> Int -> IO CInt c_pollLoop ptr len tout - | tout <= maxPollTimeout = c_poll ptr len (fromIntegral tout) + | isShortTimeout = c_poll ptr len (fromIntegral tout) | otherwise = do result <- c_poll ptr len (fromIntegral maxPollTimeout) if result == 0 then c_pollLoop ptr len (fromIntegral (tout - maxPollTimeout)) else return result + where + -- maxPollTimeout is smaller than 0 IFF Int is smaller than CInt. + -- This means any possible Int input to poll can be safely directly + -- converted to CInt. + isShortTimeout = tout <= maxPollTimeout || maxPollTimeout < 0 -- We need to account for 3 cases: -- 1. Int and CInt are of equal size. @@ -131,11 +136,10 @@ poll p mtout f = do -- c_pollLoop recursing if the provided timeout is larger. -- -- In case 3, "fromIntegral (maxBound :: CInt) :: Int" will result in a - -- negative Int, max will thus return maxBound :: Int. Since poll doesn't - -- accept values bigger than maxBound :: Int and CInt is larger than Int, - -- there is no problem converting Int to CInt for the c_poll call. + -- negative Int. This will cause isShortTimeout to be true and result in + -- the timeout being directly converted to a CInt. maxPollTimeout :: Int - maxPollTimeout = max maxBound (fromIntegral (maxBound :: CInt)) + maxPollTimeout = fromIntegral (maxBound :: CInt) fromTimeout :: E.Timeout -> Int fromTimeout E.Forever = -1 diff --git a/libraries/base/tests/T8089.hs b/libraries/base/tests/T8089.hs new file mode 100644 index 0000000..2b98f94 --- /dev/null +++ b/libraries/base/tests/T8089.hs @@ -0,0 +1,32 @@ +import Control.Applicative +import Control.Concurrent +import Control.Exception +import Control.Monad +import System.Environment +import System.Exit +import System.Process +import System.Timeout + +testLoop :: Int -> IO (Maybe a) -> IO (Maybe a) +testLoop 0 _ = return Nothing +testLoop i act = do + result <- act + case result of + Nothing -> threadDelay 100000 >> testLoop (i-1) act + Just x -> return (Just x) + + +forkTestChild :: IO () +forkTestChild = do + (_, _, _, hnd) <- createProcess (proc "./T8089" ["test"]) + result <- testLoop 50 $ getProcessExitCode hnd + case result of + Nothing -> terminateProcess hnd >> exitSuccess + Just exitCode -> exitWith exitCode + +main :: IO () +main = do + numArgs <- length <$> getArgs + if numArgs > 0 + then threadDelay maxBound + else forkTestChild diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T index ee0fb6b..f7944f4 100644 --- a/libraries/base/tests/all.T +++ b/libraries/base/tests/all.T @@ -174,3 +174,4 @@ test('T9395', normal, compile_and_run, ['']) test('T9532', normal, compile_and_run, ['']) test('T9586', normal, compile, ['']) test('T9681', normal, compile_fail, ['']) +test('T8089', normal, compile_and_run, ['']) diff --git a/rts/posix/Select.c b/rts/posix/Select.c index 38b0821..4b19235 100644 --- a/rts/posix/Select.c +++ b/rts/posix/Select.c @@ -295,9 +295,32 @@ awaitEvent(rtsBool wait) tv.tv_usec = 0; ptv = &tv; } else if (sleeping_queue != END_TSO_QUEUE) { + /* SUSv2 allows implementations to have an implementation defined + * maximum timeout for select(2). The standard requires + * implementations to silently truncate values exceeding this maximum + * to the maximum. Unfortunately, OSX and the BSD don't comply with + * SUSv2, instead opting to return EINVAL for values exceeding a + * timeout of 1e8. + * + * Select returning an error crashes the runtime in a bad way. To + * play it safe we truncate any timeout to 31 days, as SUSv2 requires + * any implementations maximum timeout to be larger than this. + * + * Truncating the timeout is not an issue, because if nothing + * interesting happens when the timeout expires, we'll see that the + * thread still wants to be blocked longer and simply block on a new + * iteration of select(2). + */ + const time_t max_seconds = 2678400; // 31 * 24 * 60 * 60 + Time min = LowResTimeToTime(sleeping_queue->block_info.target - now); tv.tv_sec = TimeToSeconds(min); - tv.tv_usec = TimeToUS(min) % 1000000; + if (tv.tv_sec < max_seconds) { + tv.tv_usec = TimeToUS(min) % 1000000; + } else { + tv.tv_sec = max_seconds; + tv.tv_usec = 0; + } ptv = &tv; } else { ptv = NULL; From git at git.haskell.org Fri Nov 7 13:32:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 13:32:52 +0000 (UTC) Subject: [commit: ghc] master: small parser/lexer cleanup (37d64a5) Message-ID: <20141107133252.B435B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/37d64a51348a803a1cf974d9e97ec9231215064a/ghc >--------------------------------------------------------------- commit 37d64a51348a803a1cf974d9e97ec9231215064a Author: Yuri de Wit Date: Fri Nov 7 07:32:26 2014 -0600 small parser/lexer cleanup Summary: The last three '#define ...' macros were removed from Parser.y.pp and this file was renamed to Parser.y. This basically got rid of a CPP step in the build. Also converted two modules in compiler/parser/ from .lhs to .hs. Test Plan: Does it build? Yes, I performed a full build here and things are looking good. Reviewers: austin Reviewed By: austin Subscribers: adamse, thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D411 >--------------------------------------------------------------- 37d64a51348a803a1cf974d9e97ec9231215064a compiler/parser/{Ctype.lhs => Ctype.hs} | 25 +- compiler/parser/Lexer.x | 43 +- compiler/parser/{Parser.y.pp => Parser.y} | 894 +++++++++++++------------- compiler/parser/{RdrHsSyn.lhs => RdrHsSyn.hs} | 108 ++-- ghc.mk | 3 +- 5 files changed, 536 insertions(+), 537 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 37d64a51348a803a1cf974d9e97ec9231215064a From git at git.haskell.org Fri Nov 7 13:32:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 13:32:55 +0000 (UTC) Subject: [commit: ghc] master: [Docs] Fixed several broken urls in user's guide (b0d5b5b) Message-ID: <20141107133255.4B79C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b0d5b5b338ab6ebbc90f94243b83d2a738982f88/ghc >--------------------------------------------------------------- commit b0d5b5b338ab6ebbc90f94243b83d2a738982f88 Author: Konstantin Zudov Date: Fri Nov 7 07:32:35 2014 -0600 [Docs] Fixed several broken urls in user's guide Summary: Some of the links in user's guide were broken, I've found the files they used to link and updated urls. Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D418 >--------------------------------------------------------------- b0d5b5b338ab6ebbc90f94243b83d2a738982f88 docs/users_guide/glasgow_exts.xml | 6 +++--- docs/users_guide/parallel.xml | 4 ++-- 2 files changed, 5 insertions(+), 5 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 06c1b3b..edd1ccc 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -3713,7 +3713,7 @@ These and many other examples are given in papers by Hongwei Xi, and Tim Sheard. There is a longer introduction on the wiki, and Ralf Hinze's -Fun with phantom types also has a number of examples. Note that papers +Fun with phantom types also has a number of examples. Note that papers may use different notation to that implemented in GHC. @@ -9007,7 +9007,7 @@ The basic idea is to compile the program twice: Quasi-quotation allows patterns and expressions to be written using programmer-defined concrete syntax; the motivation behind the extension and several examples are documented in -"Why It's +"Why It's Nice to be Quoted: Quasiquoting for Haskell" (Proc Haskell Workshop 2007). The example below shows how to write a quasiquoter for a simple expression language. @@ -9213,7 +9213,7 @@ Palgrave, 2003. -“Programming with Arrows”, +“Programming with Arrows”, John Hughes, in 5th International Summer School on Advanced Functional Programming, Lecture Notes in Computer Science vol. 3622, diff --git a/docs/users_guide/parallel.xml b/docs/users_guide/parallel.xml index 05092bc..266a93f 100644 --- a/docs/users_guide/parallel.xml +++ b/docs/users_guide/parallel.xml @@ -30,7 +30,7 @@ Concurrent Haskell is the name given to GHC's concurrency extension. It is enabled by default, so no special flags are required. The + url="https://www.haskell.org/ghc/docs/papers/concurrent-haskell.ps.gz"> Concurrent Haskell paper is still an excellent resource, as is Tackling @@ -94,7 +94,7 @@ All these features are described in the papers mentioned earlier. (GPH) supports running Parallel Haskell programs on both clusters of machines, and single multiprocessors. GPH is developed and distributed - separately from GHC (see The + separately from GHC (see The GPH Page). However, the current version of GPH is based on a much older version of GHC (4.06). From git at git.haskell.org Fri Nov 7 13:32:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 13:32:57 +0000 (UTC) Subject: [commit: ghc] master: Use bracket in `withCurrentDirectory` (f14ac52) Message-ID: <20141107133257.D104A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f14ac52a9296b378c75ea75c94f51ff1f377111e/ghc >--------------------------------------------------------------- commit f14ac52a9296b378c75ea75c94f51ff1f377111e Author: Konstantin Zudov Date: Fri Nov 7 07:32:48 2014 -0600 Use bracket in `withCurrentDirectory` Summary: There was a comment about that. Seems like a better behaviour. Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D419 >--------------------------------------------------------------- f14ac52a9296b378c75ea75c94f51ff1f377111e utils/ghc-cabal/Main.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index bf08912..1847aaf 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -21,6 +21,7 @@ import Distribution.Verbosity import qualified Distribution.InstalledPackageInfo as Installed import qualified Distribution.Simple.PackageIndex as PackageIndex +import Control.Exception (bracket) import Control.Monad import qualified Data.ByteString.Lazy.Char8 as BS import Data.List @@ -70,14 +71,10 @@ die :: [String] -> IO a die errs = do mapM_ (hPutStrLn stderr) errs exitWith (ExitFailure 1) --- XXX Should use bracket withCurrentDirectory :: FilePath -> IO a -> IO a withCurrentDirectory directory io - = do curDirectory <- getCurrentDirectory - setCurrentDirectory directory - r <- io - setCurrentDirectory curDirectory - return r + = bracket (getCurrentDirectory) (setCurrentDirectory) + (const (setCurrentDirectory directory >> io)) -- We need to use the autoconfUserHooks, as the packages that use -- configure can create a .buildinfo file, and we need any info that From git at git.haskell.org Fri Nov 7 15:02:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 15:02:39 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Renamer for PatSynSigs: handle type variable bindings (30146d7) Message-ID: <20141107150239.5060E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/30146d704ed468ef175488fcea795f5b1905ccde/ghc >--------------------------------------------------------------- commit 30146d704ed468ef175488fcea795f5b1905ccde Author: Dr. ERDI Gergo Date: Fri Nov 7 19:29:06 2014 +0800 Renamer for PatSynSigs: handle type variable bindings >--------------------------------------------------------------- 30146d704ed468ef175488fcea795f5b1905ccde compiler/hsSyn/HsBinds.lhs | 8 +++---- compiler/rename/RnBinds.lhs | 57 +++++++++++++++++++++++++++++++-------------- 2 files changed, 43 insertions(+), 22 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index bbf6bc2..23534cf 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -568,12 +568,12 @@ data Sig name TypeSig [Located name] (LHsType name) -- | A pattern synonym type signature - -- @pattern (Eq b) => P a b :: (Num a) => T a + -- @pattern type forall b. (Eq b) => P a b :: forall a. (Num a) => T a | PatSynSig (Located name) (HsPatSynDetails (LHsType name)) (LHsType name) -- Type - (LHsContext name) -- Provided context - (LHsContext name) -- Required contex + (HsExplicitFlag, LHsTyVarBndrs name, LHsContext name) -- Provided context + (HsExplicitFlag, LHsTyVarBndrs name, LHsContext name) -- Required contex -- | A type signature for a default method inside a class -- @@ -730,7 +730,7 @@ ppr_sig (SpecSig var ty inl) = pragBrackets (pprSpec (unLoc var) (ppr ty) i ppr_sig (InlineSig var inl) = pragBrackets (ppr inl <+> pprPrefixOcc (unLoc var)) ppr_sig (SpecInstSig ty) = pragBrackets (ptext (sLit "SPECIALIZE instance") <+> ppr ty) ppr_sig (MinimalSig bf) = pragBrackets (pprMinimalSig bf) -ppr_sig (PatSynSig name arg_tys ty prov req) +ppr_sig (PatSynSig name arg_tys ty (_, _, prov) (_, _, req)) = pprPatSynSig (unLoc name) False args (ppr ty) (pprCtx prov) (pprCtx req) where args = fmap ppr arg_tys diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index c2489cb..4a98a35 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -30,7 +30,7 @@ import {-# SOURCE #-} RnExpr( rnLExpr, rnStmts ) import HsSyn import TcRnMonad import TcEvidence ( emptyTcEvBinds ) -import RnTypes ( bindSigTyVarsFV, rnHsSigType, rnLHsType, checkPrecMatch, rnContext ) +import RnTypes import RnPat import RnNames import RnEnv @@ -50,6 +50,7 @@ import FastString import Data.List ( partition, sort ) import Maybes ( orElse ) import Control.Monad +import Util ( filterOut ) #if __GLASGOW_HASKELL__ < 709 import Data.Traversable ( traverse ) #endif @@ -841,23 +842,43 @@ renameSig ctxt sig@(MinimalSig bf) = do new_bf <- traverse (lookupSigOccRn ctxt sig) bf return (MinimalSig new_bf, emptyFVs) -renameSig ctxt sig@(PatSynSig v args ty prov req) - = do v' <- lookupSigOccRn ctxt sig v - let doc = quotes (ppr v) - rn_type = rnHsSigType doc - (ty', fvs1) <- rn_type ty - (args', fvs2) <- case args of - PrefixPatSyn tys -> - do (tys, fvs) <- unzip <$> mapM rn_type tys - return (PrefixPatSyn tys, plusFVs fvs) - InfixPatSyn left right -> - do (left', fvs1) <- rn_type left - (right', fvs2) <- rn_type right - return (InfixPatSyn left' right', fvs1 `plusFV` fvs2) - (prov', fvs3) <- rnContext (TypeSigCtx doc) prov - (req', fvs4) <- rnContext (TypeSigCtx doc) req - let fvs = plusFVs [fvs1, fvs2, fvs3, fvs4] - return (PatSynSig v' args' ty' prov' req', fvs) +renameSig ctxt sig@(PatSynSig v args ty (ex_flag, _ex_tvs, prov) (univ_flag, _univ_tvs, req)) + = do { v' <- lookupSigOccRn ctxt sig v + ; let doc = TypeSigCtx $ quotes (ppr v) + ; loc <- getSrcSpanM + + ; let (univ_kvs, univ_tvs) = extractHsTysRdrTyVars (ty:unLoc req) + ; let univ_tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ univ_tvs + + ; bindHsTyVars doc Nothing univ_kvs univ_tv_bndrs $ \ univ_tyvars -> do + { (req', fvs1) <- rnContext doc req + ; (ty', fvs2) <- rnLHsType doc ty + + ; let (arg_tys, rnArgs) = case args of + PrefixPatSyn tys -> + let rnArgs = do + (tys', fvs) <- mapFvRn (rnLHsType doc) tys + return (PrefixPatSyn tys', fvs) + in (tys, rnArgs) + InfixPatSyn ty1 ty2 -> + let rnArgs = do + (ty1', fvs1) <- rnLHsType doc ty1 + (ty2', fvs2) <- rnLHsType doc ty2 + return (InfixPatSyn ty1' ty2', fvs1 `plusFV` fvs2) + in ([ty1, ty2], rnArgs) + + ; let (ex_kvs, ex_tvs) = extractHsTysRdrTyVars (arg_tys ++ unLoc prov) + ex_kvs' = filterOut (`elem` univ_kvs) ex_kvs + ex_tvs' = filterOut (`elem` univ_tvs) ex_tvs + + ; let ex_tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ ex_tvs' + + ; bindHsTyVars doc Nothing ex_kvs' ex_tv_bndrs $ \ ex_tyvars -> do + { (prov', fvs3) <- rnContext doc prov + ; (args', fvs4) <- rnArgs + + ; let fvs = plusFVs [fvs1, fvs2, fvs3, fvs4] + ; return (PatSynSig v' args' ty' (ex_flag, ex_tyvars, prov') (univ_flag, univ_tyvars, req'), fvs) }}} ppr_sig_bndrs :: [Located RdrName] -> SDoc ppr_sig_bndrs bs = quotes (pprWithCommas ppr bs) From git at git.haskell.org Fri Nov 7 15:02:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 15:02:41 +0000 (UTC) Subject: [commit: ghc] wip/T8584: nlHsTyApps: for applying a function both on type- and term-level arguments (31d9f24) Message-ID: <20141107150241.E40C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/31d9f2451ceafc9262586ed104bfb3ed8f9abe07/ghc >--------------------------------------------------------------- commit 31d9f2451ceafc9262586ed104bfb3ed8f9abe07 Author: Dr. ERDI Gergo Date: Fri Nov 7 22:49:52 2014 +0800 nlHsTyApps: for applying a function both on type- and term-level arguments >--------------------------------------------------------------- 31d9f2451ceafc9262586ed104bfb3ed8f9abe07 compiler/hsSyn/HsUtils.lhs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/compiler/hsSyn/HsUtils.lhs b/compiler/hsSyn/HsUtils.lhs index eb348d1..b8ce07f 100644 --- a/compiler/hsSyn/HsUtils.lhs +++ b/compiler/hsSyn/HsUtils.lhs @@ -28,7 +28,7 @@ module HsUtils( mkHsOpApp, mkHsDo, mkHsComp, mkHsWrapPat, mkHsWrapPatCo, mkLHsPar, mkHsCmdCast, - nlHsTyApp, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, + nlHsTyApp, nlHsTyApps, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, nlHsDo, nlHsOpApp, nlHsLam, nlHsPar, nlHsIf, nlHsCase, nlList, mkLHsTupleExpr, mkLHsVarTuple, missingTupArg, toHsType, toHsKind, @@ -177,6 +177,9 @@ mkSimpleHsAlt pat expr nlHsTyApp :: name -> [Type] -> LHsExpr name nlHsTyApp fun_id tys = noLoc (HsWrap (mkWpTyApps tys) (HsVar fun_id)) +nlHsTyApps :: name -> [Type] -> [LHsExpr name] -> LHsExpr name +nlHsTyApps fun_id tys xs = foldl nlHsApp (nlHsTyApp fun_id tys) xs + --------- Adding parens --------- mkLHsPar :: LHsExpr name -> LHsExpr name -- Wrap in parens if hsExprNeedsParens says it needs them From git at git.haskell.org Fri Nov 7 15:02:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 15:02:44 +0000 (UTC) Subject: [commit: ghc] wip/T8584: tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures (808c600) Message-ID: <20141107150244.874043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/808c6001b29e609993cbc03743e90018307faac2/ghc >--------------------------------------------------------------- commit 808c6001b29e609993cbc03743e90018307faac2 Author: Dr. ERDI Gergo Date: Sun Jul 27 14:10:34 2014 +0200 tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures >--------------------------------------------------------------- 808c6001b29e609993cbc03743e90018307faac2 compiler/typecheck/TcBinds.lhs | 45 +++++++-- compiler/typecheck/TcClassDcl.lhs | 4 +- compiler/typecheck/TcPat.lhs | 23 ++++- compiler/typecheck/TcPatSyn.lhs | 185 ++++++++++++++++++++++++++--------- compiler/typecheck/TcPatSyn.lhs-boot | 9 +- 5 files changed, 208 insertions(+), 58 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 808c6001b29e609993cbc03743e90018307faac2 From git at git.haskell.org Fri Nov 7 15:02:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 15:02:47 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Show foralls (when requested) in pattern synonym types (8c9b869) Message-ID: <20141107150247.1D4383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/8c9b869d3b3bce3e24a2db6b50984fd530fa9df3/ghc >--------------------------------------------------------------- commit 8c9b869d3b3bce3e24a2db6b50984fd530fa9df3 Author: Dr. ERDI Gergo Date: Sun Aug 3 15:26:13 2014 +0200 Show foralls (when requested) in pattern synonym types >--------------------------------------------------------------- 8c9b869d3b3bce3e24a2db6b50984fd530fa9df3 compiler/hsSyn/HsBinds.lhs | 21 ++++++--------------- compiler/iface/IfaceSyn.lhs | 9 +++++---- 2 files changed, 11 insertions(+), 19 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index f75fa2e..5a45956 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -730,24 +730,18 @@ ppr_sig (SpecSig var ty inl) = pragBrackets (pprSpec (unLoc var) (ppr ty) i ppr_sig (InlineSig var inl) = pragBrackets (ppr inl <+> pprPrefixOcc (unLoc var)) ppr_sig (SpecInstSig ty) = pragBrackets (ptext (sLit "SPECIALIZE instance") <+> ppr ty) ppr_sig (MinimalSig bf) = pragBrackets (pprMinimalSig bf) -ppr_sig (PatSynSig name arg_tys ty (_, _, prov) (_, _, req)) +ppr_sig (PatSynSig name arg_tys ty prov req) = pprPatSynSig (unLoc name) False args (ppr ty) (pprCtx prov) (pprCtx req) where args = fmap ppr arg_tys - pprCtx lctx = case unLoc lctx of - [] -> Nothing - ctx -> Just (pprHsContextNoArrow ctx) + pprCtx (flag, tvs, lctx) = pprHsForAll flag tvs lctx pprPatSynSig :: (OutputableBndr a) - => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> Maybe SDoc -> Maybe SDoc -> SDoc -pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta - = sep [ ptext (sLit "pattern") - , ptext (sLit "type") - , thetaOpt prov_theta, name_and_args - , colon - , thetaOpt req_theta, rhs_ty - ] + => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> SDoc -> SDoc -> SDoc +pprPatSynSig ident is_bidir args rhs_ty prov req + = ptext (sLit "pattern type") <+> + prov <+> name_and_args <+> colon <+> req <+> rhs_ty where name_and_args = case args of PrefixPatSyn arg_tys -> @@ -755,9 +749,6 @@ pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta InfixPatSyn left_ty right_ty -> left_ty <+> pprInfixOcc ident <+> right_ty - -- TODO: support explicit foralls - thetaOpt = maybe empty (<+> darrow) - colon = if is_bidir then dcolon else dcolon -- TODO instance OutputableBndr name => Outputable (FixitySig name) where diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 7e2d6f2..d900875 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -761,11 +761,13 @@ pprIfaceDecl ss (IfaceSyn { ifName = tycon, ifTyVars = tyvars pprIfaceDecl _ (IfacePatSyn { ifName = name, ifPatWrapper = wrapper, ifPatIsInfix = is_infix, - ifPatUnivTvs = _univ_tvs, ifPatExTvs = _ex_tvs, + ifPatUnivTvs = univ_tvs, ifPatExTvs = ex_tvs, ifPatProvCtxt = prov_ctxt, ifPatReqCtxt = req_ctxt, ifPatArgs = args, ifPatTy = ty }) - = pprPatSynSig name has_wrap args' ty' (pprCtxt prov_ctxt) (pprCtxt req_ctxt) + = pprPatSynSig name has_wrap args' ty' + (pprCtxt ex_tvs prov_ctxt) + (pprCtxt univ_tvs req_ctxt) where has_wrap = isJust wrapper args' = case (is_infix, args) of @@ -776,8 +778,7 @@ pprIfaceDecl _ (IfacePatSyn { ifName = name, ifPatWrapper = wrapper, ty' = pprParendIfaceType ty - pprCtxt [] = Nothing - pprCtxt ctxt = Just $ pprIfaceContext ctxt + pprCtxt tvs ctxt = pprIfaceForAllPart tvs ctxt empty pprIfaceDecl ss (IfaceId { ifName = var, ifType = ty, ifIdDetails = details, ifIdInfo = info }) From git at git.haskell.org Fri Nov 7 15:02:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 15:02:49 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Update baseline shift/reduce conflict number (4225763) Message-ID: <20141107150249.A47D83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/4225763f683e61e1faaafeb1976d10668a3f0077/ghc >--------------------------------------------------------------- commit 4225763f683e61e1faaafeb1976d10668a3f0077 Author: Dr. ERDI Gergo Date: Wed Jul 2 19:18:43 2014 +0800 Update baseline shift/reduce conflict number >--------------------------------------------------------------- 4225763f683e61e1faaafeb1976d10668a3f0077 compiler/parser/Parser.y.pp | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/compiler/parser/Parser.y.pp b/compiler/parser/Parser.y.pp index e33808d..e0eaf4d 100644 --- a/compiler/parser/Parser.y.pp +++ b/compiler/parser/Parser.y.pp @@ -72,6 +72,12 @@ import Control.Monad ( mplus ) {- ----------------------------------------------------------------------------- +25 June 2014 + +Conflicts: 47 shift/reduce + 1 reduce/reduce + +----------------------------------------------------------------------------- 12 October 2012 Conflicts: 43 shift/reduce From git at git.haskell.org Fri Nov 7 15:02:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 15:02:52 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add parser for pattern synonym type signatures. Syntax is of the form (39ce4cd) Message-ID: <20141107150252.43EAA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/39ce4cd710754943ebf26cd2f0390bd6b4c6884e/ghc >--------------------------------------------------------------- commit 39ce4cd710754943ebf26cd2f0390bd6b4c6884e Author: Dr. ERDI Gergo Date: Mon Jul 14 18:18:44 2014 +0800 Add parser for pattern synonym type signatures. Syntax is of the form pattern type Eq a => P a T b :: Num b => R a b which declares a pattern synonym called P, with argument types a, T, and b. >--------------------------------------------------------------- 39ce4cd710754943ebf26cd2f0390bd6b4c6884e compiler/hsSyn/HsBinds.lhs | 1 + compiler/hsSyn/HsTypes.lhs | 19 +++++++++++++------ compiler/parser/Parser.y.pp | 9 +++++++-- compiler/parser/RdrHsSyn.lhs | 31 ++++++++++++++++++++++++++++++- 4 files changed, 51 insertions(+), 9 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index 23534cf..f75fa2e 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -743,6 +743,7 @@ pprPatSynSig :: (OutputableBndr a) => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> Maybe SDoc -> Maybe SDoc -> SDoc pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta = sep [ ptext (sLit "pattern") + , ptext (sLit "type") , thetaOpt prov_theta, name_and_args , colon , thetaOpt req_theta, rhs_ty diff --git a/compiler/hsSyn/HsTypes.lhs b/compiler/hsSyn/HsTypes.lhs index 9bd5845..db4d976 100644 --- a/compiler/hsSyn/HsTypes.lhs +++ b/compiler/hsSyn/HsTypes.lhs @@ -39,7 +39,7 @@ module HsTypes ( hsLTyVarName, hsLTyVarNames, hsLTyVarLocName, hsLTyVarLocNames, splitLHsInstDeclTy_maybe, splitHsClassTy_maybe, splitLHsClassTy_maybe, - splitHsFunType, + splitHsFunType, splitLHsForAllTyFlag, splitLHsForAllTy, splitHsAppTys, hsTyGetAppHead_maybe, mkHsAppTys, mkHsOpTy, -- Printing @@ -510,15 +510,22 @@ splitLHsInstDeclTy_maybe inst_ty = do (cls, tys) <- splitLHsClassTy_maybe ty return (tvs, cxt, cls, tys) +splitLHsForAllTyFlag + :: LHsType name + -> (HsExplicitFlag, LHsTyVarBndrs name, HsContext name, LHsType name) +splitLHsForAllTyFlag poly_ty + = case unLoc poly_ty of + HsParTy ty -> splitLHsForAllTyFlag ty + HsForAllTy flag tvs cxt ty -> (flag, tvs, unLoc cxt, ty) + _ -> (Implicit, emptyHsQTvs, [], poly_ty) + -- The type vars should have been computed by now, even if they were implicit + splitLHsForAllTy :: LHsType name -> (LHsTyVarBndrs name, HsContext name, LHsType name) splitLHsForAllTy poly_ty - = case unLoc poly_ty of - HsParTy ty -> splitLHsForAllTy ty - HsForAllTy _ tvs cxt ty -> (tvs, unLoc cxt, ty) - _ -> (emptyHsQTvs, [], poly_ty) - -- The type vars should have been computed by now, even if they were implicit + = let (_, tvs, cxt, ty) = splitLHsForAllTyFlag poly_ty + in (tvs, cxt, ty) splitHsClassTy_maybe :: HsType name -> Maybe (name, [LHsType name]) splitHsClassTy_maybe ty = fmap (\(L _ n, tys) -> (n, tys)) $ splitLHsClassTy_maybe (noLoc ty) diff --git a/compiler/parser/Parser.y.pp b/compiler/parser/Parser.y.pp index e0eaf4d..41ad6f0 100644 --- a/compiler/parser/Parser.y.pp +++ b/compiler/parser/Parser.y.pp @@ -856,8 +856,7 @@ role : VARID { L1 $ Just $ getVARID $1 } pattern_synonym_decl :: { LHsDecl RdrName } : 'pattern' pat '=' pat {% do { (name, args) <- splitPatSyn $2 - ; return $ LL . ValD $ mkPatSynBind name args $4 ImplicitBidirectional - }} + ; return $ LL . ValD $ mkPatSynBind name args $4 ImplicitBidirectional }} | 'pattern' pat '<-' pat {% do { (name, args) <- splitPatSyn $2 ; return $ LL . ValD $ mkPatSynBind name args $4 Unidirectional @@ -873,6 +872,11 @@ where_decls :: { Located (OrdList (LHsDecl RdrName)) } : 'where' '{' decls '}' { $3 } | 'where' vocurly decls close { $3 } +pattern_synonym_sig :: { LSig RdrName } + : 'pattern' 'type' ctype '::' ctype + {% do { (name, details, ty, prov, req) <- splitPatSynSig $3 $5 + ; return . LL $ PatSynSig name details ty prov req }} + vars0 :: { [Located RdrName] } : {- empty -} { [] } | varid vars0 { $1 : $2 } @@ -1484,6 +1488,7 @@ sigdecl :: { Located (OrdList (LHsDecl RdrName)) } { LL $ toOL [ LL $ SigD (TypeSig ($1 : reverse (unLoc $3)) $5) ] } | infix prec ops { LL $ toOL [ LL $ SigD (FixSig (FixitySig n (Fixity $2 (unLoc $1)))) | n <- unLoc $3 ] } + | pattern_synonym_sig { LL . unitOL $ LL . SigD . unLoc $ $1 } | '{-# INLINE' activation qvar '#-}' { LL $ unitOL (LL $ SigD (InlineSig $3 (mkInlinePragma (getINLINE $1) $2))) } | '{-# SPECIALISE' activation qvar '::' sigtypes1 '#-}' diff --git a/compiler/parser/RdrHsSyn.lhs b/compiler/parser/RdrHsSyn.lhs index e6969e7..3152642 100644 --- a/compiler/parser/RdrHsSyn.lhs +++ b/compiler/parser/RdrHsSyn.lhs @@ -18,7 +18,7 @@ module RdrHsSyn ( mkTyFamInst, mkFamDecl, splitCon, mkInlinePragma, - splitPatSyn, toPatSynMatchGroup, + splitPatSyn, splitPatSynSig, toPatSynMatchGroup, mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp mkTyClD, mkInstD, @@ -471,6 +471,35 @@ toPatSynMatchGroup (L _ patsyn_name) (L _ decls) = text "pattern synonym 'where' clause must bind the pattern synonym's name" <+> quotes (ppr patsyn_name) $$ ppr decl +-- Given two types like +-- Eq a => P a T b +-- and +-- Num b => R a b +-- +-- This returns +-- P as the name, +-- PrefixPatSyn [a, T, b] as the details, +-- R a b as the result type, +-- and (Eq a) and (Num b) as the provided and required thetas (respectively) +splitPatSynSig :: LHsType RdrName + -> LHsType RdrName + -> P (Located RdrName, HsPatSynDetails (LHsType RdrName), LHsType RdrName, + (HsExplicitFlag, LHsTyVarBndrs RdrName, LHsContext RdrName), + (HsExplicitFlag, LHsTyVarBndrs RdrName, LHsContext RdrName)) +splitPatSynSig lty1 lty2 = do + (name, details) <- splitCon pat_ty + details' <- case details of + PrefixCon tys -> return $ PrefixPatSyn tys + InfixCon ty1 ty2 -> return $ InfixPatSyn ty1 ty2 + RecCon{} -> parseErrorSDoc (getLoc lty1) $ + text "record syntax not supported for pattern synonym declarations:" $$ ppr lty1 + return (name, details', res_ty, (ex_flag, ex_tvs, prov'), (univ_flag, univ_tvs, req')) + where + (ex_flag, ex_tvs, prov, pat_ty) = splitLHsForAllTyFlag lty1 + (univ_flag, univ_tvs, req, res_ty) = splitLHsForAllTyFlag lty2 + prov' = L (getLoc lty1) prov + req' = L (getLoc lty2) req + mkDeprecatedGadtRecordDecl :: SrcSpan -> Located RdrName -> [ConDeclField RdrName] From git at git.haskell.org Fri Nov 7 15:02:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 15:02:55 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add test cases (6a59846) Message-ID: <20141107150255.409683A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/6a5984609aabbc1e2ae89fe3c3a4af99ae4e649d/ghc >--------------------------------------------------------------- commit 6a5984609aabbc1e2ae89fe3c3a4af99ae4e649d Author: Dr. ERDI Gergo Date: Sun Nov 2 14:35:49 2014 +0800 Add test cases >--------------------------------------------------------------- 6a5984609aabbc1e2ae89fe3c3a4af99ae4e649d testsuite/tests/patsyn/should_compile/T8584-1.hs | 10 ++++++++++ testsuite/tests/patsyn/should_compile/T8968-1.hs | 8 ++++++++ testsuite/tests/patsyn/should_compile/all.T | 2 ++ 3 files changed, 20 insertions(+) diff --git a/testsuite/tests/patsyn/should_compile/T8584-1.hs b/testsuite/tests/patsyn/should_compile/T8584-1.hs new file mode 100644 index 0000000..7a017c8 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8584-1.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms #-} +module ShouldCompile where + +pattern type (Eq a) => Single a :: (Show a) => [a] +-- pattern type Single a :: (Eq a, Show a) => [a] +-- pattern type Single a :: [a] +pattern Single x = [x] + +-- f :: (Show a) => [a] -> a +foobar (Single x) = x diff --git a/testsuite/tests/patsyn/should_compile/T8968-1.hs b/testsuite/tests/patsyn/should_compile/T8968-1.hs new file mode 100644 index 0000000..f4a1dc4 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8968-1.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE GADTs, KindSignatures, PatternSynonyms #-} +module ShouldCompile where + +data X :: (* -> *) -> * -> * where + Y :: f a -> X f (Maybe a) + +pattern type C a :: X Maybe (Maybe a) +pattern C x = Y (Just x) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index d851bc3..8896008 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -10,3 +10,5 @@ test('incomplete', normal, compile, ['']) test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) +test('T8968-1', normal, compile, ['']) +test('T8584-1', normal, compile, ['']) From git at git.haskell.org Fri Nov 7 16:16:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 16:16:42 +0000 (UTC) Subject: [commit: ghc] master: Have validate take into account stat test failures too. (832ef3f) Message-ID: <20141107161642.28BA13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/832ef3fb8f45f98add9dbfac5387281e3e0bc5dc/ghc >--------------------------------------------------------------- commit 832ef3fb8f45f98add9dbfac5387281e3e0bc5dc Author: Gintautas Miliauskas Date: Fri Nov 7 10:17:03 2014 -0600 Have validate take into account stat test failures too. This should have gone in with the update in testlib.py to split off stat test failures into a separate category in the summary. Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D451 >--------------------------------------------------------------- 832ef3fb8f45f98add9dbfac5387281e3e0bc5dc validate | 1 + 1 file changed, 1 insertion(+) diff --git a/validate b/validate index c6e6d69..7464be9 100755 --- a/validate +++ b/validate @@ -257,6 +257,7 @@ if grep '\<0 caused framework failures' testlog >/dev/null 2>/dev/null && grep '\<0 unexpected passes' testlog >/dev/null 2>/dev/null && grep '\<0 unexpected failures' testlog >/dev/null 2>/dev/null && + grep '\<0 unexpected stat failures' testlog >/dev/null 2>/dev/null && ! grep 'Some files are written by multiple tests' testlog >/dev/null 2>/dev/null ; then if [ $testsuite_only -eq 0 ] && [ $no_clean -eq 0 ] then From git at git.haskell.org Fri Nov 7 16:23:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 16:23:52 +0000 (UTC) Subject: [commit: ghc] master: base: Manually unlit .lhs into .hs modules (df3b1d4) Message-ID: <20141107162352.2ADFC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/df3b1d43cc862fe03f0724a9c0ac9e7cecdf4605/ghc >--------------------------------------------------------------- commit df3b1d43cc862fe03f0724a9c0ac9e7cecdf4605 Author: Herbert Valerio Riedel Date: Fri Nov 7 16:26:59 2014 +0100 base: Manually unlit .lhs into .hs modules This commit mostly converts literate comments into ordinary Haskell comments or sometimes even Haddock comments, while also removing literate comments in a few cases where they don't make much sense anymore. Moreover, in a few cases trailing whitespaces were removed as well. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D456 >--------------------------------------------------------------- df3b1d43cc862fe03f0724a9c0ac9e7cecdf4605 libraries/base/GHC/{Arr.lhs => Arr.hs} | 70 ++-------- libraries/base/GHC/{Base.lhs => Base.hs} | 153 +++++---------------- libraries/base/GHC/{Conc.lhs => Conc.hs} | 3 - libraries/base/GHC/{Enum.lhs => Enum.hs} | 91 ++++-------- libraries/base/GHC/{Err.lhs => Err.hs} | 25 +--- libraries/base/GHC/{Exception.lhs => Exception.hs} | 22 --- .../GHC/{Exception.lhs-boot => Exception.hs-boot} | 14 +- libraries/base/GHC/{Float.lhs => Float.hs} | 121 ++++++---------- libraries/base/GHC/{List.lhs => List.hs} | 53 ++----- libraries/base/GHC/{Num.lhs => Num.hs} | 36 ----- libraries/base/GHC/{Pack.lhs => Pack.hs} | 2 - libraries/base/GHC/{Ptr.lhs => Ptr.hs} | 3 - libraries/base/GHC/{Read.lhs => Read.hs} | 62 ++------- libraries/base/GHC/{Real.lhs => Real.hs} | 121 +++++----------- libraries/base/GHC/{ST.lhs => ST.hs} | 18 +-- libraries/base/GHC/{STRef.lhs => STRef.hs} | 3 - libraries/base/GHC/{Show.lhs => Show.hs} | 65 ++------- libraries/base/GHC/{Stable.lhs => Stable.hs} | 3 - libraries/base/GHC/{Storable.lhs => Storable.hs} | 6 - .../base/GHC/{TopHandler.lhs => TopHandler.hs} | 3 - libraries/base/GHC/{Weak.lhs => Weak.hs} | 3 - 21 files changed, 192 insertions(+), 685 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc df3b1d43cc862fe03f0724a9c0ac9e7cecdf4605 From git at git.haskell.org Fri Nov 7 16:48:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 16:48:59 +0000 (UTC) Subject: [commit: ghc] master: Preserve argument order to (==)/eq in nub and nubBy (a2e7bbf) Message-ID: <20141107164859.44F703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a2e7bbfe7656cf7dbf1af4da5c077ac0b5d41127/ghc >--------------------------------------------------------------- commit a2e7bbfe7656cf7dbf1af4da5c077ac0b5d41127 Author: Thomas Miedema Date: Fri Nov 7 17:38:59 2014 +0100 Preserve argument order to (==)/eq in nub and nubBy This makes nub and nubBy behave as specified in the Haskell 98 Report. This reverts 0ad9def53842e86fb292eccb810190711c42d7c5, and fixes #3280, #7913 and #2528 (properly). Before this change, the output of `T2528` was (4x wrong): ``` [A,B] [1,2] False False ``` Reviewed By: dfeuer, ekmett, austin, hvr Differential Revision: https://phabricator.haskell.org/D238 >--------------------------------------------------------------- a2e7bbfe7656cf7dbf1af4da5c077ac0b5d41127 libraries/base/Data/OldList.hs | 17 +++++------------ libraries/base/changelog.md | 4 ++++ libraries/base/tests/.gitignore | 1 + libraries/base/tests/T2528.hs | 27 +++++++++++++++++++++++++++ libraries/base/tests/T2528.stdout | 4 ++++ libraries/base/tests/all.T | 2 ++ 6 files changed, 43 insertions(+), 12 deletions(-) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index e1de19a..caad044 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -338,17 +338,7 @@ isInfixOf needle haystack = any (isPrefixOf needle) (tails haystack) -- It is a special case of 'nubBy', which allows the programmer to supply -- their own equality test. nub :: (Eq a) => [a] -> [a] -#ifdef USE_REPORT_PRELUDE nub = nubBy (==) -#else --- stolen from HBC -nub l = nub' l [] -- ' - where - nub' [] _ = [] -- ' - nub' (x:xs) ls -- ' - | x `elem` ls = nub' xs ls -- ' - | otherwise = x : nub' xs (x:ls) -- ' -#endif -- | The 'nubBy' function behaves just like 'nub', except it uses a -- user-supplied equality predicate instead of the overloaded '==' @@ -358,6 +348,7 @@ nubBy :: (a -> a -> Bool) -> [a] -> [a] nubBy eq [] = [] nubBy eq (x:xs) = x : nubBy eq (filter (\ y -> not (eq x y)) xs) #else +-- stolen from HBC nubBy eq l = nubBy' l [] where nubBy' [] _ = [] @@ -367,12 +358,14 @@ nubBy eq l = nubBy' l [] -- Not exported: -- Note that we keep the call to `eq` with arguments in the --- same order as in the reference implementation +-- same order as in the reference (prelude) implementation, +-- and that this order is different from how `elem` calls (==). +-- See #2528, #3280 and #7913. -- 'xs' is the list of things we've seen so far, -- 'y' is the potential new element elem_by :: (a -> a -> Bool) -> a -> [a] -> Bool elem_by _ _ [] = False -elem_by eq y (x:xs) = y `eq` x || elem_by eq y xs +elem_by eq y (x:xs) = x `eq` y || elem_by eq y xs #endif diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 86595d6..2fa25ae 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -93,6 +93,10 @@ * Add `isSubsequenceOf` to `Data.List` (#9767) + * The arguments to `==` and `eq` in `Data.List.nub` and `Data.List.nubBy` + are swapped, such that `Data.List.nubBy (<) [1,2]` now returns `[1]` + instead of `[1,2]` (#2528, #3280, #7913) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 diff --git a/libraries/base/tests/.gitignore b/libraries/base/tests/.gitignore index 973ab9d..af90b5e 100644 --- a/libraries/base/tests/.gitignore +++ b/libraries/base/tests/.gitignore @@ -190,6 +190,7 @@ /System/getArgs001 /System/getEnv001 /System/system001 +/T2528 /T4006 /T5943 /T5962 diff --git a/libraries/base/tests/T2528.hs b/libraries/base/tests/T2528.hs new file mode 100644 index 0000000..f1568db --- /dev/null +++ b/libraries/base/tests/T2528.hs @@ -0,0 +1,27 @@ +module Main where + +import qualified Data.List as L + +-- USE_REPORT_PRELUDE versions of nub and nubBy, copied from +-- libraries/base/Data/OldList.hs. +nub :: (Eq a) => [a] -> [a] +nub = nubBy (==) + +nubBy :: (a -> a -> Bool) -> [a] -> [a] +nubBy eq [] = [] +nubBy eq (x:xs) = x : nubBy eq (filter (\ y -> not (eq x y)) xs) + +data Asymmetric = A | B deriving Show + +instance Eq Asymmetric where + A == _ = True + B == _ = False + +main :: IO() +main = do + print $ L.nub [A,B] + print $ L.nubBy (<) [1,2] + -- The implementation from Data.List and the one from the Prelude defined in + -- the Haskell 98 report should have the same behavior. + print $ L.nub [A,B] == nub [A,B] + print $ L.nubBy (<) [1,2] == nubBy (<) [1,2] diff --git a/libraries/base/tests/T2528.stdout b/libraries/base/tests/T2528.stdout new file mode 100644 index 0000000..4f90091 --- /dev/null +++ b/libraries/base/tests/T2528.stdout @@ -0,0 +1,4 @@ +[A] +[1] +True +True diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T index f7944f4..d4005b7 100644 --- a/libraries/base/tests/all.T +++ b/libraries/base/tests/all.T @@ -110,6 +110,8 @@ test('stableptr005', normal, compile_and_run, ['']) test('weak001', normal, compile_and_run, ['']) +test('T2528', normal, compile_and_run, ['']) + # In the 65001 codepage, we can't even cat the expected output on msys: # $ cat 4006.stdout # It works here From git at git.haskell.org Fri Nov 7 21:37:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 21:37:22 +0000 (UTC) Subject: [commit: ghc] wip/rae: Testsuite wibbles due to #9204 (6cea8a4) Message-ID: <20141107213722.3EF343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/6cea8a49f38bd3ae50a4d77ac56912be34ece585/ghc >--------------------------------------------------------------- commit 6cea8a49f38bd3ae50a4d77ac56912be34ece585 Author: Richard Eisenberg Date: Fri Nov 7 16:32:39 2014 -0500 Testsuite wibbles due to #9204 >--------------------------------------------------------------- 6cea8a49f38bd3ae50a4d77ac56912be34ece585 .../indexed-types/should_fail/ClosedFam3.stderr | 1 + testsuite/tests/rename/should_fail/rnfail055.stderr | 20 ++++++++++++++++---- testsuite/tests/roles/should_fail/Roles12.stderr | 1 + testsuite/tests/typecheck/should_fail/T3468.stderr | 1 + .../tests/typecheck/should_fail/tcfail220.stderr | 2 ++ 5 files changed, 21 insertions(+), 4 deletions(-) diff --git a/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr b/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr index 04435ba..3b9539e 100644 --- a/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr +++ b/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr @@ -25,3 +25,4 @@ ClosedFam3.hs-boot:12:1: Baz Int = Bool Boot file: type family Baz (a :: k) :: * where Baz * Int = Bool + The types have different kinds diff --git a/testsuite/tests/rename/should_fail/rnfail055.stderr b/testsuite/tests/rename/should_fail/rnfail055.stderr index c7b51a1..1c002ac 100644 --- a/testsuite/tests/rename/should_fail/rnfail055.stderr +++ b/testsuite/tests/rename/should_fail/rnfail055.stderr @@ -10,34 +10,38 @@ RnFail055.hs-boot:4:1: and its hs-boot file Main module: f1 :: Int -> Float Boot file: f1 :: Float -> Int + The two types are different RnFail055.hs-boot:6:1: Type constructor ?S1? has conflicting definitions in the module and its hs-boot file Main module: type S1 a b = (a, b) Boot file: type S1 a b c = (a, b) + The types have different kinds RnFail055.hs-boot:8:1: Type constructor ?S2? has conflicting definitions in the module and its hs-boot file Main module: type S2 a b = forall a1. (a1, b) Boot file: type S2 a b = forall b1. (a, b1) + The roles do not match. Roles default to ?representational? in boot files RnFail055.hs-boot:12:1: Type constructor ?T1? has conflicting definitions in the module and its hs-boot file Main module: data T1 a b = T1 [b] [a] Boot file: data T1 a b = T1 [a] [b] + The constructors do not match: The types for ?T1? differ RnFail055.hs-boot:14:1: Type constructor ?T2? has conflicting definitions in the module and its hs-boot file Main module: type role T2 representational nominal - data Eq b => T2 a b - = T2 a + data Eq b => T2 a b = T2 a Boot file: type role T2 nominal representational - data Eq a => T2 a b - = T2 a + data Eq a => T2 a b = T2 a + The roles do not match. Roles default to ?representational? in boot files + The datatype contexts do not match RnFail055.hs-boot:16:11: T3 is exported by the hs-boot file, but not exported by the module @@ -50,12 +54,16 @@ RnFail055.hs-boot:21:1: and its hs-boot file Main module: data T5 a = T5 {field5 :: a} Boot file: data T5 a = T5 a + The constructors do not match: + The record label lists for ?T5? differ RnFail055.hs-boot:23:1: Type constructor ?T6? has conflicting definitions in the module and its hs-boot file Main module: data T6 = T6 Int Boot file: data T6 = T6 !Int + The constructors do not match: + The strictness annotations for ?T6? differ RnFail055.hs-boot:25:1: Type constructor ?T7? has conflicting definitions in the module @@ -64,6 +72,8 @@ RnFail055.hs-boot:25:1: data T7 a where T7 :: a1 -> T7 a Boot file: data T7 a = T7 a + The roles do not match. Roles default to ?representational? in boot files + The constructors do not match: The types for ?T7? differ RnFail055.hs-boot:27:22: RnFail055.m1 is exported by the hs-boot file, but not exported by the module @@ -76,9 +86,11 @@ RnFail055.hs-boot:28:1: m2' :: a -> b Boot file: class C2 a b where m2 :: a -> b + The methods do not match: There are different numbers of methods RnFail055.hs-boot:29:1: Class ?C3? has conflicting definitions in the module and its hs-boot file Main module: class (Eq a, Ord a) => C3 a Boot file: class (Ord a, Eq a) => C3 a + The class constraints do not match diff --git a/testsuite/tests/roles/should_fail/Roles12.stderr b/testsuite/tests/roles/should_fail/Roles12.stderr index 9b0f2cf..874ddca 100644 --- a/testsuite/tests/roles/should_fail/Roles12.stderr +++ b/testsuite/tests/roles/should_fail/Roles12.stderr @@ -5,3 +5,4 @@ Roles12.hs:5:1: Main module: type role T phantom data T a Boot file: abstract T a + The roles do not match. Roles default to ?representational? in boot files diff --git a/testsuite/tests/typecheck/should_fail/T3468.stderr b/testsuite/tests/typecheck/should_fail/T3468.stderr index 26ec192..9284df2 100644 --- a/testsuite/tests/typecheck/should_fail/T3468.stderr +++ b/testsuite/tests/typecheck/should_fail/T3468.stderr @@ -6,3 +6,4 @@ T3468.hs-boot:3:1: data Tool d where F :: a -> Tool d Boot file: abstract Tool + The types have different kinds diff --git a/testsuite/tests/typecheck/should_fail/tcfail220.stderr b/testsuite/tests/typecheck/should_fail/tcfail220.stderr index aea7906..e565cc7 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail220.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail220.stderr @@ -5,9 +5,11 @@ tcfail220.hsig:4:1: and its hsig file Main module: data Bool = False | GHC.Types.True Hsig file: data Bool a b c d = False + The types have different kinds tcfail220.hsig:5:1: Type constructor ?Maybe? has conflicting definitions in the module and its hsig file Main module: data Maybe a = Nothing | GHC.Base.Just a Hsig file: data Maybe a b = Nothing + The types have different kinds From git at git.haskell.org Fri Nov 7 21:37:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 21:37:25 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9204 in roles/should_fail/T9204 (03f9953) Message-ID: <20141107213725.8B42A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/03f99538876e2f9710356cd0cad3b9ac536d9660/ghc >--------------------------------------------------------------- commit 03f99538876e2f9710356cd0cad3b9ac536d9660 Author: Richard Eisenberg Date: Tue Nov 4 17:40:06 2014 -0500 Test #9204 in roles/should_fail/T9204 >--------------------------------------------------------------- 03f99538876e2f9710356cd0cad3b9ac536d9660 testsuite/tests/roles/should_fail/Makefile | 4 ++++ testsuite/tests/roles/should_fail/T9204.hs | 6 ++++++ testsuite/tests/roles/should_fail/T9204.hs-boot | 4 ++++ testsuite/tests/roles/should_fail/T9204.stderr | 8 ++++++++ testsuite/tests/roles/should_fail/all.T | 2 ++ 5 files changed, 24 insertions(+) diff --git a/testsuite/tests/roles/should_fail/Makefile b/testsuite/tests/roles/should_fail/Makefile index 8f80de3..14d6720 100644 --- a/testsuite/tests/roles/should_fail/Makefile +++ b/testsuite/tests/roles/should_fail/Makefile @@ -7,3 +7,7 @@ include $(TOP)/mk/test.mk Roles12: '$(TEST_HC)' $(TEST_HC_OPTS) -c Roles12.hs-boot -'$(TEST_HC)' $(TEST_HC_OPTS) -c Roles12.hs + +T9204: + '$(TEST_HC)' $(TEST_HC_OPTS) -c T9204.hs-boot + -'$(TEST_HC)' $(TEST_HC_OPTS) -c T9204.hs diff --git a/testsuite/tests/roles/should_fail/T9204.hs b/testsuite/tests/roles/should_fail/T9204.hs new file mode 100644 index 0000000..e2351a2 --- /dev/null +++ b/testsuite/tests/roles/should_fail/T9204.hs @@ -0,0 +1,6 @@ + +module T9204 where + +import {-# SOURCE #-} T9204 + +data D a diff --git a/testsuite/tests/roles/should_fail/T9204.hs-boot b/testsuite/tests/roles/should_fail/T9204.hs-boot new file mode 100644 index 0000000..7ee0f1d --- /dev/null +++ b/testsuite/tests/roles/should_fail/T9204.hs-boot @@ -0,0 +1,4 @@ + +module T9204 where + +data D a diff --git a/testsuite/tests/roles/should_fail/T9204.stderr b/testsuite/tests/roles/should_fail/T9204.stderr new file mode 100644 index 0000000..9936839 --- /dev/null +++ b/testsuite/tests/roles/should_fail/T9204.stderr @@ -0,0 +1,8 @@ + +T9204.hs:6:1: + Type constructor ?D? has conflicting definitions in the module + and its hs-boot file + Main module: type role D phantom + data D a + Boot file: abstract D a + The roles do not match. Roles default to ?representational? in boot files diff --git a/testsuite/tests/roles/should_fail/all.T b/testsuite/tests/roles/should_fail/all.T index d0d5c4d..bb90fee 100644 --- a/testsuite/tests/roles/should_fail/all.T +++ b/testsuite/tests/roles/should_fail/all.T @@ -8,3 +8,5 @@ test('Roles12', extra_clean(['Roles12.o-boot', 'Roles12.hi-boot']), run_command, ['$MAKE --no-print-directory -s Roles12']) test('T8773', normal, compile_fail, ['']) +test('T9204', [ expect_broken(9204), extra_clean(['T9204.o-boot', 'T9204.hi-boot']) ], + run_command, ['$MAKE --no-print-directory -s T9204']) From git at git.haskell.org Fri Nov 7 21:37:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 21:37:28 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9204 by outputting extra info on boot file mismatch. (25d7b84) Message-ID: <20141107213728.29A0B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/25d7b84ed2072031b97c5a6ca820c5193649d355/ghc >--------------------------------------------------------------- commit 25d7b84ed2072031b97c5a6ca820c5193649d355 Author: Richard Eisenberg Date: Wed Nov 5 10:52:57 2014 -0500 Fix #9204 by outputting extra info on boot file mismatch. >--------------------------------------------------------------- 25d7b84ed2072031b97c5a6ca820c5193649d355 compiler/typecheck/TcRnDriver.lhs | 182 +++++++++++++++++++++++--------- testsuite/tests/roles/should_fail/all.T | 2 +- 2 files changed, 135 insertions(+), 49 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 25d7b84ed2072031b97c5a6ca820c5193649d355 From git at git.haskell.org Fri Nov 7 21:41:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 21:41:44 +0000 (UTC) Subject: [commit: ghc] ghc-validate: Typofix. (b608868) Message-ID: <20141107214144.DD4F23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-validate Link : http://ghc.haskell.org/trac/ghc/changeset/b60886891bd8faae066cbf8c5c2da775a049cd88/ghc >--------------------------------------------------------------- commit b60886891bd8faae066cbf8c5c2da775a049cd88 Author: Edward Z. Yang Date: Thu Nov 6 15:04:03 2014 -0800 Typofix. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- b60886891bd8faae066cbf8c5c2da775a049cd88 compiler/typecheck/FunDeps.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/FunDeps.lhs b/compiler/typecheck/FunDeps.lhs index 36dc641..6fb9b3f 100644 --- a/compiler/typecheck/FunDeps.lhs +++ b/compiler/typecheck/FunDeps.lhs @@ -525,7 +525,7 @@ if s1 matches checkFunDeps :: (InstEnv, InstEnv) -> ClsInst -> Maybe [ClsInst] -- Nothing <=> ok -- Just dfs <=> conflict with dfs --- Check wheher adding DFunId would break functional-dependency constraints +-- Check whether adding DFunId would break functional-dependency constraints -- Used only for instance decls defined in the module being compiled checkFunDeps inst_envs ispec | null bad_fundeps = Nothing From git at git.haskell.org Fri Nov 7 21:41:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 21:41:48 +0000 (UTC) Subject: [commit: ghc] ghc-validate's head updated: Typofix. (b608868) Message-ID: <20141107214148.14CD33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'ghc-validate' now includes: 39666ae Update haddock submodule with lazy IO fix. d3f56ec Rewrite section 1 of the Backpack manual. [skip ci] 674c631 Name worker threads using pthread_setname_np 97b7593 rts: don't crash on 'hs_init(NULL, NULL)' in debug rts ad4a713 Remove a few redundant `.hs-boot` files 1032554 Fallback to `ctypes.cdll` if `ctypes.windll` unavailable 034b203 Extend windows detection in testsuite to recognize MSYS target 1942fd6 Refactor to avoid need for `Unicode.hs-boot` a36991b Fix build on some platforms c375de0 Update `time` submodule to address linker issue 05f962d Compiler performance benchmark for #9675 23da971 Adjust T9675 baseline numbers based on ghc-speed d9db81f seqDmdType needs to seq the DmdEnv as well 3575109 Update more performance numbers due to stricter seqDmdType f3ae936 T9675: Allow Much wider range of values f0af3d8 Actually put in new perf number for T4801 8376027 Fix comment typos: lll -> ll, THe -> The 4b69d96 Add a configure test for pthread_setname_np cde3a77 Make Data.List.Inits fast 7e73595 Make tails a good producer (#9670) d786781 Declare official GitHub home of libraries/deepseq a477e81 Avoid printing uniques in specialization rules 0e2bd03 Update T6056 output 1c35f9f rts: fix unused parameter warning 612f3d1 Implement optimized NCG `MO_Ctz W64` op for i386 (#9340) 7369d25 Remove obsolete Data.OldTypeable (#9639) ce23745 Generalise `Control.Monad.{foldM,foldM_}` to `Foldable` (#9586) abfbb0d Remove redundant explicit `Prelude` imports d576fc3 Python 3 support, second attempt (Trac #9184) b5930f8 Refactor module imports in base 5b9fe33 Indentation and non-semantic changes only. 4d90b53 Sync up `containers` submodule to latest `master`-tip 07da36b Revert "Fix typo in section name: no leading period." 0202b7c Revert "Check for staticclosures section in Windows linker." 89a8d81 Revert "Rename _closure to _static_closure, apply naming consistently." 126b0c4 Revert "Properly generate info tables for static closures in C--." a3860fc Revert "BC-breaking changes to C-- CLOSURE syntax." d5d6fb3 Revert "Place static closures in their own section." 47c4c91 Update Haddock submodule 07a99c1 Revert "rts/PrimOps.cmm: follow '_static_closure' update" f681c32 Test #9692 in th/T9692 2cd80ba Clarify location of Note. Comment change only. e319d6d Reify data family instances correctly. 710bc8d Update primitive, vector, and dph submodules. 27f7552 Make Applicative-Monad fixes for tests. 3687089 Updated testsuite/.gitignore to cover artifacts on Windows. 2cc2065 Use objdump instead of nm to derive constants on OpenBSD 9f29e03 ghc-prim: Use population count appropriate for platform d4fd168 Update to Unicode version 7.0 a5f4fb6 Remove extra period 3157127 Improve isDigit, isSpace, etc. ef2d027 Make findIndices fuse 1e269bf Make Data.List.concatMap fuse better 6825558 Add doctest examples for Data.Functor. 5211673 Fix typo in -XConstraintKinds docs 9c464f8 Add doctest examples for Data.Bool. c819958 Add release note about Unicode 7.0 69f6361 Fixes the ARM build 972ba12 Enabled warn on tabs by default (fixes #9230) 4faeecb [skip ci] rts: Detabify RtsMessages.c aa8d23d [skip ci] rts: Detabify RaiseAsync.h bb04867 [skip ci] rts: Detabify Capability.h 99edc35 [skip ci] rts: Detabify CheckUnload.c 6aa6ca8 [skip ci] rts: Detabify Profiling.c 570b339 [skip ci] rts: Detabify Threads.c 21eaaa1 [skip ci] rts: Detabify sm/Evac.c 9167d0e [skip ci] rts: Detabify sm/Scav.c 5bb8f14 [skip ci] rts: Detabify Stats.c 2dc21b9 [skip ci] rts: Detabify Schedule.h 1d12df3 [skip ci] rts: Detabify LdvProfile.h 3d0e695 [skip ci] rts: Detabify Proftimer.c 68c45b6 [skip ci] rts: Detabify Exception.cmm a7ab7d3 [skip ci] rts: Detabify HeapStackCheck.cmm 6811e53 [skip ci] rts: Detabify Capability.c beb5c2e [skip ci] rts: Detabify RaiseAsync.c e13478f [skip ci] rts: Detabify sm/GC.c faa3339 [skip ci] rts: Detabify sm/Sanity.c bc1609a [skip ci] rts: Detabify sm/Compact.c c8173d5 [skip ci] rts: Detabify sm/Compact.h 5106e20 [skip ci] rts: Detabify RetainerProfile.c 03c3e9a [skip ci] rts: Detabify ProfHeap.c 6abb34c [skip ci] rts: Detabify Schedule.c 9bfe602 rts: Detabify Interpreter.c df5c11a base: Mark WCsubst.c as generated for Phabricator 45cbe85 Flush stdout in T9692 aa641e5 Add forgotten import to T9692 a11f71e Fix a rare parallel GC bug 427925d More updates to Backpack manual [skip ci] 5bb73d7 Check in up-to-date PDF copies of Backpack docs. [skip ci] aa47995 Implementation of hsig (module signatures), per #9252 1addef8 Fix windows build failure. 73c7ea7 fix a typo in comments: normaliseFfiType 0855b24 Pass in CXX to libffi's configure script. 7b59db2 `M-x delete-trailing-whitespace` & `M-x untabify` a3312c3 testsuite: Fix outdated output for T5979/safePkg01 0a290ca Add new `Data.Bifunctor` module (re #9682) 9e2cb00 Optimise atomicModifyIORef' implementation (#8345) 0e1f0f7 Un-wire `Integer` type (re #9714) 0013613 Deactivate T3064 `max_bytes_used`-check 49b05d6 Improve performance of isSuffixOf (#9676) 1874501 Typo in comment aa2ceba Normalise package key hash to make tests less fragile. 63918e6 Add n-ary version of `two_normalisers` to testsuite lib 3d6422b testlib: Get rid of two_normalisers 98ed815 Make iterateFB inlineable 75979f3 base: Refactor/clean-up *List modules 5f69c8e Reorder GHC.List; fix performance regressions f109085 Update Haddock submodule for collapsible section support 64d0a19 Really fix fft2 regression. #9740 208a0c2 Fixed unused variable warning on mingw32/i686 in rts/Linker.c f9ca529 hsc2hs: Update submodule 322810e Convert GHCi sources from .lhs to .hs 257cbec Fix #9236 Error on read from closed handle 5ce1266 Use snwprintf instead of swprintf in rts/Linker.c. acb3295 Avoid setting -Werror=unused-but-set-variable on Windows. 45175e1 Extra CRs are now filtered out from the source file for :list. f10b67a Updated stale ghcpkg05.stderr-mingw32. 3d27f69 Do not use a relative path for echo in tests/ghci/prog013. c211f8e Add __GLASGOW_HASKELL_TH__=YES/NO to CPP definitions 93c776a Added mingw32-specific expected stdout files for tests/driver/sigof{01,02,03} 9de5240 Comments only c6d4ae6 Fix test driver python3 compatibility issues 578bc00 Add notes on change to hGetContents semantics 995ea1c Fixed missing trailing newline bug in pretty printer 1907e81 Updated testsuite/.gitignore to exclude some test artifacts on Windows. cbb20ab Drop deprecated `OverlappingInstances` from base 919e930 Fix comment typos 8ef4cf1 Add doctest examples for Data.Char bd6c6f6 Update Haddock submodule 54addb1 Clean-up `Data.Fixed` f12be5b Add changelog entry for recent Unicode 7.0 update d3a7126 Update doctest example style in `Data.Bool` 4667fb5 Split off stat (benchmark) test failures into a separate section in the test runner summary. 322c139 remove old .NET related code e466ea7 Remove legacy support for -optdef flags d15d704 Fix build via Haddock submodule update. 6534686 Fix comment about dropWhileEndLE e5ba360 rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) a47ff8b Fixed T5435_dyn_asm on Windows. The test code was not in sync with the expected output. f688f03 Test #9262 in th/T9262, and update other tests. 2cc593d Bring unbound tyvars into scope during reifyInstances. b174288 Test #8953 in th/T8953 9fd19f9 Always use KindedTV when reifying. (#8953) 593e8b9 Annotate reified poly-kinded tycons when necessary. (#8953) c3ecf06 Annotate poly-kinded type patterns in instance reification. 99882ba Testsuite wibbles from fixing #8953 862772b Test #9084 in th/T9084. 03d61cc Fix #9084 by calling notHandled when unknown bits are enountered. 17265c0 Fix testsuite output from #9084. 752b5e2 Test #9738 in th/T9738 209baea Fix #9738, by handling {-# ANN ... #-} in DsMeta. 18a4a5d Update release notes for #9262 #8953 #9084. 96c22d9 Tweak the error message for pattern synonym methods, since they are disallowed both in class and instance declarations c001bde Put one-Shot info in the interface c271e32 Add GHC.Prim.oneShot 072259c Use oneShot in the definition of foldl etc. 063ae61 Update expected profiling output for scc001 1c0b736 Link to oneShot from the User's Guide 6dd218e Make Foldable's foldr1 and foldl1 defaults lazier ce03c4a Further relax T1969?s max_bytes range 49fde3b Add `Alternative` wrapper to Data.Monoid 4dbe433 Minor Haddock markup improvement to Data.Monoid 828d724 Refactor Haddock comments in Data.Bits c7fa0ba Fix lost Haddock annotation for `class Monad m` 1d6124d Tidy up pretty-printing of SrcLoc and SrcSpan 27ba070 Improve pretty-printing of type variables c8c18a1 Some refactoring around endPass and debug dumping 7251798 Simplify the generation of superclass constraints in tcInstDecl2 d153e40 Add the unfolding and inline-pragma for DFuns in DsBinds, not TcInstDcls bdbb595 White space only fd46acf Fix reduceTyFamApp_maybe 33dcb81 Simplify the API for tcInstTyVars, and make it more consistent with other similar functions 9c81db4 Rename setRole_maybe to downgradeRole_maybe 54f9188 Refactor skolemising, and newClsInst 2bfc653 Refactor the treatment of lexically-scoped type variables for instance declarations e11e1b8 Get the Untouchables level right in simplifyInfer a6e7654 Normalise the type of an inferred let-binding e840d85 Typechecker debug tracing only c64539c When reporting the context of given constraints, stop when you find one that binds a variable mentioned in the wanted 15131ec Only report "could not deduce s~t from ..." for givens that include equalities f054822 Don't filter out allegedly-irrelevant bindings with -dppr-debug 84d9ef0 Minor refactoring (no change in functionality) c1a85b3 Define ctEvLoc and ctEvCoercion, and use them 4723a0e Test Trac #9211 f861fc6 Test Trac #9708 6d1ac96 Improve error message for a handwritten Typeable instance dbbffb7 Test Trac #9747 abfbdd1 Add comments explaining ProbOneShot c639560 Test Trac #9739 7c79633 Fix the superclass-cycle detection code (Trac #9739) 66658ee Comments only 5479ae0 Testsuite error message changes 652a5ef Add flattening-notes f02c915 Make this test a bit simpler ce9d6f2 Compiler performance is much worse in for loopy givens 5770029 Simon's major commit to re-engineer the constraint solver 2f0d841 Updates to safePkg01 under Edward's guidance 09aac7d Test Trac #9081 fe178b2 Test Trac #9750 1408c8d Remove redundant "Minimal complete definition"-comments 64dc4d1 Re-center perf-numbers for T5631 6a1c05f A little refactoring of HsSplice and friends 77f8221 Temporarily disable T3064 (see #9771) 0a8e899 Remove redundant contexts from Foldable methods ac0915b Clean-up Haddock in `Data.Functor` 40b1ee4 Add `isSubsequenceOf` to Data.List (#9767) 32237f0 Fix typo in testsuite Makefile 83cf31e Fix a couple of bugs in the way info tables are generated for 64-bit platforms 4cd277b Fix bugs in debug printing 3bebf3c Fix a couple of inaccurate stack checks e6b3829 Disable an assertion; see comment 081ef2f Add a comment about stack checks d14312f Add doctest examples for Data.Either d0d9dc0 Clarify confusing notice from `make maintainer-clean` ad8457f Remove -ddump-simpl-phases flag c0a2354 Remove -ddump-core-pipeline flag 303776a Update User's Guide, cleanup DynFlags 0f930ba Move expansion of 'assert' from renamer to typechecker 030abf9 Remove unused tyConsOfDataCon e7523fe Make tyConsOfType return a (NameEnv TyCon) rather than [TyCon] f81f82e Comments and white space only 528cbd7 Give T3064 the right module name (just tidying up) 096b7e6 Switch off lazy flattening (fix Trac #3064) cb6ccad Minor refacoring and trace-message printing c945477 Allow the solved dictionaries to propagate from outside in ec38deb Wibbles to notes 203cf0e Refactor the code that prevents recursion among Coercible constraints c79cbac Re-enable T3064, which works now 91c15d6 Better error messages for new per-instance overlap flags and Safe Haskell. c96a613 Add in Incoherent Instances test for Safe Haskell. f4ead30 Warn for Safe Haskell when -XOverlappingInstances or -XIncoherentInstances turned on. abba381 Improve Applicative definitions dc5fa80 Make getTag use a bang pattern instead of seq b0e8e34 Update .gitignore to properly ignore emacs temp files 24e05f4 *Really*, really fix RTS crash due to bad coercion. 37d64a5 small parser/lexer cleanup b0d5b5b [Docs] Fixed several broken urls in user's guide f14ac52 Use bracket in `withCurrentDirectory` 832ef3f Have validate take into account stat test failures too. df3b1d4 base: Manually unlit .lhs into .hs modules a2e7bbf Preserve argument order to (==)/eq in nub and nubBy b608868 Typofix. From git at git.haskell.org Fri Nov 7 21:42:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 21:42:30 +0000 (UTC) Subject: [commit: ghc] ghc-validate: Miscellaneous documentation for the Finder. (c942688) Message-ID: <20141107214230.4B6D43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-validate Link : http://ghc.haskell.org/trac/ghc/changeset/c942688917e385c02b73811083f647329785f752/ghc >--------------------------------------------------------------- commit c942688917e385c02b73811083f647329785f752 Author: Edward Z. Yang Date: Tue Nov 4 02:07:01 2014 -0800 Miscellaneous documentation for the Finder. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- c942688917e385c02b73811083f647329785f752 compiler/main/Finder.lhs | 24 ++++++++++++++++++++++-- 1 file changed, 22 insertions(+), 2 deletions(-) diff --git a/compiler/main/Finder.lhs b/compiler/main/Finder.lhs index 1283855..189ef50 100644 --- a/compiler/main/Finder.lhs +++ b/compiler/main/Finder.lhs @@ -171,7 +171,12 @@ orIfNotFound this or_this = do _other -> return res2 _other -> return res - +-- | Helper function for 'findHomeModule': this function wraps an IO action +-- which would look up @mod_name@ in the file system (the home package), +-- and first consults the 'hsc_FC' cache to see if the lookup has already +-- been done. Otherwise, do the lookup (with the IO action) and save +-- the result in the finder cache and the module location cache (if it +-- was successful.) homeSearchCache :: HscEnv -> ModuleName -> IO FindResult -> IO FindResult homeSearchCache hsc_env mod_name do_this = do m <- lookupFinderCache (hsc_FC hsc_env) mod_name @@ -234,7 +239,22 @@ uncacheModule hsc_env mod = do -- ----------------------------------------------------------------------------- -- The internal workers --- | Search for a module in the home package only. +-- | Implements the search for a module name in the home package only. Calling +-- this function directly is usually *not* what you want; currently, it's used +-- as a building block for the following operations: +-- +-- 1. When you do a normal package lookup, we first check if the module +-- is available in the home module, before looking it up in the package +-- database. +-- +-- 2. When you have a package qualified import with package name "this", +-- we shortcut to the home module. +-- +-- 3. When we look up an exact 'Module', if the package key associated with +-- the module is the current home module do a look up in the home module. +-- +-- 4. Some special-case code in GHCi (ToDo: Figure out why that needs to +-- call this.) findHomeModule :: HscEnv -> ModuleName -> IO FindResult findHomeModule hsc_env mod_name = homeSearchCache hsc_env mod_name $ From git at git.haskell.org Fri Nov 7 21:43:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 21:43:19 +0000 (UTC) Subject: [commit: ghc] master: Top-level comment for keepPackageImports. (f5996d9) Message-ID: <20141107214319.236D83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f5996d9106f5b6b12e52ad93256233fc1cc459c9/ghc >--------------------------------------------------------------- commit f5996d9106f5b6b12e52ad93256233fc1cc459c9 Author: Edward Z. Yang Date: Tue Nov 4 13:05:13 2014 -0800 Top-level comment for keepPackageImports. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- f5996d9106f5b6b12e52ad93256233fc1cc459c9 ghc/InteractiveUI.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index ed4ea7b..e6d1529 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -1469,7 +1469,10 @@ setContextKeepingPackageModules keep_ctx trans_ctx = do transient_ctx = filterSubsumed new_rem_ctx trans_ctx } setGHCContextFromGHCiState - +-- | Filters a list of 'InteractiveImport', clearing out any home package +-- imports so only imports from external packages are preserved. ('IIModule' +-- counts as a home package import, because we are only able to bring a +-- full top-level into scope when the source is available.) keepPackageImports :: [InteractiveImport] -> GHCi [InteractiveImport] keepPackageImports = filterM is_pkg_import where From git at git.haskell.org Fri Nov 7 21:43:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 21:43:21 +0000 (UTC) Subject: [commit: ghc] master's head updated: Top-level comment for keepPackageImports. (f5996d9) Message-ID: <20141107214321.314B83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: b608868 Typofix. c942688 Miscellaneous documentation for the Finder. f5996d9 Top-level comment for keepPackageImports. From git at git.haskell.org Fri Nov 7 21:51:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 21:51:43 +0000 (UTC) Subject: [commit: ghc] branch 'ghc-validate' deleted Message-ID: <20141107215143.A28903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: ghc-validate From git at git.haskell.org Fri Nov 7 23:28:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 23:28:27 +0000 (UTC) Subject: [commit: packages/array] branch 'wip/rae' created Message-ID: <20141107232827.B7DBB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array New branch : wip/rae Referencing: 86225ba71603ed73a338e5f658698fc87aadcae9 From git at git.haskell.org Fri Nov 7 23:28:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 23:28:29 +0000 (UTC) Subject: [commit: packages/array] wip/rae: Test #9220 in libraries/array/tests/T9220 (1857121) Message-ID: <20141107232829.BD2313A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array On branch : wip/rae Link : http://git.haskell.org/packages/array.git/commitdiff/1857121ed065f6bd5e5f67ea31c85070a34fabae >--------------------------------------------------------------- commit 1857121ed065f6bd5e5f67ea31c85070a34fabae Author: Richard Eisenberg Date: Fri Nov 7 17:27:54 2014 -0500 Test #9220 in libraries/array/tests/T9220 >--------------------------------------------------------------- 1857121ed065f6bd5e5f67ea31c85070a34fabae tests/.gitignore | 1 + tests/T9220.script | 4 ++++ tests/T9220.stdout | 42 ++++++++++++++++++++++++++++++++++++++++++ tests/all.T | 1 + 4 files changed, 48 insertions(+) diff --git a/tests/.gitignore b/tests/.gitignore index 95e6531..5052e9c 100644 --- a/tests/.gitignore +++ b/tests/.gitignore @@ -3,6 +3,7 @@ *.hi *.comp.std* *.run.std* +*.normalised *.eventlog *.genscript *.exe diff --git a/tests/T9220.script b/tests/T9220.script new file mode 100644 index 0000000..0254e7d --- /dev/null +++ b/tests/T9220.script @@ -0,0 +1,4 @@ +:info Data.Array.Base.UArray +:info Data.Array.IO.IOUArray +:info Data.Array.ST.STUArray +:info Data.Array.Storable.StorableArray diff --git a/tests/T9220.stdout b/tests/T9220.stdout new file mode 100644 index 0000000..7fc2f54 --- /dev/null +++ b/tests/T9220.stdout @@ -0,0 +1,42 @@ +type role Data.Array.Base.UArray representational nominal +data Data.Array.Base.UArray i e + = Data.Array.Base.UArray !i + !i + {-# UNPACK #-}Int + GHC.Prim.ByteArray# + -- Defined in ?Data.Array.Base? +instance (GHC.Arr.Ix ix, Eq e, + Data.Array.Base.IArray Data.Array.Base.UArray e) => + Eq (Data.Array.Base.UArray ix e) + -- Defined in ?Data.Array.Base? +instance (GHC.Arr.Ix ix, Ord e, + Data.Array.Base.IArray Data.Array.Base.UArray e) => + Ord (Data.Array.Base.UArray ix e) + -- Defined in ?Data.Array.Base? +instance (GHC.Arr.Ix ix, Show ix, Show e, + Data.Array.Base.IArray Data.Array.Base.UArray e) => + Show (Data.Array.Base.UArray ix e) + -- Defined in ?Data.Array.Base? +type role Data.Array.IO.Internals.IOUArray representational nominal +newtype Data.Array.IO.Internals.IOUArray i e + = Data.Array.IO.Internals.IOUArray (Data.Array.Base.STUArray + GHC.Prim.RealWorld i e) + -- Defined in ?Data.Array.IO.Internals? +instance Eq (Data.Array.IO.Internals.IOUArray i e) + -- Defined in ?Data.Array.IO.Internals? +type role Data.Array.Base.STUArray nominal representational nominal +data Data.Array.Base.STUArray s i e + = Data.Array.Base.STUArray !i + !i + {-# UNPACK #-}Int + (GHC.Prim.MutableByteArray# s) + -- Defined in ?Data.Array.Base? +instance Eq (Data.Array.Base.STUArray s i e) + -- Defined in ?Data.Array.Base? +type role Data.Array.Storable.Internals.StorableArray representational nominal +data Data.Array.Storable.Internals.StorableArray i e + = Data.Array.Storable.Internals.StorableArray !i + !i + Int + !(GHC.ForeignPtr.ForeignPtr e) + -- Defined in ?Data.Array.Storable.Internals? diff --git a/tests/all.T b/tests/all.T index 73e3b66..cd3ae47 100644 --- a/tests/all.T +++ b/tests/all.T @@ -3,3 +3,4 @@ test('T2120', normal, compile_and_run, ['']) test('largeArray', normal, compile_and_run, ['']) test('array001', extra_clean(['array001.data']), compile_and_run, ['']) +test('T9220', expect_broken(9220), ghci_script, ['T9220.script']) From git at git.haskell.org Fri Nov 7 23:28:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 23:28:31 +0000 (UTC) Subject: [commit: packages/array] wip/rae: Fix #9220 by adding role annotations. (86225ba) Message-ID: <20141107232831.C4EB13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array On branch : wip/rae Link : http://git.haskell.org/packages/array.git/commitdiff/86225ba71603ed73a338e5f658698fc87aadcae9 >--------------------------------------------------------------- commit 86225ba71603ed73a338e5f658698fc87aadcae9 Author: Richard Eisenberg Date: Fri Nov 7 17:30:58 2014 -0500 Fix #9220 by adding role annotations. >--------------------------------------------------------------- 86225ba71603ed73a338e5f658698fc87aadcae9 Data/Array/Base.hs | 9 +++++++++ Data/Array/IO/Internals.hs | 10 +++++++++- Data/Array/Storable/Internals.hs | 8 +++++++- tests/all.T | 2 +- 4 files changed, 26 insertions(+), 3 deletions(-) diff --git a/Data/Array/Base.hs b/Data/Array/Base.hs index 27e69c3..eab6318 100644 --- a/Data/Array/Base.hs +++ b/Data/Array/Base.hs @@ -1,4 +1,7 @@ {-# LANGUAGE BangPatterns, CPP, RankNTypes, MagicHash, UnboxedTuples, MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, DeriveDataTypeable, UnliftedFFITypes #-} +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} +#endif {-# OPTIONS_HADDOCK hide #-} ----------------------------------------------------------------------------- @@ -402,6 +405,9 @@ instance IArray Arr.Array e where -- data UArray i e = UArray !i !i !Int ByteArray# deriving Typeable +#if __GLASGOW_HASKELL__ >= 708 +type role UArray representational nominal +#endif {-# INLINE unsafeArrayUArray #-} unsafeArrayUArray :: (MArray (STUArray s) e (ST s), Ix i) @@ -985,6 +991,9 @@ instance MArray (STArray s) e (Lazy.ST s) where -- 'STArray' provides. data STUArray s i e = STUArray !i !i !Int (MutableByteArray# s) deriving Typeable +#if __GLASGOW_HASKELL__ >= 708 +type role STUArray nominal representational nominal +#endif instance Eq (STUArray s i e) where STUArray _ _ _ arr1# == STUArray _ _ _ arr2# = diff --git a/Data/Array/IO/Internals.hs b/Data/Array/IO/Internals.hs index 6761e99..8c8655c 100644 --- a/Data/Array/IO/Internals.hs +++ b/Data/Array/IO/Internals.hs @@ -1,4 +1,9 @@ -{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses #-} +{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, + CPP #-} +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} +#endif + {-# OPTIONS_HADDOCK hide #-} ----------------------------------------------------------------------------- -- | @@ -47,6 +52,9 @@ import GHC.IOArray (IOArray(..)) -- newtype IOUArray i e = IOUArray (STUArray RealWorld i e) deriving Typeable +#if __GLASGOW_HASKELL__ >= 708 +type role IOUArray representational nominal +#endif instance Eq (IOUArray i e) where IOUArray s1 == IOUArray s2 = s1 == s2 diff --git a/Data/Array/Storable/Internals.hs b/Data/Array/Storable/Internals.hs index c844aae..502d569 100644 --- a/Data/Array/Storable/Internals.hs +++ b/Data/Array/Storable/Internals.hs @@ -1,4 +1,7 @@ -{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, CPP #-} +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} +#endif {-# OPTIONS_HADDOCK hide #-} ----------------------------------------------------------------------------- -- | @@ -28,6 +31,9 @@ import Foreign hiding (newArray) -- |The array type data StorableArray i e = StorableArray !i !i Int !(ForeignPtr e) +#if __GLASGOW_HASKELL__ >= 708 +type role StorableArray representational nominal +#endif instance Storable e => MArray StorableArray e IO where getBounds (StorableArray l u _ _) = return (l,u) diff --git a/tests/all.T b/tests/all.T index cd3ae47..c563441 100644 --- a/tests/all.T +++ b/tests/all.T @@ -3,4 +3,4 @@ test('T2120', normal, compile_and_run, ['']) test('largeArray', normal, compile_and_run, ['']) test('array001', extra_clean(['array001.data']), compile_and_run, ['']) -test('T9220', expect_broken(9220), ghci_script, ['T9220.script']) +test('T9220', normal, ghci_script, ['T9220.script']) From git at git.haskell.org Fri Nov 7 23:30:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 23:30:20 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9204 by outputting extra info on boot file mismatch. (30c0ad4) Message-ID: <20141107233020.720063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/30c0ad45f6ad0cb9e8fae711f8ffe9c0c50e4144/ghc >--------------------------------------------------------------- commit 30c0ad45f6ad0cb9e8fae711f8ffe9c0c50e4144 Author: Richard Eisenberg Date: Wed Nov 5 10:52:57 2014 -0500 Fix #9204 by outputting extra info on boot file mismatch. [skip ci] -- testsuite wibbles are in next commit >--------------------------------------------------------------- 30c0ad45f6ad0cb9e8fae711f8ffe9c0c50e4144 compiler/typecheck/TcRnDriver.lhs | 182 +++++++++++++++++++++++--------- testsuite/tests/roles/should_fail/all.T | 2 +- 2 files changed, 135 insertions(+), 49 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 30c0ad45f6ad0cb9e8fae711f8ffe9c0c50e4144 From git at git.haskell.org Fri Nov 7 23:30:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 23:30:23 +0000 (UTC) Subject: [commit: ghc] wip/rae: Testsuite wibbles due to #9204 (8481952) Message-ID: <20141107233023.03B7C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/8481952ddb8577c0c8aa17375c7ba94c6bc9f4af/ghc >--------------------------------------------------------------- commit 8481952ddb8577c0c8aa17375c7ba94c6bc9f4af Author: Richard Eisenberg Date: Fri Nov 7 16:32:39 2014 -0500 Testsuite wibbles due to #9204 >--------------------------------------------------------------- 8481952ddb8577c0c8aa17375c7ba94c6bc9f4af .../indexed-types/should_fail/ClosedFam3.stderr | 1 + testsuite/tests/rename/should_fail/rnfail055.stderr | 20 ++++++++++++++++---- testsuite/tests/roles/should_fail/Roles12.stderr | 1 + testsuite/tests/typecheck/should_fail/T3468.stderr | 1 + .../tests/typecheck/should_fail/tcfail220.stderr | 2 ++ 5 files changed, 21 insertions(+), 4 deletions(-) diff --git a/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr b/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr index 04435ba..3b9539e 100644 --- a/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr +++ b/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr @@ -25,3 +25,4 @@ ClosedFam3.hs-boot:12:1: Baz Int = Bool Boot file: type family Baz (a :: k) :: * where Baz * Int = Bool + The types have different kinds diff --git a/testsuite/tests/rename/should_fail/rnfail055.stderr b/testsuite/tests/rename/should_fail/rnfail055.stderr index c7b51a1..1c002ac 100644 --- a/testsuite/tests/rename/should_fail/rnfail055.stderr +++ b/testsuite/tests/rename/should_fail/rnfail055.stderr @@ -10,34 +10,38 @@ RnFail055.hs-boot:4:1: and its hs-boot file Main module: f1 :: Int -> Float Boot file: f1 :: Float -> Int + The two types are different RnFail055.hs-boot:6:1: Type constructor ?S1? has conflicting definitions in the module and its hs-boot file Main module: type S1 a b = (a, b) Boot file: type S1 a b c = (a, b) + The types have different kinds RnFail055.hs-boot:8:1: Type constructor ?S2? has conflicting definitions in the module and its hs-boot file Main module: type S2 a b = forall a1. (a1, b) Boot file: type S2 a b = forall b1. (a, b1) + The roles do not match. Roles default to ?representational? in boot files RnFail055.hs-boot:12:1: Type constructor ?T1? has conflicting definitions in the module and its hs-boot file Main module: data T1 a b = T1 [b] [a] Boot file: data T1 a b = T1 [a] [b] + The constructors do not match: The types for ?T1? differ RnFail055.hs-boot:14:1: Type constructor ?T2? has conflicting definitions in the module and its hs-boot file Main module: type role T2 representational nominal - data Eq b => T2 a b - = T2 a + data Eq b => T2 a b = T2 a Boot file: type role T2 nominal representational - data Eq a => T2 a b - = T2 a + data Eq a => T2 a b = T2 a + The roles do not match. Roles default to ?representational? in boot files + The datatype contexts do not match RnFail055.hs-boot:16:11: T3 is exported by the hs-boot file, but not exported by the module @@ -50,12 +54,16 @@ RnFail055.hs-boot:21:1: and its hs-boot file Main module: data T5 a = T5 {field5 :: a} Boot file: data T5 a = T5 a + The constructors do not match: + The record label lists for ?T5? differ RnFail055.hs-boot:23:1: Type constructor ?T6? has conflicting definitions in the module and its hs-boot file Main module: data T6 = T6 Int Boot file: data T6 = T6 !Int + The constructors do not match: + The strictness annotations for ?T6? differ RnFail055.hs-boot:25:1: Type constructor ?T7? has conflicting definitions in the module @@ -64,6 +72,8 @@ RnFail055.hs-boot:25:1: data T7 a where T7 :: a1 -> T7 a Boot file: data T7 a = T7 a + The roles do not match. Roles default to ?representational? in boot files + The constructors do not match: The types for ?T7? differ RnFail055.hs-boot:27:22: RnFail055.m1 is exported by the hs-boot file, but not exported by the module @@ -76,9 +86,11 @@ RnFail055.hs-boot:28:1: m2' :: a -> b Boot file: class C2 a b where m2 :: a -> b + The methods do not match: There are different numbers of methods RnFail055.hs-boot:29:1: Class ?C3? has conflicting definitions in the module and its hs-boot file Main module: class (Eq a, Ord a) => C3 a Boot file: class (Ord a, Eq a) => C3 a + The class constraints do not match diff --git a/testsuite/tests/roles/should_fail/Roles12.stderr b/testsuite/tests/roles/should_fail/Roles12.stderr index 9b0f2cf..874ddca 100644 --- a/testsuite/tests/roles/should_fail/Roles12.stderr +++ b/testsuite/tests/roles/should_fail/Roles12.stderr @@ -5,3 +5,4 @@ Roles12.hs:5:1: Main module: type role T phantom data T a Boot file: abstract T a + The roles do not match. Roles default to ?representational? in boot files diff --git a/testsuite/tests/typecheck/should_fail/T3468.stderr b/testsuite/tests/typecheck/should_fail/T3468.stderr index 26ec192..9284df2 100644 --- a/testsuite/tests/typecheck/should_fail/T3468.stderr +++ b/testsuite/tests/typecheck/should_fail/T3468.stderr @@ -6,3 +6,4 @@ T3468.hs-boot:3:1: data Tool d where F :: a -> Tool d Boot file: abstract Tool + The types have different kinds diff --git a/testsuite/tests/typecheck/should_fail/tcfail220.stderr b/testsuite/tests/typecheck/should_fail/tcfail220.stderr index aea7906..e565cc7 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail220.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail220.stderr @@ -5,9 +5,11 @@ tcfail220.hsig:4:1: and its hsig file Main module: data Bool = False | GHC.Types.True Hsig file: data Bool a b c d = False + The types have different kinds tcfail220.hsig:5:1: Type constructor ?Maybe? has conflicting definitions in the module and its hsig file Main module: data Maybe a = Nothing | GHC.Base.Just a Hsig file: data Maybe a b = Nothing + The types have different kinds From git at git.haskell.org Fri Nov 7 23:30:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Nov 2014 23:30:25 +0000 (UTC) Subject: [commit: ghc] wip/rae: Update submodule array to fix #9220. (3f89038) Message-ID: <20141107233025.905CE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/3f89038e1424fca019d8a0de00028b17ca56194e/ghc >--------------------------------------------------------------- commit 3f89038e1424fca019d8a0de00028b17ca56194e Author: Richard Eisenberg Date: Fri Nov 7 17:34:59 2014 -0500 Update submodule array to fix #9220. >--------------------------------------------------------------- 3f89038e1424fca019d8a0de00028b17ca56194e libraries/array | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/array b/libraries/array index 19b7aeb..86225ba 160000 --- a/libraries/array +++ b/libraries/array @@ -1 +1 @@ -Subproject commit 19b7aebd7dff912728029778749aaa8a9ed1cffd +Subproject commit 86225ba71603ed73a338e5f658698fc87aadcae9 From git at git.haskell.org Sat Nov 8 03:53:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 03:53:24 +0000 (UTC) Subject: [commit: ghc] wip/T8584: tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures (e54dae3) Message-ID: <20141108035324.98BEC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/e54dae3bf1c0da8431b1ef0dd8817e3966f3f74b/ghc >--------------------------------------------------------------- commit e54dae3bf1c0da8431b1ef0dd8817e3966f3f74b Author: Dr. ERDI Gergo Date: Sun Jul 27 14:10:34 2014 +0200 tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures >--------------------------------------------------------------- e54dae3bf1c0da8431b1ef0dd8817e3966f3f74b compiler/typecheck/TcBinds.lhs | 45 +++++++-- compiler/typecheck/TcClassDcl.lhs | 4 +- compiler/typecheck/TcPat.lhs | 23 ++++- compiler/typecheck/TcPatSyn.lhs | 188 ++++++++++++++++++++++++++--------- compiler/typecheck/TcPatSyn.lhs-boot | 9 +- 5 files changed, 211 insertions(+), 58 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e54dae3bf1c0da8431b1ef0dd8817e3966f3f74b From git at git.haskell.org Sat Nov 8 03:53:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 03:53:27 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Update baseline shift/reduce conflict number (09355b0) Message-ID: <20141108035327.3F4653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/09355b0ac726db77e3c8286a7a1fcc79b0765c35/ghc >--------------------------------------------------------------- commit 09355b0ac726db77e3c8286a7a1fcc79b0765c35 Author: Dr. ERDI Gergo Date: Wed Jul 2 19:18:43 2014 +0800 Update baseline shift/reduce conflict number >--------------------------------------------------------------- 09355b0ac726db77e3c8286a7a1fcc79b0765c35 compiler/parser/Parser.y.pp | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/compiler/parser/Parser.y.pp b/compiler/parser/Parser.y.pp index e33808d..e0eaf4d 100644 --- a/compiler/parser/Parser.y.pp +++ b/compiler/parser/Parser.y.pp @@ -72,6 +72,12 @@ import Control.Monad ( mplus ) {- ----------------------------------------------------------------------------- +25 June 2014 + +Conflicts: 47 shift/reduce + 1 reduce/reduce + +----------------------------------------------------------------------------- 12 October 2012 Conflicts: 43 shift/reduce From git at git.haskell.org Sat Nov 8 03:53:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 03:53:29 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add parser for pattern synonym type signatures. Syntax is of the form (b6fe946) Message-ID: <20141108035329.DB4E13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/b6fe9464fce8923d21cfb899694f18bee60632a0/ghc >--------------------------------------------------------------- commit b6fe9464fce8923d21cfb899694f18bee60632a0 Author: Dr. ERDI Gergo Date: Mon Jul 14 18:18:44 2014 +0800 Add parser for pattern synonym type signatures. Syntax is of the form pattern type Eq a => P a T b :: Num b => R a b which declares a pattern synonym called P, with argument types a, T, and b. >--------------------------------------------------------------- b6fe9464fce8923d21cfb899694f18bee60632a0 compiler/hsSyn/HsBinds.lhs | 1 + compiler/hsSyn/HsTypes.lhs | 19 +++++++++++++------ compiler/parser/Parser.y.pp | 9 +++++++-- compiler/parser/RdrHsSyn.lhs | 31 ++++++++++++++++++++++++++++++- 4 files changed, 51 insertions(+), 9 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index 23534cf..f75fa2e 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -743,6 +743,7 @@ pprPatSynSig :: (OutputableBndr a) => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> Maybe SDoc -> Maybe SDoc -> SDoc pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta = sep [ ptext (sLit "pattern") + , ptext (sLit "type") , thetaOpt prov_theta, name_and_args , colon , thetaOpt req_theta, rhs_ty diff --git a/compiler/hsSyn/HsTypes.lhs b/compiler/hsSyn/HsTypes.lhs index 9bd5845..db4d976 100644 --- a/compiler/hsSyn/HsTypes.lhs +++ b/compiler/hsSyn/HsTypes.lhs @@ -39,7 +39,7 @@ module HsTypes ( hsLTyVarName, hsLTyVarNames, hsLTyVarLocName, hsLTyVarLocNames, splitLHsInstDeclTy_maybe, splitHsClassTy_maybe, splitLHsClassTy_maybe, - splitHsFunType, + splitHsFunType, splitLHsForAllTyFlag, splitLHsForAllTy, splitHsAppTys, hsTyGetAppHead_maybe, mkHsAppTys, mkHsOpTy, -- Printing @@ -510,15 +510,22 @@ splitLHsInstDeclTy_maybe inst_ty = do (cls, tys) <- splitLHsClassTy_maybe ty return (tvs, cxt, cls, tys) +splitLHsForAllTyFlag + :: LHsType name + -> (HsExplicitFlag, LHsTyVarBndrs name, HsContext name, LHsType name) +splitLHsForAllTyFlag poly_ty + = case unLoc poly_ty of + HsParTy ty -> splitLHsForAllTyFlag ty + HsForAllTy flag tvs cxt ty -> (flag, tvs, unLoc cxt, ty) + _ -> (Implicit, emptyHsQTvs, [], poly_ty) + -- The type vars should have been computed by now, even if they were implicit + splitLHsForAllTy :: LHsType name -> (LHsTyVarBndrs name, HsContext name, LHsType name) splitLHsForAllTy poly_ty - = case unLoc poly_ty of - HsParTy ty -> splitLHsForAllTy ty - HsForAllTy _ tvs cxt ty -> (tvs, unLoc cxt, ty) - _ -> (emptyHsQTvs, [], poly_ty) - -- The type vars should have been computed by now, even if they were implicit + = let (_, tvs, cxt, ty) = splitLHsForAllTyFlag poly_ty + in (tvs, cxt, ty) splitHsClassTy_maybe :: HsType name -> Maybe (name, [LHsType name]) splitHsClassTy_maybe ty = fmap (\(L _ n, tys) -> (n, tys)) $ splitLHsClassTy_maybe (noLoc ty) diff --git a/compiler/parser/Parser.y.pp b/compiler/parser/Parser.y.pp index e0eaf4d..41ad6f0 100644 --- a/compiler/parser/Parser.y.pp +++ b/compiler/parser/Parser.y.pp @@ -856,8 +856,7 @@ role : VARID { L1 $ Just $ getVARID $1 } pattern_synonym_decl :: { LHsDecl RdrName } : 'pattern' pat '=' pat {% do { (name, args) <- splitPatSyn $2 - ; return $ LL . ValD $ mkPatSynBind name args $4 ImplicitBidirectional - }} + ; return $ LL . ValD $ mkPatSynBind name args $4 ImplicitBidirectional }} | 'pattern' pat '<-' pat {% do { (name, args) <- splitPatSyn $2 ; return $ LL . ValD $ mkPatSynBind name args $4 Unidirectional @@ -873,6 +872,11 @@ where_decls :: { Located (OrdList (LHsDecl RdrName)) } : 'where' '{' decls '}' { $3 } | 'where' vocurly decls close { $3 } +pattern_synonym_sig :: { LSig RdrName } + : 'pattern' 'type' ctype '::' ctype + {% do { (name, details, ty, prov, req) <- splitPatSynSig $3 $5 + ; return . LL $ PatSynSig name details ty prov req }} + vars0 :: { [Located RdrName] } : {- empty -} { [] } | varid vars0 { $1 : $2 } @@ -1484,6 +1488,7 @@ sigdecl :: { Located (OrdList (LHsDecl RdrName)) } { LL $ toOL [ LL $ SigD (TypeSig ($1 : reverse (unLoc $3)) $5) ] } | infix prec ops { LL $ toOL [ LL $ SigD (FixSig (FixitySig n (Fixity $2 (unLoc $1)))) | n <- unLoc $3 ] } + | pattern_synonym_sig { LL . unitOL $ LL . SigD . unLoc $ $1 } | '{-# INLINE' activation qvar '#-}' { LL $ unitOL (LL $ SigD (InlineSig $3 (mkInlinePragma (getINLINE $1) $2))) } | '{-# SPECIALISE' activation qvar '::' sigtypes1 '#-}' diff --git a/compiler/parser/RdrHsSyn.lhs b/compiler/parser/RdrHsSyn.lhs index e6969e7..3152642 100644 --- a/compiler/parser/RdrHsSyn.lhs +++ b/compiler/parser/RdrHsSyn.lhs @@ -18,7 +18,7 @@ module RdrHsSyn ( mkTyFamInst, mkFamDecl, splitCon, mkInlinePragma, - splitPatSyn, toPatSynMatchGroup, + splitPatSyn, splitPatSynSig, toPatSynMatchGroup, mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp mkTyClD, mkInstD, @@ -471,6 +471,35 @@ toPatSynMatchGroup (L _ patsyn_name) (L _ decls) = text "pattern synonym 'where' clause must bind the pattern synonym's name" <+> quotes (ppr patsyn_name) $$ ppr decl +-- Given two types like +-- Eq a => P a T b +-- and +-- Num b => R a b +-- +-- This returns +-- P as the name, +-- PrefixPatSyn [a, T, b] as the details, +-- R a b as the result type, +-- and (Eq a) and (Num b) as the provided and required thetas (respectively) +splitPatSynSig :: LHsType RdrName + -> LHsType RdrName + -> P (Located RdrName, HsPatSynDetails (LHsType RdrName), LHsType RdrName, + (HsExplicitFlag, LHsTyVarBndrs RdrName, LHsContext RdrName), + (HsExplicitFlag, LHsTyVarBndrs RdrName, LHsContext RdrName)) +splitPatSynSig lty1 lty2 = do + (name, details) <- splitCon pat_ty + details' <- case details of + PrefixCon tys -> return $ PrefixPatSyn tys + InfixCon ty1 ty2 -> return $ InfixPatSyn ty1 ty2 + RecCon{} -> parseErrorSDoc (getLoc lty1) $ + text "record syntax not supported for pattern synonym declarations:" $$ ppr lty1 + return (name, details', res_ty, (ex_flag, ex_tvs, prov'), (univ_flag, univ_tvs, req')) + where + (ex_flag, ex_tvs, prov, pat_ty) = splitLHsForAllTyFlag lty1 + (univ_flag, univ_tvs, req, res_ty) = splitLHsForAllTyFlag lty2 + prov' = L (getLoc lty1) prov + req' = L (getLoc lty2) req + mkDeprecatedGadtRecordDecl :: SrcSpan -> Located RdrName -> [ConDeclField RdrName] From git at git.haskell.org Sat Nov 8 03:53:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 03:53:32 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Show foralls (when requested) in pattern synonym types (e281acb) Message-ID: <20141108035332.753973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/e281acb6d111e96b4b05bd712dc46b27e41d269d/ghc >--------------------------------------------------------------- commit e281acb6d111e96b4b05bd712dc46b27e41d269d Author: Dr. ERDI Gergo Date: Sun Aug 3 15:26:13 2014 +0200 Show foralls (when requested) in pattern synonym types >--------------------------------------------------------------- e281acb6d111e96b4b05bd712dc46b27e41d269d compiler/hsSyn/HsBinds.lhs | 21 ++++++--------------- compiler/iface/IfaceSyn.lhs | 9 +++++---- 2 files changed, 11 insertions(+), 19 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index f75fa2e..5a45956 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -730,24 +730,18 @@ ppr_sig (SpecSig var ty inl) = pragBrackets (pprSpec (unLoc var) (ppr ty) i ppr_sig (InlineSig var inl) = pragBrackets (ppr inl <+> pprPrefixOcc (unLoc var)) ppr_sig (SpecInstSig ty) = pragBrackets (ptext (sLit "SPECIALIZE instance") <+> ppr ty) ppr_sig (MinimalSig bf) = pragBrackets (pprMinimalSig bf) -ppr_sig (PatSynSig name arg_tys ty (_, _, prov) (_, _, req)) +ppr_sig (PatSynSig name arg_tys ty prov req) = pprPatSynSig (unLoc name) False args (ppr ty) (pprCtx prov) (pprCtx req) where args = fmap ppr arg_tys - pprCtx lctx = case unLoc lctx of - [] -> Nothing - ctx -> Just (pprHsContextNoArrow ctx) + pprCtx (flag, tvs, lctx) = pprHsForAll flag tvs lctx pprPatSynSig :: (OutputableBndr a) - => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> Maybe SDoc -> Maybe SDoc -> SDoc -pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta - = sep [ ptext (sLit "pattern") - , ptext (sLit "type") - , thetaOpt prov_theta, name_and_args - , colon - , thetaOpt req_theta, rhs_ty - ] + => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> SDoc -> SDoc -> SDoc +pprPatSynSig ident is_bidir args rhs_ty prov req + = ptext (sLit "pattern type") <+> + prov <+> name_and_args <+> colon <+> req <+> rhs_ty where name_and_args = case args of PrefixPatSyn arg_tys -> @@ -755,9 +749,6 @@ pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta InfixPatSyn left_ty right_ty -> left_ty <+> pprInfixOcc ident <+> right_ty - -- TODO: support explicit foralls - thetaOpt = maybe empty (<+> darrow) - colon = if is_bidir then dcolon else dcolon -- TODO instance OutputableBndr name => Outputable (FixitySig name) where diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 7e2d6f2..d900875 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -761,11 +761,13 @@ pprIfaceDecl ss (IfaceSyn { ifName = tycon, ifTyVars = tyvars pprIfaceDecl _ (IfacePatSyn { ifName = name, ifPatWrapper = wrapper, ifPatIsInfix = is_infix, - ifPatUnivTvs = _univ_tvs, ifPatExTvs = _ex_tvs, + ifPatUnivTvs = univ_tvs, ifPatExTvs = ex_tvs, ifPatProvCtxt = prov_ctxt, ifPatReqCtxt = req_ctxt, ifPatArgs = args, ifPatTy = ty }) - = pprPatSynSig name has_wrap args' ty' (pprCtxt prov_ctxt) (pprCtxt req_ctxt) + = pprPatSynSig name has_wrap args' ty' + (pprCtxt ex_tvs prov_ctxt) + (pprCtxt univ_tvs req_ctxt) where has_wrap = isJust wrapper args' = case (is_infix, args) of @@ -776,8 +778,7 @@ pprIfaceDecl _ (IfacePatSyn { ifName = name, ifPatWrapper = wrapper, ty' = pprParendIfaceType ty - pprCtxt [] = Nothing - pprCtxt ctxt = Just $ pprIfaceContext ctxt + pprCtxt tvs ctxt = pprIfaceForAllPart tvs ctxt empty pprIfaceDecl ss (IfaceId { ifName = var, ifType = ty, ifIdDetails = details, ifIdInfo = info }) From git at git.haskell.org Sat Nov 8 03:53:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 03:53:35 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add test cases (aa85919) Message-ID: <20141108035335.77F723A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/aa859198c8955489b515db94ee69e3fda0159b93/ghc >--------------------------------------------------------------- commit aa859198c8955489b515db94ee69e3fda0159b93 Author: Dr. ERDI Gergo Date: Sun Nov 2 14:35:49 2014 +0800 Add test cases >--------------------------------------------------------------- aa859198c8955489b515db94ee69e3fda0159b93 testsuite/tests/patsyn/should_compile/T8584-1.hs | 10 ++++++++++ testsuite/tests/patsyn/should_compile/T8968-1.hs | 8 ++++++++ testsuite/tests/patsyn/should_compile/all.T | 2 ++ 3 files changed, 20 insertions(+) diff --git a/testsuite/tests/patsyn/should_compile/T8584-1.hs b/testsuite/tests/patsyn/should_compile/T8584-1.hs new file mode 100644 index 0000000..7a017c8 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8584-1.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms #-} +module ShouldCompile where + +pattern type (Eq a) => Single a :: (Show a) => [a] +-- pattern type Single a :: (Eq a, Show a) => [a] +-- pattern type Single a :: [a] +pattern Single x = [x] + +-- f :: (Show a) => [a] -> a +foobar (Single x) = x diff --git a/testsuite/tests/patsyn/should_compile/T8968-1.hs b/testsuite/tests/patsyn/should_compile/T8968-1.hs new file mode 100644 index 0000000..f4a1dc4 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8968-1.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE GADTs, KindSignatures, PatternSynonyms #-} +module ShouldCompile where + +data X :: (* -> *) -> * -> * where + Y :: f a -> X f (Maybe a) + +pattern type C a :: X Maybe (Maybe a) +pattern C x = Y (Just x) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index d851bc3..8896008 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -10,3 +10,5 @@ test('incomplete', normal, compile, ['']) test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) +test('T8968-1', normal, compile, ['']) +test('T8584-1', normal, compile, ['']) From git at git.haskell.org Sat Nov 8 04:28:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 04:28:40 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T9783' created Message-ID: <20141108042840.3C7CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T9783 Referencing: 70911f05783ae4f16248230c9cf4b5222d8e5ae2 From git at git.haskell.org Sat Nov 8 04:28:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 04:28:43 +0000 (UTC) Subject: [commit: ghc] wip/T9783: In pattern synonym matchers, support unboxed continuation results. (a4ea93c) Message-ID: <20141108042843.349853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9783 Link : http://ghc.haskell.org/trac/ghc/changeset/a4ea93cf55b0cbe893ce67b836be22b116b063a8/ghc >--------------------------------------------------------------- commit a4ea93cf55b0cbe893ce67b836be22b116b063a8 Author: Dr. ERDI Gergo Date: Sat Nov 8 12:24:55 2014 +0800 In pattern synonym matchers, support unboxed continuation results. This requires ensuring the continuations have arguments by adding a dummy Void# argument when needed. This is so that matching on a pattern synonym is lazy even when the result is unboxed, e.g. pattern P = () f P = 0# In this case, without dummy arguments, the generated matcher's type would be $mP :: forall (r :: ?). () -> r -> r -> r which is called in `f` at type `() -> Int# -> Int# -> Int#`, so it would be strict, in particular, in the failure continuation of `patError`. We work around this by making sure both continuations have arguments: $mP :: forall (r :: ?). () -> (Void# -> r) -> (Void# -> r) -> r Of course, if `P` (and thus, the success continuation) has any arguments, we are only adding the extra dummy argument to the failure continuation. >--------------------------------------------------------------- a4ea93cf55b0cbe893ce67b836be22b116b063a8 compiler/basicTypes/PatSyn.lhs | 18 ++++++++++---- compiler/deSugar/DsUtils.lhs | 4 +++- compiler/typecheck/TcPatSyn.lhs | 28 ++++++++++++---------- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_run/T9783.hs | 15 ++++++++++++ .../tests/patsyn/should_run/T9783.stdout | 2 +- testsuite/tests/patsyn/should_run/all.T | 1 + 7 files changed, 49 insertions(+), 20 deletions(-) diff --git a/compiler/basicTypes/PatSyn.lhs b/compiler/basicTypes/PatSyn.lhs index 2081b5a..1b78dac 100644 --- a/compiler/basicTypes/PatSyn.lhs +++ b/compiler/basicTypes/PatSyn.lhs @@ -130,11 +130,19 @@ data PatSyn -- See Note [Matchers and wrappers for pattern synonyms] psMatcher :: Id, - -- Matcher function, of type - -- forall r univ_tvs. req_theta - -- => res_ty - -- -> (forall ex_tvs. prov_theta -> arg_tys -> r) - -- -> r -> r + -- Matcher function. If psArgs is empty, then it has type + -- forall (r :: ?) univ_tvs. req_theta + -- => res_ty + -- -> (forall ex_tvs. prov_theta -> Void# -> r) + -- -> (Void# -> r) + -- -> r + -- + -- Otherwise: + -- forall (r :: ?) univ_tvs. req_theta + -- => res_ty + -- -> (forall ex_tvs. prov_theta -> arg_tys -> r) + -- -> (Void# -> r) + -- -> r psWrapper :: Maybe Id -- Nothing => uni-directional pattern synonym diff --git a/compiler/deSugar/DsUtils.lhs b/compiler/deSugar/DsUtils.lhs index a269374..d36e4c9 100644 --- a/compiler/deSugar/DsUtils.lhs +++ b/compiler/deSugar/DsUtils.lhs @@ -348,13 +348,15 @@ mkPatSynCase var ty alt fail = do matcher <- dsLExpr $ mkLHsWrap wrapper $ nlHsTyApp matcher [ty] let MatchResult _ mkCont = match_result cont <- mkCoreLams bndrs <$> mkCont fail - return $ mkCoreAppsDs matcher [Var var, cont, fail] + return $ mkCoreAppsDs matcher [Var var, ensure_unstrict cont, make_unstrict fail] where MkCaseAlt{ alt_pat = psyn, alt_bndrs = bndrs, alt_wrapper = wrapper, alt_result = match_result} = alt matcher = patSynMatcher psyn + ensure_unstrict = if null (patSynArgs psyn) then make_unstrict else id + make_unstrict = Lam voidArgId mkDataConCase :: Id -> Type -> [CaseAlt DataCon] -> MatchResult mkDataConCase _ _ [] = panic "mkDataConCase: no alternatives" diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 9b2b511..2372a1b 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -24,12 +24,12 @@ import Outputable import FastString import Var import Id -import IdInfo( IdDetails( VanillaId ) ) import TcBinds import BasicTypes import TcSimplify import TcType import VarSet +import MkId #if __GLASGOW_HASKELL__ < 709 import Data.Monoid #endif @@ -124,25 +124,29 @@ tcPatSynMatcher :: Located Name -> TcM (Id, LHsBinds Id) -- See Note [Matchers and wrappers for pattern synonyms] in PatSyn tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_dicts prov_theta req_theta pat_ty - = do { res_tv <- zonkQuantifiedTyVar =<< newFlexiTyVar liftedTypeKind + = do { res_tv <- do + { uniq <- newUnique + ; let tv_name = mkInternalName uniq (mkTyVarOcc "r") loc + ; return $ mkTcTyVar tv_name openTypeKind (SkolemTv False) } ; matcher_name <- newImplicitBinder name mkMatcherOcc ; let res_ty = TyVarTy res_tv + cont_args = if null args then [voidPrimId] else args cont_ty = mkSigmaTy ex_tvs prov_theta $ - mkFunTys (map varType args) res_ty + mkFunTys (map varType cont_args) res_ty + fail_ty = mkFunTy voidPrimTy res_ty - ; let matcher_tau = mkFunTys [pat_ty, cont_ty, res_ty] res_ty + ; let matcher_tau = mkFunTys [pat_ty, cont_ty, fail_ty] res_ty matcher_sigma = mkSigmaTy (res_tv:univ_tvs) req_theta matcher_tau - matcher_id = mkExportedLocalId VanillaId matcher_name matcher_sigma + matcher_id = mkVanillaGlobal matcher_name matcher_sigma ; traceTc "tcPatSynMatcher" (ppr name $$ ppr (idType matcher_id)) ; let matcher_lid = L loc matcher_id ; scrutinee <- mkId "scrut" pat_ty ; cont <- mkId "cont" cont_ty - ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ args) - ; fail <- mkId "fail" res_ty - ; let fail' = nlHsVar fail - + ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ cont_args) + ; fail <- mkId "fail" fail_ty + ; let fail' = nlHsApps fail [nlHsVar voidPrimId] ; let args = map nlVarPat [scrutinee, cont, fail] lwpat = noLoc $ WildPat pat_ty @@ -185,9 +189,7 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; return (matcher_id, matcher_bind) } where - mkId s ty = do - name <- newName . mkVarOccFS . fsLit $ s - return $ mkLocalId name ty + mkId s ty = mkSysLocalM (fsLit s) ty isBidirectional :: HsPatSynDir a -> Bool isBidirectional Unidirectional = False @@ -243,7 +245,7 @@ mkPatSynWrapperId (L _ name) args univ_tvs ex_tvs theta pat_ty wrapper_sigma = mkSigmaTy wrapper_tvs wrapper_theta wrapper_tau ; wrapper_name <- newImplicitBinder name mkDataConWrapperOcc - ; return $ mkExportedLocalId VanillaId wrapper_name wrapper_sigma } + ; return $ mkVanillaGlobal wrapper_name wrapper_sigma } mkPatSynWrapper :: Id -> HsBind Name diff --git a/testsuite/.gitignore b/testsuite/.gitignore index ce5c2c2..2423e15 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -1097,6 +1097,7 @@ mk/ghcconfig*_inplace_bin_ghc-stage2.exe.mk /tests/patsyn/should_run/ex-prov /tests/patsyn/should_run/ex-prov-run /tests/patsyn/should_run/match +/tests/patsyn/should_run/match-unboxed /tests/perf/compiler/T1969.comp.stats /tests/perf/compiler/T3064.comp.stats /tests/perf/compiler/T3294.comp.stats diff --git a/testsuite/tests/patsyn/should_run/T9783.hs b/testsuite/tests/patsyn/should_run/T9783.hs new file mode 100644 index 0000000..daef960 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/T9783.hs @@ -0,0 +1,15 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module Main where + +import GHC.Base + +pattern P1 <- 0 +pattern P2 <- 1 + +f :: Int -> Int# +f P1 = 42# +f P2 = 44# + +main = do + print $ I# (f 0) + print $ I# (f 1) diff --git a/libraries/base/tests/IO/hGetChar001.stdin b/testsuite/tests/patsyn/should_run/T9783.stdout similarity index 50% copy from libraries/base/tests/IO/hGetChar001.stdin copy to testsuite/tests/patsyn/should_run/T9783.stdout index 2510fca..c26b130 100644 --- a/libraries/base/tests/IO/hGetChar001.stdin +++ b/testsuite/tests/patsyn/should_run/T9783.stdout @@ -1,2 +1,2 @@ 42 --7 +44 diff --git a/testsuite/tests/patsyn/should_run/all.T b/testsuite/tests/patsyn/should_run/all.T index b3c6b74..9c3f16b 100644 --- a/testsuite/tests/patsyn/should_run/all.T +++ b/testsuite/tests/patsyn/should_run/all.T @@ -3,3 +3,4 @@ test('match', normal, compile_and_run, ['']) test('ex-prov-run', normal, compile_and_run, ['']) test('bidir-explicit', normal, compile_and_run, ['']) test('bidir-explicit-scope', normal, compile_and_run, ['']) +test('T9783', normal, compile_and_run, ['']) From git at git.haskell.org Sat Nov 8 04:28:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 04:28:45 +0000 (UTC) Subject: [commit: ghc] wip/T9783: Group PatSyn req/prov arguments together so that they're not all over the place (70911f0) Message-ID: <20141108042845.BD2CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9783 Link : http://ghc.haskell.org/trac/ghc/changeset/70911f05783ae4f16248230c9cf4b5222d8e5ae2/ghc >--------------------------------------------------------------- commit 70911f05783ae4f16248230c9cf4b5222d8e5ae2 Author: Dr. ERDI Gergo Date: Thu Nov 6 19:01:38 2014 +0800 Group PatSyn req/prov arguments together so that they're not all over the place >--------------------------------------------------------------- 70911f05783ae4f16248230c9cf4b5222d8e5ae2 compiler/basicTypes/PatSyn.lhs | 27 ++++++++++++++------------- compiler/iface/BuildTyCl.lhs | 23 ++++++++++------------- compiler/iface/TcIface.lhs | 3 ++- compiler/typecheck/TcPatSyn.lhs | 4 ++-- 4 files changed, 28 insertions(+), 29 deletions(-) diff --git a/compiler/basicTypes/PatSyn.lhs b/compiler/basicTypes/PatSyn.lhs index 1b78dac..af77d36 100644 --- a/compiler/basicTypes/PatSyn.lhs +++ b/compiler/basicTypes/PatSyn.lhs @@ -123,9 +123,9 @@ data PatSyn psInfix :: Bool, -- True <=> declared infix psUnivTyVars :: [TyVar], -- Universially-quantified type variables + psReqTheta :: ThetaType, -- Required dictionaries psExTyVars :: [TyVar], -- Existentially-quantified type vars psProvTheta :: ThetaType, -- Provided dictionaries - psReqTheta :: ThetaType, -- Required dictionaries psOrigResTy :: Type, -- Mentions only psUnivTyVars -- See Note [Matchers and wrappers for pattern synonyms] @@ -202,19 +202,20 @@ instance Data.Data PatSyn where \begin{code} -- | Build a new pattern synonym mkPatSyn :: Name - -> Bool -- ^ Is the pattern synonym declared infix? - -> [Type] -- ^ Original arguments - -> [TyVar] -- ^ Universially-quantified type variables - -> [TyVar] -- ^ Existentially-quantified type variables - -> ThetaType -- ^ Wanted dicts - -> ThetaType -- ^ Given dicts - -> Type -- ^ Original result type - -> Id -- ^ Name of matcher - -> Maybe Id -- ^ Name of wrapper + -> Bool -- ^ Is the pattern synonym declared infix? + -> ([TyVar], ThetaType) -- ^ Universially-quantified type variables + -- and required dicts + -> ([TyVar], ThetaType) -- ^ Existentially-quantified type variables + -- and provided dicts + -> [Type] -- ^ Original arguments + -> Type -- ^ Original result type + -> Id -- ^ Name of matcher + -> Maybe Id -- ^ Name of wrapper -> PatSyn -mkPatSyn name declared_infix orig_args - univ_tvs ex_tvs - prov_theta req_theta +mkPatSyn name declared_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) + orig_args orig_res_ty matcher wrapper = MkPatSyn {psName = name, psUnique = getUnique name, diff --git a/compiler/iface/BuildTyCl.lhs b/compiler/iface/BuildTyCl.lhs index 2a66de2..d90e63c 100644 --- a/compiler/iface/BuildTyCl.lhs +++ b/compiler/iface/BuildTyCl.lhs @@ -180,32 +180,29 @@ mkDataConStupidTheta tycon arg_tys univ_tvs ------------------------------------------------------ buildPatSyn :: Name -> Bool -> Id -> Maybe Id - -> [Type] - -> [TyVar] -> [TyVar] -- Univ and ext - -> ThetaType -> ThetaType -- Prov and req - -> Type -- Result type + -> ([TyVar], ThetaType) -- ^ Univ and req + -> ([TyVar], ThetaType) -- ^ Ex and prov + -> [Type] -- ^ Argument types + -> Type -- ^ Result type -> PatSyn buildPatSyn src_name declared_infix matcher wrapper - args univ_tvs ex_tvs prov_theta req_theta pat_ty + (univ_tvs, req_theta) (ex_tvs, prov_theta) arg_tys pat_ty = ASSERT((and [ univ_tvs == univ_tvs' , ex_tvs == ex_tvs' , pat_ty `eqType` pat_ty' , prov_theta `eqTypes` prov_theta' , req_theta `eqTypes` req_theta' - , args `eqTypes` args' + , arg_tys `eqTypes` arg_tys' ])) mkPatSyn src_name declared_infix - args - univ_tvs ex_tvs - prov_theta req_theta - pat_ty - matcher - wrapper + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty + matcher wrapper where ((_:univ_tvs'), req_theta', tau) = tcSplitSigmaTy $ idType matcher ([pat_ty', cont_sigma, _], _) = tcSplitFunTys tau (ex_tvs', prov_theta', cont_tau) = tcSplitSigmaTy cont_sigma - (args', _) = tcSplitFunTys cont_tau + (arg_tys', _) = tcSplitFunTys cont_tau \end{code} diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index 424a46c..9dd5864 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -605,7 +605,8 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name ; pat_ty <- tcIfaceType pat_ty ; arg_tys <- mapM tcIfaceType args ; return $ buildPatSyn name is_infix matcher wrapper - arg_tys univ_tvs ex_tvs prov_theta req_theta pat_ty } + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty } ; return $ AConLike . PatSynCon $ patsyn }}} where mk_doc n = ptext (sLit "Pattern synonym") <+> ppr n diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 2372a1b..cb6fe77 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -102,9 +102,9 @@ tcPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; traceTc "tcPatSynDecl }" $ ppr name ; let patSyn = mkPatSyn name is_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) (map varType args) - univ_tvs ex_tvs - prov_theta req_theta pat_ty matcher_id wrapper_id ; return (patSyn, matcher_bind) } From git at git.haskell.org Sat Nov 8 05:28:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 05:28:01 +0000 (UTC) Subject: [commit: ghc] wip/T9783: In pattern synonym matchers, support unboxed continuation results. (8fcdab8) Message-ID: <20141108052801.166F73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9783 Link : http://ghc.haskell.org/trac/ghc/changeset/8fcdab85c60a331a4269ac3a16829a7fc762e6bc/ghc >--------------------------------------------------------------- commit 8fcdab85c60a331a4269ac3a16829a7fc762e6bc Author: Dr. ERDI Gergo Date: Sat Nov 8 12:24:55 2014 +0800 In pattern synonym matchers, support unboxed continuation results. This requires ensuring the continuations have arguments by adding a dummy Void# argument when needed. This is so that matching on a pattern synonym is lazy even when the result is unboxed, e.g. pattern P = () f P = 0# In this case, without dummy arguments, the generated matcher's type would be $mP :: forall (r :: ?). () -> r -> r -> r which is called in `f` at type `() -> Int# -> Int# -> Int#`, so it would be strict, in particular, in the failure continuation of `patError`. We work around this by making sure both continuations have arguments: $mP :: forall (r :: ?). () -> (Void# -> r) -> (Void# -> r) -> r Of course, if `P` (and thus, the success continuation) has any arguments, we are only adding the extra dummy argument to the failure continuation. >--------------------------------------------------------------- 8fcdab85c60a331a4269ac3a16829a7fc762e6bc compiler/basicTypes/PatSyn.lhs | 29 ++++++++++++++++------ compiler/deSugar/DsUtils.lhs | 4 ++- compiler/typecheck/TcPatSyn.lhs | 28 +++++++++++---------- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_run/T9783.hs | 15 +++++++++++ .../tests/patsyn/should_run/T9783.stdout | 2 +- testsuite/tests/patsyn/should_run/all.T | 1 + 7 files changed, 57 insertions(+), 23 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8fcdab85c60a331a4269ac3a16829a7fc762e6bc From git at git.haskell.org Sat Nov 8 05:28:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 05:28:03 +0000 (UTC) Subject: [commit: ghc] wip/T9783: Group PatSyn req/prov arguments together so that they're not all over the place (2b37298) Message-ID: <20141108052803.A29983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9783 Link : http://ghc.haskell.org/trac/ghc/changeset/2b3729836d9236cea1546901107c845d20342688/ghc >--------------------------------------------------------------- commit 2b3729836d9236cea1546901107c845d20342688 Author: Dr. ERDI Gergo Date: Thu Nov 6 19:01:38 2014 +0800 Group PatSyn req/prov arguments together so that they're not all over the place >--------------------------------------------------------------- 2b3729836d9236cea1546901107c845d20342688 compiler/basicTypes/PatSyn.lhs | 27 ++++++++++++++------------- compiler/iface/BuildTyCl.lhs | 23 ++++++++++------------- compiler/iface/TcIface.lhs | 3 ++- compiler/typecheck/TcPatSyn.lhs | 4 ++-- 4 files changed, 28 insertions(+), 29 deletions(-) diff --git a/compiler/basicTypes/PatSyn.lhs b/compiler/basicTypes/PatSyn.lhs index 9cc7c39..89c4374 100644 --- a/compiler/basicTypes/PatSyn.lhs +++ b/compiler/basicTypes/PatSyn.lhs @@ -128,9 +128,9 @@ data PatSyn psInfix :: Bool, -- True <=> declared infix psUnivTyVars :: [TyVar], -- Universially-quantified type variables + psReqTheta :: ThetaType, -- Required dictionaries psExTyVars :: [TyVar], -- Existentially-quantified type vars psProvTheta :: ThetaType, -- Provided dictionaries - psReqTheta :: ThetaType, -- Required dictionaries psOrigResTy :: Type, -- Mentions only psUnivTyVars -- See Note [Matchers and wrappers for pattern synonyms] @@ -207,19 +207,20 @@ instance Data.Data PatSyn where \begin{code} -- | Build a new pattern synonym mkPatSyn :: Name - -> Bool -- ^ Is the pattern synonym declared infix? - -> [Type] -- ^ Original arguments - -> [TyVar] -- ^ Universially-quantified type variables - -> [TyVar] -- ^ Existentially-quantified type variables - -> ThetaType -- ^ Wanted dicts - -> ThetaType -- ^ Given dicts - -> Type -- ^ Original result type - -> Id -- ^ Name of matcher - -> Maybe Id -- ^ Name of wrapper + -> Bool -- ^ Is the pattern synonym declared infix? + -> ([TyVar], ThetaType) -- ^ Universially-quantified type variables + -- and required dicts + -> ([TyVar], ThetaType) -- ^ Existentially-quantified type variables + -- and provided dicts + -> [Type] -- ^ Original arguments + -> Type -- ^ Original result type + -> Id -- ^ Name of matcher + -> Maybe Id -- ^ Name of wrapper -> PatSyn -mkPatSyn name declared_infix orig_args - univ_tvs ex_tvs - prov_theta req_theta +mkPatSyn name declared_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) + orig_args orig_res_ty matcher wrapper = MkPatSyn {psName = name, psUnique = getUnique name, diff --git a/compiler/iface/BuildTyCl.lhs b/compiler/iface/BuildTyCl.lhs index 2a66de2..d90e63c 100644 --- a/compiler/iface/BuildTyCl.lhs +++ b/compiler/iface/BuildTyCl.lhs @@ -180,32 +180,29 @@ mkDataConStupidTheta tycon arg_tys univ_tvs ------------------------------------------------------ buildPatSyn :: Name -> Bool -> Id -> Maybe Id - -> [Type] - -> [TyVar] -> [TyVar] -- Univ and ext - -> ThetaType -> ThetaType -- Prov and req - -> Type -- Result type + -> ([TyVar], ThetaType) -- ^ Univ and req + -> ([TyVar], ThetaType) -- ^ Ex and prov + -> [Type] -- ^ Argument types + -> Type -- ^ Result type -> PatSyn buildPatSyn src_name declared_infix matcher wrapper - args univ_tvs ex_tvs prov_theta req_theta pat_ty + (univ_tvs, req_theta) (ex_tvs, prov_theta) arg_tys pat_ty = ASSERT((and [ univ_tvs == univ_tvs' , ex_tvs == ex_tvs' , pat_ty `eqType` pat_ty' , prov_theta `eqTypes` prov_theta' , req_theta `eqTypes` req_theta' - , args `eqTypes` args' + , arg_tys `eqTypes` arg_tys' ])) mkPatSyn src_name declared_infix - args - univ_tvs ex_tvs - prov_theta req_theta - pat_ty - matcher - wrapper + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty + matcher wrapper where ((_:univ_tvs'), req_theta', tau) = tcSplitSigmaTy $ idType matcher ([pat_ty', cont_sigma, _], _) = tcSplitFunTys tau (ex_tvs', prov_theta', cont_tau) = tcSplitSigmaTy cont_sigma - (args', _) = tcSplitFunTys cont_tau + (arg_tys', _) = tcSplitFunTys cont_tau \end{code} diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index 424a46c..9dd5864 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -605,7 +605,8 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name ; pat_ty <- tcIfaceType pat_ty ; arg_tys <- mapM tcIfaceType args ; return $ buildPatSyn name is_infix matcher wrapper - arg_tys univ_tvs ex_tvs prov_theta req_theta pat_ty } + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty } ; return $ AConLike . PatSynCon $ patsyn }}} where mk_doc n = ptext (sLit "Pattern synonym") <+> ppr n diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 2372a1b..cb6fe77 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -102,9 +102,9 @@ tcPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; traceTc "tcPatSynDecl }" $ ppr name ; let patSyn = mkPatSyn name is_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) (map varType args) - univ_tvs ex_tvs - prov_theta req_theta pat_ty matcher_id wrapper_id ; return (patSyn, matcher_bind) } From git at git.haskell.org Sat Nov 8 06:01:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 06:01:35 +0000 (UTC) Subject: [commit: ghc] wip/T9783: In pattern synonym matchers, support unboxed continuation results (fixes #9783). (65f32ae) Message-ID: <20141108060135.E1CC83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9783 Link : http://ghc.haskell.org/trac/ghc/changeset/65f32aed54fb9a0ff2afb953eb17c9b2603ce8f9/ghc >--------------------------------------------------------------- commit 65f32aed54fb9a0ff2afb953eb17c9b2603ce8f9 Author: Dr. ERDI Gergo Date: Sat Nov 8 12:24:55 2014 +0800 In pattern synonym matchers, support unboxed continuation results (fixes #9783). This requires ensuring the continuations have arguments by adding a dummy Void# argument when needed. This is so that matching on a pattern synonym is lazy even when the result is unboxed, e.g. pattern P = () f P = 0# In this case, without dummy arguments, the generated matcher's type would be $mP :: forall (r :: ?). () -> r -> r -> r which is called in `f` at type `() -> Int# -> Int# -> Int#`, so it would be strict, in particular, in the failure continuation of `patError`. We work around this by making sure both continuations have arguments: $mP :: forall (r :: ?). () -> (Void# -> r) -> (Void# -> r) -> r Of course, if `P` (and thus, the success continuation) has any arguments, we are only adding the extra dummy argument to the failure continuation. >--------------------------------------------------------------- 65f32aed54fb9a0ff2afb953eb17c9b2603ce8f9 compiler/basicTypes/PatSyn.lhs | 29 ++++++++++++++++------ compiler/deSugar/DsUtils.lhs | 4 ++- compiler/typecheck/TcPatSyn.lhs | 28 +++++++++++---------- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_run/T9783.hs | 15 +++++++++++ .../tests/patsyn/should_run/T9783.stdout | 2 +- testsuite/tests/patsyn/should_run/all.T | 1 + 7 files changed, 57 insertions(+), 23 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 65f32aed54fb9a0ff2afb953eb17c9b2603ce8f9 From git at git.haskell.org Sat Nov 8 06:01:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 06:01:38 +0000 (UTC) Subject: [commit: ghc] wip/T9783: Group PatSyn req/prov arguments together so that they're not all over the place (4436222) Message-ID: <20141108060138.766CB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9783 Link : http://ghc.haskell.org/trac/ghc/changeset/44362225235906c5cc76a7fd10deeb16534bac58/ghc >--------------------------------------------------------------- commit 44362225235906c5cc76a7fd10deeb16534bac58 Author: Dr. ERDI Gergo Date: Thu Nov 6 19:01:38 2014 +0800 Group PatSyn req/prov arguments together so that they're not all over the place >--------------------------------------------------------------- 44362225235906c5cc76a7fd10deeb16534bac58 compiler/basicTypes/PatSyn.lhs | 27 ++++++++++++++------------- compiler/iface/BuildTyCl.lhs | 23 ++++++++++------------- compiler/iface/TcIface.lhs | 3 ++- compiler/typecheck/TcPatSyn.lhs | 4 ++-- 4 files changed, 28 insertions(+), 29 deletions(-) diff --git a/compiler/basicTypes/PatSyn.lhs b/compiler/basicTypes/PatSyn.lhs index 9cc7c39..89c4374 100644 --- a/compiler/basicTypes/PatSyn.lhs +++ b/compiler/basicTypes/PatSyn.lhs @@ -128,9 +128,9 @@ data PatSyn psInfix :: Bool, -- True <=> declared infix psUnivTyVars :: [TyVar], -- Universially-quantified type variables + psReqTheta :: ThetaType, -- Required dictionaries psExTyVars :: [TyVar], -- Existentially-quantified type vars psProvTheta :: ThetaType, -- Provided dictionaries - psReqTheta :: ThetaType, -- Required dictionaries psOrigResTy :: Type, -- Mentions only psUnivTyVars -- See Note [Matchers and wrappers for pattern synonyms] @@ -207,19 +207,20 @@ instance Data.Data PatSyn where \begin{code} -- | Build a new pattern synonym mkPatSyn :: Name - -> Bool -- ^ Is the pattern synonym declared infix? - -> [Type] -- ^ Original arguments - -> [TyVar] -- ^ Universially-quantified type variables - -> [TyVar] -- ^ Existentially-quantified type variables - -> ThetaType -- ^ Wanted dicts - -> ThetaType -- ^ Given dicts - -> Type -- ^ Original result type - -> Id -- ^ Name of matcher - -> Maybe Id -- ^ Name of wrapper + -> Bool -- ^ Is the pattern synonym declared infix? + -> ([TyVar], ThetaType) -- ^ Universially-quantified type variables + -- and required dicts + -> ([TyVar], ThetaType) -- ^ Existentially-quantified type variables + -- and provided dicts + -> [Type] -- ^ Original arguments + -> Type -- ^ Original result type + -> Id -- ^ Name of matcher + -> Maybe Id -- ^ Name of wrapper -> PatSyn -mkPatSyn name declared_infix orig_args - univ_tvs ex_tvs - prov_theta req_theta +mkPatSyn name declared_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) + orig_args orig_res_ty matcher wrapper = MkPatSyn {psName = name, psUnique = getUnique name, diff --git a/compiler/iface/BuildTyCl.lhs b/compiler/iface/BuildTyCl.lhs index 2a66de2..d90e63c 100644 --- a/compiler/iface/BuildTyCl.lhs +++ b/compiler/iface/BuildTyCl.lhs @@ -180,32 +180,29 @@ mkDataConStupidTheta tycon arg_tys univ_tvs ------------------------------------------------------ buildPatSyn :: Name -> Bool -> Id -> Maybe Id - -> [Type] - -> [TyVar] -> [TyVar] -- Univ and ext - -> ThetaType -> ThetaType -- Prov and req - -> Type -- Result type + -> ([TyVar], ThetaType) -- ^ Univ and req + -> ([TyVar], ThetaType) -- ^ Ex and prov + -> [Type] -- ^ Argument types + -> Type -- ^ Result type -> PatSyn buildPatSyn src_name declared_infix matcher wrapper - args univ_tvs ex_tvs prov_theta req_theta pat_ty + (univ_tvs, req_theta) (ex_tvs, prov_theta) arg_tys pat_ty = ASSERT((and [ univ_tvs == univ_tvs' , ex_tvs == ex_tvs' , pat_ty `eqType` pat_ty' , prov_theta `eqTypes` prov_theta' , req_theta `eqTypes` req_theta' - , args `eqTypes` args' + , arg_tys `eqTypes` arg_tys' ])) mkPatSyn src_name declared_infix - args - univ_tvs ex_tvs - prov_theta req_theta - pat_ty - matcher - wrapper + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty + matcher wrapper where ((_:univ_tvs'), req_theta', tau) = tcSplitSigmaTy $ idType matcher ([pat_ty', cont_sigma, _], _) = tcSplitFunTys tau (ex_tvs', prov_theta', cont_tau) = tcSplitSigmaTy cont_sigma - (args', _) = tcSplitFunTys cont_tau + (arg_tys', _) = tcSplitFunTys cont_tau \end{code} diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index 4e2cfd5..65345ec 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -605,7 +605,8 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name ; pat_ty <- tcIfaceType pat_ty ; arg_tys <- mapM tcIfaceType args ; return $ buildPatSyn name is_infix matcher wrapper - arg_tys univ_tvs ex_tvs prov_theta req_theta pat_ty } + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty } ; return $ AConLike . PatSynCon $ patsyn }}} where mk_doc n = ptext (sLit "Pattern synonym") <+> ppr n diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 7dd2e33..ea2dbce 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -107,9 +107,9 @@ tcPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; traceTc "tcPatSynDecl }" $ ppr name ; let patSyn = mkPatSyn name is_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) (map varType args) - univ_tvs ex_tvs - prov_theta req_theta pat_ty matcher_id wrapper_id ; return (patSyn, matcher_bind) } From git at git.haskell.org Sat Nov 8 06:01:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 06:01:40 +0000 (UTC) Subject: [commit: ghc] wip/T9783's head updated: Group PatSyn req/prov arguments together so that they're not all over the place (4436222) Message-ID: <20141108060140.ED5B13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9783' now includes: c001bde Put one-Shot info in the interface c271e32 Add GHC.Prim.oneShot 072259c Use oneShot in the definition of foldl etc. 063ae61 Update expected profiling output for scc001 1c0b736 Link to oneShot from the User's Guide 6dd218e Make Foldable's foldr1 and foldl1 defaults lazier ce03c4a Further relax T1969?s max_bytes range 49fde3b Add `Alternative` wrapper to Data.Monoid 4dbe433 Minor Haddock markup improvement to Data.Monoid 828d724 Refactor Haddock comments in Data.Bits c7fa0ba Fix lost Haddock annotation for `class Monad m` 1d6124d Tidy up pretty-printing of SrcLoc and SrcSpan 27ba070 Improve pretty-printing of type variables c8c18a1 Some refactoring around endPass and debug dumping 7251798 Simplify the generation of superclass constraints in tcInstDecl2 d153e40 Add the unfolding and inline-pragma for DFuns in DsBinds, not TcInstDcls bdbb595 White space only fd46acf Fix reduceTyFamApp_maybe 33dcb81 Simplify the API for tcInstTyVars, and make it more consistent with other similar functions 9c81db4 Rename setRole_maybe to downgradeRole_maybe 54f9188 Refactor skolemising, and newClsInst 2bfc653 Refactor the treatment of lexically-scoped type variables for instance declarations e11e1b8 Get the Untouchables level right in simplifyInfer a6e7654 Normalise the type of an inferred let-binding e840d85 Typechecker debug tracing only c64539c When reporting the context of given constraints, stop when you find one that binds a variable mentioned in the wanted 15131ec Only report "could not deduce s~t from ..." for givens that include equalities f054822 Don't filter out allegedly-irrelevant bindings with -dppr-debug 84d9ef0 Minor refactoring (no change in functionality) c1a85b3 Define ctEvLoc and ctEvCoercion, and use them 4723a0e Test Trac #9211 f861fc6 Test Trac #9708 6d1ac96 Improve error message for a handwritten Typeable instance dbbffb7 Test Trac #9747 abfbdd1 Add comments explaining ProbOneShot c639560 Test Trac #9739 7c79633 Fix the superclass-cycle detection code (Trac #9739) 66658ee Comments only 5479ae0 Testsuite error message changes 652a5ef Add flattening-notes f02c915 Make this test a bit simpler ce9d6f2 Compiler performance is much worse in for loopy givens 5770029 Simon's major commit to re-engineer the constraint solver 2f0d841 Updates to safePkg01 under Edward's guidance 09aac7d Test Trac #9081 fe178b2 Test Trac #9750 1408c8d Remove redundant "Minimal complete definition"-comments 64dc4d1 Re-center perf-numbers for T5631 6a1c05f A little refactoring of HsSplice and friends 77f8221 Temporarily disable T3064 (see #9771) 0a8e899 Remove redundant contexts from Foldable methods ac0915b Clean-up Haddock in `Data.Functor` 40b1ee4 Add `isSubsequenceOf` to Data.List (#9767) 32237f0 Fix typo in testsuite Makefile 83cf31e Fix a couple of bugs in the way info tables are generated for 64-bit platforms 4cd277b Fix bugs in debug printing 3bebf3c Fix a couple of inaccurate stack checks e6b3829 Disable an assertion; see comment 081ef2f Add a comment about stack checks d14312f Add doctest examples for Data.Either d0d9dc0 Clarify confusing notice from `make maintainer-clean` ad8457f Remove -ddump-simpl-phases flag c0a2354 Remove -ddump-core-pipeline flag 303776a Update User's Guide, cleanup DynFlags 0f930ba Move expansion of 'assert' from renamer to typechecker 030abf9 Remove unused tyConsOfDataCon e7523fe Make tyConsOfType return a (NameEnv TyCon) rather than [TyCon] f81f82e Comments and white space only 528cbd7 Give T3064 the right module name (just tidying up) 096b7e6 Switch off lazy flattening (fix Trac #3064) cb6ccad Minor refacoring and trace-message printing c945477 Allow the solved dictionaries to propagate from outside in ec38deb Wibbles to notes 203cf0e Refactor the code that prevents recursion among Coercible constraints c79cbac Re-enable T3064, which works now 91c15d6 Better error messages for new per-instance overlap flags and Safe Haskell. c96a613 Add in Incoherent Instances test for Safe Haskell. f4ead30 Warn for Safe Haskell when -XOverlappingInstances or -XIncoherentInstances turned on. abba381 Improve Applicative definitions dc5fa80 Make getTag use a bang pattern instead of seq b0e8e34 Update .gitignore to properly ignore emacs temp files 24e05f4 *Really*, really fix RTS crash due to bad coercion. 37d64a5 small parser/lexer cleanup b0d5b5b [Docs] Fixed several broken urls in user's guide f14ac52 Use bracket in `withCurrentDirectory` 832ef3f Have validate take into account stat test failures too. df3b1d4 base: Manually unlit .lhs into .hs modules a2e7bbf Preserve argument order to (==)/eq in nub and nubBy b608868 Typofix. c942688 Miscellaneous documentation for the Finder. f5996d9 Top-level comment for keepPackageImports. 65f32ae In pattern synonym matchers, support unboxed continuation results (fixes #9783). 4436222 Group PatSyn req/prov arguments together so that they're not all over the place From git at git.haskell.org Sat Nov 8 08:21:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:21:43 +0000 (UTC) Subject: [commit: ghc] master: In pattern synonym matchers, support unboxed continuation results (fixes #9783). (474e535) Message-ID: <20141108082143.7E8F53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/474e535b6b121809a8d75df5a4c37dc574d3d302/ghc >--------------------------------------------------------------- commit 474e535b6b121809a8d75df5a4c37dc574d3d302 Author: Dr. ERDI Gergo Date: Sat Nov 8 12:24:55 2014 +0800 In pattern synonym matchers, support unboxed continuation results (fixes #9783). This requires ensuring the continuations have arguments by adding a dummy Void# argument when needed. This is so that matching on a pattern synonym is lazy even when the result is unboxed, e.g. pattern P = () f P = 0# In this case, without dummy arguments, the generated matcher's type would be $mP :: forall (r :: ?). () -> r -> r -> r which is called in `f` at type `() -> Int# -> Int# -> Int#`, so it would be strict, in particular, in the failure continuation of `patError`. We work around this by making sure both continuations have arguments: $mP :: forall (r :: ?). () -> (Void# -> r) -> (Void# -> r) -> r Of course, if `P` (and thus, the success continuation) has any arguments, we are only adding the extra dummy argument to the failure continuation. >--------------------------------------------------------------- 474e535b6b121809a8d75df5a4c37dc574d3d302 compiler/basicTypes/PatSyn.lhs | 29 ++++++++++++++++------ compiler/deSugar/DsUtils.lhs | 7 +++++- compiler/typecheck/TcPatSyn.lhs | 28 +++++++++++---------- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_run/T9783.hs | 15 +++++++++++ .../tests/patsyn/should_run/T9783.stdout | 2 +- testsuite/tests/patsyn/should_run/all.T | 1 + 7 files changed, 60 insertions(+), 23 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 474e535b6b121809a8d75df5a4c37dc574d3d302 From git at git.haskell.org Sat Nov 8 08:21:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:21:46 +0000 (UTC) Subject: [commit: ghc] master: Group PatSyn req/prov arguments together so that they're not all over the place (65dc594) Message-ID: <20141108082146.0E5423A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/65dc594b156c9cc5c2e9bc640f0762beaf3ca6ca/ghc >--------------------------------------------------------------- commit 65dc594b156c9cc5c2e9bc640f0762beaf3ca6ca Author: Dr. ERDI Gergo Date: Thu Nov 6 19:01:38 2014 +0800 Group PatSyn req/prov arguments together so that they're not all over the place >--------------------------------------------------------------- 65dc594b156c9cc5c2e9bc640f0762beaf3ca6ca compiler/basicTypes/PatSyn.lhs | 27 ++++++++++++++------------- compiler/iface/BuildTyCl.lhs | 23 ++++++++++------------- compiler/iface/TcIface.lhs | 3 ++- compiler/typecheck/TcPatSyn.lhs | 4 ++-- 4 files changed, 28 insertions(+), 29 deletions(-) diff --git a/compiler/basicTypes/PatSyn.lhs b/compiler/basicTypes/PatSyn.lhs index 9cc7c39..89c4374 100644 --- a/compiler/basicTypes/PatSyn.lhs +++ b/compiler/basicTypes/PatSyn.lhs @@ -128,9 +128,9 @@ data PatSyn psInfix :: Bool, -- True <=> declared infix psUnivTyVars :: [TyVar], -- Universially-quantified type variables + psReqTheta :: ThetaType, -- Required dictionaries psExTyVars :: [TyVar], -- Existentially-quantified type vars psProvTheta :: ThetaType, -- Provided dictionaries - psReqTheta :: ThetaType, -- Required dictionaries psOrigResTy :: Type, -- Mentions only psUnivTyVars -- See Note [Matchers and wrappers for pattern synonyms] @@ -207,19 +207,20 @@ instance Data.Data PatSyn where \begin{code} -- | Build a new pattern synonym mkPatSyn :: Name - -> Bool -- ^ Is the pattern synonym declared infix? - -> [Type] -- ^ Original arguments - -> [TyVar] -- ^ Universially-quantified type variables - -> [TyVar] -- ^ Existentially-quantified type variables - -> ThetaType -- ^ Wanted dicts - -> ThetaType -- ^ Given dicts - -> Type -- ^ Original result type - -> Id -- ^ Name of matcher - -> Maybe Id -- ^ Name of wrapper + -> Bool -- ^ Is the pattern synonym declared infix? + -> ([TyVar], ThetaType) -- ^ Universially-quantified type variables + -- and required dicts + -> ([TyVar], ThetaType) -- ^ Existentially-quantified type variables + -- and provided dicts + -> [Type] -- ^ Original arguments + -> Type -- ^ Original result type + -> Id -- ^ Name of matcher + -> Maybe Id -- ^ Name of wrapper -> PatSyn -mkPatSyn name declared_infix orig_args - univ_tvs ex_tvs - prov_theta req_theta +mkPatSyn name declared_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) + orig_args orig_res_ty matcher wrapper = MkPatSyn {psName = name, psUnique = getUnique name, diff --git a/compiler/iface/BuildTyCl.lhs b/compiler/iface/BuildTyCl.lhs index 2a66de2..d90e63c 100644 --- a/compiler/iface/BuildTyCl.lhs +++ b/compiler/iface/BuildTyCl.lhs @@ -180,32 +180,29 @@ mkDataConStupidTheta tycon arg_tys univ_tvs ------------------------------------------------------ buildPatSyn :: Name -> Bool -> Id -> Maybe Id - -> [Type] - -> [TyVar] -> [TyVar] -- Univ and ext - -> ThetaType -> ThetaType -- Prov and req - -> Type -- Result type + -> ([TyVar], ThetaType) -- ^ Univ and req + -> ([TyVar], ThetaType) -- ^ Ex and prov + -> [Type] -- ^ Argument types + -> Type -- ^ Result type -> PatSyn buildPatSyn src_name declared_infix matcher wrapper - args univ_tvs ex_tvs prov_theta req_theta pat_ty + (univ_tvs, req_theta) (ex_tvs, prov_theta) arg_tys pat_ty = ASSERT((and [ univ_tvs == univ_tvs' , ex_tvs == ex_tvs' , pat_ty `eqType` pat_ty' , prov_theta `eqTypes` prov_theta' , req_theta `eqTypes` req_theta' - , args `eqTypes` args' + , arg_tys `eqTypes` arg_tys' ])) mkPatSyn src_name declared_infix - args - univ_tvs ex_tvs - prov_theta req_theta - pat_ty - matcher - wrapper + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty + matcher wrapper where ((_:univ_tvs'), req_theta', tau) = tcSplitSigmaTy $ idType matcher ([pat_ty', cont_sigma, _], _) = tcSplitFunTys tau (ex_tvs', prov_theta', cont_tau) = tcSplitSigmaTy cont_sigma - (args', _) = tcSplitFunTys cont_tau + (arg_tys', _) = tcSplitFunTys cont_tau \end{code} diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index 4e2cfd5..65345ec 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -605,7 +605,8 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name ; pat_ty <- tcIfaceType pat_ty ; arg_tys <- mapM tcIfaceType args ; return $ buildPatSyn name is_infix matcher wrapper - arg_tys univ_tvs ex_tvs prov_theta req_theta pat_ty } + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty } ; return $ AConLike . PatSynCon $ patsyn }}} where mk_doc n = ptext (sLit "Pattern synonym") <+> ppr n diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 7dd2e33..ea2dbce 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -107,9 +107,9 @@ tcPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; traceTc "tcPatSynDecl }" $ ppr name ; let patSyn = mkPatSyn name is_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) (map varType args) - univ_tvs ex_tvs - prov_theta req_theta pat_ty matcher_id wrapper_id ; return (patSyn, matcher_bind) } From git at git.haskell.org Sat Nov 8 08:22:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:22:55 +0000 (UTC) Subject: [commit: ghc] wip/T9281: DRAFT: Implement new integer-gmp2 from scratch (re #9281) (7eddaa4) Message-ID: <20141108082255.9D1DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/7eddaa41355a5998b8fe49435259d744996da902/ghc >--------------------------------------------------------------- commit 7eddaa41355a5998b8fe49435259d744996da902 Author: Herbert Valerio Riedel Date: Sun Oct 19 20:37:40 2014 +0200 DRAFT: Implement new integer-gmp2 from scratch (re #9281) Summary: (preliminary commit message) This is done as a separate integer-gmp2 backend library because it turned out to become a complete rewrite from scratch. This has been tested only on Linux/x86_64 so far. The code has been written while taking into account Linux/i386 and "64-bit" Windows, but will probably need some tweaking to get right. Also, we don't do any autoconf stuff anymore, and rely on Cabal's "extra-libraries: gmp" to do the right thing (which probably won't work everywhere) Moreover, this is currently a big huge patch, which could easily be split into 2 or 3 commits. Test Plan: nofib & testsuite Reviewers: #ghc, austin Subscribers: ekmett, simonpj, ezyang, rwbarton, phaskell, simonmar, relrod, carter Differential Revision: https://phabricator.haskell.org/D82 GHC Trac Issues: #9281 >--------------------------------------------------------------- 7eddaa41355a5998b8fe49435259d744996da902 compiler/coreSyn/CorePrep.lhs | 3 +- compiler/ghc.mk | 8 +- compiler/prelude/PrelNames.lhs | 2 + ghc.mk | 10 +- libraries/base/GHC/Real.hs | 6 + libraries/base/base.cabal | 19 +- libraries/integer-gmp2/.gitignore | 13 + libraries/integer-gmp2/LICENSE | 30 + libraries/{base => integer-gmp2}/Setup.hs | 0 libraries/{integer-gmp => integer-gmp2}/aclocal.m4 | 0 libraries/integer-gmp2/cbits/wrappers.c | 281 ++++ .../integer-gmp2/config.guess | 0 config.sub => libraries/integer-gmp2/config.sub | 0 .../{integer-gmp => integer-gmp2}/configure.ac | 4 +- .../{integer-gmp => integer-gmp2}/gmp/config.mk.in | 0 libraries/{integer-gmp => integer-gmp2}/gmp/ghc.mk | 76 +- libraries/integer-gmp2/gmp/gmpsrc.patch | 37 + {libffi => libraries/integer-gmp2/gmp}/ln | 0 libraries/integer-gmp2/include/HsIntegerGmp2.h.in | 6 + .../integer-gmp2.buildinfo.in} | 0 libraries/integer-gmp2/integer-gmp2.cabal | 62 + .../src/GHC/Integer.hs} | 49 +- .../integer-gmp2/src/GHC/Integer/GMP2/Internals.hs | 126 ++ .../integer-gmp2/src/GHC/Integer/Logarithms.hs | 73 + .../src/GHC/Integer/Logarithms/Internals.hs | 118 ++ libraries/integer-gmp2/src/GHC/Integer/Type.hs | 1663 ++++++++++++++++++++ mk/config.mk.in | 2 +- rules/foreachLibrary.mk | 2 + testsuite/driver/testlib.py | 2 +- testsuite/tests/ghci/scripts/ghci025.stdout | 6 +- testsuite/tests/perf/should_run/all.T | 3 +- testsuite/tests/perf/space_leaks/all.T | 4 +- testsuite/tests/rename/should_compile/T3103/test.T | 2 +- testsuite/tests/rts/Makefile | 4 +- testsuite/tests/safeHaskell/check/pkg01/all.T | 8 +- testsuite/tests/simplCore/should_run/T5603.hs | 7 +- testsuite/tests/typecheck/should_fail/T5095.stderr | 4 +- .../tests/typecheck/should_fail/tcfail072.stderr | 2 +- 38 files changed, 2548 insertions(+), 84 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7eddaa41355a5998b8fe49435259d744996da902 From git at git.haskell.org Sat Nov 8 08:23:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:23:00 +0000 (UTC) Subject: [commit: ghc] wip/T9281's head updated: DRAFT: Implement new integer-gmp2 from scratch (re #9281) (7eddaa4) Message-ID: <20141108082300.B94BC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9281' now includes: 2d42564 workaround Solaris 11 GNU C CPP issue by using GNU C 3.4 as CPP 2aabda1 Fix quasi-quoter documentation (#9448) daef885 Fix broken link in Data.Data to SYB home page (Trac #9455) b287bc9 Update list of flags implied by -XGADTs in User's Guide section on GADTs a72614c Make T8832 operative on 32-bit systems (#8832) 3a67aba ghci/scripts/ghci016: Add implementation for negate 5b11b04 concurrent/should_run/throwto002: DoRec -> RecursiveDo 5d5655e Fix three problems with occurrence analysis on case alternatives. 88b1f99 testsuite/T9379: Use GHC.Conc instead of Control.Concurrent.STM 6f6ee6e Make Prelude.abs handle -0.0 correctly (#7858) d9a2057 Make Prelude.signum handle -0.0 correctly (#7858) bbd0311 Bug #9439: Ensure that stage 0 compiler isn't affected 9a708d3 UNREG: fix PackageKey emission into .hc files 0138110 Implement -rdynamic in Linux and Windows/MinGW32. d2f0100 Have the RTS linker search symbols in the originating windows binary. 955dfcb This note's name has been fixed 4333a91 includes/stg/Prim.h: add matching 'hs_atomic_*' prototypes e3c3586 Use absolute links to Cabal docs from the GHC users guide (#9154) 89f5f31 Explain how to clone GitHub forks. Ticket #8379. 2fc2294 Mention that `Data.Ix` uses row-major indexing 527bcc4 build: require GHC 7.6 for bootstrapping defc42e Add test case for #9046 806d823 Correct checkStrictBinds for generalised type 7012ed8 Check if file is present instead of directory 51a0b60 travis: Use hvr?s multi-ghc-PPA f9f89b7 rts/base: Fix #9423 f328890 validate: add simple CPU count autodetection 15faa0e Fix prepositions in the documentation of -rdynamic. 7bf49f8 Make sure that a prototype is included for 'setIOManagerControlFd' 27c99a1 Comments fix to Trac #9140 11f05c5 coreSyn: detabify/dewhitespace TrieMap 236e2ea stranal: detabify/dewhitespace WorkWrap 96c3599 simplCore: detabify/dewhitespace SAT fb9bc40 utils: detabify/dewhitespace BufWrite a9f5c81 utils: detabify/dewhitespace GraphBase e3a5bad utils: detabify/dewhitespace GraphPpr 6f01f0b simplCore: detabify/dewhitespace SetLevels 28a8cd1 simplCore: detabify/dewhitespace LiberateCase ef9dd9f prelude: detabify/dewhitespace TysPrim fbdc21b coreSyn: detabify/dewhitespace CoreTidy ffc1afe coreSyn: detabify/dewhitespace CoreSubst 8396e44 deSugar: detabify/dewhitespace DsCCall 07d01c9 stranal: detabify/dewhitespace DmdAnal 8a8ead0 hsSyn: detabify/dewhitespace HsLit 99f6224 basicTypes: detabify/dewhitespace Var 1ad35f4 basicTypes: detabify/dewhitespace NameSet 1b55153 basicTypes: detabify/dewhitespace NameEnv 37743a1 basicTypes: detabify/dewhitespace IdInfo a2d2546 genprimopcode: Don't output tabs 067bb0d Update a comment in base cbits 92bb7be Add a missing newline to a GHCi linker debugBelch ff4f844 rts: detabify/dewhitespace Ticky.c b4c7bcd rts: detabify/dewhitespace Weak.c dea58de rts: detabify/dewhitespace Updates.h 514a631 rts: detabify/dewhitespace Timer.c 43c68d6 rts: detabify/dewhitespace Trace.c 221c231 rts: detabify/dewhitespace STM.c c49f2e7 rts: reflow some comments in STM.c 4cbf966 rts: detabify/dewhitespace Task.c 684be04 rts: detabify/dewhitespace sm/Storage.h f20708c rts: detabify/dewhitespace sm/BlockAlloc.c 2f3649e rts: detabify/dewhitespace sm/MarkWeak.c 08093a9 rts: detabify/dewhitespace sm/GCAux.c 7e60787 rts: detabify/dewhitespace sm/GCUtils.h 7318aab rts: detabify/dewhitespace sm/GCUtils.c b7b427f rts: detabify/dewhitespace sm/MBlock.c 870cca8 rts: detabify/dewhitespace Apply.cmm 93ec914 rts: detabify/dewhitespace Hpc.c 219785b rts: detabify/dewhitespace Printer.h ee0e47d rts: detabify/dewhitespace Task.h c71ab57 rts: detabify/dewhitespace AutoApply.h ef02edc rts: detabify/dewhitespace StgStdThunks.cmm 1a6a610 rts: detabify/dewhitespace StgStartup.cmm 2f34ab2 rts: detabify/dewhitespace StgPrimFloat.c 584d459 rts: detabify/dewhitespace StgPrimFloat.h 7d48356 rts: detabify/dewhitespace Sparks.c 8f3611e rts: detabify/dewhitespace RtsMain.c b9ee7e8 rts: detabify/dewhitespace RtsAPI.c 00878c5 rts: detabify/dewhitespace RtsStartup.c 646f214 rts: detabify/dewhitespace RtsUtils.c f2864e9 rts: detabify/dewhitespace Disassembler.c 7200edf rts: detabify/dewhitespace LdvProfile.c 15df6d9 Comment why the include is necessary c867cbc [ci skip] includes: detabify/dewhitespace Stg.h 772ffbe [ci skip] includes: detabify/dewhitespace RtsAPI.h 6f3dd98 [ci skip] includes: detabify/dewhitespace Rts.h a784afc [ci skip] includes: detabify/dewhitespace HsFFI.h e183e35 [ci skip] includes: detabify/dewhitespace Cmm.h e232967 [ci skip] includes: detabify/dewhitespace stg/Regs.h efcf0ab [ci skip] includes: detabify/dewhitespace stg/SMP.h e7dd073 [ci skip] includes: detabify/dewhitespace stg/Types.h c607500 [ci skip] includes: detabify/dewhitespace rts/Ticky.h a739416 [ci skip] includes: detabify/dewhitespace rts/Threads.h 2957736 [ci skip] includes: detabify/dewhitespace rts/Stable.h 7d26398 [ci skip] includes: detabify/dewhitespace rts/OSThreads.h bb70e33 [ci skip] includes: detabify/dewhitespace rts/Hpc.h 1c43f62 [ci skip] includes: detabify/dewhitespace rts/prof/CCS.h f20c663 [ci skip] includes: detabify/dewhitespace rts/prof/LDV.h aa045e5 [ci skip] includes: detabify/dewhitespace rts/storage/MBlock.h e57a29a [ci skip] includes: detabify/dewhitespace rts/storage/TSO.h f6cdf04 [ci skip] includes: detabify/dewhitespace rts/storage/Closures.h b4ec067 [ci skip] includes: detabify/dewhitespace rts/storage/GC.h e9e3cf5 [ci skip] includes: detabify/dewhitespace rts/storage/Block.h 98b1b13 [ci skip] includes: detabify/dewhitespace rts/storage/InfoTables.h 840a1cb includes: detabify/dewhitespace rts/storage/ClosureMacros.h 955db0d T8832: fix no newline at end of file warning 030549a Fix #9465. f9e9e71 gitignore: Ignore tests/rts/rdynamic bf1b117 submodule update hpc/stm with gitignore. 22520cd Do not zero out version number when processing wired-in packages. 4748f59 Revert "rts/base: Fix #9423" 2719526 Normalise GHC version number to make tests less fragile. d333c03 Enable GHC API tests by default. ff9f4ad testsuite: T7815 requires SMP support from ghc fcdd58d testsuite: disable gcc's warnings about casts of incompatible prototypes in UNREG eb64be7 testsuite: disable memcpy asm comparison tests on UNREG 2fcb36e testsuite: mark testwsdeque mark as faulty on NOSMP builds 104a66a rts/Linker.c: declare 'deRefStablePtr' as an exported 'rts' symbol cfd08a9 Add MO_AddIntC, MO_SubIntC MachOps and implement in X86 backend e1d77a1 testsuite: added 'bytes allocated' for T9339 wordsize(32) 78ba9f0 Declare official GitHub home of libraries/{directory,process} 5295cd2 testsuite: add 16-byte case for T9329 9f8754e Use DumpStyle rather than UserStyle for pprTrace output c0fe1d9 Introduce the Call data types af4bc31 Do not duplicate call information in SpecConstr (Trac #8852) 5c4df28 More refactoring in SpecConstr 8ff4671 Make Core Lint check for un-saturated type applications ee4501b Check for un-saturated type family applications 06600e7 Two buglets in record wild-cards (Trac #9436 and #9437) 67a6ade Improve documentation of record wildcards 43f1b2e UNREG: fix emission of large Integer literals in C codegen a93ab43 driver: pass '-fPIC' option to assembler as well 78863ed Revert "disable shared libs on sparc (linux/solaris) (fixes #8857)" e9cd1d5 Less voluminous output when printing continuations 6e0f6ed Refactor unfoldings 3af1adf Kill unused setUnfoldingTemplate 8f09937 Make maybeUnfoldingTemplate respond to DFunUnfoldings 9cf5906 Make worker/wrapper work on INLINEABLE things 4c03791 Specialise Eq, Ord, Read, Show at Int, Char, String 3436333 Move the Enum Word instance into GHC.Enum 949ad67 Don't float out (classop dict e1 e2) 2ef997b Slightly improve fusion rules for 'take' 99178c1 Specialise monad functions, and make them INLINEABLE baa3c9a Wibbles to "...plus N others" error message about instances in scope a3e207f More SPEC rules fire dce7095 Compiler performance increases -- yay! b9e49d3 Add -fspecialise-aggressively fa582cc Fix an egregious bug in the NonRec case of bindFreeVars 6d48ce2 Make tidyProgram discard speculative specialisation rules 86a2ebf Comments only 1122857 Run float-inwards immediately before the strictness analyser. 082e41b Testsuite wibbles bb87726 Performance changes a0b2897 Simple refactor of the case-of-case transform 6c6b001 Remove dead lookup_dfun_id (merge-o) 39ccdf9 White space only a1a400e Testsuite wibbles 1145568 testsuite: disable T367_letnoescape on 'optllvm' 75d998b testsuite: disable 'rdynamic' for 'ghci' way 94926b1 Add an interesting type-family/GADT example of deletion for red-black trees 87c1568 Comments only b7bdf13 Temporary fix to the crash aa49892 [ci skip] ghc-prim: Update .gitignore 8270ff3 [ci skip] Update .gitignore 9072f2f PprC: cleanup: don't emit 'FB_' / 'FE_' in via-C 49370ce Improve trimming of auto-rules 4a87142 Fix syntax in perf/compiler/all.T 7eae141 White space only 2da63c6 Better compiler performance (30% less allocation) for T783! dfc9d30 Define mapUnionVarSet, and use it 8df3159 Rename red-black test in indexed-types to red-black-delete db5868c In GHC.Real, specialise 'even' and 'odd' to Int and Integer 9fae691 Improve "specImport discarding" message b2affa0 Testsuite wibbles 69e9f6e Simplify conversion in binary serialisation of ghc-pkg db 557c8b8 Drop support for single-file style package databases ce29a26 Improve the ghc-pkg warnings for missing and out of date package cache files 8d7a1dc Introduce new file format for the package database binary cache 27d6c08 Use ghc-local types for packages, rather than Cabal types 0af7d0c Move Cabal Binary instances from bin-package-db to ghc-pkg itself 9597a25 Drop ghc library dep on Cabal 227205e Make binary a boot package 6930a88 Fix warnings arising from the package db refactoring 29f84d3 Fix long lines and trailing whitespace 8955b5e Remove a TODO that is now done a4cb9a6 Add a ghc -show-packages mode to display ghc's view of the package env 1bc2a55 Make mkFastStringByteString pure and fix up uses c72efd7 Switch the package id types to use FastString (rather than String) b00deb7 Fix string conversions in ghc-pkg to be correct w.r.t. Unicode 42f99e9 Address a number of Edward's code review comments 9d6fbcc Fix validation error in Linker arising from package rep changes 01461ce Update Cabal and haddock submodules to follow the Canal-dep removal changes da72898 Change testsuite to not use old-style file package databases 616dd87 Fix a few minor issues spotted in code review 6d8c70c Add release notes about ghc-pkg change, and Cabal dep removal 020bd49 Fix failing test on BINDIST=YES cb2ac47 Suppress binary warnings for bootstrapping as well as stage1. f0db185 Include pattern synonyms as AConLikes in the type environment, even for simplified/boot ModDetails (fixes #9417) 4e0e774 Fix a bug in CSE, for INLINE/INLNEABLE things ab4c27e Comments, white space, and rename "InlineRule" to "stable unfolding" 3521c50 When finding loop breakers, distinguish INLINE from INLINEABLE 7af33e9 Better specImport discarding message (again) e5f766c Give the worker for an INLINABLE function a suitably-phased Activation 3935062 Finally! Test Trac #6056 5da580b Performance improvement of the compiler itself fa9dd06 Do not say we cannot when we clearly can 9491fea Typos in comments eac8728 Fix to bin-package-db for ming32-only code 985e367 testsuite: normalise integer library name for T8958 0dc2426 Some typos 54db6fa Revert "Comment why the include is necessary" b760cc5 Revert "Make sure that a prototype is included for 'setIOManagerControlFd'" 393b820 Re-export Word from Prelude (re #9531) a8a969a Add `FiniteBits(count{Leading,Trailing}Zeros)` 737f368 `M-x delete-trailing-whitespace` & `M-x untabify`... 3241ac5 Remove incorrect property in docstring (re #9532) a4ec0c9 Make ghc-api cleaning less aggressive. 01a27c9 testsuite: update T6056 rule firing order e81e028 includes/Stg.h: remove unused 'wcStore' inline 9e93940 StringBuffer should not contain initial byte-order mark (BOM) 0f31c2e Cleanup and better documentation of sync-all script 64c9898 Make Lexer.x more like the 2010 report 3be704a genprimopcode: GHC.Prim is Unsafe (#9449) 2f343b0 Refactor stack squeezing logic 918719b Set llc and opt commands on all platforms 9711f78 Fix a couple test failures encountered when building on Windows 4d4d077 systools: fix gcc version detecton on non-english locale 31f43e8 Revert "Fix a couple test failures encountered when building on Windows" 8c427eb Remove max_bytes_used test from haddock test cases 8b107b5 rts/Printer.c: update comments about using USING_LIBBFD 9692393 configure.ac: cleanup: remove unused 'HaveLibDL' subst 1719c42 Update nofib submodule: Hide Word from Prelude e428b5b Add Data.List.uncons 89baab4 Revert "Remove max_bytes_used test from haddock test cases" 498d7dd Do not test max_bytes_used et. al for haddock tests b5a5776 Update performance numbers (mostly improved) 3034dd4 Another test for type function saturation 4c359f5 Small improvement to unsaturated-type-function error message 6af1c9b Add missing changelog/since entry for `uncons` e18525f pprC: declare extern cmm primitives as functions, not data 55e4e5a Revert "Do not test max_bytes_used et. al for haddock tests" 7bf7ca2 Do not use max_bytes_used for haddock test 7d3f2df PostTcType replaced with TypeAnnot 5a1def9 Update T4801 perf numbers 78209d7 INLINE unfoldr f0e725a Typos 049bef7 rules: cleanup: use '$way_*suf' var instead of open-coded '($3_way_)s' fdfe6c0 rules: fix buld failure due to o-boot suffix typo d94de87 Make Applicative a superclass of Monad 0829f4c base: Bump version to 4.8.0.0 27a642c Revert "base: Bump version to 4.8.0.0" c6f502b Bump `base` version to 4.8.0.0 for real 68ecc57 base: replace ver 4.7.1.0 references by 4.8.0.0 841924c build.mk.sample: Stage1 needn't be built with -fllvm 1e40037 Update nofib submodule to fix errors in main suite. f3d2694 Update nofib submodule to track gc bitrot updates. 6477b3d testsuite: AMPify ioprof.hs 29e50da testsuite: AMPify T3001-2 71c8530 Update performance numbers 57fd8ce Fix T5321Fun perf number 23e764f T4801 perf numbers: Another typo c0c1772 Kill obsolete pre GHC 7.6 bootstrapping support 0b54f62 Make GHC `time-1.5`-ready 695d15d Update nofib submodule: Update gitignore with more generated files 946cbce Fix support for deriving Generic1 for data families (FIX #9563) 9d71315 Remove obsolete comment about (!!) b10a7a4 base: Drop obsolete/redundant `__GLASGOW_HASKELL__` checks b53c95f Move ($!) from Prelude into GHC.Base 45cd30d Follow-up to b53c95fe621d3a66a82e6dad383e1c0c08f3871e 6999223 Fixup test-case broken by Follow-up to b53c95fe621 abff2ff Move docstring of `seq` to primops.txt.pp 2cd76c1 Detabify primops.txt.pp 5fbd4e36 Update haskell2010 submodule 39e206a Update libffi-tarballs submodule to libffi 3.1 (re #8701) 004c5f4 Tweak perf-numbers for T1969 and T4801 c0fa383 Export `Traversable()` and `Foldable()` from Prelude df2fa25 base: Remove bunk default impl of (>>=) 65f887e base: Add some notes about the default impl of '(>>)' b72478f Don't offer hidden modules for autocomplete. f8ff637 Declare official GitHub home of libraries/filepath a9b5d99 Mark T8639_api/T8628 as PHONY 72d6d0c Update config.{guess,sub} to GNU automake 1.14.1 d24a618 Follow-up to 72d6d0c2704ee6d9 updating submodules for real 628b21a haskeline: update submodule to fix Windows breakage cdf5a1c Add special stdout for hClose002 on x64 Solaris cfd8c7d Find the target gcc when cross-compiling 3681c88 Fix cppcheck warnings fe9f7e4 Remove special casing of singleton strings, split all strings. 52eab67 Add the ability to :set -l{foo} in ghci, fix #1407. caf449e Return nBytes instead of nextAddr from utf8DecodeChar 7e658bc Revert "Revert "rts/base: Fix #9423"" and resolve issue that caused the revert. e7a0f5b Fix typo "Rrestriction" in user's guide (lspitzner, #9528) b475219 Move `Maybe`-typedef into GHC.Base 1574871 Re-add SPECIALISE liftM* pragmas dropped in d94de87252d0fe 9b8e24a Typo 74f0e15 Simplify 3c28290 Typo in comment b62bd5e Implement `decodeDouble_Int64#` primop 2622eae Remove unnecessary imports in GHC.Event.KQueue to fix compiler warnings. 393f0bb Comments only: explain checkAxInstCo in OptCoercion a8d7f81 Update haddock submodule for package key fix. c4c8924 Fix formatting bug in core-spec. 8b90836 Move (=<<) to GHC.Base eae1911 Move `when` to GHC.Base a94dc4c Move Applicative/MonadPlus into GHC.Base fbf1e30 Move Control.Monad.void into Data.Functor af22696 Invert module-dep between Control.Monad and Data.Foldable b406085 Generalise Control.Monad.{sequence_,msum,mapM_,forM_} ed58ec0 Revert "Update haddock submodule for package key fix." 275dcaf Add -fwarn-context-quantification (#4426) 8c79dcb Update haddock submodule (miscellaneous fixes) e12a6a8 Propositional equality for Datatype meta-information 0a8e6fc Make constructor metadata parametrized (with intended parameter <- datatype) f097b77 Implement sameConstructor cc618e6 get roles right and fix a FIXME 79c7125 Actually parametrize the Constructor with the Datatype 7bd4bab Supply a reasonable name (should be derived from d_name tho) 09fcd70 Use 'd_name' as the name (should be derived from d_name tho) 4d90e44 Add default case (fixes -Werror) 6d84b66 Revert accidental wip/generics-propeq-conservative merge fdc03a7 Auto-derive a few manually coded Show instances c96c64f Increase -fcontext-stack=N default to 100 ebb7334 Spelling error in flags.xml 48f17f1 Use mapAccumL (refactoring only) 2a5eb83 Typo in comment in GHC.Generics 1378ba3 Fix garbled comment wording 28059ba Define Util.leLength :: [a] -> [b] -> Bool 24e51b0 White space only 0aaf812 Clean up Coercible handling, and interaction of data families with newtypes e1c6352 Fixup overlooked `unless` occurence d48fed4 Define fixity for `Data.Foldable.{elem,notElem}` 5e300d5 Typos e76fafa Fix potential `mingw32_HOST_OS` breakage from eae19112462fe77 83c5821 Fix potential `mingw32_HOST_OS` -Werror failure 4805abf Deactive T4801 `max_bytes_used`-check & bump T3064 numbers 9f7e363 Change linker message verbosity to `-v2` (re #7863) 3daf002 Set up framework for generalising Data.List to Foldables 1812898 Turn a few existing folds into `Foldable`-methods (#9621) 05cf18f Generalise (some of) Data.List to Foldables (re #9568) ed65808 Add missing changelog entries for current state of #9586 e7c1633 Simplify import-graph a bit more bfc7195 Update haskell2010, haskell98, and array submodules 835d874 Make libffi install into a predictable directory (#9620) 5ed1281 Move `mapM` and `sequence` to GHC.Base and break import-cycles 1f7f46f Generalise Data.List/Control.Monad to Foldable/Traversable b8f5839 Export `Monoid(..)`/`Foldable(..)`/`Traversable(..)` from Prelude 27b937e Fix windows breakage from 5ed12810e0972b1e due to import cycles 38cb5ec Update haskeline submodule to avoid -Werror failure 5fa6e75 Ensure that loop breakers are computed when glomming 01906c7 Test Trac #9565 and #9583 2a743bb Delete hack when takeDirectory returns "" 330bb3e Delete all /* ! __GLASGOW_HASKELL__ */ code d5e4874 Change all hashbangs to /usr/bin/env (#9057) 165072b Adapt nofib submodule to #9586 changes 4b648be Update Cabal submodule & ghc-pkg to use new module re-export types 805ee11 `M-x delete-trailing-whitespace` & `M-x untabify` fb84817 `M-x delete-trailing-whitespace` & `M-x untabify` 6b02626 Update time submodule to 1.5.0 release f1d8841 Link from 7.6.3.4 to 7.7.2.6 in the user guide. 55e04cb Remove a few redundant `-fno-warn-tabs`s 46a5b7c Detab DataCon 3ecca02 Update `binary` submodule in an attempt to address #9630 c315702 [ci skip] iface: detabify/dewhitespace IfaceSyn 3765e21 [ci skip] simplCore: detabify/dewhitespace CoreMonad 7567ad3 [ci skip] typecheck: detabify/dewhitespace TcInstDecls c4ea319 [ci skip] typecheck: detabify/dewhitespace TcPat a3dcaa5 [ci skip] typecheck: detabify/dewhitespace TcTyDecls 18155ac [ci skip] typecheck: detabify/dewhitespace TcUnify efdf4b9 types: detabify/dewhitespace Unify dc1fce1 Refer to 'mask' instead of 'block' in Control.Exception a7ec061 Delete hack that was once needed to fix the build 2388146 User's Guide: various unfolding-related fixes c23beff Fixes cyclic import on OS X(#9635) 74ae598 Defer errors in derived instances 20632d3 Do not discard insoluble Derived constraints 8c9d0ce Wibble to implicit-parameter error message 1a88f9a Improve error messages from functional dependencies 0e16cbf Two improved error messages ac157de Complain about illegal type literals in renamer, not parser 0ef1cc6 De-tabify and remove trailing whitespace 0686897 This test should have -XDataKinds 2e4f364 Comments c5f65c6 Update `unix` submodule to disable getlogin tests 319703e Don't re-export `Alternative(..)` from Control.Monad (re #9586) 4b9c92b Update Cabal submodule to latest master branch tip b3aa6e4 Replace obsolete `defaultUserHooks` by `autoconfUserHooks` 51aa2fa Stop exporting, and stop using, functions marked as deprecated f636faa Set default-impl of `mapM`/`sequence` methods to `traverse`/`sequenceA` 071167c User's Guide: Fix compiler plugin example (#9641, #7682) a07ce16 Generalise `Control.Monad.{when,unless,guard}` bf33291 Generalise `guard` for real this time e5cca4a Extend `Foldable` class with `length` and `null` methods ee15686 Fixup nofib submodule to cope with e5cca4ab246ca2 e97234d bugfix: EventCapsetID should be EventThreadID aeb9c93 Document that -dynamic is needed for loading compiled code into GHCi 7371d7e Revert "rts: add Emacs 'Local Variables' to every .c file" 23bb904 Add emacs indentation/line-length settings 5d16c4d Update hsc2hs submodule 8d04eb2 Fix bogus comment 04ded40 Comments about the let/app invariant 1c10b4f Don't use newSysLocal etc for Coercible 864bed7 Update Win32 submodule to avoid potential -Werror failure 488e95b Make foldr2 a bit more strict 4e1dfc3 Make scanr a good producer and consumer d41dd03 Make mapAccumL a good consumer 7893210 Fusion rule for "foldr k z (x:build g)" 96a4062 Make filterM a good consumer 93b8d0f Simplify mergeSATInfo by using zipWith bcbb045 First stab at making ./validate less verbose 15f661c update cabal submodule to fix build failure on Solaris f3b5e16 rts/includes: Fix up .dir-locals.el 3a549ba [ci skip] compiler: Kill last remaining tabs in CallArity ca3089d [ci skip] Kill tabs in md5.h 53a2d46 [ci skip] Kill unused count_bytes script 2a88568 Use dropWhileEndLE p instead of reverse . dropWhile p . reverse 084d241 Basic Python 3 support for testsuite driver (Trac #9184) 644c76a Use LinkerInternals.h for exitLinker. b23ba2a Place static closures in their own section. 3b5a840 BC-breaking changes to C-- CLOSURE syntax. 178eb90 Properly generate info tables for static closures in C--. 3567207 Rename _closure to _static_closure, apply naming consistently. d6d5c12 Revert "Use dropWhileEndLE p instead of reverse . dropWhile p . reverse" 9bf5228 Use dropWhileEndLE p instead of reverse . dropWhile p . reverse eb191ab rts/PrimOps.cmm: follow '_static_closure' update eb35339 Really fix dropWhileEndLE commit 2b59c7a arclint: Don't complain about tabs unless it's inside the diff. 582217f Comments only (instances for Proxy are lazy) e4a597f Revert "Basic Python 3 support for testsuite driver (Trac #9184)" 4977efc Restore spaces instead of tabs, caused by revert of Python 3 2fc0c6c Check for staticclosures section in Windows linker. e8dac6d Fix typo in section name: no leading period. 2a8ea47 ghc.mk: fix list for dll-split on GHCi-less builds 3549c95 Implement `MIN_VERSION_GLASGOW_HASKELL()` macro cb0a503 rts: unrust 'libbfd' debug symbols parser 6a36636 testsuite: fix tcrun036 build against Prelude/Main 'traverse' clash a1b5391 testsuite: fix T5751 build failure (AMP) b30b185 testsuite: fix T1735_Help/State.hs build failure (AMP) 6ecf19c testsuite: fix seward-space-leak build aganst Prelude/Main 'traverse' clash 48089cc Use correct precedence when printing contexts with class operators 85aba49 Merge branch 'master' of http://git.haskell.org/ghc 3c5648a Fix a typo in an error message 460eebe Remove RAWCPP_FLAGS b3e5a7b Delete __GLASGOW_HASKELL__ ifdefs for stage0 < 7.6. 2ee2527 Remove unused hashName declaration adcb9db Add support for LINE pragma in template-haskell 1ec9113 Fix configure check for 9439 bug 1f92420 configure in base: add msys to windows check 9ebbdf3 Clean up and remove todo. 205b103 Fix closing parenthesis d45693a Make scanl fuse; add scanl' bdb0c43 Code size micro-optimizations in the X86 backend ffde9d2 testsuite: T5486 requires integer-gmp internals e87135c Bump haddock.base perf numbers 6f2eca1 Use Data.Map.mergeWithKey 21dff57 Initial commit of the Backpack manual [skip ci] 21389bc Update some out-of-date things in Backpack implementation doc [skip ci] d14d3f9 Make Data.List.takeWhile fuse: fix #9132 eb6b04c Update T4801 perf numbers 0ed9a27 Preemptive performance number updates 5300099 Make the linker more robust to errors 267ad95 Ignore exe files in base (from tests) 39666ae Update haddock submodule with lazy IO fix. d3f56ec Rewrite section 1 of the Backpack manual. [skip ci] 674c631 Name worker threads using pthread_setname_np 97b7593 rts: don't crash on 'hs_init(NULL, NULL)' in debug rts ad4a713 Remove a few redundant `.hs-boot` files 1032554 Fallback to `ctypes.cdll` if `ctypes.windll` unavailable 034b203 Extend windows detection in testsuite to recognize MSYS target 1942fd6 Refactor to avoid need for `Unicode.hs-boot` a36991b Fix build on some platforms c375de0 Update `time` submodule to address linker issue 05f962d Compiler performance benchmark for #9675 23da971 Adjust T9675 baseline numbers based on ghc-speed d9db81f seqDmdType needs to seq the DmdEnv as well 3575109 Update more performance numbers due to stricter seqDmdType f3ae936 T9675: Allow Much wider range of values f0af3d8 Actually put in new perf number for T4801 8376027 Fix comment typos: lll -> ll, THe -> The 4b69d96 Add a configure test for pthread_setname_np cde3a77 Make Data.List.Inits fast 7e73595 Make tails a good producer (#9670) d786781 Declare official GitHub home of libraries/deepseq a477e81 Avoid printing uniques in specialization rules 0e2bd03 Update T6056 output 1c35f9f rts: fix unused parameter warning 612f3d1 Implement optimized NCG `MO_Ctz W64` op for i386 (#9340) 7369d25 Remove obsolete Data.OldTypeable (#9639) ce23745 Generalise `Control.Monad.{foldM,foldM_}` to `Foldable` (#9586) abfbb0d Remove redundant explicit `Prelude` imports d576fc3 Python 3 support, second attempt (Trac #9184) b5930f8 Refactor module imports in base 5b9fe33 Indentation and non-semantic changes only. 4d90b53 Sync up `containers` submodule to latest `master`-tip 07da36b Revert "Fix typo in section name: no leading period." 0202b7c Revert "Check for staticclosures section in Windows linker." 89a8d81 Revert "Rename _closure to _static_closure, apply naming consistently." 126b0c4 Revert "Properly generate info tables for static closures in C--." a3860fc Revert "BC-breaking changes to C-- CLOSURE syntax." d5d6fb3 Revert "Place static closures in their own section." 47c4c91 Update Haddock submodule 07a99c1 Revert "rts/PrimOps.cmm: follow '_static_closure' update" f681c32 Test #9692 in th/T9692 2cd80ba Clarify location of Note. Comment change only. e319d6d Reify data family instances correctly. 710bc8d Update primitive, vector, and dph submodules. 27f7552 Make Applicative-Monad fixes for tests. 3687089 Updated testsuite/.gitignore to cover artifacts on Windows. 2cc2065 Use objdump instead of nm to derive constants on OpenBSD 9f29e03 ghc-prim: Use population count appropriate for platform d4fd168 Update to Unicode version 7.0 a5f4fb6 Remove extra period 3157127 Improve isDigit, isSpace, etc. ef2d027 Make findIndices fuse 1e269bf Make Data.List.concatMap fuse better 6825558 Add doctest examples for Data.Functor. 5211673 Fix typo in -XConstraintKinds docs 9c464f8 Add doctest examples for Data.Bool. c819958 Add release note about Unicode 7.0 69f6361 Fixes the ARM build 972ba12 Enabled warn on tabs by default (fixes #9230) 4faeecb [skip ci] rts: Detabify RtsMessages.c aa8d23d [skip ci] rts: Detabify RaiseAsync.h bb04867 [skip ci] rts: Detabify Capability.h 99edc35 [skip ci] rts: Detabify CheckUnload.c 6aa6ca8 [skip ci] rts: Detabify Profiling.c 570b339 [skip ci] rts: Detabify Threads.c 21eaaa1 [skip ci] rts: Detabify sm/Evac.c 9167d0e [skip ci] rts: Detabify sm/Scav.c 5bb8f14 [skip ci] rts: Detabify Stats.c 2dc21b9 [skip ci] rts: Detabify Schedule.h 1d12df3 [skip ci] rts: Detabify LdvProfile.h 3d0e695 [skip ci] rts: Detabify Proftimer.c 68c45b6 [skip ci] rts: Detabify Exception.cmm a7ab7d3 [skip ci] rts: Detabify HeapStackCheck.cmm 6811e53 [skip ci] rts: Detabify Capability.c beb5c2e [skip ci] rts: Detabify RaiseAsync.c e13478f [skip ci] rts: Detabify sm/GC.c faa3339 [skip ci] rts: Detabify sm/Sanity.c bc1609a [skip ci] rts: Detabify sm/Compact.c c8173d5 [skip ci] rts: Detabify sm/Compact.h 5106e20 [skip ci] rts: Detabify RetainerProfile.c 03c3e9a [skip ci] rts: Detabify ProfHeap.c 6abb34c [skip ci] rts: Detabify Schedule.c 9bfe602 rts: Detabify Interpreter.c df5c11a base: Mark WCsubst.c as generated for Phabricator 45cbe85 Flush stdout in T9692 aa641e5 Add forgotten import to T9692 a11f71e Fix a rare parallel GC bug 427925d More updates to Backpack manual [skip ci] 5bb73d7 Check in up-to-date PDF copies of Backpack docs. [skip ci] aa47995 Implementation of hsig (module signatures), per #9252 1addef8 Fix windows build failure. 73c7ea7 fix a typo in comments: normaliseFfiType 0855b24 Pass in CXX to libffi's configure script. 7b59db2 `M-x delete-trailing-whitespace` & `M-x untabify` a3312c3 testsuite: Fix outdated output for T5979/safePkg01 0a290ca Add new `Data.Bifunctor` module (re #9682) 9e2cb00 Optimise atomicModifyIORef' implementation (#8345) 0e1f0f7 Un-wire `Integer` type (re #9714) 0013613 Deactivate T3064 `max_bytes_used`-check 49b05d6 Improve performance of isSuffixOf (#9676) 1874501 Typo in comment aa2ceba Normalise package key hash to make tests less fragile. 63918e6 Add n-ary version of `two_normalisers` to testsuite lib 3d6422b testlib: Get rid of two_normalisers 98ed815 Make iterateFB inlineable 75979f3 base: Refactor/clean-up *List modules 5f69c8e Reorder GHC.List; fix performance regressions f109085 Update Haddock submodule for collapsible section support 64d0a19 Really fix fft2 regression. #9740 208a0c2 Fixed unused variable warning on mingw32/i686 in rts/Linker.c f9ca529 hsc2hs: Update submodule 322810e Convert GHCi sources from .lhs to .hs 257cbec Fix #9236 Error on read from closed handle 5ce1266 Use snwprintf instead of swprintf in rts/Linker.c. acb3295 Avoid setting -Werror=unused-but-set-variable on Windows. 45175e1 Extra CRs are now filtered out from the source file for :list. f10b67a Updated stale ghcpkg05.stderr-mingw32. 3d27f69 Do not use a relative path for echo in tests/ghci/prog013. c211f8e Add __GLASGOW_HASKELL_TH__=YES/NO to CPP definitions 93c776a Added mingw32-specific expected stdout files for tests/driver/sigof{01,02,03} 9de5240 Comments only c6d4ae6 Fix test driver python3 compatibility issues 578bc00 Add notes on change to hGetContents semantics 995ea1c Fixed missing trailing newline bug in pretty printer 1907e81 Updated testsuite/.gitignore to exclude some test artifacts on Windows. cbb20ab Drop deprecated `OverlappingInstances` from base 919e930 Fix comment typos 8ef4cf1 Add doctest examples for Data.Char bd6c6f6 Update Haddock submodule 54addb1 Clean-up `Data.Fixed` f12be5b Add changelog entry for recent Unicode 7.0 update d3a7126 Update doctest example style in `Data.Bool` 4667fb5 Split off stat (benchmark) test failures into a separate section in the test runner summary. 322c139 remove old .NET related code e466ea7 Remove legacy support for -optdef flags d15d704 Fix build via Haddock submodule update. 6534686 Fix comment about dropWhileEndLE e5ba360 rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) a47ff8b Fixed T5435_dyn_asm on Windows. The test code was not in sync with the expected output. f688f03 Test #9262 in th/T9262, and update other tests. 2cc593d Bring unbound tyvars into scope during reifyInstances. b174288 Test #8953 in th/T8953 9fd19f9 Always use KindedTV when reifying. (#8953) 593e8b9 Annotate reified poly-kinded tycons when necessary. (#8953) c3ecf06 Annotate poly-kinded type patterns in instance reification. 99882ba Testsuite wibbles from fixing #8953 862772b Test #9084 in th/T9084. 03d61cc Fix #9084 by calling notHandled when unknown bits are enountered. 17265c0 Fix testsuite output from #9084. 752b5e2 Test #9738 in th/T9738 209baea Fix #9738, by handling {-# ANN ... #-} in DsMeta. 18a4a5d Update release notes for #9262 #8953 #9084. 96c22d9 Tweak the error message for pattern synonym methods, since they are disallowed both in class and instance declarations c001bde Put one-Shot info in the interface c271e32 Add GHC.Prim.oneShot 072259c Use oneShot in the definition of foldl etc. 063ae61 Update expected profiling output for scc001 1c0b736 Link to oneShot from the User's Guide 6dd218e Make Foldable's foldr1 and foldl1 defaults lazier ce03c4a Further relax T1969?s max_bytes range 49fde3b Add `Alternative` wrapper to Data.Monoid 4dbe433 Minor Haddock markup improvement to Data.Monoid 828d724 Refactor Haddock comments in Data.Bits c7fa0ba Fix lost Haddock annotation for `class Monad m` 1d6124d Tidy up pretty-printing of SrcLoc and SrcSpan 27ba070 Improve pretty-printing of type variables c8c18a1 Some refactoring around endPass and debug dumping 7251798 Simplify the generation of superclass constraints in tcInstDecl2 d153e40 Add the unfolding and inline-pragma for DFuns in DsBinds, not TcInstDcls bdbb595 White space only fd46acf Fix reduceTyFamApp_maybe 33dcb81 Simplify the API for tcInstTyVars, and make it more consistent with other similar functions 9c81db4 Rename setRole_maybe to downgradeRole_maybe 54f9188 Refactor skolemising, and newClsInst 2bfc653 Refactor the treatment of lexically-scoped type variables for instance declarations e11e1b8 Get the Untouchables level right in simplifyInfer a6e7654 Normalise the type of an inferred let-binding e840d85 Typechecker debug tracing only c64539c When reporting the context of given constraints, stop when you find one that binds a variable mentioned in the wanted 15131ec Only report "could not deduce s~t from ..." for givens that include equalities f054822 Don't filter out allegedly-irrelevant bindings with -dppr-debug 84d9ef0 Minor refactoring (no change in functionality) c1a85b3 Define ctEvLoc and ctEvCoercion, and use them 4723a0e Test Trac #9211 f861fc6 Test Trac #9708 6d1ac96 Improve error message for a handwritten Typeable instance dbbffb7 Test Trac #9747 abfbdd1 Add comments explaining ProbOneShot c639560 Test Trac #9739 7c79633 Fix the superclass-cycle detection code (Trac #9739) 66658ee Comments only 5479ae0 Testsuite error message changes 652a5ef Add flattening-notes f02c915 Make this test a bit simpler ce9d6f2 Compiler performance is much worse in for loopy givens 5770029 Simon's major commit to re-engineer the constraint solver 2f0d841 Updates to safePkg01 under Edward's guidance 09aac7d Test Trac #9081 fe178b2 Test Trac #9750 1408c8d Remove redundant "Minimal complete definition"-comments 64dc4d1 Re-center perf-numbers for T5631 6a1c05f A little refactoring of HsSplice and friends 77f8221 Temporarily disable T3064 (see #9771) 0a8e899 Remove redundant contexts from Foldable methods ac0915b Clean-up Haddock in `Data.Functor` 40b1ee4 Add `isSubsequenceOf` to Data.List (#9767) 32237f0 Fix typo in testsuite Makefile 83cf31e Fix a couple of bugs in the way info tables are generated for 64-bit platforms 4cd277b Fix bugs in debug printing 3bebf3c Fix a couple of inaccurate stack checks e6b3829 Disable an assertion; see comment 081ef2f Add a comment about stack checks d14312f Add doctest examples for Data.Either d0d9dc0 Clarify confusing notice from `make maintainer-clean` ad8457f Remove -ddump-simpl-phases flag c0a2354 Remove -ddump-core-pipeline flag 303776a Update User's Guide, cleanup DynFlags 0f930ba Move expansion of 'assert' from renamer to typechecker 030abf9 Remove unused tyConsOfDataCon e7523fe Make tyConsOfType return a (NameEnv TyCon) rather than [TyCon] f81f82e Comments and white space only 528cbd7 Give T3064 the right module name (just tidying up) 096b7e6 Switch off lazy flattening (fix Trac #3064) cb6ccad Minor refacoring and trace-message printing c945477 Allow the solved dictionaries to propagate from outside in ec38deb Wibbles to notes 203cf0e Refactor the code that prevents recursion among Coercible constraints c79cbac Re-enable T3064, which works now 91c15d6 Better error messages for new per-instance overlap flags and Safe Haskell. c96a613 Add in Incoherent Instances test for Safe Haskell. f4ead30 Warn for Safe Haskell when -XOverlappingInstances or -XIncoherentInstances turned on. abba381 Improve Applicative definitions dc5fa80 Make getTag use a bang pattern instead of seq b0e8e34 Update .gitignore to properly ignore emacs temp files 24e05f4 *Really*, really fix RTS crash due to bad coercion. 37d64a5 small parser/lexer cleanup b0d5b5b [Docs] Fixed several broken urls in user's guide f14ac52 Use bracket in `withCurrentDirectory` 832ef3f Have validate take into account stat test failures too. df3b1d4 base: Manually unlit .lhs into .hs modules a2e7bbf Preserve argument order to (==)/eq in nub and nubBy 7eddaa4 DRAFT: Implement new integer-gmp2 from scratch (re #9281) From git at git.haskell.org Sat Nov 8 08:48:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:48:30 +0000 (UTC) Subject: [commit: ghc] wip/T9281: Minor fixup in libraries/integer-gmp2/integer-gmp2.buildinfo.in (2a33108) Message-ID: <20141108084830.EBACA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/2a3310890d048ef6a391e788d7d35a6b7b1ccac7/ghc >--------------------------------------------------------------- commit 2a3310890d048ef6a391e788d7d35a6b7b1ccac7 Author: Herbert Valerio Riedel Date: Sat Nov 8 09:48:39 2014 +0100 Minor fixup in libraries/integer-gmp2/integer-gmp2.buildinfo.in >--------------------------------------------------------------- 2a3310890d048ef6a391e788d7d35a6b7b1ccac7 libraries/integer-gmp2/integer-gmp2.buildinfo.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/integer-gmp2/integer-gmp2.buildinfo.in b/libraries/integer-gmp2/integer-gmp2.buildinfo.in index 9b2bad9..8f7769d 100644 --- a/libraries/integer-gmp2/integer-gmp2.buildinfo.in +++ b/libraries/integer-gmp2/integer-gmp2.buildinfo.in @@ -2,4 +2,4 @@ include-dirs: @GMP_INCLUDE_DIRS@ extra-lib-dirs: @GMP_LIB_DIRS@ extra-libraries: @GMP_LIBS@ frameworks: @GMP_FRAMEWORK@ -install-includes: HsIntegerGmp.h \ No newline at end of file +install-includes: HsIntegerGmp2.h From git at git.haskell.org Sat Nov 8 08:49:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:49:26 +0000 (UTC) Subject: [commit: ghc] wip/T9281: Minor fixup in libraries/integer-gmp2/integer-gmp2.buildinfo.in (6853c87) Message-ID: <20141108084926.3EA3C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/6853c87cfc573a6dcb8084fa678bf1760333a215/ghc >--------------------------------------------------------------- commit 6853c87cfc573a6dcb8084fa678bf1760333a215 Author: Herbert Valerio Riedel Date: Sat Nov 8 09:48:39 2014 +0100 Minor fixup in libraries/integer-gmp2/integer-gmp2.buildinfo.in >--------------------------------------------------------------- 6853c87cfc573a6dcb8084fa678bf1760333a215 ghc.mk | 1 + libraries/integer-gmp2/integer-gmp2.buildinfo.in | 2 +- 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/ghc.mk b/ghc.mk index 40d782f..1bbfa90 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1220,6 +1220,7 @@ sdist_%: CLEAN_FILES += libraries/bootstrapping.conf CLEAN_FILES += libraries/integer-gmp/cbits/GmpDerivedConstants.h CLEAN_FILES += libraries/integer-gmp/include/HsIntegerGmp.h +CLEAN_FILES += libraries/integer-gmp2/include/HsIntegerGmp2.h CLEAN_FILES += libraries/base/include/EventConfig.h CLEAN_FILES += mk/config.mk.old CLEAN_FILES += mk/project.mk.old diff --git a/libraries/integer-gmp2/integer-gmp2.buildinfo.in b/libraries/integer-gmp2/integer-gmp2.buildinfo.in index 9b2bad9..8f7769d 100644 --- a/libraries/integer-gmp2/integer-gmp2.buildinfo.in +++ b/libraries/integer-gmp2/integer-gmp2.buildinfo.in @@ -2,4 +2,4 @@ include-dirs: @GMP_INCLUDE_DIRS@ extra-lib-dirs: @GMP_LIB_DIRS@ extra-libraries: @GMP_LIBS@ frameworks: @GMP_FRAMEWORK@ -install-includes: HsIntegerGmp.h \ No newline at end of file +install-includes: HsIntegerGmp2.h From git at git.haskell.org Sat Nov 8 08:53:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:53:39 +0000 (UTC) Subject: [commit: ghc] wip/T8584: nlHsTyApps: for applying a function both on type- and term-level arguments (c0af9a3) Message-ID: <20141108085339.CA9E33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/c0af9a312b63c9587aa2a3afa282bfdace9a1dc7/ghc >--------------------------------------------------------------- commit c0af9a312b63c9587aa2a3afa282bfdace9a1dc7 Author: Dr. ERDI Gergo Date: Fri Nov 7 22:49:52 2014 +0800 nlHsTyApps: for applying a function both on type- and term-level arguments >--------------------------------------------------------------- c0af9a312b63c9587aa2a3afa282bfdace9a1dc7 compiler/hsSyn/HsUtils.lhs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/compiler/hsSyn/HsUtils.lhs b/compiler/hsSyn/HsUtils.lhs index 12e2388..df2406f 100644 --- a/compiler/hsSyn/HsUtils.lhs +++ b/compiler/hsSyn/HsUtils.lhs @@ -28,7 +28,7 @@ module HsUtils( mkHsOpApp, mkHsDo, mkHsComp, mkHsWrapPat, mkHsWrapPatCo, mkLHsPar, mkHsCmdCast, - nlHsTyApp, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, + nlHsTyApp, nlHsTyApps, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, nlHsDo, nlHsOpApp, nlHsLam, nlHsPar, nlHsIf, nlHsCase, nlList, mkLHsTupleExpr, mkLHsVarTuple, missingTupArg, toHsType, toHsKind, @@ -177,6 +177,9 @@ mkSimpleHsAlt pat expr nlHsTyApp :: name -> [Type] -> LHsExpr name nlHsTyApp fun_id tys = noLoc (HsWrap (mkWpTyApps tys) (HsVar fun_id)) +nlHsTyApps :: name -> [Type] -> [LHsExpr name] -> LHsExpr name +nlHsTyApps fun_id tys xs = foldl nlHsApp (nlHsTyApp fun_id tys) xs + --------- Adding parens --------- mkLHsPar :: LHsExpr name -> LHsExpr name -- Wrap in parens if hsExprNeedsParens says it needs them From git at git.haskell.org Sat Nov 8 08:53:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:53:42 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Renamer for PatSynSigs: handle type variable bindings (37a4d47) Message-ID: <20141108085342.6DB713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/37a4d470d65ce4d567f452dc89a42e916d0c31f2/ghc >--------------------------------------------------------------- commit 37a4d470d65ce4d567f452dc89a42e916d0c31f2 Author: Dr. ERDI Gergo Date: Fri Nov 7 19:29:06 2014 +0800 Renamer for PatSynSigs: handle type variable bindings >--------------------------------------------------------------- 37a4d470d65ce4d567f452dc89a42e916d0c31f2 compiler/hsSyn/HsBinds.lhs | 8 +++---- compiler/rename/RnBinds.lhs | 57 +++++++++++++++++++++++++++++++-------------- 2 files changed, 43 insertions(+), 22 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index bbf6bc2..23534cf 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -568,12 +568,12 @@ data Sig name TypeSig [Located name] (LHsType name) -- | A pattern synonym type signature - -- @pattern (Eq b) => P a b :: (Num a) => T a + -- @pattern type forall b. (Eq b) => P a b :: forall a. (Num a) => T a | PatSynSig (Located name) (HsPatSynDetails (LHsType name)) (LHsType name) -- Type - (LHsContext name) -- Provided context - (LHsContext name) -- Required contex + (HsExplicitFlag, LHsTyVarBndrs name, LHsContext name) -- Provided context + (HsExplicitFlag, LHsTyVarBndrs name, LHsContext name) -- Required contex -- | A type signature for a default method inside a class -- @@ -730,7 +730,7 @@ ppr_sig (SpecSig var ty inl) = pragBrackets (pprSpec (unLoc var) (ppr ty) i ppr_sig (InlineSig var inl) = pragBrackets (ppr inl <+> pprPrefixOcc (unLoc var)) ppr_sig (SpecInstSig ty) = pragBrackets (ptext (sLit "SPECIALIZE instance") <+> ppr ty) ppr_sig (MinimalSig bf) = pragBrackets (pprMinimalSig bf) -ppr_sig (PatSynSig name arg_tys ty prov req) +ppr_sig (PatSynSig name arg_tys ty (_, _, prov) (_, _, req)) = pprPatSynSig (unLoc name) False args (ppr ty) (pprCtx prov) (pprCtx req) where args = fmap ppr arg_tys diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index c2489cb..4a98a35 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -30,7 +30,7 @@ import {-# SOURCE #-} RnExpr( rnLExpr, rnStmts ) import HsSyn import TcRnMonad import TcEvidence ( emptyTcEvBinds ) -import RnTypes ( bindSigTyVarsFV, rnHsSigType, rnLHsType, checkPrecMatch, rnContext ) +import RnTypes import RnPat import RnNames import RnEnv @@ -50,6 +50,7 @@ import FastString import Data.List ( partition, sort ) import Maybes ( orElse ) import Control.Monad +import Util ( filterOut ) #if __GLASGOW_HASKELL__ < 709 import Data.Traversable ( traverse ) #endif @@ -841,23 +842,43 @@ renameSig ctxt sig@(MinimalSig bf) = do new_bf <- traverse (lookupSigOccRn ctxt sig) bf return (MinimalSig new_bf, emptyFVs) -renameSig ctxt sig@(PatSynSig v args ty prov req) - = do v' <- lookupSigOccRn ctxt sig v - let doc = quotes (ppr v) - rn_type = rnHsSigType doc - (ty', fvs1) <- rn_type ty - (args', fvs2) <- case args of - PrefixPatSyn tys -> - do (tys, fvs) <- unzip <$> mapM rn_type tys - return (PrefixPatSyn tys, plusFVs fvs) - InfixPatSyn left right -> - do (left', fvs1) <- rn_type left - (right', fvs2) <- rn_type right - return (InfixPatSyn left' right', fvs1 `plusFV` fvs2) - (prov', fvs3) <- rnContext (TypeSigCtx doc) prov - (req', fvs4) <- rnContext (TypeSigCtx doc) req - let fvs = plusFVs [fvs1, fvs2, fvs3, fvs4] - return (PatSynSig v' args' ty' prov' req', fvs) +renameSig ctxt sig@(PatSynSig v args ty (ex_flag, _ex_tvs, prov) (univ_flag, _univ_tvs, req)) + = do { v' <- lookupSigOccRn ctxt sig v + ; let doc = TypeSigCtx $ quotes (ppr v) + ; loc <- getSrcSpanM + + ; let (univ_kvs, univ_tvs) = extractHsTysRdrTyVars (ty:unLoc req) + ; let univ_tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ univ_tvs + + ; bindHsTyVars doc Nothing univ_kvs univ_tv_bndrs $ \ univ_tyvars -> do + { (req', fvs1) <- rnContext doc req + ; (ty', fvs2) <- rnLHsType doc ty + + ; let (arg_tys, rnArgs) = case args of + PrefixPatSyn tys -> + let rnArgs = do + (tys', fvs) <- mapFvRn (rnLHsType doc) tys + return (PrefixPatSyn tys', fvs) + in (tys, rnArgs) + InfixPatSyn ty1 ty2 -> + let rnArgs = do + (ty1', fvs1) <- rnLHsType doc ty1 + (ty2', fvs2) <- rnLHsType doc ty2 + return (InfixPatSyn ty1' ty2', fvs1 `plusFV` fvs2) + in ([ty1, ty2], rnArgs) + + ; let (ex_kvs, ex_tvs) = extractHsTysRdrTyVars (arg_tys ++ unLoc prov) + ex_kvs' = filterOut (`elem` univ_kvs) ex_kvs + ex_tvs' = filterOut (`elem` univ_tvs) ex_tvs + + ; let ex_tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ ex_tvs' + + ; bindHsTyVars doc Nothing ex_kvs' ex_tv_bndrs $ \ ex_tyvars -> do + { (prov', fvs3) <- rnContext doc prov + ; (args', fvs4) <- rnArgs + + ; let fvs = plusFVs [fvs1, fvs2, fvs3, fvs4] + ; return (PatSynSig v' args' ty' (ex_flag, ex_tyvars, prov') (univ_flag, univ_tyvars, req'), fvs) }}} ppr_sig_bndrs :: [Located RdrName] -> SDoc ppr_sig_bndrs bs = quotes (pprWithCommas ppr bs) From git at git.haskell.org Sat Nov 8 08:53:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:53:45 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Show foralls (when requested) in pattern synonym types (54a3cc6) Message-ID: <20141108085345.107DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/54a3cc6735be0bd47db2c86befc0d1cb267a58d5/ghc >--------------------------------------------------------------- commit 54a3cc6735be0bd47db2c86befc0d1cb267a58d5 Author: Dr. ERDI Gergo Date: Sun Aug 3 15:26:13 2014 +0200 Show foralls (when requested) in pattern synonym types >--------------------------------------------------------------- 54a3cc6735be0bd47db2c86befc0d1cb267a58d5 compiler/hsSyn/HsBinds.lhs | 21 ++++++--------------- compiler/iface/IfaceSyn.lhs | 9 +++++---- 2 files changed, 11 insertions(+), 19 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index f75fa2e..5a45956 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -730,24 +730,18 @@ ppr_sig (SpecSig var ty inl) = pragBrackets (pprSpec (unLoc var) (ppr ty) i ppr_sig (InlineSig var inl) = pragBrackets (ppr inl <+> pprPrefixOcc (unLoc var)) ppr_sig (SpecInstSig ty) = pragBrackets (ptext (sLit "SPECIALIZE instance") <+> ppr ty) ppr_sig (MinimalSig bf) = pragBrackets (pprMinimalSig bf) -ppr_sig (PatSynSig name arg_tys ty (_, _, prov) (_, _, req)) +ppr_sig (PatSynSig name arg_tys ty prov req) = pprPatSynSig (unLoc name) False args (ppr ty) (pprCtx prov) (pprCtx req) where args = fmap ppr arg_tys - pprCtx lctx = case unLoc lctx of - [] -> Nothing - ctx -> Just (pprHsContextNoArrow ctx) + pprCtx (flag, tvs, lctx) = pprHsForAll flag tvs lctx pprPatSynSig :: (OutputableBndr a) - => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> Maybe SDoc -> Maybe SDoc -> SDoc -pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta - = sep [ ptext (sLit "pattern") - , ptext (sLit "type") - , thetaOpt prov_theta, name_and_args - , colon - , thetaOpt req_theta, rhs_ty - ] + => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> SDoc -> SDoc -> SDoc +pprPatSynSig ident is_bidir args rhs_ty prov req + = ptext (sLit "pattern type") <+> + prov <+> name_and_args <+> colon <+> req <+> rhs_ty where name_and_args = case args of PrefixPatSyn arg_tys -> @@ -755,9 +749,6 @@ pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta InfixPatSyn left_ty right_ty -> left_ty <+> pprInfixOcc ident <+> right_ty - -- TODO: support explicit foralls - thetaOpt = maybe empty (<+> darrow) - colon = if is_bidir then dcolon else dcolon -- TODO instance OutputableBndr name => Outputable (FixitySig name) where diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 5cfe773..d228510 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -761,11 +761,13 @@ pprIfaceDecl ss (IfaceSyn { ifName = tycon, ifTyVars = tyvars pprIfaceDecl _ (IfacePatSyn { ifName = name, ifPatWrapper = wrapper, ifPatIsInfix = is_infix, - ifPatUnivTvs = _univ_tvs, ifPatExTvs = _ex_tvs, + ifPatUnivTvs = univ_tvs, ifPatExTvs = ex_tvs, ifPatProvCtxt = prov_ctxt, ifPatReqCtxt = req_ctxt, ifPatArgs = args, ifPatTy = ty }) - = pprPatSynSig name has_wrap args' ty' (pprCtxt prov_ctxt) (pprCtxt req_ctxt) + = pprPatSynSig name has_wrap args' ty' + (pprCtxt ex_tvs prov_ctxt) + (pprCtxt univ_tvs req_ctxt) where has_wrap = isJust wrapper args' = case (is_infix, args) of @@ -776,8 +778,7 @@ pprIfaceDecl _ (IfacePatSyn { ifName = name, ifPatWrapper = wrapper, ty' = pprParendIfaceType ty - pprCtxt [] = Nothing - pprCtxt ctxt = Just $ pprIfaceContext ctxt + pprCtxt tvs ctxt = pprIfaceForAllPart tvs ctxt empty pprIfaceDecl ss (IfaceId { ifName = var, ifType = ty, ifIdDetails = details, ifIdInfo = info }) From git at git.haskell.org Sat Nov 8 08:53:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:53:47 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add parser for pattern synonym type signatures. Syntax is of the form (893f1b0) Message-ID: <20141108085347.9F20D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/893f1b0565439837069a0fe9055b1c3aadd805f5/ghc >--------------------------------------------------------------- commit 893f1b0565439837069a0fe9055b1c3aadd805f5 Author: Dr. ERDI Gergo Date: Mon Jul 14 18:18:44 2014 +0800 Add parser for pattern synonym type signatures. Syntax is of the form pattern type Eq a => P a T b :: Num b => R a b which declares a pattern synonym called P, with argument types a, T, and b. >--------------------------------------------------------------- 893f1b0565439837069a0fe9055b1c3aadd805f5 compiler/hsSyn/HsBinds.lhs | 1 + compiler/hsSyn/HsTypes.lhs | 19 +++++++++++++------ compiler/parser/Parser.y | 6 ++++++ compiler/parser/RdrHsSyn.hs | 31 ++++++++++++++++++++++++++++++- 4 files changed, 50 insertions(+), 7 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index 23534cf..f75fa2e 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -743,6 +743,7 @@ pprPatSynSig :: (OutputableBndr a) => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> Maybe SDoc -> Maybe SDoc -> SDoc pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta = sep [ ptext (sLit "pattern") + , ptext (sLit "type") , thetaOpt prov_theta, name_and_args , colon , thetaOpt req_theta, rhs_ty diff --git a/compiler/hsSyn/HsTypes.lhs b/compiler/hsSyn/HsTypes.lhs index 9bd5845..db4d976 100644 --- a/compiler/hsSyn/HsTypes.lhs +++ b/compiler/hsSyn/HsTypes.lhs @@ -39,7 +39,7 @@ module HsTypes ( hsLTyVarName, hsLTyVarNames, hsLTyVarLocName, hsLTyVarLocNames, splitLHsInstDeclTy_maybe, splitHsClassTy_maybe, splitLHsClassTy_maybe, - splitHsFunType, + splitHsFunType, splitLHsForAllTyFlag, splitLHsForAllTy, splitHsAppTys, hsTyGetAppHead_maybe, mkHsAppTys, mkHsOpTy, -- Printing @@ -510,15 +510,22 @@ splitLHsInstDeclTy_maybe inst_ty = do (cls, tys) <- splitLHsClassTy_maybe ty return (tvs, cxt, cls, tys) +splitLHsForAllTyFlag + :: LHsType name + -> (HsExplicitFlag, LHsTyVarBndrs name, HsContext name, LHsType name) +splitLHsForAllTyFlag poly_ty + = case unLoc poly_ty of + HsParTy ty -> splitLHsForAllTyFlag ty + HsForAllTy flag tvs cxt ty -> (flag, tvs, unLoc cxt, ty) + _ -> (Implicit, emptyHsQTvs, [], poly_ty) + -- The type vars should have been computed by now, even if they were implicit + splitLHsForAllTy :: LHsType name -> (LHsTyVarBndrs name, HsContext name, LHsType name) splitLHsForAllTy poly_ty - = case unLoc poly_ty of - HsParTy ty -> splitLHsForAllTy ty - HsForAllTy _ tvs cxt ty -> (tvs, unLoc cxt, ty) - _ -> (emptyHsQTvs, [], poly_ty) - -- The type vars should have been computed by now, even if they were implicit + = let (_, tvs, cxt, ty) = splitLHsForAllTyFlag poly_ty + in (tvs, cxt, ty) splitHsClassTy_maybe :: HsType name -> Maybe (name, [LHsType name]) splitHsClassTy_maybe ty = fmap (\(L _ n, tys) -> (n, tys)) $ splitLHsClassTy_maybe (noLoc ty) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 1123375..ea752cf 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -879,6 +879,11 @@ where_decls :: { Located (OrdList (LHsDecl RdrName)) } : 'where' '{' decls '}' { $3 } | 'where' vocurly decls close { $3 } +pattern_synonym_sig :: { LSig RdrName } + : 'pattern' 'type' ctype '::' ctype + {% do { (name, details, ty, prov, req) <- splitPatSynSig $3 $5 + ; return $ sLL $1 $> $ PatSynSig name details ty prov req }} + vars0 :: { [Located RdrName] } : {- empty -} { [] } | varid vars0 { $1 : $2 } @@ -1490,6 +1495,7 @@ sigdecl :: { Located (OrdList (LHsDecl RdrName)) } { sLL $1 $> $ toOL [ sLL $1 $> $ SigD (TypeSig ($1 : reverse (unLoc $3)) $5) ] } | infix prec ops { sLL $1 $> $ toOL [ sLL $1 $> $ SigD (FixSig (FixitySig n (Fixity $2 (unLoc $1)))) | n <- unLoc $3 ] } + | pattern_synonym_sig { sLL $1 $> $ unitOL $ sLL $1 $> . SigD . unLoc $ $1 } | '{-# INLINE' activation qvar '#-}' { sLL $1 $> $ unitOL (sLL $1 $> $ SigD (InlineSig $3 (mkInlinePragma (getINLINE $1) $2))) } | '{-# SPECIALISE' activation qvar '::' sigtypes1 '#-}' diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs index 625c4dc..15490c3 100644 --- a/compiler/parser/RdrHsSyn.hs +++ b/compiler/parser/RdrHsSyn.hs @@ -18,7 +18,7 @@ module RdrHsSyn ( mkTyFamInst, mkFamDecl, splitCon, mkInlinePragma, - splitPatSyn, toPatSynMatchGroup, + splitPatSyn, splitPatSynSig, toPatSynMatchGroup, mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp mkTyClD, mkInstD, @@ -464,6 +464,35 @@ toPatSynMatchGroup (L _ patsyn_name) (L _ decls) = text "pattern synonym 'where' clause must bind the pattern synonym's name" <+> quotes (ppr patsyn_name) $$ ppr decl +-- Given two types like +-- Eq a => P a T b +-- and +-- Num b => R a b +-- +-- This returns +-- P as the name, +-- PrefixPatSyn [a, T, b] as the details, +-- R a b as the result type, +-- and (Eq a) and (Num b) as the provided and required thetas (respectively) +splitPatSynSig :: LHsType RdrName + -> LHsType RdrName + -> P (Located RdrName, HsPatSynDetails (LHsType RdrName), LHsType RdrName, + (HsExplicitFlag, LHsTyVarBndrs RdrName, LHsContext RdrName), + (HsExplicitFlag, LHsTyVarBndrs RdrName, LHsContext RdrName)) +splitPatSynSig lty1 lty2 = do + (name, details) <- splitCon pat_ty + details' <- case details of + PrefixCon tys -> return $ PrefixPatSyn tys + InfixCon ty1 ty2 -> return $ InfixPatSyn ty1 ty2 + RecCon{} -> parseErrorSDoc (getLoc lty1) $ + text "record syntax not supported for pattern synonym declarations:" $$ ppr lty1 + return (name, details', res_ty, (ex_flag, ex_tvs, prov'), (univ_flag, univ_tvs, req')) + where + (ex_flag, ex_tvs, prov, pat_ty) = splitLHsForAllTyFlag lty1 + (univ_flag, univ_tvs, req, res_ty) = splitLHsForAllTyFlag lty2 + prov' = L (getLoc lty1) prov + req' = L (getLoc lty2) req + mkDeprecatedGadtRecordDecl :: SrcSpan -> Located RdrName -> [ConDeclField RdrName] From git at git.haskell.org Sat Nov 8 08:53:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:53:50 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Update baseline shift/reduce conflict number (f08b36a) Message-ID: <20141108085350.361243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/f08b36aed4903b558d8e0f583713f3103ae2912e/ghc >--------------------------------------------------------------- commit f08b36aed4903b558d8e0f583713f3103ae2912e Author: Dr. ERDI Gergo Date: Wed Jul 2 19:18:43 2014 +0800 Update baseline shift/reduce conflict number >--------------------------------------------------------------- f08b36aed4903b558d8e0f583713f3103ae2912e compiler/parser/Parser.y | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 2e1b777..1123375 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -86,6 +86,12 @@ import TysWiredIn ( unitTyCon, unitDataCon, tupleTyCon, tupleCon, nilDataC {- ----------------------------------------------------------------------------- +25 June 2014 + +Conflicts: 47 shift/reduce + 1 reduce/reduce + +----------------------------------------------------------------------------- 12 October 2012 Conflicts: 43 shift/reduce From git at git.haskell.org Sat Nov 8 08:53:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:53:52 +0000 (UTC) Subject: [commit: ghc] wip/T8584: tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures (18e8882) Message-ID: <20141108085352.C4B2C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/18e8882c2b57ce208dc4206a155a6683bf04cb92/ghc >--------------------------------------------------------------- commit 18e8882c2b57ce208dc4206a155a6683bf04cb92 Author: Dr. ERDI Gergo Date: Sun Jul 27 14:10:34 2014 +0200 tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures >--------------------------------------------------------------- 18e8882c2b57ce208dc4206a155a6683bf04cb92 compiler/typecheck/TcBinds.lhs | 45 ++++++-- compiler/typecheck/TcClassDcl.lhs | 4 +- compiler/typecheck/TcPat.lhs | 23 +++- compiler/typecheck/TcPatSyn.lhs | 199 ++++++++++++++++++++++++++--------- compiler/typecheck/TcPatSyn.lhs-boot | 9 +- 5 files changed, 217 insertions(+), 63 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 18e8882c2b57ce208dc4206a155a6683bf04cb92 From git at git.haskell.org Sat Nov 8 08:53:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:53:55 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add test cases (09b8ff7) Message-ID: <20141108085355.BB6AD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/09b8ff7bbc743b07191adc3bb2ee61e3f8870f1c/ghc >--------------------------------------------------------------- commit 09b8ff7bbc743b07191adc3bb2ee61e3f8870f1c Author: Dr. ERDI Gergo Date: Sun Nov 2 14:35:49 2014 +0800 Add test cases >--------------------------------------------------------------- 09b8ff7bbc743b07191adc3bb2ee61e3f8870f1c testsuite/tests/patsyn/should_compile/T8584-1.hs | 10 ++++++++++ testsuite/tests/patsyn/should_compile/T8968-1.hs | 8 ++++++++ testsuite/tests/patsyn/should_compile/all.T | 2 ++ 3 files changed, 20 insertions(+) diff --git a/testsuite/tests/patsyn/should_compile/T8584-1.hs b/testsuite/tests/patsyn/should_compile/T8584-1.hs new file mode 100644 index 0000000..7a017c8 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8584-1.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms #-} +module ShouldCompile where + +pattern type (Eq a) => Single a :: (Show a) => [a] +-- pattern type Single a :: (Eq a, Show a) => [a] +-- pattern type Single a :: [a] +pattern Single x = [x] + +-- f :: (Show a) => [a] -> a +foobar (Single x) = x diff --git a/testsuite/tests/patsyn/should_compile/T8968-1.hs b/testsuite/tests/patsyn/should_compile/T8968-1.hs new file mode 100644 index 0000000..f4a1dc4 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8968-1.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE GADTs, KindSignatures, PatternSynonyms #-} +module ShouldCompile where + +data X :: (* -> *) -> * -> * where + Y :: f a -> X f (Maybe a) + +pattern type C a :: X Maybe (Maybe a) +pattern C x = Y (Just x) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index d851bc3..8896008 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -10,3 +10,5 @@ test('incomplete', normal, compile, ['']) test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) +test('T8968-1', normal, compile, ['']) +test('T8584-1', normal, compile, ['']) From git at git.haskell.org Sat Nov 8 08:53:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:53:58 +0000 (UTC) Subject: [commit: ghc] wip/T8584's head updated: Add test cases (09b8ff7) Message-ID: <20141108085358.59BF53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T8584' now includes: c001bde Put one-Shot info in the interface c271e32 Add GHC.Prim.oneShot 072259c Use oneShot in the definition of foldl etc. 063ae61 Update expected profiling output for scc001 1c0b736 Link to oneShot from the User's Guide 6dd218e Make Foldable's foldr1 and foldl1 defaults lazier ce03c4a Further relax T1969?s max_bytes range 49fde3b Add `Alternative` wrapper to Data.Monoid 4dbe433 Minor Haddock markup improvement to Data.Monoid 828d724 Refactor Haddock comments in Data.Bits c7fa0ba Fix lost Haddock annotation for `class Monad m` 1d6124d Tidy up pretty-printing of SrcLoc and SrcSpan 27ba070 Improve pretty-printing of type variables c8c18a1 Some refactoring around endPass and debug dumping 7251798 Simplify the generation of superclass constraints in tcInstDecl2 d153e40 Add the unfolding and inline-pragma for DFuns in DsBinds, not TcInstDcls bdbb595 White space only fd46acf Fix reduceTyFamApp_maybe 33dcb81 Simplify the API for tcInstTyVars, and make it more consistent with other similar functions 9c81db4 Rename setRole_maybe to downgradeRole_maybe 54f9188 Refactor skolemising, and newClsInst 2bfc653 Refactor the treatment of lexically-scoped type variables for instance declarations e11e1b8 Get the Untouchables level right in simplifyInfer a6e7654 Normalise the type of an inferred let-binding e840d85 Typechecker debug tracing only c64539c When reporting the context of given constraints, stop when you find one that binds a variable mentioned in the wanted 15131ec Only report "could not deduce s~t from ..." for givens that include equalities f054822 Don't filter out allegedly-irrelevant bindings with -dppr-debug 84d9ef0 Minor refactoring (no change in functionality) c1a85b3 Define ctEvLoc and ctEvCoercion, and use them 4723a0e Test Trac #9211 f861fc6 Test Trac #9708 6d1ac96 Improve error message for a handwritten Typeable instance dbbffb7 Test Trac #9747 abfbdd1 Add comments explaining ProbOneShot c639560 Test Trac #9739 7c79633 Fix the superclass-cycle detection code (Trac #9739) 66658ee Comments only 5479ae0 Testsuite error message changes 652a5ef Add flattening-notes f02c915 Make this test a bit simpler ce9d6f2 Compiler performance is much worse in for loopy givens 5770029 Simon's major commit to re-engineer the constraint solver 2f0d841 Updates to safePkg01 under Edward's guidance 09aac7d Test Trac #9081 fe178b2 Test Trac #9750 1408c8d Remove redundant "Minimal complete definition"-comments 64dc4d1 Re-center perf-numbers for T5631 6a1c05f A little refactoring of HsSplice and friends 77f8221 Temporarily disable T3064 (see #9771) 0a8e899 Remove redundant contexts from Foldable methods ac0915b Clean-up Haddock in `Data.Functor` 40b1ee4 Add `isSubsequenceOf` to Data.List (#9767) 32237f0 Fix typo in testsuite Makefile 83cf31e Fix a couple of bugs in the way info tables are generated for 64-bit platforms 4cd277b Fix bugs in debug printing 3bebf3c Fix a couple of inaccurate stack checks e6b3829 Disable an assertion; see comment 081ef2f Add a comment about stack checks d14312f Add doctest examples for Data.Either d0d9dc0 Clarify confusing notice from `make maintainer-clean` ad8457f Remove -ddump-simpl-phases flag c0a2354 Remove -ddump-core-pipeline flag 303776a Update User's Guide, cleanup DynFlags 0f930ba Move expansion of 'assert' from renamer to typechecker 030abf9 Remove unused tyConsOfDataCon e7523fe Make tyConsOfType return a (NameEnv TyCon) rather than [TyCon] f81f82e Comments and white space only 528cbd7 Give T3064 the right module name (just tidying up) 096b7e6 Switch off lazy flattening (fix Trac #3064) cb6ccad Minor refacoring and trace-message printing c945477 Allow the solved dictionaries to propagate from outside in ec38deb Wibbles to notes 203cf0e Refactor the code that prevents recursion among Coercible constraints c79cbac Re-enable T3064, which works now 91c15d6 Better error messages for new per-instance overlap flags and Safe Haskell. c96a613 Add in Incoherent Instances test for Safe Haskell. f4ead30 Warn for Safe Haskell when -XOverlappingInstances or -XIncoherentInstances turned on. abba381 Improve Applicative definitions dc5fa80 Make getTag use a bang pattern instead of seq b0e8e34 Update .gitignore to properly ignore emacs temp files 24e05f4 *Really*, really fix RTS crash due to bad coercion. 37d64a5 small parser/lexer cleanup b0d5b5b [Docs] Fixed several broken urls in user's guide f14ac52 Use bracket in `withCurrentDirectory` 832ef3f Have validate take into account stat test failures too. df3b1d4 base: Manually unlit .lhs into .hs modules a2e7bbf Preserve argument order to (==)/eq in nub and nubBy b608868 Typofix. c942688 Miscellaneous documentation for the Finder. f5996d9 Top-level comment for keepPackageImports. 474e535 In pattern synonym matchers, support unboxed continuation results (fixes #9783). 65dc594 Group PatSyn req/prov arguments together so that they're not all over the place c0af9a3 nlHsTyApps: for applying a function both on type- and term-level arguments 37a4d47 Renamer for PatSynSigs: handle type variable bindings 18e8882 tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures f08b36a Update baseline shift/reduce conflict number 893f1b0 Add parser for pattern synonym type signatures. Syntax is of the form 54a3cc6 Show foralls (when requested) in pattern synonym types 09b8ff7 Add test cases From git at git.haskell.org Sat Nov 8 08:55:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:55:41 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Fix typo in panic message (7e9b8e6) Message-ID: <20141108085541.51C9C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/7e9b8e6df209f8cc91093db7609f671f72f0ff50/ghc >--------------------------------------------------------------- commit 7e9b8e6df209f8cc91093db7609f671f72f0ff50 Author: Dr. ERDI Gergo Date: Thu Nov 6 19:38:40 2014 +0800 Fix typo in panic message >--------------------------------------------------------------- 7e9b8e6df209f8cc91093db7609f671f72f0ff50 compiler/main/TidyPgm.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs index a975fdd..b7a867d 100644 --- a/compiler/main/TidyPgm.lhs +++ b/compiler/main/TidyPgm.lhs @@ -421,7 +421,7 @@ lookup_aux_id :: TypeEnv -> Var -> Id lookup_aux_id type_env id = case lookupTypeEnv type_env (idName id) of Just (AnId id') -> id' - _other -> pprPanic "lookup_axu_id" (ppr id) + _other -> pprPanic "lookup_aux_id" (ppr id) \end{code} From git at git.haskell.org Sat Nov 8 08:55:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:55:44 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Binding things matched by an unboxed pattern synonym should require a bang (dc5f25f) Message-ID: <20141108085544.503973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/dc5f25fbec32be4cfe681eee36766dfa8840b0cc/ghc >--------------------------------------------------------------- commit dc5f25fbec32be4cfe681eee36766dfa8840b0cc Author: Dr. ERDI Gergo Date: Sat Nov 1 12:00:19 2014 +0800 Binding things matched by an unboxed pattern synonym should require a bang >--------------------------------------------------------------- dc5f25fbec32be4cfe681eee36766dfa8840b0cc testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/all.T | 1 + .../should_fail/{unboxed-wrapper-naked.hs => unboxed-bind.hs} | 6 ++++-- testsuite/tests/patsyn/should_fail/unboxed-bind.stderr | 6 ++++++ 5 files changed, 22 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index e8cfb60..97d4317 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -11,3 +11,4 @@ test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) test('T9732', normal, compile, ['']) +test('unboxed-bind-bang', normal, compile, ['']) diff --git a/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs new file mode 100644 index 0000000..a972b21 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash, BangPatterns #-} +module ShouldCompile where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let !(P arg) = x in arg diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index 3979288..96cb097 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -8,3 +8,4 @@ test('T9161-2', normal, compile_fail, ['']) test('T9705-1', normal, compile_fail, ['']) test('T9705-2', normal, compile_fail, ['']) test('unboxed-wrapper-naked', normal, compile_fail, ['']) +test('unboxed-bind', normal, compile_fail, ['']) diff --git a/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs similarity index 52% copy from testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs copy to testsuite/tests/patsyn/should_fail/unboxed-bind.hs index 6e7cc94..ef1b070 100644 --- a/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs @@ -3,6 +3,8 @@ module ShouldFail where import GHC.Base -pattern P1 = 42# +data Foo = MkFoo Int# Int# -x = P1 +pattern P x = MkFoo 0# x + +f x = let P arg = x in arg diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr new file mode 100644 index 0000000..17ca7af --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr @@ -0,0 +1,6 @@ + +unboxed-bind.hs:10:11: + Pattern bindings containing unlifted types should use an outermost bang pattern: + P arg = x + In the expression: let P arg = x in arg + In an equation for ?f?: f x = let P arg = x in arg From git at git.haskell.org Sat Nov 8 08:55:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:55:47 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Add a dummy Void# argument to pattern synonym wrapper if it has no arguments and returns an unboxed type (see #9732) (d9c15c6) Message-ID: <20141108085547.77C233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/d9c15c6b841d65eba0b30aa41f3dd549c0b69859/ghc >--------------------------------------------------------------- commit d9c15c6b841d65eba0b30aa41f3dd549c0b69859 Author: Dr. ERDI Gergo Date: Thu Nov 6 18:07:31 2014 +0800 Add a dummy Void# argument to pattern synonym wrapper if it has no arguments and returns an unboxed type (see #9732) >--------------------------------------------------------------- d9c15c6b841d65eba0b30aa41f3dd549c0b69859 compiler/typecheck/TcPatSyn.lhs | 68 +++++++++++----------- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_compile/T9732.hs | 4 ++ testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_fail/all.T | 2 +- .../patsyn/should_fail/unboxed-wrapper-naked.hs | 8 +++ .../should_fail/unboxed-wrapper-naked.stderr | 3 + testsuite/tests/patsyn/should_run/all.T | 2 + .../tests/patsyn/should_run/unboxed-wrapper.hs | 9 +++ .../should_run/unboxed-wrapper.stdout} | 0 10 files changed, 64 insertions(+), 34 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d9c15c6b841d65eba0b30aa41f3dd549c0b69859 From git at git.haskell.org Sat Nov 8 08:55:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:55:50 +0000 (UTC) Subject: [commit: ghc] wip/T9732: #stash (2e550dd) Message-ID: <20141108085550.06C063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/2e550dd4caba298e380e597a1ee55d4f4e652045/ghc >--------------------------------------------------------------- commit 2e550dd4caba298e380e597a1ee55d4f4e652045 Author: Dr. ERDI Gergo Date: Fri Nov 7 19:07:40 2014 +0800 #stash >--------------------------------------------------------------- 2e550dd4caba298e380e597a1ee55d4f4e652045 compiler/basicTypes/PatSyn.lhs | 2 +- compiler/iface/MkIface.lhs | 2 +- compiler/iface/TcIface.lhs | 3 ++- compiler/main/TidyPgm.lhs | 5 +++-- 4 files changed, 7 insertions(+), 5 deletions(-) diff --git a/compiler/basicTypes/PatSyn.lhs b/compiler/basicTypes/PatSyn.lhs index aa33efa..e862d88 100644 --- a/compiler/basicTypes/PatSyn.lhs +++ b/compiler/basicTypes/PatSyn.lhs @@ -296,7 +296,7 @@ tidyPatSynIds tidy_fn ps@(MkPatSyn { psMatcher = match_id, psWrapperWorker = mb_ = ps { psMatcher = tidy_fn match_id, psWrapperWorker = fmap tidy_ww mb_ww } where tidy_ww (wrapper, Nothing) = (tidy_fn wrapper, Nothing) - tidy_ww (wrapper, Just worker) = (wrapper, Just (tidy_fn worker)) + tidy_ww (wrapper, Just worker) = (tidy_fn wrapper, Just (tidy_fn worker)) patSynInstArgTys :: PatSyn -> [Type] -> [Type] -- Return the types of the argument patterns diff --git a/compiler/iface/MkIface.lhs b/compiler/iface/MkIface.lhs index 436356b..c11e62c 100644 --- a/compiler/iface/MkIface.lhs +++ b/compiler/iface/MkIface.lhs @@ -262,7 +262,7 @@ mkIface_ hsc_env maybe_old_fingerprint usages <- mkUsageInfo hsc_env this_mod dir_imp_mods used_names dependent_files let entities = typeEnvElts type_env - decls = pprTrace "entities" (ppr entities) $ + decls = pprTrace "entities" (ppr type_env) $ [ tyThingToIfaceDecl entity | entity <- entities, let name = getName entity, diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index 801037a..61e169c 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -281,7 +281,8 @@ typecheckIface iface -- no global envt for the current interface; instead, the knot is tied -- through the if_rec_types field of IfGblEnv ; names_w_things <- loadDecls ignore_prags (mi_decls iface) - ; let type_env = mkNameEnv names_w_things + ; let type_env = pprTrace "names_w_things" (ppr names_w_things) $ + mkNameEnv names_w_things ; writeMutVar tc_env_var type_env -- Now do those rules, instances and annotations diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs index b7a867d..bccb195 100644 --- a/compiler/main/TidyPgm.lhs +++ b/compiler/main/TidyPgm.lhs @@ -340,8 +340,9 @@ tidyProgram hsc_env (ModGuts { mg_module = mod ; (tidy_env, tidy_binds) <- tidyTopBinds hsc_env mod unfold_env tidy_occ_env trimmed_binds - ; let { final_ids = [ id | id <- bindersOfBinds tidy_binds, - isExternalName (idName id)] + ; let { final_ids = pprTrace "unfold_env" (ppr unfold_env) $ + [ id | id <- bindersOfBinds tidy_binds, + pprTrace "final_id" (ppr id) $ isExternalName (idName id)] ; type_env1 = extendTypeEnvWithIds type_env final_ids ; tidy_insts = map (tidyClsInstDFun (lookup_aux_id tidy_type_env)) insts From git at git.haskell.org Sat Nov 8 08:55:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:55:52 +0000 (UTC) Subject: [commit: ghc] wip/T9732: #WIP #STASH (1dd00bd) Message-ID: <20141108085552.95CC73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/1dd00bdd7602e9ec86a4a88eebf1821d6c02855a/ghc >--------------------------------------------------------------- commit 1dd00bdd7602e9ec86a4a88eebf1821d6c02855a Author: Dr. ERDI Gergo Date: Thu Nov 6 21:44:44 2014 +0800 #WIP #STASH >--------------------------------------------------------------- 1dd00bdd7602e9ec86a4a88eebf1821d6c02855a compiler/basicTypes/PatSyn.lhs | 29 ++++++++++---- compiler/iface/BuildTyCl.lhs | 6 +-- compiler/iface/IfaceSyn.lhs | 15 ++++--- compiler/iface/MkIface.lhs | 12 +++--- compiler/iface/TcIface.lhs | 16 ++++---- compiler/typecheck/TcBinds.lhs | 8 +++- compiler/typecheck/TcPatSyn.lhs | 89 +++++++++++++++++++++++++++-------------- 7 files changed, 113 insertions(+), 62 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1dd00bdd7602e9ec86a4a88eebf1821d6c02855a From git at git.haskell.org Sat Nov 8 08:55:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 08:55:54 +0000 (UTC) Subject: [commit: ghc] wip/T9732's head updated: #stash (2e550dd) Message-ID: <20141108085554.F1B0A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9732' now includes: c001bde Put one-Shot info in the interface c271e32 Add GHC.Prim.oneShot 072259c Use oneShot in the definition of foldl etc. 063ae61 Update expected profiling output for scc001 1c0b736 Link to oneShot from the User's Guide 6dd218e Make Foldable's foldr1 and foldl1 defaults lazier ce03c4a Further relax T1969?s max_bytes range 49fde3b Add `Alternative` wrapper to Data.Monoid 4dbe433 Minor Haddock markup improvement to Data.Monoid 828d724 Refactor Haddock comments in Data.Bits c7fa0ba Fix lost Haddock annotation for `class Monad m` 1d6124d Tidy up pretty-printing of SrcLoc and SrcSpan 27ba070 Improve pretty-printing of type variables c8c18a1 Some refactoring around endPass and debug dumping 7251798 Simplify the generation of superclass constraints in tcInstDecl2 d153e40 Add the unfolding and inline-pragma for DFuns in DsBinds, not TcInstDcls bdbb595 White space only fd46acf Fix reduceTyFamApp_maybe 33dcb81 Simplify the API for tcInstTyVars, and make it more consistent with other similar functions 9c81db4 Rename setRole_maybe to downgradeRole_maybe 54f9188 Refactor skolemising, and newClsInst 2bfc653 Refactor the treatment of lexically-scoped type variables for instance declarations e11e1b8 Get the Untouchables level right in simplifyInfer a6e7654 Normalise the type of an inferred let-binding e840d85 Typechecker debug tracing only c64539c When reporting the context of given constraints, stop when you find one that binds a variable mentioned in the wanted 15131ec Only report "could not deduce s~t from ..." for givens that include equalities f054822 Don't filter out allegedly-irrelevant bindings with -dppr-debug 84d9ef0 Minor refactoring (no change in functionality) c1a85b3 Define ctEvLoc and ctEvCoercion, and use them 4723a0e Test Trac #9211 f861fc6 Test Trac #9708 6d1ac96 Improve error message for a handwritten Typeable instance dbbffb7 Test Trac #9747 abfbdd1 Add comments explaining ProbOneShot c639560 Test Trac #9739 7c79633 Fix the superclass-cycle detection code (Trac #9739) 66658ee Comments only 5479ae0 Testsuite error message changes 652a5ef Add flattening-notes f02c915 Make this test a bit simpler ce9d6f2 Compiler performance is much worse in for loopy givens 5770029 Simon's major commit to re-engineer the constraint solver 2f0d841 Updates to safePkg01 under Edward's guidance 09aac7d Test Trac #9081 fe178b2 Test Trac #9750 1408c8d Remove redundant "Minimal complete definition"-comments 64dc4d1 Re-center perf-numbers for T5631 6a1c05f A little refactoring of HsSplice and friends 77f8221 Temporarily disable T3064 (see #9771) 0a8e899 Remove redundant contexts from Foldable methods ac0915b Clean-up Haddock in `Data.Functor` 40b1ee4 Add `isSubsequenceOf` to Data.List (#9767) 32237f0 Fix typo in testsuite Makefile 83cf31e Fix a couple of bugs in the way info tables are generated for 64-bit platforms 4cd277b Fix bugs in debug printing 3bebf3c Fix a couple of inaccurate stack checks e6b3829 Disable an assertion; see comment 081ef2f Add a comment about stack checks d14312f Add doctest examples for Data.Either d0d9dc0 Clarify confusing notice from `make maintainer-clean` ad8457f Remove -ddump-simpl-phases flag c0a2354 Remove -ddump-core-pipeline flag 303776a Update User's Guide, cleanup DynFlags 0f930ba Move expansion of 'assert' from renamer to typechecker 030abf9 Remove unused tyConsOfDataCon e7523fe Make tyConsOfType return a (NameEnv TyCon) rather than [TyCon] f81f82e Comments and white space only 528cbd7 Give T3064 the right module name (just tidying up) 096b7e6 Switch off lazy flattening (fix Trac #3064) cb6ccad Minor refacoring and trace-message printing c945477 Allow the solved dictionaries to propagate from outside in ec38deb Wibbles to notes 203cf0e Refactor the code that prevents recursion among Coercible constraints c79cbac Re-enable T3064, which works now 91c15d6 Better error messages for new per-instance overlap flags and Safe Haskell. c96a613 Add in Incoherent Instances test for Safe Haskell. f4ead30 Warn for Safe Haskell when -XOverlappingInstances or -XIncoherentInstances turned on. abba381 Improve Applicative definitions dc5fa80 Make getTag use a bang pattern instead of seq b0e8e34 Update .gitignore to properly ignore emacs temp files 24e05f4 *Really*, really fix RTS crash due to bad coercion. 37d64a5 small parser/lexer cleanup b0d5b5b [Docs] Fixed several broken urls in user's guide f14ac52 Use bracket in `withCurrentDirectory` 832ef3f Have validate take into account stat test failures too. df3b1d4 base: Manually unlit .lhs into .hs modules a2e7bbf Preserve argument order to (==)/eq in nub and nubBy b608868 Typofix. c942688 Miscellaneous documentation for the Finder. f5996d9 Top-level comment for keepPackageImports. 474e535 In pattern synonym matchers, support unboxed continuation results (fixes #9783). 65dc594 Group PatSyn req/prov arguments together so that they're not all over the place 7e9b8e6 Fix typo in panic message d9c15c6 Add a dummy Void# argument to pattern synonym wrapper if it has no arguments and returns an unboxed type (see #9732) dc5f25f Binding things matched by an unboxed pattern synonym should require a bang 1dd00bd #WIP #STASH 2e550dd #stash From git at git.haskell.org Sat Nov 8 11:12:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 11:12:20 +0000 (UTC) Subject: [commit: ghc] wip/T9281: Fix bindist failure while installing HsIntegerGmp2.h (9227636) Message-ID: <20141108111220.593CA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/92276367f948f8f84846ea54cc8f4ef1e744cce8/ghc >--------------------------------------------------------------- commit 92276367f948f8f84846ea54cc8f4ef1e744cce8 Author: Herbert Valerio Riedel Date: Sat Nov 8 11:26:34 2014 +0100 Fix bindist failure while installing HsIntegerGmp2.h >--------------------------------------------------------------- 92276367f948f8f84846ea54cc8f4ef1e744cce8 libraries/integer-gmp2/integer-gmp2.cabal | 2 ++ 1 file changed, 2 insertions(+) diff --git a/libraries/integer-gmp2/integer-gmp2.cabal b/libraries/integer-gmp2/integer-gmp2.cabal index 4464d41..2727845 100644 --- a/libraries/integer-gmp2/integer-gmp2.cabal +++ b/libraries/integer-gmp2/integer-gmp2.cabal @@ -17,6 +17,7 @@ extra-source-files: configure configure.ac gmp/config.mk.in + include/HsIntegerGmp2.h.in integer-gmp2.buildinfo.in extra-tmp-files: @@ -48,6 +49,7 @@ library ghc-options: -this-package-key integer-gmp2 -Wall cc-options: -std=c99 -Wall + include-dirs: include c-sources: cbits/wrappers.c From git at git.haskell.org Sat Nov 8 14:06:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 14:06:21 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Fix typo in panic message (170c98f) Message-ID: <20141108140621.CB0E83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/170c98f5a3c298bd3869238e3590798fbc0c9699/ghc >--------------------------------------------------------------- commit 170c98f5a3c298bd3869238e3590798fbc0c9699 Author: Dr. ERDI Gergo Date: Thu Nov 6 19:38:40 2014 +0800 Fix typo in panic message >--------------------------------------------------------------- 170c98f5a3c298bd3869238e3590798fbc0c9699 compiler/main/TidyPgm.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs index a975fdd..b7a867d 100644 --- a/compiler/main/TidyPgm.lhs +++ b/compiler/main/TidyPgm.lhs @@ -421,7 +421,7 @@ lookup_aux_id :: TypeEnv -> Var -> Id lookup_aux_id type_env id = case lookupTypeEnv type_env (idName id) of Just (AnId id') -> id' - _other -> pprPanic "lookup_axu_id" (ppr id) + _other -> pprPanic "lookup_aux_id" (ppr id) \end{code} From git at git.haskell.org Sat Nov 8 14:06:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 14:06:24 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Binding things matched by an unboxed pattern synonym should require a bang (76efaa8) Message-ID: <20141108140624.D87273A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/76efaa860c5b58985a5e6c3a8ab4e9dd8fb7dbeb/ghc >--------------------------------------------------------------- commit 76efaa860c5b58985a5e6c3a8ab4e9dd8fb7dbeb Author: Dr. ERDI Gergo Date: Sat Nov 8 16:59:47 2014 +0800 Binding things matched by an unboxed pattern synonym should require a bang >--------------------------------------------------------------- 76efaa860c5b58985a5e6c3a8ab4e9dd8fb7dbeb testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/all.T | 2 +- testsuite/tests/patsyn/should_fail/unboxed-bind.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/unboxed-bind.stderr | 6 ++++++ 5 files changed, 28 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index d851bc3..94950a1 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -10,3 +10,4 @@ test('incomplete', normal, compile, ['']) test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) +test('unboxed-bind-bang', normal, compile, ['']) diff --git a/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs new file mode 100644 index 0000000..a972b21 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash, BangPatterns #-} +module ShouldCompile where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let !(P arg) = x in arg diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index ea671dc..ee5768c 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -1,4 +1,3 @@ - test('mono', normal, compile_fail, ['']) test('unidir', normal, compile_fail, ['']) test('local', normal, compile_fail, ['']) @@ -8,3 +7,4 @@ test('T9161-1', normal, compile_fail, ['']) test('T9161-2', normal, compile_fail, ['']) test('T9705-1', normal, compile_fail, ['']) test('T9705-2', normal, compile_fail, ['']) +test('unboxed-bind', normal, compile_fail, ['']) diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.hs b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs new file mode 100644 index 0000000..ef1b070 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module ShouldFail where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let P arg = x in arg diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr new file mode 100644 index 0000000..17ca7af --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr @@ -0,0 +1,6 @@ + +unboxed-bind.hs:10:11: + Pattern bindings containing unlifted types should use an outermost bang pattern: + P arg = x + In the expression: let P arg = x in arg + In an equation for ?f?: f x = let P arg = x in arg From git at git.haskell.org Sat Nov 8 14:06:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 14:06:28 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Tests (a946c7d) Message-ID: <20141108140628.28F963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/a946c7d4ea0bf472fc8f7201b690e43654f9fe73/ghc >--------------------------------------------------------------- commit a946c7d4ea0bf472fc8f7201b690e43654f9fe73 Author: Dr. ERDI Gergo Date: Sat Nov 8 17:01:05 2014 +0800 Tests >--------------------------------------------------------------- a946c7d4ea0bf472fc8f7201b690e43654f9fe73 testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_compile/T9732.hs | 4 ++++ testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_fail/all.T | 1 + .../{unboxed-bind.hs => unboxed-wrapper-naked.hs} | 6 ++---- .../patsyn/should_fail/unboxed-wrapper-naked.stderr | 3 +++ testsuite/tests/patsyn/should_run/all.T | 2 ++ testsuite/tests/patsyn/should_run/match-unboxed.hs | 21 +++++++++++++++++++++ .../should_run/match-unboxed.stdout} | 2 ++ .../tests/patsyn/should_run/unboxed-wrapper.hs | 9 +++++++++ .../should_run/unboxed-wrapper.stdout} | 0 11 files changed, 46 insertions(+), 4 deletions(-) diff --git a/testsuite/.gitignore b/testsuite/.gitignore index 3a5d816..a07a376 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -1098,6 +1098,7 @@ mk/ghcconfig*_inplace_bin_ghc-stage2.exe.mk /tests/patsyn/should_run/ex-prov-run /tests/patsyn/should_run/match /tests/patsyn/should_run/match-unboxed +/tests/patsyn/should_run/unboxed-wrapper /tests/perf/compiler/T1969.comp.stats /tests/perf/compiler/T3064.comp.stats /tests/perf/compiler/T3294.comp.stats diff --git a/testsuite/tests/patsyn/should_compile/T9732.hs b/testsuite/tests/patsyn/should_compile/T9732.hs new file mode 100644 index 0000000..7fd0515 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T9732.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module ShouldCompile where + +pattern P = 0# diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index 94950a1..55e3b83 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -11,3 +11,4 @@ test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) test('unboxed-bind-bang', normal, compile, ['']) +test('T9732', normal, compile, ['']) diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index ee5768c..b38776e 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -8,3 +8,4 @@ test('T9161-2', normal, compile_fail, ['']) test('T9705-1', normal, compile_fail, ['']) test('T9705-2', normal, compile_fail, ['']) test('unboxed-bind', normal, compile_fail, ['']) +test('unboxed-wrapper-naked', normal, compile_fail, ['']) diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.hs b/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs similarity index 52% copy from testsuite/tests/patsyn/should_fail/unboxed-bind.hs copy to testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs index ef1b070..6e7cc94 100644 --- a/testsuite/tests/patsyn/should_fail/unboxed-bind.hs +++ b/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.hs @@ -3,8 +3,6 @@ module ShouldFail where import GHC.Base -data Foo = MkFoo Int# Int# +pattern P1 = 42# -pattern P x = MkFoo 0# x - -f x = let P arg = x in arg +x = P1 diff --git a/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.stderr b/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.stderr new file mode 100644 index 0000000..e8d8950 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-wrapper-naked.stderr @@ -0,0 +1,3 @@ + +unboxed-wrapper-naked.hs:8:1: + Top-level bindings for unlifted types aren't allowed: x = P1 diff --git a/testsuite/tests/patsyn/should_run/all.T b/testsuite/tests/patsyn/should_run/all.T index 9c3f16b..40ec3e3 100644 --- a/testsuite/tests/patsyn/should_run/all.T +++ b/testsuite/tests/patsyn/should_run/all.T @@ -4,3 +4,5 @@ test('ex-prov-run', normal, compile_and_run, ['']) test('bidir-explicit', normal, compile_and_run, ['']) test('bidir-explicit-scope', normal, compile_and_run, ['']) test('T9783', normal, compile_and_run, ['']) +test('match-unboxed', normal, compile_and_run, ['']) +test('unboxed-wrapper', normal, compile_and_run, ['']) diff --git a/testsuite/tests/patsyn/should_run/match-unboxed.hs b/testsuite/tests/patsyn/should_run/match-unboxed.hs new file mode 100644 index 0000000..ec6de0c --- /dev/null +++ b/testsuite/tests/patsyn/should_run/match-unboxed.hs @@ -0,0 +1,21 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module Main where + +import GHC.Base + +pattern P1 <- 0# +pattern P2 <- 1# + +f :: Int# -> Int# +f P1 = 42# +f P2 = 44# + +g :: Int# -> Int +g P1 = 42 +g P2 = 44 + +main = do + print $ I# (f 0#) + print $ I# (f 1#) + print $ g 0# + print $ g 1# diff --git a/testsuite/tests/array/should_run/arr020.stdout b/testsuite/tests/patsyn/should_run/match-unboxed.stdout similarity index 50% copy from testsuite/tests/array/should_run/arr020.stdout copy to testsuite/tests/patsyn/should_run/match-unboxed.stdout index daaac9e..da4a47e 100644 --- a/testsuite/tests/array/should_run/arr020.stdout +++ b/testsuite/tests/patsyn/should_run/match-unboxed.stdout @@ -1,2 +1,4 @@ 42 +44 42 +44 diff --git a/testsuite/tests/patsyn/should_run/unboxed-wrapper.hs b/testsuite/tests/patsyn/should_run/unboxed-wrapper.hs new file mode 100644 index 0000000..367c8cc --- /dev/null +++ b/testsuite/tests/patsyn/should_run/unboxed-wrapper.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module Main where + +import GHC.Base + +pattern P1 = 42# + +main = do + print $ I# P1 diff --git a/testsuite/tests/codeGen/should_run/cgrun002.stdout b/testsuite/tests/patsyn/should_run/unboxed-wrapper.stdout similarity index 100% copy from testsuite/tests/codeGen/should_run/cgrun002.stdout copy to testsuite/tests/patsyn/should_run/unboxed-wrapper.stdout From git at git.haskell.org Sat Nov 8 14:06:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 14:06:30 +0000 (UTC) Subject: [commit: ghc] wip/T9732: If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. (d16342c) Message-ID: <20141108140630.C7A693A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/d16342c0d2f6583abbd43dcd1eeaae35af8a407d/ghc >--------------------------------------------------------------- commit d16342c0d2f6583abbd43dcd1eeaae35af8a407d Author: Dr. ERDI Gergo Date: Sat Nov 8 18:38:12 2014 +0800 If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. >--------------------------------------------------------------- d16342c0d2f6583abbd43dcd1eeaae35af8a407d compiler/basicTypes/PatSyn.lhs | 50 ++++++++++++-- compiler/ghc.mk | 1 + compiler/iface/BuildTyCl.lhs | 2 +- compiler/iface/IfaceSyn.lhs | 10 +-- compiler/iface/MkIface.lhs | 4 +- compiler/iface/TcIface.lhs | 62 +++++++++++++++--- compiler/typecheck/TcBinds.lhs | 8 +-- compiler/typecheck/TcPatSyn.lhs | 122 ++++++++++++++++++----------------- compiler/typecheck/TcPatSyn.lhs-boot | 4 +- 9 files changed, 176 insertions(+), 87 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d16342c0d2f6583abbd43dcd1eeaae35af8a407d From git at git.haskell.org Sat Nov 8 14:16:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 14:16:01 +0000 (UTC) Subject: [commit: ghc] master: Unlit overlooked GHC/Conc/Sync.lhs (8e66365) Message-ID: <20141108141601.09BB53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8e66365b0046f78d4f3b24f2ba39171c633568fa/ghc >--------------------------------------------------------------- commit 8e66365b0046f78d4f3b24f2ba39171c633568fa Author: Herbert Valerio Riedel Date: Sat Nov 8 15:13:59 2014 +0100 Unlit overlooked GHC/Conc/Sync.lhs This is a follow-up commit to df3b1d43cc862fe03f0724a9c0ac9e7cecdf4605 >--------------------------------------------------------------- 8e66365b0046f78d4f3b24f2ba39171c633568fa libraries/base/GHC/Conc/{Sync.lhs => Sync.hs} | 45 +++++++++------------------ 1 file changed, 14 insertions(+), 31 deletions(-) diff --git a/libraries/base/GHC/Conc/Sync.lhs b/libraries/base/GHC/Conc/Sync.hs similarity index 95% rename from libraries/base/GHC/Conc/Sync.lhs rename to libraries/base/GHC/Conc/Sync.hs index da9f376..6d2e772 100644 --- a/libraries/base/GHC/Conc/Sync.lhs +++ b/libraries/base/GHC/Conc/Sync.hs @@ -1,4 +1,3 @@ -\begin{code} {-# LANGUAGE Unsafe #-} {-# LANGUAGE CPP , NoImplicitPrelude @@ -118,15 +117,11 @@ import GHC.Show ( Show(..), showString ) import GHC.Weak infixr 0 `par`, `pseq` -\end{code} -%************************************************************************ -%* * -\subsection{@ThreadId@, @par@, and @fork@} -%* * -%************************************************************************ +----------------------------------------------------------------------------- +-- 'ThreadId', 'par', and 'fork' +----------------------------------------------------------------------------- -\begin{code} data ThreadId = ThreadId ThreadId# deriving( Typeable ) -- ToDo: data ThreadId = ThreadId (Weak ThreadId#) -- But since ThreadId# is unlifted, the Weak type must use open @@ -528,19 +523,15 @@ mkWeakThreadId :: ThreadId -> IO (Weak ThreadId) mkWeakThreadId t@(ThreadId t#) = IO $ \s -> case mkWeakNoFinalizer# t# t s of (# s1, w #) -> (# s1, Weak w #) -\end{code} -%************************************************************************ -%* * -\subsection[stm]{Transactional heap operations} -%* * -%************************************************************************ +----------------------------------------------------------------------------- +-- Transactional heap operations +----------------------------------------------------------------------------- -TVars are shared memory locations which support atomic memory -transactions. +-- TVars are shared memory locations which support atomic memory +-- transactions. -\begin{code} -- |A monad supporting atomic memory transactions. newtype STM a = STM (State# RealWorld -> (# State# RealWorld, a #)) deriving Typeable @@ -733,11 +724,10 @@ writeTVar (TVar tvar#) val = STM $ \s1# -> case writeTVar# tvar# val s1# of s2# -> (# s2#, () #) -\end{code} - -MVar utilities +----------------------------------------------------------------------------- +-- MVar utilities +----------------------------------------------------------------------------- -\begin{code} withMVar :: MVar a -> (a -> IO b) -> IO b withMVar m io = mask $ \restore -> do @@ -755,15 +745,10 @@ modifyMVar_ m io = (\e -> do putMVar m a; throw e) putMVar m a' return () -\end{code} - -%************************************************************************ -%* * -\subsection{Thread waiting} -%* * -%************************************************************************ -\begin{code} +----------------------------------------------------------------------------- +-- Thread waiting +----------------------------------------------------------------------------- -- Machinery needed to ensureb that we only have one copy of certain -- CAFs in this module even when the base package is present twice, as @@ -824,5 +809,3 @@ setUncaughtExceptionHandler = writeIORef uncaughtExceptionHandler getUncaughtExceptionHandler :: IO (SomeException -> IO ()) getUncaughtExceptionHandler = readIORef uncaughtExceptionHandler - -\end{code} From git at git.haskell.org Sat Nov 8 20:43:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Nov 2014 20:43:39 +0000 (UTC) Subject: [commit: ghc] master: Use (.) and id from Base in Control.Applicative (e2769df) Message-ID: <20141108204339.570D63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e2769df912672d39346727616750ba8066e489f9/ghc >--------------------------------------------------------------- commit e2769df912672d39346727616750ba8066e489f9 Author: David Feuer Date: Sat Nov 8 21:43:27 2014 +0100 Use (.) and id from Base in Control.Applicative Control.Applicative previously imported `(.)` and `id` from `Control.Arrow`, but then only applied them to functions. Reviewed By: ekmett, hvr Differential Revision: https://phabricator.haskell.org/D462 >--------------------------------------------------------------- e2769df912672d39346727616750ba8066e489f9 libraries/base/Control/Applicative.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/base/Control/Applicative.hs b/libraries/base/Control/Applicative.hs index cc87343..924ad5e 100644 --- a/libraries/base/Control/Applicative.hs +++ b/libraries/base/Control/Applicative.hs @@ -49,7 +49,7 @@ module Control.Applicative ( optional, ) where -import Control.Category +import Control.Category hiding ((.), id) import Control.Arrow import Data.Maybe import Data.Tuple @@ -58,7 +58,7 @@ import Data.Ord import Data.Foldable (Foldable(..)) import Data.Functor ((<$>)) -import GHC.Base hiding ((.), id) +import GHC.Base import GHC.Generics import GHC.List (repeat, zipWith) import GHC.Read (Read) From git at git.haskell.org Sun Nov 9 20:52:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Nov 2014 20:52:08 +0000 (UTC) Subject: [commit: ghc] wip/T9281: DRAFT: Implement new integer-gmp2 from scratch (re #9281) (46f362a) Message-ID: <20141109205208.8E7C43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/46f362a5f599f34fe5e8ceae8f4023ee249deaec/ghc >--------------------------------------------------------------- commit 46f362a5f599f34fe5e8ceae8f4023ee249deaec Author: Herbert Valerio Riedel Date: Sun Oct 19 20:37:40 2014 +0200 DRAFT: Implement new integer-gmp2 from scratch (re #9281) Summary: (preliminary commit message) This is done as a separate integer-gmp2 backend library because it turned out to become a complete rewrite from scratch. This has been tested only on Linux/x86_64 so far. The code has been written while taking into account Linux/i386 and "64-bit" Windows, but will probably need some tweaking to get right. Also, we don't do any autoconf stuff anymore, and rely on Cabal's "extra-libraries: gmp" to do the right thing (which probably won't work everywhere) Moreover, this is currently a big huge patch, which could easily be split into 2 or 3 commits. Test Plan: nofib & testsuite Reviewers: #ghc, austin Subscribers: ekmett, simonpj, ezyang, rwbarton, phaskell, simonmar, relrod, carter Differential Revision: https://phabricator.haskell.org/D82 GHC Trac Issues: #9281 >--------------------------------------------------------------- 46f362a5f599f34fe5e8ceae8f4023ee249deaec compiler/coreSyn/CorePrep.lhs | 3 +- compiler/ghc.mk | 8 +- compiler/prelude/PrelNames.lhs | 2 + ghc.mk | 10 +- libraries/base/GHC/Real.hs | 6 + libraries/base/base.cabal | 19 +- libraries/integer-gmp2/.gitignore | 13 + libraries/integer-gmp2/LICENSE | 30 + libraries/{base => integer-gmp2}/Setup.hs | 0 libraries/{integer-gmp => integer-gmp2}/aclocal.m4 | 0 libraries/integer-gmp2/cbits/wrappers.c | 281 ++++ .../integer-gmp2/config.guess | 0 config.sub => libraries/integer-gmp2/config.sub | 0 .../{integer-gmp => integer-gmp2}/configure.ac | 4 +- .../{integer-gmp => integer-gmp2}/gmp/config.mk.in | 0 libraries/{integer-gmp => integer-gmp2}/gmp/ghc.mk | 76 +- libraries/integer-gmp2/gmp/gmpsrc.patch | 37 + {libffi => libraries/integer-gmp2/gmp}/ln | 0 libraries/integer-gmp2/include/HsIntegerGmp2.h.in | 6 + .../integer-gmp2.buildinfo.in} | 0 libraries/integer-gmp2/integer-gmp2.cabal | 62 + .../src/GHC/Integer.hs} | 49 +- .../integer-gmp2/src/GHC/Integer/GMP2/Internals.hs | 126 ++ .../integer-gmp2/src/GHC/Integer/Logarithms.hs | 73 + .../src/GHC/Integer/Logarithms/Internals.hs | 118 ++ libraries/integer-gmp2/src/GHC/Integer/Type.hs | 1663 ++++++++++++++++++++ mk/config.mk.in | 2 +- rules/foreachLibrary.mk | 2 + testsuite/driver/testlib.py | 2 +- testsuite/tests/ghci/scripts/ghci025.stdout | 6 +- testsuite/tests/perf/should_run/all.T | 3 +- testsuite/tests/perf/space_leaks/all.T | 4 +- testsuite/tests/rename/should_compile/T3103/test.T | 2 +- testsuite/tests/rts/Makefile | 4 +- testsuite/tests/safeHaskell/check/pkg01/all.T | 8 +- testsuite/tests/simplCore/should_run/T5603.hs | 7 +- testsuite/tests/typecheck/should_fail/T5095.stderr | 4 +- .../tests/typecheck/should_fail/tcfail072.stderr | 2 +- 38 files changed, 2548 insertions(+), 84 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 46f362a5f599f34fe5e8ceae8f4023ee249deaec From git at git.haskell.org Sun Nov 9 20:52:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Nov 2014 20:52:11 +0000 (UTC) Subject: [commit: ghc] wip/T9281: Fix bindist failure while installing HsIntegerGmp2.h (9500487) Message-ID: <20141109205211.3D4683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/9500487e8a48f666d9c5d2bea09e50447648393c/ghc >--------------------------------------------------------------- commit 9500487e8a48f666d9c5d2bea09e50447648393c Author: Herbert Valerio Riedel Date: Sat Nov 8 11:26:34 2014 +0100 Fix bindist failure while installing HsIntegerGmp2.h >--------------------------------------------------------------- 9500487e8a48f666d9c5d2bea09e50447648393c libraries/integer-gmp2/integer-gmp2.cabal | 2 ++ 1 file changed, 2 insertions(+) diff --git a/libraries/integer-gmp2/integer-gmp2.cabal b/libraries/integer-gmp2/integer-gmp2.cabal index 4464d41..2727845 100644 --- a/libraries/integer-gmp2/integer-gmp2.cabal +++ b/libraries/integer-gmp2/integer-gmp2.cabal @@ -17,6 +17,7 @@ extra-source-files: configure configure.ac gmp/config.mk.in + include/HsIntegerGmp2.h.in integer-gmp2.buildinfo.in extra-tmp-files: @@ -48,6 +49,7 @@ library ghc-options: -this-package-key integer-gmp2 -Wall cc-options: -std=c99 -Wall + include-dirs: include c-sources: cbits/wrappers.c From git at git.haskell.org Sun Nov 9 20:52:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Nov 2014 20:52:13 +0000 (UTC) Subject: [commit: ghc] wip/T9281: Minor fixup in libraries/integer-gmp2/integer-gmp2.buildinfo.in (58b9870) Message-ID: <20141109205213.CD1493A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/58b98708b20f0d89b9cabed4fe729cb4e2ed3f5e/ghc >--------------------------------------------------------------- commit 58b98708b20f0d89b9cabed4fe729cb4e2ed3f5e Author: Herbert Valerio Riedel Date: Sat Nov 8 09:48:39 2014 +0100 Minor fixup in libraries/integer-gmp2/integer-gmp2.buildinfo.in >--------------------------------------------------------------- 58b98708b20f0d89b9cabed4fe729cb4e2ed3f5e ghc.mk | 1 + libraries/integer-gmp2/integer-gmp2.buildinfo.in | 2 +- 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/ghc.mk b/ghc.mk index 40d782f..1bbfa90 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1220,6 +1220,7 @@ sdist_%: CLEAN_FILES += libraries/bootstrapping.conf CLEAN_FILES += libraries/integer-gmp/cbits/GmpDerivedConstants.h CLEAN_FILES += libraries/integer-gmp/include/HsIntegerGmp.h +CLEAN_FILES += libraries/integer-gmp2/include/HsIntegerGmp2.h CLEAN_FILES += libraries/base/include/EventConfig.h CLEAN_FILES += mk/config.mk.old CLEAN_FILES += mk/project.mk.old diff --git a/libraries/integer-gmp2/integer-gmp2.buildinfo.in b/libraries/integer-gmp2/integer-gmp2.buildinfo.in index 9b2bad9..8f7769d 100644 --- a/libraries/integer-gmp2/integer-gmp2.buildinfo.in +++ b/libraries/integer-gmp2/integer-gmp2.buildinfo.in @@ -2,4 +2,4 @@ include-dirs: @GMP_INCLUDE_DIRS@ extra-lib-dirs: @GMP_LIB_DIRS@ extra-libraries: @GMP_LIBS@ frameworks: @GMP_FRAMEWORK@ -install-includes: HsIntegerGmp.h \ No newline at end of file +install-includes: HsIntegerGmp2.h From git at git.haskell.org Sun Nov 9 20:52:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Nov 2014 20:52:16 +0000 (UTC) Subject: [commit: ghc] wip/T9281: Rename GHC.Integer.GMP2.Internals to *.GMP.* (82d9041) Message-ID: <20141109205216.9E1D03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/82d904171775a0862057502138725b0e98a76d7c/ghc >--------------------------------------------------------------- commit 82d904171775a0862057502138725b0e98a76d7c Author: Herbert Valerio Riedel Date: Sun Nov 9 21:35:47 2014 +0100 Rename GHC.Integer.GMP2.Internals to *.GMP.* >--------------------------------------------------------------- 82d904171775a0862057502138725b0e98a76d7c libraries/integer-gmp2/integer-gmp2.cabal | 2 +- libraries/integer-gmp2/src/GHC/Integer.hs | 2 +- libraries/integer-gmp2/src/GHC/Integer/{GMP2 => GMP}/Internals.hs | 4 ++-- 3 files changed, 4 insertions(+), 4 deletions(-) diff --git a/libraries/integer-gmp2/integer-gmp2.cabal b/libraries/integer-gmp2/integer-gmp2.cabal index 2727845..950cbff 100644 --- a/libraries/integer-gmp2/integer-gmp2.cabal +++ b/libraries/integer-gmp2/integer-gmp2.cabal @@ -58,7 +58,7 @@ library GHC.Integer.Logarithms GHC.Integer.Logarithms.Internals - GHC.Integer.GMP2.Internals + GHC.Integer.GMP.Internals other-modules: GHC.Integer.Type diff --git a/libraries/integer-gmp2/src/GHC/Integer.hs b/libraries/integer-gmp2/src/GHC/Integer.hs index 2335a5d..c9675f5 100644 --- a/libraries/integer-gmp2/src/GHC/Integer.hs +++ b/libraries/integer-gmp2/src/GHC/Integer.hs @@ -16,7 +16,7 @@ -- The 'Integer' type. -- -- This module exposes the /portable/ 'Integer' API. See --- "GHC.Integer.GMP2.Internals" for the @integer-gmp2 at -specific internal +-- "GHC.Integer.GMP.Internals" for the @integer-gmp2 at -specific internal -- representation of 'Integer' as well as optimized GMP-specific -- operations. diff --git a/libraries/integer-gmp2/src/GHC/Integer/GMP2/Internals.hs b/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs similarity index 97% rename from libraries/integer-gmp2/src/GHC/Integer/GMP2/Internals.hs rename to libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs index 6e4a25f..e4169e7 100644 --- a/libraries/integer-gmp2/src/GHC/Integer/GMP2/Internals.hs +++ b/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs @@ -12,7 +12,7 @@ #include "MachDeps.h" -- | --- Module : GHC.Integer.GMP2.Internals +-- Module : GHC.Integer.GMP.Internals -- Copyright : (c) Herbert Valerio Riedel 2014 -- License : BSD3 -- @@ -31,7 +31,7 @@ -- See also -- . -module GHC.Integer.GMP2.Internals +module GHC.Integer.GMP.Internals ( -- * The 'Integer' type Integer(..) , isValidInteger# From git at git.haskell.org Sun Nov 9 20:52:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Nov 2014 20:52:19 +0000 (UTC) Subject: [commit: ghc] wip/T9281: Remove obsolete references to mkGmpDerivedConstants (3df3a0b) Message-ID: <20141109205219.437F63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/3df3a0b23b61ba06759e42bb92079cd35468c1af/ghc >--------------------------------------------------------------- commit 3df3a0b23b61ba06759e42bb92079cd35468c1af Author: Herbert Valerio Riedel Date: Sun Nov 9 21:37:16 2014 +0100 Remove obsolete references to mkGmpDerivedConstants >--------------------------------------------------------------- 3df3a0b23b61ba06759e42bb92079cd35468c1af libraries/integer-gmp2/gmp/ghc.mk | 6 ------ 1 file changed, 6 deletions(-) diff --git a/libraries/integer-gmp2/gmp/ghc.mk b/libraries/integer-gmp2/gmp/ghc.mk index a7a39d0..9790b53 100644 --- a/libraries/integer-gmp2/gmp/ghc.mk +++ b/libraries/integer-gmp2/gmp/ghc.mk @@ -49,9 +49,6 @@ ifeq "$(findstring clean,$(MAKECMDGOALS))" "" include libraries/integer-gmp2/gmp/config.mk endif -libraries/integer-gmp2_dist-install_EXTRA_CC_OPTS += -Ilibraries/integer-gmp2/mkGmpDerivedConstants/dist -libraries/integer-gmp2_dist-install_EXTRA_HC_OPTS += -Ilibraries/integer-gmp2/mkGmpDerivedConstants/dist - gmp_CC_OPTS += $(addprefix -I,$(GMP_INCLUDE_DIRS)) gmp_CC_OPTS += $(addprefix -L,$(GMP_LIB_DIRS)) @@ -78,14 +75,11 @@ HaveFrameworkGMP = NO endif endif -$(libraries/integer-gmp2_dist-install_depfile_c_asm): $$(GmpDerivedConstants_HEADER) - ifneq "$(HaveLibGmp)" "YES" ifneq "$(HaveFrameworkGMP)" "YES" $(libraries/integer-gmp2_dist-install_depfile_c_asm): libraries/integer-gmp2/gmp/gmp.h gmp_CC_OPTS += -Ilibraries/integer-gmp2/gmp -gmp_CC_OPTS += -Ilibraries/integer-gmp2/mkGmpDerivedConstants/dist libraries/integer-gmp2_dist-install_EXTRA_OBJS += libraries/integer-gmp2/gmp/objs/*.o From git at git.haskell.org Sun Nov 9 20:52:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Nov 2014 20:52:21 +0000 (UTC) Subject: [commit: ghc] wip/T9281: Rename constructor `SI#` to `S#` (61cf3b5) Message-ID: <20141109205221.EBF613A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/61cf3b5ac1813049458a9d0cd6d88524d6bd486d/ghc >--------------------------------------------------------------- commit 61cf3b5ac1813049458a9d0cd6d88524d6bd486d Author: Herbert Valerio Riedel Date: Sun Nov 9 21:51:21 2014 +0100 Rename constructor `SI#` to `S#` >--------------------------------------------------------------- 61cf3b5ac1813049458a9d0cd6d88524d6bd486d compiler/prelude/PrelNames.lhs | 2 +- .../integer-gmp2/src/GHC/Integer/Logarithms.hs | 4 +- .../src/GHC/Integer/Logarithms/Internals.hs | 4 +- libraries/integer-gmp2/src/GHC/Integer/Type.hs | 286 ++++++++++----------- testsuite/tests/ghci/scripts/ghci025.stdout | 2 +- testsuite/tests/simplCore/should_run/T5603.hs | 2 +- 6 files changed, 150 insertions(+), 150 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 61cf3b5ac1813049458a9d0cd6d88524d6bd486d From git at git.haskell.org Sun Nov 9 20:52:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Nov 2014 20:52:24 +0000 (UTC) Subject: [commit: ghc] wip/T9281's head updated: Rename constructor `SI#` to `S#` (61cf3b5) Message-ID: <20141109205224.501183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9281' now includes: b608868 Typofix. c942688 Miscellaneous documentation for the Finder. f5996d9 Top-level comment for keepPackageImports. 474e535 In pattern synonym matchers, support unboxed continuation results (fixes #9783). 65dc594 Group PatSyn req/prov arguments together so that they're not all over the place 8e66365 Unlit overlooked GHC/Conc/Sync.lhs e2769df Use (.) and id from Base in Control.Applicative 46f362a DRAFT: Implement new integer-gmp2 from scratch (re #9281) 58b9870 Minor fixup in libraries/integer-gmp2/integer-gmp2.buildinfo.in 9500487 Fix bindist failure while installing HsIntegerGmp2.h 82d9041 Rename GHC.Integer.GMP2.Internals to *.GMP.* 3df3a0b Remove obsolete references to mkGmpDerivedConstants 61cf3b5 Rename constructor `SI#` to `S#` From git at git.haskell.org Sun Nov 9 20:55:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Nov 2014 20:55:01 +0000 (UTC) Subject: [commit: ghc] wip/T9281: Disable T4801/peak_megabytes_allocated (83df1f3) Message-ID: <20141109205501.854533A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/83df1f371f33c03166411d984594871ab8082c0f/ghc >--------------------------------------------------------------- commit 83df1f371f33c03166411d984594871ab8082c0f Author: Herbert Valerio Riedel Date: Sun Nov 9 21:54:43 2014 +0100 Disable T4801/peak_megabytes_allocated This test seems to close to a tipping point >--------------------------------------------------------------- 83df1f371f33c03166411d984594871ab8082c0f testsuite/tests/perf/compiler/all.T | 34 ++++++++++++++++++---------------- 1 file changed, 18 insertions(+), 16 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index f6f52d7..fa8d62a 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -167,22 +167,24 @@ test('T3294', test('T4801', [ # expect_broken(5224), # temporarily unbroken (#5227) - compiler_stats_num_field('peak_megabytes_allocated',# Note [residency] - [(platform('x86_64-apple-darwin'), 70, 1), - # expected value: 58 (amd64/OS X) - # 13/01/2014 - 70 - (wordsize(32), 30, 20), - (wordsize(64), 48, 20)]), - # prev: 50 (amd64/Linux) - # 19/10/2012: 64 (amd64/Linux) - # (^ REASON UNKNOWN!) - # 12/11/2012: 49 (amd64/Linux) - # (^ REASON UNKNOWN!) - # 28/8/13: 60 (amd64/Linux) - # (^ REASON UNKNOWN!) - # 2014-09-10: 55 post-AMP-cleanup - # 2014-10-08: 62 (jumps between 55 and 71 observed -- GC tipping point?) - # 2014-10-13: 48 stricter seqDmdType +################################### +# deactivated for now, as this metric became to volatile recently +# compiler_stats_num_field('peak_megabytes_allocated',# Note [residency] +# [(platform('x86_64-apple-darwin'), 70, 1), +# # expected value: 58 (amd64/OS X) +# # 13/01/2014 - 70 +# (wordsize(32), 30, 20), +# (wordsize(64), 48, 20)]), +# # prev: 50 (amd64/Linux) +# # 19/10/2012: 64 (amd64/Linux) +# # (^ REASON UNKNOWN!) +# # 12/11/2012: 49 (amd64/Linux) +# # (^ REASON UNKNOWN!) +# # 28/8/13: 60 (amd64/Linux) +# # (^ REASON UNKNOWN!) +# # 2014-09-10: 55 post-AMP-cleanup +# # 2014-10-08: 62 (jumps between 55 and 71 observed -- GC tipping point?) +# # 2014-10-13: 48 stricter seqDmdType compiler_stats_num_field('bytes allocated', [(platform('x86_64-apple-darwin'), 464872776, 5), From git at git.haskell.org Sun Nov 9 20:58:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Nov 2014 20:58:46 +0000 (UTC) Subject: [commit: ghc] wip/T9281: Remove obsolete references to mkGmpDerivedConstants (4bfc41f) Message-ID: <20141109205846.A50053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/4bfc41fe7fd4bde7feda224471e8bdd0d13aac32/ghc >--------------------------------------------------------------- commit 4bfc41fe7fd4bde7feda224471e8bdd0d13aac32 Author: Herbert Valerio Riedel Date: Sun Nov 9 21:37:16 2014 +0100 Remove obsolete references to mkGmpDerivedConstants >--------------------------------------------------------------- 4bfc41fe7fd4bde7feda224471e8bdd0d13aac32 libraries/integer-gmp2/gmp/ghc.mk | 6 ------ 1 file changed, 6 deletions(-) diff --git a/libraries/integer-gmp2/gmp/ghc.mk b/libraries/integer-gmp2/gmp/ghc.mk index a7a39d0..9790b53 100644 --- a/libraries/integer-gmp2/gmp/ghc.mk +++ b/libraries/integer-gmp2/gmp/ghc.mk @@ -49,9 +49,6 @@ ifeq "$(findstring clean,$(MAKECMDGOALS))" "" include libraries/integer-gmp2/gmp/config.mk endif -libraries/integer-gmp2_dist-install_EXTRA_CC_OPTS += -Ilibraries/integer-gmp2/mkGmpDerivedConstants/dist -libraries/integer-gmp2_dist-install_EXTRA_HC_OPTS += -Ilibraries/integer-gmp2/mkGmpDerivedConstants/dist - gmp_CC_OPTS += $(addprefix -I,$(GMP_INCLUDE_DIRS)) gmp_CC_OPTS += $(addprefix -L,$(GMP_LIB_DIRS)) @@ -78,14 +75,11 @@ HaveFrameworkGMP = NO endif endif -$(libraries/integer-gmp2_dist-install_depfile_c_asm): $$(GmpDerivedConstants_HEADER) - ifneq "$(HaveLibGmp)" "YES" ifneq "$(HaveFrameworkGMP)" "YES" $(libraries/integer-gmp2_dist-install_depfile_c_asm): libraries/integer-gmp2/gmp/gmp.h gmp_CC_OPTS += -Ilibraries/integer-gmp2/gmp -gmp_CC_OPTS += -Ilibraries/integer-gmp2/mkGmpDerivedConstants/dist libraries/integer-gmp2_dist-install_EXTRA_OBJS += libraries/integer-gmp2/gmp/objs/*.o From git at git.haskell.org Sun Nov 9 20:58:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Nov 2014 20:58:49 +0000 (UTC) Subject: [commit: ghc] wip/T9281: Rename GHC.Integer.GMP2.Internals to *.GMP.* (40c2037) Message-ID: <20141109205849.8A9513A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/40c203746cec3cf17d5af00b8f0b9b57cece9bb4/ghc >--------------------------------------------------------------- commit 40c203746cec3cf17d5af00b8f0b9b57cece9bb4 Author: Herbert Valerio Riedel Date: Sun Nov 9 21:35:47 2014 +0100 Rename GHC.Integer.GMP2.Internals to *.GMP.* >--------------------------------------------------------------- 40c203746cec3cf17d5af00b8f0b9b57cece9bb4 libraries/base/GHC/Real.hs | 4 +--- libraries/integer-gmp2/integer-gmp2.cabal | 2 +- libraries/integer-gmp2/src/GHC/Integer.hs | 2 +- libraries/integer-gmp2/src/GHC/Integer/{GMP2 => GMP}/Internals.hs | 4 ++-- testsuite/tests/simplCore/should_run/T5603.hs | 2 +- 5 files changed, 6 insertions(+), 8 deletions(-) diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs index efdb74d..2b5f6cc 100644 --- a/libraries/base/GHC/Real.hs +++ b/libraries/base/GHC/Real.hs @@ -27,10 +27,8 @@ import GHC.Show import {-# SOURCE #-} GHC.Exception( divZeroException, overflowException, ratioZeroDenomException ) #ifdef OPTIMISE_INTEGER_GCD_LCM -# if defined(MIN_VERSION_integer_gmp) +# if defined(MIN_VERSION_integer_gmp) || defined(MIN_VERSION_integer_gmp2) import GHC.Integer.GMP.Internals -# elif defined(MIN_VERSION_integer_gmp2) -import GHC.Integer.GMP2.Internals # else # error unsupported OPTIMISE_INTEGER_GCD_LCM configuration # endif diff --git a/libraries/integer-gmp2/integer-gmp2.cabal b/libraries/integer-gmp2/integer-gmp2.cabal index 2727845..950cbff 100644 --- a/libraries/integer-gmp2/integer-gmp2.cabal +++ b/libraries/integer-gmp2/integer-gmp2.cabal @@ -58,7 +58,7 @@ library GHC.Integer.Logarithms GHC.Integer.Logarithms.Internals - GHC.Integer.GMP2.Internals + GHC.Integer.GMP.Internals other-modules: GHC.Integer.Type diff --git a/libraries/integer-gmp2/src/GHC/Integer.hs b/libraries/integer-gmp2/src/GHC/Integer.hs index 2335a5d..c9675f5 100644 --- a/libraries/integer-gmp2/src/GHC/Integer.hs +++ b/libraries/integer-gmp2/src/GHC/Integer.hs @@ -16,7 +16,7 @@ -- The 'Integer' type. -- -- This module exposes the /portable/ 'Integer' API. See --- "GHC.Integer.GMP2.Internals" for the @integer-gmp2 at -specific internal +-- "GHC.Integer.GMP.Internals" for the @integer-gmp2 at -specific internal -- representation of 'Integer' as well as optimized GMP-specific -- operations. diff --git a/libraries/integer-gmp2/src/GHC/Integer/GMP2/Internals.hs b/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs similarity index 97% rename from libraries/integer-gmp2/src/GHC/Integer/GMP2/Internals.hs rename to libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs index 6e4a25f..e4169e7 100644 --- a/libraries/integer-gmp2/src/GHC/Integer/GMP2/Internals.hs +++ b/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs @@ -12,7 +12,7 @@ #include "MachDeps.h" -- | --- Module : GHC.Integer.GMP2.Internals +-- Module : GHC.Integer.GMP.Internals -- Copyright : (c) Herbert Valerio Riedel 2014 -- License : BSD3 -- @@ -31,7 +31,7 @@ -- See also -- . -module GHC.Integer.GMP2.Internals +module GHC.Integer.GMP.Internals ( -- * The 'Integer' type Integer(..) , isValidInteger# diff --git a/testsuite/tests/simplCore/should_run/T5603.hs b/testsuite/tests/simplCore/should_run/T5603.hs index 846a33f..0d3d25f 100644 --- a/testsuite/tests/simplCore/should_run/T5603.hs +++ b/testsuite/tests/simplCore/should_run/T5603.hs @@ -4,7 +4,7 @@ module Main (main) where import GHC.Base -import GHC.Integer.GMP2.Internals +import GHC.Integer.GMP.Internals main :: IO () main = (encodeDouble 0 :: Double) `seq` return () From git at git.haskell.org Sun Nov 9 20:58:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Nov 2014 20:58:52 +0000 (UTC) Subject: [commit: ghc] wip/T9281: Rename constructor `SI#` to `S#` (11e6008) Message-ID: <20141109205852.428773A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/11e6008daae04401da34a76cbe59d00f9aa1f0e6/ghc >--------------------------------------------------------------- commit 11e6008daae04401da34a76cbe59d00f9aa1f0e6 Author: Herbert Valerio Riedel Date: Sun Nov 9 21:51:21 2014 +0100 Rename constructor `SI#` to `S#` >--------------------------------------------------------------- 11e6008daae04401da34a76cbe59d00f9aa1f0e6 compiler/prelude/PrelNames.lhs | 2 +- .../integer-gmp2/src/GHC/Integer/Logarithms.hs | 4 +- .../src/GHC/Integer/Logarithms/Internals.hs | 4 +- libraries/integer-gmp2/src/GHC/Integer/Type.hs | 286 ++++++++++----------- testsuite/tests/ghci/scripts/ghci025.stdout | 2 +- testsuite/tests/simplCore/should_run/T5603.hs | 2 +- 6 files changed, 150 insertions(+), 150 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 11e6008daae04401da34a76cbe59d00f9aa1f0e6 From git at git.haskell.org Sun Nov 9 20:58:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Nov 2014 20:58:54 +0000 (UTC) Subject: [commit: ghc] wip/T9281: Disable T4801/peak_megabytes_allocated (ce50db6) Message-ID: <20141109205854.D9C483A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/ce50db6dd46e84f70cd31df360d28be783b7ec81/ghc >--------------------------------------------------------------- commit ce50db6dd46e84f70cd31df360d28be783b7ec81 Author: Herbert Valerio Riedel Date: Sun Nov 9 21:54:43 2014 +0100 Disable T4801/peak_megabytes_allocated This test seems to close to a tipping point >--------------------------------------------------------------- ce50db6dd46e84f70cd31df360d28be783b7ec81 testsuite/tests/perf/compiler/all.T | 34 ++++++++++++++++++---------------- 1 file changed, 18 insertions(+), 16 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index f6f52d7..fa8d62a 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -167,22 +167,24 @@ test('T3294', test('T4801', [ # expect_broken(5224), # temporarily unbroken (#5227) - compiler_stats_num_field('peak_megabytes_allocated',# Note [residency] - [(platform('x86_64-apple-darwin'), 70, 1), - # expected value: 58 (amd64/OS X) - # 13/01/2014 - 70 - (wordsize(32), 30, 20), - (wordsize(64), 48, 20)]), - # prev: 50 (amd64/Linux) - # 19/10/2012: 64 (amd64/Linux) - # (^ REASON UNKNOWN!) - # 12/11/2012: 49 (amd64/Linux) - # (^ REASON UNKNOWN!) - # 28/8/13: 60 (amd64/Linux) - # (^ REASON UNKNOWN!) - # 2014-09-10: 55 post-AMP-cleanup - # 2014-10-08: 62 (jumps between 55 and 71 observed -- GC tipping point?) - # 2014-10-13: 48 stricter seqDmdType +################################### +# deactivated for now, as this metric became to volatile recently +# compiler_stats_num_field('peak_megabytes_allocated',# Note [residency] +# [(platform('x86_64-apple-darwin'), 70, 1), +# # expected value: 58 (amd64/OS X) +# # 13/01/2014 - 70 +# (wordsize(32), 30, 20), +# (wordsize(64), 48, 20)]), +# # prev: 50 (amd64/Linux) +# # 19/10/2012: 64 (amd64/Linux) +# # (^ REASON UNKNOWN!) +# # 12/11/2012: 49 (amd64/Linux) +# # (^ REASON UNKNOWN!) +# # 28/8/13: 60 (amd64/Linux) +# # (^ REASON UNKNOWN!) +# # 2014-09-10: 55 post-AMP-cleanup +# # 2014-10-08: 62 (jumps between 55 and 71 observed -- GC tipping point?) +# # 2014-10-13: 48 stricter seqDmdType compiler_stats_num_field('bytes allocated', [(platform('x86_64-apple-darwin'), 464872776, 5), From git at git.haskell.org Sun Nov 9 22:14:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Nov 2014 22:14:33 +0000 (UTC) Subject: [commit: ghc] wip/T9281: Rename integer-gmp2's package name to `integer-gmp` (749e0ea) Message-ID: <20141109221433.4F6AD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/749e0ea748da5b6f52f7d868efc54142c19f69e0/ghc >--------------------------------------------------------------- commit 749e0ea748da5b6f52f7d868efc54142c19f69e0 Author: Herbert Valerio Riedel Date: Sun Nov 9 23:13:39 2014 +0100 Rename integer-gmp2's package name to `integer-gmp` While the folder-name stays the same. This also bumps the version number to 1.0.0.0 (old integer-gmp is at 0.5.1.x) >--------------------------------------------------------------- 749e0ea748da5b6f52f7d868efc54142c19f69e0 compiler/basicTypes/Module.lhs | 7 ++++++- ghc.mk | 2 +- libraries/base/base.cabal | 2 +- libraries/integer-gmp2/.gitignore | 4 ++-- libraries/integer-gmp2/configure.ac | 2 +- .../include/HsIntegerGmp.h.in | 0 libraries/integer-gmp2/include/HsIntegerGmp2.h.in | 6 ------ ...{integer-gmp2.buildinfo.in => integer-gmp.buildinfo.in} | 0 .../integer-gmp2/{integer-gmp2.cabal => integer-gmp.cabal} | 14 +++++++------- libraries/integer-gmp2/src/GHC/Integer.hs | 2 +- libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs | 2 +- testsuite/driver/testlib.py | 2 +- testsuite/tests/ghci/scripts/ghci025.stdout | 6 +++--- testsuite/tests/lib/integer/all.T | 2 +- testsuite/tests/llvm/should_compile/all.T | 2 +- testsuite/tests/rename/should_compile/T3103/test.T | 2 +- testsuite/tests/rts/Makefile | 4 ++-- testsuite/tests/safeHaskell/check/pkg01/all.T | 5 +---- testsuite/tests/typecheck/should_fail/T5095.stderr | 6 +++--- 19 files changed, 33 insertions(+), 37 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 749e0ea748da5b6f52f7d868efc54142c19f69e0 From git at git.haskell.org Sun Nov 9 23:07:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Nov 2014 23:07:50 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Merge remote-tracking branch 'origin/master' into wip/tc-plugins (723e672) Message-ID: <20141109230750.C39BD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/723e6722040a1d476f0fdb9e7daddb821f2f90bc/ghc >--------------------------------------------------------------- commit 723e6722040a1d476f0fdb9e7daddb821f2f90bc Merge: 1313ef8 8e66365 Author: Iavor S. Diatchki Date: Sun Nov 9 15:04:35 2014 -0800 Merge remote-tracking branch 'origin/master' into wip/tc-plugins Conflicts: compiler/main/DynFlags.hs compiler/simplCore/SimplCore.lhs compiler/typecheck/Flattening-notes compiler/typecheck/Inst.lhs compiler/typecheck/TcBinds.lhs compiler/typecheck/TcCanonical.lhs compiler/typecheck/TcDeriv.lhs compiler/typecheck/TcInstDcls.lhs compiler/typecheck/TcInteract.lhs compiler/typecheck/TcMType.lhs compiler/typecheck/TcRnTypes.lhs compiler/typecheck/TcSMonad.lhs compiler/typecheck/TcSimplify.lhs compiler/typecheck/TcType.lhs compiler/types/FamInstEnv.lhs rts/Linker.c testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.hs testsuite/tests/indexed-types/should_fail/T1897b.stderr testsuite/tests/indexed-types/should_fail/T2664.stderr testsuite/tests/indexed-types/should_fail/T4093a.hs testsuite/tests/indexed-types/should_fail/T7010.stderr testsuite/tests/indexed-types/should_fail/T8518.stderr testsuite/tests/perf/compiler/T5837.hs testsuite/tests/simplCore/should_compile/T3772.stdout >--------------------------------------------------------------- Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 723e6722040a1d476f0fdb9e7daddb821f2f90bc From git at git.haskell.org Sun Nov 9 23:07:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Nov 2014 23:07:53 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins's head updated: Merge remote-tracking branch 'origin/master' into wip/tc-plugins (723e672) Message-ID: <20141109230753.D3E6B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/tc-plugins' now includes: 710bc8d Update primitive, vector, and dph submodules. 27f7552 Make Applicative-Monad fixes for tests. 3687089 Updated testsuite/.gitignore to cover artifacts on Windows. 2cc2065 Use objdump instead of nm to derive constants on OpenBSD 9f29e03 ghc-prim: Use population count appropriate for platform d4fd168 Update to Unicode version 7.0 a5f4fb6 Remove extra period 3157127 Improve isDigit, isSpace, etc. ef2d027 Make findIndices fuse 1e269bf Make Data.List.concatMap fuse better 6825558 Add doctest examples for Data.Functor. 5211673 Fix typo in -XConstraintKinds docs 9c464f8 Add doctest examples for Data.Bool. c819958 Add release note about Unicode 7.0 69f6361 Fixes the ARM build 972ba12 Enabled warn on tabs by default (fixes #9230) 4faeecb [skip ci] rts: Detabify RtsMessages.c aa8d23d [skip ci] rts: Detabify RaiseAsync.h bb04867 [skip ci] rts: Detabify Capability.h 99edc35 [skip ci] rts: Detabify CheckUnload.c 6aa6ca8 [skip ci] rts: Detabify Profiling.c 570b339 [skip ci] rts: Detabify Threads.c 21eaaa1 [skip ci] rts: Detabify sm/Evac.c 9167d0e [skip ci] rts: Detabify sm/Scav.c 5bb8f14 [skip ci] rts: Detabify Stats.c 2dc21b9 [skip ci] rts: Detabify Schedule.h 1d12df3 [skip ci] rts: Detabify LdvProfile.h 3d0e695 [skip ci] rts: Detabify Proftimer.c 68c45b6 [skip ci] rts: Detabify Exception.cmm a7ab7d3 [skip ci] rts: Detabify HeapStackCheck.cmm 6811e53 [skip ci] rts: Detabify Capability.c beb5c2e [skip ci] rts: Detabify RaiseAsync.c e13478f [skip ci] rts: Detabify sm/GC.c faa3339 [skip ci] rts: Detabify sm/Sanity.c bc1609a [skip ci] rts: Detabify sm/Compact.c c8173d5 [skip ci] rts: Detabify sm/Compact.h 5106e20 [skip ci] rts: Detabify RetainerProfile.c 03c3e9a [skip ci] rts: Detabify ProfHeap.c 6abb34c [skip ci] rts: Detabify Schedule.c 9bfe602 rts: Detabify Interpreter.c df5c11a base: Mark WCsubst.c as generated for Phabricator 45cbe85 Flush stdout in T9692 aa641e5 Add forgotten import to T9692 a11f71e Fix a rare parallel GC bug 427925d More updates to Backpack manual [skip ci] 5bb73d7 Check in up-to-date PDF copies of Backpack docs. [skip ci] aa47995 Implementation of hsig (module signatures), per #9252 1addef8 Fix windows build failure. 73c7ea7 fix a typo in comments: normaliseFfiType 0855b24 Pass in CXX to libffi's configure script. 7b59db2 `M-x delete-trailing-whitespace` & `M-x untabify` a3312c3 testsuite: Fix outdated output for T5979/safePkg01 0a290ca Add new `Data.Bifunctor` module (re #9682) 9e2cb00 Optimise atomicModifyIORef' implementation (#8345) 0e1f0f7 Un-wire `Integer` type (re #9714) 0013613 Deactivate T3064 `max_bytes_used`-check 49b05d6 Improve performance of isSuffixOf (#9676) 1874501 Typo in comment aa2ceba Normalise package key hash to make tests less fragile. 63918e6 Add n-ary version of `two_normalisers` to testsuite lib 3d6422b testlib: Get rid of two_normalisers 98ed815 Make iterateFB inlineable 75979f3 base: Refactor/clean-up *List modules 5f69c8e Reorder GHC.List; fix performance regressions f109085 Update Haddock submodule for collapsible section support 64d0a19 Really fix fft2 regression. #9740 208a0c2 Fixed unused variable warning on mingw32/i686 in rts/Linker.c f9ca529 hsc2hs: Update submodule 322810e Convert GHCi sources from .lhs to .hs 257cbec Fix #9236 Error on read from closed handle 5ce1266 Use snwprintf instead of swprintf in rts/Linker.c. acb3295 Avoid setting -Werror=unused-but-set-variable on Windows. 45175e1 Extra CRs are now filtered out from the source file for :list. f10b67a Updated stale ghcpkg05.stderr-mingw32. 3d27f69 Do not use a relative path for echo in tests/ghci/prog013. c211f8e Add __GLASGOW_HASKELL_TH__=YES/NO to CPP definitions 93c776a Added mingw32-specific expected stdout files for tests/driver/sigof{01,02,03} 9de5240 Comments only c6d4ae6 Fix test driver python3 compatibility issues 578bc00 Add notes on change to hGetContents semantics 995ea1c Fixed missing trailing newline bug in pretty printer 1907e81 Updated testsuite/.gitignore to exclude some test artifacts on Windows. cbb20ab Drop deprecated `OverlappingInstances` from base 919e930 Fix comment typos 8ef4cf1 Add doctest examples for Data.Char bd6c6f6 Update Haddock submodule 54addb1 Clean-up `Data.Fixed` f12be5b Add changelog entry for recent Unicode 7.0 update d3a7126 Update doctest example style in `Data.Bool` 4667fb5 Split off stat (benchmark) test failures into a separate section in the test runner summary. 322c139 remove old .NET related code e466ea7 Remove legacy support for -optdef flags d15d704 Fix build via Haddock submodule update. 6534686 Fix comment about dropWhileEndLE e5ba360 rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) a47ff8b Fixed T5435_dyn_asm on Windows. The test code was not in sync with the expected output. f688f03 Test #9262 in th/T9262, and update other tests. 2cc593d Bring unbound tyvars into scope during reifyInstances. b174288 Test #8953 in th/T8953 9fd19f9 Always use KindedTV when reifying. (#8953) 593e8b9 Annotate reified poly-kinded tycons when necessary. (#8953) c3ecf06 Annotate poly-kinded type patterns in instance reification. 99882ba Testsuite wibbles from fixing #8953 862772b Test #9084 in th/T9084. 03d61cc Fix #9084 by calling notHandled when unknown bits are enountered. 17265c0 Fix testsuite output from #9084. 752b5e2 Test #9738 in th/T9738 209baea Fix #9738, by handling {-# ANN ... #-} in DsMeta. 18a4a5d Update release notes for #9262 #8953 #9084. 96c22d9 Tweak the error message for pattern synonym methods, since they are disallowed both in class and instance declarations c001bde Put one-Shot info in the interface c271e32 Add GHC.Prim.oneShot 072259c Use oneShot in the definition of foldl etc. 063ae61 Update expected profiling output for scc001 1c0b736 Link to oneShot from the User's Guide 6dd218e Make Foldable's foldr1 and foldl1 defaults lazier ce03c4a Further relax T1969?s max_bytes range 49fde3b Add `Alternative` wrapper to Data.Monoid 4dbe433 Minor Haddock markup improvement to Data.Monoid 828d724 Refactor Haddock comments in Data.Bits c7fa0ba Fix lost Haddock annotation for `class Monad m` 1d6124d Tidy up pretty-printing of SrcLoc and SrcSpan 27ba070 Improve pretty-printing of type variables c8c18a1 Some refactoring around endPass and debug dumping 7251798 Simplify the generation of superclass constraints in tcInstDecl2 d153e40 Add the unfolding and inline-pragma for DFuns in DsBinds, not TcInstDcls bdbb595 White space only fd46acf Fix reduceTyFamApp_maybe 33dcb81 Simplify the API for tcInstTyVars, and make it more consistent with other similar functions 9c81db4 Rename setRole_maybe to downgradeRole_maybe 54f9188 Refactor skolemising, and newClsInst 2bfc653 Refactor the treatment of lexically-scoped type variables for instance declarations e11e1b8 Get the Untouchables level right in simplifyInfer a6e7654 Normalise the type of an inferred let-binding e840d85 Typechecker debug tracing only c64539c When reporting the context of given constraints, stop when you find one that binds a variable mentioned in the wanted 15131ec Only report "could not deduce s~t from ..." for givens that include equalities f054822 Don't filter out allegedly-irrelevant bindings with -dppr-debug 84d9ef0 Minor refactoring (no change in functionality) c1a85b3 Define ctEvLoc and ctEvCoercion, and use them 4723a0e Test Trac #9211 f861fc6 Test Trac #9708 6d1ac96 Improve error message for a handwritten Typeable instance dbbffb7 Test Trac #9747 abfbdd1 Add comments explaining ProbOneShot c639560 Test Trac #9739 7c79633 Fix the superclass-cycle detection code (Trac #9739) 66658ee Comments only 5479ae0 Testsuite error message changes 652a5ef Add flattening-notes f02c915 Make this test a bit simpler ce9d6f2 Compiler performance is much worse in for loopy givens 5770029 Simon's major commit to re-engineer the constraint solver 2f0d841 Updates to safePkg01 under Edward's guidance 09aac7d Test Trac #9081 fe178b2 Test Trac #9750 1408c8d Remove redundant "Minimal complete definition"-comments 64dc4d1 Re-center perf-numbers for T5631 6a1c05f A little refactoring of HsSplice and friends 77f8221 Temporarily disable T3064 (see #9771) 0a8e899 Remove redundant contexts from Foldable methods ac0915b Clean-up Haddock in `Data.Functor` 40b1ee4 Add `isSubsequenceOf` to Data.List (#9767) 32237f0 Fix typo in testsuite Makefile 83cf31e Fix a couple of bugs in the way info tables are generated for 64-bit platforms 4cd277b Fix bugs in debug printing 3bebf3c Fix a couple of inaccurate stack checks e6b3829 Disable an assertion; see comment 081ef2f Add a comment about stack checks d14312f Add doctest examples for Data.Either d0d9dc0 Clarify confusing notice from `make maintainer-clean` ad8457f Remove -ddump-simpl-phases flag c0a2354 Remove -ddump-core-pipeline flag 303776a Update User's Guide, cleanup DynFlags 0f930ba Move expansion of 'assert' from renamer to typechecker 030abf9 Remove unused tyConsOfDataCon e7523fe Make tyConsOfType return a (NameEnv TyCon) rather than [TyCon] f81f82e Comments and white space only 528cbd7 Give T3064 the right module name (just tidying up) 096b7e6 Switch off lazy flattening (fix Trac #3064) cb6ccad Minor refacoring and trace-message printing c945477 Allow the solved dictionaries to propagate from outside in ec38deb Wibbles to notes 203cf0e Refactor the code that prevents recursion among Coercible constraints c79cbac Re-enable T3064, which works now 91c15d6 Better error messages for new per-instance overlap flags and Safe Haskell. c96a613 Add in Incoherent Instances test for Safe Haskell. f4ead30 Warn for Safe Haskell when -XOverlappingInstances or -XIncoherentInstances turned on. abba381 Improve Applicative definitions dc5fa80 Make getTag use a bang pattern instead of seq b0e8e34 Update .gitignore to properly ignore emacs temp files 24e05f4 *Really*, really fix RTS crash due to bad coercion. 37d64a5 small parser/lexer cleanup b0d5b5b [Docs] Fixed several broken urls in user's guide f14ac52 Use bracket in `withCurrentDirectory` 832ef3f Have validate take into account stat test failures too. df3b1d4 base: Manually unlit .lhs into .hs modules a2e7bbf Preserve argument order to (==)/eq in nub and nubBy b608868 Typofix. c942688 Miscellaneous documentation for the Finder. f5996d9 Top-level comment for keepPackageImports. 474e535 In pattern synonym matchers, support unboxed continuation results (fixes #9783). 65dc594 Group PatSyn req/prov arguments together so that they're not all over the place 8e66365 Unlit overlooked GHC/Conc/Sync.lhs 723e672 Merge remote-tracking branch 'origin/master' into wip/tc-plugins From git at git.haskell.org Mon Nov 10 00:04:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Nov 2014 00:04:32 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Type-checker plugins as a single patch. (31729d0) Message-ID: <20141110000432.193743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/31729d092c813edc4ef5682db2ee18b33aea6911/ghc >--------------------------------------------------------------- commit 31729d092c813edc4ef5682db2ee18b33aea6911 Author: Iavor S. Diatchki Date: Sun Nov 9 15:52:52 2014 -0800 Type-checker plugins as a single patch. >--------------------------------------------------------------- 31729d092c813edc4ef5682db2ee18b33aea6911 compiler/ghc.mk | 13 ++++- compiler/ghci/RtClosureInspect.hs | 4 +- compiler/main/DynFlags.hs | 19 ++++--- compiler/main/DynamicLoading.hs | 6 +- compiler/main/DynamicLoading.hs-boot | 12 ++++ compiler/prelude/PrelNames.lhs | 9 ++- compiler/simplCore/SimplCore.lhs | 3 +- compiler/typecheck/TcInteract.lhs | 82 +++++++++++++++++++++++++--- compiler/typecheck/TcRnDriver.lhs | 7 ++- compiler/typecheck/TcRnMonad.lhs | 100 ++++++++++++++++++++++++++++++++-- compiler/typecheck/TcRnTypes.lhs | 81 ++++++++++++++++++++++++++- compiler/typecheck/TcRnTypes.lhs-boot | 6 +- compiler/typecheck/TcSMonad.lhs | 19 ++++++- compiler/typecheck/TcTypeNats.hs | 8 +++ 14 files changed, 331 insertions(+), 38 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 31729d092c813edc4ef5682db2ee18b33aea6911 From git at git.haskell.org Mon Nov 10 00:04:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Nov 2014 00:04:34 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Merge branch 'wip/tc-plugins' into merge-plugins (bc0ccfa) Message-ID: <20141110000434.F075B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/bc0ccfaf5b926a6fc735abd04416920d09996349/ghc >--------------------------------------------------------------- commit bc0ccfaf5b926a6fc735abd04416920d09996349 Merge: 31729d0 723e672 Author: Iavor S. Diatchki Date: Sun Nov 9 15:56:08 2014 -0800 Merge branch 'wip/tc-plugins' into merge-plugins The temporary branch `merge-plugins` squashed all changes on ths branch in a single commit. It also removed some accidental changes. This "merge" simply declares that all the content of `wip/tc-plugins` is already present (i.e. I am using merge startegy `ours`). >--------------------------------------------------------------- bc0ccfaf5b926a6fc735abd04416920d09996349 From git at git.haskell.org Mon Nov 10 00:04:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Nov 2014 00:04:37 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins's head updated: Merge branch 'wip/tc-plugins' into merge-plugins (bc0ccfa) Message-ID: <20141110000437.272853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/tc-plugins' now includes: e2769df Use (.) and id from Base in Control.Applicative 31729d0 Type-checker plugins as a single patch. bc0ccfa Merge branch 'wip/tc-plugins' into merge-plugins From git at git.haskell.org Mon Nov 10 12:04:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Nov 2014 12:04:19 +0000 (UTC) Subject: [commit: ghc] wip/T9281: Rename integer-gmp2's package name to `integer-gmp` (335251a) Message-ID: <20141110120419.C013F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9281 Link : http://ghc.haskell.org/trac/ghc/changeset/335251a2a623e879beba71971bc5e180bebbb778/ghc >--------------------------------------------------------------- commit 335251a2a623e879beba71971bc5e180bebbb778 Author: Herbert Valerio Riedel Date: Sun Nov 9 23:13:39 2014 +0100 Rename integer-gmp2's package name to `integer-gmp` While the folder-name stays the same. This also bumps the version number to 1.0.0.0 (old integer-gmp is at 0.5.1.x) >--------------------------------------------------------------- 335251a2a623e879beba71971bc5e180bebbb778 compiler/basicTypes/Module.lhs | 7 ++++++- ghc.mk | 2 +- libraries/base/base.cabal | 2 +- libraries/integer-gmp2/.gitignore | 4 ++-- libraries/integer-gmp2/configure.ac | 2 +- .../include/HsIntegerGmp.h.in | 0 libraries/integer-gmp2/include/HsIntegerGmp2.h.in | 6 ------ ...{integer-gmp2.buildinfo.in => integer-gmp.buildinfo.in} | 2 +- .../integer-gmp2/{integer-gmp2.cabal => integer-gmp.cabal} | 14 +++++++------- libraries/integer-gmp2/src/GHC/Integer.hs | 2 +- libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs | 2 +- testsuite/driver/testlib.py | 2 +- testsuite/tests/ghci/scripts/ghci025.stdout | 6 +++--- testsuite/tests/lib/integer/all.T | 2 +- testsuite/tests/llvm/should_compile/all.T | 2 +- testsuite/tests/rename/should_compile/T3103/test.T | 2 +- testsuite/tests/rts/Makefile | 4 ++-- testsuite/tests/safeHaskell/check/pkg01/all.T | 5 +---- testsuite/tests/typecheck/should_fail/T5095.stderr | 6 +++--- utils/ghc-cabal/Main.hs | 3 +++ 20 files changed, 37 insertions(+), 38 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 335251a2a623e879beba71971bc5e180bebbb778 From git at git.haskell.org Mon Nov 10 14:08:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Nov 2014 14:08:13 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T8584.spj' created Message-ID: <20141110140813.9401F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T8584.spj Referencing: b0a25b9e30c9c2d9635a4dc9786f5ba00e3e060a From git at git.haskell.org Mon Nov 10 14:08:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Nov 2014 14:08:16 +0000 (UTC) Subject: [commit: ghc] wip/T8584.spj: Parser for SPJ's pattern synonym signature syntax (8a48465) Message-ID: <20141110140816.4540A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584.spj Link : http://ghc.haskell.org/trac/ghc/changeset/8a4846565e492ca76b344397df778cc0977200aa/ghc >--------------------------------------------------------------- commit 8a4846565e492ca76b344397df778cc0977200aa Author: Dr. ERDI Gergo Date: Sun Nov 9 13:20:57 2014 +0800 Parser for SPJ's pattern synonym signature syntax >--------------------------------------------------------------- 8a4846565e492ca76b344397df778cc0977200aa compiler/hsSyn/HsTypes.lhs | 2 ++ compiler/parser/Parser.y | 30 ++++++++++++++++++++++-------- compiler/parser/RdrHsSyn.hs | 17 +++++++++++++++++ 3 files changed, 41 insertions(+), 8 deletions(-) diff --git a/compiler/hsSyn/HsTypes.lhs b/compiler/hsSyn/HsTypes.lhs index db4d976..7af05c3 100644 --- a/compiler/hsSyn/HsTypes.lhs +++ b/compiler/hsSyn/HsTypes.lhs @@ -272,6 +272,8 @@ data HsType name | HsTyLit HsTyLit -- A promoted numeric literal. | HsWrapTy HsTyWrapper (HsType name) -- only in typechecker output + + | HsContextPair (LHsContext name) (LHsContext name) -- only during parsing deriving (Typeable) deriving instance (DataId name) => Data (HsType name) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index ea752cf..7d817ed 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -880,9 +880,16 @@ where_decls :: { Located (OrdList (LHsDecl RdrName)) } | 'where' vocurly decls close { $3 } pattern_synonym_sig :: { LSig RdrName } - : 'pattern' 'type' ctype '::' ctype - {% do { (name, details, ty, prov, req) <- splitPatSynSig $3 $5 - ; return $ sLL $1 $> $ PatSynSig name details ty prov req }} + : 'pattern' 'type' con '::' ptype + { undefined } + +ptype :: { () } + : 'forall' tv_bndrs '.' ptype {% hintExplicitForall (getLoc $1) >> + return () } + | pcontext '=>' type { () } + +pcontext :: { (LHsContext RdrName, LHsContext RdrName) } + : btype {% checkContextPair $1 } vars0 :: { [Located RdrName] } : {- empty -} { [] } @@ -1207,6 +1214,7 @@ atype :: { LHsType RdrName } | '(' ctype ',' comma_types1 ')' { sLL $1 $> $ HsTupleTy HsBoxedOrConstraintTuple ($2:$4) } | '(#' '#)' { sLL $1 $> $ HsTupleTy HsUnboxedTuple [] } | '(#' comma_types1 '#)' { sLL $1 $> $ HsTupleTy HsUnboxedTuple $2 } + | '(' comma_ltypes0 ';' comma_ltypes0 ')' { sLL $1 $> $ HsContextPair $2 $4 } | '[' ctype ']' { sLL $1 $> $ HsListTy $2 } | '[:' ctype ':]' { sLL $1 $> $ HsPArrTy $2 } | '(' ctype ')' { sLL $1 $> $ HsParTy $2 } @@ -1238,13 +1246,19 @@ inst_types1 :: { [LHsType RdrName] } : inst_type { [$1] } | inst_type ',' inst_types1 { $1 : $3 } +comma_ltypes0 :: { Located [LHsType RdrName] } + : comma_ltypes1 { $1 } + | {- empty -} { noLoc [] } + +comma_ltypes1 :: { Located [LHsType RdrName] } + : ctype { sL1 $1 [$1] } + | ctype ',' comma_ltypes1 { sLL $1 $> $ $1 : unLoc $3 } + comma_types0 :: { [LHsType RdrName] } - : comma_types1 { $1 } - | {- empty -} { [] } + : comma_ltypes0 { unLoc $1 } -comma_types1 :: { [LHsType RdrName] } - : ctype { [$1] } - | ctype ',' comma_types1 { $1 : $3 } +comma_types1 :: { [LHsType RdrName] } + : comma_ltypes1 { unLoc $1 } tv_bndrs :: { [LHsTyVarBndr RdrName] } : tv_bndr tv_bndrs { $1 : $2 } diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs index 15490c3..4b3d519 100644 --- a/compiler/parser/RdrHsSyn.hs +++ b/compiler/parser/RdrHsSyn.hs @@ -41,6 +41,7 @@ module RdrHsSyn ( -- checking and constructing values checkPrecP, -- Int -> P Int checkContext, -- HsType -> P HsContext + checkContextPair, -- HsType -> P (HsContext, HsContext) checkPattern, -- HsExp -> P HsPat bang_RDR, checkPatterns, -- SrcLoc -> [HsExp] -> P [HsPat] @@ -673,6 +674,22 @@ checkContext (L l orig_t) check _ = return (L l [L l orig_t]) +checkContextPair :: LHsType RdrName -> P (LHsContext RdrName, LHsContext RdrName) +checkContextPair (L l orig_t) + = check orig_t + where + check (HsTupleTy _ ts) -- Required context can be empty + = return (L l ts, noLoc []) + + check (HsParTy ty) -- to be sure HsParTy doesn't get into the way + = check (unLoc ty) + + check (HsContextPair prov req) + = return (prov, req) + + check _ + = return (L l [L l orig_t], noLoc []) + -- ------------------------------------------------------------------------- -- Checking Patterns. From git at git.haskell.org Mon Nov 10 14:08:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Nov 2014 14:08:19 +0000 (UTC) Subject: [commit: ghc] wip/T8584.spj: In concrete syntax, existential and universial tyvars of a pattern synonym type signature are not split (7061f2b) Message-ID: <20141110140819.112023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584.spj Link : http://ghc.haskell.org/trac/ghc/changeset/7061f2b897216786c5fa3366ce51531d8efe06b5/ghc >--------------------------------------------------------------- commit 7061f2b897216786c5fa3366ce51531d8efe06b5 Author: Dr. ERDI Gergo Date: Sun Nov 9 14:40:13 2014 +0800 In concrete syntax, existential and universial tyvars of a pattern synonym type signature are not split >--------------------------------------------------------------- 7061f2b897216786c5fa3366ce51531d8efe06b5 compiler/hsSyn/HsBinds.lhs | 21 +++++++++++--------- compiler/iface/IfaceSyn.lhs | 3 +++ compiler/rename/RnBinds.lhs | 44 +++++++++++------------------------------- compiler/typecheck/TcBinds.lhs | 27 +++++++++++++------------- 4 files changed, 39 insertions(+), 56 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7061f2b897216786c5fa3366ce51531d8efe06b5 From git at git.haskell.org Mon Nov 10 14:08:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Nov 2014 14:08:21 +0000 (UTC) Subject: [commit: ghc] wip/T8584.spj: Finish parser (7a1f9a8) Message-ID: <20141110140821.AC4133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584.spj Link : http://ghc.haskell.org/trac/ghc/changeset/7a1f9a8c1b60c3b040398e37c13a7e5394fe1af6/ghc >--------------------------------------------------------------- commit 7a1f9a8c1b60c3b040398e37c13a7e5394fe1af6 Author: Dr. ERDI Gergo Date: Sun Nov 9 14:42:30 2014 +0800 Finish parser >--------------------------------------------------------------- 7a1f9a8c1b60c3b040398e37c13a7e5394fe1af6 compiler/parser/Parser.y | 22 +++++++++++++--------- 1 file changed, 13 insertions(+), 9 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 7d817ed..bf62286 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -881,15 +881,19 @@ where_decls :: { Located (OrdList (LHsDecl RdrName)) } pattern_synonym_sig :: { LSig RdrName } : 'pattern' 'type' con '::' ptype - { undefined } - -ptype :: { () } - : 'forall' tv_bndrs '.' ptype {% hintExplicitForall (getLoc $1) >> - return () } - | pcontext '=>' type { () } - -pcontext :: { (LHsContext RdrName, LHsContext RdrName) } - : btype {% checkContextPair $1 } + { let (flag, qtvs, prov, req, ty) = unLoc $5 + in sLL $1 $> $ PatSynSig $3 (flag, mkHsQTvs qtvs) prov req ty } + +ptype :: { Located (HsExplicitFlag, [LHsTyVarBndr RdrName], LHsContext RdrName, LHsContext RdrName, LHsType RdrName) } + : 'forall' tv_bndrs '.' ptype + {% do { hintExplicitForall (getLoc $1) + ; let (_, qtvs', prov, req, ty) = unLoc $4 + ; return $ sLL $1 $> (Explicit, $2 ++ qtvs', prov, req ,ty) }} + | pcontext '=>' type + { let (prov, req) = unLoc $1 in sLL $1 $> (Implicit, [], prov, req, $3) } + +pcontext :: { Located (LHsContext RdrName, LHsContext RdrName) } + : btype {% fmap (sL1 $1) $ checkContextPair $1 } vars0 :: { [Located RdrName] } : {- empty -} { [] } From git at git.haskell.org Mon Nov 10 14:08:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Nov 2014 14:08:24 +0000 (UTC) Subject: [commit: ghc] wip/T8584.spj: Use user-supplied type variables (when available) in pattern synonym type signatures (c7ced1f) Message-ID: <20141110140824.5DA8E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584.spj Link : http://ghc.haskell.org/trac/ghc/changeset/c7ced1f37263093b224fc7bafbc1fd622e15fd8a/ghc >--------------------------------------------------------------- commit c7ced1f37263093b224fc7bafbc1fd622e15fd8a Author: Dr. ERDI Gergo Date: Sun Nov 9 15:46:46 2014 +0800 Use user-supplied type variables (when available) in pattern synonym type signatures >--------------------------------------------------------------- c7ced1f37263093b224fc7bafbc1fd622e15fd8a compiler/rename/RnBinds.lhs | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index 8fe5213..0669277 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -847,8 +847,16 @@ renameSig ctxt sig@(PatSynSig v (flag, qtvs) prov req ty) ; let doc = TypeSigCtx $ quotes (ppr v) ; loc <- getSrcSpanM - ; let (tv_kvs, tvs) = extractHsTysRdrTyVars (ty:unLoc prov ++ unLoc req) - ; let tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ tvs + ; let (tv_kvs, mentioned) = extractHsTysRdrTyVars (ty:unLoc prov ++ unLoc req) + ; tv_bndrs <- case flag of + Implicit -> + return $ mkHsQTvs . userHsTyVarBndrs loc $ mentioned + Explicit -> + do { let heading = ptext (sLit "In the pattern synonym type signature") + <+> quotes (ppr sig) + ; warnUnusedForAlls (heading $$ docOfHsDocContext doc) qtvs mentioned + ; return qtvs } + Qualified -> panic "renameSig: Qualified" ; bindHsTyVars doc Nothing tv_kvs tv_bndrs $ \ tyvars -> do { (prov', fvs1) <- rnContext doc prov From git at git.haskell.org Mon Nov 10 14:08:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Nov 2014 14:08:27 +0000 (UTC) Subject: [commit: ghc] wip/T8584.spj: renamer fixup: remove tab (18cfb4a) Message-ID: <20141110140827.1DDF93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584.spj Link : http://ghc.haskell.org/trac/ghc/changeset/18cfb4a282242000d525e3d3affbf88e6119df7e/ghc >--------------------------------------------------------------- commit 18cfb4a282242000d525e3d3affbf88e6119df7e Author: Dr. ERDI Gergo Date: Mon Nov 10 21:59:15 2014 +0800 renamer fixup: remove tab >--------------------------------------------------------------- 18cfb4a282242000d525e3d3affbf88e6119df7e compiler/rename/RnBinds.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index 0669277..983cac7 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -843,7 +843,7 @@ renameSig ctxt sig@(MinimalSig bf) return (MinimalSig new_bf, emptyFVs) renameSig ctxt sig@(PatSynSig v (flag, qtvs) prov req ty) - = do { v' <- lookupSigOccRn ctxt sig v + = do { v' <- lookupSigOccRn ctxt sig v ; let doc = TypeSigCtx $ quotes (ppr v) ; loc <- getSrcSpanM From git at git.haskell.org Mon Nov 10 14:08:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Nov 2014 14:08:29 +0000 (UTC) Subject: [commit: ghc] wip/T8584.spj: Look ma, no 'pattern type'! (b0a25b9) Message-ID: <20141110140829.C96793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584.spj Link : http://ghc.haskell.org/trac/ghc/changeset/b0a25b9e30c9c2d9635a4dc9786f5ba00e3e060a/ghc >--------------------------------------------------------------- commit b0a25b9e30c9c2d9635a4dc9786f5ba00e3e060a Author: Dr. ERDI Gergo Date: Mon Nov 10 21:52:12 2014 +0800 Look ma, no 'pattern type'! >--------------------------------------------------------------- b0a25b9e30c9c2d9635a4dc9786f5ba00e3e060a compiler/parser/Parser.y | 39 ++++++++++++++++++++------------------- 1 file changed, 20 insertions(+), 19 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index bf62286..80bc48d 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -860,29 +860,34 @@ role : VARID { sL1 $1 $ Just $ getVARID $1 } -- Glasgow extension: pattern synonyms pattern_synonym_decl :: { LHsDecl RdrName } - : 'pattern' pat '=' pat - {% do { (name, args) <- splitPatSyn $2 - ; return $ sLL $1 $> . ValD $ mkPatSynBind name args $4 ImplicitBidirectional - }} - | 'pattern' pat '<-' pat - {% do { (name, args) <- splitPatSyn $2 - ; return $ sLL $1 $> . ValD $ mkPatSynBind name args $4 Unidirectional - }} - | 'pattern' pat '<-' pat where_decls - {% do { (name, args) <- splitPatSyn $2 + : 'pattern' pattern_synonym_lhs '=' pat + { let (name, args) = $2 + in sLL $1 $> . ValD $ mkPatSynBind name args $4 ImplicitBidirectional } + | 'pattern' pattern_synonym_lhs '<-' pat + { let (name, args) = $2 + in sLL $1 $> . ValD $ mkPatSynBind name args $4 Unidirectional } + | 'pattern' pattern_synonym_lhs '<-' pat where_decls + {% do { let (name, args) = $2 ; mg <- toPatSynMatchGroup name $5 ; return $ sLL $1 $> . ValD $ - mkPatSynBind name args $4 (ExplicitBidirectional mg) - }} + mkPatSynBind name args $4 (ExplicitBidirectional mg) }} + +pattern_synonym_lhs :: { (Located RdrName, HsPatSynDetails (Located RdrName)) } + : con vars0 { ($1, PrefixPatSyn $2) } + | varid consym varid { ($2, InfixPatSyn $1 $3) } + +vars0 :: { [Located RdrName] } + : {- empty -} { [] } + | varid vars0 { $1 : $2 } where_decls :: { Located (OrdList (LHsDecl RdrName)) } : 'where' '{' decls '}' { $3 } | 'where' vocurly decls close { $3 } pattern_synonym_sig :: { LSig RdrName } - : 'pattern' 'type' con '::' ptype - { let (flag, qtvs, prov, req, ty) = unLoc $5 - in sLL $1 $> $ PatSynSig $3 (flag, mkHsQTvs qtvs) prov req ty } + : 'pattern' con '::' ptype + { let (flag, qtvs, prov, req, ty) = unLoc $4 + in sLL $1 $> $ PatSynSig $2 (flag, mkHsQTvs qtvs) prov req ty } ptype :: { Located (HsExplicitFlag, [LHsTyVarBndr RdrName], LHsContext RdrName, LHsContext RdrName, LHsType RdrName) } : 'forall' tv_bndrs '.' ptype @@ -895,10 +900,6 @@ ptype :: { Located (HsExplicitFlag, [LHsTyVarBndr RdrName], LHsContext RdrName, pcontext :: { Located (LHsContext RdrName, LHsContext RdrName) } : btype {% fmap (sL1 $1) $ checkContextPair $1 } -vars0 :: { [Located RdrName] } - : {- empty -} { [] } - | varid vars0 { $1 : $2 } - ----------------------------------------------------------------------------- -- Nested declarations From git at git.haskell.org Mon Nov 10 20:51:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Nov 2014 20:51:26 +0000 (UTC) Subject: [commit: ghc] master: Move Data.Functor.Identity from transformers to base (8710136) Message-ID: <20141110205126.D5E4A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/87101364e0c2db5e472c6331ad35503028b2ec3c/ghc >--------------------------------------------------------------- commit 87101364e0c2db5e472c6331ad35503028b2ec3c Author: Herbert Valerio Riedel Date: Sun Oct 5 15:18:49 2014 +0200 Move Data.Functor.Identity from transformers to base This also updates the `transformers` submodule to the just released `transformers-0.4.2.0` package version. See #9664 for more details Reviewed By: austin, ekmett Differential Revision: https://phabricator.haskell.org/D313 >--------------------------------------------------------------- 87101364e0c2db5e472c6331ad35503028b2ec3c libraries/base/Data/Functor/Identity.hs | 75 +++++++++++++++++++++++++++++++ libraries/base/base.cabal | 1 + libraries/base/changelog.md | 3 ++ libraries/transformers | 2 +- testsuite/tests/ghci/scripts/T5979.stderr | 6 +-- 5 files changed, 83 insertions(+), 4 deletions(-) diff --git a/libraries/base/Data/Functor/Identity.hs b/libraries/base/Data/Functor/Identity.hs new file mode 100644 index 0000000..4058df8 --- /dev/null +++ b/libraries/base/Data/Functor/Identity.hs @@ -0,0 +1,75 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE AutoDeriveTypeable #-} +----------------------------------------------------------------------------- +-- | +-- Module : Data.Functor.Identity +-- Copyright : (c) Andy Gill 2001, +-- (c) Oregon Graduate Institute of Science and Technology 2001 +-- License : BSD-style (see the file LICENSE) +-- +-- Maintainer : ross at soi.city.ac.uk +-- Stability : experimental +-- Portability : portable +-- +-- The identity functor and monad. +-- +-- This trivial type constructor serves two purposes: +-- +-- * It can be used with functions parameterized by functor or monad classes. +-- +-- * It can be used as a base monad to which a series of monad +-- transformers may be applied to construct a composite monad. +-- Most monad transformer modules include the special case of +-- applying the transformer to 'Identity'. For example, @State s@ +-- is an abbreviation for @StateT s 'Identity'@. +-- +-- /Since: 4.8.0.0/ +----------------------------------------------------------------------------- + +module Data.Functor.Identity ( + Identity(..), + ) where + +import Control.Monad.Fix +import Data.Functor + +-- | Identity functor and monad. (a non-strict monad) +-- +-- /Since: 4.8.0.0/ +newtype Identity a = Identity { runIdentity :: a } + deriving (Eq, Ord) + +-- | This instance would be equivalent to the derived instances of the +-- 'Identity' newtype if the 'runIdentity' field were removed +instance (Read a) => Read (Identity a) where + readsPrec d = readParen (d > 10) $ \ r -> + [(Identity x,t) | ("Identity",s) <- lex r, (x,t) <- readsPrec 11 s] + +-- | This instance would be equivalent to the derived instances of the +-- 'Identity' newtype if the 'runIdentity' field were removed +instance (Show a) => Show (Identity a) where + showsPrec d (Identity x) = showParen (d > 10) $ + showString "Identity " . showsPrec 11 x + +-- --------------------------------------------------------------------------- +-- Identity instances for Functor and Monad + +instance Functor Identity where + fmap f m = Identity (f (runIdentity m)) + +instance Foldable Identity where + foldMap f (Identity x) = f x + +instance Traversable Identity where + traverse f (Identity x) = Identity <$> f x + +instance Applicative Identity where + pure a = Identity a + Identity f <*> Identity x = Identity (f x) + +instance Monad Identity where + return a = Identity a + m >>= k = k (runIdentity m) + +instance MonadFix Identity where + mfix f = Identity (fix (runIdentity . f)) diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal index 6277d89..7e5ca15 100644 --- a/libraries/base/base.cabal +++ b/libraries/base/base.cabal @@ -130,6 +130,7 @@ Library Data.Foldable Data.Function Data.Functor + Data.Functor.Identity Data.IORef Data.Int Data.Ix diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 2fa25ae..c5047ce 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -97,6 +97,9 @@ are swapped, such that `Data.List.nubBy (<) [1,2]` now returns `[1]` instead of `[1,2]` (#2528, #3280, #7913) + * New module `Data.Functor.Identity` (previously provided by `transformers` + package). (#9664) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 diff --git a/libraries/transformers b/libraries/transformers index 87d9892..c55953c 160000 --- a/libraries/transformers +++ b/libraries/transformers @@ -1 +1 @@ -Subproject commit 87d9892a604b56d687ce70f1d1abc7848f78c6e4 +Subproject commit c55953c1298a5b63e250dfcd402154f6d187825e diff --git a/testsuite/tests/ghci/scripts/T5979.stderr b/testsuite/tests/ghci/scripts/T5979.stderr index c8fc7c2..9be8573 100644 --- a/testsuite/tests/ghci/scripts/T5979.stderr +++ b/testsuite/tests/ghci/scripts/T5979.stderr @@ -2,6 +2,6 @@ : Could not find module ?Control.Monad.Trans.State? Perhaps you meant - Control.Monad.Trans.State (from transformers-0.4.1.0 at trans_) - Control.Monad.Trans.Class (from transformers-0.4.1.0 at trans_) - Control.Monad.Trans.Cont (from transformers-0.4.1.0 at trans_) + Control.Monad.Trans.State (from transformers-0.4.2.0 at trans_) + Control.Monad.Trans.Class (from transformers-0.4.2.0 at trans_) + Control.Monad.Trans.Cont (from transformers-0.4.2.0 at trans_) From git at git.haskell.org Mon Nov 10 21:15:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Nov 2014 21:15:25 +0000 (UTC) Subject: [commit: ghc] master: Typo fix; Trac #9787 (7ae596a) Message-ID: <20141110211525.29C093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7ae596af381278dc43b7312d48a18b7cce6e4ab9/ghc >--------------------------------------------------------------- commit 7ae596af381278dc43b7312d48a18b7cce6e4ab9 Author: Austin Seipp Date: Mon Nov 10 15:13:26 2014 -0600 Typo fix; Trac #9787 Also, reword :print description. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 7ae596af381278dc43b7312d48a18b7cce6e4ab9 ghc/InteractiveUI.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index e6d1529..1d45048 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -275,8 +275,8 @@ defFullHelpText = " :list show the source code around current breakpoint\n" ++ " :list show the source code for \n" ++ " :list [] show the source code around line number \n" ++ - " :print [ ...] prints a value without forcing its computation\n" ++ - " :sprint [ ...] simplifed version of :print\n" ++ + " :print [ ...] show a value without forcing its computation\n" ++ + " :sprint [ ...] simplified version of :print\n" ++ " :step single-step after stopping at a breakpoint\n"++ " :step single-step into \n"++ " :steplocal single-step within the current top-level binding\n"++ From git at git.haskell.org Tue Nov 11 02:30:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 02:30:59 +0000 (UTC) Subject: [commit: ghc] wip/rae: Update submodule array and the testsuite to fix #9220. (f683169) Message-ID: <20141111023059.371DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/f683169197cb651d02e022625a0f1cc7c1416974/ghc >--------------------------------------------------------------- commit f683169197cb651d02e022625a0f1cc7c1416974 Author: Richard Eisenberg Date: Fri Nov 7 17:34:59 2014 -0500 Update submodule array and the testsuite to fix #9220. >--------------------------------------------------------------- f683169197cb651d02e022625a0f1cc7c1416974 libraries/array | 2 +- testsuite/tests/roles/should_compile/all.T | 1 - .../{should_compile => should_fail}/RolesIArray.hs | 0 .../tests/roles/should_fail/RolesIArray.stderr | 100 +++++++++++++++++++++ testsuite/tests/roles/should_fail/all.T | 1 + 5 files changed, 102 insertions(+), 2 deletions(-) diff --git a/libraries/array b/libraries/array index 19b7aeb..86225ba 160000 --- a/libraries/array +++ b/libraries/array @@ -1 +1 @@ -Subproject commit 19b7aebd7dff912728029778749aaa8a9ed1cffd +Subproject commit 86225ba71603ed73a338e5f658698fc87aadcae9 diff --git a/testsuite/tests/roles/should_compile/all.T b/testsuite/tests/roles/should_compile/all.T index 744b934..0bd779f 100644 --- a/testsuite/tests/roles/should_compile/all.T +++ b/testsuite/tests/roles/should_compile/all.T @@ -4,5 +4,4 @@ test('Roles3', only_ways('normal'), compile, ['-ddump-tc']) test('Roles4', only_ways('normal'), compile, ['-ddump-tc']) test('Roles13', only_ways('normal'), compile, ['-ddump-simpl -dsuppress-uniques']) test('Roles14', only_ways('normal'), compile, ['-ddump-tc']) -test('RolesIArray', only_ways('normal'), compile, ['']) test('T8958', [normalise_fun(normalise_errmsg), only_ways('normal')], compile, ['-ddump-tc -dsuppress-uniques']) diff --git a/testsuite/tests/roles/should_compile/RolesIArray.hs b/testsuite/tests/roles/should_fail/RolesIArray.hs similarity index 100% rename from testsuite/tests/roles/should_compile/RolesIArray.hs rename to testsuite/tests/roles/should_fail/RolesIArray.hs diff --git a/testsuite/tests/roles/should_fail/RolesIArray.stderr b/testsuite/tests/roles/should_fail/RolesIArray.stderr new file mode 100644 index 0000000..aad2f2b --- /dev/null +++ b/testsuite/tests/roles/should_fail/RolesIArray.stderr @@ -0,0 +1,100 @@ + +RolesIArray.hs:10:13: + Could not coerce from ?UArray i Word64? to ?UArray i N? + because the second type argument of ?UArray? has role Nominal, + but the arguments ?Word64? and ?N? differ + arising from the coercion of the method ?Data.Array.Base.unsafeAccumArray? + from type ?forall e' i. + Ix i => + (Word64 -> e' -> Word64) + -> Word64 -> (i, i) -> [(Int, e')] -> UArray i Word64? + to type ?forall e' i. + Ix i => + (N -> e' -> N) -> N -> (i, i) -> [(Int, e')] -> UArray i N? + Possible fix: + use a standalone 'deriving instance' declaration, + so you can specify the instance context yourself + When deriving the instance for (IArray UArray N) + +RolesIArray.hs:10:13: + Could not coerce from ?UArray i Word64? to ?UArray i N? + because the second type argument of ?UArray? has role Nominal, + but the arguments ?Word64? and ?N? differ + arising from the coercion of the method ?Data.Array.Base.unsafeAccum? + from type ?forall e' i. + Ix i => + (Word64 -> e' -> Word64) + -> UArray i Word64 -> [(Int, e')] -> UArray i Word64? + to type ?forall e' i. + Ix i => + (N -> e' -> N) -> UArray i N -> [(Int, e')] -> UArray i N? + Possible fix: + use a standalone 'deriving instance' declaration, + so you can specify the instance context yourself + When deriving the instance for (IArray UArray N) + +RolesIArray.hs:10:13: + Could not coerce from ?UArray i Word64? to ?UArray i N? + because the second type argument of ?UArray? has role Nominal, + but the arguments ?Word64? and ?N? differ + arising from the coercion of the method ?Data.Array.Base.unsafeReplace? + from type ?forall i. + Ix i => + UArray i Word64 -> [(Int, Word64)] -> UArray i Word64? + to type ?forall i. + Ix i => + UArray i N -> [(Int, N)] -> UArray i N? + Possible fix: + use a standalone 'deriving instance' declaration, + so you can specify the instance context yourself + When deriving the instance for (IArray UArray N) + +RolesIArray.hs:10:13: + Could not coerce from ?UArray i Word64? to ?UArray i N? + because the second type argument of ?UArray? has role Nominal, + but the arguments ?Word64? and ?N? differ + arising from the coercion of the method ?Data.Array.Base.unsafeAt? + from type ?forall i. Ix i => UArray i Word64 -> Int -> Word64? + to type ?forall i. Ix i => UArray i N -> Int -> N? + Possible fix: + use a standalone 'deriving instance' declaration, + so you can specify the instance context yourself + When deriving the instance for (IArray UArray N) + +RolesIArray.hs:10:13: + Could not coerce from ?UArray i Word64? to ?UArray i N? + because the second type argument of ?UArray? has role Nominal, + but the arguments ?Word64? and ?N? differ + arising from the coercion of the method ?Data.Array.Base.unsafeArray? + from type ?forall i. + Ix i => + (i, i) -> [(Int, Word64)] -> UArray i Word64? + to type ?forall i. Ix i => (i, i) -> [(Int, N)] -> UArray i N? + Possible fix: + use a standalone 'deriving instance' declaration, + so you can specify the instance context yourself + When deriving the instance for (IArray UArray N) + +RolesIArray.hs:10:13: + Could not coerce from ?UArray i Word64? to ?UArray i N? + because the second type argument of ?UArray? has role Nominal, + but the arguments ?Word64? and ?N? differ + arising from the coercion of the method ?Data.Array.Base.numElements? + from type ?forall i. Ix i => UArray i Word64 -> Int? + to type ?forall i. Ix i => UArray i N -> Int? + Possible fix: + use a standalone 'deriving instance' declaration, + so you can specify the instance context yourself + When deriving the instance for (IArray UArray N) + +RolesIArray.hs:10:13: + Could not coerce from ?UArray i Word64? to ?UArray i N? + because the second type argument of ?UArray? has role Nominal, + but the arguments ?Word64? and ?N? differ + arising from the coercion of the method ?bounds? + from type ?forall i. Ix i => UArray i Word64 -> (i, i)? + to type ?forall i. Ix i => UArray i N -> (i, i)? + Possible fix: + use a standalone 'deriving instance' declaration, + so you can specify the instance context yourself + When deriving the instance for (IArray UArray N) diff --git a/testsuite/tests/roles/should_fail/all.T b/testsuite/tests/roles/should_fail/all.T index 1c69b7c..94674da 100644 --- a/testsuite/tests/roles/should_fail/all.T +++ b/testsuite/tests/roles/should_fail/all.T @@ -10,3 +10,4 @@ test('Roles12', test('T8773', normal, compile_fail, ['']) test('T9204', extra_clean(['T9204.o-boot', 'T9204.hi-boot']), run_command, ['$MAKE --no-print-directory -s T9204']) +test('RolesIArray', normal, compile_fail, ['']) From git at git.haskell.org Tue Nov 11 02:31:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 02:31:01 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9788 by giving `coerce` the right type. (8f78bd9) Message-ID: <20141111023101.DA6753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/8f78bd9e8394a3de02d326bd941fe3850254cf8f/ghc >--------------------------------------------------------------- commit 8f78bd9e8394a3de02d326bd941fe3850254cf8f Author: Richard Eisenberg Date: Mon Nov 10 20:41:38 2014 -0500 Fix #9788 by giving `coerce` the right type. No test case added, as the original mistake is just one level up from a typo. >--------------------------------------------------------------- 8f78bd9e8394a3de02d326bd941fe3850254cf8f compiler/basicTypes/MkId.lhs | 19 ++++++++----------- 1 file changed, 8 insertions(+), 11 deletions(-) diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index 9fc728b..b32a2b7 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -1146,17 +1146,14 @@ coerceId = pcMiscPrelId coerceName ty info where info = noCafIdInfo `setInlinePragInfo` alwaysInlinePragma `setUnfoldingInfo` mkCompulsoryUnfolding rhs - kv = kKiVar - k = mkTyVarTy kv - a:b:_ = tyVarList k - [aTy,bTy] = map mkTyVarTy [a,b] - eqRTy = mkTyConApp coercibleTyCon [k, aTy, bTy] - eqRPrimTy = mkTyConApp eqReprPrimTyCon [k, aTy, bTy] - ty = mkForAllTys [kv, a, b] (mkFunTys [eqRTy, aTy] bTy) - - [eqR,x,eq] = mkTemplateLocals [eqRTy, aTy,eqRPrimTy] - rhs = mkLams [kv,a,b,eqR,x] $ - mkWildCase (Var eqR) eqRTy bTy $ + eqRTy = mkTyConApp coercibleTyCon [liftedTypeKind, alphaTy, betaTy] + eqRPrimTy = mkTyConApp eqReprPrimTyCon [liftedTypeKind, alphaTy, betaTy] + ty = mkForAllTys [alphaTyVar, betaTyVar] $ + mkFunTys [eqRTy, alphaTy] betaTy + + [eqR,x,eq] = mkTemplateLocals [eqRTy, alphaTy, eqRPrimTy] + rhs = mkLams [alphaTyVar, betaTyVar, eqR, x] $ + mkWildCase (Var eqR) eqRTy betaTy $ [(DataAlt coercibleDataCon, [eq], Cast (Var x) (CoVarCo eq))] \end{code} From git at git.haskell.org Tue Nov 11 02:31:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 02:31:04 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9404 by removing tcInfExpr. (1393ea9) Message-ID: <20141111023104.A507C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/1393ea9387c3e69342799ef4f3b79f329329d8d5/ghc >--------------------------------------------------------------- commit 1393ea9387c3e69342799ef4f3b79f329329d8d5 Author: Richard Eisenberg Date: Mon Nov 10 21:27:58 2014 -0500 Fix #9404 by removing tcInfExpr. See the ticket for more info about the new algorithm. This is a small simplification, unifying the treatment of type checking in a few similar situations. >--------------------------------------------------------------- 1393ea9387c3e69342799ef4f3b79f329329d8d5 compiler/typecheck/TcExpr.lhs | 29 ++--------------- compiler/typecheck/TcMType.lhs | 7 ++-- compiler/typecheck/TcType.lhs | 4 ++- compiler/typecheck/TcUnify.lhs | 44 +++++++++++++++++++++++--- testsuite/tests/typecheck/should_compile/all.T | 4 +-- 5 files changed, 50 insertions(+), 38 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1393ea9387c3e69342799ef4f3b79f329329d8d5 From git at git.haskell.org Tue Nov 11 02:31:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 02:31:07 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9404 (typecheck/should_compile/T9404 and T9404b) (3df41d0) Message-ID: <20141111023107.CD6993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/3df41d065980a355e6c4698ccb2faf25ea2df7d2/ghc >--------------------------------------------------------------- commit 3df41d065980a355e6c4698ccb2faf25ea2df7d2 Author: Richard Eisenberg Date: Thu Aug 7 09:20:41 2014 -0400 Test #9404 (typecheck/should_compile/T9404 and T9404b) >--------------------------------------------------------------- 3df41d065980a355e6c4698ccb2faf25ea2df7d2 testsuite/tests/typecheck/should_compile/T9404.hs | 6 ++++++ testsuite/tests/typecheck/should_compile/T9404b.hs | 15 +++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 2 ++ 3 files changed, 23 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T9404.hs b/testsuite/tests/typecheck/should_compile/T9404.hs new file mode 100644 index 0000000..4cb530a --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9404.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE UnboxedTuples #-} + +module T9404 where + +foo _ = case seq () (# #) of (# #) -> () +foo2 _ = case () `seq` (# #) of (# #) -> () diff --git a/testsuite/tests/typecheck/should_compile/T9404b.hs b/testsuite/tests/typecheck/should_compile/T9404b.hs new file mode 100644 index 0000000..f9db0a3 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9404b.hs @@ -0,0 +1,15 @@ +{-# LANGUAGE RankNTypes, TypeFamilies #-} + +module T9404b where + +type family ListTF x where + ListTF x = [x] + +bar :: (forall x. ListTF x -> Int) -> () +bar _ = () + +myconst :: ((forall r. ListTF r -> Int) -> ()) -> x -> (forall r. ListTF r -> Int) -> () +myconst x _ = x + +foo = (bar `myconst` ()) $ length +foo2 = (myconst bar ()) $ length diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index a6cb78a..8448411 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -422,3 +422,5 @@ test('T8856', normal, compile, ['']) test('T9117', normal, compile, ['']) test('T9117_2', expect_broken('9117'), compile, ['']) test('T9708', normal, compile_fail, ['']) +test('T9404', expect_broken(9404), compile, ['']) +test('T9404b', expect_broken(9404), compile, ['']) From git at git.haskell.org Tue Nov 11 07:22:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 07:22:37 +0000 (UTC) Subject: [commit: ghc] master: Define list monad operations using comprehensions (4923cea) Message-ID: <20141111072237.C184F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4923cea56345060faaf77e4c475eac6aa3c77506/ghc >--------------------------------------------------------------- commit 4923cea56345060faaf77e4c475eac6aa3c77506 Author: David Feuer Date: Tue Nov 11 07:59:34 2014 +0100 Define list monad operations using comprehensions Define list monad operations using list comprehensions. Code using monad operations with lists did not fuse fully. Writing list code with `do` notation or `(>>=)` and `(>>)` operations could allocate more than equivalent code using list comprehensions. Define `mapM` directly, instead of using `sequence` and `map`. This leads to substantially less allocation in `cryptarithm2`. Addresses #9781 Reviewed By: ekmett, nomeata Differential Revision: https://phabricator.haskell.org/D455 >--------------------------------------------------------------- 4923cea56345060faaf77e4c475eac6aa3c77506 libraries/base/GHC/Base.hs | 51 +++++++++++++++++++++++++++++++++++++++------- 1 file changed, 44 insertions(+), 7 deletions(-) diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index 501a6d5..0d20e34 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -225,8 +225,32 @@ class Monoid a where mconcat = foldr mappend mempty instance Monoid [a] where + {-# INLINE mempty #-} mempty = [] + {-# INLINE mappend #-} mappend = (++) + {-# INLINE mconcat #-} + mconcat xss = [x | xs <- xss, x <- xs] +-- See Note: [List comprehensions and inlining] + +{- +Note: [List comprehensions and inlining] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The list monad operations are traditionally described in terms of concatMap: + +xs >>= f = concatMap f xs + +Similarly, mconcat for lists is just concat. Here in Base, however, we don't +have concatMap, and we'll refrain from adding it here so it won't have to be +hidden in imports. Instead, we use GHC's list comprehension desugaring +mechanism to define mconcat and the Applicative and Monad instances for lists. +We mark them INLINE because the inliner is not generally too keen to inline +build forms such as the ones these desugar to without our insistence. Defining +these using list comprehensions instead of foldr has an additional potential +benefit, as described in compiler/deSugar/DsListComp.lhs: if optimizations +needed to make foldr/build forms efficient are turned off, we'll get reasonably +efficient translations anyway. +-} instance Monoid b => Monoid (a -> b) where mempty _ = mempty @@ -501,7 +525,9 @@ sequence ms = foldr k (return []) ms -- | @'mapM' f@ is equivalent to @'sequence' . 'map' f at . mapM :: Monad m => (a -> m b) -> [a] -> m [b] {-# INLINE mapM #-} -mapM f as = sequence (map f as) +mapM f as = foldr k (return []) as + where + k a r = do { x <- f a; xs <- r; return (x:xs) } -- | Promote a function to a monad. liftM :: (Monad m) => (a1 -> r) -> m a1 -> m r @@ -667,16 +693,27 @@ instance MonadPlus Maybe -- The list type instance Functor [] where + {-# INLINE fmap #-} fmap = map +-- See Note: [List comprehensions and inlining] instance Applicative [] where - pure = return - (<*>) = ap - -instance Monad [] where - m >>= k = foldr ((++) . k) [] m - m >> k = foldr ((++) . (\ _ -> k)) [] m + {-# INLINE pure #-} + pure x = [x] + {-# INLINE (<*>) #-} + fs <*> xs = [f x | f <- fs, x <- xs] + {-# INLINE (*>) #-} + xs *> ys = [y | _ <- xs, y <- ys] + +-- See Note: [List comprehensions and inlining] +instance Monad [] where + {-# INLINE (>>=) #-} + xs >>= f = [y | x <- xs, y <- f x] + {-# INLINE (>>) #-} + (>>) = (*>) + {-# INLINE return #-} return x = [x] + {-# INLINE fail #-} fail _ = [] instance Alternative [] where From git at git.haskell.org Tue Nov 11 08:06:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 08:06:52 +0000 (UTC) Subject: [commit: ghc] master: De-bias Data.Foldable and improve docstrings (e567130) Message-ID: <20141111080652.A2C573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e56713024e1bfbb7892986800afd9944731b2aa1/ghc >--------------------------------------------------------------- commit e56713024e1bfbb7892986800afd9944731b2aa1 Author: David Feuer Date: Tue Nov 11 08:35:37 2014 +0100 De-bias Data.Foldable and improve docstrings Use fewer left/right-biased folds for defaults and functions in `Data.Foldable`, to better support things that don't look like cons lists. This also extends the Haddock docstrings in `Data.Foldable`. Reviewed By: hvr, ekmett Differential Revision: https://phabricator.haskell.org/D441 >--------------------------------------------------------------- e56713024e1bfbb7892986800afd9944731b2aa1 libraries/base/Data/Foldable.hs | 158 +++++++++++++++++++++++++++++++++------- 1 file changed, 132 insertions(+), 26 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e56713024e1bfbb7892986800afd9944731b2aa1 From git at git.haskell.org Tue Nov 11 10:31:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 10:31:55 +0000 (UTC) Subject: [commit: ghc] wip/T5462: Error message tweaks (4ecc2de) Message-ID: <20141111103155.854113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T5462 Link : http://ghc.haskell.org/trac/ghc/changeset/4ecc2deed3160673c334366517057c0d5dd92f77/ghc >--------------------------------------------------------------- commit 4ecc2deed3160673c334366517057c0d5dd92f77 Author: Jose Pedro Magalhaes Date: Tue Nov 11 10:32:17 2014 +0000 Error message tweaks >--------------------------------------------------------------- 4ecc2deed3160673c334366517057c0d5dd92f77 compiler/typecheck/TcDeriv.lhs | 27 +++++++++++++++++++-------- compiler/typecheck/TcGenDeriv.lhs | 19 +++++++------------ testsuite/tests/generics/T5462No1.hs | 4 +++- testsuite/tests/generics/T5462No1.stderr | 7 ++++--- testsuite/tests/generics/T5462No2.hs | 10 +++++++--- testsuite/tests/generics/T5462No2.stderr | 12 ++++++------ 6 files changed, 46 insertions(+), 33 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4ecc2deed3160673c334366517057c0d5dd92f77 From git at git.haskell.org Tue Nov 11 12:16:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 12:16:23 +0000 (UTC) Subject: [commit: ghc] branch 'wip/tc-plugins-amg' created Message-ID: <20141111121623.B43AD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/tc-plugins-amg Referencing: be95bd9179ea073dae4376a6ac29130a4edc9e00 From git at git.haskell.org Tue Nov 11 12:16:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 12:16:26 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins-amg: Move withTcPlugins to TcRnDriver, removing need for hs-boot file (1ed1e63) Message-ID: <20141111121626.5CD973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins-amg Link : http://ghc.haskell.org/trac/ghc/changeset/1ed1e63906e99f9b74fb2629af01bfac04e3c6bb/ghc >--------------------------------------------------------------- commit 1ed1e63906e99f9b74fb2629af01bfac04e3c6bb Author: Adam Gundry Date: Tue Nov 11 09:47:01 2014 +0000 Move withTcPlugins to TcRnDriver, removing need for hs-boot file This makes the caller of initTc responsible for loading plugins if required, rather than passing a boolean flag indicating whether to load them. Hence withTcPlugins can move to TcRnDriver, avoiding the need for DynamicLoading.hs-boot. >--------------------------------------------------------------- 1ed1e63906e99f9b74fb2629af01bfac04e3c6bb compiler/ghc.mk | 12 +---- compiler/ghci/RtClosureInspect.hs | 2 +- compiler/main/DynamicLoading.hs-boot | 12 ----- compiler/typecheck/TcRnDriver.lhs | 79 +++++++++++++++++++++++++++-- compiler/typecheck/TcRnMonad.lhs | 96 ++++-------------------------------- 5 files changed, 88 insertions(+), 113 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1ed1e63906e99f9b74fb2629af01bfac04e3c6bb From git at git.haskell.org Tue Nov 11 12:16:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 12:16:29 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins-amg: Move core2core plugins to a new module Plugins (ce850aa) Message-ID: <20141111121629.4CE423A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins-amg Link : http://ghc.haskell.org/trac/ghc/changeset/ce850aaba222c44d983cc13df21ca3365b2fdd19/ghc >--------------------------------------------------------------- commit ce850aaba222c44d983cc13df21ca3365b2fdd19 Author: Adam Gundry Date: Tue Nov 11 10:22:15 2014 +0000 Move core2core plugins to a new module Plugins >--------------------------------------------------------------- ce850aaba222c44d983cc13df21ca3365b2fdd19 compiler/ghc.cabal.in | 1 + compiler/main/DynamicLoading.hs | 42 ++++++++++++++++++++++++++++++++++++++-- compiler/main/GhcPlugins.hs | 7 ++++--- compiler/main/Plugins.hs | 31 +++++++++++++++++++++++++++++ compiler/prelude/PrelNames.lhs | 6 +++--- compiler/simplCore/CoreMonad.lhs | 27 +------------------------- compiler/simplCore/SimplCore.lhs | 39 ++----------------------------------- 7 files changed, 82 insertions(+), 71 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ce850aaba222c44d983cc13df21ca3365b2fdd19 From git at git.haskell.org Tue Nov 11 12:16:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 12:16:32 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins-amg: Make TcPlugin part of Plugin so we can eliminate -ftc-plugin (be95bd9) Message-ID: <20141111121632.0B75A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins-amg Link : http://ghc.haskell.org/trac/ghc/changeset/be95bd9179ea073dae4376a6ac29130a4edc9e00/ghc >--------------------------------------------------------------- commit be95bd9179ea073dae4376a6ac29130a4edc9e00 Author: Adam Gundry Date: Tue Nov 11 11:25:50 2014 +0000 Make TcPlugin part of Plugin so we can eliminate -ftc-plugin >--------------------------------------------------------------- be95bd9179ea073dae4376a6ac29130a4edc9e00 compiler/main/DynFlags.hs | 16 ++++++--------- compiler/main/DynamicLoading.hs | 18 +++++++++++------ compiler/main/Plugins.hs | 4 ++++ compiler/simplCore/SimplCore.lhs | 5 +---- compiler/typecheck/TcRnDriver.lhs | 41 +++++++-------------------------------- compiler/typecheck/TcRnTypes.lhs | 2 +- 6 files changed, 31 insertions(+), 55 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc be95bd9179ea073dae4376a6ac29130a4edc9e00 From git at git.haskell.org Tue Nov 11 13:05:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 13:05:35 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T8584.spj' deleted Message-ID: <20141111130535.9771C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T8584.spj From git at git.haskell.org Tue Nov 11 13:05:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 13:05:46 +0000 (UTC) Subject: [commit: ghc] wip/T8584: tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures (068695e) Message-ID: <20141111130546.668083A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/068695e4150680506ed3feb8f608b48200bf7522/ghc >--------------------------------------------------------------- commit 068695e4150680506ed3feb8f608b48200bf7522 Author: Dr. ERDI Gergo Date: Sun Jul 27 14:10:34 2014 +0200 tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures >--------------------------------------------------------------- 068695e4150680506ed3feb8f608b48200bf7522 compiler/typecheck/TcBinds.lhs | 52 +++++++-- compiler/typecheck/TcClassDcl.lhs | 4 +- compiler/typecheck/TcPat.lhs | 23 +++- compiler/typecheck/TcPatSyn.lhs | 199 ++++++++++++++++++++++++++--------- compiler/typecheck/TcPatSyn.lhs-boot | 9 +- 5 files changed, 223 insertions(+), 64 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 068695e4150680506ed3feb8f608b48200bf7522 From git at git.haskell.org Tue Nov 11 13:05:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 13:05:49 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add parser for pattern synonym type signatures. Syntax is of the form (8c74ee9) Message-ID: <20141111130549.149CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/8c74ee9f6fc68414426440db6752725754b93dc1/ghc >--------------------------------------------------------------- commit 8c74ee9f6fc68414426440db6752725754b93dc1 Author: Dr. ERDI Gergo Date: Tue Nov 11 18:54:14 2014 +0800 Add parser for pattern synonym type signatures. Syntax is of the form pattern P :: (Prov b) => (Req a) => a -> b -> Int -> T a which declares a pattern synonym called `P`, with argument types `a`, `b`, and `Int`, and result type `T a`, with provided context `(Prov b)` and required context `(Req a)`. >--------------------------------------------------------------- 8c74ee9f6fc68414426440db6752725754b93dc1 compiler/parser/Parser.y | 51 +++++++++++++++++++++++++++++++-------------- compiler/parser/RdrHsSyn.hs | 27 +++++------------------- 2 files changed, 40 insertions(+), 38 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 1123375..0cceb09 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -860,29 +860,47 @@ role : VARID { sL1 $1 $ Just $ getVARID $1 } -- Glasgow extension: pattern synonyms pattern_synonym_decl :: { LHsDecl RdrName } - : 'pattern' pat '=' pat - {% do { (name, args) <- splitPatSyn $2 - ; return $ sLL $1 $> . ValD $ mkPatSynBind name args $4 ImplicitBidirectional - }} - | 'pattern' pat '<-' pat - {% do { (name, args) <- splitPatSyn $2 - ; return $ sLL $1 $> . ValD $ mkPatSynBind name args $4 Unidirectional - }} - | 'pattern' pat '<-' pat where_decls - {% do { (name, args) <- splitPatSyn $2 - ; mg <- toPatSynMatchGroup name $5 + : 'pattern' pattern_synonym_lhs '=' pat + { let (name, args) = $2 + in sLL $1 $> . ValD $ mkPatSynBind name args $4 ImplicitBidirectional } + | 'pattern' pattern_synonym_lhs '<-' pat + { let (name, args) = $2 + in sLL $1 $> . ValD $ mkPatSynBind name args $4 Unidirectional } + | 'pattern' pattern_synonym_lhs '<-' pat where_decls + {% do { let (name, args) = $2 + ; mg <- mkPatSynMatchGroup name $5 ; return $ sLL $1 $> . ValD $ - mkPatSynBind name args $4 (ExplicitBidirectional mg) - }} + mkPatSynBind name args $4 (ExplicitBidirectional mg) }} -where_decls :: { Located (OrdList (LHsDecl RdrName)) } - : 'where' '{' decls '}' { $3 } - | 'where' vocurly decls close { $3 } +pattern_synonym_lhs :: { (Located RdrName, HsPatSynDetails (Located RdrName)) } + : con vars0 { ($1, PrefixPatSyn $2) } + | varid consym varid { ($2, InfixPatSyn $1 $3) } vars0 :: { [Located RdrName] } : {- empty -} { [] } | varid vars0 { $1 : $2 } +where_decls :: { Located (OrdList (LHsDecl RdrName)) } + : 'where' '{' decls '}' { $3 } + | 'where' vocurly decls close { $3 } + +pattern_synonym_sig :: { LSig RdrName } + : 'pattern' con '::' ptype + { let (flag, qtvs, prov, req, ty) = unLoc $4 + in sLL $1 $> $ PatSynSig $2 (flag, mkHsQTvs qtvs) prov req ty } + +ptype :: { Located (HsExplicitFlag, [LHsTyVarBndr RdrName], LHsContext RdrName, LHsContext RdrName, LHsType RdrName) } + : 'forall' tv_bndrs '.' ptype + {% do { hintExplicitForall (getLoc $1) + ; let (_, qtvs', prov, req, ty) = unLoc $4 + ; return $ sLL $1 $> (Explicit, $2 ++ qtvs', prov, req ,ty) }} + | context '=>' context '=>' type + { sLL $1 $> (Implicit, [], $1, $3, $5) } + | context '=>' type + { sLL $1 $> (Implicit, [], $1, noLoc [], $3) } + | type + { sL1 $1 (Implicit, [], noLoc [], noLoc [], $1) } + ----------------------------------------------------------------------------- -- Nested declarations @@ -1490,6 +1508,7 @@ sigdecl :: { Located (OrdList (LHsDecl RdrName)) } { sLL $1 $> $ toOL [ sLL $1 $> $ SigD (TypeSig ($1 : reverse (unLoc $3)) $5) ] } | infix prec ops { sLL $1 $> $ toOL [ sLL $1 $> $ SigD (FixSig (FixitySig n (Fixity $2 (unLoc $1)))) | n <- unLoc $3 ] } + | pattern_synonym_sig { sLL $1 $> $ unitOL $ sLL $1 $> . SigD . unLoc $ $1 } | '{-# INLINE' activation qvar '#-}' { sLL $1 $> $ unitOL (sLL $1 $> $ SigD (InlineSig $3 (mkInlinePragma (getINLINE $1) $2))) } | '{-# SPECIALISE' activation qvar '::' sigtypes1 '#-}' diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs index 625c4dc..e945e43 100644 --- a/compiler/parser/RdrHsSyn.hs +++ b/compiler/parser/RdrHsSyn.hs @@ -18,7 +18,7 @@ module RdrHsSyn ( mkTyFamInst, mkFamDecl, splitCon, mkInlinePragma, - splitPatSyn, toPatSynMatchGroup, + mkPatSynMatchGroup, mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp mkTyClD, mkInstD, @@ -414,33 +414,16 @@ splitCon ty mk_rest [L _ (HsRecTy flds)] = RecCon flds mk_rest ts = PrefixCon ts -splitPatSyn :: LPat RdrName - -> P (Located RdrName, HsPatSynDetails (Located RdrName)) -splitPatSyn (L _ (ParPat pat)) = splitPatSyn pat -splitPatSyn pat@(L loc (ConPatIn con details)) = do - details' <- case details of - PrefixCon pats -> liftM PrefixPatSyn (mapM patVar pats) - InfixCon pat1 pat2 -> liftM2 InfixPatSyn (patVar pat1) (patVar pat2) - RecCon{} -> recordPatSynErr loc pat - return (con, details') - where - patVar :: LPat RdrName -> P (Located RdrName) - patVar (L loc (VarPat v)) = return $ L loc v - patVar (L _ (ParPat pat)) = patVar pat - patVar (L loc pat) = parseErrorSDoc loc $ - text "Pattern synonym arguments must be variable names:" $$ - ppr pat -splitPatSyn pat@(L loc _) = parseErrorSDoc loc $ - text "invalid pattern synonym declaration:" $$ ppr pat - recordPatSynErr :: SrcSpan -> LPat RdrName -> P a recordPatSynErr loc pat = parseErrorSDoc loc $ text "record syntax not supported for pattern synonym declarations:" $$ ppr pat -toPatSynMatchGroup :: Located RdrName -> Located (OrdList (LHsDecl RdrName)) -> P (MatchGroup RdrName (LHsExpr RdrName)) -toPatSynMatchGroup (L _ patsyn_name) (L _ decls) = +mkPatSynMatchGroup :: Located RdrName + -> Located (OrdList (LHsDecl RdrName)) + -> P (MatchGroup RdrName (LHsExpr RdrName)) +mkPatSynMatchGroup (L _ patsyn_name) (L _ decls) = do { matches <- mapM fromDecl (fromOL decls) ; return $ mkMatchGroup FromSource matches } where From git at git.haskell.org Tue Nov 11 13:05:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 13:05:51 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Renamer for PatSynSigs: handle type variable bindings (0276534) Message-ID: <20141111130551.C06963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/0276534ce117d77e75d92d57136716ee57e3392f/ghc >--------------------------------------------------------------- commit 0276534ce117d77e75d92d57136716ee57e3392f Author: Dr. ERDI Gergo Date: Fri Nov 7 19:29:06 2014 +0800 Renamer for PatSynSigs: handle type variable bindings >--------------------------------------------------------------- 0276534ce117d77e75d92d57136716ee57e3392f compiler/hsSyn/HsBinds.lhs | 8 ++++---- compiler/rename/RnBinds.lhs | 34 ++++++++++++++++------------------ 2 files changed, 20 insertions(+), 22 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index bbf6bc2..23534cf 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -568,12 +568,12 @@ data Sig name TypeSig [Located name] (LHsType name) -- | A pattern synonym type signature - -- @pattern (Eq b) => P a b :: (Num a) => T a + -- @pattern type forall b. (Eq b) => P a b :: forall a. (Num a) => T a | PatSynSig (Located name) (HsPatSynDetails (LHsType name)) (LHsType name) -- Type - (LHsContext name) -- Provided context - (LHsContext name) -- Required contex + (HsExplicitFlag, LHsTyVarBndrs name, LHsContext name) -- Provided context + (HsExplicitFlag, LHsTyVarBndrs name, LHsContext name) -- Required contex -- | A type signature for a default method inside a class -- @@ -730,7 +730,7 @@ ppr_sig (SpecSig var ty inl) = pragBrackets (pprSpec (unLoc var) (ppr ty) i ppr_sig (InlineSig var inl) = pragBrackets (ppr inl <+> pprPrefixOcc (unLoc var)) ppr_sig (SpecInstSig ty) = pragBrackets (ptext (sLit "SPECIALIZE instance") <+> ppr ty) ppr_sig (MinimalSig bf) = pragBrackets (pprMinimalSig bf) -ppr_sig (PatSynSig name arg_tys ty prov req) +ppr_sig (PatSynSig name arg_tys ty (_, _, prov) (_, _, req)) = pprPatSynSig (unLoc name) False args (ppr ty) (pprCtx prov) (pprCtx req) where args = fmap ppr arg_tys diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index c2489cb..b43993e 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -30,7 +30,7 @@ import {-# SOURCE #-} RnExpr( rnLExpr, rnStmts ) import HsSyn import TcRnMonad import TcEvidence ( emptyTcEvBinds ) -import RnTypes ( bindSigTyVarsFV, rnHsSigType, rnLHsType, checkPrecMatch, rnContext ) +import RnTypes import RnPat import RnNames import RnEnv @@ -841,23 +841,21 @@ renameSig ctxt sig@(MinimalSig bf) = do new_bf <- traverse (lookupSigOccRn ctxt sig) bf return (MinimalSig new_bf, emptyFVs) -renameSig ctxt sig@(PatSynSig v args ty prov req) - = do v' <- lookupSigOccRn ctxt sig v - let doc = quotes (ppr v) - rn_type = rnHsSigType doc - (ty', fvs1) <- rn_type ty - (args', fvs2) <- case args of - PrefixPatSyn tys -> - do (tys, fvs) <- unzip <$> mapM rn_type tys - return (PrefixPatSyn tys, plusFVs fvs) - InfixPatSyn left right -> - do (left', fvs1) <- rn_type left - (right', fvs2) <- rn_type right - return (InfixPatSyn left' right', fvs1 `plusFV` fvs2) - (prov', fvs3) <- rnContext (TypeSigCtx doc) prov - (req', fvs4) <- rnContext (TypeSigCtx doc) req - let fvs = plusFVs [fvs1, fvs2, fvs3, fvs4] - return (PatSynSig v' args' ty' prov' req', fvs) +renameSig ctxt sig@(PatSynSig v (flag, qtvs) prov req ty) + = do { v' <- lookupSigOccRn ctxt sig v + ; let doc = TypeSigCtx $ quotes (ppr v) + ; loc <- getSrcSpanM + + ; let (tv_kvs, tvs) = extractHsTysRdrTyVars (ty:unLoc prov ++ unLoc req) + ; let tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ tvs + + ; bindHsTyVars doc Nothing tv_kvs tv_bndrs $ \ tyvars -> do + { (prov', fvs1) <- rnContext doc prov + ; (req', fvs2) <- rnContext doc req + ; (ty', fvs3) <- rnLHsType doc ty + + ; let fvs = plusFVs [fvs1, fvs2, fvs3] + ; return (PatSynSig v' (flag, tyvars) prov' req' ty', fvs) }} ppr_sig_bndrs :: [Located RdrName] -> SDoc ppr_sig_bndrs bs = quotes (pprWithCommas ppr bs) From git at git.haskell.org Tue Nov 11 13:05:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 13:05:54 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Update baseline shift/reduce conflict number (70a5606) Message-ID: <20141111130554.6FAFE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/70a5606a0a154803ed6ba1380d92f4ee29ddcc1c/ghc >--------------------------------------------------------------- commit 70a5606a0a154803ed6ba1380d92f4ee29ddcc1c Author: Dr. ERDI Gergo Date: Wed Jul 2 19:18:43 2014 +0800 Update baseline shift/reduce conflict number >--------------------------------------------------------------- 70a5606a0a154803ed6ba1380d92f4ee29ddcc1c compiler/parser/Parser.y | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 2e1b777..1123375 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -86,6 +86,12 @@ import TysWiredIn ( unitTyCon, unitDataCon, tupleTyCon, tupleCon, nilDataC {- ----------------------------------------------------------------------------- +25 June 2014 + +Conflicts: 47 shift/reduce + 1 reduce/reduce + +----------------------------------------------------------------------------- 12 October 2012 Conflicts: 43 shift/reduce From git at git.haskell.org Tue Nov 11 13:05:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 13:05:57 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Use user-supplied type variables (when available) in pattern synonym type signatures (282fb3a) Message-ID: <20141111130557.1CF6A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/282fb3a985c9ee76f562a733d401c90446576b34/ghc >--------------------------------------------------------------- commit 282fb3a985c9ee76f562a733d401c90446576b34 Author: Dr. ERDI Gergo Date: Sun Nov 9 15:46:46 2014 +0800 Use user-supplied type variables (when available) in pattern synonym type signatures >--------------------------------------------------------------- 282fb3a985c9ee76f562a733d401c90446576b34 compiler/rename/RnBinds.lhs | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index b43993e..80239e9 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -846,8 +846,16 @@ renameSig ctxt sig@(PatSynSig v (flag, qtvs) prov req ty) ; let doc = TypeSigCtx $ quotes (ppr v) ; loc <- getSrcSpanM - ; let (tv_kvs, tvs) = extractHsTysRdrTyVars (ty:unLoc prov ++ unLoc req) - ; let tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ tvs + ; let (tv_kvs, mentioned) = extractHsTysRdrTyVars (ty:unLoc prov ++ unLoc req) + ; tv_bndrs <- case flag of + Implicit -> + return $ mkHsQTvs . userHsTyVarBndrs loc $ mentioned + Explicit -> + do { let heading = ptext (sLit "In the pattern synonym type signature") + <+> quotes (ppr sig) + ; warnUnusedForAlls (heading $$ docOfHsDocContext doc) qtvs mentioned + ; return qtvs } + Qualified -> panic "renameSig: Qualified" ; bindHsTyVars doc Nothing tv_kvs tv_bndrs $ \ tyvars -> do { (prov', fvs1) <- rnContext doc prov From git at git.haskell.org Tue Nov 11 13:05:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 13:05:59 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Change output of ':i' for pattern synonyms to be in sync with new syntax (c6d4d04) Message-ID: <20141111130559.C6BEA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/c6d4d040551c88ea48aa64e23853b7ee7f65ae56/ghc >--------------------------------------------------------------- commit c6d4d040551c88ea48aa64e23853b7ee7f65ae56 Author: Dr. ERDI Gergo Date: Sun Aug 3 15:26:13 2014 +0200 Change output of ':i' for pattern synonyms to be in sync with new syntax >--------------------------------------------------------------- c6d4d040551c88ea48aa64e23853b7ee7f65ae56 compiler/hsSyn/HsBinds.lhs | 52 +++++++++++++++++++------------------------- compiler/hsSyn/HsTypes.lhs | 16 +++++++++----- compiler/iface/IfaceSyn.lhs | 19 ++++++---------- compiler/iface/IfaceType.lhs | 15 ++++++++----- 4 files changed, 49 insertions(+), 53 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c6d4d040551c88ea48aa64e23853b7ee7f65ae56 From git at git.haskell.org Tue Nov 11 13:06:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 13:06:02 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add test cases (1d67ee5) Message-ID: <20141111130602.F0AB83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/1d67ee59a89eff0add62179e3d9fd244c753fddc/ghc >--------------------------------------------------------------- commit 1d67ee59a89eff0add62179e3d9fd244c753fddc Author: Dr. ERDI Gergo Date: Sun Nov 2 14:35:49 2014 +0800 Add test cases >--------------------------------------------------------------- 1d67ee59a89eff0add62179e3d9fd244c753fddc testsuite/tests/patsyn/should_compile/T8584-1.hs | 10 ++++++++++ testsuite/tests/patsyn/should_compile/T8968-1.hs | 8 ++++++++ testsuite/tests/patsyn/should_compile/all.T | 2 ++ 3 files changed, 20 insertions(+) diff --git a/testsuite/tests/patsyn/should_compile/T8584-1.hs b/testsuite/tests/patsyn/should_compile/T8584-1.hs new file mode 100644 index 0000000..7a017c8 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8584-1.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms #-} +module ShouldCompile where + +pattern type (Eq a) => Single a :: (Show a) => [a] +-- pattern type Single a :: (Eq a, Show a) => [a] +-- pattern type Single a :: [a] +pattern Single x = [x] + +-- f :: (Show a) => [a] -> a +foobar (Single x) = x diff --git a/testsuite/tests/patsyn/should_compile/T8968-1.hs b/testsuite/tests/patsyn/should_compile/T8968-1.hs new file mode 100644 index 0000000..f4a1dc4 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8968-1.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE GADTs, KindSignatures, PatternSynonyms #-} +module ShouldCompile where + +data X :: (* -> *) -> * -> * where + Y :: f a -> X f (Maybe a) + +pattern type C a :: X Maybe (Maybe a) +pattern C x = Y (Just x) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index d851bc3..8896008 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -10,3 +10,5 @@ test('incomplete', normal, compile, ['']) test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) +test('T8968-1', normal, compile, ['']) +test('T8584-1', normal, compile, ['']) From git at git.haskell.org Tue Nov 11 13:10:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 13:10:13 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #9662 (ed57ea4) Message-ID: <20141111131013.2AE213A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ed57ea499958824e82c111bd53a69129a8178659/ghc >--------------------------------------------------------------- commit ed57ea499958824e82c111bd53a69129a8178659 Author: Simon Peyton Jones Date: Tue Nov 11 11:35:48 2014 +0000 Test Trac #9662 >--------------------------------------------------------------- ed57ea499958824e82c111bd53a69129a8178659 .../tests/indexed-types/should_compile/T9662.hs | 53 ++++++++++++++++++++++ testsuite/tests/indexed-types/should_fail/T9662.hs | 53 ++++++++++++++++++++++ testsuite/tests/indexed-types/should_fail/all.T | 1 + 3 files changed, 107 insertions(+) diff --git a/testsuite/tests/indexed-types/should_compile/T9662.hs b/testsuite/tests/indexed-types/should_compile/T9662.hs new file mode 100644 index 0000000..2972eca --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T9662.hs @@ -0,0 +1,53 @@ +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE FlexibleContexts #-} + +module T9662 where + +data Exp a = Exp +data (a:.b) = a:.b + +type family Plain e :: * +type instance Plain (Exp a) = a +type instance Plain (a:.b) = Plain a :. Plain b + +class (Plain (Unlifted pattern) ~ Tuple pattern) => Unlift pattern where + type Unlifted pattern + type Tuple pattern + +modify :: (Unlift pattern) => + pattern -> + (Unlifted pattern -> a) -> + Exp (Tuple pattern) -> Exp (Plain a) +modify p f = undefined + + +data Atom a = Atom + +atom :: Atom a +atom = Atom + + +instance (Unlift pa, int ~ Atom Int) => Unlift (pa :. int) where + type Unlifted (pa :. int) = Unlifted pa :. Exp Int + type Tuple (pa :. int) = Tuple pa :. Int + + +data Shape sh = Shape + +backpermute :: + (Exp sh -> Exp sh') -> + (Exp sh' -> Exp sh) -> + Shape sh -> Shape sh' +backpermute = undefined + +test :: Shape (sh:.k:.m:.n) -> Shape (sh:.m:.n:.k) +test = + backpermute + (modify (atom:.atom:.atom:.atom) + (\(sh:.k:.m:.n) -> (sh:.m:.n:.k))) + id + +-- With this arg instead of just 'id', it worked +-- (modify (atom:.atom:.atom:.atom) +-- (\(ix:.m:.n:.k) -> (ix:.k:.m:.n))) diff --git a/testsuite/tests/indexed-types/should_fail/T9662.hs b/testsuite/tests/indexed-types/should_fail/T9662.hs new file mode 100644 index 0000000..2972eca --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T9662.hs @@ -0,0 +1,53 @@ +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE FlexibleContexts #-} + +module T9662 where + +data Exp a = Exp +data (a:.b) = a:.b + +type family Plain e :: * +type instance Plain (Exp a) = a +type instance Plain (a:.b) = Plain a :. Plain b + +class (Plain (Unlifted pattern) ~ Tuple pattern) => Unlift pattern where + type Unlifted pattern + type Tuple pattern + +modify :: (Unlift pattern) => + pattern -> + (Unlifted pattern -> a) -> + Exp (Tuple pattern) -> Exp (Plain a) +modify p f = undefined + + +data Atom a = Atom + +atom :: Atom a +atom = Atom + + +instance (Unlift pa, int ~ Atom Int) => Unlift (pa :. int) where + type Unlifted (pa :. int) = Unlifted pa :. Exp Int + type Tuple (pa :. int) = Tuple pa :. Int + + +data Shape sh = Shape + +backpermute :: + (Exp sh -> Exp sh') -> + (Exp sh' -> Exp sh) -> + Shape sh -> Shape sh' +backpermute = undefined + +test :: Shape (sh:.k:.m:.n) -> Shape (sh:.m:.n:.k) +test = + backpermute + (modify (atom:.atom:.atom:.atom) + (\(sh:.k:.m:.n) -> (sh:.m:.n:.k))) + id + +-- With this arg instead of just 'id', it worked +-- (modify (atom:.atom:.atom:.atom) +-- (\(ix:.m:.n:.k) -> (ix:.k:.m:.n))) diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index f06060e..0fbee70 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -129,4 +129,5 @@ test('T9371', normal, compile_fail, ['']) test('T9433', normal, compile_fail, ['']) test('BadSock', normal, compile_fail, ['']) test('T9580', normal, multimod_compile_fail, ['T9580', '']) +test('T9662', normal, compile_fail, ['']) From git at git.haskell.org Tue Nov 11 13:10:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 13:10:10 +0000 (UTC) Subject: [commit: ghc] master: Comments only (on recursive dictionaries) (97420b0) Message-ID: <20141111131010.2C9FA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/97420b053a3d05a347a5ce38978252bd5ad2f854/ghc >--------------------------------------------------------------- commit 97420b053a3d05a347a5ce38978252bd5ad2f854 Author: Simon Peyton Jones Date: Tue Nov 11 10:27:51 2014 +0000 Comments only (on recursive dictionaries) >--------------------------------------------------------------- 97420b053a3d05a347a5ce38978252bd5ad2f854 compiler/typecheck/TcInstDcls.lhs | 15 ++++--- compiler/typecheck/TcInteract.lhs | 83 ++++++++++++++++++++++----------------- 2 files changed, 58 insertions(+), 40 deletions(-) diff --git a/compiler/typecheck/TcInstDcls.lhs b/compiler/typecheck/TcInstDcls.lhs index ddb2e65..b6c0da1 100644 --- a/compiler/typecheck/TcInstDcls.lhs +++ b/compiler/typecheck/TcInstDcls.lhs @@ -1009,23 +1009,28 @@ superclass is bottom when it should not be. Consider the following (extreme) situation: class C a => D a where ... - instance D [a] => D [a] where ... + instance D [a] => D [a] where ... (dfunD) + instance C [a] => C [a] where ... (dfunC) Although this looks wrong (assume D [a] to prove D [a]), it is only a more extreme case of what happens with recursive dictionaries, and it can, just about, make sense because the methods do some work before recursing. -To implement the dfun we must generate code for the superclass C [a], +To implement the dfunD we must generate code for the superclass C [a], which we had better not get by superclass selection from the supplied argument: - dfun :: forall a. D [a] -> D [a] - dfun = \d::D [a] -> MkD (scsel d) .. + dfunD :: forall a. D [a] -> D [a] + dfunD = \d::D [a] -> MkD (scsel d) .. Otherwise if we later encounter a situation where we have a [Wanted] dw::D [a] we might solve it thus: - dw := dfun dw + dw := dfunD dw Which is all fine except that now ** the superclass C is bottom **! +The instance we want is: + dfunD :: forall a. D [a] -> D [a] + dfunD = \d::D [a] -> MkD (dfunC (scsel d)) ... + THE SOLUTION Our solution to this problem "silent superclass arguments". We pass diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 6fbed77..3501a99 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -1087,56 +1087,69 @@ Consider generating the superclasses of the instance declaration instance Foo a => Foo [a] So our problem is this - d0 :_g Foo t - d1 :_w Data Maybe [t] + [G] d0 : Foo t + [W] d1 : Data Maybe [t] -- Desired superclass We may add the given in the inert set, along with its superclasses [assuming we don't fail because there is a matching instance, see topReactionsStage, given case ] Inert: - d0 :_g Foo t + [G] d0 : Foo t + [G] d01 : Data Maybe t -- Superclass of d0 WorkList - d01 :_g Data Maybe t -- d2 := EvDictSuperClass d0 0 - d1 :_w Data Maybe [t] -Then d2 can readily enter the inert, and we also do solving of the wanted + [W] d1 : Data Maybe [t] + +Solve d1 using instance dfunData2; d1 := dfunData2 d2 d3 Inert: - d0 :_g Foo t - d1 :_s Data Maybe [t] d1 := dfunData2 d2 d3 + [G] d0 : Foo t + [G] d01 : Data Maybe t -- Superclass of d0 + Solved: + d1 : Data Maybe [t] WorkList - d2 :_w Sat (Maybe [t]) - d3 :_w Data Maybe t - d01 :_g Data Maybe t -Now, we may simplify d2 more: + [W] d2 : Sat (Maybe [t]) + [W] d3 : Data Maybe t + +Now, we may simplify d2 using dfunSat; d2 := dfunSat d4 Inert: - d0 :_g Foo t - d1 :_s Data Maybe [t] d1 := dfunData2 d2 d3 - d1 :_g Data Maybe [t] - d2 :_g Sat (Maybe [t]) d2 := dfunSat d4 + [G] d0 : Foo t + [G] d01 : Data Maybe t -- Superclass of d0 + Solved: + d1 : Data Maybe [t] + d2 : Sat (Maybe [t]) WorkList: - d3 :_w Data Maybe t - d4 :_w Foo [t] - d01 :_g Data Maybe t + [W] d3 : Data Maybe t + [W] d4 : Foo [t] -Now, we can just solve d3. +Now, we can just solve d3 from d01; d3 := d01 Inert - d0 :_g Foo t - d1 :_s Data Maybe [t] d1 := dfunData2 d2 d3 - d2 :_g Sat (Maybe [t]) d2 := dfunSat d4 + [G] d0 : Foo t + [G] d01 : Data Maybe t -- Superclass of d0 + Solved: + d1 : Data Maybe [t] + d2 : Sat (Maybe [t]) WorkList - d4 :_w Foo [t] - d01 :_g Data Maybe t -And now we can simplify d4 again, but since it has superclasses we *add* them to the worklist: + [W] d4 : Foo [t] + +Now, solve d4 using dfunFoo2; d4 := dfunFoo2 d5 Inert - d0 :_g Foo t - d1 :_s Data Maybe [t] d1 := dfunData2 d2 d3 - d2 :_g Sat (Maybe [t]) d2 := dfunSat d4 - d4 :_g Foo [t] d4 := dfunFoo2 d5 + [G] d0 : Foo t + [G] d01 : Data Maybe t -- Superclass of d0 + Solved: + d1 : Data Maybe [t] + d2 : Sat (Maybe [t]) + d4 : Foo [t] WorkList: - d5 :_w Foo t - d6 :_g Data Maybe [t] d6 := EvDictSuperClass d4 0 - d01 :_g Data Maybe t -Now, d5 can be solved! (and its superclass enter scope) - Inert + [W] d5 : Foo t + +Now, d5 can be solved! d5 := d0 + +Result + d1 := dfunData2 d2 d3 + d2 := dfunSat d4 + d3 := d01 + d4 := dfunFoo2 d5 + d5 := d0 + d0 :_g Foo t d1 :_s Data Maybe [t] d1 := dfunData2 d2 d3 d2 :_g Sat (Maybe [t]) d2 := dfunSat d4 From git at git.haskell.org Tue Nov 11 13:10:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 13:10:15 +0000 (UTC) Subject: [commit: ghc] master: Comments only (e9d3e28) Message-ID: <20141111131015.DA4003A302@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e9d3e28afc8b473e250ae43eabd928809c4a4c3a/ghc >--------------------------------------------------------------- commit e9d3e28afc8b473e250ae43eabd928809c4a4c3a Author: Simon Peyton Jones Date: Tue Nov 11 11:36:16 2014 +0000 Comments only >--------------------------------------------------------------- e9d3e28afc8b473e250ae43eabd928809c4a4c3a compiler/typecheck/TcFlatten.lhs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/compiler/typecheck/TcFlatten.lhs b/compiler/typecheck/TcFlatten.lhs index 3ee4d59..2e9c6eb 100644 --- a/compiler/typecheck/TcFlatten.lhs +++ b/compiler/typecheck/TcFlatten.lhs @@ -601,6 +601,9 @@ goals. But to be honest I'm not absolutely certain, so I am leaving FM_Avoid in the code base. What I'm removing is the unique place where it is *used*, namely in TcCanonical.canEqTyVar. +See also Note [Conservative unification check] in TcUnify, which gives +other examples where lazy flattening caused problems. + Bottom line: FM_Avoid is unused for now (Nov 14). Note: T5321Fun got faster when I disabled FM_Avoid T5837 did too, but it's pathalogical anyway From git at git.haskell.org Tue Nov 11 13:10:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 13:10:18 +0000 (UTC) Subject: [commit: ghc] master: Improve documentation of -ticky a little (7cbe34f) Message-ID: <20141111131018.80E2E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7cbe34f940c34bd25d58fbb115d449b1113bacc7/ghc >--------------------------------------------------------------- commit 7cbe34f940c34bd25d58fbb115d449b1113bacc7 Author: Simon Peyton Jones Date: Tue Nov 11 11:36:57 2014 +0000 Improve documentation of -ticky a little >--------------------------------------------------------------- 7cbe34f940c34bd25d58fbb115d449b1113bacc7 docs/users_guide/flags.xml | 7 +++++++ docs/users_guide/profiling.xml | 2 +- docs/users_guide/runtime_control.xml | 3 +-- 3 files changed, 9 insertions(+), 3 deletions(-) diff --git a/docs/users_guide/flags.xml b/docs/users_guide/flags.xml index ac3cc04..2c0e548 100644 --- a/docs/users_guide/flags.xml +++ b/docs/users_guide/flags.xml @@ -2522,6 +2522,13 @@ - + + For linking, this simply implies ; + see . + dynamic + - + + Enable runtime event tracing dynamic diff --git a/docs/users_guide/profiling.xml b/docs/users_guide/profiling.xml index 5bb396d..4971a7d 100644 --- a/docs/users_guide/profiling.xml +++ b/docs/users_guide/profiling.xml @@ -1771,7 +1771,7 @@ Options: Because ticky-ticky profiling requires a certain familiarity with GHC internals, we have moved the documentation to the - wiki. Take a look at its overview of the profiling options, which includeds a link to the ticky-ticky profiling page. diff --git a/docs/users_guide/runtime_control.xml b/docs/users_guide/runtime_control.xml index d26dd96..cdd9fd4 100644 --- a/docs/users_guide/runtime_control.xml +++ b/docs/users_guide/runtime_control.xml @@ -1442,8 +1442,7 @@ $ ./a.out +RTS --info -threaded option) and rts_p (profiling runtime, i.e. linked using the -prof option). Other variants include debug - (linked using -debug), - t (ticky-ticky profiling) and + (linked using -debug), and dyn (the RTS is linked in dynamically, i.e. a shared library, rather than statically linked into the executable itself). These can be combined, From git at git.haskell.org Tue Nov 11 13:10:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 13:10:21 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #9077 (13817f0) Message-ID: <20141111131021.676683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/13817f06bc8065476711451307039387e3e34576/ghc >--------------------------------------------------------------- commit 13817f06bc8065476711451307039387e3e34576 Author: Simon Peyton Jones Date: Tue Nov 11 11:46:52 2014 +0000 Test Trac #9077 >--------------------------------------------------------------- 13817f06bc8065476711451307039387e3e34576 testsuite/tests/rename/should_fail/T9077.hs | 4 ++++ testsuite/tests/rename/should_fail/T9077.stderr | 2 ++ testsuite/tests/rename/should_fail/all.T | 1 + 3 files changed, 7 insertions(+) diff --git a/testsuite/tests/rename/should_fail/T9077.hs b/testsuite/tests/rename/should_fail/T9077.hs new file mode 100644 index 0000000..d30a5ca --- /dev/null +++ b/testsuite/tests/rename/should_fail/T9077.hs @@ -0,0 +1,4 @@ +module T9077 where + +main :: IO {} +main = print "hello" diff --git a/testsuite/tests/rename/should_fail/T9077.stderr b/testsuite/tests/rename/should_fail/T9077.stderr new file mode 100644 index 0000000..a3a9d49 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T9077.stderr @@ -0,0 +1,2 @@ + +T9077.hs:3:12: Record syntax is illegal here: {} diff --git a/testsuite/tests/rename/should_fail/all.T b/testsuite/tests/rename/should_fail/all.T index 72331e7..f2664dc 100644 --- a/testsuite/tests/rename/should_fail/all.T +++ b/testsuite/tests/rename/should_fail/all.T @@ -118,3 +118,4 @@ test('T9156', normal, compile_fail, ['']) test('T9177', normal, compile_fail, ['']) test('T9436', normal, compile_fail, ['']) test('T9437', normal, compile_fail, ['']) +test('T9077', normal, compile_fail, ['']) From git at git.haskell.org Tue Nov 11 13:10:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 13:10:24 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #7862 (2b67b8f) Message-ID: <20141111131024.8ED6C3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2b67b8f9b259c95ef9394c3a8ff801dc00e968d9/ghc >--------------------------------------------------------------- commit 2b67b8f9b259c95ef9394c3a8ff801dc00e968d9 Author: Simon Peyton Jones Date: Tue Nov 11 13:06:21 2014 +0000 Test Trac #7862 >--------------------------------------------------------------- 2b67b8f9b259c95ef9394c3a8ff801dc00e968d9 testsuite/tests/indexed-types/should_fail/T7862.hs | 19 +++++++++++++++++++ .../tests/indexed-types/should_fail/T7862.stderr | 17 +++++++++++++++++ testsuite/tests/indexed-types/should_fail/all.T | 2 +- 3 files changed, 37 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/indexed-types/should_fail/T7862.hs b/testsuite/tests/indexed-types/should_fail/T7862.hs new file mode 100644 index 0000000..98b99ab --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T7862.hs @@ -0,0 +1,19 @@ +{-# LANGUAGE TypeFamilies, FlexibleContexts #-} + +module T7862 where + +type family Scalar t + +newtype Tower s a = Tower [a] + +type instance Scalar (Tower s a) = a + +class (Num (Scalar t), Num t) => Mode t where + (<+>) :: t -> t -> t + +instance (Num a) => Mode (Tower s a) where + Tower as <+> _ = undefined + where + _ = (Tower as) <+> (Tower as) + +instance Num a => Num (Tower s a) where diff --git a/testsuite/tests/indexed-types/should_fail/T7862.stderr b/testsuite/tests/indexed-types/should_fail/T7862.stderr new file mode 100644 index 0000000..c2583d8 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T7862.stderr @@ -0,0 +1,17 @@ + +T7862.hs:17:24: + Overlapping instances for Num (Tower s0 a) + arising from a use of ?<+>? + Matching givens (or their superclasses): + (Num (Tower s a)) + bound by the instance declaration at T7862.hs:14:10-36 + Matching instances: + instance Num a => Num (Tower s a) -- Defined at T7862.hs:19:10 + (The choice depends on the instantiation of ?a, s0?) + In the expression: (Tower as) <+> (Tower as) + In a pattern binding: _ = (Tower as) <+> (Tower as) + In an equation for ?<+>?: + (Tower as) <+> _ + = undefined + where + _ = (Tower as) <+> (Tower as) diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index 0fbee70..286360a 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -130,4 +130,4 @@ test('T9433', normal, compile_fail, ['']) test('BadSock', normal, compile_fail, ['']) test('T9580', normal, multimod_compile_fail, ['T9580', '']) test('T9662', normal, compile_fail, ['']) - +test('T7862', normal, compile_fail, ['']) From git at git.haskell.org Tue Nov 11 15:06:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 15:06:46 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9788 by giving `coerce` the right type. (92544d6) Message-ID: <20141111150646.66A8D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/92544d6363182b23baea5a5f5ee769c026a11080/ghc >--------------------------------------------------------------- commit 92544d6363182b23baea5a5f5ee769c026a11080 Author: Richard Eisenberg Date: Mon Nov 10 20:41:38 2014 -0500 Fix #9788 by giving `coerce` the right type. No test case added, as the original mistake is just one level up from a typo. >--------------------------------------------------------------- 92544d6363182b23baea5a5f5ee769c026a11080 compiler/basicTypes/MkId.lhs | 19 ++++++++----------- testsuite/tests/ghci/scripts/ghci059.stdout | 4 +--- 2 files changed, 9 insertions(+), 14 deletions(-) diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index 9fc728b..b32a2b7 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -1146,17 +1146,14 @@ coerceId = pcMiscPrelId coerceName ty info where info = noCafIdInfo `setInlinePragInfo` alwaysInlinePragma `setUnfoldingInfo` mkCompulsoryUnfolding rhs - kv = kKiVar - k = mkTyVarTy kv - a:b:_ = tyVarList k - [aTy,bTy] = map mkTyVarTy [a,b] - eqRTy = mkTyConApp coercibleTyCon [k, aTy, bTy] - eqRPrimTy = mkTyConApp eqReprPrimTyCon [k, aTy, bTy] - ty = mkForAllTys [kv, a, b] (mkFunTys [eqRTy, aTy] bTy) - - [eqR,x,eq] = mkTemplateLocals [eqRTy, aTy,eqRPrimTy] - rhs = mkLams [kv,a,b,eqR,x] $ - mkWildCase (Var eqR) eqRTy bTy $ + eqRTy = mkTyConApp coercibleTyCon [liftedTypeKind, alphaTy, betaTy] + eqRPrimTy = mkTyConApp eqReprPrimTyCon [liftedTypeKind, alphaTy, betaTy] + ty = mkForAllTys [alphaTyVar, betaTyVar] $ + mkFunTys [eqRTy, alphaTy] betaTy + + [eqR,x,eq] = mkTemplateLocals [eqRTy, alphaTy, eqRPrimTy] + rhs = mkLams [alphaTyVar, betaTyVar, eqR, x] $ + mkWildCase (Var eqR) eqRTy betaTy $ [(DataAlt coercibleDataCon, [eq], Cast (Var x) (CoVarCo eq))] \end{code} diff --git a/testsuite/tests/ghci/scripts/ghci059.stdout b/testsuite/tests/ghci/scripts/ghci059.stdout index ffc893f..6b2c8f8 100644 --- a/testsuite/tests/ghci/scripts/ghci059.stdout +++ b/testsuite/tests/ghci/scripts/ghci059.stdout @@ -1,6 +1,4 @@ type role Coercible representational representational class Coercible (a :: k) (b :: k) -- Defined in ?GHC.Types? -coerce :: - forall (k :: BOX) (a :: k) (b :: k). Coercible a b => a -> b - -- Defined in ?GHC.Prim? +coerce :: Coercible a b => a -> b -- Defined in ?GHC.Prim? From git at git.haskell.org Tue Nov 11 15:06:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 15:06:49 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9404 (typecheck/should_compile/T9404 and T9404b) (e0c2207) Message-ID: <20141111150649.DA24D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/e0c2207b07a5869c58f64ad36c9d3f5938372307/ghc >--------------------------------------------------------------- commit e0c2207b07a5869c58f64ad36c9d3f5938372307 Author: Richard Eisenberg Date: Thu Aug 7 09:20:41 2014 -0400 Test #9404 (typecheck/should_compile/T9404 and T9404b) >--------------------------------------------------------------- e0c2207b07a5869c58f64ad36c9d3f5938372307 testsuite/tests/typecheck/should_compile/T9404.hs | 6 ++++++ testsuite/tests/typecheck/should_compile/T9404b.hs | 15 +++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 2 ++ 3 files changed, 23 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T9404.hs b/testsuite/tests/typecheck/should_compile/T9404.hs new file mode 100644 index 0000000..4cb530a --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9404.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE UnboxedTuples #-} + +module T9404 where + +foo _ = case seq () (# #) of (# #) -> () +foo2 _ = case () `seq` (# #) of (# #) -> () diff --git a/testsuite/tests/typecheck/should_compile/T9404b.hs b/testsuite/tests/typecheck/should_compile/T9404b.hs new file mode 100644 index 0000000..f9db0a3 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9404b.hs @@ -0,0 +1,15 @@ +{-# LANGUAGE RankNTypes, TypeFamilies #-} + +module T9404b where + +type family ListTF x where + ListTF x = [x] + +bar :: (forall x. ListTF x -> Int) -> () +bar _ = () + +myconst :: ((forall r. ListTF r -> Int) -> ()) -> x -> (forall r. ListTF r -> Int) -> () +myconst x _ = x + +foo = (bar `myconst` ()) $ length +foo2 = (myconst bar ()) $ length diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index a6cb78a..8448411 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -422,3 +422,5 @@ test('T8856', normal, compile, ['']) test('T9117', normal, compile, ['']) test('T9117_2', expect_broken('9117'), compile, ['']) test('T9708', normal, compile_fail, ['']) +test('T9404', expect_broken(9404), compile, ['']) +test('T9404b', expect_broken(9404), compile, ['']) From git at git.haskell.org Tue Nov 11 15:06:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 15:06:52 +0000 (UTC) Subject: [commit: ghc] wip/rae: Testsuite wibble due to #9404 (95a024c) Message-ID: <20141111150652.8CFCD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/95a024c460c3b775549516645cf673da283811b3/ghc >--------------------------------------------------------------- commit 95a024c460c3b775549516645cf673da283811b3 Author: Richard Eisenberg Date: Tue Nov 11 07:58:03 2014 -0500 Testsuite wibble due to #9404 >--------------------------------------------------------------- 95a024c460c3b775549516645cf673da283811b3 testsuite/tests/ghci/scripts/ghci046.script | 4 ++-- testsuite/tests/ghci/scripts/ghci046.stdout | 6 ++++-- 2 files changed, 6 insertions(+), 4 deletions(-) diff --git a/testsuite/tests/ghci/scripts/ghci046.script b/testsuite/tests/ghci/scripts/ghci046.script index f07e06f..28c5cde 100644 --- a/testsuite/tests/ghci/scripts/ghci046.script +++ b/testsuite/tests/ghci/scripts/ghci046.script @@ -12,8 +12,8 @@ type instance OR HTrue HTrue = HTrue type instance OR HTrue HFalse = HTrue type instance OR HFalse HTrue = HTrue type instance OR HFalse HFalse = HFalse -:t undefined :: AND HTrue HTrue -:t undefined :: AND (OR HFalse HTrue) (OR HTrue HFalse) +:kind! AND HTrue HTrue +:kind! AND (OR HFalse HTrue) (OR HTrue HFalse) let t = undefined :: AND HTrue HTrue let f = undefined :: AND HTrue HFalse type instance AND HTrue HTrue = HFalse diff --git a/testsuite/tests/ghci/scripts/ghci046.stdout b/testsuite/tests/ghci/scripts/ghci046.stdout index d600596..c4e7cf3 100644 --- a/testsuite/tests/ghci/scripts/ghci046.stdout +++ b/testsuite/tests/ghci/scripts/ghci046.stdout @@ -1,4 +1,6 @@ -undefined :: AND HTrue HTrue :: HTrue -undefined :: AND (OR HFalse HTrue) (OR HTrue HFalse) :: HTrue +AND HTrue HTrue :: * += HTrue +AND (OR HFalse HTrue) (OR HTrue HFalse) :: * += HTrue t :: HTrue t :: HFalse From git at git.haskell.org Tue Nov 11 15:06:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 15:06:55 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9404 by removing tcInfExpr. (1a63e50) Message-ID: <20141111150655.488D23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/1a63e50377aba1f57cf2bed36bc11427302deae5/ghc >--------------------------------------------------------------- commit 1a63e50377aba1f57cf2bed36bc11427302deae5 Author: Richard Eisenberg Date: Mon Nov 10 21:27:58 2014 -0500 Fix #9404 by removing tcInfExpr. See the ticket for more info about the new algorithm. This is a small simplification, unifying the treatment of type checking in a few similar situations. >--------------------------------------------------------------- 1a63e50377aba1f57cf2bed36bc11427302deae5 compiler/typecheck/TcExpr.lhs | 32 +++------------ compiler/typecheck/TcMType.lhs | 15 ++++--- compiler/typecheck/TcType.lhs | 47 ++++++++++++++++++---- compiler/typecheck/TcUnify.lhs | 24 ++++++++--- compiler/utils/MonadUtils.hs | 6 +++ .../{should_fail => should_compile}/T7220.hs | 0 testsuite/tests/typecheck/should_compile/all.T | 5 ++- testsuite/tests/typecheck/should_fail/T7220.stderr | 9 ----- testsuite/tests/typecheck/should_fail/all.T | 1 - 9 files changed, 78 insertions(+), 61 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1a63e50377aba1f57cf2bed36bc11427302deae5 From git at git.haskell.org Tue Nov 11 15:14:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 15:14:21 +0000 (UTC) Subject: [commit: ghc] master: Add stderr for T9662 (76d47ed) Message-ID: <20141111151421.33B993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/76d47ed5ba1085c4f3f0d9d8a0ad75be3efb39d3/ghc >--------------------------------------------------------------- commit 76d47ed5ba1085c4f3f0d9d8a0ad75be3efb39d3 Author: Simon Peyton Jones Date: Tue Nov 11 15:14:20 2014 +0000 Add stderr for T9662 >--------------------------------------------------------------- 76d47ed5ba1085c4f3f0d9d8a0ad75be3efb39d3 .../tests/indexed-types/should_fail/T9662.stderr | 84 ++++++++++++++++++++++ 1 file changed, 84 insertions(+) diff --git a/testsuite/tests/indexed-types/should_fail/T9662.stderr b/testsuite/tests/indexed-types/should_fail/T9662.stderr new file mode 100644 index 0000000..984a2ea --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T9662.stderr @@ -0,0 +1,84 @@ + +T9662.hs:47:8: + Couldn't match type ?k? with ?Int? + ?k? is a rigid type variable bound by + the type signature for + test :: Shape (((sh :. k) :. m) :. n) + -> Shape (((sh :. m) :. n) :. k) + at T9662.hs:44:9 + Expected type: Exp (((sh :. k) :. m) :. n) + -> Exp (((sh :. m) :. n) :. k) + Actual type: Exp + (Tuple (((Atom a0 :. Atom Int) :. Atom Int) :. Atom Int)) + -> Exp + (Plain (((Unlifted (Atom a0) :. Exp Int) :. Exp Int) :. Exp Int)) + Relevant bindings include + test :: Shape (((sh :. k) :. m) :. n) + -> Shape (((sh :. m) :. n) :. k) + (bound at T9662.hs:45:1) + In the first argument of ?backpermute?, namely + ?(modify + (atom :. atom :. atom :. atom) + (\ (sh :. k :. m :. n) -> (sh :. m :. n :. k)))? + In the expression: + backpermute + (modify + (atom :. atom :. atom :. atom) + (\ (sh :. k :. m :. n) -> (sh :. m :. n :. k))) + id + +T9662.hs:47:8: + Couldn't match type ?m? with ?Int? + ?m? is a rigid type variable bound by + the type signature for + test :: Shape (((sh :. k) :. m) :. n) + -> Shape (((sh :. m) :. n) :. k) + at T9662.hs:44:9 + Expected type: Exp (((sh :. k) :. m) :. n) + -> Exp (((sh :. m) :. n) :. k) + Actual type: Exp + (Tuple (((Atom a0 :. Atom Int) :. Atom Int) :. Atom Int)) + -> Exp + (Plain (((Unlifted (Atom a0) :. Exp Int) :. Exp Int) :. Exp Int)) + Relevant bindings include + test :: Shape (((sh :. k) :. m) :. n) + -> Shape (((sh :. m) :. n) :. k) + (bound at T9662.hs:45:1) + In the first argument of ?backpermute?, namely + ?(modify + (atom :. atom :. atom :. atom) + (\ (sh :. k :. m :. n) -> (sh :. m :. n :. k)))? + In the expression: + backpermute + (modify + (atom :. atom :. atom :. atom) + (\ (sh :. k :. m :. n) -> (sh :. m :. n :. k))) + id + +T9662.hs:47:8: + Couldn't match type ?n? with ?Int? + ?n? is a rigid type variable bound by + the type signature for + test :: Shape (((sh :. k) :. m) :. n) + -> Shape (((sh :. m) :. n) :. k) + at T9662.hs:44:9 + Expected type: Exp (((sh :. k) :. m) :. n) + -> Exp (((sh :. m) :. n) :. k) + Actual type: Exp + (Tuple (((Atom a0 :. Atom Int) :. Atom Int) :. Atom Int)) + -> Exp + (Plain (((Unlifted (Atom a0) :. Exp Int) :. Exp Int) :. Exp Int)) + Relevant bindings include + test :: Shape (((sh :. k) :. m) :. n) + -> Shape (((sh :. m) :. n) :. k) + (bound at T9662.hs:45:1) + In the first argument of ?backpermute?, namely + ?(modify + (atom :. atom :. atom :. atom) + (\ (sh :. k :. m :. n) -> (sh :. m :. n :. k)))? + In the expression: + backpermute + (modify + (atom :. atom :. atom :. atom) + (\ (sh :. k :. m :. n) -> (sh :. m :. n :. k))) + id From git at git.haskell.org Tue Nov 11 17:44:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 17:44:50 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData2: Use TypeLits in the meta-data encoding of GHC.Generics (97f7064) Message-ID: <20141111174450.0AFD43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData2 Link : http://ghc.haskell.org/trac/ghc/changeset/97f706483316377bbc83910da354850f4b17ff68/ghc >--------------------------------------------------------------- commit 97f706483316377bbc83910da354850f4b17ff68 Author: Jose Pedro Magalhaes Date: Thu Oct 2 08:38:05 2014 +0100 Use TypeLits in the meta-data encoding of GHC.Generics The following wiki page contains more information about this: https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/GenericDeriving#Amoreconservativefirstapproachtothisproblem >--------------------------------------------------------------- 97f706483316377bbc83910da354850f4b17ff68 compiler/prelude/PrelNames.lhs | 71 ++++++-- compiler/typecheck/TcDeriv.lhs | 64 ++----- compiler/typecheck/TcGenDeriv.lhs | 18 +- compiler/typecheck/TcGenGenerics.lhs | 308 +++++++++----------------------- libraries/base/Data/Monoid.hs | 1 + libraries/base/GHC/Generics.hs | 190 ++++++++++++++++---- testsuite/tests/generics/GShow/GShow.hs | 1 + 7 files changed, 314 insertions(+), 339 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 97f706483316377bbc83910da354850f4b17ff68 From git at git.haskell.org Tue Nov 11 17:44:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 17:44:52 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData2: Update test output (16ac82a7) Message-ID: <20141111174452.C441B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData2 Link : http://ghc.haskell.org/trac/ghc/changeset/16ac82a70724190ed551a1a5cde42258a3327e41/ghc >--------------------------------------------------------------- commit 16ac82a70724190ed551a1a5cde42258a3327e41 Author: Jose Pedro Magalhaes Date: Tue Nov 4 10:02:17 2014 +0000 Update test output >--------------------------------------------------------------- 16ac82a70724190ed551a1a5cde42258a3327e41 testsuite/tests/generics/GenDerivOutput.stderr | 120 +++++----- testsuite/tests/generics/GenDerivOutput1_0.stderr | 48 ++-- testsuite/tests/generics/GenDerivOutput1_1.stderr | 254 ++++++++++------------ 3 files changed, 187 insertions(+), 235 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 16ac82a70724190ed551a1a5cde42258a3327e41 From git at git.haskell.org Tue Nov 11 17:44:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 17:44:58 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData2: Also export FixityI. (91ff17e) Message-ID: <20141111174458.391963A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData2 Link : http://ghc.haskell.org/trac/ghc/changeset/91ff17e83ebc8ceb31aec0113d9bfdc19b468d2f/ghc >--------------------------------------------------------------- commit 91ff17e83ebc8ceb31aec0113d9bfdc19b468d2f Author: Jose Pedro Magalhaes Date: Tue Nov 11 16:48:46 2014 +0000 Also export FixityI. >--------------------------------------------------------------- 91ff17e83ebc8ceb31aec0113d9bfdc19b468d2f libraries/base/GHC/Generics.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs index d22e5ee..1e4728d 100644 --- a/libraries/base/GHC/Generics.hs +++ b/libraries/base/GHC/Generics.hs @@ -560,7 +560,7 @@ module GHC.Generics ( -- * Meta-information , Datatype(..), Constructor(..), Selector(..), NoSelector - , Fixity(..), Associativity(..), prec + , Fixity(..), FixityI(..), Associativity(..), prec , Meta(..) -- * Generic type classes @@ -686,6 +686,8 @@ instance (KnownSymbol n, SingI f, SingI r) => Constructor (MetaCons n f r) where -- | declaration directly corresponds to an application of 'Infix'. data Fixity = Prefix | Infix Associativity Int deriving (Eq, Show, Ord, Read, Generic) + +-- | This variant of 'Fixity' appears at the type level. data FixityI = PrefixI | InfixI Associativity Nat -- | Get the precedence of a fixity value. From git at git.haskell.org Tue Nov 11 17:44:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 17:44:55 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData2: Code cleanup (b8a6685) Message-ID: <20141111174455.82A433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData2 Link : http://ghc.haskell.org/trac/ghc/changeset/b8a6685089b4e3748c1992d0c6451c1e080d2802/ghc >--------------------------------------------------------------- commit b8a6685089b4e3748c1992d0c6451c1e080d2802 Author: Jose Pedro Magalhaes Date: Tue Nov 11 14:52:50 2014 +0000 Code cleanup >--------------------------------------------------------------- b8a6685089b4e3748c1992d0c6451c1e080d2802 compiler/prelude/PrelNames.lhs | 40 ++++------- compiler/typecheck/TcGenGenerics.lhs | 26 +++---- libraries/base/Data/Monoid.hs | 1 - libraries/base/GHC/Generics.hs | 118 +++----------------------------- testsuite/tests/generics/GShow/GShow.hs | 3 +- 5 files changed, 32 insertions(+), 156 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b8a6685089b4e3748c1992d0c6451c1e080d2802 From git at git.haskell.org Tue Nov 11 17:45:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 17:45:00 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData2: Documentation (b54c051) Message-ID: <20141111174501.005163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData2 Link : http://ghc.haskell.org/trac/ghc/changeset/b54c051a767a000eb9c4b9f92c44668b6f325049/ghc >--------------------------------------------------------------- commit b54c051a767a000eb9c4b9f92c44668b6f325049 Author: Jose Pedro Magalhaes Date: Tue Nov 11 16:49:44 2014 +0000 Documentation >--------------------------------------------------------------- b54c051a767a000eb9c4b9f92c44668b6f325049 docs/users_guide/glasgow_exts.xml | 30 ++++--------- libraries/base/GHC/Generics.hs | 92 +++++++++++++++++++-------------------- 2 files changed, 54 insertions(+), 68 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b54c051a767a000eb9c4b9f92c44668b6f325049 From git at git.haskell.org Tue Nov 11 17:45:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 17:45:03 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData2's head updated: Documentation (b54c051) Message-ID: <20141111174503.648603A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/GenericsMetaData2' now includes: 64dc4d1 Re-center perf-numbers for T5631 6a1c05f A little refactoring of HsSplice and friends 77f8221 Temporarily disable T3064 (see #9771) 0a8e899 Remove redundant contexts from Foldable methods ac0915b Clean-up Haddock in `Data.Functor` 40b1ee4 Add `isSubsequenceOf` to Data.List (#9767) 32237f0 Fix typo in testsuite Makefile 83cf31e Fix a couple of bugs in the way info tables are generated for 64-bit platforms 4cd277b Fix bugs in debug printing 3bebf3c Fix a couple of inaccurate stack checks e6b3829 Disable an assertion; see comment 081ef2f Add a comment about stack checks d14312f Add doctest examples for Data.Either d0d9dc0 Clarify confusing notice from `make maintainer-clean` ad8457f Remove -ddump-simpl-phases flag c0a2354 Remove -ddump-core-pipeline flag 303776a Update User's Guide, cleanup DynFlags 0f930ba Move expansion of 'assert' from renamer to typechecker 030abf9 Remove unused tyConsOfDataCon e7523fe Make tyConsOfType return a (NameEnv TyCon) rather than [TyCon] f81f82e Comments and white space only 528cbd7 Give T3064 the right module name (just tidying up) 096b7e6 Switch off lazy flattening (fix Trac #3064) cb6ccad Minor refacoring and trace-message printing c945477 Allow the solved dictionaries to propagate from outside in ec38deb Wibbles to notes 203cf0e Refactor the code that prevents recursion among Coercible constraints c79cbac Re-enable T3064, which works now 91c15d6 Better error messages for new per-instance overlap flags and Safe Haskell. c96a613 Add in Incoherent Instances test for Safe Haskell. f4ead30 Warn for Safe Haskell when -XOverlappingInstances or -XIncoherentInstances turned on. abba381 Improve Applicative definitions dc5fa80 Make getTag use a bang pattern instead of seq b0e8e34 Update .gitignore to properly ignore emacs temp files 24e05f4 *Really*, really fix RTS crash due to bad coercion. 37d64a5 small parser/lexer cleanup b0d5b5b [Docs] Fixed several broken urls in user's guide f14ac52 Use bracket in `withCurrentDirectory` 832ef3f Have validate take into account stat test failures too. df3b1d4 base: Manually unlit .lhs into .hs modules a2e7bbf Preserve argument order to (==)/eq in nub and nubBy b608868 Typofix. c942688 Miscellaneous documentation for the Finder. f5996d9 Top-level comment for keepPackageImports. 474e535 In pattern synonym matchers, support unboxed continuation results (fixes #9783). 65dc594 Group PatSyn req/prov arguments together so that they're not all over the place 8e66365 Unlit overlooked GHC/Conc/Sync.lhs e2769df Use (.) and id from Base in Control.Applicative 8710136 Move Data.Functor.Identity from transformers to base 7ae596a Typo fix; Trac #9787 4923cea Define list monad operations using comprehensions e567130 De-bias Data.Foldable and improve docstrings 97420b0 Comments only (on recursive dictionaries) ed57ea4 Test Trac #9662 e9d3e28 Comments only 7cbe34f Improve documentation of -ticky a little 13817f0 Test Trac #9077 2b67b8f Test Trac #7862 76d47ed Add stderr for T9662 97f7064 Use TypeLits in the meta-data encoding of GHC.Generics 16ac82a7 Update test output b8a6685 Code cleanup 91ff17e Also export FixityI. b54c051 Documentation From git at git.haskell.org Tue Nov 11 18:12:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 18:12:32 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins's head updated: Make TcPlugin part of Plugin so we can eliminate -ftc-plugin (be95bd9) Message-ID: <20141111181232.49E173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/tc-plugins' now includes: 1ed1e63 Move withTcPlugins to TcRnDriver, removing need for hs-boot file ce850aa Move core2core plugins to a new module Plugins be95bd9 Make TcPlugin part of Plugin so we can eliminate -ftc-plugin From git at git.haskell.org Tue Nov 11 21:13:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 21:13:54 +0000 (UTC) Subject: [commit: packages/stm] master: Update Travis CI job (0aa55b3) Message-ID: <20141111211354.3591B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm On branch : master Link : http://git.haskell.org/packages/stm.git/commitdiff/0aa55b39aa9b1c9e9e84bb206c625631d294842e >--------------------------------------------------------------- commit 0aa55b39aa9b1c9e9e84bb206c625631d294842e Author: Herbert Valerio Riedel Date: Tue Nov 11 22:13:55 2014 +0100 Update Travis CI job >--------------------------------------------------------------- 0aa55b39aa9b1c9e9e84bb206c625631d294842e .travis.yml | 56 +++++++++++++++++++++++++++++--------------------------- 1 file changed, 29 insertions(+), 27 deletions(-) diff --git a/.travis.yml b/.travis.yml index 1ca0118..5d6dcc8 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,43 +1,45 @@ env: -# - GHCVER=6.12.3 - - GHCVER=7.0.1 - - GHCVER=7.0.2 - - GHCVER=7.0.3 - - GHCVER=7.0.4 - - GHCVER=7.2.1 - - GHCVER=7.2.2 - - GHCVER=7.4.1 - - GHCVER=7.4.2 - - GHCVER=7.6.1 - - GHCVER=7.6.2 - - GHCVER=7.6.3 - - GHCVER=7.8.1 - - GHCVER=head + - GHCVER=7.0.1 CABALVER=1.16 + - GHCVER=7.0.2 CABALVER=1.16 + - GHCVER=7.0.3 CABALVER=1.16 + - GHCVER=7.0.4 CABALVER=1.16 + - GHCVER=7.2.1 CABALVER=1.16 + - GHCVER=7.2.2 CABALVER=1.16 + - GHCVER=7.4.1 CABALVER=1.16 + - GHCVER=7.4.2 CABALVER=1.16 + - GHCVER=7.6.1 CABALVER=1.16 + - GHCVER=7.6.2 CABALVER=1.16 + - GHCVER=7.6.3 CABALVER=1.16 + - GHCVER=7.8.1 CABALVER=1.18 + - GHCVER=7.8.2 CABALVER=1.18 + - GHCVER=7.8.3 CABALVER=1.18 + - GHCVER=head CABALVER=head matrix: allow_failures: - - env: GHCVER=head + - env: GHCVER=head CABALVER=head before_install: - - sudo add-apt-repository -y ppa:hvr/ghc - - sudo apt-get update - - sudo apt-get install cabal-install-1.18 ghc-$GHCVER - - export PATH=/opt/ghc/$GHCVER/bin:$PATH + - travis_retry sudo add-apt-repository -y ppa:hvr/ghc + - travis_retry sudo apt-get update + - travis_retry sudo apt-get install cabal-install-$CABALVER ghc-$GHCVER + - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH + - cabal --version install: - - cabal-1.18 update + - travis_retry cabal update script: - - cabal-1.18 configure -v2 - - cabal-1.18 build - - cabal-1.18 check - - cabal-1.18 sdist - - export SRC_TGZ=$(cabal-1.18 info . | awk '{print $2 ".tar.gz";exit}') ; + - cabal configure -v2 + - cabal build + - cabal check + - cabal sdist + - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; if [ -f "dist/$SRC_TGZ" ]; then - cabal-1.18 install "dist/$SRC_TGZ"; + cabal install "dist/$SRC_TGZ"; else echo "expected '$SRC_TGZ' not found"; exit 1; fi - - cabal-1.18 install random + - cabal install random - tests/runtests.sh From git at git.haskell.org Tue Nov 11 21:28:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Nov 2014 21:28:48 +0000 (UTC) Subject: [commit: packages/stm] master: M-x untabify & M-x delete-trailing-whitespace (f2334b9) Message-ID: <20141111212848.C3D563A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm On branch : master Link : http://git.haskell.org/packages/stm.git/commitdiff/f2334b91a7f0aeb34d8f35f45c8b4e1f348bcadd >--------------------------------------------------------------- commit f2334b91a7f0aeb34d8f35f45c8b4e1f348bcadd Author: Herbert Valerio Riedel Date: Tue Nov 11 22:23:30 2014 +0100 M-x untabify & M-x delete-trailing-whitespace >--------------------------------------------------------------- f2334b91a7f0aeb34d8f35f45c8b4e1f348bcadd Control/Concurrent/STM.hs | 8 ++--- Control/Concurrent/STM/TBQueue.hs | 16 ++++----- Control/Concurrent/STM/TChan.hs | 24 +++++++------- Control/Concurrent/STM/TMVar.hs | 28 ++++++++-------- Control/Concurrent/STM/TQueue.hs | 16 ++++----- Control/Concurrent/STM/TVar.hs | 20 ++++++------ Control/Monad/STM.hs | 10 +++--- Control/Sequential/STM.hs | 26 +++++++-------- tests/stm046.hs | 34 ++++++++------------ tests/stm047.hs | 10 +----- tests/stm048.hs | 5 +-- tests/stm049.hs | 68 +++++++++++++++++++-------------------- tests/stm050.hs | 2 +- tests/stm052.hs | 12 +++---- tests/stm056.hs | 3 +- 15 files changed, 130 insertions(+), 152 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f2334b91a7f0aeb34d8f35f45c8b4e1f348bcadd From git at git.haskell.org Wed Nov 12 08:43:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 08:43:30 +0000 (UTC) Subject: [commit: ghc] master: Disable T4801/peak_megabytes_allocated (fcfc87d) Message-ID: <20141112084330.497393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fcfc87dce752c3c1702eeb54d1023213729f1832/ghc >--------------------------------------------------------------- commit fcfc87dce752c3c1702eeb54d1023213729f1832 Author: Herbert Valerio Riedel Date: Sun Nov 9 21:54:43 2014 +0100 Disable T4801/peak_megabytes_allocated This test seems too close to a tipping point (and thus too sensitive to the build-env used) and T4801's `max_bytes_used` was disabled as well some time ago for a similiar reason. >--------------------------------------------------------------- fcfc87dce752c3c1702eeb54d1023213729f1832 testsuite/tests/perf/compiler/all.T | 36 +++++++++++++++++++----------------- 1 file changed, 19 insertions(+), 17 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index f6f52d7..92d1326 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -167,22 +167,24 @@ test('T3294', test('T4801', [ # expect_broken(5224), # temporarily unbroken (#5227) - compiler_stats_num_field('peak_megabytes_allocated',# Note [residency] - [(platform('x86_64-apple-darwin'), 70, 1), - # expected value: 58 (amd64/OS X) - # 13/01/2014 - 70 - (wordsize(32), 30, 20), - (wordsize(64), 48, 20)]), - # prev: 50 (amd64/Linux) - # 19/10/2012: 64 (amd64/Linux) - # (^ REASON UNKNOWN!) - # 12/11/2012: 49 (amd64/Linux) - # (^ REASON UNKNOWN!) - # 28/8/13: 60 (amd64/Linux) - # (^ REASON UNKNOWN!) - # 2014-09-10: 55 post-AMP-cleanup - # 2014-10-08: 62 (jumps between 55 and 71 observed -- GC tipping point?) - # 2014-10-13: 48 stricter seqDmdType +################################### +# deactivated for now, as this metric became too volatile recently +# compiler_stats_num_field('peak_megabytes_allocated',# Note [residency] +# [(platform('x86_64-apple-darwin'), 70, 1), +# # expected value: 58 (amd64/OS X) +# # 13/01/2014 - 70 +# (wordsize(32), 30, 20), +# (wordsize(64), 48, 20)]), +# # prev: 50 (amd64/Linux) +# # 19/10/2012: 64 (amd64/Linux) +# # (^ REASON UNKNOWN!) +# # 12/11/2012: 49 (amd64/Linux) +# # (^ REASON UNKNOWN!) +# # 28/8/13: 60 (amd64/Linux) +# # (^ REASON UNKNOWN!) +# # 2014-09-10: 55 post-AMP-cleanup +# # 2014-10-08: 62 (jumps between 55 and 71 observed -- GC tipping point?) +# # 2014-10-13: 48 stricter seqDmdType compiler_stats_num_field('bytes allocated', [(platform('x86_64-apple-darwin'), 464872776, 5), @@ -200,7 +202,7 @@ test('T4801', # 2014-10-08: 382056344 (amd64/Linux) stricter foldr2 488e95b ################################### -# deactivated for now, as this metric became to volatile recently +# deactivated for now, as this metric became too volatile recently # # compiler_stats_num_field('max_bytes_used', # [(platform('x86_64-apple-darwin'), 25145320, 5), From git at git.haskell.org Wed Nov 12 09:37:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 09:37:56 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Binding things matched by an unboxed pattern synonym should require a bang (3bfd4d8) Message-ID: <20141112093756.157103A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/3bfd4d8f9ad0bc40fd8c8f54acc6072a1122dc34/ghc >--------------------------------------------------------------- commit 3bfd4d8f9ad0bc40fd8c8f54acc6072a1122dc34 Author: Dr. ERDI Gergo Date: Sat Nov 8 16:59:47 2014 +0800 Binding things matched by an unboxed pattern synonym should require a bang >--------------------------------------------------------------- 3bfd4d8f9ad0bc40fd8c8f54acc6072a1122dc34 testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/all.T | 2 +- testsuite/tests/patsyn/should_fail/unboxed-bind.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/unboxed-bind.stderr | 6 ++++++ 5 files changed, 28 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index d851bc3..94950a1 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -10,3 +10,4 @@ test('incomplete', normal, compile, ['']) test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) +test('unboxed-bind-bang', normal, compile, ['']) diff --git a/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs new file mode 100644 index 0000000..a972b21 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash, BangPatterns #-} +module ShouldCompile where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let !(P arg) = x in arg diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index ea671dc..ee5768c 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -1,4 +1,3 @@ - test('mono', normal, compile_fail, ['']) test('unidir', normal, compile_fail, ['']) test('local', normal, compile_fail, ['']) @@ -8,3 +7,4 @@ test('T9161-1', normal, compile_fail, ['']) test('T9161-2', normal, compile_fail, ['']) test('T9705-1', normal, compile_fail, ['']) test('T9705-2', normal, compile_fail, ['']) +test('unboxed-bind', normal, compile_fail, ['']) diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.hs b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs new file mode 100644 index 0000000..ef1b070 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module ShouldFail where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let P arg = x in arg diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr new file mode 100644 index 0000000..17ca7af --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr @@ -0,0 +1,6 @@ + +unboxed-bind.hs:10:11: + Pattern bindings containing unlifted types should use an outermost bang pattern: + P arg = x + In the expression: let P arg = x in arg + In an equation for ?f?: f x = let P arg = x in arg From git at git.haskell.org Wed Nov 12 09:37:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 09:37:58 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Fix typo in panic message (53c0120) Message-ID: <20141112093758.98EFE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/53c01205bee8d99b32af383a137ab4b9b97c70e3/ghc >--------------------------------------------------------------- commit 53c01205bee8d99b32af383a137ab4b9b97c70e3 Author: Dr. ERDI Gergo Date: Thu Nov 6 19:38:40 2014 +0800 Fix typo in panic message >--------------------------------------------------------------- 53c01205bee8d99b32af383a137ab4b9b97c70e3 compiler/main/TidyPgm.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs index a975fdd..b7a867d 100644 --- a/compiler/main/TidyPgm.lhs +++ b/compiler/main/TidyPgm.lhs @@ -421,7 +421,7 @@ lookup_aux_id :: TypeEnv -> Var -> Id lookup_aux_id type_env id = case lookupTypeEnv type_env (idName id) of Just (AnId id') -> id' - _other -> pprPanic "lookup_axu_id" (ppr id) + _other -> pprPanic "lookup_aux_id" (ppr id) \end{code} From git at git.haskell.org Wed Nov 12 09:38:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 09:38:01 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Apply compulsory unfoldings during desugaring (3df7ad1) Message-ID: <20141112093801.2A30A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/3df7ad1921afe1a231d00cd3bcf49a6554ecd3af/ghc >--------------------------------------------------------------- commit 3df7ad1921afe1a231d00cd3bcf49a6554ecd3af Author: Gergo Erdi Date: Wed Nov 12 10:24:44 2014 +0800 Apply compulsory unfoldings during desugaring >--------------------------------------------------------------- 3df7ad1921afe1a231d00cd3bcf49a6554ecd3af compiler/deSugar/DsExpr.lhs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/compiler/deSugar/DsExpr.lhs b/compiler/deSugar/DsExpr.lhs index 6844f48..004a80b 100644 --- a/compiler/deSugar/DsExpr.lhs +++ b/compiler/deSugar/DsExpr.lhs @@ -191,7 +191,11 @@ dsLExpr (L loc e) = putSrcSpanDs loc $ dsExpr e dsExpr :: HsExpr Id -> DsM CoreExpr dsExpr (HsPar e) = dsLExpr e dsExpr (ExprWithTySigOut e _) = dsLExpr e -dsExpr (HsVar var) = return (varToCoreExpr var) -- See Note [Desugaring vars] +dsExpr (HsVar var) + | isCompulsoryUnfolding unfolding = return $ unfoldingTemplate unfolding + | otherwise = return (varToCoreExpr var) -- See Note [Desugaring vars] + where + unfolding = idUnfolding var dsExpr (HsIPVar _) = panic "dsExpr: HsIPVar" dsExpr (HsLit lit) = dsLit lit dsExpr (HsOverLit lit) = dsOverLit lit From git at git.haskell.org Wed Nov 12 09:38:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 09:38:04 +0000 (UTC) Subject: [commit: ghc] wip/T9732: If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. (3cb2a48) Message-ID: <20141112093804.90E263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/3cb2a48e1b6fc761ad61afb201b191d7f0c6e10c/ghc >--------------------------------------------------------------- commit 3cb2a48e1b6fc761ad61afb201b191d7f0c6e10c Author: Dr. ERDI Gergo Date: Sat Nov 8 18:38:12 2014 +0800 If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. >--------------------------------------------------------------- 3cb2a48e1b6fc761ad61afb201b191d7f0c6e10c compiler/basicTypes/PatSyn.lhs | 50 +++++++-- compiler/ghc.mk | 1 + compiler/iface/BuildTyCl.lhs | 2 +- compiler/iface/IfaceSyn.lhs | 10 +- compiler/iface/MkIface.lhs | 4 +- compiler/iface/TcIface.lhs | 62 +++++++++-- compiler/typecheck/TcBinds.lhs | 8 +- compiler/typecheck/TcPatSyn.lhs | 119 +++++++++++---------- compiler/typecheck/TcPatSyn.lhs-boot | 4 +- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_compile/T9732.hs | 4 + testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_fail/all.T | 1 + .../{unboxed-bind.hs => unboxed-wrapper-naked.hs} | 6 +- .../should_fail/unboxed-wrapper-naked.stderr | 3 + testsuite/tests/patsyn/should_run/all.T | 2 + testsuite/tests/patsyn/should_run/match-unboxed.hs | 21 ++++ .../should_run/match-unboxed.stdout} | 2 + .../tests/patsyn/should_run/unboxed-wrapper.hs | 9 ++ .../should_run/unboxed-wrapper.stdout} | 0 20 files changed, 219 insertions(+), 91 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3cb2a48e1b6fc761ad61afb201b191d7f0c6e10c From git at git.haskell.org Wed Nov 12 09:38:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 09:38:06 +0000 (UTC) Subject: [commit: ghc] wip/T9732's head updated: Apply compulsory unfoldings during desugaring (3df7ad1) Message-ID: <20141112093806.A6CEB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9732' now includes: 8e66365 Unlit overlooked GHC/Conc/Sync.lhs e2769df Use (.) and id from Base in Control.Applicative 8710136 Move Data.Functor.Identity from transformers to base 7ae596a Typo fix; Trac #9787 4923cea Define list monad operations using comprehensions e567130 De-bias Data.Foldable and improve docstrings 97420b0 Comments only (on recursive dictionaries) ed57ea4 Test Trac #9662 e9d3e28 Comments only 7cbe34f Improve documentation of -ticky a little 13817f0 Test Trac #9077 2b67b8f Test Trac #7862 76d47ed Add stderr for T9662 fcfc87d Disable T4801/peak_megabytes_allocated 53c0120 Fix typo in panic message 3bfd4d8 Binding things matched by an unboxed pattern synonym should require a bang 3cb2a48 If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. 3df7ad1 Apply compulsory unfoldings during desugaring From git at git.haskell.org Wed Nov 12 10:05:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 10:05:03 +0000 (UTC) Subject: [commit: ghc] master: Implement new integer-gmp2 from scratch (re #9281) (c774b28) Message-ID: <20141112100503.105203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c774b28f76ee4c220f7c1c9fd81585e0e3af0e8a/ghc >--------------------------------------------------------------- commit c774b28f76ee4c220f7c1c9fd81585e0e3af0e8a Author: Herbert Valerio Riedel Date: Sun Oct 19 20:37:40 2014 +0200 Implement new integer-gmp2 from scratch (re #9281) This is done as a separate `integer-gmp2` backend library because it turned out to become a complete rewrite from scratch. Due to the different (over)allocation scheme and potentially different accounting (via the new `{shrink,resize}MutableByteArray#` primitives), some of the nofib benchmarks actually results in increased allocation numbers (but not necessarily an increase in runtime!). I believe the allocation numbers could improve if `{resize,shrink}MutableByteArray#` could be optimised to reallocate in-place more efficiently. Here are the more apparent changes in the latest nofib comparision between `integer-gmp` and `integer-gmp2`: ------------------------------------------------------------------ Program Size Allocs Runtime Elapsed TotalMem ------------------------------------------------------------------ ... bernouilli +1.6% +15.3% 0.132 0.132 0.0% ... cryptarithm1 -2.2% 0.0% -9.7% -9.7% 0.0% ... fasta -0.7% -0.0% +10.9% +10.9% 0.0% ... kahan +0.6% +38.9% 0.169 0.169 0.0% ... lcss -0.7% -0.0% -6.4% -6.4% 0.0% ... mandel +1.6% +33.6% 0.049 0.049 0.0% ... pidigits +0.8% +8.5% +3.9% +3.9% 0.0% power +1.4% -23.8% -18.6% -18.6% -16.7% ... primetest +1.3% +50.1% 0.085 0.085 0.0% ... rsa +1.6% +53.4% 0.026 0.026 0.0% ... scs +1.2% +6.6% +6.5% +6.6% +14.3% ... symalg +1.0% +9.5% 0.010 0.010 0.0% ... transform -0.6% -0.0% -5.9% -5.9% 0.0% ... ------------------------------------------------------------------ Min -2.3% -23.8% -18.6% -18.6% -16.7% Max +1.6% +53.4% +10.9% +10.9% +14.3% Geometric Mean -0.3% +1.9% -0.8% -0.8% +0.0% (see P35 / https://phabricator.haskell.org/P35 for full report) By default, `INTEGER_LIBRARY=integer-gmp2` is active now, which results in the package `integer-gmp-1.0.0.0` being registered in the package db. The previous `integer-gmp-0.5.1.0` can be restored by setting `INTEGER_LIBRARY=integer-gmp` (but will probably be removed altogether for GHC 7.12). In-tree GMP support has been stolen from the old `integer-gmp` (while unpatching the custom memory-allocators, as well as forcing `-fPIC`) A minor hack to `ghc-cabal` was necessary in order to support two different `integer-gmp` packages (in different folders) with the same package key. There will be a couple of follow-up commits re-implementing some features that were dropped to keep D82 minimal, as well as further clean-ups/improvements. More information can be found via #9281 and https://ghc.haskell.org/trac/ghc/wiki/Design/IntegerGmp2 Reviewed By: austin, rwbarton, simonmar Differential Revision: https://phabricator.haskell.org/D82 >--------------------------------------------------------------- c774b28f76ee4c220f7c1c9fd81585e0e3af0e8a compiler/basicTypes/Module.lhs | 7 +- compiler/coreSyn/CorePrep.lhs | 3 +- compiler/ghc.mk | 8 +- compiler/prelude/PrelNames.lhs | 2 + ghc.mk | 11 +- libraries/base/GHC/Real.hs | 4 + libraries/base/base.cabal | 19 +- libraries/{integer-gmp => integer-gmp2}/.gitignore | 5 +- libraries/integer-gmp2/LICENSE | 30 + libraries/{base => integer-gmp2}/Setup.hs | 0 libraries/{integer-gmp => integer-gmp2}/aclocal.m4 | 0 libraries/integer-gmp2/cbits/wrappers.c | 281 ++++ .../{integer-gmp => integer-gmp2}/changelog.md | 7 + .../integer-gmp2/config.guess | 0 config.sub => libraries/integer-gmp2/config.sub | 0 .../{integer-gmp => integer-gmp2}/configure.ac | 2 +- .../{integer-gmp => integer-gmp2}/gmp/config.mk.in | 0 libraries/integer-gmp2/gmp/ghc.mk | 124 ++ libraries/integer-gmp2/gmp/gmpsrc.patch | 37 + {libffi => libraries/integer-gmp2/gmp}/ln | 0 .../include/HsIntegerGmp.h.in | 0 .../integer-gmp.buildinfo.in | 0 libraries/integer-gmp2/integer-gmp.cabal | 65 + .../src/GHC/Integer.hs} | 49 +- .../integer-gmp2/src/GHC/Integer/GMP/Internals.hs | 126 ++ .../integer-gmp2/src/GHC/Integer/Logarithms.hs | 73 + .../src/GHC/Integer/Logarithms/Internals.hs | 118 ++ libraries/integer-gmp2/src/GHC/Integer/Type.hs | 1663 ++++++++++++++++++++ mk/config.mk.in | 2 +- rules/foreachLibrary.mk | 2 + testsuite/tests/ghci/scripts/ghci025.stdout | 6 +- testsuite/tests/lib/integer/all.T | 3 +- testsuite/tests/llvm/should_compile/all.T | 2 +- testsuite/tests/perf/should_run/all.T | 3 +- testsuite/tests/perf/space_leaks/all.T | 6 +- testsuite/tests/safeHaskell/check/pkg01/all.T | 1 + testsuite/tests/simplCore/should_run/T5603.hs | 3 +- testsuite/tests/typecheck/should_fail/T5095.stderr | 4 +- .../tests/typecheck/should_fail/tcfail072.stderr | 2 +- utils/ghc-cabal/Main.hs | 4 + 40 files changed, 2628 insertions(+), 44 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c774b28f76ee4c220f7c1c9fd81585e0e3af0e8a From git at git.haskell.org Wed Nov 12 10:48:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 10:48:18 +0000 (UTC) Subject: [commit: ghc] wip/T5462: Do not cleanup GFunctor.o (80111e6) Message-ID: <20141112104818.8FEAE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T5462 Link : http://ghc.haskell.org/trac/ghc/changeset/80111e68dfa2283dcf5f744a1c6ca46c05e9a26c/ghc >--------------------------------------------------------------- commit 80111e68dfa2283dcf5f744a1c6ca46c05e9a26c Author: Jose Pedro Magalhaes Date: Wed Nov 12 10:46:19 2014 +0000 Do not cleanup GFunctor.o T5462No1 removes GFunctor.hi and GFunctor.o as it only has to fail to compile, but T5462Yes might still be using them (if we're running the testsuite in parallel), so it's a bad idea to delete. >--------------------------------------------------------------- 80111e68dfa2283dcf5f744a1c6ca46c05e9a26c testsuite/tests/generics/all.T | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/generics/all.T b/testsuite/tests/generics/all.T index abe28c0..656fac5 100644 --- a/testsuite/tests/generics/all.T +++ b/testsuite/tests/generics/all.T @@ -20,8 +20,8 @@ test('GenCannotDoRep1_7', normal, compile_fail, ['']) test('GenCannotDoRep1_8', normal, compile_fail, ['']) test('T5462Yes', normal, multimod_compile_and_run, ['T5462Yes', '-iGEq -iGEnum -iGFunctor']) -test('T5462No1', extra_clean(['GFunctor/GFunctor.hi', 'GFunctor/GFunctor.o']), multimod_compile_fail, ['T5462No1', '-iGFunctor']) -test('T5462No2', extra_clean(['GFunctor/GFunctor.hi', 'GFunctor/GFunctor.o']), multimod_compile_fail, ['T5462No2', '-iGFunctor']) +test('T5462No1', normal, multimod_compile_fail, ['T5462No1', '-iGFunctor']) +test('T5462No2', normal, multimod_compile_fail, ['T5462No2', '-iGFunctor']) test('T5884', normal, compile, ['']) test('GenNewtype', normal, compile_and_run, ['']) From git at git.haskell.org Wed Nov 12 11:06:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 11:06:55 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Binding things matched by an unboxed pattern synonym should require a bang (05feff2) Message-ID: <20141112110655.9ADAA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/05feff27130542204e5300b53053abe6fd624602/ghc >--------------------------------------------------------------- commit 05feff27130542204e5300b53053abe6fd624602 Author: Dr. ERDI Gergo Date: Sat Nov 8 16:59:47 2014 +0800 Binding things matched by an unboxed pattern synonym should require a bang >--------------------------------------------------------------- 05feff27130542204e5300b53053abe6fd624602 testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/all.T | 2 +- testsuite/tests/patsyn/should_fail/unboxed-bind.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/unboxed-bind.stderr | 6 ++++++ 5 files changed, 28 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index d851bc3..94950a1 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -10,3 +10,4 @@ test('incomplete', normal, compile, ['']) test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) +test('unboxed-bind-bang', normal, compile, ['']) diff --git a/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs new file mode 100644 index 0000000..a972b21 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash, BangPatterns #-} +module ShouldCompile where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let !(P arg) = x in arg diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index ea671dc..ee5768c 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -1,4 +1,3 @@ - test('mono', normal, compile_fail, ['']) test('unidir', normal, compile_fail, ['']) test('local', normal, compile_fail, ['']) @@ -8,3 +7,4 @@ test('T9161-1', normal, compile_fail, ['']) test('T9161-2', normal, compile_fail, ['']) test('T9705-1', normal, compile_fail, ['']) test('T9705-2', normal, compile_fail, ['']) +test('unboxed-bind', normal, compile_fail, ['']) diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.hs b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs new file mode 100644 index 0000000..ef1b070 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module ShouldFail where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let P arg = x in arg diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr new file mode 100644 index 0000000..17ca7af --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr @@ -0,0 +1,6 @@ + +unboxed-bind.hs:10:11: + Pattern bindings containing unlifted types should use an outermost bang pattern: + P arg = x + In the expression: let P arg = x in arg + In an equation for ?f?: f x = let P arg = x in arg From git at git.haskell.org Wed Nov 12 11:06:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 11:06:59 +0000 (UTC) Subject: [commit: ghc] wip/T9732: If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. (9d9b615) Message-ID: <20141112110659.1CC2B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/9d9b615c068a4eed11e7eb0ad6470dd5d97b9081/ghc >--------------------------------------------------------------- commit 9d9b615c068a4eed11e7eb0ad6470dd5d97b9081 Author: Dr. ERDI Gergo Date: Sat Nov 8 18:38:12 2014 +0800 If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. >--------------------------------------------------------------- 9d9b615c068a4eed11e7eb0ad6470dd5d97b9081 compiler/basicTypes/PatSyn.lhs | 50 +++++++-- compiler/ghc.mk | 1 + compiler/iface/BuildTyCl.lhs | 2 +- compiler/iface/IfaceSyn.lhs | 10 +- compiler/iface/MkIface.lhs | 4 +- compiler/iface/TcIface.lhs | 62 +++++++++-- compiler/typecheck/TcBinds.lhs | 8 +- compiler/typecheck/TcPatSyn.lhs | 119 +++++++++++---------- compiler/typecheck/TcPatSyn.lhs-boot | 4 +- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_compile/T9732.hs | 4 + testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_fail/all.T | 1 + .../{unboxed-bind.hs => unboxed-wrapper-naked.hs} | 6 +- .../should_fail/unboxed-wrapper-naked.stderr | 3 + testsuite/tests/patsyn/should_run/all.T | 2 + testsuite/tests/patsyn/should_run/match-unboxed.hs | 21 ++++ .../should_run/match-unboxed.stdout} | 2 + .../tests/patsyn/should_run/unboxed-wrapper.hs | 9 ++ .../should_run/unboxed-wrapper.stdout} | 0 20 files changed, 219 insertions(+), 91 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9d9b615c068a4eed11e7eb0ad6470dd5d97b9081 From git at git.haskell.org Wed Nov 12 11:07:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 11:07:01 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Apply compulsory unfoldings during desugaring. See Note [Unfolding while desugaring] for the rationale. (7ca6589) Message-ID: <20141112110701.A82ED3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/7ca65890bf532b268f6e26212c6909d42d55af81/ghc >--------------------------------------------------------------- commit 7ca65890bf532b268f6e26212c6909d42d55af81 Author: Dr. ERDI Gergo Date: Wed Nov 12 18:18:09 2014 +0800 Apply compulsory unfoldings during desugaring. See Note [Unfolding while desugaring] for the rationale. >--------------------------------------------------------------- 7ca65890bf532b268f6e26212c6909d42d55af81 compiler/deSugar/DsExpr.lhs | 19 ++++++++++++++++++- 1 file changed, 18 insertions(+), 1 deletion(-) diff --git a/compiler/deSugar/DsExpr.lhs b/compiler/deSugar/DsExpr.lhs index 6844f48..10d20d3 100644 --- a/compiler/deSugar/DsExpr.lhs +++ b/compiler/deSugar/DsExpr.lhs @@ -191,7 +191,11 @@ dsLExpr (L loc e) = putSrcSpanDs loc $ dsExpr e dsExpr :: HsExpr Id -> DsM CoreExpr dsExpr (HsPar e) = dsLExpr e dsExpr (ExprWithTySigOut e _) = dsLExpr e -dsExpr (HsVar var) = return (varToCoreExpr var) -- See Note [Desugaring vars] +dsExpr (HsVar var) -- See Note [Unfolding while desugaring] + | isCompulsoryUnfolding unfolding = return $ unfoldingTemplate unfolding + | otherwise = return (varToCoreExpr var) -- See Note [Desugaring vars] + where + unfolding = idUnfolding var dsExpr (HsIPVar _) = panic "dsExpr: HsIPVar" dsExpr (HsLit lit) = dsLit lit dsExpr (HsOverLit lit) = dsOverLit lit @@ -220,6 +224,19 @@ dsExpr (HsApp fun arg) dsExpr (HsUnboundVar _) = panic "dsExpr: HsUnboundVar" \end{code} +Note [Unfolding while desugaring] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Variables with compulsory unfolding must be substituted at desugaring +time. This is needed to preserve the let/app invariant in cases where +the unfolding changes whether wrapping in a case is needed. +Suppose we have a call like this: + I# x +where 'x' has an unfolding like this: + f void# +In this case, 'mkCoreAppDs' needs to see 'f void#', not 'x', to be +able to do the right thing. + + Note [Desugaring vars] ~~~~~~~~~~~~~~~~~~~~~~ In one situation we can get a *coercion* variable in a HsVar, namely From git at git.haskell.org Wed Nov 12 11:07:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 11:07:04 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Fix typo in panic message (b11c8b8) Message-ID: <20141112110704.3B3143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/b11c8b83a244524b554538d126795823f1b0ecf4/ghc >--------------------------------------------------------------- commit b11c8b83a244524b554538d126795823f1b0ecf4 Author: Dr. ERDI Gergo Date: Thu Nov 6 19:38:40 2014 +0800 Fix typo in panic message >--------------------------------------------------------------- b11c8b83a244524b554538d126795823f1b0ecf4 compiler/main/TidyPgm.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs index a975fdd..b7a867d 100644 --- a/compiler/main/TidyPgm.lhs +++ b/compiler/main/TidyPgm.lhs @@ -421,7 +421,7 @@ lookup_aux_id :: TypeEnv -> Var -> Id lookup_aux_id type_env id = case lookupTypeEnv type_env (idName id) of Just (AnId id') -> id' - _other -> pprPanic "lookup_axu_id" (ppr id) + _other -> pprPanic "lookup_aux_id" (ppr id) \end{code} From git at git.haskell.org Wed Nov 12 11:07:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 11:07:06 +0000 (UTC) Subject: [commit: ghc] wip/T9732's head updated: Apply compulsory unfoldings during desugaring. See Note [Unfolding while desugaring] for the rationale. (7ca6589) Message-ID: <20141112110706.4768B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9732' now includes: c774b28 Implement new integer-gmp2 from scratch (re #9281) b11c8b8 Fix typo in panic message 05feff2 Binding things matched by an unboxed pattern synonym should require a bang 9d9b615 If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. 7ca6589 Apply compulsory unfoldings during desugaring. See Note [Unfolding while desugaring] for the rationale. From git at git.haskell.org Wed Nov 12 11:47:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 11:47:57 +0000 (UTC) Subject: [commit: ghc] branch 'wip/desugar-unfold' created Message-ID: <20141112114757.DBBAD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/desugar-unfold Referencing: 28bea84e0625af922aef104d6c6e6f06f5b89a0e From git at git.haskell.org Wed Nov 12 11:48:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 11:48:00 +0000 (UTC) Subject: [commit: ghc] wip/desugar-unfold: Apply compulsory unfoldings during desugaring. See Note [Unfolding while desugaring] for the rationale. (28bea84) Message-ID: <20141112114800.72AA73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/desugar-unfold Link : http://ghc.haskell.org/trac/ghc/changeset/28bea84e0625af922aef104d6c6e6f06f5b89a0e/ghc >--------------------------------------------------------------- commit 28bea84e0625af922aef104d6c6e6f06f5b89a0e Author: Dr. ERDI Gergo Date: Wed Nov 12 18:18:09 2014 +0800 Apply compulsory unfoldings during desugaring. See Note [Unfolding while desugaring] for the rationale. >--------------------------------------------------------------- 28bea84e0625af922aef104d6c6e6f06f5b89a0e compiler/deSugar/DsExpr.lhs | 19 ++++++++++++++++++- 1 file changed, 18 insertions(+), 1 deletion(-) diff --git a/compiler/deSugar/DsExpr.lhs b/compiler/deSugar/DsExpr.lhs index 6844f48..10d20d3 100644 --- a/compiler/deSugar/DsExpr.lhs +++ b/compiler/deSugar/DsExpr.lhs @@ -191,7 +191,11 @@ dsLExpr (L loc e) = putSrcSpanDs loc $ dsExpr e dsExpr :: HsExpr Id -> DsM CoreExpr dsExpr (HsPar e) = dsLExpr e dsExpr (ExprWithTySigOut e _) = dsLExpr e -dsExpr (HsVar var) = return (varToCoreExpr var) -- See Note [Desugaring vars] +dsExpr (HsVar var) -- See Note [Unfolding while desugaring] + | isCompulsoryUnfolding unfolding = return $ unfoldingTemplate unfolding + | otherwise = return (varToCoreExpr var) -- See Note [Desugaring vars] + where + unfolding = idUnfolding var dsExpr (HsIPVar _) = panic "dsExpr: HsIPVar" dsExpr (HsLit lit) = dsLit lit dsExpr (HsOverLit lit) = dsOverLit lit @@ -220,6 +224,19 @@ dsExpr (HsApp fun arg) dsExpr (HsUnboundVar _) = panic "dsExpr: HsUnboundVar" \end{code} +Note [Unfolding while desugaring] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Variables with compulsory unfolding must be substituted at desugaring +time. This is needed to preserve the let/app invariant in cases where +the unfolding changes whether wrapping in a case is needed. +Suppose we have a call like this: + I# x +where 'x' has an unfolding like this: + f void# +In this case, 'mkCoreAppDs' needs to see 'f void#', not 'x', to be +able to do the right thing. + + Note [Desugaring vars] ~~~~~~~~~~~~~~~~~~~~~~ In one situation we can get a *coercion* variable in a HsVar, namely From git at git.haskell.org Wed Nov 12 12:05:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 12:05:44 +0000 (UTC) Subject: [commit: ghc] wip/T8584: nlHsTyApps: for applying a function both on type- and term-level arguments (a9e5e5d) Message-ID: <20141112120544.8D34C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/a9e5e5d1bbb620335586d857ed844f8e242162f2/ghc >--------------------------------------------------------------- commit a9e5e5d1bbb620335586d857ed844f8e242162f2 Author: Dr. ERDI Gergo Date: Fri Nov 7 22:49:52 2014 +0800 nlHsTyApps: for applying a function both on type- and term-level arguments >--------------------------------------------------------------- a9e5e5d1bbb620335586d857ed844f8e242162f2 compiler/hsSyn/HsUtils.lhs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/compiler/hsSyn/HsUtils.lhs b/compiler/hsSyn/HsUtils.lhs index 12e2388..df2406f 100644 --- a/compiler/hsSyn/HsUtils.lhs +++ b/compiler/hsSyn/HsUtils.lhs @@ -28,7 +28,7 @@ module HsUtils( mkHsOpApp, mkHsDo, mkHsComp, mkHsWrapPat, mkHsWrapPatCo, mkLHsPar, mkHsCmdCast, - nlHsTyApp, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, + nlHsTyApp, nlHsTyApps, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, nlHsDo, nlHsOpApp, nlHsLam, nlHsPar, nlHsIf, nlHsCase, nlList, mkLHsTupleExpr, mkLHsVarTuple, missingTupArg, toHsType, toHsKind, @@ -177,6 +177,9 @@ mkSimpleHsAlt pat expr nlHsTyApp :: name -> [Type] -> LHsExpr name nlHsTyApp fun_id tys = noLoc (HsWrap (mkWpTyApps tys) (HsVar fun_id)) +nlHsTyApps :: name -> [Type] -> [LHsExpr name] -> LHsExpr name +nlHsTyApps fun_id tys xs = foldl nlHsApp (nlHsTyApp fun_id tys) xs + --------- Adding parens --------- mkLHsPar :: LHsExpr name -> LHsExpr name -- Wrap in parens if hsExprNeedsParens says it needs them From git at git.haskell.org Wed Nov 12 12:05:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 12:05:49 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Renamer for PatSynSigs: handle type variable bindings (03fe096) Message-ID: <20141112120549.B1F053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/03fe09665941be7bea305c114789109cbedfffcb/ghc >--------------------------------------------------------------- commit 03fe09665941be7bea305c114789109cbedfffcb Author: Dr. ERDI Gergo Date: Fri Nov 7 19:29:06 2014 +0800 Renamer for PatSynSigs: handle type variable bindings >--------------------------------------------------------------- 03fe09665941be7bea305c114789109cbedfffcb compiler/hsSyn/HsBinds.lhs | 8 ++++---- compiler/rename/RnBinds.lhs | 34 ++++++++++++++++------------------ 2 files changed, 20 insertions(+), 22 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index bbf6bc2..23534cf 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -568,12 +568,12 @@ data Sig name TypeSig [Located name] (LHsType name) -- | A pattern synonym type signature - -- @pattern (Eq b) => P a b :: (Num a) => T a + -- @pattern type forall b. (Eq b) => P a b :: forall a. (Num a) => T a | PatSynSig (Located name) (HsPatSynDetails (LHsType name)) (LHsType name) -- Type - (LHsContext name) -- Provided context - (LHsContext name) -- Required contex + (HsExplicitFlag, LHsTyVarBndrs name, LHsContext name) -- Provided context + (HsExplicitFlag, LHsTyVarBndrs name, LHsContext name) -- Required contex -- | A type signature for a default method inside a class -- @@ -730,7 +730,7 @@ ppr_sig (SpecSig var ty inl) = pragBrackets (pprSpec (unLoc var) (ppr ty) i ppr_sig (InlineSig var inl) = pragBrackets (ppr inl <+> pprPrefixOcc (unLoc var)) ppr_sig (SpecInstSig ty) = pragBrackets (ptext (sLit "SPECIALIZE instance") <+> ppr ty) ppr_sig (MinimalSig bf) = pragBrackets (pprMinimalSig bf) -ppr_sig (PatSynSig name arg_tys ty prov req) +ppr_sig (PatSynSig name arg_tys ty (_, _, prov) (_, _, req)) = pprPatSynSig (unLoc name) False args (ppr ty) (pprCtx prov) (pprCtx req) where args = fmap ppr arg_tys diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index c2489cb..b43993e 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -30,7 +30,7 @@ import {-# SOURCE #-} RnExpr( rnLExpr, rnStmts ) import HsSyn import TcRnMonad import TcEvidence ( emptyTcEvBinds ) -import RnTypes ( bindSigTyVarsFV, rnHsSigType, rnLHsType, checkPrecMatch, rnContext ) +import RnTypes import RnPat import RnNames import RnEnv @@ -841,23 +841,21 @@ renameSig ctxt sig@(MinimalSig bf) = do new_bf <- traverse (lookupSigOccRn ctxt sig) bf return (MinimalSig new_bf, emptyFVs) -renameSig ctxt sig@(PatSynSig v args ty prov req) - = do v' <- lookupSigOccRn ctxt sig v - let doc = quotes (ppr v) - rn_type = rnHsSigType doc - (ty', fvs1) <- rn_type ty - (args', fvs2) <- case args of - PrefixPatSyn tys -> - do (tys, fvs) <- unzip <$> mapM rn_type tys - return (PrefixPatSyn tys, plusFVs fvs) - InfixPatSyn left right -> - do (left', fvs1) <- rn_type left - (right', fvs2) <- rn_type right - return (InfixPatSyn left' right', fvs1 `plusFV` fvs2) - (prov', fvs3) <- rnContext (TypeSigCtx doc) prov - (req', fvs4) <- rnContext (TypeSigCtx doc) req - let fvs = plusFVs [fvs1, fvs2, fvs3, fvs4] - return (PatSynSig v' args' ty' prov' req', fvs) +renameSig ctxt sig@(PatSynSig v (flag, qtvs) prov req ty) + = do { v' <- lookupSigOccRn ctxt sig v + ; let doc = TypeSigCtx $ quotes (ppr v) + ; loc <- getSrcSpanM + + ; let (tv_kvs, tvs) = extractHsTysRdrTyVars (ty:unLoc prov ++ unLoc req) + ; let tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ tvs + + ; bindHsTyVars doc Nothing tv_kvs tv_bndrs $ \ tyvars -> do + { (prov', fvs1) <- rnContext doc prov + ; (req', fvs2) <- rnContext doc req + ; (ty', fvs3) <- rnLHsType doc ty + + ; let fvs = plusFVs [fvs1, fvs2, fvs3] + ; return (PatSynSig v' (flag, tyvars) prov' req' ty', fvs) }} ppr_sig_bndrs :: [Located RdrName] -> SDoc ppr_sig_bndrs bs = quotes (pprWithCommas ppr bs) From git at git.haskell.org Wed Nov 12 12:05:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 12:05:47 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Change output of ':i' for pattern synonyms to be in sync with new syntax (faa9d47) Message-ID: <20141112120547.2A9E83A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/faa9d4792df0ae9197b858e5c12ee7e2112724d2/ghc >--------------------------------------------------------------- commit faa9d4792df0ae9197b858e5c12ee7e2112724d2 Author: Dr. ERDI Gergo Date: Sun Aug 3 15:26:13 2014 +0200 Change output of ':i' for pattern synonyms to be in sync with new syntax >--------------------------------------------------------------- faa9d4792df0ae9197b858e5c12ee7e2112724d2 compiler/hsSyn/HsBinds.lhs | 52 +++++++++++++++++++------------------------- compiler/hsSyn/HsTypes.lhs | 16 +++++++++----- compiler/iface/IfaceSyn.lhs | 19 ++++++---------- compiler/iface/IfaceType.lhs | 15 ++++++++----- 4 files changed, 49 insertions(+), 53 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc faa9d4792df0ae9197b858e5c12ee7e2112724d2 From git at git.haskell.org Wed Nov 12 12:05:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 12:05:54 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add parser for pattern synonym type signatures. Syntax is of the form (b99afa8) Message-ID: <20141112120554.D82E63A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/b99afa87a790532259e949ed987da50573742daa/ghc >--------------------------------------------------------------- commit b99afa87a790532259e949ed987da50573742daa Author: Dr. ERDI Gergo Date: Tue Nov 11 18:54:14 2014 +0800 Add parser for pattern synonym type signatures. Syntax is of the form pattern P :: (Prov b) => (Req a) => a -> b -> Int -> T a which declares a pattern synonym called `P`, with argument types `a`, `b`, and `Int`, and result type `T a`, with provided context `(Prov b)` and required context `(Req a)`. >--------------------------------------------------------------- b99afa87a790532259e949ed987da50573742daa compiler/parser/Parser.y | 51 +++++++++++++++++++++++++++++++-------------- compiler/parser/RdrHsSyn.hs | 27 +++++------------------- 2 files changed, 40 insertions(+), 38 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 1123375..0cceb09 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -860,29 +860,47 @@ role : VARID { sL1 $1 $ Just $ getVARID $1 } -- Glasgow extension: pattern synonyms pattern_synonym_decl :: { LHsDecl RdrName } - : 'pattern' pat '=' pat - {% do { (name, args) <- splitPatSyn $2 - ; return $ sLL $1 $> . ValD $ mkPatSynBind name args $4 ImplicitBidirectional - }} - | 'pattern' pat '<-' pat - {% do { (name, args) <- splitPatSyn $2 - ; return $ sLL $1 $> . ValD $ mkPatSynBind name args $4 Unidirectional - }} - | 'pattern' pat '<-' pat where_decls - {% do { (name, args) <- splitPatSyn $2 - ; mg <- toPatSynMatchGroup name $5 + : 'pattern' pattern_synonym_lhs '=' pat + { let (name, args) = $2 + in sLL $1 $> . ValD $ mkPatSynBind name args $4 ImplicitBidirectional } + | 'pattern' pattern_synonym_lhs '<-' pat + { let (name, args) = $2 + in sLL $1 $> . ValD $ mkPatSynBind name args $4 Unidirectional } + | 'pattern' pattern_synonym_lhs '<-' pat where_decls + {% do { let (name, args) = $2 + ; mg <- mkPatSynMatchGroup name $5 ; return $ sLL $1 $> . ValD $ - mkPatSynBind name args $4 (ExplicitBidirectional mg) - }} + mkPatSynBind name args $4 (ExplicitBidirectional mg) }} -where_decls :: { Located (OrdList (LHsDecl RdrName)) } - : 'where' '{' decls '}' { $3 } - | 'where' vocurly decls close { $3 } +pattern_synonym_lhs :: { (Located RdrName, HsPatSynDetails (Located RdrName)) } + : con vars0 { ($1, PrefixPatSyn $2) } + | varid consym varid { ($2, InfixPatSyn $1 $3) } vars0 :: { [Located RdrName] } : {- empty -} { [] } | varid vars0 { $1 : $2 } +where_decls :: { Located (OrdList (LHsDecl RdrName)) } + : 'where' '{' decls '}' { $3 } + | 'where' vocurly decls close { $3 } + +pattern_synonym_sig :: { LSig RdrName } + : 'pattern' con '::' ptype + { let (flag, qtvs, prov, req, ty) = unLoc $4 + in sLL $1 $> $ PatSynSig $2 (flag, mkHsQTvs qtvs) prov req ty } + +ptype :: { Located (HsExplicitFlag, [LHsTyVarBndr RdrName], LHsContext RdrName, LHsContext RdrName, LHsType RdrName) } + : 'forall' tv_bndrs '.' ptype + {% do { hintExplicitForall (getLoc $1) + ; let (_, qtvs', prov, req, ty) = unLoc $4 + ; return $ sLL $1 $> (Explicit, $2 ++ qtvs', prov, req ,ty) }} + | context '=>' context '=>' type + { sLL $1 $> (Implicit, [], $1, $3, $5) } + | context '=>' type + { sLL $1 $> (Implicit, [], $1, noLoc [], $3) } + | type + { sL1 $1 (Implicit, [], noLoc [], noLoc [], $1) } + ----------------------------------------------------------------------------- -- Nested declarations @@ -1490,6 +1508,7 @@ sigdecl :: { Located (OrdList (LHsDecl RdrName)) } { sLL $1 $> $ toOL [ sLL $1 $> $ SigD (TypeSig ($1 : reverse (unLoc $3)) $5) ] } | infix prec ops { sLL $1 $> $ toOL [ sLL $1 $> $ SigD (FixSig (FixitySig n (Fixity $2 (unLoc $1)))) | n <- unLoc $3 ] } + | pattern_synonym_sig { sLL $1 $> $ unitOL $ sLL $1 $> . SigD . unLoc $ $1 } | '{-# INLINE' activation qvar '#-}' { sLL $1 $> $ unitOL (sLL $1 $> $ SigD (InlineSig $3 (mkInlinePragma (getINLINE $1) $2))) } | '{-# SPECIALISE' activation qvar '::' sigtypes1 '#-}' diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs index 625c4dc..e945e43 100644 --- a/compiler/parser/RdrHsSyn.hs +++ b/compiler/parser/RdrHsSyn.hs @@ -18,7 +18,7 @@ module RdrHsSyn ( mkTyFamInst, mkFamDecl, splitCon, mkInlinePragma, - splitPatSyn, toPatSynMatchGroup, + mkPatSynMatchGroup, mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp mkTyClD, mkInstD, @@ -414,33 +414,16 @@ splitCon ty mk_rest [L _ (HsRecTy flds)] = RecCon flds mk_rest ts = PrefixCon ts -splitPatSyn :: LPat RdrName - -> P (Located RdrName, HsPatSynDetails (Located RdrName)) -splitPatSyn (L _ (ParPat pat)) = splitPatSyn pat -splitPatSyn pat@(L loc (ConPatIn con details)) = do - details' <- case details of - PrefixCon pats -> liftM PrefixPatSyn (mapM patVar pats) - InfixCon pat1 pat2 -> liftM2 InfixPatSyn (patVar pat1) (patVar pat2) - RecCon{} -> recordPatSynErr loc pat - return (con, details') - where - patVar :: LPat RdrName -> P (Located RdrName) - patVar (L loc (VarPat v)) = return $ L loc v - patVar (L _ (ParPat pat)) = patVar pat - patVar (L loc pat) = parseErrorSDoc loc $ - text "Pattern synonym arguments must be variable names:" $$ - ppr pat -splitPatSyn pat@(L loc _) = parseErrorSDoc loc $ - text "invalid pattern synonym declaration:" $$ ppr pat - recordPatSynErr :: SrcSpan -> LPat RdrName -> P a recordPatSynErr loc pat = parseErrorSDoc loc $ text "record syntax not supported for pattern synonym declarations:" $$ ppr pat -toPatSynMatchGroup :: Located RdrName -> Located (OrdList (LHsDecl RdrName)) -> P (MatchGroup RdrName (LHsExpr RdrName)) -toPatSynMatchGroup (L _ patsyn_name) (L _ decls) = +mkPatSynMatchGroup :: Located RdrName + -> Located (OrdList (LHsDecl RdrName)) + -> P (MatchGroup RdrName (LHsExpr RdrName)) +mkPatSynMatchGroup (L _ patsyn_name) (L _ decls) = do { matches <- mapM fromDecl (fromOL decls) ; return $ mkMatchGroup FromSource matches } where From git at git.haskell.org Wed Nov 12 12:05:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 12:05:52 +0000 (UTC) Subject: [commit: ghc] wip/T8584: tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures (2f2639d) Message-ID: <20141112120552.4DF2B3A302@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/2f2639de9be9edb073439b3233de620b0572ee50/ghc >--------------------------------------------------------------- commit 2f2639de9be9edb073439b3233de620b0572ee50 Author: Dr. ERDI Gergo Date: Sun Jul 27 14:10:34 2014 +0200 tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures >--------------------------------------------------------------- 2f2639de9be9edb073439b3233de620b0572ee50 compiler/typecheck/TcBinds.lhs | 52 +++++++-- compiler/typecheck/TcClassDcl.lhs | 4 +- compiler/typecheck/TcPat.lhs | 23 +++- compiler/typecheck/TcPatSyn.lhs | 199 ++++++++++++++++++++++++++--------- compiler/typecheck/TcPatSyn.lhs-boot | 9 +- 5 files changed, 223 insertions(+), 64 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2f2639de9be9edb073439b3233de620b0572ee50 From git at git.haskell.org Wed Nov 12 12:06:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 12:06:03 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Update baseline shift/reduce conflict number (24ef4c6) Message-ID: <20141112120603.029153A302@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/24ef4c6431101d3c0fb46a9aea0e8e78d0d3b1b3/ghc >--------------------------------------------------------------- commit 24ef4c6431101d3c0fb46a9aea0e8e78d0d3b1b3 Author: Dr. ERDI Gergo Date: Wed Jul 2 19:18:43 2014 +0800 Update baseline shift/reduce conflict number >--------------------------------------------------------------- 24ef4c6431101d3c0fb46a9aea0e8e78d0d3b1b3 compiler/parser/Parser.y | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 2e1b777..1123375 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -86,6 +86,12 @@ import TysWiredIn ( unitTyCon, unitDataCon, tupleTyCon, tupleCon, nilDataC {- ----------------------------------------------------------------------------- +25 June 2014 + +Conflicts: 47 shift/reduce + 1 reduce/reduce + +----------------------------------------------------------------------------- 12 October 2012 Conflicts: 43 shift/reduce From git at git.haskell.org Wed Nov 12 12:05:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 12:05:57 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add test cases (8ea3a36) Message-ID: <20141112120557.DE2C43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/8ea3a36666982c8631b9a9ad7a54674a3fa5ae06/ghc >--------------------------------------------------------------- commit 8ea3a36666982c8631b9a9ad7a54674a3fa5ae06 Author: Dr. ERDI Gergo Date: Sun Nov 2 14:35:49 2014 +0800 Add test cases >--------------------------------------------------------------- 8ea3a36666982c8631b9a9ad7a54674a3fa5ae06 testsuite/tests/patsyn/should_compile/T8584-1.hs | 10 ++++++++++ testsuite/tests/patsyn/should_compile/T8968-1.hs | 8 ++++++++ testsuite/tests/patsyn/should_compile/all.T | 2 ++ 3 files changed, 20 insertions(+) diff --git a/testsuite/tests/patsyn/should_compile/T8584-1.hs b/testsuite/tests/patsyn/should_compile/T8584-1.hs new file mode 100644 index 0000000..7a017c8 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8584-1.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms #-} +module ShouldCompile where + +pattern type (Eq a) => Single a :: (Show a) => [a] +-- pattern type Single a :: (Eq a, Show a) => [a] +-- pattern type Single a :: [a] +pattern Single x = [x] + +-- f :: (Show a) => [a] -> a +foobar (Single x) = x diff --git a/testsuite/tests/patsyn/should_compile/T8968-1.hs b/testsuite/tests/patsyn/should_compile/T8968-1.hs new file mode 100644 index 0000000..f4a1dc4 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8968-1.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE GADTs, KindSignatures, PatternSynonyms #-} +module ShouldCompile where + +data X :: (* -> *) -> * -> * where + Y :: f a -> X f (Maybe a) + +pattern type C a :: X Maybe (Maybe a) +pattern C x = Y (Just x) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index d851bc3..8896008 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -10,3 +10,5 @@ test('incomplete', normal, compile, ['']) test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) +test('T8968-1', normal, compile, ['']) +test('T8584-1', normal, compile, ['']) From git at git.haskell.org Wed Nov 12 12:06:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 12:06:05 +0000 (UTC) Subject: [commit: ghc] wip/T8584's head updated: Add test cases (8ea3a36) Message-ID: <20141112120605.474A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T8584' now includes: 8e66365 Unlit overlooked GHC/Conc/Sync.lhs e2769df Use (.) and id from Base in Control.Applicative 8710136 Move Data.Functor.Identity from transformers to base 7ae596a Typo fix; Trac #9787 4923cea Define list monad operations using comprehensions e567130 De-bias Data.Foldable and improve docstrings 97420b0 Comments only (on recursive dictionaries) ed57ea4 Test Trac #9662 e9d3e28 Comments only 7cbe34f Improve documentation of -ticky a little 13817f0 Test Trac #9077 2b67b8f Test Trac #7862 76d47ed Add stderr for T9662 fcfc87d Disable T4801/peak_megabytes_allocated c774b28 Implement new integer-gmp2 from scratch (re #9281) a9e5e5d nlHsTyApps: for applying a function both on type- and term-level arguments 03fe096 Renamer for PatSynSigs: handle type variable bindings 2f2639d tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures faa9d47 Change output of ':i' for pattern synonyms to be in sync with new syntax 353d11f Use user-supplied type variables (when available) in pattern synonym type signatures 24ef4c6 Update baseline shift/reduce conflict number b99afa8 Add parser for pattern synonym type signatures. Syntax is of the form 8ea3a36 Add test cases From git at git.haskell.org Wed Nov 12 12:06:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 12:06:00 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Use user-supplied type variables (when available) in pattern synonym type signatures (353d11f) Message-ID: <20141112120600.6FDCB3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/353d11fca8e52eae31b1f48832ae8db2db35eec1/ghc >--------------------------------------------------------------- commit 353d11fca8e52eae31b1f48832ae8db2db35eec1 Author: Dr. ERDI Gergo Date: Sun Nov 9 15:46:46 2014 +0800 Use user-supplied type variables (when available) in pattern synonym type signatures >--------------------------------------------------------------- 353d11fca8e52eae31b1f48832ae8db2db35eec1 compiler/rename/RnBinds.lhs | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index b43993e..80239e9 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -846,8 +846,16 @@ renameSig ctxt sig@(PatSynSig v (flag, qtvs) prov req ty) ; let doc = TypeSigCtx $ quotes (ppr v) ; loc <- getSrcSpanM - ; let (tv_kvs, tvs) = extractHsTysRdrTyVars (ty:unLoc prov ++ unLoc req) - ; let tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ tvs + ; let (tv_kvs, mentioned) = extractHsTysRdrTyVars (ty:unLoc prov ++ unLoc req) + ; tv_bndrs <- case flag of + Implicit -> + return $ mkHsQTvs . userHsTyVarBndrs loc $ mentioned + Explicit -> + do { let heading = ptext (sLit "In the pattern synonym type signature") + <+> quotes (ppr sig) + ; warnUnusedForAlls (heading $$ docOfHsDocContext doc) qtvs mentioned + ; return qtvs } + Qualified -> panic "renameSig: Qualified" ; bindHsTyVars doc Nothing tv_kvs tv_bndrs $ \ tyvars -> do { (prov', fvs1) <- rnContext doc prov From git at git.haskell.org Wed Nov 12 13:12:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 13:12:44 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T9705' deleted Message-ID: <20141112131244.793E13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T9705 From git at git.haskell.org Wed Nov 12 13:14:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 13:14:00 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T9783' deleted Message-ID: <20141112131400.A64283A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T9783 From git at git.haskell.org Wed Nov 12 15:34:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 15:34:54 +0000 (UTC) Subject: [commit: ghc] master: Fix build errors on Windows (these tests still don't work though) (4b5d62a) Message-ID: <20141112153454.23DC43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4b5d62ab04103843ba07128d90499fbe103d773b/ghc >--------------------------------------------------------------- commit 4b5d62ab04103843ba07128d90499fbe103d773b Author: Simon Marlow Date: Wed Nov 5 18:05:10 2014 +0000 Fix build errors on Windows (these tests still don't work though) >--------------------------------------------------------------- 4b5d62ab04103843ba07128d90499fbe103d773b testsuite/tests/rts/linker_error.c | 3 +++ testsuite/tests/rts/linker_unload.c | 3 +++ 2 files changed, 6 insertions(+) diff --git a/testsuite/tests/rts/linker_error.c b/testsuite/tests/rts/linker_error.c index 60d24a5..715eabd 100644 --- a/testsuite/tests/rts/linker_error.c +++ b/testsuite/tests/rts/linker_error.c @@ -2,6 +2,9 @@ #include #include #include "Rts.h" +#if defined(mingw32_HOST_OS) +#include +#endif #define ITERATIONS 10 diff --git a/testsuite/tests/rts/linker_unload.c b/testsuite/tests/rts/linker_unload.c index 4980eeb..8d1984f 100644 --- a/testsuite/tests/rts/linker_unload.c +++ b/testsuite/tests/rts/linker_unload.c @@ -2,6 +2,9 @@ #include #include #include "Rts.h" +#if defined(mingw32_HOST_OS) +#include +#endif #define ITERATIONS 10000 From git at git.haskell.org Wed Nov 12 15:35:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 15:35:00 +0000 (UTC) Subject: [commit: ghc] master: fix allocLimit3 on Windows (8c10b67) Message-ID: <20141112153500.C8B223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8c10b67ba049477cc9ed23e61f5bd119e1cefc29/ghc >--------------------------------------------------------------- commit 8c10b67ba049477cc9ed23e61f5bd119e1cefc29 Author: Simon Marlow Date: Thu Nov 6 16:42:49 2014 +0000 fix allocLimit3 on Windows >--------------------------------------------------------------- 8c10b67ba049477cc9ed23e61f5bd119e1cefc29 testsuite/tests/concurrent/should_run/all.T | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/concurrent/should_run/all.T b/testsuite/tests/concurrent/should_run/all.T index b77d9ac..e72bffe 100644 --- a/testsuite/tests/concurrent/should_run/all.T +++ b/testsuite/tests/concurrent/should_run/all.T @@ -90,7 +90,12 @@ test('T9379', normal, compile_and_run, ['']) test('allocLimit1', exit_code(1), compile_and_run, ['']) test('allocLimit2', normal, compile_and_run, ['']) -test('allocLimit3', exit_code(1), compile_and_run, ['']) + +# The non-threaded RTS on Windows doesn't handle throwing exceptions at I/O +# operations very well, and ends up duplicating the I/O, giving wrong results. +test('allocLimit3', [ when(opsys('mingw32'), only_ways(threaded_ways)), + exit_code(1) ], compile_and_run, ['']) + test('allocLimit4', [ extra_run_opts('+RTS -xq300k -RTS') ], compile_and_run, ['']) From git at git.haskell.org Wed Nov 12 15:34:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 15:34:58 +0000 (UTC) Subject: [commit: ghc] master: Per-thread allocation counters and limits (d70b19b) Message-ID: <20141112153458.2993D3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d70b19bfb5ed79b22c2ac31e22f46782fc47a117/ghc >--------------------------------------------------------------- commit d70b19bfb5ed79b22c2ac31e22f46782fc47a117 Author: Simon Marlow Date: Wed Oct 15 00:03:15 2014 +0100 Per-thread allocation counters and limits This reverts commit f0fcc41d755876a1b02d1c7c79f57515059f6417. New changes: now works on 32-bit platforms too. I added some basic support for 64-bit subtraction and comparison operations to the x86 NCG. >--------------------------------------------------------------- d70b19bfb5ed79b22c2ac31e22f46782fc47a117 compiler/cmm/CmmLayoutStack.hs | 9 +- compiler/cmm/CmmMachOp.hs | 28 ++- compiler/codeGen/StgCmmForeign.hs | 274 +++++++++++++++------ compiler/nativeGen/X86/CodeGen.hs | 71 ++++-- compiler/nativeGen/X86/Instr.hs | 3 + compiler/nativeGen/X86/Ppr.hs | 7 +- includes/rts/Constants.h | 6 + includes/rts/Flags.h | 8 + includes/rts/Threads.h | 8 +- includes/rts/storage/TSO.h | 31 ++- libraries/base/Control/Exception.hs | 1 + libraries/base/Control/Exception/Base.hs | 1 + libraries/base/GHC/Conc.hs | 6 + libraries/base/GHC/Conc/Sync.hs | 92 ++++++- libraries/base/GHC/IO/Exception.hs | 21 +- rts/Capability.c | 4 + rts/HeapStackCheck.cmm | 4 +- rts/Linker.c | 4 + rts/Prelude.h | 2 + rts/RaiseAsync.c | 54 ++++ rts/RaiseAsync.h | 4 + rts/RtsFlags.c | 10 + rts/RtsStartup.c | 1 + rts/Schedule.c | 19 ++ rts/Threads.c | 77 +++--- rts/package.conf.in | 2 + rts/sm/Storage.c | 6 + rts/win32/libHSbase.def | 5 +- testsuite/tests/concurrent/should_run/all.T | 7 + .../tests/concurrent/should_run/allocLimit1.hs | 9 + .../tests/concurrent/should_run/allocLimit1.stderr | 1 + .../tests/concurrent/should_run/allocLimit2.hs | 17 ++ .../tests/concurrent/should_run/allocLimit3.hs | 15 ++ .../tests/concurrent/should_run/allocLimit3.stderr | 1 + .../should_run/allocLimit3.stdout} | 1 - .../tests/concurrent/should_run/allocLimit4.hs | 31 +++ utils/deriveConstants/DeriveConstants.hs | 1 + 37 files changed, 673 insertions(+), 168 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d70b19bfb5ed79b22c2ac31e22f46782fc47a117 From git at git.haskell.org Wed Nov 12 15:48:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 15:48:56 +0000 (UTC) Subject: [commit: ghc] wip/rae: Testsuite wibble due to #9404 (13f9812) Message-ID: <20141112154856.025673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/13f98123317d4dfe66db09a78e196c5b7cd48a7c/ghc >--------------------------------------------------------------- commit 13f98123317d4dfe66db09a78e196c5b7cd48a7c Author: Richard Eisenberg Date: Tue Nov 11 07:58:03 2014 -0500 Testsuite wibble due to #9404 [skip ci] >--------------------------------------------------------------- 13f98123317d4dfe66db09a78e196c5b7cd48a7c testsuite/tests/ghci/scripts/ghci046.script | 4 ++-- testsuite/tests/ghci/scripts/ghci046.stdout | 6 ++++-- testsuite/tests/typecheck/should_fail/T5570.stderr | 2 +- testsuite/tests/typecheck/should_fail/T7857.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/tcfail133.stderr | 6 +++--- 5 files changed, 12 insertions(+), 10 deletions(-) diff --git a/testsuite/tests/ghci/scripts/ghci046.script b/testsuite/tests/ghci/scripts/ghci046.script index f07e06f..28c5cde 100644 --- a/testsuite/tests/ghci/scripts/ghci046.script +++ b/testsuite/tests/ghci/scripts/ghci046.script @@ -12,8 +12,8 @@ type instance OR HTrue HTrue = HTrue type instance OR HTrue HFalse = HTrue type instance OR HFalse HTrue = HTrue type instance OR HFalse HFalse = HFalse -:t undefined :: AND HTrue HTrue -:t undefined :: AND (OR HFalse HTrue) (OR HTrue HFalse) +:kind! AND HTrue HTrue +:kind! AND (OR HFalse HTrue) (OR HTrue HFalse) let t = undefined :: AND HTrue HTrue let f = undefined :: AND HTrue HFalse type instance AND HTrue HTrue = HFalse diff --git a/testsuite/tests/ghci/scripts/ghci046.stdout b/testsuite/tests/ghci/scripts/ghci046.stdout index d600596..c4e7cf3 100644 --- a/testsuite/tests/ghci/scripts/ghci046.stdout +++ b/testsuite/tests/ghci/scripts/ghci046.stdout @@ -1,4 +1,6 @@ -undefined :: AND HTrue HTrue :: HTrue -undefined :: AND (OR HFalse HTrue) (OR HTrue HFalse) :: HTrue +AND HTrue HTrue :: * += HTrue +AND (OR HFalse HTrue) (OR HTrue HFalse) :: * += HTrue t :: HTrue t :: HFalse diff --git a/testsuite/tests/typecheck/should_fail/T5570.stderr b/testsuite/tests/typecheck/should_fail/T5570.stderr index 21a4e0c..15d5c8a 100644 --- a/testsuite/tests/typecheck/should_fail/T5570.stderr +++ b/testsuite/tests/typecheck/should_fail/T5570.stderr @@ -2,7 +2,7 @@ T5570.hs:7:16: Couldn't match kind ?*? with ?#? When matching types - s0 :: * + r0 :: * Double# :: # In the second argument of ?($)?, namely ?D# $ 3.0##? In the expression: print $ D# $ 3.0## diff --git a/testsuite/tests/typecheck/should_fail/T7857.stderr b/testsuite/tests/typecheck/should_fail/T7857.stderr index 6517b77..698d280 100644 --- a/testsuite/tests/typecheck/should_fail/T7857.stderr +++ b/testsuite/tests/typecheck/should_fail/T7857.stderr @@ -1,10 +1,10 @@ T7857.hs:8:11: - Could not deduce (PrintfType s0) arising from a use of ?printf? + Could not deduce (PrintfType r0) arising from a use of ?printf? from the context (PrintfArg t) bound by the inferred type of g :: PrintfArg t => t -> b at T7857.hs:8:1-21 - The type variable ?s0? is ambiguous + The type variable ?r0? is ambiguous Note: there are several potential instances: instance [safe] (PrintfArg a, PrintfType r) => PrintfType (a -> r) -- Defined in ?Text.Printf? diff --git a/testsuite/tests/typecheck/should_fail/tcfail133.stderr b/testsuite/tests/typecheck/should_fail/tcfail133.stderr index 058b063..0198f3c 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail133.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail133.stderr @@ -3,8 +3,8 @@ tcfail133.hs:2:61: Warning: -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language. tcfail133.hs:68:7: - No instance for (Show s0) arising from a use of ?show? - The type variable ?s0? is ambiguous + No instance for (Show r0) arising from a use of ?show? + The type variable ?r0? is ambiguous Note: there are several potential instances: instance Show Zero -- Defined at tcfail133.hs:8:29 instance Show One -- Defined at tcfail133.hs:9:28 @@ -17,7 +17,7 @@ tcfail133.hs:68:7: foo = show $ add (One :@ Zero) (One :@ One) tcfail133.hs:68:14: - No instance for (AddDigit (Zero :@ (One :@ One)) One s0) + No instance for (AddDigit (Zero :@ (One :@ One)) One r0) arising from a use of ?add? In the second argument of ?($)?, namely ?add (One :@ Zero) (One :@ One)? From git at git.haskell.org Wed Nov 12 15:48:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 15:48:58 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9404 by removing tcInfExpr. (4014fce) Message-ID: <20141112154858.D67283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/4014fceca01cad8df9caca8824e78b0bfda33d4d/ghc >--------------------------------------------------------------- commit 4014fceca01cad8df9caca8824e78b0bfda33d4d Author: Richard Eisenberg Date: Mon Nov 10 21:27:58 2014 -0500 Fix #9404 by removing tcInfExpr. See the ticket for more info about the new algorithm. This is a small simplification, unifying the treatment of type checking in a few similar situations. >--------------------------------------------------------------- 4014fceca01cad8df9caca8824e78b0bfda33d4d compiler/typecheck/TcExpr.lhs | 32 +++------------ compiler/typecheck/TcMType.lhs | 15 ++++--- compiler/typecheck/TcType.lhs | 47 ++++++++++++++++++---- compiler/typecheck/TcUnify.lhs | 25 +++++++++--- compiler/utils/MonadUtils.hs | 6 +++ .../{should_fail => should_compile}/T7220.hs | 0 testsuite/tests/typecheck/should_compile/all.T | 5 ++- testsuite/tests/typecheck/should_fail/T7220.stderr | 9 ----- testsuite/tests/typecheck/should_fail/all.T | 1 - 9 files changed, 79 insertions(+), 61 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4014fceca01cad8df9caca8824e78b0bfda33d4d From git at git.haskell.org Wed Nov 12 18:27:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:27:52 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9066 in th/T9066 (1d35c85) Message-ID: <20141112182752.097DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/1d35c85679416a955a4aee8e8a6a1b71d4ac827e/ghc >--------------------------------------------------------------- commit 1d35c85679416a955a4aee8e8a6a1b71d4ac827e Author: Richard Eisenberg Date: Sun Nov 2 13:44:27 2014 -0500 Test #9066 in th/T9066 >--------------------------------------------------------------- 1d35c85679416a955a4aee8e8a6a1b71d4ac827e testsuite/tests/th/T9066.hs | 10 ++++++++++ testsuite/tests/th/all.T | 2 ++ 2 files changed, 12 insertions(+) diff --git a/testsuite/tests/th/T9066.hs b/testsuite/tests/th/T9066.hs new file mode 100644 index 0000000..2e46fe5 --- /dev/null +++ b/testsuite/tests/th/T9066.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T9066 where + +$([d| data Blargh = (:<=>) Int Int + infix 4 :<=> + + type Foo a b = Either a b + infix 5 `Foo` + |]) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index a35e126..3d64060 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -336,3 +336,5 @@ test('T8953', normal, compile, ['-v0']) test('T9084', normal, compile_fail, ['-v0']) test('T9738', normal, compile, ['-v0']) test('T9081', normal, compile, ['-v0']) +test('T9066', expect_broken(9066), compile, ['-v0']) + From git at git.haskell.org Wed Nov 12 18:27:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:27:54 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9066. (d782694) Message-ID: <20141112182754.BA28D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/d782694f47c3b05605e4564850623dbd03af7ecc/ghc >--------------------------------------------------------------- commit d782694f47c3b05605e4564850623dbd03af7ecc Author: Richard Eisenberg Date: Mon Nov 3 11:15:35 2014 -0500 Fix #9066. When splicing in a fixity declaration, look for both term-level things and type-level things. This requires some changes elsewhere in the code to allow for more flexibility when looking up Exact names, which can be assigned the wrong namespace during fixity declaration conversion. See the ticket for more info. >--------------------------------------------------------------- d782694f47c3b05605e4564850623dbd03af7ecc compiler/basicTypes/RdrName.lhs | 11 +++++--- compiler/hsSyn/Convert.lhs | 17 +++++++++--- compiler/rename/RnEnv.lhs | 57 ++++++++++++++++++++++++++--------------- testsuite/tests/th/all.T | 3 +-- 4 files changed, 58 insertions(+), 30 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d782694f47c3b05605e4564850623dbd03af7ecc From git at git.haskell.org Wed Nov 12 18:27:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:27:57 +0000 (UTC) Subject: [commit: ghc] wip/rae: Untabify template-haskell. (f61b3c4) Message-ID: <20141112182757.797A33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/f61b3c41b35ff77f68aa995ba96dc0757d5d3d60/ghc >--------------------------------------------------------------- commit f61b3c41b35ff77f68aa995ba96dc0757d5d3d60 Author: Richard Eisenberg Date: Tue Nov 4 13:43:17 2014 -0500 Untabify template-haskell. >--------------------------------------------------------------- f61b3c41b35ff77f68aa995ba96dc0757d5d3d60 libraries/template-haskell/Language/Haskell/TH.hs | 8 +-- .../template-haskell/Language/Haskell/TH/Lib.hs | 2 +- .../template-haskell/Language/Haskell/TH/Ppr.hs | 24 ++++---- .../template-haskell/Language/Haskell/TH/PprLib.hs | 66 +++++++++++----------- .../template-haskell/Language/Haskell/TH/Quote.hs | 2 +- 5 files changed, 51 insertions(+), 51 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f61b3c41b35ff77f68aa995ba96dc0757d5d3d60 From git at git.haskell.org Wed Nov 12 18:28:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:28:00 +0000 (UTC) Subject: [commit: ghc] wip/rae: Remove unboxed Int# fields from NameFlavour (#9527) (1d66167) Message-ID: <20141112182800.280CA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/1d66167e56317bbd0e06301fe3cbdc40c9c3e34b/ghc >--------------------------------------------------------------- commit 1d66167e56317bbd0e06301fe3cbdc40c9c3e34b Author: Richard Eisenberg Date: Tue Nov 4 13:03:48 2014 -0500 Remove unboxed Int# fields from NameFlavour (#9527) >--------------------------------------------------------------- 1d66167e56317bbd0e06301fe3cbdc40c9c3e34b compiler/hsSyn/Convert.lhs | 6 +- .../template-haskell/Language/Haskell/TH/PprLib.hs | 7 +- .../template-haskell/Language/Haskell/TH/Syntax.hs | 110 +++------------------ 3 files changed, 21 insertions(+), 102 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1d66167e56317bbd0e06301fe3cbdc40c9c3e34b From git at git.haskell.org Wed Nov 12 18:28:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:28:02 +0000 (UTC) Subject: [commit: ghc] wip/rae: Derive Generic for TH types (#9527) (88a42be) Message-ID: <20141112182802.C33F93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/88a42be1b40c55241f835da815faa9eb8b356331/ghc >--------------------------------------------------------------- commit 88a42be1b40c55241f835da815faa9eb8b356331 Author: Richard Eisenberg Date: Tue Nov 4 13:21:57 2014 -0500 Derive Generic for TH types (#9527) >--------------------------------------------------------------- 88a42be1b40c55241f835da815faa9eb8b356331 .../template-haskell/Language/Haskell/TH/Syntax.hs | 83 +++++++++++----------- 1 file changed, 42 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 88a42be1b40c55241f835da815faa9eb8b356331 From git at git.haskell.org Wed Nov 12 18:28:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:28:05 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #8100 in th/T8100 (767feb3) Message-ID: <20141112182805.C84FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/767feb370d0a05a78a34a9498fe11b90d395d158/ghc >--------------------------------------------------------------- commit 767feb370d0a05a78a34a9498fe11b90d395d158 Author: Richard Eisenberg Date: Tue Nov 4 15:15:56 2014 -0500 Test #8100 in th/T8100 >--------------------------------------------------------------- 767feb370d0a05a78a34a9498fe11b90d395d158 testsuite/tests/th/T8100.hs | 20 ++++++++++++++++++++ testsuite/tests/th/all.T | 1 + 2 files changed, 21 insertions(+) diff --git a/testsuite/tests/th/T8100.hs b/testsuite/tests/th/T8100.hs new file mode 100644 index 0000000..debc2f7 --- /dev/null +++ b/testsuite/tests/th/T8100.hs @@ -0,0 +1,20 @@ +{-# LANGUAGE TemplateHaskell, StandaloneDeriving #-} + +module T8100 where + +import Language.Haskell.TH + +data Foo a = Foo a +data Bar = Bar Int + +$( do decs <- [d| deriving instance Eq a => Eq (Foo a) + deriving instance Ord a => Ord (Foo a) |] + return ( StandaloneDerivD [] (ConT ''Eq `AppT` ConT ''Bar) + : StandaloneDerivD [] (ConT ''Ord `AppT` ConT ''Bar) + : decs ) ) + +blah :: Ord a => Foo a -> Foo a -> Ordering +blah = compare + +buzz :: Bar -> Bar -> Ordering +buzz = compare diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 342f5e3..4a8e340 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -337,3 +337,4 @@ test('T9084', normal, compile_fail, ['-v0']) test('T9738', normal, compile, ['-v0']) test('T9081', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) +test('T8100', expect_broken(8100), compile, ['-v0']) From git at git.haskell.org Wed Nov 12 18:28:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:28:08 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #8100, by adding StandaloneDerivD to TH's Dec type. (4ac9e90) Message-ID: <20141112182808.8E2A73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/4ac9e902327683ba032df5fb0e92a80c7b7fccd4/ghc >--------------------------------------------------------------- commit 4ac9e902327683ba032df5fb0e92a80c7b7fccd4 Author: Richard Eisenberg Date: Tue Nov 4 15:24:33 2014 -0500 Fix #8100, by adding StandaloneDerivD to TH's Dec type. >--------------------------------------------------------------- 4ac9e902327683ba032df5fb0e92a80c7b7fccd4 compiler/deSugar/DsMeta.hs | 56 ++++++++++++++-------- compiler/hsSyn/Convert.lhs | 7 +++ libraries/template-haskell/Language/Haskell/TH.hs | 2 +- .../template-haskell/Language/Haskell/TH/Lib.hs | 7 +++ .../template-haskell/Language/Haskell/TH/Ppr.hs | 3 ++ .../template-haskell/Language/Haskell/TH/Syntax.hs | 1 + testsuite/tests/th/all.T | 2 +- 7 files changed, 56 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4ac9e902327683ba032df5fb0e92a80c7b7fccd4 From git at git.haskell.org Wed Nov 12 18:28:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:28:11 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9064 in th/T9064 (fe71a7e) Message-ID: <20141112182811.B943B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/fe71a7e6e3513ff18f7e6ec57284168c052262fc/ghc >--------------------------------------------------------------- commit fe71a7e6e3513ff18f7e6ec57284168c052262fc Author: Richard Eisenberg Date: Tue Nov 4 15:28:40 2014 -0500 Test #9064 in th/T9064 >--------------------------------------------------------------- fe71a7e6e3513ff18f7e6ec57284168c052262fc testsuite/tests/th/T9064.hs | 23 +++++++++++++++++++++++ testsuite/tests/th/T9064.stderr | 7 +++++++ testsuite/tests/th/all.T | 1 + 3 files changed, 31 insertions(+) diff --git a/testsuite/tests/th/T9064.hs b/testsuite/tests/th/T9064.hs new file mode 100644 index 0000000..3451e2e --- /dev/null +++ b/testsuite/tests/th/T9064.hs @@ -0,0 +1,23 @@ +{-# LANGUAGE TemplateHaskell, DefaultSignatures #-} + +module T9064 where + +import Language.Haskell.TH +import System.IO + +$( [d| class C a where + foo :: a -> String + default foo :: Show a => a -> String + foo = show |] ) + +data Bar = Bar deriving Show +instance C Bar + +x :: Bar -> String +x = foo + +$( do info <- reify ''C + runIO $ do + putStrLn $ pprint info + hFlush stdout + return [] ) diff --git a/testsuite/tests/th/T9064.stderr b/testsuite/tests/th/T9064.stderr new file mode 100644 index 0000000..f9c1716 --- /dev/null +++ b/testsuite/tests/th/T9064.stderr @@ -0,0 +1,7 @@ +class T9064.C (a_0 :: *) + where T9064.foo :: forall (a_0 :: *) . T9064.C a_0 => + a_0 -> GHC.Base.String + default T9064.foo :: forall (a_0 :: *) . (T9064.C a_0, + GHC.Show.Show a_0) => + a_0 -> GHC.Base.String +instance T9064.C T9064.Bar diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 199ad15..86e7fd8 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -338,3 +338,4 @@ test('T9738', normal, compile, ['-v0']) test('T9081', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T8100', normal, compile, ['-v0']) +test('T9064', expect_broken(9064), compile, ['-v0']) From git at git.haskell.org Wed Nov 12 18:28:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:28:14 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9064 by adding support for generic default signatures to TH. (e4efb7b) Message-ID: <20141112182814.80BD73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/e4efb7b8de8ff3781a42e69e35dee981d9885fcf/ghc >--------------------------------------------------------------- commit e4efb7b8de8ff3781a42e69e35dee981d9885fcf Author: Richard Eisenberg Date: Tue Nov 4 16:38:22 2014 -0500 Fix #9064 by adding support for generic default signatures to TH. >--------------------------------------------------------------- e4efb7b8de8ff3781a42e69e35dee981d9885fcf compiler/deSugar/DsMeta.hs | 24 +++++++++++----------- compiler/hsSyn/Convert.lhs | 5 +++++ compiler/typecheck/TcSplice.lhs | 13 +++++++++--- libraries/template-haskell/Language/Haskell/TH.hs | 2 +- .../template-haskell/Language/Haskell/TH/Lib.hs | 6 ++++++ .../template-haskell/Language/Haskell/TH/Ppr.hs | 3 +++ .../template-haskell/Language/Haskell/TH/Syntax.hs | 1 + testsuite/tests/th/all.T | 2 +- 8 files changed, 39 insertions(+), 17 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e4efb7b8de8ff3781a42e69e35dee981d9885fcf From git at git.haskell.org Wed Nov 12 18:28:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:28:17 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9204 by outputting extra info on boot file mismatch. (ee0f34d) Message-ID: <20141112182817.509943A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/ee0f34d53291a7223185f83c644a25b54ea16fab/ghc >--------------------------------------------------------------- commit ee0f34d53291a7223185f83c644a25b54ea16fab Author: Richard Eisenberg Date: Wed Nov 5 10:52:57 2014 -0500 Fix #9204 by outputting extra info on boot file mismatch. [skip ci] -- testsuite wibbles are in next commit >--------------------------------------------------------------- ee0f34d53291a7223185f83c644a25b54ea16fab compiler/typecheck/TcRnDriver.lhs | 182 +++++++++++++++++++++++--------- testsuite/tests/roles/should_fail/all.T | 2 +- 2 files changed, 135 insertions(+), 49 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ee0f34d53291a7223185f83c644a25b54ea16fab From git at git.haskell.org Wed Nov 12 18:28:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:28:20 +0000 (UTC) Subject: [commit: ghc] wip/rae: Testsuite wibbles due to #9204 (90a2bb6) Message-ID: <20141112182820.045B33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/90a2bb6fc66e9341ae466ff3ff6c9da438e159c2/ghc >--------------------------------------------------------------- commit 90a2bb6fc66e9341ae466ff3ff6c9da438e159c2 Author: Richard Eisenberg Date: Fri Nov 7 16:32:39 2014 -0500 Testsuite wibbles due to #9204 >--------------------------------------------------------------- 90a2bb6fc66e9341ae466ff3ff6c9da438e159c2 .../indexed-types/should_fail/ClosedFam3.stderr | 1 + testsuite/tests/rename/should_fail/rnfail055.stderr | 20 ++++++++++++++++---- testsuite/tests/roles/should_fail/Roles12.stderr | 1 + testsuite/tests/typecheck/should_fail/T3468.stderr | 1 + .../tests/typecheck/should_fail/tcfail220.stderr | 2 ++ 5 files changed, 21 insertions(+), 4 deletions(-) diff --git a/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr b/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr index 04435ba..3b9539e 100644 --- a/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr +++ b/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr @@ -25,3 +25,4 @@ ClosedFam3.hs-boot:12:1: Baz Int = Bool Boot file: type family Baz (a :: k) :: * where Baz * Int = Bool + The types have different kinds diff --git a/testsuite/tests/rename/should_fail/rnfail055.stderr b/testsuite/tests/rename/should_fail/rnfail055.stderr index c7b51a1..1c002ac 100644 --- a/testsuite/tests/rename/should_fail/rnfail055.stderr +++ b/testsuite/tests/rename/should_fail/rnfail055.stderr @@ -10,34 +10,38 @@ RnFail055.hs-boot:4:1: and its hs-boot file Main module: f1 :: Int -> Float Boot file: f1 :: Float -> Int + The two types are different RnFail055.hs-boot:6:1: Type constructor ?S1? has conflicting definitions in the module and its hs-boot file Main module: type S1 a b = (a, b) Boot file: type S1 a b c = (a, b) + The types have different kinds RnFail055.hs-boot:8:1: Type constructor ?S2? has conflicting definitions in the module and its hs-boot file Main module: type S2 a b = forall a1. (a1, b) Boot file: type S2 a b = forall b1. (a, b1) + The roles do not match. Roles default to ?representational? in boot files RnFail055.hs-boot:12:1: Type constructor ?T1? has conflicting definitions in the module and its hs-boot file Main module: data T1 a b = T1 [b] [a] Boot file: data T1 a b = T1 [a] [b] + The constructors do not match: The types for ?T1? differ RnFail055.hs-boot:14:1: Type constructor ?T2? has conflicting definitions in the module and its hs-boot file Main module: type role T2 representational nominal - data Eq b => T2 a b - = T2 a + data Eq b => T2 a b = T2 a Boot file: type role T2 nominal representational - data Eq a => T2 a b - = T2 a + data Eq a => T2 a b = T2 a + The roles do not match. Roles default to ?representational? in boot files + The datatype contexts do not match RnFail055.hs-boot:16:11: T3 is exported by the hs-boot file, but not exported by the module @@ -50,12 +54,16 @@ RnFail055.hs-boot:21:1: and its hs-boot file Main module: data T5 a = T5 {field5 :: a} Boot file: data T5 a = T5 a + The constructors do not match: + The record label lists for ?T5? differ RnFail055.hs-boot:23:1: Type constructor ?T6? has conflicting definitions in the module and its hs-boot file Main module: data T6 = T6 Int Boot file: data T6 = T6 !Int + The constructors do not match: + The strictness annotations for ?T6? differ RnFail055.hs-boot:25:1: Type constructor ?T7? has conflicting definitions in the module @@ -64,6 +72,8 @@ RnFail055.hs-boot:25:1: data T7 a where T7 :: a1 -> T7 a Boot file: data T7 a = T7 a + The roles do not match. Roles default to ?representational? in boot files + The constructors do not match: The types for ?T7? differ RnFail055.hs-boot:27:22: RnFail055.m1 is exported by the hs-boot file, but not exported by the module @@ -76,9 +86,11 @@ RnFail055.hs-boot:28:1: m2' :: a -> b Boot file: class C2 a b where m2 :: a -> b + The methods do not match: There are different numbers of methods RnFail055.hs-boot:29:1: Class ?C3? has conflicting definitions in the module and its hs-boot file Main module: class (Eq a, Ord a) => C3 a Boot file: class (Ord a, Eq a) => C3 a + The class constraints do not match diff --git a/testsuite/tests/roles/should_fail/Roles12.stderr b/testsuite/tests/roles/should_fail/Roles12.stderr index 9b0f2cf..874ddca 100644 --- a/testsuite/tests/roles/should_fail/Roles12.stderr +++ b/testsuite/tests/roles/should_fail/Roles12.stderr @@ -5,3 +5,4 @@ Roles12.hs:5:1: Main module: type role T phantom data T a Boot file: abstract T a + The roles do not match. Roles default to ?representational? in boot files diff --git a/testsuite/tests/typecheck/should_fail/T3468.stderr b/testsuite/tests/typecheck/should_fail/T3468.stderr index 26ec192..9284df2 100644 --- a/testsuite/tests/typecheck/should_fail/T3468.stderr +++ b/testsuite/tests/typecheck/should_fail/T3468.stderr @@ -6,3 +6,4 @@ T3468.hs-boot:3:1: data Tool d where F :: a -> Tool d Boot file: abstract Tool + The types have different kinds diff --git a/testsuite/tests/typecheck/should_fail/tcfail220.stderr b/testsuite/tests/typecheck/should_fail/tcfail220.stderr index aea7906..e565cc7 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail220.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail220.stderr @@ -5,9 +5,11 @@ tcfail220.hsig:4:1: and its hsig file Main module: data Bool = False | GHC.Types.True Hsig file: data Bool a b c d = False + The types have different kinds tcfail220.hsig:5:1: Type constructor ?Maybe? has conflicting definitions in the module and its hsig file Main module: data Maybe a = Nothing | GHC.Base.Just a Hsig file: data Maybe a b = Nothing + The types have different kinds From git at git.haskell.org Wed Nov 12 18:28:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:28:23 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9204 in roles/should_fail/T9204 (ec8781f) Message-ID: <20141112182823.4F7AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/ec8781f063d246a79ce1d4eb207dbee4b6317c94/ghc >--------------------------------------------------------------- commit ec8781f063d246a79ce1d4eb207dbee4b6317c94 Author: Richard Eisenberg Date: Tue Nov 4 17:40:06 2014 -0500 Test #9204 in roles/should_fail/T9204 >--------------------------------------------------------------- ec8781f063d246a79ce1d4eb207dbee4b6317c94 testsuite/tests/roles/should_fail/Makefile | 4 ++++ testsuite/tests/roles/should_fail/T9204.hs | 6 ++++++ testsuite/tests/roles/should_fail/T9204.hs-boot | 4 ++++ testsuite/tests/roles/should_fail/T9204.stderr | 8 ++++++++ testsuite/tests/roles/should_fail/all.T | 2 ++ 5 files changed, 24 insertions(+) diff --git a/testsuite/tests/roles/should_fail/Makefile b/testsuite/tests/roles/should_fail/Makefile index 8f80de3..14d6720 100644 --- a/testsuite/tests/roles/should_fail/Makefile +++ b/testsuite/tests/roles/should_fail/Makefile @@ -7,3 +7,7 @@ include $(TOP)/mk/test.mk Roles12: '$(TEST_HC)' $(TEST_HC_OPTS) -c Roles12.hs-boot -'$(TEST_HC)' $(TEST_HC_OPTS) -c Roles12.hs + +T9204: + '$(TEST_HC)' $(TEST_HC_OPTS) -c T9204.hs-boot + -'$(TEST_HC)' $(TEST_HC_OPTS) -c T9204.hs diff --git a/testsuite/tests/roles/should_fail/T9204.hs b/testsuite/tests/roles/should_fail/T9204.hs new file mode 100644 index 0000000..e2351a2 --- /dev/null +++ b/testsuite/tests/roles/should_fail/T9204.hs @@ -0,0 +1,6 @@ + +module T9204 where + +import {-# SOURCE #-} T9204 + +data D a diff --git a/testsuite/tests/roles/should_fail/T9204.hs-boot b/testsuite/tests/roles/should_fail/T9204.hs-boot new file mode 100644 index 0000000..7ee0f1d --- /dev/null +++ b/testsuite/tests/roles/should_fail/T9204.hs-boot @@ -0,0 +1,4 @@ + +module T9204 where + +data D a diff --git a/testsuite/tests/roles/should_fail/T9204.stderr b/testsuite/tests/roles/should_fail/T9204.stderr new file mode 100644 index 0000000..9936839 --- /dev/null +++ b/testsuite/tests/roles/should_fail/T9204.stderr @@ -0,0 +1,8 @@ + +T9204.hs:6:1: + Type constructor ?D? has conflicting definitions in the module + and its hs-boot file + Main module: type role D phantom + data D a + Boot file: abstract D a + The roles do not match. Roles default to ?representational? in boot files diff --git a/testsuite/tests/roles/should_fail/all.T b/testsuite/tests/roles/should_fail/all.T index d0d5c4d..bb90fee 100644 --- a/testsuite/tests/roles/should_fail/all.T +++ b/testsuite/tests/roles/should_fail/all.T @@ -8,3 +8,5 @@ test('Roles12', extra_clean(['Roles12.o-boot', 'Roles12.hi-boot']), run_command, ['$MAKE --no-print-directory -s Roles12']) test('T8773', normal, compile_fail, ['']) +test('T9204', [ expect_broken(9204), extra_clean(['T9204.o-boot', 'T9204.hi-boot']) ], + run_command, ['$MAKE --no-print-directory -s T9204']) From git at git.haskell.org Wed Nov 12 18:28:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:28:26 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9404 (typecheck/should_compile/T9404 and T9404b) (e6e45a1) Message-ID: <20141112182826.B21363A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/e6e45a1c497eae37fbc5daf5e201fe97181e840c/ghc >--------------------------------------------------------------- commit e6e45a1c497eae37fbc5daf5e201fe97181e840c Author: Richard Eisenberg Date: Thu Aug 7 09:20:41 2014 -0400 Test #9404 (typecheck/should_compile/T9404 and T9404b) >--------------------------------------------------------------- e6e45a1c497eae37fbc5daf5e201fe97181e840c testsuite/tests/typecheck/should_compile/T9404.hs | 6 ++++++ testsuite/tests/typecheck/should_compile/T9404b.hs | 15 +++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 2 ++ 3 files changed, 23 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T9404.hs b/testsuite/tests/typecheck/should_compile/T9404.hs new file mode 100644 index 0000000..4cb530a --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9404.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE UnboxedTuples #-} + +module T9404 where + +foo _ = case seq () (# #) of (# #) -> () +foo2 _ = case () `seq` (# #) of (# #) -> () diff --git a/testsuite/tests/typecheck/should_compile/T9404b.hs b/testsuite/tests/typecheck/should_compile/T9404b.hs new file mode 100644 index 0000000..f9db0a3 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9404b.hs @@ -0,0 +1,15 @@ +{-# LANGUAGE RankNTypes, TypeFamilies #-} + +module T9404b where + +type family ListTF x where + ListTF x = [x] + +bar :: (forall x. ListTF x -> Int) -> () +bar _ = () + +myconst :: ((forall r. ListTF r -> Int) -> ()) -> x -> (forall r. ListTF r -> Int) -> () +myconst x _ = x + +foo = (bar `myconst` ()) $ length +foo2 = (myconst bar ()) $ length diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index a6cb78a..8448411 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -422,3 +422,5 @@ test('T8856', normal, compile, ['']) test('T9117', normal, compile, ['']) test('T9117_2', expect_broken('9117'), compile, ['']) test('T9708', normal, compile_fail, ['']) +test('T9404', expect_broken(9404), compile, ['']) +test('T9404b', expect_broken(9404), compile, ['']) From git at git.haskell.org Wed Nov 12 18:28:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:28:29 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9788 by giving `coerce` the right type. (294ac47) Message-ID: <20141112182829.73E7D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/294ac47ef7aa68d09cf730c60223259893fc0933/ghc >--------------------------------------------------------------- commit 294ac47ef7aa68d09cf730c60223259893fc0933 Author: Richard Eisenberg Date: Mon Nov 10 20:41:38 2014 -0500 Fix #9788 by giving `coerce` the right type. No test case added, as the original mistake is just one level up from a typo. >--------------------------------------------------------------- 294ac47ef7aa68d09cf730c60223259893fc0933 compiler/basicTypes/MkId.lhs | 19 ++++++++----------- testsuite/tests/ghci/scripts/ghci059.stdout | 4 +--- 2 files changed, 9 insertions(+), 14 deletions(-) diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index 9fc728b..b32a2b7 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -1146,17 +1146,14 @@ coerceId = pcMiscPrelId coerceName ty info where info = noCafIdInfo `setInlinePragInfo` alwaysInlinePragma `setUnfoldingInfo` mkCompulsoryUnfolding rhs - kv = kKiVar - k = mkTyVarTy kv - a:b:_ = tyVarList k - [aTy,bTy] = map mkTyVarTy [a,b] - eqRTy = mkTyConApp coercibleTyCon [k, aTy, bTy] - eqRPrimTy = mkTyConApp eqReprPrimTyCon [k, aTy, bTy] - ty = mkForAllTys [kv, a, b] (mkFunTys [eqRTy, aTy] bTy) - - [eqR,x,eq] = mkTemplateLocals [eqRTy, aTy,eqRPrimTy] - rhs = mkLams [kv,a,b,eqR,x] $ - mkWildCase (Var eqR) eqRTy bTy $ + eqRTy = mkTyConApp coercibleTyCon [liftedTypeKind, alphaTy, betaTy] + eqRPrimTy = mkTyConApp eqReprPrimTyCon [liftedTypeKind, alphaTy, betaTy] + ty = mkForAllTys [alphaTyVar, betaTyVar] $ + mkFunTys [eqRTy, alphaTy] betaTy + + [eqR,x,eq] = mkTemplateLocals [eqRTy, alphaTy, eqRPrimTy] + rhs = mkLams [alphaTyVar, betaTyVar, eqR, x] $ + mkWildCase (Var eqR) eqRTy betaTy $ [(DataAlt coercibleDataCon, [eq], Cast (Var x) (CoVarCo eq))] \end{code} diff --git a/testsuite/tests/ghci/scripts/ghci059.stdout b/testsuite/tests/ghci/scripts/ghci059.stdout index ffc893f..6b2c8f8 100644 --- a/testsuite/tests/ghci/scripts/ghci059.stdout +++ b/testsuite/tests/ghci/scripts/ghci059.stdout @@ -1,6 +1,4 @@ type role Coercible representational representational class Coercible (a :: k) (b :: k) -- Defined in ?GHC.Types? -coerce :: - forall (k :: BOX) (a :: k) (b :: k). Coercible a b => a -> b - -- Defined in ?GHC.Prim? +coerce :: Coercible a b => a -> b -- Defined in ?GHC.Prim? From git at git.haskell.org Wed Nov 12 18:28:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:28:32 +0000 (UTC) Subject: [commit: ghc] wip/rae: Testsuite wibble due to #9404 (fe6a517) Message-ID: <20141112182832.296843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/fe6a51715a23e2ee31e1d03b71f06c4417e964e0/ghc >--------------------------------------------------------------- commit fe6a51715a23e2ee31e1d03b71f06c4417e964e0 Author: Richard Eisenberg Date: Tue Nov 11 07:58:03 2014 -0500 Testsuite wibble due to #9404 [skip ci] >--------------------------------------------------------------- fe6a51715a23e2ee31e1d03b71f06c4417e964e0 testsuite/tests/ghci/scripts/ghci046.script | 4 ++-- testsuite/tests/ghci/scripts/ghci046.stdout | 6 ++++-- testsuite/tests/typecheck/should_fail/T5570.stderr | 2 +- testsuite/tests/typecheck/should_fail/T7857.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/tcfail133.stderr | 6 +++--- 5 files changed, 12 insertions(+), 10 deletions(-) diff --git a/testsuite/tests/ghci/scripts/ghci046.script b/testsuite/tests/ghci/scripts/ghci046.script index f07e06f..28c5cde 100644 --- a/testsuite/tests/ghci/scripts/ghci046.script +++ b/testsuite/tests/ghci/scripts/ghci046.script @@ -12,8 +12,8 @@ type instance OR HTrue HTrue = HTrue type instance OR HTrue HFalse = HTrue type instance OR HFalse HTrue = HTrue type instance OR HFalse HFalse = HFalse -:t undefined :: AND HTrue HTrue -:t undefined :: AND (OR HFalse HTrue) (OR HTrue HFalse) +:kind! AND HTrue HTrue +:kind! AND (OR HFalse HTrue) (OR HTrue HFalse) let t = undefined :: AND HTrue HTrue let f = undefined :: AND HTrue HFalse type instance AND HTrue HTrue = HFalse diff --git a/testsuite/tests/ghci/scripts/ghci046.stdout b/testsuite/tests/ghci/scripts/ghci046.stdout index d600596..c4e7cf3 100644 --- a/testsuite/tests/ghci/scripts/ghci046.stdout +++ b/testsuite/tests/ghci/scripts/ghci046.stdout @@ -1,4 +1,6 @@ -undefined :: AND HTrue HTrue :: HTrue -undefined :: AND (OR HFalse HTrue) (OR HTrue HFalse) :: HTrue +AND HTrue HTrue :: * += HTrue +AND (OR HFalse HTrue) (OR HTrue HFalse) :: * += HTrue t :: HTrue t :: HFalse diff --git a/testsuite/tests/typecheck/should_fail/T5570.stderr b/testsuite/tests/typecheck/should_fail/T5570.stderr index 21a4e0c..15d5c8a 100644 --- a/testsuite/tests/typecheck/should_fail/T5570.stderr +++ b/testsuite/tests/typecheck/should_fail/T5570.stderr @@ -2,7 +2,7 @@ T5570.hs:7:16: Couldn't match kind ?*? with ?#? When matching types - s0 :: * + r0 :: * Double# :: # In the second argument of ?($)?, namely ?D# $ 3.0##? In the expression: print $ D# $ 3.0## diff --git a/testsuite/tests/typecheck/should_fail/T7857.stderr b/testsuite/tests/typecheck/should_fail/T7857.stderr index 6517b77..698d280 100644 --- a/testsuite/tests/typecheck/should_fail/T7857.stderr +++ b/testsuite/tests/typecheck/should_fail/T7857.stderr @@ -1,10 +1,10 @@ T7857.hs:8:11: - Could not deduce (PrintfType s0) arising from a use of ?printf? + Could not deduce (PrintfType r0) arising from a use of ?printf? from the context (PrintfArg t) bound by the inferred type of g :: PrintfArg t => t -> b at T7857.hs:8:1-21 - The type variable ?s0? is ambiguous + The type variable ?r0? is ambiguous Note: there are several potential instances: instance [safe] (PrintfArg a, PrintfType r) => PrintfType (a -> r) -- Defined in ?Text.Printf? diff --git a/testsuite/tests/typecheck/should_fail/tcfail133.stderr b/testsuite/tests/typecheck/should_fail/tcfail133.stderr index 058b063..0198f3c 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail133.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail133.stderr @@ -3,8 +3,8 @@ tcfail133.hs:2:61: Warning: -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language. tcfail133.hs:68:7: - No instance for (Show s0) arising from a use of ?show? - The type variable ?s0? is ambiguous + No instance for (Show r0) arising from a use of ?show? + The type variable ?r0? is ambiguous Note: there are several potential instances: instance Show Zero -- Defined at tcfail133.hs:8:29 instance Show One -- Defined at tcfail133.hs:9:28 @@ -17,7 +17,7 @@ tcfail133.hs:68:7: foo = show $ add (One :@ Zero) (One :@ One) tcfail133.hs:68:14: - No instance for (AddDigit (Zero :@ (One :@ One)) One s0) + No instance for (AddDigit (Zero :@ (One :@ One)) One r0) arising from a use of ?add? In the second argument of ?($)?, namely ?add (One :@ Zero) (One :@ One)? From git at git.haskell.org Wed Nov 12 18:28:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:28:34 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9404 by removing tcInfExpr. (1e2002d) Message-ID: <20141112182834.E7D393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/1e2002d8e89e3267e2c9c8d92235ee083a272657/ghc >--------------------------------------------------------------- commit 1e2002d8e89e3267e2c9c8d92235ee083a272657 Author: Richard Eisenberg Date: Mon Nov 10 21:27:58 2014 -0500 Fix #9404 by removing tcInfExpr. See the ticket for more info about the new algorithm. This is a small simplification, unifying the treatment of type checking in a few similar situations. >--------------------------------------------------------------- 1e2002d8e89e3267e2c9c8d92235ee083a272657 compiler/typecheck/TcExpr.lhs | 32 +++------------ compiler/typecheck/TcMType.lhs | 15 ++++--- compiler/typecheck/TcType.lhs | 47 ++++++++++++++++++---- compiler/typecheck/TcUnify.lhs | 25 +++++++++--- compiler/utils/MonadUtils.hs | 6 +++ .../{should_fail => should_compile}/T7220.hs | 0 testsuite/tests/typecheck/should_compile/all.T | 5 ++- testsuite/tests/typecheck/should_fail/T7220.stderr | 9 ----- testsuite/tests/typecheck/should_fail/all.T | 1 - 9 files changed, 79 insertions(+), 61 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1e2002d8e89e3267e2c9c8d92235ee083a272657 From git at git.haskell.org Wed Nov 12 18:28:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 18:28:37 +0000 (UTC) Subject: [commit: ghc] wip/rae's head updated: Fix #9404 by removing tcInfExpr. (1e2002d) Message-ID: <20141112182837.854853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/rae' now includes: 77f8221 Temporarily disable T3064 (see #9771) 0a8e899 Remove redundant contexts from Foldable methods ac0915b Clean-up Haddock in `Data.Functor` 40b1ee4 Add `isSubsequenceOf` to Data.List (#9767) 32237f0 Fix typo in testsuite Makefile 83cf31e Fix a couple of bugs in the way info tables are generated for 64-bit platforms 4cd277b Fix bugs in debug printing 3bebf3c Fix a couple of inaccurate stack checks e6b3829 Disable an assertion; see comment 081ef2f Add a comment about stack checks d14312f Add doctest examples for Data.Either d0d9dc0 Clarify confusing notice from `make maintainer-clean` ad8457f Remove -ddump-simpl-phases flag c0a2354 Remove -ddump-core-pipeline flag 303776a Update User's Guide, cleanup DynFlags 0f930ba Move expansion of 'assert' from renamer to typechecker 030abf9 Remove unused tyConsOfDataCon e7523fe Make tyConsOfType return a (NameEnv TyCon) rather than [TyCon] f81f82e Comments and white space only 528cbd7 Give T3064 the right module name (just tidying up) 096b7e6 Switch off lazy flattening (fix Trac #3064) cb6ccad Minor refacoring and trace-message printing c945477 Allow the solved dictionaries to propagate from outside in ec38deb Wibbles to notes 203cf0e Refactor the code that prevents recursion among Coercible constraints c79cbac Re-enable T3064, which works now 91c15d6 Better error messages for new per-instance overlap flags and Safe Haskell. c96a613 Add in Incoherent Instances test for Safe Haskell. f4ead30 Warn for Safe Haskell when -XOverlappingInstances or -XIncoherentInstances turned on. abba381 Improve Applicative definitions dc5fa80 Make getTag use a bang pattern instead of seq b0e8e34 Update .gitignore to properly ignore emacs temp files 24e05f4 *Really*, really fix RTS crash due to bad coercion. 37d64a5 small parser/lexer cleanup b0d5b5b [Docs] Fixed several broken urls in user's guide f14ac52 Use bracket in `withCurrentDirectory` 832ef3f Have validate take into account stat test failures too. df3b1d4 base: Manually unlit .lhs into .hs modules a2e7bbf Preserve argument order to (==)/eq in nub and nubBy b608868 Typofix. c942688 Miscellaneous documentation for the Finder. f5996d9 Top-level comment for keepPackageImports. 474e535 In pattern synonym matchers, support unboxed continuation results (fixes #9783). 65dc594 Group PatSyn req/prov arguments together so that they're not all over the place 8e66365 Unlit overlooked GHC/Conc/Sync.lhs e2769df Use (.) and id from Base in Control.Applicative 8710136 Move Data.Functor.Identity from transformers to base 7ae596a Typo fix; Trac #9787 4923cea Define list monad operations using comprehensions e567130 De-bias Data.Foldable and improve docstrings 97420b0 Comments only (on recursive dictionaries) ed57ea4 Test Trac #9662 e9d3e28 Comments only 7cbe34f Improve documentation of -ticky a little 13817f0 Test Trac #9077 2b67b8f Test Trac #7862 76d47ed Add stderr for T9662 fcfc87d Disable T4801/peak_megabytes_allocated c774b28 Implement new integer-gmp2 from scratch (re #9281) d70b19b Per-thread allocation counters and limits 4b5d62a Fix build errors on Windows (these tests still don't work though) 8c10b67 fix allocLimit3 on Windows 1d35c85 Test #9066 in th/T9066 d782694 Fix #9066. f61b3c4 Untabify template-haskell. 1d66167 Remove unboxed Int# fields from NameFlavour (#9527) 88a42be Derive Generic for TH types (#9527) 767feb3 Test #8100 in th/T8100 4ac9e90 Fix #8100, by adding StandaloneDerivD to TH's Dec type. fe71a7e Test #9064 in th/T9064 e4efb7b Fix #9064 by adding support for generic default signatures to TH. ec8781f Test #9204 in roles/should_fail/T9204 ee0f34d Fix #9204 by outputting extra info on boot file mismatch. 90a2bb6 Testsuite wibbles due to #9204 294ac47 Fix #9788 by giving `coerce` the right type. e6e45a1 Test #9404 (typecheck/should_compile/T9404 and T9404b) fe6a517 Testsuite wibble due to #9404 1e2002d Fix #9404 by removing tcInfExpr. From git at git.haskell.org Wed Nov 12 19:52:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 19:52:08 +0000 (UTC) Subject: [commit: ghc] master's head updated: Fix #9404 by removing tcInfExpr. (1e2002d) Message-ID: <20141112195208.BEFDC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: 1d35c85 Test #9066 in th/T9066 d782694 Fix #9066. f61b3c4 Untabify template-haskell. 1d66167 Remove unboxed Int# fields from NameFlavour (#9527) 88a42be Derive Generic for TH types (#9527) 767feb3 Test #8100 in th/T8100 4ac9e90 Fix #8100, by adding StandaloneDerivD to TH's Dec type. fe71a7e Test #9064 in th/T9064 e4efb7b Fix #9064 by adding support for generic default signatures to TH. ec8781f Test #9204 in roles/should_fail/T9204 ee0f34d Fix #9204 by outputting extra info on boot file mismatch. 90a2bb6 Testsuite wibbles due to #9204 294ac47 Fix #9788 by giving `coerce` the right type. e6e45a1 Test #9404 (typecheck/should_compile/T9404 and T9404b) fe6a517 Testsuite wibble due to #9404 1e2002d Fix #9404 by removing tcInfExpr. From git at git.haskell.org Wed Nov 12 23:36:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Nov 2014 23:36:07 +0000 (UTC) Subject: [commit: ghc] master: includes/Stg.h: define _DEFAULT_SOURCE for glibc-2.20 (c65221b) Message-ID: <20141112233607.27A343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c65221bdbdebb0a6e615970cb0ca78abcb4202f8/ghc >--------------------------------------------------------------- commit c65221bdbdebb0a6e615970cb0ca78abcb4202f8 Author: Sergei Trofimovich Date: Wed Nov 12 23:18:38 2014 +0000 includes/Stg.h: define _DEFAULT_SOURCE for glibc-2.20 _BSD_SOURCE we are using for 'gamma()' and friends was deprecated in glibc-2.20 in favour of '_DEFAULT_SOURCE'. gcc says: In file included from /usr/include/math.h:26:0: 0, from includes/Stg.h:69, from /tmp/ghc19488_0/ghc19488_2.hc:3: /usr/include/features.h:148:3: warning: #warning "_BSD_SOURCE and _SVID_SOURCE are deprecated, use _DEFAULT_SOURCE" [-Wcpp] # warning "_BSD_SOURCE and _SVID_SOURCE are deprecated, use _DEFAULT_SOURCE" ^ Patch fixes testsuite failures on UNREG (stderr are not cluttered by warnings anymore). Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- c65221bdbdebb0a6e615970cb0ca78abcb4202f8 includes/Stg.h | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/includes/Stg.h b/includes/Stg.h index 4c26e3e..f09fc00 100644 --- a/includes/Stg.h +++ b/includes/Stg.h @@ -47,6 +47,10 @@ // We need _BSD_SOURCE so that math.h defines things like gamma // on Linux # define _BSD_SOURCE + +// '_BSD_SOURCE' is deprecated since glibc-2.20 +// in favour of '_DEFAULT_SOURCE' +# define _DEFAULT_SOURCE #endif #if IN_STG_CODE == 0 || defined(llvm_CC_FLAVOR) From git at git.haskell.org Thu Nov 13 00:09:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 00:09:32 +0000 (UTC) Subject: [commit: ghc] master: Add in `-fwarn-trustworthy-safe` flag. (1f8b4ee) Message-ID: <20141113000932.177603A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1f8b4ee074b4d9e3d847b3139dc89fff1bb5d2e6/ghc >--------------------------------------------------------------- commit 1f8b4ee074b4d9e3d847b3139dc89fff1bb5d2e6 Author: David Terei Date: Fri Nov 7 14:11:19 2014 -0800 Add in `-fwarn-trustworthy-safe` flag. This warns when a module marked as `-XTrustworthy` could have been inferred as safe instead. >--------------------------------------------------------------- 1f8b4ee074b4d9e3d847b3139dc89fff1bb5d2e6 compiler/main/DynFlags.hs | 14 +- compiler/main/HscMain.hs | 149 +++++++++++++-------- .../tests/safeHaskell/check/pkg01/ImpSafe01.hs | 2 +- .../tests/safeHaskell/check/pkg01/ImpSafe02.hs | 2 +- .../tests/safeHaskell/check/pkg01/ImpSafe03.hs | 8 ++ .../tests/safeHaskell/check/pkg01/ImpSafe03.stderr | 4 + .../tests/safeHaskell/check/pkg01/ImpSafe03_A.hs | 8 ++ .../check/pkg01/{ImpSafe01.hs => ImpSafe04.hs} | 7 +- .../tests/safeHaskell/check/pkg01/ImpSafe04.stderr | 4 + testsuite/tests/safeHaskell/check/pkg01/all.T | 11 +- .../tests/safeHaskell/safeInfered/SafeWarn01.hs | 11 ++ .../safeHaskell/safeInfered/SafeWarn01.stderr | 3 + .../safeHaskell/safeInfered/TrustworthySafe01.hs | 9 ++ .../safeHaskell/safeInfered/TrustworthySafe02.hs | 10 ++ .../safeInfered/TrustworthySafe02.stderr | 3 + .../safeHaskell/safeInfered/TrustworthySafe04.hs | 10 ++ .../tests/safeHaskell/safeInfered/UnsafeWarn01.hs | 11 ++ .../safeHaskell/safeInfered/UnsafeWarn01.stderr | 7 + .../tests/safeHaskell/safeInfered/UnsafeWarn02.hs | 10 ++ .../safeHaskell/safeInfered/UnsafeWarn02.stderr | 6 + .../tests/safeHaskell/safeInfered/UnsafeWarn03.hs | 12 ++ .../safeHaskell/safeInfered/UnsafeWarn03.stderr | 7 + .../tests/safeHaskell/safeInfered/UnsafeWarn04.hs | 12 ++ .../safeHaskell/safeInfered/UnsafeWarn04.stderr | 7 + .../tests/safeHaskell/safeInfered/UnsafeWarn05.hs | 19 +++ .../safeHaskell/safeInfered/UnsafeWarn05.stderr | 14 ++ .../tests/safeHaskell/safeInfered/UnsafeWarn06.hs | 12 ++ .../safeHaskell/safeInfered/UnsafeWarn06.stderr | 7 + .../tests/safeHaskell/safeInfered/UnsafeWarn07.hs | 13 ++ .../safeHaskell/safeInfered/UnsafeWarn07.stderr | 7 + testsuite/tests/safeHaskell/safeInfered/all.T | 17 +++ .../tests/safeHaskell/safeLanguage/SafeLang18.hs | 14 ++ testsuite/tests/safeHaskell/safeLanguage/all.T | 2 + .../tests/safeHaskell/unsafeLibs/BadImport08.hs | 2 +- .../safeHaskell/unsafeLibs/BadImport08.stderr | 2 +- .../unsafeLibs/{BadImport08.hs => BadImport09.hs} | 2 +- .../safeHaskell/unsafeLibs/BadImport09.stderr | 4 + testsuite/tests/safeHaskell/unsafeLibs/all.T | 1 + 38 files changed, 377 insertions(+), 66 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1f8b4ee074b4d9e3d847b3139dc89fff1bb5d2e6 From git at git.haskell.org Thu Nov 13 00:09:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 00:09:34 +0000 (UTC) Subject: [commit: ghc] master: Remove a stray Trustworthy flag in ghc. (064c289) Message-ID: <20141113000934.A95623A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/064c28960730ed2f592fb675c9a11310e2371b66/ghc >--------------------------------------------------------------- commit 064c28960730ed2f592fb675c9a11310e2371b66 Author: David Terei Date: Wed Nov 12 13:54:55 2014 -0800 Remove a stray Trustworthy flag in ghc. >--------------------------------------------------------------- 064c28960730ed2f592fb675c9a11310e2371b66 compiler/cmm/Hoopl/Dataflow.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/compiler/cmm/Hoopl/Dataflow.hs b/compiler/cmm/Hoopl/Dataflow.hs index f551151..4fbf42e 100644 --- a/compiler/cmm/Hoopl/Dataflow.hs +++ b/compiler/cmm/Hoopl/Dataflow.hs @@ -3,7 +3,6 @@ {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE Trustworthy #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -fprof-auto-top #-} From git at git.haskell.org Thu Nov 13 01:37:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 01:37:19 +0000 (UTC) Subject: [commit: packages/stm] master: Tighten Safe Haskell bounds. (6b63e91) Message-ID: <20141113013719.DC69B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm On branch : master Link : http://git.haskell.org/packages/stm.git/commitdiff/6b63e91b2b0b7d7b4bef654117da62c22cac34da >--------------------------------------------------------------- commit 6b63e91b2b0b7d7b4bef654117da62c22cac34da Author: David Terei Date: Wed Nov 12 17:35:21 2014 -0800 Tighten Safe Haskell bounds. >--------------------------------------------------------------- 6b63e91b2b0b7d7b4bef654117da62c22cac34da Control/Concurrent/STM.hs | 4 +++- Control/Sequential/STM.hs | 4 +++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/Control/Concurrent/STM.hs b/Control/Concurrent/STM.hs index 1fc6a77..83fbdc5 100644 --- a/Control/Concurrent/STM.hs +++ b/Control/Concurrent/STM.hs @@ -1,6 +1,8 @@ {-# LANGUAGE CPP #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Trustworthy #-} #endif diff --git a/Control/Sequential/STM.hs b/Control/Sequential/STM.hs index 686a406..226c788 100644 --- a/Control/Sequential/STM.hs +++ b/Control/Sequential/STM.hs @@ -4,7 +4,9 @@ {-# LANGUAGE CPP #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Trustworthy #-} #endif From git at git.haskell.org Thu Nov 13 01:40:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 01:40:16 +0000 (UTC) Subject: [commit: packages/hpc] master: Mark Mix as Safe, not Trustworthy. (60e7bbf) Message-ID: <20141113014016.BE9CE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : master Link : http://git.haskell.org/packages/hpc.git/commitdiff/60e7bbfeea8ba54688b8f432f0f337b275f06c58 >--------------------------------------------------------------- commit 60e7bbfeea8ba54688b8f432f0f337b275f06c58 Author: David Terei Date: Wed Nov 12 17:40:23 2014 -0800 Mark Mix as Safe, not Trustworthy. >--------------------------------------------------------------- 60e7bbfeea8ba54688b8f432f0f337b275f06c58 Trace/Hpc/Mix.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index 83e8c02..28050ad 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP #-} -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Trustworthy #-} #endif --------------------------------------------------------------- From git at git.haskell.org Thu Nov 13 01:42:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 01:42:13 +0000 (UTC) Subject: [commit: packages/hoopl] master: Mark a few modules as Safe rather than Trustworthy. (a90a3af) Message-ID: <20141113014213.4F3603A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hoopl On branch : master Link : http://git.haskell.org/packages/hoopl.git/commitdiff/a90a3af92be400af8912555bce21b041a1c48ad4 >--------------------------------------------------------------- commit a90a3af92be400af8912555bce21b041a1c48ad4 Author: David Terei Date: Wed Nov 12 17:42:14 2014 -0800 Mark a few modules as Safe rather than Trustworthy. >--------------------------------------------------------------- a90a3af92be400af8912555bce21b041a1c48ad4 src/Compiler/Hoopl/Dataflow.hs | 10 ++++++---- src/Compiler/Hoopl/Unique.hs | 5 ++++- src/Compiler/Hoopl/XUtil.hs | 4 +++- 3 files changed, 13 insertions(+), 6 deletions(-) diff --git a/src/Compiler/Hoopl/Dataflow.hs b/src/Compiler/Hoopl/Dataflow.hs index e496931..23254ca 100644 --- a/src/Compiler/Hoopl/Dataflow.hs +++ b/src/Compiler/Hoopl/Dataflow.hs @@ -1,10 +1,12 @@ {-# LANGUAGE CPP, RankNTypes, ScopedTypeVariables, GADTs, TypeFamilies, MultiParamTypeClasses #-} -#if __GLASGOW_HASKELL__ >= 703 -{- OPTIONS_GHC -fprof-auto #-} -#endif -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Trustworthy #-} #endif +#if __GLASGOW_HASKELL__ >= 703 +{-# OPTIONS_GHC -fprof-auto #-} +#endif #if __GLASGOW_HASKELL__ < 701 {-# OPTIONS_GHC -fno-warn-incomplete-patterns #-} #endif diff --git a/src/Compiler/Hoopl/Unique.hs b/src/Compiler/Hoopl/Unique.hs index bf3de75..0e88fb4 100644 --- a/src/Compiler/Hoopl/Unique.hs +++ b/src/Compiler/Hoopl/Unique.hs @@ -1,8 +1,11 @@ {-# LANGUAGE CPP, TypeFamilies #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Trustworthy #-} #endif + module Compiler.Hoopl.Unique ( Unique, intToUnique , UniqueSet, UniqueMap diff --git a/src/Compiler/Hoopl/XUtil.hs b/src/Compiler/Hoopl/XUtil.hs index 60551f9..4132113 100644 --- a/src/Compiler/Hoopl/XUtil.hs +++ b/src/Compiler/Hoopl/XUtil.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP, GADTs, RankNTypes, ScopedTypeVariables, TypeFamilies #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Trustworthy #-} #endif From git at git.haskell.org Thu Nov 13 01:44:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 01:44:02 +0000 (UTC) Subject: [commit: packages/haskell98] master: Mark some modules as Safe rather than Trustworthy. (cf064d9) Message-ID: <20141113014402.9E8473A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskell98 On branch : master Link : http://git.haskell.org/packages/haskell98.git/commitdiff/cf064d954c511a2edddb5a55a1984d57ce36c407 >--------------------------------------------------------------- commit cf064d954c511a2edddb5a55a1984d57ce36c407 Author: David Terei Date: Wed Nov 12 17:44:03 2014 -0800 Mark some modules as Safe rather than Trustworthy. >--------------------------------------------------------------- cf064d954c511a2edddb5a55a1984d57ce36c407 Array.hs | 4 +++- Directory.hs | 4 +++- Locale.hs | 4 +++- System.hs | 4 +++- Time.hs | 4 +++- 5 files changed, 15 insertions(+), 5 deletions(-) diff --git a/Array.hs b/Array.hs index 86e8796..3bcc271 100644 --- a/Array.hs +++ b/Array.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Trustworthy #-} #endif diff --git a/Directory.hs b/Directory.hs index 68f67ba..bfea5de 100644 --- a/Directory.hs +++ b/Directory.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Trustworthy #-} #endif diff --git a/Locale.hs b/Locale.hs index ba231f6..65123da 100644 --- a/Locale.hs +++ b/Locale.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Trustworthy #-} #endif diff --git a/System.hs b/System.hs index ebc4ea7..212af71 100644 --- a/System.hs +++ b/System.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Trustworthy #-} #endif diff --git a/Time.hs b/Time.hs index 736256e..67f4c85 100644 --- a/Time.hs +++ b/Time.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Trustworthy #-} #endif From git at git.haskell.org Thu Nov 13 01:44:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 01:44:45 +0000 (UTC) Subject: [commit: packages/haskell2010] master: Mark Array as Safe rather than Trustworthy. (a21abff) Message-ID: <20141113014445.714C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskell2010 On branch : master Link : http://git.haskell.org/packages/haskell2010.git/commitdiff/a21abff3e385a85e1353aa720516e148865710a1 >--------------------------------------------------------------- commit a21abff3e385a85e1353aa720516e148865710a1 Author: David Terei Date: Wed Nov 12 17:44:59 2014 -0800 Mark Array as Safe rather than Trustworthy. >--------------------------------------------------------------- a21abff3e385a85e1353aa720516e148865710a1 Data/Array.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/Data/Array.hs b/Data/Array.hs index 100674d..760c26e 100644 --- a/Data/Array.hs +++ b/Data/Array.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP, PackageImports #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Trustworthy #-} #endif From git at git.haskell.org Thu Nov 13 02:23:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 02:23:01 +0000 (UTC) Subject: [commit: ghc] master: Add `--fwarn-trustworthy-safe` to `-Wall` (475dd93) Message-ID: <20141113022301.B39553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/475dd93efa5158a0f9516f6819a24edfc30c1a76/ghc >--------------------------------------------------------------- commit 475dd93efa5158a0f9516f6819a24edfc30c1a76 Author: David Terei Date: Wed Nov 12 16:11:39 2014 -0800 Add `--fwarn-trustworthy-safe` to `-Wall` Update submodule haskell2010, haskell98, hoop, hpc and stm to fix new warnings. >--------------------------------------------------------------- 475dd93efa5158a0f9516f6819a24edfc30c1a76 compiler/main/DynFlags.hs | 3 ++- libraries/haskell2010 | 2 +- libraries/haskell98 | 2 +- libraries/hoopl | 2 +- libraries/hpc | 2 +- libraries/stm | 2 +- mk/validate-settings.mk | 7 +++++++ .../safeInfered/{TrustworthySafe01.hs => TrustworthySafe03.hs} | 5 +++-- testsuite/tests/safeHaskell/safeInfered/TrustworthySafe03.stderr | 3 +++ testsuite/tests/safeHaskell/safeInfered/all.T | 1 + 10 files changed, 21 insertions(+), 8 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 043174f..70fc6d3 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -3154,7 +3154,8 @@ minusWallOpts Opt_WarnMissingSigs, Opt_WarnHiShadows, Opt_WarnOrphans, - Opt_WarnUnusedDoBind + Opt_WarnUnusedDoBind, + Opt_WarnTrustworthySafe ] enableGlasgowExts :: DynP () diff --git a/libraries/haskell2010 b/libraries/haskell2010 index 425df1d..a21abff 160000 --- a/libraries/haskell2010 +++ b/libraries/haskell2010 @@ -1 +1 @@ -Subproject commit 425df1d9ea7adcf823bbb5426528bd80eb2b820e +Subproject commit a21abff3e385a85e1353aa720516e148865710a1 diff --git a/libraries/haskell98 b/libraries/haskell98 index 401283a..cf064d9 160000 --- a/libraries/haskell98 +++ b/libraries/haskell98 @@ -1 +1 @@ -Subproject commit 401283a98a818f66f856939f939562de5c4a2b47 +Subproject commit cf064d954c511a2edddb5a55a1984d57ce36c407 diff --git a/libraries/hoopl b/libraries/hoopl index 7f06b16..a90a3af 160000 --- a/libraries/hoopl +++ b/libraries/hoopl @@ -1 +1 @@ -Subproject commit 7f06b16ba3a49c2c927fb06fe7dc89089dd7e29f +Subproject commit a90a3af92be400af8912555bce21b041a1c48ad4 diff --git a/libraries/hpc b/libraries/hpc index d430be4..60e7bbf 160000 --- a/libraries/hpc +++ b/libraries/hpc @@ -1 +1 @@ -Subproject commit d430be4664aac337cd0e49dd6b69e818f21cde6b +Subproject commit 60e7bbfeea8ba54688b8f432f0f337b275f06c58 diff --git a/libraries/stm b/libraries/stm index 40fd6d8..6b63e91 160000 --- a/libraries/stm +++ b/libraries/stm @@ -1 +1 @@ -Subproject commit 40fd6d88f75c31b66419ab93f436225c9403846c +Subproject commit 6b63e91b2b0b7d7b4bef654117da62c22cac34da diff --git a/mk/validate-settings.mk b/mk/validate-settings.mk index 52aa648..150aec3 100644 --- a/mk/validate-settings.mk +++ b/mk/validate-settings.mk @@ -163,6 +163,13 @@ libraries/dph/dph-lifted-common-install_EXTRA_HC_OPTS += -Wwarn # We need to turn of deprecated warnings for SafeHaskell transition libraries/array_dist-install_EXTRA_HC_OPTS += -fno-warn-warnings-deprecations +# Turn of trustworthy-safe warning +libraries/base_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe +libraries/ghc-prim_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe +libraries/containers_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe +libraries/process_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe +libraries/unix_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe + # Temporarely disable inline rule shadowing warning libraries/bytestring_dist-install_EXTRA_HC_OPTS += -fno-warn-inline-rule-shadowing libraries/template-haskell_dist-install_EXTRA_HC_OPTS += -fno-warn-inline-rule-shadowing diff --git a/testsuite/tests/safeHaskell/safeInfered/TrustworthySafe01.hs b/testsuite/tests/safeHaskell/safeInfered/TrustworthySafe03.hs similarity index 57% copy from testsuite/tests/safeHaskell/safeInfered/TrustworthySafe01.hs copy to testsuite/tests/safeHaskell/safeInfered/TrustworthySafe03.hs index 6d65130..12be9b1 100644 --- a/testsuite/tests/safeHaskell/safeInfered/TrustworthySafe01.hs +++ b/testsuite/tests/safeHaskell/safeInfered/TrustworthySafe03.hs @@ -1,8 +1,9 @@ {-# LANGUAGE Trustworthy #-} +{-# OPTIONS_GHC -Wall #-} -- | This module is marked trustworthy but should be inferable as -XSafe. --- But no warning enabled. -module TrustworthySafe01 where +-- Warning enabled through `-W`. +module TrustworthySafe03 where g :: Int g = 1 diff --git a/testsuite/tests/safeHaskell/safeInfered/TrustworthySafe03.stderr b/testsuite/tests/safeHaskell/safeInfered/TrustworthySafe03.stderr new file mode 100644 index 0000000..9505d06 --- /dev/null +++ b/testsuite/tests/safeHaskell/safeInfered/TrustworthySafe03.stderr @@ -0,0 +1,3 @@ + +TrustworthySafe03.hs:1:14: Warning: + ?TrustworthySafe03? is marked as Trustworthy but has been inferred as safe! diff --git a/testsuite/tests/safeHaskell/safeInfered/all.T b/testsuite/tests/safeHaskell/safeInfered/all.T index 89062cd..12e80a7 100644 --- a/testsuite/tests/safeHaskell/safeInfered/all.T +++ b/testsuite/tests/safeHaskell/safeInfered/all.T @@ -76,6 +76,7 @@ test('Mixed03', normal, compile_fail, ['']) # Trustworthy Safe modules test('TrustworthySafe01', normal, compile, ['']) test('TrustworthySafe02', normal, compile, ['']) +test('TrustworthySafe03', normal, compile, ['']) test('TrustworthySafe04', normal, compile, ['']) # Check -fwarn-unsafe works From git at git.haskell.org Thu Nov 13 02:51:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 02:51:31 +0000 (UTC) Subject: [commit: ghc] master: Update userguide for new `-fwarn-trustworthy-safe` flag. (8fe2bbe) Message-ID: <20141113025131.E873E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8fe2bbe9502b4accafb14a4234f264f4457f3ff2/ghc >--------------------------------------------------------------- commit 8fe2bbe9502b4accafb14a4234f264f4457f3ff2 Author: David Terei Date: Wed Nov 12 18:39:01 2014 -0800 Update userguide for new `-fwarn-trustworthy-safe` flag. >--------------------------------------------------------------- 8fe2bbe9502b4accafb14a4234f264f4457f3ff2 docs/users_guide/7.10.1-notes.xml | 30 ++++++++++++++++++++++++++++++ docs/users_guide/flags.xml | 21 +++++++++++++++++++-- docs/users_guide/safe_haskell.xml | 11 ++++++++++- 3 files changed, 59 insertions(+), 3 deletions(-) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 7c1e65a..2e509e1 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -91,6 +91,36 @@ + + A new warning flag, + has been added and is turned on with + . It warns when a module that is + compiled with is actually + infered as an module. This lets the + module author know that they can tighten their Safe Haskell + bounds if desired. + + + + + The and + that warn if a module was + infered as Safe or Unsafe have been improved to work with + all Safe Haskell module types. Previously, they only worked + for unmarked modules where the compiler was infering the + modules Safe Haskell type. They now work even for modules + marked as or + . This is useful either to have + GHC check your assumptions, or to generate a list of + reasons easily why a module is regarded as Unsafe. + + + For many use cases, the new + flag is better + suited than either of these two. + + + and flags have been removed. diff --git a/docs/users_guide/flags.xml b/docs/users_guide/flags.xml index 2c0e548..33af295 100644 --- a/docs/users_guide/flags.xml +++ b/docs/users_guide/flags.xml @@ -1565,7 +1565,10 @@ warn if the module being compiled is regarded to be unsafe. Should be used to check the safety status of modules when using safe - inference. + inference. Works on all module types, even those using explicit + Safe Haskell modes (such as + ) and so can be used to have the + compiler check any assumptions made. dynamic @@ -1574,7 +1577,21 @@ warn if the module being compiled is regarded to be safe. Should be used to check the safety status of modules when using safe - inference. + inference. Works on all module types, even those using explicit + Safe Haskell modes (such as + ) and so can be used to have the + compiler check any assumptions made. + dynamic + + + + + + warn if the module being compiled is marked as + but it could instead be marked as + , a more informative bound. Can be used to + detect once a Safe Haskell bound can be improved as dependencies + are updated. dynamic diff --git a/docs/users_guide/safe_haskell.xml b/docs/users_guide/safe_haskell.xml index 10d0a63..634482a 100644 --- a/docs/users_guide/safe_haskell.xml +++ b/docs/users_guide/safe_haskell.xml @@ -705,7 +705,7 @@ - And two warning flags: + And three warning flags: @@ -724,6 +724,15 @@ when using safe inference. + + -fwarn-trustworthy-safe + -fwarn-trustworthy-safe + Issue a warning if the module being compiled is marked as + but it could instead be marked as + , a more informative bound. Can be used to + detect once a Safe Haskell bound can be improved as dependencies are + updated. + From git at git.haskell.org Thu Nov 13 07:43:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 07:43:58 +0000 (UTC) Subject: [commit: ghc] master: base: Fix map/coerce comment (413c747) Message-ID: <20141113074358.1181D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/413c747ab1daaf489b6ef4106739df280323525b/ghc >--------------------------------------------------------------- commit 413c747ab1daaf489b6ef4106739df280323525b Author: David Feuer Date: Thu Nov 13 08:43:33 2014 +0100 base: Fix map/coerce comment Make the comment on the map/coerce rule refer to the right section in the paper; give the full name of the papers, and name its authors. [skip ci] Differential Revision: https://phabricator.haskell.org/D472 >--------------------------------------------------------------- 413c747ab1daaf489b6ef4106739df280323525b libraries/base/GHC/Base.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index 0d20e34..397e2b7 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -864,9 +864,8 @@ mapFB c f = \x ys -> c (f x) ys "mapFB" forall c f g. mapFB (mapFB c f) g = mapFB c (f.g) #-} --- There's also a rule for Map and Data.Coerce. See "Safe Coercions", --- section 6.4: --- +-- See Breitner, Eisenberg, Peyton Jones, and Weirich, "Safe Zero-cost +-- Coercions for Haskell", section 6.5: -- http://research.microsoft.com/en-us/um/people/simonpj/papers/ext-f/coercible.pdf {-# RULES "map/coerce" [1] map coerce = coerce #-} From git at git.haskell.org Thu Nov 13 08:01:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 08:01:08 +0000 (UTC) Subject: [commit: ghc] master: Make unwords and words fuse somewhat (e73ab54) Message-ID: <20141113080108.DD0D93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e73ab5412935392c03ce736ebee2b1282932c2ff/ghc >--------------------------------------------------------------- commit e73ab5412935392c03ce736ebee2b1282932c2ff Author: David Feuer Date: Thu Nov 13 08:59:14 2014 +0100 Make unwords and words fuse somewhat Make `words` a good producer and `unwords` a good consumer for list fusion. Thus `unwords . words` will avoid producing an intermediate list of words, although it will produce each individual word. Make `unwords` slightly lazier, so that `unwords (s : undefined) = s ++ undefined` instead of `= undefined`. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D375 >--------------------------------------------------------------- e73ab5412935392c03ce736ebee2b1282932c2ff libraries/base/Data/OldList.hs | 47 ++++++++++++++++++++++++++++++++++++++---- 1 file changed, 43 insertions(+), 4 deletions(-) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index caad044..551b8be 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -754,6 +754,7 @@ groupBy eq (x:xs) = (x:ys) : groupBy eq zs inits :: [a] -> [[a]] inits = map toListSB . scanl' snocSB emptySB {-# NOINLINE inits #-} + -- We do not allow inits to inline, because it plays havoc with Call Arity -- if it fuses with a consumer, and it would generally lead to serious -- loss of sharing if allowed to fuse with a producer. @@ -1066,12 +1067,26 @@ unlines (l:ls) = l ++ '\n' : unlines ls -- | 'words' breaks a string up into a list of words, which were delimited -- by white space. words :: String -> [String] +{-# NOINLINE [1] words #-} words s = case dropWhile {-partain:Char.-}isSpace s of "" -> [] s' -> w : words s'' where (w, s'') = break {-partain:Char.-}isSpace s' +{-# RULES +"words" [~1] forall s . words s = build (\c n -> wordsFB c n s) +"wordsList" [1] wordsFB (:) [] = words + #-} +wordsFB :: ([Char] -> b -> b) -> b -> String -> b +{-# NOINLINE [0] wordsFB #-} +wordsFB c n = go + where + go s = case dropWhile isSpace s of + "" -> n + s' -> w `c` go s'' + where (w, s'') = break isSpace s' + -- | 'unwords' is an inverse operation to 'words'. -- It joins words with separating spaces. unwords :: [String] -> String @@ -1079,11 +1094,35 @@ unwords :: [String] -> String unwords [] = "" unwords ws = foldr1 (\w s -> w ++ ' ':s) ws #else --- HBC version (stolen) --- here's a more efficient version +-- Here's a lazier version that can get the last element of a +-- _|_-terminated list. +{-# NOINLINE [1] unwords #-} unwords [] = "" -unwords [w] = w -unwords (w:ws) = w ++ ' ' : unwords ws +unwords (w:ws) = w ++ go ws + where + go [] = "" + go (v:vs) = ' ' : (v ++ go vs) + +-- In general, the foldr-based version is probably slightly worse +-- than the HBC version, because it adds an extra space and then takes +-- it back off again. But when it fuses, it reduces allocation. How much +-- depends entirely on the average word length--it's most effective when +-- the words are on the short side. +{-# RULES +"unwords" [~1] forall ws . + unwords ws = tailUnwords (foldr unwordsFB "" ws) +"unwordsList" [1] forall ws . + tailUnwords (foldr unwordsFB "" ws) = unwords ws + #-} + +{-# INLINE [0] tailUnwords #-} +tailUnwords :: String -> String +tailUnwords [] = [] +tailUnwords (_:xs) = xs + +{-# INLINE [0] unwordsFB #-} +unwordsFB :: String -> String -> String +unwordsFB w r = ' ' : w ++ r #endif {- A "SnocBuilder" is a version of Chris Okasaki's banker's queue that supports From git at git.haskell.org Thu Nov 13 08:06:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 08:06:43 +0000 (UTC) Subject: [commit: ghc] master: base: define `sequence = mapM id` (c016e6f) Message-ID: <20141113080643.3730B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c016e6f74e26708586352fec657798f271b0675b/ghc >--------------------------------------------------------------- commit c016e6f74e26708586352fec657798f271b0675b Author: David Feuer Date: Thu Nov 13 09:05:22 2014 +0100 base: define `sequence = mapM id` This avoids duplication in `GHC.Base`; originally, we had mapM f = sequence . map f This led to excessive allocation in `cryptarithm2`. Defining sequence = mapM id does not appear to cause any `nofib` problems. Reviewed By: hvr Differential Revision: https://phabricator.haskell.org/D470 >--------------------------------------------------------------- c016e6f74e26708586352fec657798f271b0675b libraries/base/GHC/Base.hs | 22 +++++++++++++++++++--- 1 file changed, 19 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index 397e2b7..f2a447d 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -518,9 +518,8 @@ when p s = if p then s else pure () -- and collect the results. sequence :: Monad m => [m a] -> m [a] {-# INLINE sequence #-} -sequence ms = foldr k (return []) ms - where - k m m' = do { x <- m; xs <- m'; return (x:xs) } +sequence = mapM id +-- Note: [sequence and mapM] -- | @'mapM' f@ is equivalent to @'sequence' . 'map' f at . mapM :: Monad m => (a -> m b) -> [a] -> m [b] @@ -529,6 +528,23 @@ mapM f as = foldr k (return []) as where k a r = do { x <- f a; xs <- r; return (x:xs) } +{- +Note: [sequence and mapM] +~~~~~~~~~~~~~~~~~~~~~~~~~ +Originally, we defined + +mapM f = sequence . map f + +This relied on list fusion to produce efficient code for mapM, and led to +excessive allocation in cryptarithm2. Defining + +sequence = mapM id + +relies only on inlining a tiny function (id) and beta reduction, which tends to +be a more reliable aspect of simplification. Indeed, this does not lead to +similar problems in nofib. +-} + -- | Promote a function to a monad. liftM :: (Monad m) => (a1 -> r) -> m a1 -> m r liftM f m1 = do { x1 <- m1; return (f x1) } From git at git.haskell.org Thu Nov 13 08:17:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 08:17:58 +0000 (UTC) Subject: [commit: ghc] master: Improve `Foldable` instance for `Array` (212a350) Message-ID: <20141113081758.61DD53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/212a350547e950cc5be465a3d76e346ef14bf2ab/ghc >--------------------------------------------------------------- commit 212a350547e950cc5be465a3d76e346ef14bf2ab Author: David Feuer Date: Thu Nov 13 09:10:57 2014 +0100 Improve `Foldable` instance for `Array` Previously, `Array`s were simply converted to lists, and the list methods used. That works acceptably well for `foldr` and `foldr1`, but not so sensibly for most other things. Left folds ended up "twisted" the way they are for lists, leading to surprising performance characteristics. Moreover, this implements `length` and `null` so they check the array size directly. Finally, a test is added to the testsuite ensuring the overridden `Foldable` methods agree with their expected default semantics. Addresses #9763 Reviewed By: hvr, austin Differential Revision: https://phabricator.haskell.org/D459 >--------------------------------------------------------------- 212a350547e950cc5be465a3d76e346ef14bf2ab libraries/base/Data/Foldable.hs | 18 +++-- libraries/base/GHC/Arr.hs | 59 +++++++++++++- libraries/base/tests/all.T | 1 + libraries/base/tests/foldableArray.hs | 129 ++++++++++++++++++++++++++++++ libraries/base/tests/foldableArray.stdout | 13 +++ 5 files changed, 214 insertions(+), 6 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 212a350547e950cc5be465a3d76e346ef14bf2ab From git at git.haskell.org Thu Nov 13 09:43:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 09:43:21 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Avoid premature unfolding of `seq` (bbefa6d) Message-ID: <20141113094321.0CCED3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/bbefa6d2f2ee57f56ef7d0f5bc636818460c9165/ghc >--------------------------------------------------------------- commit bbefa6d2f2ee57f56ef7d0f5bc636818460c9165 Author: Dr. ERDI Gergo Date: Thu Nov 13 17:39:03 2014 +0800 Avoid premature unfolding of `seq` >--------------------------------------------------------------- bbefa6d2f2ee57f56ef7d0f5bc636818460c9165 compiler/basicTypes/MkId.lhs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index 9fc728b..011df11 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -1088,7 +1088,7 @@ seqId :: Id -- See Note [seqId magic] seqId = pcMiscPrelId seqName ty info where info = noCafIdInfo `setInlinePragInfo` alwaysInlinePragma - `setUnfoldingInfo` mkCompulsoryUnfolding rhs + `setUnfoldingInfo` mkInlineUnfolding (Just 2) rhs `setSpecInfo` mkSpecInfo [seq_cast_rule] @@ -1097,7 +1097,7 @@ seqId = pcMiscPrelId seqName ty info -- NB argBetaTyVar; see Note [seqId magic] [x,y] = mkTemplateLocals [alphaTy, betaTy] - rhs = mkLams [alphaTyVar,betaTyVar,x,y] (Case (Var x) x betaTy [(DEFAULT, [], Var y)]) + rhs = mkLams [alphaTyVar,openBetaTyVar,x,y] (Case (Var x) x betaTy [(DEFAULT, [], Var y)]) -- See Note [Built-in RULES for seq] seq_cast_rule = BuiltinRule { ru_name = fsLit "seq of cast" From git at git.haskell.org Thu Nov 13 09:43:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 09:43:23 +0000 (UTC) Subject: [commit: ghc] wip/T9732: When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments (93182cd) Message-ID: <20141113094323.A353B3A302@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/93182cdd039a59fd999185cc2cf8d132d1a28f74/ghc >--------------------------------------------------------------- commit 93182cdd039a59fd999185cc2cf8d132d1a28f74 Author: Dr. ERDI Gergo Date: Thu Nov 13 17:41:29 2014 +0800 When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments >--------------------------------------------------------------- 93182cdd039a59fd999185cc2cf8d132d1a28f74 compiler/typecheck/TcPatSyn.lhs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 8ba69fd..464beaa 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -139,7 +139,7 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; let tv_name = mkInternalName uniq (mkTyVarOcc "r") loc ; return $ mkTcTyVar tv_name openTypeKind (SkolemTv False) } ; matcher_name <- newImplicitBinder name mkMatcherOcc - ; let res_ty = TyVarTy res_tv + ; let res_ty = mkTyVarTy res_tv cont_args = if null args then [voidPrimId] else args cont_ty = mkSigmaTy ex_tvs prov_theta $ mkFunTys (map varType cont_args) res_ty @@ -154,7 +154,8 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; scrutinee <- mkId "scrut" pat_ty ; cont <- mkId "cont" cont_ty - ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ cont_args) + ; let cont' = nlHsTyApps cont (map mkTyVarTy ex_tvs) $ + map nlHsVar (prov_dicts ++ cont_args) ; fail <- mkId "fail" fail_ty ; let fail' = nlHsApps fail [nlHsVar voidPrimId] From git at git.haskell.org Thu Nov 13 09:43:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 09:43:18 +0000 (UTC) Subject: [commit: ghc] wip/T9732: nlHsTyApps: for applying a function both on type- and term-level arguments (41ea4a3) Message-ID: <20141113094318.6912E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/41ea4a336b51d77ba7a4ed4e7d80d7c612c22659/ghc >--------------------------------------------------------------- commit 41ea4a336b51d77ba7a4ed4e7d80d7c612c22659 Author: Dr. ERDI Gergo Date: Fri Nov 7 22:49:52 2014 +0800 nlHsTyApps: for applying a function both on type- and term-level arguments >--------------------------------------------------------------- 41ea4a336b51d77ba7a4ed4e7d80d7c612c22659 compiler/hsSyn/HsUtils.lhs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/compiler/hsSyn/HsUtils.lhs b/compiler/hsSyn/HsUtils.lhs index 12e2388..df2406f 100644 --- a/compiler/hsSyn/HsUtils.lhs +++ b/compiler/hsSyn/HsUtils.lhs @@ -28,7 +28,7 @@ module HsUtils( mkHsOpApp, mkHsDo, mkHsComp, mkHsWrapPat, mkHsWrapPatCo, mkLHsPar, mkHsCmdCast, - nlHsTyApp, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, + nlHsTyApp, nlHsTyApps, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, nlHsDo, nlHsOpApp, nlHsLam, nlHsPar, nlHsIf, nlHsCase, nlList, mkLHsTupleExpr, mkLHsVarTuple, missingTupArg, toHsType, toHsKind, @@ -177,6 +177,9 @@ mkSimpleHsAlt pat expr nlHsTyApp :: name -> [Type] -> LHsExpr name nlHsTyApp fun_id tys = noLoc (HsWrap (mkWpTyApps tys) (HsVar fun_id)) +nlHsTyApps :: name -> [Type] -> [LHsExpr name] -> LHsExpr name +nlHsTyApps fun_id tys xs = foldl nlHsApp (nlHsTyApp fun_id tys) xs + --------- Adding parens --------- mkLHsPar :: LHsExpr name -> LHsExpr name -- Wrap in parens if hsExprNeedsParens says it needs them From git at git.haskell.org Thu Nov 13 09:49:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 09:49:01 +0000 (UTC) Subject: [commit: ghc] wip/T9732: When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments (7038a5c) Message-ID: <20141113094901.775033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/7038a5c21915a869291d53eca524ac0d4f06727c/ghc >--------------------------------------------------------------- commit 7038a5c21915a869291d53eca524ac0d4f06727c Author: Dr. ERDI Gergo Date: Thu Nov 13 17:47:18 2014 +0800 When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments >--------------------------------------------------------------- 7038a5c21915a869291d53eca524ac0d4f06727c compiler/typecheck/TcPatSyn.lhs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 8ba69fd..d6f6817 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -37,7 +37,6 @@ import Data.Monoid import Bag import TcEvidence import BuildTyCl -import TypeRep import Data.Maybe #include "HsVersions.h" @@ -139,7 +138,7 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; let tv_name = mkInternalName uniq (mkTyVarOcc "r") loc ; return $ mkTcTyVar tv_name openTypeKind (SkolemTv False) } ; matcher_name <- newImplicitBinder name mkMatcherOcc - ; let res_ty = TyVarTy res_tv + ; let res_ty = mkTyVarTy res_tv cont_args = if null args then [voidPrimId] else args cont_ty = mkSigmaTy ex_tvs prov_theta $ mkFunTys (map varType cont_args) res_ty @@ -154,7 +153,8 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; scrutinee <- mkId "scrut" pat_ty ; cont <- mkId "cont" cont_ty - ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ cont_args) + ; let cont' = nlHsTyApps cont (map mkTyVarTy ex_tvs) $ + map nlHsVar (prov_dicts ++ cont_args) ; fail <- mkId "fail" fail_ty ; let fail' = nlHsApps fail [nlHsVar voidPrimId] From git at git.haskell.org Thu Nov 13 09:51:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 09:51:14 +0000 (UTC) Subject: [commit: ghc] master: Fix `integer-gmp2` compilation with GMP 4.x (#9281) (63a9d93) Message-ID: <20141113095114.150533A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/63a9d9387f27e5842bed5946c5f1381f209d2918/ghc >--------------------------------------------------------------- commit 63a9d9387f27e5842bed5946c5f1381f209d2918 Author: Herbert Valerio Riedel Date: Thu Nov 13 10:49:43 2014 +0100 Fix `integer-gmp2` compilation with GMP 4.x (#9281) GMP 4.x didn't provide the `mp_bitcnt_t` typedef yet, so we locally define one if GMP 4.x is detected. >--------------------------------------------------------------- 63a9d9387f27e5842bed5946c5f1381f209d2918 libraries/integer-gmp2/cbits/wrappers.c | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/libraries/integer-gmp2/cbits/wrappers.c b/libraries/integer-gmp2/cbits/wrappers.c index ecee592..930f5b8 100644 --- a/libraries/integer-gmp2/cbits/wrappers.c +++ b/libraries/integer-gmp2/cbits/wrappers.c @@ -14,6 +14,15 @@ #include "HsFFI.h" #include "MachDeps.h" +// GMP 4.x compatibility +#if !defined(__GNU_MP_VERSION) +# error __GNU_MP_VERSION not defined +#elif __GNU_MP_VERSION < 4 +# error need GMP 4.0 or later +#elif __GNU_MP_VERSION < 5 +typedef unsigned long int mp_bitcnt_t; +#endif + #if (GMP_NUMB_BITS) != (GMP_LIMB_BITS) # error GMP_NUMB_BITS != GMP_LIMB_BITS not supported #endif From git at git.haskell.org Thu Nov 13 10:53:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 10:53:03 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Binding things matched by an unboxed pattern synonym should require a bang (e70019a) Message-ID: <20141113105303.3FC5F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/e70019a8544beaac9856e7682f7cc1abb3f25664/ghc >--------------------------------------------------------------- commit e70019a8544beaac9856e7682f7cc1abb3f25664 Author: Dr. ERDI Gergo Date: Sat Nov 8 16:59:47 2014 +0800 Binding things matched by an unboxed pattern synonym should require a bang >--------------------------------------------------------------- e70019a8544beaac9856e7682f7cc1abb3f25664 testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/all.T | 2 +- testsuite/tests/patsyn/should_fail/unboxed-bind.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/unboxed-bind.stderr | 6 ++++++ 5 files changed, 28 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index d851bc3..94950a1 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -10,3 +10,4 @@ test('incomplete', normal, compile, ['']) test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) +test('unboxed-bind-bang', normal, compile, ['']) diff --git a/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs new file mode 100644 index 0000000..a972b21 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash, BangPatterns #-} +module ShouldCompile where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let !(P arg) = x in arg diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index ea671dc..ee5768c 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -1,4 +1,3 @@ - test('mono', normal, compile_fail, ['']) test('unidir', normal, compile_fail, ['']) test('local', normal, compile_fail, ['']) @@ -8,3 +7,4 @@ test('T9161-1', normal, compile_fail, ['']) test('T9161-2', normal, compile_fail, ['']) test('T9705-1', normal, compile_fail, ['']) test('T9705-2', normal, compile_fail, ['']) +test('unboxed-bind', normal, compile_fail, ['']) diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.hs b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs new file mode 100644 index 0000000..ef1b070 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module ShouldFail where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let P arg = x in arg diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr new file mode 100644 index 0000000..17ca7af --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr @@ -0,0 +1,6 @@ + +unboxed-bind.hs:10:11: + Pattern bindings containing unlifted types should use an outermost bang pattern: + P arg = x + In the expression: let P arg = x in arg + In an equation for ?f?: f x = let P arg = x in arg From git at git.haskell.org Thu Nov 13 10:53:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 10:53:05 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Fix typo in panic message (0541c85) Message-ID: <20141113105305.C75933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/0541c8585601d726eb898f657b9b6bc8eaa5575d/ghc >--------------------------------------------------------------- commit 0541c8585601d726eb898f657b9b6bc8eaa5575d Author: Dr. ERDI Gergo Date: Thu Nov 6 19:38:40 2014 +0800 Fix typo in panic message >--------------------------------------------------------------- 0541c8585601d726eb898f657b9b6bc8eaa5575d compiler/main/TidyPgm.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs index a975fdd..b7a867d 100644 --- a/compiler/main/TidyPgm.lhs +++ b/compiler/main/TidyPgm.lhs @@ -421,7 +421,7 @@ lookup_aux_id :: TypeEnv -> Var -> Id lookup_aux_id type_env id = case lookupTypeEnv type_env (idName id) of Just (AnId id') -> id' - _other -> pprPanic "lookup_axu_id" (ppr id) + _other -> pprPanic "lookup_aux_id" (ppr id) \end{code} From git at git.haskell.org Thu Nov 13 10:53:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 10:53:08 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Avoid premature unfolding of `seq` (df5ca31) Message-ID: <20141113105308.5585A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/df5ca319629577c2fdfc3dce0b0e9c49ac8f9cdf/ghc >--------------------------------------------------------------- commit df5ca319629577c2fdfc3dce0b0e9c49ac8f9cdf Author: Dr. ERDI Gergo Date: Thu Nov 13 17:39:03 2014 +0800 Avoid premature unfolding of `seq` >--------------------------------------------------------------- df5ca319629577c2fdfc3dce0b0e9c49ac8f9cdf compiler/basicTypes/MkId.lhs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index b32a2b7..738b195 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -1088,7 +1088,7 @@ seqId :: Id -- See Note [seqId magic] seqId = pcMiscPrelId seqName ty info where info = noCafIdInfo `setInlinePragInfo` alwaysInlinePragma - `setUnfoldingInfo` mkCompulsoryUnfolding rhs + `setUnfoldingInfo` mkInlineUnfolding (Just 2) rhs `setSpecInfo` mkSpecInfo [seq_cast_rule] @@ -1097,7 +1097,7 @@ seqId = pcMiscPrelId seqName ty info -- NB argBetaTyVar; see Note [seqId magic] [x,y] = mkTemplateLocals [alphaTy, betaTy] - rhs = mkLams [alphaTyVar,betaTyVar,x,y] (Case (Var x) x betaTy [(DEFAULT, [], Var y)]) + rhs = mkLams [alphaTyVar,openBetaTyVar,x,y] (Case (Var x) x betaTy [(DEFAULT, [], Var y)]) -- See Note [Built-in RULES for seq] seq_cast_rule = BuiltinRule { ru_name = fsLit "seq of cast" From git at git.haskell.org Thu Nov 13 10:53:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 10:53:10 +0000 (UTC) Subject: [commit: ghc] wip/T9732: When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments (ab4762a) Message-ID: <20141113105310.DD49D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/ab4762a15268206bce3a45f662c50d2469ed5b4c/ghc >--------------------------------------------------------------- commit ab4762a15268206bce3a45f662c50d2469ed5b4c Author: Dr. ERDI Gergo Date: Thu Nov 13 17:47:18 2014 +0800 When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments >--------------------------------------------------------------- ab4762a15268206bce3a45f662c50d2469ed5b4c compiler/typecheck/TcPatSyn.lhs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 8ba69fd..d6f6817 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -37,7 +37,6 @@ import Data.Monoid import Bag import TcEvidence import BuildTyCl -import TypeRep import Data.Maybe #include "HsVersions.h" @@ -139,7 +138,7 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; let tv_name = mkInternalName uniq (mkTyVarOcc "r") loc ; return $ mkTcTyVar tv_name openTypeKind (SkolemTv False) } ; matcher_name <- newImplicitBinder name mkMatcherOcc - ; let res_ty = TyVarTy res_tv + ; let res_ty = mkTyVarTy res_tv cont_args = if null args then [voidPrimId] else args cont_ty = mkSigmaTy ex_tvs prov_theta $ mkFunTys (map varType cont_args) res_ty @@ -154,7 +153,8 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; scrutinee <- mkId "scrut" pat_ty ; cont <- mkId "cont" cont_ty - ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ cont_args) + ; let cont' = nlHsTyApps cont (map mkTyVarTy ex_tvs) $ + map nlHsVar (prov_dicts ++ cont_args) ; fail <- mkId "fail" fail_ty ; let fail' = nlHsApps fail [nlHsVar voidPrimId] From git at git.haskell.org Thu Nov 13 10:53:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 10:53:14 +0000 (UTC) Subject: [commit: ghc] wip/T9732: If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. (f82543c) Message-ID: <20141113105314.539203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/f82543cbf83696a6c715ae61b5fd66b663d3ef17/ghc >--------------------------------------------------------------- commit f82543cbf83696a6c715ae61b5fd66b663d3ef17 Author: Dr. ERDI Gergo Date: Sat Nov 8 18:38:12 2014 +0800 If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. >--------------------------------------------------------------- f82543cbf83696a6c715ae61b5fd66b663d3ef17 compiler/basicTypes/PatSyn.lhs | 50 +++++++-- compiler/ghc.mk | 1 + compiler/iface/BuildTyCl.lhs | 2 +- compiler/iface/IfaceSyn.lhs | 10 +- compiler/iface/MkIface.lhs | 4 +- compiler/iface/TcIface.lhs | 62 +++++++++-- compiler/typecheck/TcBinds.lhs | 8 +- compiler/typecheck/TcPatSyn.lhs | 119 +++++++++++---------- compiler/typecheck/TcPatSyn.lhs-boot | 4 +- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_compile/T9732.hs | 4 + testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_fail/all.T | 1 + .../{unboxed-bind.hs => unboxed-wrapper-naked.hs} | 6 +- .../should_fail/unboxed-wrapper-naked.stderr | 3 + testsuite/tests/patsyn/should_run/all.T | 2 + testsuite/tests/patsyn/should_run/match-unboxed.hs | 21 ++++ .../should_run/match-unboxed.stdout} | 2 + .../tests/patsyn/should_run/unboxed-wrapper.hs | 9 ++ .../should_run/unboxed-wrapper.stdout} | 0 20 files changed, 219 insertions(+), 91 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f82543cbf83696a6c715ae61b5fd66b663d3ef17 From git at git.haskell.org Thu Nov 13 10:53:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 10:53:16 +0000 (UTC) Subject: [commit: ghc] wip/T9732: nlHsTyApps: for applying a function both on type- and term-level arguments (249f819) Message-ID: <20141113105316.E00013A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/249f81901e657c7570b0ee1bc34d2f49fe800090/ghc >--------------------------------------------------------------- commit 249f81901e657c7570b0ee1bc34d2f49fe800090 Author: Dr. ERDI Gergo Date: Fri Nov 7 22:49:52 2014 +0800 nlHsTyApps: for applying a function both on type- and term-level arguments >--------------------------------------------------------------- 249f81901e657c7570b0ee1bc34d2f49fe800090 compiler/hsSyn/HsUtils.lhs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/compiler/hsSyn/HsUtils.lhs b/compiler/hsSyn/HsUtils.lhs index 12e2388..df2406f 100644 --- a/compiler/hsSyn/HsUtils.lhs +++ b/compiler/hsSyn/HsUtils.lhs @@ -28,7 +28,7 @@ module HsUtils( mkHsOpApp, mkHsDo, mkHsComp, mkHsWrapPat, mkHsWrapPatCo, mkLHsPar, mkHsCmdCast, - nlHsTyApp, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, + nlHsTyApp, nlHsTyApps, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, nlHsDo, nlHsOpApp, nlHsLam, nlHsPar, nlHsIf, nlHsCase, nlList, mkLHsTupleExpr, mkLHsVarTuple, missingTupArg, toHsType, toHsKind, @@ -177,6 +177,9 @@ mkSimpleHsAlt pat expr nlHsTyApp :: name -> [Type] -> LHsExpr name nlHsTyApp fun_id tys = noLoc (HsWrap (mkWpTyApps tys) (HsVar fun_id)) +nlHsTyApps :: name -> [Type] -> [LHsExpr name] -> LHsExpr name +nlHsTyApps fun_id tys xs = foldl nlHsApp (nlHsTyApp fun_id tys) xs + --------- Adding parens --------- mkLHsPar :: LHsExpr name -> LHsExpr name -- Wrap in parens if hsExprNeedsParens says it needs them From git at git.haskell.org Thu Nov 13 10:53:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 10:53:19 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Apply compulsory unfoldings during desugaring. See Note [Unfolding while desugaring] for the rationale. (4177ccb) Message-ID: <20141113105319.730B13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/4177ccb6e6e2bf2e6b68ea1e6ef1d9cc3569c4fc/ghc >--------------------------------------------------------------- commit 4177ccb6e6e2bf2e6b68ea1e6ef1d9cc3569c4fc Author: Dr. ERDI Gergo Date: Wed Nov 12 18:18:09 2014 +0800 Apply compulsory unfoldings during desugaring. See Note [Unfolding while desugaring] for the rationale. >--------------------------------------------------------------- 4177ccb6e6e2bf2e6b68ea1e6ef1d9cc3569c4fc compiler/deSugar/DsExpr.lhs | 19 ++++++++++++++++++- 1 file changed, 18 insertions(+), 1 deletion(-) diff --git a/compiler/deSugar/DsExpr.lhs b/compiler/deSugar/DsExpr.lhs index 6844f48..10d20d3 100644 --- a/compiler/deSugar/DsExpr.lhs +++ b/compiler/deSugar/DsExpr.lhs @@ -191,7 +191,11 @@ dsLExpr (L loc e) = putSrcSpanDs loc $ dsExpr e dsExpr :: HsExpr Id -> DsM CoreExpr dsExpr (HsPar e) = dsLExpr e dsExpr (ExprWithTySigOut e _) = dsLExpr e -dsExpr (HsVar var) = return (varToCoreExpr var) -- See Note [Desugaring vars] +dsExpr (HsVar var) -- See Note [Unfolding while desugaring] + | isCompulsoryUnfolding unfolding = return $ unfoldingTemplate unfolding + | otherwise = return (varToCoreExpr var) -- See Note [Desugaring vars] + where + unfolding = idUnfolding var dsExpr (HsIPVar _) = panic "dsExpr: HsIPVar" dsExpr (HsLit lit) = dsLit lit dsExpr (HsOverLit lit) = dsOverLit lit @@ -220,6 +224,19 @@ dsExpr (HsApp fun arg) dsExpr (HsUnboundVar _) = panic "dsExpr: HsUnboundVar" \end{code} +Note [Unfolding while desugaring] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Variables with compulsory unfolding must be substituted at desugaring +time. This is needed to preserve the let/app invariant in cases where +the unfolding changes whether wrapping in a case is needed. +Suppose we have a call like this: + I# x +where 'x' has an unfolding like this: + f void# +In this case, 'mkCoreAppDs' needs to see 'f void#', not 'x', to be +able to do the right thing. + + Note [Desugaring vars] ~~~~~~~~~~~~~~~~~~~~~~ In one situation we can get a *coercion* variable in a HsVar, namely From git at git.haskell.org Thu Nov 13 10:53:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 10:53:21 +0000 (UTC) Subject: [commit: ghc] wip/T9732's head updated: When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments (ab4762a) Message-ID: <20141113105321.9F4923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9732' now includes: d70b19b Per-thread allocation counters and limits 4b5d62a Fix build errors on Windows (these tests still don't work though) 8c10b67 fix allocLimit3 on Windows 1d35c85 Test #9066 in th/T9066 d782694 Fix #9066. f61b3c4 Untabify template-haskell. 1d66167 Remove unboxed Int# fields from NameFlavour (#9527) 88a42be Derive Generic for TH types (#9527) 767feb3 Test #8100 in th/T8100 4ac9e90 Fix #8100, by adding StandaloneDerivD to TH's Dec type. fe71a7e Test #9064 in th/T9064 e4efb7b Fix #9064 by adding support for generic default signatures to TH. ec8781f Test #9204 in roles/should_fail/T9204 ee0f34d Fix #9204 by outputting extra info on boot file mismatch. 90a2bb6 Testsuite wibbles due to #9204 294ac47 Fix #9788 by giving `coerce` the right type. e6e45a1 Test #9404 (typecheck/should_compile/T9404 and T9404b) fe6a517 Testsuite wibble due to #9404 1e2002d Fix #9404 by removing tcInfExpr. c65221b includes/Stg.h: define _DEFAULT_SOURCE for glibc-2.20 064c289 Remove a stray Trustworthy flag in ghc. 1f8b4ee Add in `-fwarn-trustworthy-safe` flag. 475dd93 Add `--fwarn-trustworthy-safe` to `-Wall` 8fe2bbe Update userguide for new `-fwarn-trustworthy-safe` flag. 413c747 base: Fix map/coerce comment e73ab54 Make unwords and words fuse somewhat c016e6f base: define `sequence = mapM id` 212a350 Improve `Foldable` instance for `Array` 0541c85 Fix typo in panic message e70019a Binding things matched by an unboxed pattern synonym should require a bang f82543c If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. 4177ccb Apply compulsory unfoldings during desugaring. See Note [Unfolding while desugaring] for the rationale. df5ca31 Avoid premature unfolding of `seq` 249f819 nlHsTyApps: for applying a function both on type- and term-level arguments ab4762a When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments From git at git.haskell.org Thu Nov 13 14:44:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 14:44:42 +0000 (UTC) Subject: [commit: ghc] wip/T9732: When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments (8ad3e26) Message-ID: <20141113144442.A8E783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/8ad3e26c616aeba854321d1e8284528915e2b611/ghc >--------------------------------------------------------------- commit 8ad3e26c616aeba854321d1e8284528915e2b611 Author: Dr. ERDI Gergo Date: Thu Nov 13 17:47:18 2014 +0800 When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments >--------------------------------------------------------------- 8ad3e26c616aeba854321d1e8284528915e2b611 compiler/typecheck/TcPatSyn.lhs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 8ba69fd..d6f6817 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -37,7 +37,6 @@ import Data.Monoid import Bag import TcEvidence import BuildTyCl -import TypeRep import Data.Maybe #include "HsVersions.h" @@ -139,7 +138,7 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; let tv_name = mkInternalName uniq (mkTyVarOcc "r") loc ; return $ mkTcTyVar tv_name openTypeKind (SkolemTv False) } ; matcher_name <- newImplicitBinder name mkMatcherOcc - ; let res_ty = TyVarTy res_tv + ; let res_ty = mkTyVarTy res_tv cont_args = if null args then [voidPrimId] else args cont_ty = mkSigmaTy ex_tvs prov_theta $ mkFunTys (map varType cont_args) res_ty @@ -154,7 +153,8 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; scrutinee <- mkId "scrut" pat_ty ; cont <- mkId "cont" cont_ty - ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ cont_args) + ; let cont' = nlHsTyApps cont (map mkTyVarTy ex_tvs) $ + map nlHsVar (prov_dicts ++ cont_args) ; fail <- mkId "fail" fail_ty ; let fail' = nlHsApps fail [nlHsVar voidPrimId] From git at git.haskell.org Thu Nov 13 14:44:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 14:44:45 +0000 (UTC) Subject: [commit: ghc] wip/T9732: nlHsTyApps: for applying a function both on type- and term-level arguments (a8d3d81) Message-ID: <20141113144445.518BA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/a8d3d81efcef6b3b8209328b7abd1d3af8d7bc88/ghc >--------------------------------------------------------------- commit a8d3d81efcef6b3b8209328b7abd1d3af8d7bc88 Author: Dr. ERDI Gergo Date: Fri Nov 7 22:49:52 2014 +0800 nlHsTyApps: for applying a function both on type- and term-level arguments >--------------------------------------------------------------- a8d3d81efcef6b3b8209328b7abd1d3af8d7bc88 compiler/hsSyn/HsUtils.lhs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/compiler/hsSyn/HsUtils.lhs b/compiler/hsSyn/HsUtils.lhs index 12e2388..df2406f 100644 --- a/compiler/hsSyn/HsUtils.lhs +++ b/compiler/hsSyn/HsUtils.lhs @@ -28,7 +28,7 @@ module HsUtils( mkHsOpApp, mkHsDo, mkHsComp, mkHsWrapPat, mkHsWrapPatCo, mkLHsPar, mkHsCmdCast, - nlHsTyApp, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, + nlHsTyApp, nlHsTyApps, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, nlHsDo, nlHsOpApp, nlHsLam, nlHsPar, nlHsIf, nlHsCase, nlList, mkLHsTupleExpr, mkLHsVarTuple, missingTupArg, toHsType, toHsKind, @@ -177,6 +177,9 @@ mkSimpleHsAlt pat expr nlHsTyApp :: name -> [Type] -> LHsExpr name nlHsTyApp fun_id tys = noLoc (HsWrap (mkWpTyApps tys) (HsVar fun_id)) +nlHsTyApps :: name -> [Type] -> [LHsExpr name] -> LHsExpr name +nlHsTyApps fun_id tys xs = foldl nlHsApp (nlHsTyApp fun_id tys) xs + --------- Adding parens --------- mkLHsPar :: LHsExpr name -> LHsExpr name -- Wrap in parens if hsExprNeedsParens says it needs them From git at git.haskell.org Thu Nov 13 14:44:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 14:44:47 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Avoid premature unfolding of `seq`, and provide a source-level binding in GHC.Magic for cases when it slips through (1804be5) Message-ID: <20141113144447.E7AB63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/1804be5f22de4b08b25efc8d8544f4d1110816b6/ghc >--------------------------------------------------------------- commit 1804be5f22de4b08b25efc8d8544f4d1110816b6 Author: Dr. ERDI Gergo Date: Thu Nov 13 17:39:03 2014 +0800 Avoid premature unfolding of `seq`, and provide a source-level binding in GHC.Magic for cases when it slips through >--------------------------------------------------------------- 1804be5f22de4b08b25efc8d8544f4d1110816b6 compiler/basicTypes/MkId.lhs | 9 ++++----- libraries/base/GHC/Event/IntTable.hs | 2 +- libraries/base/GHC/Exts.hs | 2 +- libraries/ghc-prim/GHC/Magic.hs | 12 +++++++++++- 4 files changed, 17 insertions(+), 8 deletions(-) diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index b32a2b7..8f97d49 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -119,7 +119,7 @@ is right here. \begin{code} wiredInIds :: [Id] wiredInIds - = [lazyId, dollarId, oneShotId] + = [lazyId, dollarId, oneShotId, seqId] ++ errorIds -- Defined in MkCore ++ ghcPrimIds @@ -132,7 +132,6 @@ ghcPrimIds voidPrimId, unsafeCoerceId, nullAddrId, - seqId, magicDictId, coerceId, proxyHashId @@ -1019,7 +1018,7 @@ lazyIdName, unsafeCoerceName, nullAddrName, seqName, magicDictName, coerceName, proxyName, dollarName, oneShotName :: Name unsafeCoerceName = mkWiredInIdName gHC_PRIM (fsLit "unsafeCoerce#") unsafeCoerceIdKey unsafeCoerceId nullAddrName = mkWiredInIdName gHC_PRIM (fsLit "nullAddr#") nullAddrIdKey nullAddrId -seqName = mkWiredInIdName gHC_PRIM (fsLit "seq") seqIdKey seqId +seqName = mkWiredInIdName gHC_MAGIC (fsLit "seq") seqIdKey seqId realWorldName = mkWiredInIdName gHC_PRIM (fsLit "realWorld#") realWorldPrimIdKey realWorldPrimId voidPrimIdName = mkWiredInIdName gHC_PRIM (fsLit "void#") voidPrimIdKey voidPrimId lazyIdName = mkWiredInIdName gHC_MAGIC (fsLit "lazy") lazyIdKey lazyId @@ -1088,7 +1087,7 @@ seqId :: Id -- See Note [seqId magic] seqId = pcMiscPrelId seqName ty info where info = noCafIdInfo `setInlinePragInfo` alwaysInlinePragma - `setUnfoldingInfo` mkCompulsoryUnfolding rhs + `setUnfoldingInfo` mkInlineUnfolding (Just 2) rhs `setSpecInfo` mkSpecInfo [seq_cast_rule] @@ -1097,7 +1096,7 @@ seqId = pcMiscPrelId seqName ty info -- NB argBetaTyVar; see Note [seqId magic] [x,y] = mkTemplateLocals [alphaTy, betaTy] - rhs = mkLams [alphaTyVar,betaTyVar,x,y] (Case (Var x) x betaTy [(DEFAULT, [], Var y)]) + rhs = mkLams [alphaTyVar,openBetaTyVar,x,y] (Case (Var x) x betaTy [(DEFAULT, [], Var y)]) -- See Note [Built-in RULES for seq] seq_cast_rule = BuiltinRule { ru_name = fsLit "seq of cast" diff --git a/libraries/base/GHC/Event/IntTable.hs b/libraries/base/GHC/Event/IntTable.hs index cb76319..dc4485f 100644 --- a/libraries/base/GHC/Event/IntTable.hs +++ b/libraries/base/GHC/Event/IntTable.hs @@ -21,7 +21,7 @@ import GHC.Base (Monad(..), (=<<), ($), const, liftM, otherwise, when) import GHC.Classes (Eq(..), Ord(..)) import GHC.Event.Arr (Arr) import GHC.Num (Num(..)) -import GHC.Prim (seq) +import GHC.Magic (seq) import GHC.Types (Bool(..), IO(..), Int(..)) import qualified GHC.Event.Arr as Arr diff --git a/libraries/base/GHC/Exts.hs b/libraries/base/GHC/Exts.hs index 6754edc..c536021 100755 --- a/libraries/base/GHC/Exts.hs +++ b/libraries/base/GHC/Exts.hs @@ -44,7 +44,7 @@ module GHC.Exts breakpoint, breakpointCond, -- * Ids with special behaviour - lazy, inline, + lazy, inline, seq, -- * Safe coercions -- diff --git a/libraries/ghc-prim/GHC/Magic.hs b/libraries/ghc-prim/GHC/Magic.hs index 1a6af92..37d0cb2 100644 --- a/libraries/ghc-prim/GHC/Magic.hs +++ b/libraries/ghc-prim/GHC/Magic.hs @@ -17,7 +17,9 @@ -- ----------------------------------------------------------------------------- -module GHC.Magic ( inline, lazy, oneShot ) where +module GHC.Magic ( inline, lazy, oneShot, seq ) where + +infixr 0 `seq` -- | The call @inline f@ arranges that 'f' is inlined, regardless of -- its size. More precisely, the call @inline f@ rewrites to the @@ -73,3 +75,11 @@ oneShot :: (a -> b) -> (a -> b) oneShot f = f -- Implementation note: This is wired in in MkId.lhs, so the code here is -- mostly there to have a place for the documentation. + +-- | The 'seq' function forces evaluation of its first argument to WHNF +-- and returns its second argument unchanged. +seq :: a -> b -> b +seq x y = seq x y +-- Implementation note: This is wired in in MkId.lhs, so the code here is +-- mostly there to have a place for the documentation, and to have a fallback +-- when seq fails to be unfolded in a call From git at git.haskell.org Thu Nov 13 15:13:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 15:13:00 +0000 (UTC) Subject: [commit: ghc] wip/T9732: If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. Fixes #9732. (06a167b) Message-ID: <20141113151300.5292F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/06a167b164e1c2ba58a14e65f4eeff231371bedc/ghc >--------------------------------------------------------------- commit 06a167b164e1c2ba58a14e65f4eeff231371bedc Author: Dr. ERDI Gergo Date: Sat Nov 8 18:38:12 2014 +0800 If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. Fixes #9732. >--------------------------------------------------------------- 06a167b164e1c2ba58a14e65f4eeff231371bedc compiler/basicTypes/PatSyn.lhs | 50 +++++++-- compiler/ghc.mk | 1 + compiler/iface/BuildTyCl.lhs | 2 +- compiler/iface/IfaceSyn.lhs | 10 +- compiler/iface/MkIface.lhs | 4 +- compiler/iface/TcIface.lhs | 62 +++++++++-- compiler/typecheck/TcBinds.lhs | 8 +- compiler/typecheck/TcPatSyn.lhs | 119 +++++++++++---------- compiler/typecheck/TcPatSyn.lhs-boot | 4 +- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_compile/T9732.hs | 4 + testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_fail/all.T | 1 + .../{unboxed-bind.hs => unboxed-wrapper-naked.hs} | 6 +- .../should_fail/unboxed-wrapper-naked.stderr | 3 + testsuite/tests/patsyn/should_run/all.T | 2 + testsuite/tests/patsyn/should_run/match-unboxed.hs | 21 ++++ .../should_run/match-unboxed.stdout} | 2 + .../tests/patsyn/should_run/unboxed-wrapper.hs | 9 ++ .../should_run/unboxed-wrapper.stdout} | 0 20 files changed, 219 insertions(+), 91 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 06a167b164e1c2ba58a14e65f4eeff231371bedc From git at git.haskell.org Thu Nov 13 15:13:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 15:13:02 +0000 (UTC) Subject: [commit: ghc] wip/T9732: nlHsTyApps: for applying a function both on type- and term-level arguments (a78ef85) Message-ID: <20141113151302.E65533A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/a78ef85fff5e581b1312a3aa5c60b27906e805f7/ghc >--------------------------------------------------------------- commit a78ef85fff5e581b1312a3aa5c60b27906e805f7 Author: Dr. ERDI Gergo Date: Fri Nov 7 22:49:52 2014 +0800 nlHsTyApps: for applying a function both on type- and term-level arguments >--------------------------------------------------------------- a78ef85fff5e581b1312a3aa5c60b27906e805f7 compiler/hsSyn/HsUtils.lhs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/compiler/hsSyn/HsUtils.lhs b/compiler/hsSyn/HsUtils.lhs index 12e2388..df2406f 100644 --- a/compiler/hsSyn/HsUtils.lhs +++ b/compiler/hsSyn/HsUtils.lhs @@ -28,7 +28,7 @@ module HsUtils( mkHsOpApp, mkHsDo, mkHsComp, mkHsWrapPat, mkHsWrapPatCo, mkLHsPar, mkHsCmdCast, - nlHsTyApp, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, + nlHsTyApp, nlHsTyApps, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, nlHsDo, nlHsOpApp, nlHsLam, nlHsPar, nlHsIf, nlHsCase, nlList, mkLHsTupleExpr, mkLHsVarTuple, missingTupArg, toHsType, toHsKind, @@ -177,6 +177,9 @@ mkSimpleHsAlt pat expr nlHsTyApp :: name -> [Type] -> LHsExpr name nlHsTyApp fun_id tys = noLoc (HsWrap (mkWpTyApps tys) (HsVar fun_id)) +nlHsTyApps :: name -> [Type] -> [LHsExpr name] -> LHsExpr name +nlHsTyApps fun_id tys xs = foldl nlHsApp (nlHsTyApp fun_id tys) xs + --------- Adding parens --------- mkLHsPar :: LHsExpr name -> LHsExpr name -- Wrap in parens if hsExprNeedsParens says it needs them From git at git.haskell.org Thu Nov 13 15:13:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 15:13:05 +0000 (UTC) Subject: [commit: ghc] wip/T9732: When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments (de3d584) Message-ID: <20141113151305.95AAB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/de3d584ea43f0f280c5f8fb3d00184a9ffa68a60/ghc >--------------------------------------------------------------- commit de3d584ea43f0f280c5f8fb3d00184a9ffa68a60 Author: Dr. ERDI Gergo Date: Thu Nov 13 17:47:18 2014 +0800 When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments >--------------------------------------------------------------- de3d584ea43f0f280c5f8fb3d00184a9ffa68a60 compiler/typecheck/TcPatSyn.lhs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 8ba69fd..d6f6817 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -37,7 +37,6 @@ import Data.Monoid import Bag import TcEvidence import BuildTyCl -import TypeRep import Data.Maybe #include "HsVersions.h" @@ -139,7 +138,7 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; let tv_name = mkInternalName uniq (mkTyVarOcc "r") loc ; return $ mkTcTyVar tv_name openTypeKind (SkolemTv False) } ; matcher_name <- newImplicitBinder name mkMatcherOcc - ; let res_ty = TyVarTy res_tv + ; let res_ty = mkTyVarTy res_tv cont_args = if null args then [voidPrimId] else args cont_ty = mkSigmaTy ex_tvs prov_theta $ mkFunTys (map varType cont_args) res_ty @@ -154,7 +153,8 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; scrutinee <- mkId "scrut" pat_ty ; cont <- mkId "cont" cont_ty - ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ cont_args) + ; let cont' = nlHsTyApps cont (map mkTyVarTy ex_tvs) $ + map nlHsVar (prov_dicts ++ cont_args) ; fail <- mkId "fail" fail_ty ; let fail' = nlHsApps fail [nlHsVar voidPrimId] From git at git.haskell.org Thu Nov 13 15:13:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 15:13:08 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Apply compulsory unfoldings during desugaring, except for `seq` which is special. See Note [Unfolding while desugaring] for the rationale. (95eb232) Message-ID: <20141113151308.3264B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/95eb2321d5ca9e021eaff1e0494ae3770d4934ef/ghc >--------------------------------------------------------------- commit 95eb2321d5ca9e021eaff1e0494ae3770d4934ef Author: Dr. ERDI Gergo Date: Wed Nov 12 18:18:09 2014 +0800 Apply compulsory unfoldings during desugaring, except for `seq` which is special. See Note [Unfolding while desugaring] for the rationale. >--------------------------------------------------------------- 95eb2321d5ca9e021eaff1e0494ae3770d4934ef compiler/deSugar/DsExpr.lhs | 22 +++++++++++++++++++++- 1 file changed, 21 insertions(+), 1 deletion(-) diff --git a/compiler/deSugar/DsExpr.lhs b/compiler/deSugar/DsExpr.lhs index 6844f48..ce2d5a5 100644 --- a/compiler/deSugar/DsExpr.lhs +++ b/compiler/deSugar/DsExpr.lhs @@ -46,12 +46,14 @@ import MkCore import DynFlags import CostCentre import Id +import Unique import Module import VarSet import VarEnv import ConLike import DataCon import TysWiredIn +import PrelNames ( seqIdKey ) import BasicTypes import Maybes import SrcLoc @@ -191,7 +193,12 @@ dsLExpr (L loc e) = putSrcSpanDs loc $ dsExpr e dsExpr :: HsExpr Id -> DsM CoreExpr dsExpr (HsPar e) = dsLExpr e dsExpr (ExprWithTySigOut e _) = dsLExpr e -dsExpr (HsVar var) = return (varToCoreExpr var) -- See Note [Desugaring vars] +dsExpr (HsVar var) -- See Note [Unfolding while desugaring] + | unfold_var = return $ unfoldingTemplate unfolding + | otherwise = return (varToCoreExpr var) -- See Note [Desugaring vars] + where + unfold_var = isCompulsoryUnfolding unfolding && not (var `hasKey` seqIdKey) + unfolding = idUnfolding var dsExpr (HsIPVar _) = panic "dsExpr: HsIPVar" dsExpr (HsLit lit) = dsLit lit dsExpr (HsOverLit lit) = dsOverLit lit @@ -220,6 +227,19 @@ dsExpr (HsApp fun arg) dsExpr (HsUnboundVar _) = panic "dsExpr: HsUnboundVar" \end{code} +Note [Unfolding while desugaring] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Variables with compulsory unfolding must be substituted at desugaring +time. This is needed to preserve the let/app invariant in cases where +the unfolding changes whether wrapping in a case is needed. +Suppose we have a call like this: + I# x +where 'x' has an unfolding like this: + f void# +In this case, 'mkCoreAppDs' needs to see 'f void#', not 'x', to be +able to do the right thing. + + Note [Desugaring vars] ~~~~~~~~~~~~~~~~~~~~~~ In one situation we can get a *coercion* variable in a HsVar, namely From git at git.haskell.org Thu Nov 13 15:41:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 15:41:06 +0000 (UTC) Subject: [commit: ghc] master: If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. Fixes #9732. (7f92986) Message-ID: <20141113154106.F04553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7f929862388afd54043d59b37f2f5375c5315344/ghc >--------------------------------------------------------------- commit 7f929862388afd54043d59b37f2f5375c5315344 Author: Dr. ERDI Gergo Date: Sat Nov 8 18:38:12 2014 +0800 If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. Fixes #9732. >--------------------------------------------------------------- 7f929862388afd54043d59b37f2f5375c5315344 compiler/basicTypes/PatSyn.lhs | 50 +++++++-- compiler/ghc.mk | 1 + compiler/iface/BuildTyCl.lhs | 2 +- compiler/iface/IfaceSyn.lhs | 10 +- compiler/iface/MkIface.lhs | 4 +- compiler/iface/TcIface.lhs | 62 +++++++++-- compiler/typecheck/TcBinds.lhs | 8 +- compiler/typecheck/TcPatSyn.lhs | 119 +++++++++++---------- compiler/typecheck/TcPatSyn.lhs-boot | 4 +- testsuite/.gitignore | 1 + testsuite/tests/patsyn/should_compile/T9732.hs | 4 + testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_fail/all.T | 1 + .../{unboxed-bind.hs => unboxed-wrapper-naked.hs} | 6 +- .../should_fail/unboxed-wrapper-naked.stderr | 3 + testsuite/tests/patsyn/should_run/all.T | 2 + testsuite/tests/patsyn/should_run/match-unboxed.hs | 21 ++++ .../should_run/match-unboxed.stdout} | 2 + .../tests/patsyn/should_run/unboxed-wrapper.hs | 9 ++ .../should_run/unboxed-wrapper.stdout} | 0 20 files changed, 219 insertions(+), 91 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7f929862388afd54043d59b37f2f5375c5315344 From git at git.haskell.org Thu Nov 13 15:41:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 15:41:10 +0000 (UTC) Subject: [commit: ghc] master: Binding things matched by an unboxed pattern synonym should require a bang (745c4c0) Message-ID: <20141113154110.0A9E13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/745c4c0e04168ce2eac1e8f81a45326ecef401e4/ghc >--------------------------------------------------------------- commit 745c4c0e04168ce2eac1e8f81a45326ecef401e4 Author: Dr. ERDI Gergo Date: Sat Nov 8 16:59:47 2014 +0800 Binding things matched by an unboxed pattern synonym should require a bang >--------------------------------------------------------------- 745c4c0e04168ce2eac1e8f81a45326ecef401e4 testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/all.T | 2 +- testsuite/tests/patsyn/should_fail/unboxed-bind.hs | 10 ++++++++++ testsuite/tests/patsyn/should_fail/unboxed-bind.stderr | 6 ++++++ 5 files changed, 28 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index d851bc3..94950a1 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -10,3 +10,4 @@ test('incomplete', normal, compile, ['']) test('export', normal, compile, ['']) test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) +test('unboxed-bind-bang', normal, compile, ['']) diff --git a/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs new file mode 100644 index 0000000..a972b21 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/unboxed-bind-bang.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash, BangPatterns #-} +module ShouldCompile where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let !(P arg) = x in arg diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index ea671dc..ee5768c 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -1,4 +1,3 @@ - test('mono', normal, compile_fail, ['']) test('unidir', normal, compile_fail, ['']) test('local', normal, compile_fail, ['']) @@ -8,3 +7,4 @@ test('T9161-1', normal, compile_fail, ['']) test('T9161-2', normal, compile_fail, ['']) test('T9705-1', normal, compile_fail, ['']) test('T9705-2', normal, compile_fail, ['']) +test('unboxed-bind', normal, compile_fail, ['']) diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.hs b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs new file mode 100644 index 0000000..ef1b070 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +module ShouldFail where + +import GHC.Base + +data Foo = MkFoo Int# Int# + +pattern P x = MkFoo 0# x + +f x = let P arg = x in arg diff --git a/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr new file mode 100644 index 0000000..17ca7af --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr @@ -0,0 +1,6 @@ + +unboxed-bind.hs:10:11: + Pattern bindings containing unlifted types should use an outermost bang pattern: + P arg = x + In the expression: let P arg = x in arg + In an equation for ?f?: f x = let P arg = x in arg From git at git.haskell.org Thu Nov 13 15:41:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 15:41:12 +0000 (UTC) Subject: [commit: ghc] master: Apply compulsory unfoldings during desugaring, except for `seq` which is special. See Note [Unfolding while desugaring] for the rationale. (5fe872d) Message-ID: <20141113154112.A68A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5fe872d3bc2d03976fb89b5659e14d2179210ee1/ghc >--------------------------------------------------------------- commit 5fe872d3bc2d03976fb89b5659e14d2179210ee1 Author: Dr. ERDI Gergo Date: Wed Nov 12 18:18:09 2014 +0800 Apply compulsory unfoldings during desugaring, except for `seq` which is special. See Note [Unfolding while desugaring] for the rationale. >--------------------------------------------------------------- 5fe872d3bc2d03976fb89b5659e14d2179210ee1 compiler/deSugar/DsExpr.lhs | 22 +++++++++++++++++++++- 1 file changed, 21 insertions(+), 1 deletion(-) diff --git a/compiler/deSugar/DsExpr.lhs b/compiler/deSugar/DsExpr.lhs index 6844f48..ce2d5a5 100644 --- a/compiler/deSugar/DsExpr.lhs +++ b/compiler/deSugar/DsExpr.lhs @@ -46,12 +46,14 @@ import MkCore import DynFlags import CostCentre import Id +import Unique import Module import VarSet import VarEnv import ConLike import DataCon import TysWiredIn +import PrelNames ( seqIdKey ) import BasicTypes import Maybes import SrcLoc @@ -191,7 +193,12 @@ dsLExpr (L loc e) = putSrcSpanDs loc $ dsExpr e dsExpr :: HsExpr Id -> DsM CoreExpr dsExpr (HsPar e) = dsLExpr e dsExpr (ExprWithTySigOut e _) = dsLExpr e -dsExpr (HsVar var) = return (varToCoreExpr var) -- See Note [Desugaring vars] +dsExpr (HsVar var) -- See Note [Unfolding while desugaring] + | unfold_var = return $ unfoldingTemplate unfolding + | otherwise = return (varToCoreExpr var) -- See Note [Desugaring vars] + where + unfold_var = isCompulsoryUnfolding unfolding && not (var `hasKey` seqIdKey) + unfolding = idUnfolding var dsExpr (HsIPVar _) = panic "dsExpr: HsIPVar" dsExpr (HsLit lit) = dsLit lit dsExpr (HsOverLit lit) = dsOverLit lit @@ -220,6 +227,19 @@ dsExpr (HsApp fun arg) dsExpr (HsUnboundVar _) = panic "dsExpr: HsUnboundVar" \end{code} +Note [Unfolding while desugaring] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Variables with compulsory unfolding must be substituted at desugaring +time. This is needed to preserve the let/app invariant in cases where +the unfolding changes whether wrapping in a case is needed. +Suppose we have a call like this: + I# x +where 'x' has an unfolding like this: + f void# +In this case, 'mkCoreAppDs' needs to see 'f void#', not 'x', to be +able to do the right thing. + + Note [Desugaring vars] ~~~~~~~~~~~~~~~~~~~~~~ In one situation we can get a *coercion* variable in a HsVar, namely From git at git.haskell.org Thu Nov 13 15:41:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 15:41:15 +0000 (UTC) Subject: [commit: ghc] master: nlHsTyApps: for applying a function both on type- and term-level arguments (faeb0a6) Message-ID: <20141113154115.4F10F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/faeb0a687ea291cb2d497a7042af4829f55e223d/ghc >--------------------------------------------------------------- commit faeb0a687ea291cb2d497a7042af4829f55e223d Author: Dr. ERDI Gergo Date: Fri Nov 7 22:49:52 2014 +0800 nlHsTyApps: for applying a function both on type- and term-level arguments >--------------------------------------------------------------- faeb0a687ea291cb2d497a7042af4829f55e223d compiler/hsSyn/HsUtils.lhs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/compiler/hsSyn/HsUtils.lhs b/compiler/hsSyn/HsUtils.lhs index 12e2388..df2406f 100644 --- a/compiler/hsSyn/HsUtils.lhs +++ b/compiler/hsSyn/HsUtils.lhs @@ -28,7 +28,7 @@ module HsUtils( mkHsOpApp, mkHsDo, mkHsComp, mkHsWrapPat, mkHsWrapPatCo, mkLHsPar, mkHsCmdCast, - nlHsTyApp, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, + nlHsTyApp, nlHsTyApps, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, nlHsDo, nlHsOpApp, nlHsLam, nlHsPar, nlHsIf, nlHsCase, nlList, mkLHsTupleExpr, mkLHsVarTuple, missingTupArg, toHsType, toHsKind, @@ -177,6 +177,9 @@ mkSimpleHsAlt pat expr nlHsTyApp :: name -> [Type] -> LHsExpr name nlHsTyApp fun_id tys = noLoc (HsWrap (mkWpTyApps tys) (HsVar fun_id)) +nlHsTyApps :: name -> [Type] -> [LHsExpr name] -> LHsExpr name +nlHsTyApps fun_id tys xs = foldl nlHsApp (nlHsTyApp fun_id tys) xs + --------- Adding parens --------- mkLHsPar :: LHsExpr name -> LHsExpr name -- Wrap in parens if hsExprNeedsParens says it needs them From git at git.haskell.org Thu Nov 13 15:41:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 15:41:17 +0000 (UTC) Subject: [commit: ghc] master: When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments (6389911) Message-ID: <20141113154117.ED69D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/638991114f9358ee78f32d5d5c98bb3001b52ec9/ghc >--------------------------------------------------------------- commit 638991114f9358ee78f32d5d5c98bb3001b52ec9 Author: Dr. ERDI Gergo Date: Thu Nov 13 17:47:18 2014 +0800 When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments >--------------------------------------------------------------- 638991114f9358ee78f32d5d5c98bb3001b52ec9 compiler/typecheck/TcPatSyn.lhs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 8ba69fd..d6f6817 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -37,7 +37,6 @@ import Data.Monoid import Bag import TcEvidence import BuildTyCl -import TypeRep import Data.Maybe #include "HsVersions.h" @@ -139,7 +138,7 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; let tv_name = mkInternalName uniq (mkTyVarOcc "r") loc ; return $ mkTcTyVar tv_name openTypeKind (SkolemTv False) } ; matcher_name <- newImplicitBinder name mkMatcherOcc - ; let res_ty = TyVarTy res_tv + ; let res_ty = mkTyVarTy res_tv cont_args = if null args then [voidPrimId] else args cont_ty = mkSigmaTy ex_tvs prov_theta $ mkFunTys (map varType cont_args) res_ty @@ -154,7 +153,8 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; scrutinee <- mkId "scrut" pat_ty ; cont <- mkId "cont" cont_ty - ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ cont_args) + ; let cont' = nlHsTyApps cont (map mkTyVarTy ex_tvs) $ + map nlHsVar (prov_dicts ++ cont_args) ; fail <- mkId "fail" fail_ty ; let fail' = nlHsApps fail [nlHsVar voidPrimId] From git at git.haskell.org Thu Nov 13 15:41:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 15:41:20 +0000 (UTC) Subject: [commit: ghc] master: Fix typo in panic message (9b30d9d) Message-ID: <20141113154120.937D03A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9b30d9de12c4450149e5b06218e248be3d5c3dff/ghc >--------------------------------------------------------------- commit 9b30d9de12c4450149e5b06218e248be3d5c3dff Author: Dr. ERDI Gergo Date: Thu Nov 6 19:38:40 2014 +0800 Fix typo in panic message >--------------------------------------------------------------- 9b30d9de12c4450149e5b06218e248be3d5c3dff compiler/main/TidyPgm.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs index a975fdd..b7a867d 100644 --- a/compiler/main/TidyPgm.lhs +++ b/compiler/main/TidyPgm.lhs @@ -421,7 +421,7 @@ lookup_aux_id :: TypeEnv -> Var -> Id lookup_aux_id type_env id = case lookupTypeEnv type_env (idName id) of Just (AnId id') -> id' - _other -> pprPanic "lookup_axu_id" (ppr id) + _other -> pprPanic "lookup_aux_id" (ppr id) \end{code} From git at git.haskell.org Thu Nov 13 20:15:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Nov 2014 20:15:57 +0000 (UTC) Subject: [commit: ghc] master: Implement amap/coerce for Array (re #9796) (603b7be) Message-ID: <20141113201557.73BCD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/603b7be7bd3abaf0e2c210e8d9015b1d613b4715/ghc >--------------------------------------------------------------- commit 603b7be7bd3abaf0e2c210e8d9015b1d613b4715 Author: David Feuer Date: Thu Nov 13 21:12:05 2014 +0100 Implement amap/coerce for Array (re #9796) Implement an `amap`/`coerce` rule in `GHC.Arr` to match the `map`/`coerce` rule in GHC.Base. In order to do so, delay inlining `amap` until phase 1. To prevent the inlining delay from causing major inefficiencies due to missed list fusion, rewrite `amap` to avoid relying on list fusion. This has the extra benefit of reducing the size of the compiled amap code by skipping the impossible case of an array with a negative size. Reviewed By: nomeata Differential Revision: https://phabricator.haskell.org/D471 >--------------------------------------------------------------- 603b7be7bd3abaf0e2c210e8d9015b1d613b4715 libraries/base/GHC/Arr.hs | 40 ++++++++++++++++++++-- .../should_run/{T2110.hs => AmapCoerce.hs} | 15 ++++---- .../should_run/{T2110.stdout => AmapCoerce.stdout} | 0 testsuite/tests/simplCore/should_run/all.T | 1 + 4 files changed, 46 insertions(+), 10 deletions(-) diff --git a/libraries/base/GHC/Arr.hs b/libraries/base/GHC/Arr.hs index 67702ea..02bf7d8 100644 --- a/libraries/base/GHC/Arr.hs +++ b/libraries/base/GHC/Arr.hs @@ -704,10 +704,44 @@ unsafeAccum f arr ies = runST (do STArray l u n marr# <- thawSTArray arr ST (foldr (adjust f marr#) (done l u n marr#) ies)) -{-# INLINE amap #-} +{-# INLINE [1] amap #-} amap :: Ix i => (a -> b) -> Array i a -> Array i b -amap f arr@(Array l u n _) = - unsafeArray' (l,u) n [(i, f (unsafeAt arr i)) | i <- [0 .. n - 1]] +amap f arr@(Array l u n@(I# n#) _) = runST (ST $ \s1# -> + case newArray# n# arrEleBottom s1# of + (# s2#, marr# #) -> + let go i s# + | i == n = done l u n marr# s# + | otherwise = fill marr# (i, f (unsafeAt arr i)) (go (i+1)) s# + in go 0 s2# ) + +{- +amap was originally defined like this: + + amap f arr@(Array l u n _) = + unsafeArray' (l,u) n [(i, f (unsafeAt arr i)) | i <- [0 .. n - 1]] + +There are two problems: + +1. The enumFromTo implementation produces (spurious) code for the impossible +case of n<0 that ends up duplicating the array freezing code. + +2. This implementation relies on list fusion for efficiency. In order to +implement the amap/coerce rule, we need to delay inlining amap until simplifier +phase 1, which is when the eftIntList rule kicks in and makes that impossible. +-} + + +-- See Breitner, Eisenberg, Peyton Jones, and Weirich, "Safe Zero-cost +-- Coercions for Haskell", section 6.5: +-- http://research.microsoft.com/en-us/um/people/simonpj/papers/ext-f/coercible.pdf +{-# RULES +"amap/coerce" amap coerce = coerce + #-} + +-- Second functor law: +{-# RULES +"amap/amap" forall f g a . amap f (amap g a) = amap (f . g) a + #-} -- | 'ixmap' allows for transformations on array indices. -- It may be thought of as providing function composition on the right diff --git a/testsuite/tests/simplCore/should_run/T2110.hs b/testsuite/tests/simplCore/should_run/AmapCoerce.hs similarity index 54% copy from testsuite/tests/simplCore/should_run/T2110.hs copy to testsuite/tests/simplCore/should_run/AmapCoerce.hs index 610be09..01a9a5d 100644 --- a/testsuite/tests/simplCore/should_run/T2110.hs +++ b/testsuite/tests/simplCore/should_run/AmapCoerce.hs @@ -2,15 +2,16 @@ import GHC.Exts import Unsafe.Coerce +import Data.Array newtype Age = Age Int -fooAge :: [Int] -> [Age] -fooAge = map Age -fooCoerce :: [Int] -> [Age] -fooCoerce = map coerce -fooUnsafeCoerce :: [Int] -> [Age] -fooUnsafeCoerce = map unsafeCoerce +fooAge :: Array Int Int -> Array Int Age +fooAge = fmap Age +fooCoerce :: Array Int Int -> Array Int Age +fooCoerce = fmap coerce +fooUnsafeCoerce :: Array Int Int -> Array Int Age +fooUnsafeCoerce = fmap unsafeCoerce same :: a -> b -> IO () same x y = case reallyUnsafePtrEquality# (unsafeCoerce x) y of @@ -18,7 +19,7 @@ same x y = case reallyUnsafePtrEquality# (unsafeCoerce x) y of _ -> putStrLn "no" main = do - let l = [1,2,3] + let l = listArray (1,3) [1,2,3] same (fooAge l) l same (fooCoerce l) l same (fooUnsafeCoerce l) l diff --git a/testsuite/tests/simplCore/should_run/T2110.stdout b/testsuite/tests/simplCore/should_run/AmapCoerce.stdout similarity index 100% copy from testsuite/tests/simplCore/should_run/T2110.stdout copy to testsuite/tests/simplCore/should_run/AmapCoerce.stdout diff --git a/testsuite/tests/simplCore/should_run/all.T b/testsuite/tests/simplCore/should_run/all.T index 93dc4c6..364dfd6 100644 --- a/testsuite/tests/simplCore/should_run/all.T +++ b/testsuite/tests/simplCore/should_run/all.T @@ -53,6 +53,7 @@ test('T5441', extra_clean(['T5441a.o','T5441a.hi']), multimod_compile_and_run, ['T5441','']) test('T5603', normal, compile_and_run, ['']) test('T2110', normal, compile_and_run, ['']) +test('AmapCoerce', normal, compile_and_run, ['']) # Run these tests *without* optimisation too test('T5625', [ only_ways(['normal','optasm']), exit_code(1) ], compile_and_run, ['']) From git at git.haskell.org Fri Nov 14 09:36:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 09:36:48 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Update baseline shift/reduce conflict number (42d491a) Message-ID: <20141114093648.8477D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/42d491af1f6e33a5cc0adecef59fcce41c7bb2fa/ghc >--------------------------------------------------------------- commit 42d491af1f6e33a5cc0adecef59fcce41c7bb2fa Author: Dr. ERDI Gergo Date: Wed Jul 2 19:18:43 2014 +0800 Update baseline shift/reduce conflict number >--------------------------------------------------------------- 42d491af1f6e33a5cc0adecef59fcce41c7bb2fa compiler/parser/Parser.y | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 2e1b777..1123375 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -86,6 +86,12 @@ import TysWiredIn ( unitTyCon, unitDataCon, tupleTyCon, tupleCon, nilDataC {- ----------------------------------------------------------------------------- +25 June 2014 + +Conflicts: 47 shift/reduce + 1 reduce/reduce + +----------------------------------------------------------------------------- 12 October 2012 Conflicts: 43 shift/reduce From git at git.haskell.org Fri Nov 14 09:36:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 09:36:51 +0000 (UTC) Subject: [commit: ghc] wip/T8584: tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures (c27e81a) Message-ID: <20141114093651.2A8683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/c27e81a416d6d7d328eb71b06c0b4816c98b2f27/ghc >--------------------------------------------------------------- commit c27e81a416d6d7d328eb71b06c0b4816c98b2f27 Author: Dr. ERDI Gergo Date: Fri Nov 7 19:29:06 2014 +0800 tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures >--------------------------------------------------------------- c27e81a416d6d7d328eb71b06c0b4816c98b2f27 compiler/hsSyn/HsBinds.lhs | 51 ++++----- compiler/hsSyn/HsTypes.lhs | 16 +-- compiler/iface/IfaceSyn.lhs | 21 ++-- compiler/iface/IfaceType.lhs | 15 ++- compiler/rename/RnBinds.lhs | 34 +++--- compiler/typecheck/TcBinds.lhs | 50 +++++++-- compiler/typecheck/TcClassDcl.lhs | 4 +- compiler/typecheck/TcPat.lhs | 23 ++++- compiler/typecheck/TcPatSyn.lhs | 195 ++++++++++++++++++++++++++--------- compiler/typecheck/TcPatSyn.lhs-boot | 9 +- 10 files changed, 281 insertions(+), 137 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c27e81a416d6d7d328eb71b06c0b4816c98b2f27 From git at git.haskell.org Fri Nov 14 09:36:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 09:36:53 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Use user-supplied type variables (when available) in pattern synonym type signatures (2b160b4) Message-ID: <20141114093653.B3BFD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/2b160b4464750569711cffef742cc85feadfa22a/ghc >--------------------------------------------------------------- commit 2b160b4464750569711cffef742cc85feadfa22a Author: Dr. ERDI Gergo Date: Sun Nov 9 15:46:46 2014 +0800 Use user-supplied type variables (when available) in pattern synonym type signatures >--------------------------------------------------------------- 2b160b4464750569711cffef742cc85feadfa22a compiler/rename/RnBinds.lhs | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index b43993e..80239e9 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -846,8 +846,16 @@ renameSig ctxt sig@(PatSynSig v (flag, qtvs) prov req ty) ; let doc = TypeSigCtx $ quotes (ppr v) ; loc <- getSrcSpanM - ; let (tv_kvs, tvs) = extractHsTysRdrTyVars (ty:unLoc prov ++ unLoc req) - ; let tv_bndrs = mkHsQTvs . userHsTyVarBndrs loc $ tvs + ; let (tv_kvs, mentioned) = extractHsTysRdrTyVars (ty:unLoc prov ++ unLoc req) + ; tv_bndrs <- case flag of + Implicit -> + return $ mkHsQTvs . userHsTyVarBndrs loc $ mentioned + Explicit -> + do { let heading = ptext (sLit "In the pattern synonym type signature") + <+> quotes (ppr sig) + ; warnUnusedForAlls (heading $$ docOfHsDocContext doc) qtvs mentioned + ; return qtvs } + Qualified -> panic "renameSig: Qualified" ; bindHsTyVars doc Nothing tv_kvs tv_bndrs $ \ tyvars -> do { (prov', fvs1) <- rnContext doc prov From git at git.haskell.org Fri Nov 14 09:36:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 09:36:56 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add parser for pattern synonym type signatures. Syntax is of the form (935f931) Message-ID: <20141114093656.4B0053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/935f93128152973b7ae0ed9ddd96f6d563a9deff/ghc >--------------------------------------------------------------- commit 935f93128152973b7ae0ed9ddd96f6d563a9deff Author: Dr. ERDI Gergo Date: Tue Nov 11 18:54:14 2014 +0800 Add parser for pattern synonym type signatures. Syntax is of the form pattern P :: (Prov b) => (Req a) => a -> b -> Int -> T a which declares a pattern synonym called `P`, with argument types `a`, `b`, and `Int`, and result type `T a`, with provided context `(Prov b)` and required context `(Req a)`. >--------------------------------------------------------------- 935f93128152973b7ae0ed9ddd96f6d563a9deff compiler/parser/Parser.y | 51 +++++++++++++++++++++++++++++++-------------- compiler/parser/RdrHsSyn.hs | 27 +++++------------------- 2 files changed, 40 insertions(+), 38 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 1123375..0cceb09 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -860,29 +860,47 @@ role : VARID { sL1 $1 $ Just $ getVARID $1 } -- Glasgow extension: pattern synonyms pattern_synonym_decl :: { LHsDecl RdrName } - : 'pattern' pat '=' pat - {% do { (name, args) <- splitPatSyn $2 - ; return $ sLL $1 $> . ValD $ mkPatSynBind name args $4 ImplicitBidirectional - }} - | 'pattern' pat '<-' pat - {% do { (name, args) <- splitPatSyn $2 - ; return $ sLL $1 $> . ValD $ mkPatSynBind name args $4 Unidirectional - }} - | 'pattern' pat '<-' pat where_decls - {% do { (name, args) <- splitPatSyn $2 - ; mg <- toPatSynMatchGroup name $5 + : 'pattern' pattern_synonym_lhs '=' pat + { let (name, args) = $2 + in sLL $1 $> . ValD $ mkPatSynBind name args $4 ImplicitBidirectional } + | 'pattern' pattern_synonym_lhs '<-' pat + { let (name, args) = $2 + in sLL $1 $> . ValD $ mkPatSynBind name args $4 Unidirectional } + | 'pattern' pattern_synonym_lhs '<-' pat where_decls + {% do { let (name, args) = $2 + ; mg <- mkPatSynMatchGroup name $5 ; return $ sLL $1 $> . ValD $ - mkPatSynBind name args $4 (ExplicitBidirectional mg) - }} + mkPatSynBind name args $4 (ExplicitBidirectional mg) }} -where_decls :: { Located (OrdList (LHsDecl RdrName)) } - : 'where' '{' decls '}' { $3 } - | 'where' vocurly decls close { $3 } +pattern_synonym_lhs :: { (Located RdrName, HsPatSynDetails (Located RdrName)) } + : con vars0 { ($1, PrefixPatSyn $2) } + | varid consym varid { ($2, InfixPatSyn $1 $3) } vars0 :: { [Located RdrName] } : {- empty -} { [] } | varid vars0 { $1 : $2 } +where_decls :: { Located (OrdList (LHsDecl RdrName)) } + : 'where' '{' decls '}' { $3 } + | 'where' vocurly decls close { $3 } + +pattern_synonym_sig :: { LSig RdrName } + : 'pattern' con '::' ptype + { let (flag, qtvs, prov, req, ty) = unLoc $4 + in sLL $1 $> $ PatSynSig $2 (flag, mkHsQTvs qtvs) prov req ty } + +ptype :: { Located (HsExplicitFlag, [LHsTyVarBndr RdrName], LHsContext RdrName, LHsContext RdrName, LHsType RdrName) } + : 'forall' tv_bndrs '.' ptype + {% do { hintExplicitForall (getLoc $1) + ; let (_, qtvs', prov, req, ty) = unLoc $4 + ; return $ sLL $1 $> (Explicit, $2 ++ qtvs', prov, req ,ty) }} + | context '=>' context '=>' type + { sLL $1 $> (Implicit, [], $1, $3, $5) } + | context '=>' type + { sLL $1 $> (Implicit, [], $1, noLoc [], $3) } + | type + { sL1 $1 (Implicit, [], noLoc [], noLoc [], $1) } + ----------------------------------------------------------------------------- -- Nested declarations @@ -1490,6 +1508,7 @@ sigdecl :: { Located (OrdList (LHsDecl RdrName)) } { sLL $1 $> $ toOL [ sLL $1 $> $ SigD (TypeSig ($1 : reverse (unLoc $3)) $5) ] } | infix prec ops { sLL $1 $> $ toOL [ sLL $1 $> $ SigD (FixSig (FixitySig n (Fixity $2 (unLoc $1)))) | n <- unLoc $3 ] } + | pattern_synonym_sig { sLL $1 $> $ unitOL $ sLL $1 $> . SigD . unLoc $ $1 } | '{-# INLINE' activation qvar '#-}' { sLL $1 $> $ unitOL (sLL $1 $> $ SigD (InlineSig $3 (mkInlinePragma (getINLINE $1) $2))) } | '{-# SPECIALISE' activation qvar '::' sigtypes1 '#-}' diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs index 625c4dc..e945e43 100644 --- a/compiler/parser/RdrHsSyn.hs +++ b/compiler/parser/RdrHsSyn.hs @@ -18,7 +18,7 @@ module RdrHsSyn ( mkTyFamInst, mkFamDecl, splitCon, mkInlinePragma, - splitPatSyn, toPatSynMatchGroup, + mkPatSynMatchGroup, mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp mkTyClD, mkInstD, @@ -414,33 +414,16 @@ splitCon ty mk_rest [L _ (HsRecTy flds)] = RecCon flds mk_rest ts = PrefixCon ts -splitPatSyn :: LPat RdrName - -> P (Located RdrName, HsPatSynDetails (Located RdrName)) -splitPatSyn (L _ (ParPat pat)) = splitPatSyn pat -splitPatSyn pat@(L loc (ConPatIn con details)) = do - details' <- case details of - PrefixCon pats -> liftM PrefixPatSyn (mapM patVar pats) - InfixCon pat1 pat2 -> liftM2 InfixPatSyn (patVar pat1) (patVar pat2) - RecCon{} -> recordPatSynErr loc pat - return (con, details') - where - patVar :: LPat RdrName -> P (Located RdrName) - patVar (L loc (VarPat v)) = return $ L loc v - patVar (L _ (ParPat pat)) = patVar pat - patVar (L loc pat) = parseErrorSDoc loc $ - text "Pattern synonym arguments must be variable names:" $$ - ppr pat -splitPatSyn pat@(L loc _) = parseErrorSDoc loc $ - text "invalid pattern synonym declaration:" $$ ppr pat - recordPatSynErr :: SrcSpan -> LPat RdrName -> P a recordPatSynErr loc pat = parseErrorSDoc loc $ text "record syntax not supported for pattern synonym declarations:" $$ ppr pat -toPatSynMatchGroup :: Located RdrName -> Located (OrdList (LHsDecl RdrName)) -> P (MatchGroup RdrName (LHsExpr RdrName)) -toPatSynMatchGroup (L _ patsyn_name) (L _ decls) = +mkPatSynMatchGroup :: Located RdrName + -> Located (OrdList (LHsDecl RdrName)) + -> P (MatchGroup RdrName (LHsExpr RdrName)) +mkPatSynMatchGroup (L _ patsyn_name) (L _ decls) = do { matches <- mapM fromDecl (fromOL decls) ; return $ mkMatchGroup FromSource matches } where From git at git.haskell.org Fri Nov 14 09:36:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 09:36:59 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add test cases (e87edf0) Message-ID: <20141114093659.4F5023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/e87edf08c59e23c725296e85672ce380b0643a20/ghc >--------------------------------------------------------------- commit e87edf08c59e23c725296e85672ce380b0643a20 Author: Dr. ERDI Gergo Date: Fri Nov 14 16:21:45 2014 +0800 Add test cases >--------------------------------------------------------------- e87edf08c59e23c725296e85672ce380b0643a20 testsuite/tests/patsyn/should_compile/T8584-1.hs | 8 ++++++++ testsuite/tests/patsyn/should_compile/T8968-1.hs | 8 ++++++++ testsuite/tests/patsyn/should_compile/all.T | 2 ++ 3 files changed, 18 insertions(+) diff --git a/testsuite/tests/patsyn/should_compile/T8584-1.hs b/testsuite/tests/patsyn/should_compile/T8584-1.hs new file mode 100644 index 0000000..00aeb70 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8584-1.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE PatternSynonyms #-} +module ShouldCompile where + +pattern Single :: () => (Show a) => a -> [a] +pattern Single x = [x] + +-- f :: (Show a) => [a] -> a +foobar (Single x) = x diff --git a/testsuite/tests/patsyn/should_compile/T8968-1.hs b/testsuite/tests/patsyn/should_compile/T8968-1.hs new file mode 100644 index 0000000..f41ed53 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8968-1.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE GADTs, KindSignatures, PatternSynonyms #-} +module ShouldCompile where + +data X :: (* -> *) -> * -> * where + Y :: f a -> X f (Maybe a) + +pattern C :: a -> X Maybe (Maybe a) +pattern C x = Y (Just x) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index 55e3b83..ed8961d 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -12,3 +12,5 @@ test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) test('unboxed-bind-bang', normal, compile, ['']) test('T9732', normal, compile, ['']) +test('T8968-1', normal, compile, ['']) +test('T8584-1', normal, compile, ['']) From git at git.haskell.org Fri Nov 14 09:37:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 09:37:01 +0000 (UTC) Subject: [commit: ghc] wip/T8584's head updated: Add test cases (e87edf0) Message-ID: <20141114093701.ACF503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T8584' now includes: d70b19b Per-thread allocation counters and limits 4b5d62a Fix build errors on Windows (these tests still don't work though) 8c10b67 fix allocLimit3 on Windows 1d35c85 Test #9066 in th/T9066 d782694 Fix #9066. f61b3c4 Untabify template-haskell. 1d66167 Remove unboxed Int# fields from NameFlavour (#9527) 88a42be Derive Generic for TH types (#9527) 767feb3 Test #8100 in th/T8100 4ac9e90 Fix #8100, by adding StandaloneDerivD to TH's Dec type. fe71a7e Test #9064 in th/T9064 e4efb7b Fix #9064 by adding support for generic default signatures to TH. ec8781f Test #9204 in roles/should_fail/T9204 ee0f34d Fix #9204 by outputting extra info on boot file mismatch. 90a2bb6 Testsuite wibbles due to #9204 294ac47 Fix #9788 by giving `coerce` the right type. e6e45a1 Test #9404 (typecheck/should_compile/T9404 and T9404b) fe6a517 Testsuite wibble due to #9404 1e2002d Fix #9404 by removing tcInfExpr. c65221b includes/Stg.h: define _DEFAULT_SOURCE for glibc-2.20 064c289 Remove a stray Trustworthy flag in ghc. 1f8b4ee Add in `-fwarn-trustworthy-safe` flag. 475dd93 Add `--fwarn-trustworthy-safe` to `-Wall` 8fe2bbe Update userguide for new `-fwarn-trustworthy-safe` flag. 413c747 base: Fix map/coerce comment e73ab54 Make unwords and words fuse somewhat c016e6f base: define `sequence = mapM id` 212a350 Improve `Foldable` instance for `Array` 63a9d93 Fix `integer-gmp2` compilation with GMP 4.x (#9281) 9b30d9d Fix typo in panic message 745c4c0 Binding things matched by an unboxed pattern synonym should require a bang 7f92986 If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. Fixes #9732. 5fe872d Apply compulsory unfoldings during desugaring, except for `seq` which is special. See Note [Unfolding while desugaring] for the rationale. faeb0a6 nlHsTyApps: for applying a function both on type- and term-level arguments 6389911 When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments 603b7be Implement amap/coerce for Array (re #9796) c27e81a tcCheckPatSynDecl: typechecker for pattern synonyms with user-supplied type signatures 2b160b4 Use user-supplied type variables (when available) in pattern synonym type signatures 42d491a Update baseline shift/reduce conflict number 935f931 Add parser for pattern synonym type signatures. Syntax is of the form e87edf0 Add test cases From git at git.haskell.org Fri Nov 14 11:19:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 11:19:17 +0000 (UTC) Subject: [commit: ghc] master: Update .mailmap (fa75309) Message-ID: <20141114111917.A126E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fa75309456a30b097b1003fcd7b7aa073bab9314/ghc >--------------------------------------------------------------- commit fa75309456a30b097b1003fcd7b7aa073bab9314 Author: Thomas Miedema Date: Sat Nov 8 13:44:57 2014 +0100 Update .mailmap [skip ci] >--------------------------------------------------------------- fa75309456a30b097b1003fcd7b7aa073bab9314 .mailmap | 86 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++------- 1 file changed, 77 insertions(+), 9 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fa75309456a30b097b1003fcd7b7aa073bab9314 From git at git.haskell.org Fri Nov 14 16:50:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 16:50:51 +0000 (UTC) Subject: [commit: ghc] wip/T5462: Implement #5462 (deriving clause for arbitrary classes) (2ad0518) Message-ID: <20141114165051.4423D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T5462 Link : http://ghc.haskell.org/trac/ghc/changeset/2ad051866b5e5bc7751f7f9210e026bb989509f4/ghc >--------------------------------------------------------------- commit 2ad051866b5e5bc7751f7f9210e026bb989509f4 Author: Jose Pedro Magalhaes Date: Mon Sep 29 10:38:00 2014 +0100 Implement #5462 (deriving clause for arbitrary classes) >--------------------------------------------------------------- 2ad051866b5e5bc7751f7f9210e026bb989509f4 compiler/basicTypes/BasicTypes.lhs | 1 + compiler/main/DynFlags.hs | 9 ++++ compiler/typecheck/TcDeriv.lhs | 76 ++++++++++++++++++++++++---- compiler/typecheck/TcGenDeriv.lhs | 31 +++++++++++- testsuite/tests/generics/GEnum/Enum.hs | 87 ++++++++++++++++++++++++++++++++ testsuite/tests/generics/GEq/GEq1A.hs | 3 +- testsuite/tests/generics/T5462No1.hs | 25 +++++++++ testsuite/tests/generics/T5462No1.stderr | 19 +++++++ testsuite/tests/generics/T5462No2.hs | 26 ++++++++++ testsuite/tests/generics/T5462No2.stderr | 19 +++++++ testsuite/tests/generics/T5462Yes.hs | 48 ++++++++++++++++++ testsuite/tests/generics/T5462Yes.stdout | 1 + testsuite/tests/generics/all.T | 12 +++-- testsuite/tests/module/mod53.stderr | 1 + 14 files changed, 340 insertions(+), 18 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2ad051866b5e5bc7751f7f9210e026bb989509f4 From git at git.haskell.org Fri Nov 14 16:50:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 16:50:53 +0000 (UTC) Subject: [commit: ghc] wip/T5462: Use MINIMAL to decide whether we can derive or not, and do not reject newtypes (ffb4520) Message-ID: <20141114165053.DA47B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T5462 Link : http://ghc.haskell.org/trac/ghc/changeset/ffb45204de1841ff1aff7c8e3c04acf3f7081595/ghc >--------------------------------------------------------------- commit ffb45204de1841ff1aff7c8e3c04acf3f7081595 Author: Jose Pedro Magalhaes Date: Wed Nov 5 16:25:25 2014 +0000 Use MINIMAL to decide whether we can derive or not, and do not reject newtypes >--------------------------------------------------------------- ffb45204de1841ff1aff7c8e3c04acf3f7081595 compiler/typecheck/TcDeriv.lhs | 7 +++---- compiler/typecheck/TcGenDeriv.lhs | 14 +++++++++----- 2 files changed, 12 insertions(+), 9 deletions(-) diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index 231f928..ef12d55 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -1568,7 +1568,6 @@ mkNewTypeEqn dflags overlap_mode tvs , ds_newtype = True } | otherwise = case checkSideConditions dflags mtheta cls cls_tys rep_tycon rep_tc_args of - CanDerive -> go_for_it -- Use the standard H98 method DerivableClassError msg -- Error with standard class | might_derive_via_coercible -> bale_out (msg $$ suggest_nd) | otherwise -> bale_out msg @@ -1577,7 +1576,7 @@ mkNewTypeEqn dflags overlap_mode tvs | might_derive_via_coercible -> bale_out (non_std $$ suggest_nd) -- Try newtype deriving! | derivingViaGenerics -> bale_out msg | otherwise -> bale_out non_std - DerivableViaGenerics -> panicGenericsNewtype + _ -> go_for_it -- CanDerive/DerivableViaGenerics where newtype_deriving = xopt Opt_GeneralizedNewtypeDeriving dflags derivingViaGenerics = xopt Opt_DerivingViaGenerics dflags @@ -1586,8 +1585,8 @@ mkNewTypeEqn dflags overlap_mode tvs non_std = nonStdErr cls suggest_nd = ptext (sLit "Try GeneralizedNewtypeDeriving for GHC's newtype-deriving extension") - panicGenericsNewtype = pprPanic "mkNewTypeEqn: DerivableViaGenerics" - (ppr (cls, rep_tycon)) + -- panicGenericsNewtype = pprPanic "mkNewTypeEqn: DerivableViaGenerics" + -- (ppr (cls, rep_tycon)) -- Here is the plan for newtype derivings. We see -- newtype T a1...an = MkT (t ak+1...an) deriving (.., C s1 .. sm, ...) diff --git a/compiler/typecheck/TcGenDeriv.lhs b/compiler/typecheck/TcGenDeriv.lhs index 88c2929..232bfe8 100644 --- a/compiler/typecheck/TcGenDeriv.lhs +++ b/compiler/typecheck/TcGenDeriv.lhs @@ -69,6 +69,7 @@ import TcEnv (InstInfo) import ListSetOps ( assocMaybe ) import Data.List ( partition, intersperse ) import Data.Maybe ( isNothing ) +import BooleanFormula ( isTrue ) \end{code} \begin{code} @@ -132,7 +133,7 @@ genDerivedBinds dflags fix_env clas loc tycon -- We can derive a given class via Generics iff canDeriveViaGenerics :: DynFlags -> TyCon -> Class -> Maybe SDoc canDeriveViaGenerics dflags tycon clas = - let dfs = map (defMethSpecOfDefMeth . snd) . classOpItems $ clas + let _dfs = map (defMethSpecOfDefMeth . snd) . classOpItems $ clas b `orElse` s = if b then Nothing else Just (ptext (sLit s)) Just m <> _ = Just m Nothing <> n = n @@ -141,11 +142,14 @@ canDeriveViaGenerics dflags tycon clas = -- 2) Opt_DerivingViaGenerics is on <> (xopt Opt_DerivingViaGenerics dflags `orElse` "Try enabling DerivingViaGenerics") -- 3) It has no non-default methods - <> (all (/= NoDM) dfs `orElse` "There are methods without a default definition") + -- <> (all (/= NoDM) dfs `orElse` "There are methods without a default definition") -- 4) It has at least one generic default method - <> (any (== GenericDM) dfs `orElse` "There must be at least one method with a default signature") - -- 5) It's not a newtype (that conflicts with GeneralizedNewtypeDeriving) - <> (not (isNewTyCon tycon) `orElse` "DerivingViaGenerics is not supported for newtypes") + -- <> (any (== GenericDM) dfs `orElse` "There must be at least one method with a default signature") + -- 3/4) Its MINIMAL set is empty + <> (isTrue (classMinimalDef clas) `orElse` "because its MINIMAL set is not empty") + -- 5) It a newtype and GND is enabled + <> (not (isNewTyCon tycon && xopt Opt_GeneralizedNewtypeDeriving dflags) + `orElse` "I don't know whether to use DerivingViaGenerics or GeneralizedNewtypeDeriving") -- Nothing: we can derive it via Generics -- Just s: we can't, reason s \end{code} From git at git.haskell.org Fri Nov 14 16:50:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 16:50:56 +0000 (UTC) Subject: [commit: ghc] wip/T5462: Error message tweaks (a7e26ea) Message-ID: <20141114165056.91BE43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T5462 Link : http://ghc.haskell.org/trac/ghc/changeset/a7e26ea762aeb25125ab13450f4df46249c6cfde/ghc >--------------------------------------------------------------- commit a7e26ea762aeb25125ab13450f4df46249c6cfde Author: Jose Pedro Magalhaes Date: Tue Nov 11 10:32:17 2014 +0000 Error message tweaks >--------------------------------------------------------------- a7e26ea762aeb25125ab13450f4df46249c6cfde compiler/typecheck/TcDeriv.lhs | 27 +++++++++++++++++++-------- compiler/typecheck/TcGenDeriv.lhs | 19 +++++++------------ testsuite/tests/generics/T5462No1.hs | 4 +++- testsuite/tests/generics/T5462No1.stderr | 7 ++++--- testsuite/tests/generics/T5462No2.hs | 10 +++++++--- testsuite/tests/generics/T5462No2.stderr | 12 ++++++------ 6 files changed, 46 insertions(+), 33 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a7e26ea762aeb25125ab13450f4df46249c6cfde From git at git.haskell.org Fri Nov 14 16:50:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 16:50:59 +0000 (UTC) Subject: [commit: ghc] wip/T5462: Do not cleanup GFunctor.o (d2dfe4a) Message-ID: <20141114165059.45C0B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T5462 Link : http://ghc.haskell.org/trac/ghc/changeset/d2dfe4ac7c8264a8bcce733107e6d1bcdaabcb41/ghc >--------------------------------------------------------------- commit d2dfe4ac7c8264a8bcce733107e6d1bcdaabcb41 Author: Jose Pedro Magalhaes Date: Wed Nov 12 10:46:19 2014 +0000 Do not cleanup GFunctor.o T5462No1 removes GFunctor.hi and GFunctor.o as it only has to fail to compile, but T5462Yes might still be using them (if we're running the testsuite in parallel), so it's a bad idea to delete. >--------------------------------------------------------------- d2dfe4ac7c8264a8bcce733107e6d1bcdaabcb41 testsuite/tests/generics/all.T | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/generics/all.T b/testsuite/tests/generics/all.T index abe28c0..656fac5 100644 --- a/testsuite/tests/generics/all.T +++ b/testsuite/tests/generics/all.T @@ -20,8 +20,8 @@ test('GenCannotDoRep1_7', normal, compile_fail, ['']) test('GenCannotDoRep1_8', normal, compile_fail, ['']) test('T5462Yes', normal, multimod_compile_and_run, ['T5462Yes', '-iGEq -iGEnum -iGFunctor']) -test('T5462No1', extra_clean(['GFunctor/GFunctor.hi', 'GFunctor/GFunctor.o']), multimod_compile_fail, ['T5462No1', '-iGFunctor']) -test('T5462No2', extra_clean(['GFunctor/GFunctor.hi', 'GFunctor/GFunctor.o']), multimod_compile_fail, ['T5462No2', '-iGFunctor']) +test('T5462No1', normal, multimod_compile_fail, ['T5462No1', '-iGFunctor']) +test('T5462No2', normal, multimod_compile_fail, ['T5462No2', '-iGFunctor']) test('T5884', normal, compile, ['']) test('GenNewtype', normal, compile_and_run, ['']) From git at git.haskell.org Fri Nov 14 16:51:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 16:51:02 +0000 (UTC) Subject: [commit: ghc] wip/T5462: Rename flag, adapt tests, write documentation (b91cb3f) Message-ID: <20141114165102.6516E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T5462 Link : http://ghc.haskell.org/trac/ghc/changeset/b91cb3fb3a5b06c9ba6807df3df9eb60b735605a/ghc >--------------------------------------------------------------- commit b91cb3fb3a5b06c9ba6807df3df9eb60b735605a Author: Jose Pedro Magalhaes Date: Fri Nov 14 16:28:19 2014 +0000 Rename flag, adapt tests, write documentation >--------------------------------------------------------------- b91cb3fb3a5b06c9ba6807df3df9eb60b735605a compiler/main/DynFlags.hs | 4 +- compiler/typecheck/TcDeriv.lhs | 60 +++++++++------------- compiler/typecheck/TcGenDeriv.lhs | 20 +++----- docs/users_guide/flags.xml | 7 +++ docs/users_guide/glasgow_exts.xml | 26 +++++++++- testsuite/tests/generics/T5462No1.hs | 2 +- testsuite/tests/generics/T5462No1.stderr | 4 +- testsuite/tests/generics/T5462No2.hs | 30 ----------- testsuite/tests/generics/T5462No2.stderr | 19 ------- .../tests/generics/{T5462Yes.hs => T5462Yes1.hs} | 2 +- .../generics/{T5462Yes.stdout => T5462Yes1.stdout} | 0 testsuite/tests/generics/T5462Yes2.hs | 37 +++++++++++++ .../T5149.stdout => generics/T5462Yes2.stdout} | 0 testsuite/tests/generics/all.T | 4 +- 14 files changed, 107 insertions(+), 108 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b91cb3fb3a5b06c9ba6807df3df9eb60b735605a From git at git.haskell.org Fri Nov 14 16:51:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 16:51:05 +0000 (UTC) Subject: [commit: ghc] wip/T5462: Minor change (b56cbbf) Message-ID: <20141114165105.4A7E23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T5462 Link : http://ghc.haskell.org/trac/ghc/changeset/b56cbbf588a311624429820c6a77e3fa66893ee2/ghc >--------------------------------------------------------------- commit b56cbbf588a311624429820c6a77e3fa66893ee2 Author: Jose Pedro Magalhaes Date: Fri Nov 14 16:36:28 2014 +0000 Minor change >--------------------------------------------------------------- b56cbbf588a311624429820c6a77e3fa66893ee2 compiler/main/DynFlags.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 096ecce..9d2df7a 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -563,7 +563,7 @@ data ExtensionFlag | Opt_DeriveFoldable | Opt_DeriveGeneric -- Allow deriving Generic/1 | Opt_DefaultSignatures -- Allow extra signatures for defmeths - | Opt_DeriveAnyClass -- Allow deriving classes via GHC.Generics + | Opt_DeriveAnyClass -- Allow deriving any class | Opt_TypeSynonymInstances | Opt_FlexibleContexts @@ -2954,7 +2954,7 @@ xFlags = [ ( "DeriveFunctor", Opt_DeriveFunctor, nop ), ( "DeriveTraversable", Opt_DeriveTraversable, nop ), ( "DeriveFoldable", Opt_DeriveFoldable, nop ), - ( "DeriveAnyClass", Opt_DeriveAnyClass, nop ), + ( "DeriveAnyClass", Opt_DeriveAnyClass, nop ), ( "DeriveGeneric", Opt_DeriveGeneric, nop ), ( "DefaultSignatures", Opt_DefaultSignatures, nop ), ( "TemplateHaskell", Opt_TemplateHaskell, From git at git.haskell.org Fri Nov 14 16:51:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 16:51:07 +0000 (UTC) Subject: [commit: ghc] wip/T5462's head updated: Minor change (b56cbbf) Message-ID: <20141114165107.E0C4C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T5462' now includes: ac0915b Clean-up Haddock in `Data.Functor` 40b1ee4 Add `isSubsequenceOf` to Data.List (#9767) 32237f0 Fix typo in testsuite Makefile 83cf31e Fix a couple of bugs in the way info tables are generated for 64-bit platforms 4cd277b Fix bugs in debug printing 3bebf3c Fix a couple of inaccurate stack checks e6b3829 Disable an assertion; see comment 081ef2f Add a comment about stack checks d14312f Add doctest examples for Data.Either d0d9dc0 Clarify confusing notice from `make maintainer-clean` ad8457f Remove -ddump-simpl-phases flag c0a2354 Remove -ddump-core-pipeline flag 303776a Update User's Guide, cleanup DynFlags 0f930ba Move expansion of 'assert' from renamer to typechecker 030abf9 Remove unused tyConsOfDataCon e7523fe Make tyConsOfType return a (NameEnv TyCon) rather than [TyCon] f81f82e Comments and white space only 528cbd7 Give T3064 the right module name (just tidying up) 096b7e6 Switch off lazy flattening (fix Trac #3064) cb6ccad Minor refacoring and trace-message printing c945477 Allow the solved dictionaries to propagate from outside in ec38deb Wibbles to notes 203cf0e Refactor the code that prevents recursion among Coercible constraints c79cbac Re-enable T3064, which works now 91c15d6 Better error messages for new per-instance overlap flags and Safe Haskell. c96a613 Add in Incoherent Instances test for Safe Haskell. f4ead30 Warn for Safe Haskell when -XOverlappingInstances or -XIncoherentInstances turned on. abba381 Improve Applicative definitions dc5fa80 Make getTag use a bang pattern instead of seq b0e8e34 Update .gitignore to properly ignore emacs temp files 24e05f4 *Really*, really fix RTS crash due to bad coercion. 37d64a5 small parser/lexer cleanup b0d5b5b [Docs] Fixed several broken urls in user's guide f14ac52 Use bracket in `withCurrentDirectory` 832ef3f Have validate take into account stat test failures too. df3b1d4 base: Manually unlit .lhs into .hs modules a2e7bbf Preserve argument order to (==)/eq in nub and nubBy b608868 Typofix. c942688 Miscellaneous documentation for the Finder. f5996d9 Top-level comment for keepPackageImports. 474e535 In pattern synonym matchers, support unboxed continuation results (fixes #9783). 65dc594 Group PatSyn req/prov arguments together so that they're not all over the place 8e66365 Unlit overlooked GHC/Conc/Sync.lhs e2769df Use (.) and id from Base in Control.Applicative 8710136 Move Data.Functor.Identity from transformers to base 7ae596a Typo fix; Trac #9787 4923cea Define list monad operations using comprehensions e567130 De-bias Data.Foldable and improve docstrings 97420b0 Comments only (on recursive dictionaries) ed57ea4 Test Trac #9662 e9d3e28 Comments only 7cbe34f Improve documentation of -ticky a little 13817f0 Test Trac #9077 2b67b8f Test Trac #7862 76d47ed Add stderr for T9662 fcfc87d Disable T4801/peak_megabytes_allocated c774b28 Implement new integer-gmp2 from scratch (re #9281) d70b19b Per-thread allocation counters and limits 4b5d62a Fix build errors on Windows (these tests still don't work though) 8c10b67 fix allocLimit3 on Windows 1d35c85 Test #9066 in th/T9066 d782694 Fix #9066. f61b3c4 Untabify template-haskell. 1d66167 Remove unboxed Int# fields from NameFlavour (#9527) 88a42be Derive Generic for TH types (#9527) 767feb3 Test #8100 in th/T8100 4ac9e90 Fix #8100, by adding StandaloneDerivD to TH's Dec type. fe71a7e Test #9064 in th/T9064 e4efb7b Fix #9064 by adding support for generic default signatures to TH. ec8781f Test #9204 in roles/should_fail/T9204 ee0f34d Fix #9204 by outputting extra info on boot file mismatch. 90a2bb6 Testsuite wibbles due to #9204 294ac47 Fix #9788 by giving `coerce` the right type. e6e45a1 Test #9404 (typecheck/should_compile/T9404 and T9404b) fe6a517 Testsuite wibble due to #9404 1e2002d Fix #9404 by removing tcInfExpr. c65221b includes/Stg.h: define _DEFAULT_SOURCE for glibc-2.20 064c289 Remove a stray Trustworthy flag in ghc. 1f8b4ee Add in `-fwarn-trustworthy-safe` flag. 475dd93 Add `--fwarn-trustworthy-safe` to `-Wall` 8fe2bbe Update userguide for new `-fwarn-trustworthy-safe` flag. 413c747 base: Fix map/coerce comment e73ab54 Make unwords and words fuse somewhat c016e6f base: define `sequence = mapM id` 212a350 Improve `Foldable` instance for `Array` 63a9d93 Fix `integer-gmp2` compilation with GMP 4.x (#9281) 9b30d9d Fix typo in panic message 745c4c0 Binding things matched by an unboxed pattern synonym should require a bang 7f92986 If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. Fixes #9732. 5fe872d Apply compulsory unfoldings during desugaring, except for `seq` which is special. See Note [Unfolding while desugaring] for the rationale. faeb0a6 nlHsTyApps: for applying a function both on type- and term-level arguments 6389911 When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments 603b7be Implement amap/coerce for Array (re #9796) fa75309 Update .mailmap 2ad0518 Implement #5462 (deriving clause for arbitrary classes) ffb4520 Use MINIMAL to decide whether we can derive or not, and do not reject newtypes a7e26ea Error message tweaks d2dfe4a Do not cleanup GFunctor.o b91cb3f Rename flag, adapt tests, write documentation b56cbbf Minor change From git at git.haskell.org Fri Nov 14 17:13:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 17:13:37 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins-amg: Experimental alternative approach to invoking typechecker plugins (2811b64) Message-ID: <20141114171337.4BB163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins-amg Link : http://ghc.haskell.org/trac/ghc/changeset/2811b64baf98feaa3e60d7d29a744fc57d2e1c5d/ghc >--------------------------------------------------------------- commit 2811b64baf98feaa3e60d7d29a744fc57d2e1c5d Author: Adam Gundry Date: Fri Nov 14 16:23:52 2014 +0000 Experimental alternative approach to invoking typechecker plugins The solver is now provided with a boolean flag, which is False when invoked inside solveFlats and True when invoked on the unflattened constraints at the end. >--------------------------------------------------------------- 2811b64baf98feaa3e60d7d29a744fc57d2e1c5d compiler/typecheck/TcInteract.lhs | 63 +++++++++++++++++++++++++++++++-------- compiler/typecheck/TcRnTypes.lhs | 3 +- compiler/typecheck/TcSMonad.lhs | 2 +- 3 files changed, 54 insertions(+), 14 deletions(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 78fb3f3..9890ab8 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -43,7 +43,7 @@ import Data.List( partition, foldl' ) import VarEnv -import Control.Monad( when, unless, forM ) +import Control.Monad( when, unless, forM, foldM ) import Pair (Pair(..)) import Unique( hasKey ) import FastString ( sLit ) @@ -134,9 +134,13 @@ solveFlatWanteds wanteds ; zonked <- zonkFlats (others `andCts` unflattened_eqs) -- Postcondition is that the wl_flats are zonked - ; return (WC { wc_flat = zonked - , wc_insol = insols - , wc_impl = implics }) } + + ; (wanteds', rerun) <- runTcPluginsFinal zonked + ; if rerun then updInertTcS prepareInertsForImplications >> solveFlatWanteds wanteds' + else return (WC { wc_flat = wanteds' + , wc_insol = insols + , wc_impl = implics }) } + -- The main solver loop implements Note [Basic Simplifier Plan] --------------------------------------------------------------- @@ -181,14 +185,9 @@ runTcPlugin :: TcPluginSolver -> TcS () runTcPlugin solver = do iSet <- getTcSInerts let iCans = inert_cans iSet - allCts = foldDicts (:) (inert_dicts iCans) - $ foldFunEqs (:) (inert_funeqs iCans) - $ concat (varEnvElts (inert_eqs iCans)) + (given,derived,wanted) = splitInertCans iCans - (derived,other) = partition isDerivedCt allCts - (wanted,given) = partition isWantedCt other - - result <- runTcPluginTcS (solver given derived wanted) + result <- runTcPluginTcS (solver False given derived wanted) case result of TcPluginContradiction bad_cts -> @@ -197,7 +196,6 @@ runTcPlugin solver = TcPluginOk solved_cts new_cts -> do setInertCans (removeInertCts iCans (map snd solved_cts)) - let setEv (ev,ct) = setEvBind (ctev_evar (cc_ev ct)) ev mapM_ setEv solved_cts updWorkListTcS (extendWorkListCts new_cts) where @@ -225,6 +223,47 @@ runTcPlugin solver = CNonCanonical {} -> panic "runTcPlugin/removeInert: CNonCanonical" CHoleCan {} -> panic "runTcPlugin/removeInert: CHoleCan" + +splitInertCans :: InertCans -> ([Ct], [Ct], [Ct]) +splitInertCans iCans = (given,derived,wanted) + where + allCts = foldDicts (:) (inert_dicts iCans) + $ foldFunEqs (:) (inert_funeqs iCans) + $ concat (varEnvElts (inert_eqs iCans)) + + (derived,other) = partition isDerivedCt allCts + (wanted,given) = partition isWantedCt other + + +setEv :: (EvTerm,Ct) -> TcS () +setEv (ev,ct) = case ctEvidence ct of + CtWanted {ctev_evar = evar} -> setEvBind evar ev + _ -> return () + + +runTcPluginsFinal :: Cts -> TcS (Cts, Bool) +runTcPluginsFinal zonked_wanteds = do + gblEnv <- getGblEnv + (given,derived,_) <- fmap splitInertCans getInertCans + foldM (f given derived) (zonked_wanteds, False) (tcg_tc_plugins gblEnv) + where + f :: [Ct] -> [Ct] -> (Cts, Bool) -> TcPluginSolver -> TcS (Cts, Bool) + f given derived (wanteds, rerun) solver = do + result <- runTcPluginTcS (solver True given derived (bagToList wanteds)) + case result of + TcPluginContradiction bad_cts -> do mapM_ emitInsoluble bad_cts + return (discard bad_cts wanteds, rerun) + TcPluginOk [] [] -> return (wanteds, rerun) + TcPluginOk solved_cts new_cts -> do + mapM_ setEv solved_cts + return (discard (map snd solved_cts) wanteds `unionBags` listToBag new_cts + , rerun || notNull new_cts) + where + discard cs = filterBag (\ c -> not $ any (eqCt c) cs) + + eqCt c c' = ctEvPred (ctEvidence c) `eqType` ctEvPred (ctEvidence c') + + type WorkItem = Ct type SimplifierStage = WorkItem -> TcS (StopOrContinue Ct) diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index 3e0c053..402b7f3 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -1974,7 +1974,8 @@ Constraint Solver Plugins \begin{code} -type TcPluginSolver = [Ct] -- given +type TcPluginSolver = Bool + -> [Ct] -- given -> [Ct] -- derived -> [Ct] -- wanted -> TcPluginM TcPluginResult diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index da79f32..120c248 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -14,7 +14,7 @@ module TcSMonad ( updWorkListTcS, updWorkListTcS_return, - updInertCans, updInertDicts, updInertIrreds, updInertFunEqs, + updInertTcS, updInertCans, updInertDicts, updInertIrreds, updInertFunEqs, Ct(..), Xi, tyVarsOfCt, tyVarsOfCts, emitInsoluble, emitWorkNC, From git at git.haskell.org Fri Nov 14 17:13:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 17:13:40 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins-amg: Fix validate errors introduced by plugins redesign (6c00ae9) Message-ID: <20141114171340.02F893A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins-amg Link : http://ghc.haskell.org/trac/ghc/changeset/6c00ae9cbc70e14bb16d14c26484a1f82e8e9e8c/ghc >--------------------------------------------------------------- commit 6c00ae9cbc70e14bb16d14c26484a1f82e8e9e8c Author: Adam Gundry Date: Fri Nov 14 17:05:06 2014 +0000 Fix validate errors introduced by plugins redesign >--------------------------------------------------------------- 6c00ae9cbc70e14bb16d14c26484a1f82e8e9e8c compiler/simplCore/SimplCore.lhs | 13 ++++++------- 1 file changed, 6 insertions(+), 7 deletions(-) diff --git a/compiler/simplCore/SimplCore.lhs b/compiler/simplCore/SimplCore.lhs index 1cfd9bd..883f2ef 100644 --- a/compiler/simplCore/SimplCore.lhs +++ b/compiler/simplCore/SimplCore.lhs @@ -26,7 +26,6 @@ import SimplUtils ( simplEnvForGHCi, activeRule ) import SimplEnv import SimplMonad import CoreMonad -import Plugins import qualified ErrUtils as Err import FloatIn ( floatInwards ) import FloatOut ( floatOutwards ) @@ -54,6 +53,7 @@ import Control.Monad #ifdef GHCI import DynamicLoading ( loadPlugins ) +import Plugins ( installCoreToDos ) #endif \end{code} @@ -72,7 +72,7 @@ core2core hsc_env guts ; let builtin_passes = getCoreToDo dflags ; ; (guts2, stats) <- runCoreM hsc_env hpt_rule_base us mod print_unqual $ - do { all_passes <- addPluginPasses dflags builtin_passes + do { all_passes <- addPluginPasses builtin_passes ; runCorePasses all_passes guts } ; Err.dumpIfSet_dyn dflags Opt_D_dump_simpl_stats @@ -316,17 +316,16 @@ getCoreToDo dflags Loading plugins \begin{code} -addPluginPasses :: DynFlags -> [CoreToDo] -> CoreM [CoreToDo] +addPluginPasses :: [CoreToDo] -> CoreM [CoreToDo] #ifndef GHCI -addPluginPasses _ builtin_passes = return builtin_passes +addPluginPasses builtin_passes = return builtin_passes #else -addPluginPasses dflags builtin_passes +addPluginPasses builtin_passes = do { hsc_env <- getHscEnv ; named_plugins <- liftIO (loadPlugins hsc_env) ; foldM query_plug builtin_passes named_plugins } where - query_plug todos (mod_nm, plug, options) - = installCoreToDos plug options todos + query_plug todos (_, plug, options) = installCoreToDos plug options todos #endif \end{code} From git at git.haskell.org Fri Nov 14 17:51:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 17:51:54 +0000 (UTC) Subject: [commit: ghc] master: Partially revert 475dd93efa (452d6aa) Message-ID: <20141114175154.2BB3B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/452d6aa95b754a08e1e61800680ccbf6f968aef0/ghc >--------------------------------------------------------------- commit 452d6aa95b754a08e1e61800680ccbf6f968aef0 Author: Austin Seipp Date: Fri Nov 14 11:51:31 2014 -0600 Partially revert 475dd93efa This introduces ./validate failures for Windows right now, so in the mean time let's just back this flag out as a default -Wall flag. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 452d6aa95b754a08e1e61800680ccbf6f968aef0 compiler/main/DynFlags.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 70fc6d3..043174f 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -3154,8 +3154,7 @@ minusWallOpts Opt_WarnMissingSigs, Opt_WarnHiShadows, Opt_WarnOrphans, - Opt_WarnUnusedDoBind, - Opt_WarnTrustworthySafe + Opt_WarnUnusedDoBind ] enableGlasgowExts :: DynP () From git at git.haskell.org Fri Nov 14 18:51:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 18:51:18 +0000 (UTC) Subject: [commit: ghc] wip/T5462: Remove wrongly introduced duplication (1f848a9) Message-ID: <20141114185118.6BEF13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T5462 Link : http://ghc.haskell.org/trac/ghc/changeset/1f848a919f9476fbe2b70c4d40b93b872067674b/ghc >--------------------------------------------------------------- commit 1f848a919f9476fbe2b70c4d40b93b872067674b Author: Jose Pedro Magalhaes Date: Fri Nov 14 16:55:59 2014 +0000 Remove wrongly introduced duplication >--------------------------------------------------------------- 1f848a919f9476fbe2b70c4d40b93b872067674b compiler/main/DynFlags.hs | 9 +-------- 1 file changed, 1 insertion(+), 8 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 9d2df7a..354a64d 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -2871,6 +2871,7 @@ xFlags = [ $ deprecate $ "It was widely considered a misfeature, " ++ "and has been removed from the Haskell language." ), ( "DefaultSignatures", Opt_DefaultSignatures, nop ), + ( "DeriveAnyClass", Opt_DeriveAnyClass, nop ), ( "DeriveDataTypeable", Opt_DeriveDataTypeable, nop ), ( "DeriveFoldable", Opt_DeriveFoldable, nop ), ( "DeriveFunctor", Opt_DeriveFunctor, nop ), @@ -2949,14 +2950,6 @@ xFlags = [ ( "RoleAnnotations", Opt_RoleAnnotations, nop ), ( "ScopedTypeVariables", Opt_ScopedTypeVariables, nop ), ( "StandaloneDeriving", Opt_StandaloneDeriving, nop ), - ( "DeriveDataTypeable", Opt_DeriveDataTypeable, nop ), - ( "AutoDeriveTypeable", Opt_AutoDeriveTypeable, nop ), - ( "DeriveFunctor", Opt_DeriveFunctor, nop ), - ( "DeriveTraversable", Opt_DeriveTraversable, nop ), - ( "DeriveFoldable", Opt_DeriveFoldable, nop ), - ( "DeriveAnyClass", Opt_DeriveAnyClass, nop ), - ( "DeriveGeneric", Opt_DeriveGeneric, nop ), - ( "DefaultSignatures", Opt_DefaultSignatures, nop ), ( "TemplateHaskell", Opt_TemplateHaskell, checkTemplateHaskellOk ), ( "TraditionalRecordSyntax", Opt_TraditionalRecordSyntax, nop ), From git at git.haskell.org Fri Nov 14 18:51:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 18:51:21 +0000 (UTC) Subject: [commit: ghc] wip/T5462: Rename flag (4f6fb9f) Message-ID: <20141114185121.312323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T5462 Link : http://ghc.haskell.org/trac/ghc/changeset/4f6fb9fde548d7e337671619dda5a081b059f5b6/ghc >--------------------------------------------------------------- commit 4f6fb9fde548d7e337671619dda5a081b059f5b6 Author: Jose Pedro Magalhaes Date: Fri Nov 14 18:51:24 2014 +0000 Rename flag >--------------------------------------------------------------- 4f6fb9fde548d7e337671619dda5a081b059f5b6 testsuite/tests/module/mod53.stderr | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/module/mod53.stderr b/testsuite/tests/module/mod53.stderr index a4417e2..2a046de 100644 --- a/testsuite/tests/module/mod53.stderr +++ b/testsuite/tests/module/mod53.stderr @@ -2,5 +2,5 @@ mod53.hs:4:22: Can't make a derived instance of ?C T?: ?C? is not a derivable class - Try enabling DerivingViaGenerics + Try enabling DerivingAnyClass In the data declaration for ?T? From git at git.haskell.org Fri Nov 14 21:45:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 21:45:46 +0000 (UTC) Subject: [commit: ghc] wip/T5462: Mispelling (1f3131e) Message-ID: <20141114214546.1CB393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T5462 Link : http://ghc.haskell.org/trac/ghc/changeset/1f3131eb5dd4812f5d854f8017c7b4138449823d/ghc >--------------------------------------------------------------- commit 1f3131eb5dd4812f5d854f8017c7b4138449823d Author: Jose Pedro Magalhaes Date: Fri Nov 14 19:34:27 2014 +0000 Mispelling >--------------------------------------------------------------- 1f3131eb5dd4812f5d854f8017c7b4138449823d testsuite/tests/module/mod53.stderr | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/module/mod53.stderr b/testsuite/tests/module/mod53.stderr index 2a046de..2630e9c 100644 --- a/testsuite/tests/module/mod53.stderr +++ b/testsuite/tests/module/mod53.stderr @@ -2,5 +2,5 @@ mod53.hs:4:22: Can't make a derived instance of ?C T?: ?C? is not a derivable class - Try enabling DerivingAnyClass + Try enabling DeriveAnyClass In the data declaration for ?T? From git at git.haskell.org Fri Nov 14 21:45:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Nov 2014 21:45:48 +0000 (UTC) Subject: [commit: ghc] wip/T5462: Make DeriveAnyClass an expected GHC-only extension for now (6e5bac5) Message-ID: <20141114214548.ADD0B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T5462 Link : http://ghc.haskell.org/trac/ghc/changeset/6e5bac5fe077ee3e25267ad1725cf408aace098d/ghc >--------------------------------------------------------------- commit 6e5bac5fe077ee3e25267ad1725cf408aace098d Author: Jose Pedro Magalhaes Date: Fri Nov 14 21:46:02 2014 +0000 Make DeriveAnyClass an expected GHC-only extension for now >--------------------------------------------------------------- 6e5bac5fe077ee3e25267ad1725cf408aace098d testsuite/tests/driver/T4437.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/testsuite/tests/driver/T4437.hs b/testsuite/tests/driver/T4437.hs index 40ddb4b..1dfaa8b 100644 --- a/testsuite/tests/driver/T4437.hs +++ b/testsuite/tests/driver/T4437.hs @@ -33,6 +33,7 @@ expectedGhcOnlyExtensions :: [String] expectedGhcOnlyExtensions = ["RelaxedLayout", "AlternativeLayoutRule", "AlternativeLayoutRuleTransitional", + "DeriveAnyClass", "JavaScriptFFI", "PatternSynonyms"] From git at git.haskell.org Sat Nov 15 09:39:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 15 Nov 2014 09:39:17 +0000 (UTC) Subject: [commit: ghc] master: Generalize exposed-modules field in installed package database (e14a973) Message-ID: <20141115093917.985053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e14a973215102cb3774e3b4370c64edcff0e10bc/ghc >--------------------------------------------------------------- commit e14a973215102cb3774e3b4370c64edcff0e10bc Author: Edward Z. Yang Date: Sat Nov 15 00:08:53 2014 -0800 Generalize exposed-modules field in installed package database Summary: Instead of recording exposed-modules and reexported-modules as seperate fields in the installed package database, this commit merges them into a single field (exposed-modules). The motivation for this change is in preparation for the inclusion of *signatures* into the installed package database, which may also be reexported. Merging the representation means that we can treat reexports uniformly, no matter if they're a normal module or a signature. This commit adds a stub for signatures, but that code isn't wired up to anything yet. Contains Cabal submodule update to accommodate these changes. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, duncan, austin Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D421 >--------------------------------------------------------------- e14a973215102cb3774e3b4370c64edcff0e10bc compiler/main/PackageConfig.hs | 27 ++++++- compiler/main/Packages.lhs | 23 +++--- libraries/Cabal | 2 +- libraries/bin-package-db/GHC/PackageDb.hs | 98 +++++++++++++++++------- testsuite/tests/cabal/Makefile | 4 +- testsuite/tests/cabal/ghcpkg07.stdout | 13 ++-- testsuite/tests/cabal/test7a.pkg | 4 +- testsuite/tests/cabal/test7b.pkg | 4 +- utils/ghc-pkg/Main.hs | 123 ++++++++++++++++++------------ 9 files changed, 191 insertions(+), 107 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e14a973215102cb3774e3b4370c64edcff0e10bc From git at git.haskell.org Sat Nov 15 10:19:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 15 Nov 2014 10:19:47 +0000 (UTC) Subject: [commit: ghc] master: Workaround 452d6aa95b7 breaking TrustworthySafe03 (1854825) Message-ID: <20141115101947.0EFED3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/185482524d4fa5954243476de1452219fb077228/ghc >--------------------------------------------------------------- commit 185482524d4fa5954243476de1452219fb077228 Author: Herbert Valerio Riedel Date: Sat Nov 15 11:18:12 2014 +0100 Workaround 452d6aa95b7 breaking TrustworthySafe03 This is only a temporary kludge until the issue workarounded by 452d6aa95b7 gets properly fixed >--------------------------------------------------------------- 185482524d4fa5954243476de1452219fb077228 testsuite/tests/safeHaskell/safeInfered/TrustworthySafe03.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/testsuite/tests/safeHaskell/safeInfered/TrustworthySafe03.hs b/testsuite/tests/safeHaskell/safeInfered/TrustworthySafe03.hs index 12be9b1..ad63e09 100644 --- a/testsuite/tests/safeHaskell/safeInfered/TrustworthySafe03.hs +++ b/testsuite/tests/safeHaskell/safeInfered/TrustworthySafe03.hs @@ -1,5 +1,6 @@ {-# LANGUAGE Trustworthy #-} {-# OPTIONS_GHC -Wall #-} +{-# OPTIONS_GHC -fwarn-trustworthy-safe #-} -- temp broken by 452d6aa95 -- | This module is marked trustworthy but should be inferable as -XSafe. -- Warning enabled through `-W`. From git at git.haskell.org Sat Nov 15 11:26:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 15 Nov 2014 11:26:08 +0000 (UTC) Subject: [commit: ghc] master: Update to (unreleased) `deepseq-1.4.0.0` (609cd28) Message-ID: <20141115112609.00F4D3A302@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/609cd28a1a8616f4076088c87e443850d807ba7d/ghc >--------------------------------------------------------------- commit 609cd28a1a8616f4076088c87e443850d807ba7d Author: Herbert Valerio Riedel Date: Sat Nov 15 12:16:38 2014 +0100 Update to (unreleased) `deepseq-1.4.0.0` This pulls in the new `Generic`-based `-XDefaultSignature`-based default implementation for `rnf`[1], and will be interesting to use in combination with the soon to be merged `-XDeriveAnyClass` extension. This requires updating several other submodules as well in order to relax the upper bound on `deepseq` and/or in a few cases to avoid relying on the default method implementation of `rnf`: - `Cabal` - `bytestring` - `containers` - `parallel` - `process` - `time` [1]: http://permalink.gmane.org/gmane.comp.lang.haskell.libraries/23031 >--------------------------------------------------------------- 609cd28a1a8616f4076088c87e443850d807ba7d libraries/Cabal | 2 +- libraries/bytestring | 2 +- libraries/containers | 2 +- libraries/deepseq | 2 +- libraries/parallel | 2 +- libraries/process | 2 +- libraries/time | 2 +- mk/validate-settings.mk | 3 +++ testsuite/tests/safeHaskell/check/Check09.stderr | 2 +- testsuite/tests/safeHaskell/check/pkg01/ImpSafe03.stderr | 2 +- testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr | 2 +- testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr | 2 +- testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout | 6 +++--- utils/haddock | 2 +- 14 files changed, 18 insertions(+), 15 deletions(-) diff --git a/libraries/Cabal b/libraries/Cabal index 1f8a0a2..f54e7f9 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 1f8a0a20c7a010b50fbafc0effde9bcd663d8716 +Subproject commit f54e7f95412c2ee9ee76ce9517b7d8aa769bdcfa diff --git a/libraries/bytestring b/libraries/bytestring index 6ad8c0d..7a7602a 160000 --- a/libraries/bytestring +++ b/libraries/bytestring @@ -1 +1 @@ -Subproject commit 6ad8c0d27bcff28c80684a29b57d7a8dbf00caca +Subproject commit 7a7602a142a1deae2e4f73782d88a91f39a0fa98 diff --git a/libraries/containers b/libraries/containers index 530fc76..c802c36 160000 --- a/libraries/containers +++ b/libraries/containers @@ -1 +1 @@ -Subproject commit 530fc76bdd17089fcaaa655d66156abbc2092c2c +Subproject commit c802c36dbed4b800d8c2131181f5af3db837aded diff --git a/libraries/deepseq b/libraries/deepseq index 3815fe8..75ce576 160000 --- a/libraries/deepseq +++ b/libraries/deepseq @@ -1 +1 @@ -Subproject commit 3815fe819ba465159cc618b3521adcba97e3c0d1 +Subproject commit 75ce5767488774065025df34cbc80de6f03c4fd1 diff --git a/libraries/parallel b/libraries/parallel index 94e1aa6..50a2b2a 160000 --- a/libraries/parallel +++ b/libraries/parallel @@ -1 +1 @@ -Subproject commit 94e1aa6f621df464c237c9987bb7f65bd4cb5ff1 +Subproject commit 50a2b2a622898786d623a9f933183525305058d3 diff --git a/libraries/process b/libraries/process index 7b3ede7..bc5f234 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 7b3ede7dbbb2de80b906c76f747d0b3196c4669a +Subproject commit bc5f2348b982d9e86bf2f15065187a0ba535a1a3 diff --git a/libraries/time b/libraries/time index 991e6be..ab6475c 160000 --- a/libraries/time +++ b/libraries/time @@ -1 +1 @@ -Subproject commit 991e6be84974b02d7f968601ab02d2e2b3e14190 +Subproject commit ab6475cb94260f4303afbbd4b770cbd14ec2f57e diff --git a/mk/validate-settings.mk b/mk/validate-settings.mk index 150aec3..cce5063 100644 --- a/mk/validate-settings.mk +++ b/mk/validate-settings.mk @@ -108,6 +108,9 @@ libraries/stm_dist-install_EXTRA_HC_OPTS += -fno-warn-unused-imports libraries/parallel_dist-install_EXTRA_HC_OPTS += -fno-warn-unused-imports libraries/vector_dist-install_EXTRA_HC_OPTS += -fno-warn-unused-imports +# haddock's attoparsec uses deprecated `inlinePerformIO` +utils/haddock_dist_EXTRA_HC_OPTS += -fno-warn-deprecations + # bytestring has identities at the moment libraries/bytestring_dist-install_EXTRA_HC_OPTS += -fno-warn-identities diff --git a/testsuite/tests/safeHaskell/check/Check09.stderr b/testsuite/tests/safeHaskell/check/Check09.stderr index 6954dd1..75803cf 100644 --- a/testsuite/tests/safeHaskell/check/Check09.stderr +++ b/testsuite/tests/safeHaskell/check/Check09.stderr @@ -5,4 +5,4 @@ Check09.hs:4:1: Check09.hs:5:1: Data.ByteString.Char8: Can't be safely imported! - The package (bytestring-0.10.4.0) the module resides in isn't trusted. + The package (bytestring-0.10.5.0) the module resides in isn't trusted. diff --git a/testsuite/tests/safeHaskell/check/pkg01/ImpSafe03.stderr b/testsuite/tests/safeHaskell/check/pkg01/ImpSafe03.stderr index 2fdf45c..0a012f7 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/ImpSafe03.stderr +++ b/testsuite/tests/safeHaskell/check/pkg01/ImpSafe03.stderr @@ -1,4 +1,4 @@ [2 of 2] Compiling Main ( ImpSafe03.hs, ImpSafe03.o ) : - The package (bytestring-0.10.4.0) is required to be trusted but it isn't! + The package (bytestring-0.10.5.0) is required to be trusted but it isn't! diff --git a/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr b/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr index 884f080..3dd6759 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr +++ b/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr @@ -3,4 +3,4 @@ The package (base-4.8.0.0) is required to be trusted but it isn't! : - The package (bytestring-0.10.4.0) is required to be trusted but it isn't! + The package (bytestring-0.10.5.0) is required to be trusted but it isn't! diff --git a/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr b/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr index 884f080..3dd6759 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr +++ b/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr @@ -3,4 +3,4 @@ The package (base-4.8.0.0) is required to be trusted but it isn't! : - The package (bytestring-0.10.4.0) is required to be trusted but it isn't! + The package (bytestring-0.10.5.0) is required to be trusted but it isn't! diff --git a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout index 44ea89f..1567b60 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout +++ b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout @@ -29,17 +29,17 @@ trusted: safe require own pkg trusted: True M_SafePkg6 -package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.4.0* deepseq-1.3.0.3 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.5.0* deepseq-1.4.0.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 trusted: trustworthy require own pkg trusted: False M_SafePkg7 -package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.4.0* deepseq-1.3.0.3 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.5.0* deepseq-1.4.0.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 trusted: safe require own pkg trusted: False M_SafePkg8 -package dependencies: array-0.5.0.1 base-4.8.0.0 bytestring-0.10.4.0* deepseq-1.3.0.3 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: array-0.5.0.1 base-4.8.0.0 bytestring-0.10.5.0* deepseq-1.4.0.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 trusted: trustworthy require own pkg trusted: False diff --git a/utils/haddock b/utils/haddock index 199936a..9cdf19b 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 199936af5bb902c81f822b2dc57308dc25e18cfc +Subproject commit 9cdf19bad54a6cc4b322396fdd06f4c1ee045b22 From git at git.haskell.org Sat Nov 15 11:24:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 15 Nov 2014 11:24:51 +0000 (UTC) Subject: [commit: packages/parallel] master: Fix-up 94e1aa6f621df46 re changelog name (3badfae) Message-ID: <20141115112451.BAF713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/parallel On branch : master Link : http://git.haskell.org/packages/parallel.git/commitdiff/3badfae89b2456c38590b9af18b23d5cf2b35071 >--------------------------------------------------------------- commit 3badfae89b2456c38590b9af18b23d5cf2b35071 Author: Herbert Valerio Riedel Date: Sat Nov 15 11:39:24 2014 +0100 Fix-up 94e1aa6f621df46 re changelog name The changelog file was renamed but the .cabal file wasn't updated to reflect that rename. >--------------------------------------------------------------- 3badfae89b2456c38590b9af18b23d5cf2b35071 parallel.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/parallel.cabal b/parallel.cabal index 38c3293..e63423c 100644 --- a/parallel.cabal +++ b/parallel.cabal @@ -12,7 +12,7 @@ tested-with: GHC==7.6.3, GHC==7.6.2, GHC==7.6.1, GHC==7.4.2, GHC==7.4.1, GHC= description: This package provides a library for parallel programming. -extra-source-files: changelog +extra-source-files: changelog.md source-repository head type: git From git at git.haskell.org Sat Nov 15 11:24:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 15 Nov 2014 11:24:53 +0000 (UTC) Subject: [commit: packages/parallel] master: Bump upper bound for `deepseq` (50a2b2a) Message-ID: <20141115112453.BF3E33A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/parallel On branch : master Link : http://git.haskell.org/packages/parallel.git/commitdiff/50a2b2a622898786d623a9f933183525305058d3 >--------------------------------------------------------------- commit 50a2b2a622898786d623a9f933183525305058d3 Author: Herbert Valerio Riedel Date: Sat Nov 15 11:41:09 2014 +0100 Bump upper bound for `deepseq` The upcoming `deepseq-1.4.0.0` version's changes don't affect `parallel` so we can safely bump the upper bound >--------------------------------------------------------------- 50a2b2a622898786d623a9f933183525305058d3 parallel.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/parallel.cabal b/parallel.cabal index e63423c..90f0583 100644 --- a/parallel.cabal +++ b/parallel.cabal @@ -36,7 +36,7 @@ library array >= 0.3 && < 0.6, base >= 4.3 && < 4.9, containers >= 0.4 && < 0.6, - deepseq >= 1.1 && < 1.4 + deepseq >= 1.1 && < 1.5 ghc-options: -Wall From git at git.haskell.org Mon Nov 17 02:30:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Nov 2014 02:30:35 +0000 (UTC) Subject: [commit: ghc] master: Update validate settings now that containers and process have been updated to handle `-fwarn-trustworthy-safe`. (a2c0a8d) Message-ID: <20141117023035.8F3933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a2c0a8dd15de2023e17078fa5f421ba581b3a5fa/ghc >--------------------------------------------------------------- commit a2c0a8dd15de2023e17078fa5f421ba581b3a5fa Author: David Terei Date: Sun Nov 16 18:29:58 2014 -0800 Update validate settings now that containers and process have been updated to handle `-fwarn-trustworthy-safe`. >--------------------------------------------------------------- a2c0a8dd15de2023e17078fa5f421ba581b3a5fa mk/validate-settings.mk | 2 -- 1 file changed, 2 deletions(-) diff --git a/mk/validate-settings.mk b/mk/validate-settings.mk index cce5063..e06135b 100644 --- a/mk/validate-settings.mk +++ b/mk/validate-settings.mk @@ -169,8 +169,6 @@ libraries/array_dist-install_EXTRA_HC_OPTS += -fno-warn-warnings-deprecations # Turn of trustworthy-safe warning libraries/base_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe libraries/ghc-prim_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe -libraries/containers_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe -libraries/process_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe libraries/unix_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe # Temporarely disable inline rule shadowing warning From git at git.haskell.org Mon Nov 17 13:13:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Nov 2014 13:13:48 +0000 (UTC) Subject: [commit: ghc] master: Fix a bug introduced with allocation counters (2a6f193) Message-ID: <20141117131348.D90DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2a6f193bb82f88e8dcb919ee7affc13feae56e98/ghc >--------------------------------------------------------------- commit 2a6f193bb82f88e8dcb919ee7affc13feae56e98 Author: Simon Marlow Date: Mon Nov 17 13:03:56 2014 +0000 Fix a bug introduced with allocation counters >--------------------------------------------------------------- 2a6f193bb82f88e8dcb919ee7affc13feae56e98 rts/Schedule.c | 3 +++ testsuite/tests/ffi/should_run/all.T | 4 ++++ testsuite/tests/ffi/should_run/ffi023.hs | 23 +++++++++++++++++++++++ testsuite/tests/ffi/should_run/ffi023_c.c | 9 +++++++++ 4 files changed, 39 insertions(+) diff --git a/rts/Schedule.c b/rts/Schedule.c index c2260f0..e9b0289 100644 --- a/rts/Schedule.c +++ b/rts/Schedule.c @@ -2233,6 +2233,9 @@ suspendThread (StgRegTable *reg, rtsBool interruptible) task->incall->suspended_tso = tso; task->incall->suspended_cap = cap; + // Otherwise allocate() will write to invalid memory. + cap->r.rCurrentTSO = NULL + ACQUIRE_LOCK(&cap->lock); suspendTask(cap,task); diff --git a/testsuite/tests/ffi/should_run/all.T b/testsuite/tests/ffi/should_run/all.T index 6fe0878..0499631 100644 --- a/testsuite/tests/ffi/should_run/all.T +++ b/testsuite/tests/ffi/should_run/all.T @@ -209,3 +209,7 @@ test('T8083', compile_and_run, ['T8083_c.c']) +test('ffi023', [ omit_ways(['ghci']), + extra_clean(['ffi023_c.o']), + extra_run_opts('1000 4') ], + compile_and_run, ['ffi023_c.c']) diff --git a/testsuite/tests/ffi/should_run/ffi023.hs b/testsuite/tests/ffi/should_run/ffi023.hs new file mode 100644 index 0000000..96a6092 --- /dev/null +++ b/testsuite/tests/ffi/should_run/ffi023.hs @@ -0,0 +1,23 @@ +-- Tests for a bug fixed in + +module Main where + +import System.Environment +import Control.Concurrent +import Control.Monad + +foreign import ccall safe "out" + out :: Int -> IO Int + +foreign export ccall "incall" incall :: Int -> IO Int + +incall :: Int -> IO Int +incall x = return $ x + 1 + +main = do + [n, m] <- fmap (fmap read) getArgs + ms <- replicateM m $ do + v <- newEmptyMVar + forkIO $ do mapM out [0..n]; putMVar v () + return v + mapM_ takeMVar ms diff --git a/testsuite/tests/ffi/should_run/ffi023_c.c b/testsuite/tests/ffi/should_run/ffi023_c.c new file mode 100644 index 0000000..a8a5a15 --- /dev/null +++ b/testsuite/tests/ffi/should_run/ffi023_c.c @@ -0,0 +1,9 @@ +#include "ffi023_stub.h" +#include "HsFFI.h" +#include "Rts.h" + +HsInt out (HsInt x) +{ + performMajorGC(); + return incall(x); +} From git at git.haskell.org Mon Nov 17 18:16:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Nov 2014 18:16:41 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins-amg: Return insoluble constraints from solveFlatWanteds (2eab231) Message-ID: <20141117181641.C7D063A337@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins-amg Link : http://ghc.haskell.org/trac/ghc/changeset/2eab231965aeca6ff4042e0ade96f4bda23c1fe3/ghc >--------------------------------------------------------------- commit 2eab231965aeca6ff4042e0ade96f4bda23c1fe3 Author: Adam Gundry Date: Mon Nov 17 18:16:18 2014 +0000 Return insoluble constraints from solveFlatWanteds It turns out that emitInsoluble isn't the right thing, because the insolubles should be returned in the wc_insol field of the WantedConstraints. >--------------------------------------------------------------- 2eab231965aeca6ff4042e0ade96f4bda23c1fe3 compiler/typecheck/TcInteract.lhs | 23 ++++++++++++----------- 1 file changed, 12 insertions(+), 11 deletions(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 47997c6..811b16a 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -139,10 +139,10 @@ solveFlatWanteds wanteds ; zonked <- zonkFlats (others `andCts` unflattened_eqs) -- Postcondition is that the wl_flats are zonked - ; (wanteds', rerun) <- runTcPluginsWanted zonked + ; (wanteds', insols', rerun) <- runTcPluginsWanted zonked ; if rerun then updInertTcS prepareInertsForImplications >> solveFlatWanteds wanteds' else return (WC { wc_flat = wanteds' - , wc_insol = insols + , wc_insol = insols' `unionBags` insols , wc_impl = implics }) } @@ -244,26 +244,27 @@ runTcPluginsGiven = do eqCt c c' = ctEvPred (ctEvidence c) `eqType` ctEvPred (ctEvidence c') -- | Given a bag of (flattened, zonked) wanteds, invoke the plugins on --- them and produce an updated bag of wanteds. If the boolean is --- 'True', these should be fed back into the main solver. -runTcPluginsWanted :: Cts -> TcS (Cts, Bool) +-- them and produce an updated bag of wanteds and a bag of fresh +-- insolubles. If the boolean is 'True', the wanteds should be fed +-- back into the main solver. +runTcPluginsWanted :: Cts -> TcS (Cts, Cts, Bool) runTcPluginsWanted zonked_wanteds = do gblEnv <- getGblEnv (given,derived,_) <- fmap splitInertCans getInertCans - foldM (f given derived) (zonked_wanteds, False) (tcg_tc_plugins gblEnv) + foldM (f given derived) (zonked_wanteds, emptyBag, False) (tcg_tc_plugins gblEnv) where - f :: [Ct] -> [Ct] -> (Cts, Bool) -> TcPluginSolver -> TcS (Cts, Bool) - f given derived (wanteds, rerun) solver = do + f :: [Ct] -> [Ct] -> (Cts, Cts, Bool) -> TcPluginSolver -> TcS (Cts, Cts, Bool) + f given derived (wanteds, insols, rerun) solver = do result <- runTcPluginTcS (solver given derived (bagToList wanteds)) case result of - TcPluginContradiction bad_cts -> do mapM_ emitInsoluble bad_cts - return (discard bad_cts wanteds, rerun) - TcPluginOk [] [] -> return (wanteds, rerun) + TcPluginContradiction bad_cts -> return (discard bad_cts wanteds, listToBag bad_cts `unionBags` insols, rerun) + TcPluginOk [] [] -> return (wanteds, insols, rerun) TcPluginOk solved_cts new_cts -> do mapM_ setEv solved_cts let new_facts = [ct | ct <- new_cts, not (any (eqCt ct) (given ++ derived ++ bagToList wanteds))] updWorkListTcS (extendWorkListCts new_facts) return ( discard (map snd solved_cts) wanteds + , insols , rerun || notNull new_facts) where discard cs = filterBag (\ c -> not $ any (eqCt c) cs) From git at git.haskell.org Mon Nov 17 17:43:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Nov 2014 17:43:54 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins-amg: Modify runTcPluginsGiven to allow solving givens, avoid duplicating work (3080c9b) Message-ID: <20141117174354.85B043A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins-amg Link : http://ghc.haskell.org/trac/ghc/changeset/3080c9b4a60aac47368f6adb04ac1483383af62c/ghc >--------------------------------------------------------------- commit 3080c9b4a60aac47368f6adb04ac1483383af62c Author: Adam Gundry Date: Mon Nov 17 17:27:17 2014 +0000 Modify runTcPluginsGiven to allow solving givens, avoid duplicating work >--------------------------------------------------------------- 3080c9b4a60aac47368f6adb04ac1483383af62c compiler/typecheck/TcInteract.lhs | 71 ++++++++++++++++++++++++++++----------- 1 file changed, 52 insertions(+), 19 deletions(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index c8fedfb..47997c6 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -39,7 +39,7 @@ import TcErrors import TcSMonad import Bag -import Data.List( partition ) +import Data.List( partition, foldl', deleteFirstsBy ) import VarEnv @@ -125,8 +125,8 @@ solveFlatGivens loc givens , ctev_pred = evVarPred ev_id , ctev_loc = loc }) go givens = do { solveFlats givens - ; (upd_givens, rerun) <- runTcPluginsGiven givens - ; when rerun (go upd_givens) + ; new_givens <- runTcPluginsGiven + ; when (notNull new_givens) (go (listToBag new_givens)) } solveFlatWanteds :: Cts -> TcS WantedConstraints @@ -189,30 +189,63 @@ setEv (ev,ct) = case ctEvidence ct of CtWanted {ctev_evar = evar} -> setEvBind evar ev _ -> return () -runTcPluginsGiven :: Cts -> TcS (Cts, Bool) -runTcPluginsGiven givens = do +removeInertCts :: [Ct] -> InertCans -> InertCans +removeInertCts cts icans = foldl' removeInertCt icans cts + +-- Remove the constraint from the inert set. We use this either when: +-- * a wanted constraint was solved, or +-- * some constraint was marked as insoluable, and so it will be +-- put right back into InertSet, but in the insoluable section. +removeInertCt :: InertCans -> Ct -> InertCans +removeInertCt is ct = + case ct of + + CDictCan { cc_class = cl, cc_tyargs = tys } -> + is { inert_dicts = delDict (inert_dicts is) cl tys } + + CFunEqCan { cc_fun = tf, cc_tyargs = tys } -> + is { inert_funeqs = delFunEq (inert_funeqs is) tf tys } + + CTyEqCan { cc_tyvar = x, cc_rhs = ty } -> + is { inert_eqs = delTyEq (inert_eqs is) x ty } + + CIrredEvCan {} -> panic "runTcPlugin/removeInert: CIrredEvCan" + CNonCanonical {} -> panic "runTcPlugin/removeInert: CNonCanonical" + CHoleCan {} -> panic "runTcPlugin/removeInert: CHoleCan" + + +-- | Extract the (inert) givens and invoke the plugins on them, +-- removing solved givens from the inert set and emitting unsolvable +-- constraints as we go. Return new work produced by all the plugins, +-- so that 'solveFlatGivens' can feed it back into the main solver. +-- +-- It is slightly unfortunate that this doesn't quite line up with +-- 'runTcPluginsWanted'... +runTcPluginsGiven :: TcS [Ct] +runTcPluginsGiven = do gblEnv <- getGblEnv - foldM f (givens, False) (tcg_tc_plugins gblEnv) + (givens,_,_) <- fmap splitInertCans getInertCans + fmap snd $ foldM f (givens, []) (tcg_tc_plugins gblEnv) where - f :: (Cts, Bool) -> TcPluginSolver -> TcS (Cts, Bool) - f (givens, rerun) solver = do - result <- runTcPluginTcS (solver (bagToList givens) [] []) + f :: ([Ct], [Ct]) -> TcPluginSolver -> TcS ([Ct], [Ct]) + f (old_givens, new_givens) solver = do + result <- runTcPluginTcS (solver old_givens [] []) case result of TcPluginContradiction bad_cts -> do mapM_ emitInsoluble bad_cts - return (discard bad_cts givens, rerun) - TcPluginOk [] [] -> return (givens, rerun) - TcPluginOk [] new_cts -> do - let new_facts = [ct | ct <- new_cts, not (any (eqCt ct) (bagToList givens))] - updWorkListTcS (extendWorkListCts new_facts) - return ( unionBags givens (listToBag new_facts) - , rerun || notNull new_facts) - TcPluginOk _solved_cts _new_cts -> - panic "runTcPluginsGiven: plugin solved a given constraint" + return (discard bad_cts old_givens, new_givens) + TcPluginOk solved_cts new_cts -> do + updInertCans (removeInertCts $ map snd solved_cts) + let new_facts = [ct | ct <- new_cts, not (any (eqCt ct) old_givens)] + return ( discard (map snd solved_cts) old_givens + , new_facts ++ new_givens) where - discard cs = filterBag (\ c -> not $ any (eqCt c) cs) + discard ys xs = deleteFirstsBy eqCt xs ys eqCt c c' = ctEvPred (ctEvidence c) `eqType` ctEvPred (ctEvidence c') +-- | Given a bag of (flattened, zonked) wanteds, invoke the plugins on +-- them and produce an updated bag of wanteds. If the boolean is +-- 'True', these should be fed back into the main solver. runTcPluginsWanted :: Cts -> TcS (Cts, Bool) runTcPluginsWanted zonked_wanteds = do gblEnv <- getGblEnv From git at git.haskell.org Mon Nov 17 17:43:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Nov 2014 17:43:51 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins-amg: separate tcplugin passes for improving givens vs solving wanteds (85487f3) Message-ID: <20141117174351.D96DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins-amg Link : http://ghc.haskell.org/trac/ghc/changeset/85487f37c1bf3fb8819db48a642f3564dc150643/ghc >--------------------------------------------------------------- commit 85487f37c1bf3fb8819db48a642f3564dc150643 Author: Eric Seidel Date: Sun Nov 16 10:45:29 2014 -0800 separate tcplugin passes for improving givens vs solving wanteds >--------------------------------------------------------------- 85487f37c1bf3fb8819db48a642f3564dc150643 compiler/typecheck/TcInteract.lhs | 117 +++++++++++++++----------------------- compiler/typecheck/TcRnTypes.lhs | 3 +- 2 files changed, 46 insertions(+), 74 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 85487f37c1bf3fb8819db48a642f3564dc150643 From git at git.haskell.org Tue Nov 18 01:19:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 01:19:58 +0000 (UTC) Subject: [commit: ghc] master: document addDependentFile uses contents, not mtime (0515055) Message-ID: <20141118011958.0A2E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0515055abfcf5957d7a957607b4785320627fd65/ghc >--------------------------------------------------------------- commit 0515055abfcf5957d7a957607b4785320627fd65 Author: Greg Weber Date: Mon Nov 17 19:15:51 2014 -0600 document addDependentFile uses contents, not mtime Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D481 GHC Trac Issues: #4900 >--------------------------------------------------------------- 0515055abfcf5957d7a957607b4785320627fd65 libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index ddbe3a9..48199a4 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -377,9 +377,16 @@ runIO :: IO a -> Q a runIO m = Q (qRunIO m) -- | Record external files that runIO is using (dependent upon). --- The compiler can then recognize that it should re-compile the file using this TH when the external file changes. --- Note that ghc -M will still not know about these dependencies - it does not execute TH. +-- The compiler can then recognize that it should re-compile the Haskell file +-- when an external file changes. +-- -- Expects an absolute file path. +-- +-- Notes: +-- +-- * ghc -M does not know about these dependencies - it does not execute TH. +-- +-- * The dependency is based on file content, not a modification time addDependentFile :: FilePath -> Q () addDependentFile fp = Q (qAddDependentFile fp) From git at git.haskell.org Tue Nov 18 01:20:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 01:20:00 +0000 (UTC) Subject: [commit: ghc] master: Don't use absolute paths for perl in validate (d997ca8) Message-ID: <20141118012000.9CF6D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d997ca85a33f34f9f461096eb1b25d5f25b53072/ghc >--------------------------------------------------------------- commit d997ca85a33f34f9f461096eb1b25d5f25b53072 Author: Mateusz Kowalczyk Date: Mon Nov 17 19:15:59 2014 -0600 Don't use absolute paths for perl in validate Summary: This will *not* work on NixOS for example. Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D479 GHC Trac Issues: #9057 >--------------------------------------------------------------- d997ca85a33f34f9f461096eb1b25d5f25b53072 validate | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/validate b/validate index 7464be9..5954e96 100755 --- a/validate +++ b/validate @@ -157,9 +157,9 @@ if [ $no_clean -eq 0 ]; then fi if [ $use_dph -eq 1 ]; then - /usr/bin/perl -w boot --validate --required-tag=dph + perl -w boot --validate --required-tag=dph else - /usr/bin/perl -w boot --validate + perl -w boot --validate fi ./configure --prefix="$INSTDIR" $config_args fi @@ -299,4 +299,3 @@ Please fix them before pushing/sending patches. EOF exit 1 fi - From git at git.haskell.org Tue Nov 18 01:20:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 01:20:03 +0000 (UTC) Subject: [commit: ghc] master: Remove outdated TODO in TimeManager (a520761) Message-ID: <20141118012003.47A7C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a520761d065a84838896e8dd09d8aaec77480d60/ghc >--------------------------------------------------------------- commit a520761d065a84838896e8dd09d8aaec77480d60 Author: Yuras Shumovich Date: Mon Nov 17 19:16:08 2014 -0600 Remove outdated TODO in TimeManager Summary: It describes a work around Trac #3838, but it is already fixed and the workaround removed, Trac #7653 Test Plan: not needed Reviewers: hvr, Mikolaj, austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D478 >--------------------------------------------------------------- a520761d065a84838896e8dd09d8aaec77480d60 libraries/base/GHC/Event/TimerManager.hs | 26 -------------------------- 1 file changed, 26 deletions(-) diff --git a/libraries/base/GHC/Event/TimerManager.hs b/libraries/base/GHC/Event/TimerManager.hs index bf6339a..c1ab64c 100644 --- a/libraries/base/GHC/Event/TimerManager.hs +++ b/libraries/base/GHC/Event/TimerManager.hs @@ -81,32 +81,6 @@ data State = Created -- | A priority search queue, with timeouts as priorities. type TimeoutQueue = Q.PSQ TimeoutCallback -{- -Instead of directly modifying the 'TimeoutQueue' in -e.g. 'registerTimeout' we keep a list of edits to perform, in the form -of a chain of function closures, and have the I/O manager thread -perform the edits later. This exist to address the following GC -problem: - -Since e.g. 'registerTimeout' doesn't force the evaluation of the -thunks inside the 'emTimeouts' IORef a number of thunks build up -inside the IORef. If the I/O manager thread doesn't evaluate these -thunks soon enough they'll get promoted to the old generation and -become roots for all subsequent minor GCs. - -When the thunks eventually get evaluated they will each create a new -intermediate 'TimeoutQueue' that immediately becomes garbage. Since -the thunks serve as roots until the next major GC these intermediate -'TimeoutQueue's will get copied unnecessarily in the next minor GC, -increasing GC time. This problem is known as "floating garbage". - -Keeping a list of edits doesn't stop this from happening but makes the -amount of data that gets copied smaller. - -TODO: Evaluate the content of the IORef to WHNF on each insert once -this bug is resolved: http://ghc.haskell.org/trac/ghc/ticket/3838 --} - -- | An edit to apply to a 'TimeoutQueue'. type TimeoutEdit = TimeoutQueue -> TimeoutQueue From git at git.haskell.org Tue Nov 18 01:20:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 01:20:08 +0000 (UTC) Subject: [commit: ghc] master: Docs only (df22507) Message-ID: <20141118012008.8FC9D3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/df22507fef86407de35a89294ca901056dfde37a/ghc >--------------------------------------------------------------- commit df22507fef86407de35a89294ca901056dfde37a Author: Edward Z. Yang Date: Mon Nov 17 19:19:00 2014 -0600 Docs only Summary: Signed-off-by: Edward Z. Yang Test Plan: n/a Reviewers: austin, Mikolaj Reviewed By: austin, Mikolaj Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D446 >--------------------------------------------------------------- df22507fef86407de35a89294ca901056dfde37a compiler/deSugar/DsMonad.lhs | 2 +- compiler/iface/LoadIface.lhs | 7 +++++-- compiler/iface/TcIface.lhs | 4 ++-- compiler/typecheck/TcRnMonad.lhs | 3 +++ compiler/typecheck/TcRnTypes.lhs | 27 ++++++++++++++++++++------- 5 files changed, 31 insertions(+), 12 deletions(-) diff --git a/compiler/deSugar/DsMonad.lhs b/compiler/deSugar/DsMonad.lhs index c017a7c..1c707c4 100644 --- a/compiler/deSugar/DsMonad.lhs +++ b/compiler/deSugar/DsMonad.lhs @@ -221,7 +221,7 @@ initDs hsc_env mod rdr_env type_env fam_inst_env thing_inside } where -- Extend the global environment with a 'GlobalRdrEnv' containing the exported entities of - -- * 'Data.Array.Parallel' iff '-XParallalArrays' specified (see also 'checkLoadDAP'). + -- * 'Data.Array.Parallel' iff '-XParallelArrays' specified (see also 'checkLoadDAP'). -- * 'Data.Array.Parallel.Prim' iff '-fvectorise' specified. loadDAP thing_inside = do { dapEnv <- loadOneModule dATA_ARRAY_PARALLEL_NAME checkLoadDAP paErr diff --git a/compiler/iface/LoadIface.lhs b/compiler/iface/LoadIface.lhs index faaea6c..3b2f7f2 100644 --- a/compiler/iface/LoadIface.lhs +++ b/compiler/iface/LoadIface.lhs @@ -92,7 +92,7 @@ loadSrcInterface doc mod want_boot maybe_pkg Failed err -> failWithTc err Succeeded iface -> return iface } --- | Like loadSrcInterface, but returns a MaybeErr +-- | Like 'loadSrcInterface', but returns a 'MaybeErr'. loadSrcInterface_maybe :: SDoc -> ModuleName -> IsBootInterface -- {-# SOURCE #-} ? @@ -111,7 +111,10 @@ loadSrcInterface_maybe doc mod want_boot maybe_pkg Found _ mod -> initIfaceTcRn $ loadInterface doc mod (ImportByUser want_boot) err -> return (Failed (cannotFindInterface (hsc_dflags hsc_env) mod err)) } --- | Load interface for a module. +-- | Load interface directly for a fully qualified 'Module'. (This is a fairly +-- rare operation, but in particular it is used to load orphan modules +-- in order to pull their instances into the global package table and to +-- handle some operations in GHCi). loadModuleInterface :: SDoc -> Module -> TcM ModIface loadModuleInterface doc mod = initIfaceTcRn (loadSysInterface doc mod) diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index cabf311..85ea0f9 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -184,9 +184,9 @@ We need to make sure that we have at least *read* the interface files for any module with an instance decl or RULE that we might want. * If the instance decl is an orphan, we have a whole separate mechanism - (loadOprhanModules) + (loadOrphanModules) -* If the instance decl not an orphan, then the act of looking at the +* If the instance decl is not an orphan, then the act of looking at the TyCon or Class will force in the defining module for the TyCon/Class, and hence the instance decl diff --git a/compiler/typecheck/TcRnMonad.lhs b/compiler/typecheck/TcRnMonad.lhs index cd41499..1088c84 100644 --- a/compiler/typecheck/TcRnMonad.lhs +++ b/compiler/typecheck/TcRnMonad.lhs @@ -1250,6 +1250,9 @@ mkIfLclEnv mod loc = IfLclEnv { if_mod = mod, if_tv_env = emptyUFM, if_id_env = emptyUFM } +-- | Run an 'IfG' (top-level interface monad) computation inside an existing +-- 'TcRn' (typecheck-renaming monad) computation by initializing an 'IfGblEnv' +-- based on 'TcGblEnv'. initIfaceTcRn :: IfG a -> TcRn a initIfaceTcRn thing_inside = do { tcg_env <- getGblEnv diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index e1762a8..2634aa8 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -143,7 +143,11 @@ import qualified Language.Haskell.TH as TH The monad itself has to be defined here, because it is mentioned by ErrCtxt \begin{code} +-- | Type alias for 'IORef'; the convention is we'll use this for mutable +-- bits of data in 'TcGblEnv' which are updated during typechecking and +-- returned at the end. type TcRef a = IORef a +-- ToDo: when should I refer to it as a 'TcId' instead of an 'Id'? type TcId = Id type TcIdSet = IdSet @@ -153,9 +157,19 @@ type IfM lcl = TcRnIf IfGblEnv lcl -- Iface stuff type IfG = IfM () -- Top level type IfL = IfM IfLclEnv -- Nested + +-- | Type-checking and renaming monad: the main monad that most type-checking +-- takes place in. The global environment is 'TcGblEnv', which tracks +-- all of the top-level type-checking information we've accumulated while +-- checking a module, while the local environment is 'TcLclEnv', which +-- tracks local information as we move inside expressions. type TcRn = TcRnIf TcGblEnv TcLclEnv -type RnM = TcRn -- Historical -type TcM = TcRn -- Historical + +-- | Historical "renaming monad" (now it's just 'TcRn'). +type RnM = TcRn + +-- | Historical "type-checking monad" (now it's just 'TcRn'). +type TcM = TcRn \end{code} Representation of type bindings to uninstantiated meta variables used during @@ -203,12 +217,11 @@ instance ContainsDynFlags (Env gbl lcl) where instance ContainsModule gbl => ContainsModule (Env gbl lcl) where extractModule env = extractModule (env_gbl env) --- TcGblEnv describes the top-level of the module at the +-- | 'TcGblEnv' describes the top-level of the module at the -- point at which the typechecker is finished work. -- It is this structure that is handed on to the desugarer -- For state that needs to be updated during the typechecking --- phase and returned at end, use a TcRef (= IORef). - +-- phase and returned at end, use a 'TcRef' (= 'IORef'). data TcGblEnv = TcGblEnv { tcg_mod :: Module, -- ^ Module being compiled @@ -494,8 +507,8 @@ data IfLclEnv %* * %************************************************************************ -The Global-Env/Local-Env story -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Note [The Global-Env/Local-Env story] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ During type checking, we keep in the tcg_type_env * All types and classes * All Ids derived from types and classes (constructors, selectors) From git at git.haskell.org Tue Nov 18 01:20:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 01:20:05 +0000 (UTC) Subject: [commit: ghc] master: Make listArray fuse (bc68ed0) Message-ID: <20141118012005.E25B43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bc68ed02e52d8e1c201aff16c4464fd0ca53d0bc/ghc >--------------------------------------------------------------- commit bc68ed02e52d8e1c201aff16c4464fd0ca53d0bc Author: David Feuer Date: Mon Nov 17 19:16:16 2014 -0600 Make listArray fuse Summary: Make listArray fuse with a list producer. Note: if code size increases too much, we can fix that with some `RULES`. Reviewers: nomeata, hvr, austin, ekmett, simonmar, bgamari Reviewed By: bgamari Subscribers: bgamari, thomie, carter Differential Revision: https://phabricator.haskell.org/D474 GHC Trac Issues: #9801 >--------------------------------------------------------------- bc68ed02e52d8e1c201aff16c4464fd0ca53d0bc libraries/base/GHC/Arr.hs | 24 +++++++++++------------- 1 file changed, 11 insertions(+), 13 deletions(-) diff --git a/libraries/base/GHC/Arr.hs b/libraries/base/GHC/Arr.hs index 02bf7d8..e68c70f 100644 --- a/libraries/base/GHC/Arr.hs +++ b/libraries/base/GHC/Arr.hs @@ -468,12 +468,6 @@ done l u n@(I# _) marr# = \s1# -> case unsafeFreezeArray# marr# s1# of (# s2#, arr# #) -> (# s2#, Array l u n arr# #) --- This is inefficient and I'm not sure why: --- listArray (l,u) es = unsafeArray (l,u) (zip [0 .. rangeSize (l,u) - 1] es) --- The code below is better. It still doesn't enable foldr/build --- transformation on the list of elements; I guess it's impossible --- using mechanisms currently available. - -- | Construct an array from a pair of bounds and a list of values in -- index order. {-# INLINE listArray #-} @@ -481,13 +475,17 @@ listArray :: Ix i => (i,i) -> [e] -> Array i e listArray (l,u) es = runST (ST $ \s1# -> case safeRangeSize (l,u) of { n@(I# n#) -> case newArray# n# arrEleBottom s1# of { (# s2#, marr# #) -> - let fillFromList i# xs s3# | isTrue# (i# ==# n#) = s3# - | otherwise = case xs of - [] -> s3# - y:ys -> case writeArray# marr# i# y s3# of { s4# -> - fillFromList (i# +# 1#) ys s4# } in - case fillFromList 0# es s2# of { s3# -> - done l u n marr# s3# }}}) + let + go y r = \ i# s3# -> + case writeArray# marr# i# y s3# of + s4# -> if (isTrue# (i# ==# n# -# 1#)) + then s4# + else r (i# +# 1#) s4# + in + done l u n marr# ( + if n == 0 + then s2# + else foldr go (\_ s# -> s#) es 0# s2#)}}) -- | The value at the given index in an array. {-# INLINE (!) #-} From git at git.haskell.org Tue Nov 18 01:20:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 01:20:12 +0000 (UTC) Subject: [commit: ghc] master: Adding dedicated Show instances for SrcSpan/SrcLoc (ce2cc64) Message-ID: <20141118012012.05DC43A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ce2cc64f0b4c447bf83fd0d0b260f00126a0c4d6/ghc >--------------------------------------------------------------- commit ce2cc64f0b4c447bf83fd0d0b260f00126a0c4d6 Author: Alan Zimmerman Date: Mon Nov 17 19:19:10 2014 -0600 Adding dedicated Show instances for SrcSpan/SrcLoc Summary: The derived Show instances for SrcSpan and SrcLoc are very verbose. This patch replaces them with hand-made ones which use positional syntax for the record constructors, rather than exhaustively listing each one. Test Plan: sh ./validate Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D445 >--------------------------------------------------------------- ce2cc64f0b4c447bf83fd0d0b260f00126a0c4d6 compiler/basicTypes/SrcLoc.lhs | 20 +++++++++++-- .../ghc-api/{landmines => show-srcspan}/.gitignore | 2 +- testsuite/tests/ghc-api/show-srcspan/Makefile | 13 +++++++++ testsuite/tests/ghc-api/show-srcspan/all.T | 1 + .../tests/ghc-api/show-srcspan/showsrcspan.hs | 33 ++++++++++++++++++++++ .../tests/ghc-api/show-srcspan/showsrcspan.stdout | 7 +++++ 6 files changed, 72 insertions(+), 4 deletions(-) diff --git a/compiler/basicTypes/SrcLoc.lhs b/compiler/basicTypes/SrcLoc.lhs index 6b46454..c7e1fbe 100644 --- a/compiler/basicTypes/SrcLoc.lhs +++ b/compiler/basicTypes/SrcLoc.lhs @@ -99,11 +99,11 @@ data RealSrcLoc = SrcLoc FastString -- A precise location (file name) {-# UNPACK #-} !Int -- line number, begins at 1 {-# UNPACK #-} !Int -- column number, begins at 1 - deriving Show data SrcLoc = RealSrcLoc {-# UNPACK #-}!RealSrcLoc | UnhelpfulLoc FastString -- Just a general indication + deriving Show \end{code} %************************************************************************ @@ -259,8 +259,7 @@ data RealSrcSpan srcSpanLine :: {-# UNPACK #-} !Int, srcSpanCol :: {-# UNPACK #-} !Int } - deriving (Eq, Typeable, Show) -- Show is used by Lexer.x, because we - -- derive Show for Token + deriving (Eq, Typeable) data SrcSpan = RealSrcSpan !RealSrcSpan @@ -433,6 +432,21 @@ instance Ord SrcSpan where (srcSpanStart a `compare` srcSpanStart b) `thenCmp` (srcSpanEnd a `compare` srcSpanEnd b) +instance Show RealSrcLoc where + show (SrcLoc filename row col) + = "SrcLoc " ++ show filename ++ " " ++ show row ++ " " ++ show col + +-- Show is used by Lexer.x, because we derive Show for Token +instance Show RealSrcSpan where + show (SrcSpanOneLine file l sc ec) + = "SrcSpanOneLine " ++ show file ++ " " + ++ intercalate " " (map show [l,sc,ec]) + show (SrcSpanMultiLine file sl sc el ec) + = "SrcSpanMultiLine " ++ show file ++ " " + ++ intercalate " " (map show [sl,sc,el,ec]) + show (SrcSpanPoint file l c) + = "SrcSpanPoint " ++ show file ++ " " ++ intercalate " " (map show [l,c]) + instance Outputable RealSrcSpan where ppr span = pprUserRealSpan True span diff --git a/testsuite/tests/ghc-api/landmines/.gitignore b/testsuite/tests/ghc-api/show-srcspan/.gitignore similarity index 71% copy from testsuite/tests/ghc-api/landmines/.gitignore copy to testsuite/tests/ghc-api/show-srcspan/.gitignore index 1452e78..e135b85 100644 --- a/testsuite/tests/ghc-api/landmines/.gitignore +++ b/testsuite/tests/ghc-api/show-srcspan/.gitignore @@ -1,4 +1,4 @@ -landmines +showsrcspan *.hi *.o *.run.* diff --git a/testsuite/tests/ghc-api/show-srcspan/Makefile b/testsuite/tests/ghc-api/show-srcspan/Makefile new file mode 100644 index 0000000..e467b61 --- /dev/null +++ b/testsuite/tests/ghc-api/show-srcspan/Makefile @@ -0,0 +1,13 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +clean: + rm -f *.o *.hi + +showsrcspan: clean + '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc showsrcspan + ./showsrcspan "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" + + +.PHONY: clean diff --git a/testsuite/tests/ghc-api/show-srcspan/all.T b/testsuite/tests/ghc-api/show-srcspan/all.T new file mode 100644 index 0000000..fbb8d04 --- /dev/null +++ b/testsuite/tests/ghc-api/show-srcspan/all.T @@ -0,0 +1 @@ +test('showsrcspan', normal, run_command, ['$MAKE -s --no-print-directory showsrcspan']) \ No newline at end of file diff --git a/testsuite/tests/ghc-api/show-srcspan/showsrcspan.hs b/testsuite/tests/ghc-api/show-srcspan/showsrcspan.hs new file mode 100644 index 0000000..bf73b59 --- /dev/null +++ b/testsuite/tests/ghc-api/show-srcspan/showsrcspan.hs @@ -0,0 +1,33 @@ +module Main where + +import Data.Data +import System.IO +import GHC +import FastString +import SrcLoc +import MonadUtils +import Outputable +import Bag (filterBag,isEmptyBag) +import System.Directory (removeFile) +import System.Environment( getArgs ) + +main::IO() +main = do + let + loc1 = mkSrcLoc (mkFastString "filename") 1 3 + loc2 = mkSrcLoc (mkFastString "filename") 1 5 + loc3 = mkSrcLoc (mkFastString "filename") 10 1 + badLoc = mkGeneralSrcLoc (mkFastString "bad loc") + + pointSpan = mkSrcSpan loc1 loc1 + lineSpan = mkSrcSpan loc1 loc2 + multiSpan = mkSrcSpan loc2 loc3 + badSpan = mkGeneralSrcSpan (mkFastString "bad span") + + print $ show loc1 + print $ show loc2 + print $ show badLoc + print $ show pointSpan + print $ show lineSpan + print $ show multiSpan + print $ show badSpan diff --git a/testsuite/tests/ghc-api/show-srcspan/showsrcspan.stdout b/testsuite/tests/ghc-api/show-srcspan/showsrcspan.stdout new file mode 100644 index 0000000..f896565 --- /dev/null +++ b/testsuite/tests/ghc-api/show-srcspan/showsrcspan.stdout @@ -0,0 +1,7 @@ +"RealSrcLoc SrcLoc \"filename\" 1 3" +"RealSrcLoc SrcLoc \"filename\" 1 5" +"UnhelpfulLoc \"bad loc\"" +"RealSrcSpan SrcSpanPoint \"filename\" 1 3" +"RealSrcSpan SrcSpanOneLine \"filename\" 1 3 5" +"RealSrcSpan SrcSpanMultiLine \"filename\" 1 5 10 1" +"UnhelpfulSpan \"bad span\"" From git at git.haskell.org Tue Nov 18 01:20:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 01:20:14 +0000 (UTC) Subject: [commit: ghc] master: Change a comment referring falsely to seq (74a6a8a) Message-ID: <20141118012014.9A5743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/74a6a8a979837d1344fc3236ad6fc4ca76ea49a7/ghc >--------------------------------------------------------------- commit 74a6a8a979837d1344fc3236ad6fc4ca76ea49a7 Author: David Feuer Date: Mon Nov 17 19:19:18 2014 -0600 Change a comment referring falsely to seq Summary: Instead, describe what it actually does. Reviewers: austin, ekmett, simonpj, hvr Reviewed By: austin, ekmett Subscribers: simonpj, thomie, carter Projects: #ghc Differential Revision: https://phabricator.haskell.org/D448 >--------------------------------------------------------------- 74a6a8a979837d1344fc3236ad6fc4ca76ea49a7 libraries/base/GHC/Base.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index f2a447d..25596e0 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -1029,7 +1029,10 @@ flip f x y = f y x ($) :: (a -> b) -> a -> b f $ x = f x --- | Strict (call-by-value) application, defined in terms of 'seq'. +-- | Strict (call-by-value) application operator. It takes a function and an +-- argument, evaluates the argument to weak head normal form (WHNF), then calls +-- the function with that value. + ($!) :: (a -> b) -> a -> b f $! x = let !vx = x in f vx -- see #2273 From git at git.haskell.org Tue Nov 18 04:37:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 04:37:12 +0000 (UTC) Subject: [commit: ghc] master: Remove optimized package lookup, simplifying code. (44f1582) Message-ID: <20141118043712.36F503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/44f1582e99e3ca6710279e3dacea91d4166ecec6/ghc >--------------------------------------------------------------- commit 44f1582e99e3ca6710279e3dacea91d4166ecec6 Author: Edward Z. Yang Date: Sat Nov 15 01:43:42 2014 -0800 Remove optimized package lookup, simplifying code. Summary: A while back when I was refactoring the package code, I tried to solve a performance problem by introducing a fastpath for module lookups. Well, it turned out the performance problem was unrelated, but I kept the optimization because it seemed vaguely useful. In this commit, I remove the optimization because I don't really think it's buying us much and it increased code complexity. ToDo: Inline mkModuleToPkgConfGeneric into mkModuleToPkgConfAll Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D434 >--------------------------------------------------------------- 44f1582e99e3ca6710279e3dacea91d4166ecec6 compiler/main/Packages.lhs | 50 +--------------------------------------------- 1 file changed, 1 insertion(+), 49 deletions(-) diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs index d757461..519353e 100644 --- a/compiler/main/Packages.lhs +++ b/compiler/main/Packages.lhs @@ -210,17 +210,6 @@ originEmpty :: ModuleOrigin -> Bool originEmpty (ModOrigin Nothing [] [] False) = True originEmpty _ = False --- | When we do a plain lookup (e.g. for an import), initially, all we want --- to know is if we can find it or not (and if we do and it's a reexport, --- what the real name is). If the find fails, we'll want to investigate more --- to give a good error message. -data SimpleModuleConf = - SModConf Module PackageConfig ModuleOrigin - | SModConfAmbiguous - --- | 'UniqFM' map from 'ModuleName' -type ModuleNameMap = UniqFM - -- | 'UniqFM' map from 'PackageKey' type PackageKeyMap = UniqFM @@ -252,10 +241,6 @@ data PackageState = PackageState { -- is always mentioned before the packages it depends on. preloadPackages :: [PackageKey], - -- | This is a simplified map from 'ModuleName' to original 'Module' and - -- package configuration providing it. - moduleToPkgConf :: ModuleNameMap SimpleModuleConf, - -- | This is a full map from 'ModuleName' to all modules which may possibly -- be providing it. These providers may be hidden (but we'll still want -- to report them in error messages), or it may be an ambiguous import. @@ -996,7 +981,6 @@ mkPackageState dflags pkgs0 preload0 this_package = do let pstate = PackageState{ preloadPackages = dep_preload, pkgIdMap = pkg_db, - moduleToPkgConf = mkModuleToPkgConf dflags pkg_db ipid_map vis_map, moduleToPkgConfAll = mkModuleToPkgConfAll dflags pkg_db ipid_map vis_map, installedPackageIdMap = ipid_map } @@ -1070,29 +1054,6 @@ mkModuleToPkgConfGeneric emptyMap sing setOrigins addListTo exposed_mods = exposedModules pkg hidden_mods = hiddenModules pkg --- | This is a quick and efficient module map, which only contains an entry --- if it is specified unambiguously. -mkModuleToPkgConf - :: DynFlags - -> PackageConfigMap - -> InstalledPackageIdMap - -> VisibilityMap - -> ModuleNameMap SimpleModuleConf -mkModuleToPkgConf = - mkModuleToPkgConfGeneric emptyMap sing setOrigins addListTo - where emptyMap = emptyUFM - sing pk m pkg = SModConf (mkModule pk m) pkg - -- NB: don't put hidden entries in the map, they're not valid! - addListTo m xs = addListToUFM_C merge m (filter isVisible xs) - isVisible (_, SModConf _ _ o) = originVisible o - isVisible (_, SModConfAmbiguous) = False - merge (SModConf m pkg o) (SModConf m' _ o') - | m == m' = SModConf m pkg (o `mappend` o') - | otherwise = SModConfAmbiguous - merge _ _ = SModConfAmbiguous - setOrigins (SModConf m pkg _) os = SModConf m pkg os - setOrigins SModConfAmbiguous _ = SModConfAmbiguous - -- | This is a slow and complete map, which includes information about -- everything, including hidden modules mkModuleToPkgConfAll @@ -1240,17 +1201,11 @@ lookupModuleWithSuggestions :: DynFlags -> Maybe FastString -> LookupResult lookupModuleWithSuggestions dflags m mb_pn - = case lookupUFM (moduleToPkgConf pkg_state) m of - Just (SModConf m pkg o) | matches mb_pn pkg o -> - ASSERT( originVisible o ) LookupFound m pkg - _ -> case Map.lookup m (moduleToPkgConfAll pkg_state) of + = case Map.lookup m (moduleToPkgConfAll pkg_state) of Nothing -> LookupNotFound suggestions Just xs -> case foldl' classify ([],[],[]) (Map.toList xs) of ([], [], []) -> LookupNotFound suggestions - -- NB: Yes, we have to check this case too, since package qualified - -- imports could cause the main lookup to fail due to ambiguity, - -- but the second lookup to succeed. (_, _, [(m, _)]) -> LookupFound m (mod_pkg m) (_, _, exposed@(_:_)) -> LookupMultiple exposed (hidden_pkg, hidden_mod, []) -> LookupHidden hidden_pkg hidden_mod @@ -1268,9 +1223,6 @@ lookupModuleWithSuggestions dflags m mb_pn pkg_state = pkgState dflags mod_pkg = pkg_lookup . modulePackageKey - matches Nothing _ _ = True -- shortcut for efficiency - matches mb_pn pkg o = originVisible (filterOrigin mb_pn pkg o) - -- Filters out origins which are not associated with the given package -- qualifier. No-op if there is no package qualifier. Test if this -- excluded all origins with 'originEmpty'. From git at git.haskell.org Tue Nov 18 05:29:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 05:29:46 +0000 (UTC) Subject: [commit: ghc] master: Add a note why tcGetInstEnvs is duplicated. (b9096df) Message-ID: <20141118052946.5C7153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b9096df6a9733e38e15361e79973ef5659fc5c22/ghc >--------------------------------------------------------------- commit b9096df6a9733e38e15361e79973ef5659fc5c22 Author: Edward Z. Yang Date: Wed Nov 5 20:57:03 2014 -0800 Add a note why tcGetInstEnvs is duplicated. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- b9096df6a9733e38e15361e79973ef5659fc5c22 compiler/typecheck/TcEnv.lhs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/typecheck/TcEnv.lhs b/compiler/typecheck/TcEnv.lhs index bcd6bfd..0ef74a1 100644 --- a/compiler/typecheck/TcEnv.lhs +++ b/compiler/typecheck/TcEnv.lhs @@ -225,6 +225,7 @@ tcLookupInstance cls tys extractTyVar (TyVarTy tv) = tv extractTyVar _ = panic "TcEnv.tcLookupInstance: extractTyVar" + -- NB: duplicated to prevent circular dependence on Inst tcGetInstEnvs = do { eps <- getEps; env <- getGblEnv; ; return (eps_inst_env eps, tcg_inst_env env) } From git at git.haskell.org Tue Nov 18 09:44:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 09:44:15 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T8558' created Message-ID: <20141118094415.952183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T8558 Referencing: aa1c1b2a364e443ceb11b898cf3e648c14954fd9 From git at git.haskell.org Tue Nov 18 09:44:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 09:44:18 +0000 (UTC) Subject: [commit: ghc] wip/T8558: Build xhtml and haddock only when `HADDOCK_DOCS=YES` (aa1c1b2) Message-ID: <20141118094418.3F8B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8558 Link : http://ghc.haskell.org/trac/ghc/changeset/aa1c1b2a364e443ceb11b898cf3e648c14954fd9/ghc >--------------------------------------------------------------- commit aa1c1b2a364e443ceb11b898cf3e648c14954fd9 Author: Joachim Breitner Date: Tue Nov 18 10:44:23 2014 +0100 Build xhtml and haddock only when `HADDOCK_DOCS=YES` This fixes #8558 >--------------------------------------------------------------- aa1c1b2a364e443ceb11b898cf3e648c14954fd9 ghc.mk | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/ghc.mk b/ghc.mk index 587152d..1e8ea58 100644 --- a/ghc.mk +++ b/ghc.mk @@ -425,7 +425,10 @@ PACKAGES_STAGE2 += haskell98 PACKAGES_STAGE2 += haskell2010 endif +ifeq "$(HADDOCK_DOCS)" "YES" PACKAGES_STAGE1 += xhtml +endif + ifeq "$(Windows_Target)" "NO" ifneq "$(TargetOS_CPP)" "ios" PACKAGES_STAGE1 += terminfo @@ -665,8 +668,11 @@ else ifneq "$(findstring clean,$(MAKECMDGOALS))" "" BUILD_DIRS += libraries/integer-gmp2/gmp endif +ifeq "$(HADDOCK_DOCS)" "YES" BUILD_DIRS += utils/haddock BUILD_DIRS += utils/haddock/doc +endif + BUILD_DIRS += compiler BUILD_DIRS += utils/hsc2hs BUILD_DIRS += utils/ghc-pkg From git at git.haskell.org Tue Nov 18 11:30:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 11:30:03 +0000 (UTC) Subject: [commit: ghc] master's head updated: Build xhtml and haddock only when `HADDOCK_DOCS=YES` (aa1c1b2) Message-ID: <20141118113003.382343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: aa1c1b2 Build xhtml and haddock only when `HADDOCK_DOCS=YES` From git at git.haskell.org Tue Nov 18 12:16:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 12:16:16 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins-amg: Trivial changes to clean up typechecker plugins diff (7a0e27f) Message-ID: <20141118121616.4FCDF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins-amg Link : http://ghc.haskell.org/trac/ghc/changeset/7a0e27f930b0bfe4e76cd326e4e137fff482d738/ghc >--------------------------------------------------------------- commit 7a0e27f930b0bfe4e76cd326e4e137fff482d738 Author: Adam Gundry Date: Tue Nov 18 10:09:34 2014 +0000 Trivial changes to clean up typechecker plugins diff >--------------------------------------------------------------- 7a0e27f930b0bfe4e76cd326e4e137fff482d738 compiler/ghc.mk | 1 + compiler/ghci/RtClosureInspect.hs | 2 -- compiler/main/DynFlags.hs | 9 ++++----- compiler/main/DynamicLoading.hs | 6 +++--- compiler/typecheck/TcRnDriver.lhs | 1 - compiler/typecheck/TcRnMonad.lhs | 13 +------------ compiler/typecheck/TcRnTypes.lhs | 1 - 7 files changed, 9 insertions(+), 24 deletions(-) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index 69ab4fc..b5f5dbc 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -589,6 +589,7 @@ compiler_stage2_dll0_MODULES = \ Var \ VarEnv \ VarSet + ifeq "$(GhcWithInterpreter)" "YES" # These files are reacheable from DynFlags # only by GHCi-enabled code (see #9552) diff --git a/compiler/ghci/RtClosureInspect.hs b/compiler/ghci/RtClosureInspect.hs index a5bcf5d..1f751d1 100644 --- a/compiler/ghci/RtClosureInspect.hs +++ b/compiler/ghci/RtClosureInspect.hs @@ -568,8 +568,6 @@ runTR hsc_env thing = do runTR_maybe :: HscEnv -> TR a -> IO (Maybe a) runTR_maybe hsc_env thing_inside - -- When we initialize the type checker we do not load any pluguns. - -- Is that OK? = do { (_errs, res) <- initTc hsc_env HsSrcFile False (icInteractiveModule (hsc_IC hsc_env)) thing_inside diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index fbfd17e..0c6639a 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -719,7 +719,7 @@ data DynFlags = DynFlags { -- Plugins pluginModNames :: [ModuleName], - pluginModNameOpts :: [(ModuleName, String)], + pluginModNameOpts :: [(ModuleName,String)], -- GHC API hooks hooks :: Hooks, @@ -1880,8 +1880,7 @@ setSigOf :: String -> DynFlags -> DynFlags setSigOf s d = d { sigOf = parseSigOf s } addPluginModuleName :: String -> DynFlags -> DynFlags -addPluginModuleName name d = - d { pluginModNames = mkModuleName name : pluginModNames d } +addPluginModuleName name d = d { pluginModNames = (mkModuleName name) : (pluginModNames d) } addPluginModuleNameOption :: String -> DynFlags -> DynFlags addPluginModuleNameOption optflag d = d { pluginModNameOpts = (mkModuleName m, option) : (pluginModNameOpts d) } @@ -2455,8 +2454,8 @@ dynamic_flags = [ , Flag "w" (NoArg (upd (\dfs -> dfs {warningFlags = IntSet.empty}))) ------ Plugin flags ------------------------------------------------ - , Flag "fplugin-opt" (hasArg addPluginModuleNameOption) - , Flag "fplugin" (hasArg addPluginModuleName) + , Flag "fplugin-opt" (hasArg addPluginModuleNameOption) + , Flag "fplugin" (hasArg addPluginModuleName) ------ Optimisation flags ------------------------------------------ , Flag "O" (noArgM (setOptLevel 1)) diff --git a/compiler/main/DynamicLoading.hs b/compiler/main/DynamicLoading.hs index 87b97f2..2356c23 100644 --- a/compiler/main/DynamicLoading.hs +++ b/compiler/main/DynamicLoading.hs @@ -25,7 +25,7 @@ module DynamicLoading ( import Linker ( linkModule, getHValue ) import SrcLoc ( noSrcSpan ) import Finder ( findImportedModule, cannotFindModule ) -import TcRnMonad ( initTcDynamic, initIfaceTcRn ) +import TcRnMonad ( initTcInteractive, initIfaceTcRn ) import LoadIface ( loadPluginInterface ) import RdrName ( RdrName, Provenance(..), ImportSpec(..), ImpDeclSpec(..) , ImpItemSpec(..), mkGlobalRdrEnv, lookupGRE_RdrName @@ -96,7 +96,7 @@ loadPlugin hsc_env mod_name -- for debugging (@-ddump-if-trace@) only: it is shown as the reason why the module is being loaded. forceLoadModuleInterfaces :: HscEnv -> SDoc -> [Module] -> IO () forceLoadModuleInterfaces hsc_env doc modules - = (initTcDynamic hsc_env $ + = (initTcInteractive hsc_env $ initIfaceTcRn $ mapM_ (loadPluginInterface doc) modules) >> return () @@ -198,7 +198,7 @@ lookupRdrNameInModuleForPlugins hsc_env mod_name rdr_name = do case found_module of Found _ mod -> do -- Find the exports of the module - (_, mb_iface) <- initTcDynamic hsc_env $ + (_, mb_iface) <- initTcInteractive hsc_env $ initIfaceTcRn $ loadPluginInterface doc mod case mb_iface of diff --git a/compiler/typecheck/TcRnDriver.lhs b/compiler/typecheck/TcRnDriver.lhs index aed04c2..02d0026 100644 --- a/compiler/typecheck/TcRnDriver.lhs +++ b/compiler/typecheck/TcRnDriver.lhs @@ -377,7 +377,6 @@ implicitPreludeWarn \end{code} - %************************************************************************ %* * Import declarations diff --git a/compiler/typecheck/TcRnMonad.lhs b/compiler/typecheck/TcRnMonad.lhs index d3b3502..19bd602 100644 --- a/compiler/typecheck/TcRnMonad.lhs +++ b/compiler/typecheck/TcRnMonad.lhs @@ -72,7 +72,6 @@ import qualified Data.Map as Map \begin{code} - -- | Setup the initial typechecking environment initTc :: HscEnv -> HscSource @@ -207,22 +206,12 @@ initTc hsc_env hsc_src keep_rn_syntax mod do_this initTcInteractive :: HscEnv -> TcM a -> IO (Messages, Maybe a) --- ^ Initialise the type checker monad for use in GHCi; the --- thing_inside is responsible for loading plugins +-- Initialise the type checker monad for use in GHCi initTcInteractive hsc_env thing_inside = initTc hsc_env HsSrcFile False (icInteractiveModule (hsc_IC hsc_env)) thing_inside -initTcDynamic :: HscEnv -> TcM a -> IO (Messages, Maybe a) --- ^ Initialise the type checker for use in in dynamic loading; note --- that plugins will not be loaded -initTcDynamic hsc_env thing_inside - = initTc hsc_env HsSrcFile False - (icInteractiveModule (hsc_IC hsc_env)) - thing_inside - - initTcForLookup :: HscEnv -> TcM a -> IO a -- The thing_inside is just going to look up something -- in the environment, so we don't need much setup diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index 3e0c053..cc76c03 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -2031,4 +2031,3 @@ data TcPluginResult -- the constraint solver. \end{code} - From git at git.haskell.org Tue Nov 18 12:16:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 12:16:18 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins-amg: Remove an unused lhs-boot file (c0f657f) Message-ID: <20141118121618.D80B43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins-amg Link : http://ghc.haskell.org/trac/ghc/changeset/c0f657fd2549719b2959dbf93fcd744c02427a5c/ghc >--------------------------------------------------------------- commit c0f657fd2549719b2959dbf93fcd744c02427a5c Author: Adam Gundry Date: Tue Nov 18 10:14:43 2014 +0000 Remove an unused lhs-boot file >--------------------------------------------------------------- c0f657fd2549719b2959dbf93fcd744c02427a5c compiler/typecheck/TcRnTypes.lhs-boot | 13 ------------- 1 file changed, 13 deletions(-) diff --git a/compiler/typecheck/TcRnTypes.lhs-boot b/compiler/typecheck/TcRnTypes.lhs-boot deleted file mode 100644 index 8a5ee15..0000000 --- a/compiler/typecheck/TcRnTypes.lhs-boot +++ /dev/null @@ -1,13 +0,0 @@ -\begin{code} -module TcRnTypes where - -import IOEnv - -type TcM = TcRn -type TcRn = TcRnIf TcGblEnv TcLclEnv -type TcRnIf a b = IOEnv (Env a b) - -data Env a b -data TcGblEnv -data TcLclEnv -\end{code} From git at git.haskell.org Tue Nov 18 12:16:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 12:16:22 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins-amg: Merge remote-tracking branch 'origin/master' into wip/tc-plugins-amg (7b24feb) Message-ID: <20141118121622.17B7C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins-amg Link : http://ghc.haskell.org/trac/ghc/changeset/7b24febb2afc92289846a1ff7593d9a4ae2b61d1/ghc >--------------------------------------------------------------- commit 7b24febb2afc92289846a1ff7593d9a4ae2b61d1 Merge: c0f657f b9096df Author: Adam Gundry Date: Tue Nov 18 10:17:22 2014 +0000 Merge remote-tracking branch 'origin/master' into wip/tc-plugins-amg >--------------------------------------------------------------- Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7b24febb2afc92289846a1ff7593d9a4ae2b61d1 From git at git.haskell.org Tue Nov 18 12:16:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 12:16:24 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins-amg's head updated: Merge remote-tracking branch 'origin/master' into wip/tc-plugins-amg (7b24feb) Message-ID: <20141118121624.873953A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/tc-plugins-amg' now includes: 8710136 Move Data.Functor.Identity from transformers to base 7ae596a Typo fix; Trac #9787 4923cea Define list monad operations using comprehensions e567130 De-bias Data.Foldable and improve docstrings 97420b0 Comments only (on recursive dictionaries) ed57ea4 Test Trac #9662 e9d3e28 Comments only 7cbe34f Improve documentation of -ticky a little 13817f0 Test Trac #9077 2b67b8f Test Trac #7862 76d47ed Add stderr for T9662 fcfc87d Disable T4801/peak_megabytes_allocated c774b28 Implement new integer-gmp2 from scratch (re #9281) d70b19b Per-thread allocation counters and limits 4b5d62a Fix build errors on Windows (these tests still don't work though) 8c10b67 fix allocLimit3 on Windows 1d35c85 Test #9066 in th/T9066 d782694 Fix #9066. f61b3c4 Untabify template-haskell. 1d66167 Remove unboxed Int# fields from NameFlavour (#9527) 88a42be Derive Generic for TH types (#9527) 767feb3 Test #8100 in th/T8100 4ac9e90 Fix #8100, by adding StandaloneDerivD to TH's Dec type. fe71a7e Test #9064 in th/T9064 e4efb7b Fix #9064 by adding support for generic default signatures to TH. ec8781f Test #9204 in roles/should_fail/T9204 ee0f34d Fix #9204 by outputting extra info on boot file mismatch. 90a2bb6 Testsuite wibbles due to #9204 294ac47 Fix #9788 by giving `coerce` the right type. e6e45a1 Test #9404 (typecheck/should_compile/T9404 and T9404b) fe6a517 Testsuite wibble due to #9404 1e2002d Fix #9404 by removing tcInfExpr. c65221b includes/Stg.h: define _DEFAULT_SOURCE for glibc-2.20 064c289 Remove a stray Trustworthy flag in ghc. 1f8b4ee Add in `-fwarn-trustworthy-safe` flag. 475dd93 Add `--fwarn-trustworthy-safe` to `-Wall` 8fe2bbe Update userguide for new `-fwarn-trustworthy-safe` flag. 413c747 base: Fix map/coerce comment e73ab54 Make unwords and words fuse somewhat c016e6f base: define `sequence = mapM id` 212a350 Improve `Foldable` instance for `Array` 63a9d93 Fix `integer-gmp2` compilation with GMP 4.x (#9281) 9b30d9d Fix typo in panic message 745c4c0 Binding things matched by an unboxed pattern synonym should require a bang 7f92986 If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. Fixes #9732. 5fe872d Apply compulsory unfoldings during desugaring, except for `seq` which is special. See Note [Unfolding while desugaring] for the rationale. faeb0a6 nlHsTyApps: for applying a function both on type- and term-level arguments 6389911 When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments 603b7be Implement amap/coerce for Array (re #9796) fa75309 Update .mailmap 452d6aa Partially revert 475dd93efa e14a973 Generalize exposed-modules field in installed package database 1854825 Workaround 452d6aa95b7 breaking TrustworthySafe03 609cd28 Update to (unreleased) `deepseq-1.4.0.0` c45e2e2 Fix compilation of `integer-gmp2` with `-O0` a2c0a8d Update validate settings now that containers and process have been updated to handle `-fwarn-trustworthy-safe`. 2a6f193 Fix a bug introduced with allocation counters 0515055 document addDependentFile uses contents, not mtime d997ca8 Don't use absolute paths for perl in validate a520761 Remove outdated TODO in TimeManager bc68ed0 Make listArray fuse df22507 Docs only ce2cc64 Adding dedicated Show instances for SrcSpan/SrcLoc 74a6a8a Change a comment referring falsely to seq 44f1582 Remove optimized package lookup, simplifying code. b9096df Add a note why tcGetInstEnvs is duplicated. 7a0e27f Trivial changes to clean up typechecker plugins diff c0f657f Remove an unused lhs-boot file 7b24feb Merge remote-tracking branch 'origin/master' into wip/tc-plugins-amg From git at git.haskell.org Tue Nov 18 12:36:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 12:36:39 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T8558' deleted Message-ID: <20141118123639.72F703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T8558 From git at git.haskell.org Tue Nov 18 13:45:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 13:45:25 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData2: Use TypeLits in the meta-data encoding of GHC.Generics (84a5fda) Message-ID: <20141118134525.E22B53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData2 Link : http://ghc.haskell.org/trac/ghc/changeset/84a5fda68f323b3fc639260af7b0b960f0be9644/ghc >--------------------------------------------------------------- commit 84a5fda68f323b3fc639260af7b0b960f0be9644 Author: Jose Pedro Magalhaes Date: Thu Oct 2 08:38:05 2014 +0100 Use TypeLits in the meta-data encoding of GHC.Generics The following wiki page contains more information about this: https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/GenericDeriving#Amoreconservativefirstapproachtothisproblem >--------------------------------------------------------------- 84a5fda68f323b3fc639260af7b0b960f0be9644 compiler/prelude/PrelNames.lhs | 59 ++-- compiler/typecheck/TcDeriv.lhs | 64 +---- compiler/typecheck/TcGenDeriv.lhs | 18 +- compiler/typecheck/TcGenGenerics.lhs | 304 +++++--------------- docs/users_guide/glasgow_exts.xml | 30 +- libraries/base/GHC/Generics.hs | 324 ++++++++++++---------- nofib | 2 +- testsuite/tests/generics/GShow/GShow.hs | 4 +- testsuite/tests/generics/GenDerivOutput.stderr | 120 ++++---- testsuite/tests/generics/GenDerivOutput1_0.stderr | 48 ++-- testsuite/tests/generics/GenDerivOutput1_1.stderr | 254 ++++++++--------- 11 files changed, 509 insertions(+), 718 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 84a5fda68f323b3fc639260af7b0b960f0be9644 From git at git.haskell.org Tue Nov 18 13:45:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 13:45:28 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData2's head updated: Use TypeLits in the meta-data encoding of GHC.Generics (84a5fda) Message-ID: <20141118134528.4D4653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/GenericsMetaData2' now includes: fcfc87d Disable T4801/peak_megabytes_allocated c774b28 Implement new integer-gmp2 from scratch (re #9281) d70b19b Per-thread allocation counters and limits 4b5d62a Fix build errors on Windows (these tests still don't work though) 8c10b67 fix allocLimit3 on Windows 1d35c85 Test #9066 in th/T9066 d782694 Fix #9066. f61b3c4 Untabify template-haskell. 1d66167 Remove unboxed Int# fields from NameFlavour (#9527) 88a42be Derive Generic for TH types (#9527) 767feb3 Test #8100 in th/T8100 4ac9e90 Fix #8100, by adding StandaloneDerivD to TH's Dec type. fe71a7e Test #9064 in th/T9064 e4efb7b Fix #9064 by adding support for generic default signatures to TH. ec8781f Test #9204 in roles/should_fail/T9204 ee0f34d Fix #9204 by outputting extra info on boot file mismatch. 90a2bb6 Testsuite wibbles due to #9204 294ac47 Fix #9788 by giving `coerce` the right type. e6e45a1 Test #9404 (typecheck/should_compile/T9404 and T9404b) fe6a517 Testsuite wibble due to #9404 1e2002d Fix #9404 by removing tcInfExpr. c65221b includes/Stg.h: define _DEFAULT_SOURCE for glibc-2.20 064c289 Remove a stray Trustworthy flag in ghc. 1f8b4ee Add in `-fwarn-trustworthy-safe` flag. 475dd93 Add `--fwarn-trustworthy-safe` to `-Wall` 8fe2bbe Update userguide for new `-fwarn-trustworthy-safe` flag. 413c747 base: Fix map/coerce comment e73ab54 Make unwords and words fuse somewhat c016e6f base: define `sequence = mapM id` 212a350 Improve `Foldable` instance for `Array` 63a9d93 Fix `integer-gmp2` compilation with GMP 4.x (#9281) 9b30d9d Fix typo in panic message 745c4c0 Binding things matched by an unboxed pattern synonym should require a bang 7f92986 If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. Fixes #9732. 5fe872d Apply compulsory unfoldings during desugaring, except for `seq` which is special. See Note [Unfolding while desugaring] for the rationale. faeb0a6 nlHsTyApps: for applying a function both on type- and term-level arguments 6389911 When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments 603b7be Implement amap/coerce for Array (re #9796) fa75309 Update .mailmap 452d6aa Partially revert 475dd93efa e14a973 Generalize exposed-modules field in installed package database 1854825 Workaround 452d6aa95b7 breaking TrustworthySafe03 609cd28 Update to (unreleased) `deepseq-1.4.0.0` c45e2e2 Fix compilation of `integer-gmp2` with `-O0` a2c0a8d Update validate settings now that containers and process have been updated to handle `-fwarn-trustworthy-safe`. 2a6f193 Fix a bug introduced with allocation counters 0515055 document addDependentFile uses contents, not mtime d997ca8 Don't use absolute paths for perl in validate a520761 Remove outdated TODO in TimeManager bc68ed0 Make listArray fuse df22507 Docs only ce2cc64 Adding dedicated Show instances for SrcSpan/SrcLoc 74a6a8a Change a comment referring falsely to seq 44f1582 Remove optimized package lookup, simplifying code. b9096df Add a note why tcGetInstEnvs is duplicated. aa1c1b2 Build xhtml and haddock only when `HADDOCK_DOCS=YES` 84a5fda Use TypeLits in the meta-data encoding of GHC.Generics From git at git.haskell.org Tue Nov 18 13:56:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 13:56:35 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData2: Use TypeLits in the meta-data encoding of GHC.Generics (ff91dc7) Message-ID: <20141118135635.721D43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData2 Link : http://ghc.haskell.org/trac/ghc/changeset/ff91dc71f4fffb2cc506e5ab5ce5c6a7bad4d7a4/ghc >--------------------------------------------------------------- commit ff91dc71f4fffb2cc506e5ab5ce5c6a7bad4d7a4 Author: Jose Pedro Magalhaes Date: Thu Oct 2 08:38:05 2014 +0100 Use TypeLits in the meta-data encoding of GHC.Generics The following wiki page contains more information about this: https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/GenericDeriving#Amoreconservativefirstapproachtothisproblem >--------------------------------------------------------------- ff91dc71f4fffb2cc506e5ab5ce5c6a7bad4d7a4 compiler/prelude/PrelNames.lhs | 59 ++-- compiler/typecheck/TcDeriv.lhs | 64 +---- compiler/typecheck/TcGenDeriv.lhs | 18 +- compiler/typecheck/TcGenGenerics.lhs | 304 +++++--------------- docs/users_guide/glasgow_exts.xml | 30 +- libraries/base/GHC/Generics.hs | 324 ++++++++++++---------- testsuite/tests/generics/GShow/GShow.hs | 4 +- testsuite/tests/generics/GenDerivOutput.stderr | 120 ++++---- testsuite/tests/generics/GenDerivOutput1_0.stderr | 48 ++-- testsuite/tests/generics/GenDerivOutput1_1.stderr | 254 ++++++++--------- 10 files changed, 508 insertions(+), 717 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ff91dc71f4fffb2cc506e5ab5ce5c6a7bad4d7a4 From git at git.haskell.org Tue Nov 18 15:40:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 15:40:27 +0000 (UTC) Subject: [commit: ghc] master: Fix ffi023 (9a20379) Message-ID: <20141118154027.A84AF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9a20379ee2305b5a74ad982585d46680f2b3439f/ghc >--------------------------------------------------------------- commit 9a20379ee2305b5a74ad982585d46680f2b3439f Author: Simon Marlow Date: Tue Nov 18 15:40:45 2014 +0000 Fix ffi023 >--------------------------------------------------------------- 9a20379ee2305b5a74ad982585d46680f2b3439f testsuite/tests/ffi/should_run/Makefile | 3 +++ testsuite/tests/ffi/should_run/all.T | 6 +++++- 2 files changed, 8 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/ffi/should_run/Makefile b/testsuite/tests/ffi/should_run/Makefile index 12e51b2..98d26fe 100644 --- a/testsuite/tests/ffi/should_run/Makefile +++ b/testsuite/tests/ffi/should_run/Makefile @@ -20,6 +20,9 @@ T5402_setup : T5594_setup : '$(TEST_HC)' $(TEST_HC_OPTS) -c T5594.hs +ffi023_setup : + '$(TEST_HC)' $(TEST_HC_OPTS) -c ffi023.hs + .PHONY: Capi_Ctype_001 Capi_Ctype_001: '$(HSC2HS)' Capi_Ctype_A_001.hsc diff --git a/testsuite/tests/ffi/should_run/all.T b/testsuite/tests/ffi/should_run/all.T index 0499631..0352f31 100644 --- a/testsuite/tests/ffi/should_run/all.T +++ b/testsuite/tests/ffi/should_run/all.T @@ -211,5 +211,9 @@ test('T8083', test('ffi023', [ omit_ways(['ghci']), extra_clean(['ffi023_c.o']), - extra_run_opts('1000 4') ], + extra_run_opts('1000 4'), + pre_cmd('$MAKE -s --no-print-directory ffi023_setup') ], + # The ffi023_setup hack is to ensure that we generate + # ffi023_stub.h before compiling ffi023_c.c, which + # needs it. compile_and_run, ['ffi023_c.c']) From git at git.haskell.org Tue Nov 18 16:59:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 16:59:15 +0000 (UTC) Subject: [commit: ghc] master: Outputable instance for IfaceVectInfo (ac1281f) Message-ID: <20141118165915.748A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ac1281f723364580e883c8e0eeffebdad12bcd0c/ghc >--------------------------------------------------------------- commit ac1281f723364580e883c8e0eeffebdad12bcd0c Author: Mateusz Kowalczyk Date: Tue Nov 18 16:58:56 2014 +0000 Outputable instance for IfaceVectInfo >--------------------------------------------------------------- ac1281f723364580e883c8e0eeffebdad12bcd0c compiler/main/HscTypes.lhs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs index c676b98..4d1cccb 100644 --- a/compiler/main/HscTypes.lhs +++ b/compiler/main/HscTypes.lhs @@ -2514,6 +2514,16 @@ instance Outputable VectInfo where , ptext (sLit "parallel tycons :") <+> ppr (vectInfoParallelTyCons info) ] +instance Outputable IfaceVectInfo where + ppr info = vcat + [ ptext (sLit "variables :") <+> ppr (ifaceVectInfoVar info) + , ptext (sLit "tycons :") <+> ppr (ifaceVectInfoTyCon info) + , ptext (sLit "tycons reuse :") <+> ppr (ifaceVectInfoTyConReuse info) + , ptext (sLit "parallel vars :") <+> ppr (ifaceVectInfoParallelVars info) + , ptext (sLit "parallel tycons :") <+> ppr (ifaceVectInfoParallelTyCons info) + ] + + instance Binary IfaceVectInfo where put_ bh (IfaceVectInfo a1 a2 a3 a4 a5) = do put_ bh a1 From git at git.haskell.org Tue Nov 18 16:59:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 16:59:18 +0000 (UTC) Subject: [commit: ghc] master: Whitespace only (20226c2) Message-ID: <20141118165918.2E8863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/20226c2ae8e95fad828ab1df97d993a717e2e788/ghc >--------------------------------------------------------------- commit 20226c2ae8e95fad828ab1df97d993a717e2e788 Author: Mateusz Kowalczyk Date: Tue Nov 18 16:58:45 2014 +0000 Whitespace only >--------------------------------------------------------------- 20226c2ae8e95fad828ab1df97d993a717e2e788 compiler/main/HscTypes.lhs | 0 1 file changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Tue Nov 18 17:08:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 17:08:14 +0000 (UTC) Subject: [commit: ghc] master: Add missing semicolon in Schedule.c (535644f) Message-ID: <20141118170814.609983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/535644facb7fb35baacd3e4fd0c8181eadb24379/ghc >--------------------------------------------------------------- commit 535644facb7fb35baacd3e4fd0c8181eadb24379 Author: Simon Peyton Jones Date: Tue Nov 18 17:07:41 2014 +0000 Add missing semicolon in Schedule.c I think this went wrong in 2a6f193b >--------------------------------------------------------------- 535644facb7fb35baacd3e4fd0c8181eadb24379 rts/Schedule.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/Schedule.c b/rts/Schedule.c index e9b0289..6a06f79 100644 --- a/rts/Schedule.c +++ b/rts/Schedule.c @@ -2234,7 +2234,7 @@ suspendThread (StgRegTable *reg, rtsBool interruptible) task->incall->suspended_cap = cap; // Otherwise allocate() will write to invalid memory. - cap->r.rCurrentTSO = NULL + cap->r.rCurrentTSO = NULL; ACQUIRE_LOCK(&cap->lock); From git at git.haskell.org Tue Nov 18 17:19:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 17:19:56 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData2: Use TypeLits in the meta-data encoding of GHC.Generics (013f62b) Message-ID: <20141118171956.70DF93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData2 Link : http://ghc.haskell.org/trac/ghc/changeset/013f62b5058797fb1ecd4449fe572a1f5204158e/ghc >--------------------------------------------------------------- commit 013f62b5058797fb1ecd4449fe572a1f5204158e Author: Jose Pedro Magalhaes Date: Thu Oct 2 08:38:05 2014 +0100 Use TypeLits in the meta-data encoding of GHC.Generics The following wiki page contains more information about this: https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/GenericDeriving#Amoreconservativefirstapproachtothisproblem >--------------------------------------------------------------- 013f62b5058797fb1ecd4449fe572a1f5204158e compiler/prelude/PrelNames.lhs | 59 ++-- compiler/typecheck/TcDeriv.lhs | 64 +---- compiler/typecheck/TcGenDeriv.lhs | 18 +- compiler/typecheck/TcGenGenerics.lhs | 304 +++++--------------- docs/users_guide/glasgow_exts.xml | 30 +- libraries/base/GHC/Generics.hs | 324 ++++++++++++---------- testsuite/tests/generics/GShow/GShow.hs | 5 +- testsuite/tests/generics/GenDerivOutput.stderr | 120 ++++---- testsuite/tests/generics/GenDerivOutput1_0.stderr | 48 ++-- testsuite/tests/generics/GenDerivOutput1_1.stderr | 254 ++++++++--------- 10 files changed, 509 insertions(+), 717 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 013f62b5058797fb1ecd4449fe572a1f5204158e From git at git.haskell.org Tue Nov 18 18:21:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 18:21:45 +0000 (UTC) Subject: [commit: ghc] master: base: Fix (**) instance for Data.Complex (#8539) (1f6b1ab) Message-ID: <20141118182145.B22973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1f6b1ab4b6d7203481bfaf374b014972f7756fb2/ghc >--------------------------------------------------------------- commit 1f6b1ab4b6d7203481bfaf374b014972f7756fb2 Author: Austin Seipp Date: Tue Nov 18 12:10:34 2014 -0600 base: Fix (**) instance for Data.Complex (#8539) Reviewed-by: Edward Kmett Authored-by: Yalas, Scott Turner Signed-off-by: Austin Seipp >--------------------------------------------------------------- 1f6b1ab4b6d7203481bfaf374b014972f7756fb2 libraries/base/Data/Complex.hs | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/libraries/base/Data/Complex.hs b/libraries/base/Data/Complex.hs index 2baa60b..756ea67 100644 --- a/libraries/base/Data/Complex.hs +++ b/libraries/base/Data/Complex.hs @@ -138,6 +138,22 @@ instance (RealFloat a) => Floating (Complex a) where where expx = exp x log z = log (magnitude z) :+ phase z + x ** y = case (x,y) of + (_ , (0:+0)) -> 1 :+ 0 + ((0:+0), (re:+_)) + | re > 0 -> 0 :+ 0 + | re < 0 -> inf :+ 0 + | otherwise -> nan :+ nan + ((re:+im), y) + | (isInfinite re || isInfinite im) -> case y of + (exp_re:+_) | exp_re > 0 -> inf :+ 0 + | exp_re < 0 -> 0 :+ 0 + | otherwise -> nan :+ nan + (x, y) -> exp (log x * y) + where + inf = 1/0 + nan = 0/0 + sqrt (0:+0) = 0 sqrt z@(x:+y) = u :+ (if y < 0 then -v else v) where (u,v) = if x < 0 then (v',u') else (u',v') From git at git.haskell.org Tue Nov 18 18:21:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 18:21:48 +0000 (UTC) Subject: [commit: ghc] master: Update comment about C helper for foreign exports (#9713) (ddb484c) Message-ID: <20141118182148.598EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ddb484c2335c75f8fd767f54377e418db400aede/ghc >--------------------------------------------------------------- commit ddb484c2335c75f8fd767f54377e418db400aede Author: Bertram Felgenhauer Date: Tue Nov 18 12:15:33 2014 -0600 Update comment about C helper for foreign exports (#9713) Signed-off-by: Austin Seipp >--------------------------------------------------------------- ddb484c2335c75f8fd767f54377e418db400aede compiler/deSugar/DsForeign.lhs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/compiler/deSugar/DsForeign.lhs b/compiler/deSugar/DsForeign.lhs index c60e914..311069e 100644 --- a/compiler/deSugar/DsForeign.lhs +++ b/compiler/deSugar/DsForeign.lhs @@ -398,12 +398,16 @@ f cback = foreign import "&f_helper" f_helper :: FunPtr (StablePtr Fun -> Fun) --- and the helper in C: +-- and the helper in C: (approximately; see `mkFExportCBits` below) f_helper(StablePtr s, HsBool b, HsInt i) { - rts_evalIO(rts_apply(rts_apply(deRefStablePtr(s), + Capability *cap; + cap = rts_lock(); + rts_evalIO(&cap, + rts_apply(rts_apply(deRefStablePtr(s), rts_mkBool(b)), rts_mkInt(i))); + rts_unlock(cap); } \end{verbatim} From git at git.haskell.org Tue Nov 18 18:21:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 18:21:50 +0000 (UTC) Subject: [commit: ghc] master: Fix usage of `find -perm` in aclocal.m4 (#9697) (87cd37b) Message-ID: <20141118182150.E801D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/87cd37b7e61ef90842101a0d2fb1f6c9c8580976/ghc >--------------------------------------------------------------- commit 87cd37b7e61ef90842101a0d2fb1f6c9c8580976 Author: Nicholas Hart Date: Tue Nov 18 12:21:03 2014 -0600 Fix usage of `find -perm` in aclocal.m4 (#9697) Signed-off-by: Austin Seipp >--------------------------------------------------------------- 87cd37b7e61ef90842101a0d2fb1f6c9c8580976 aclocal.m4 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index 0db231d..68ffd9c 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2062,7 +2062,7 @@ AC_DEFUN([FIND_LLVM_PROG],[ if test "$windows" = YES; then $1=`${FindCmd} "${p}" -type f -maxdepth 1 -regex '.*/$3-[[0-9]]\.[[0-9]]' -or -type l -maxdepth 1 -regex '.*/$3-[[0-9]]\.[[0-9]]' | ${SortCmd} -n | tail -1` else - $1=`${FindCmd} "${p}" -type f -perm +111 -maxdepth 1 -regex '.*/$3-[[0-9]]\.[[0-9]]' -or -type l -perm +111 -maxdepth 1 -regex '.*/$3-[[0-9]]\.[[0-9]]' | ${SortCmd} -n | tail -1` + $1=`${FindCmd} "${p}" -type f -perm \111 -maxdepth 1 -regex '.*/$3-[[0-9]]\.[[0-9]]' -or -type l -perm \111 -maxdepth 1 -regex '.*/$3-[[0-9]]\.[[0-9]]' | ${SortCmd} -n | tail -1` fi if test -n "$$1"; then break From git at git.haskell.org Tue Nov 18 18:21:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 18:21:53 +0000 (UTC) Subject: [commit: ghc] master: mapMaybe: Typo in the comment (#9644) (21f9bc4) Message-ID: <20141118182153.909493A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/21f9bc434c12e928005d59c494e4f48c242b0613/ghc >--------------------------------------------------------------- commit 21f9bc434c12e928005d59c494e4f48c242b0613 Author: Wieland Hoffmann Date: Sun Sep 28 19:22:37 2014 +0200 mapMaybe: Typo in the comment (#9644) Signed-off-by: Austin Seipp >--------------------------------------------------------------- 21f9bc434c12e928005d59c494e4f48c242b0613 libraries/base/Data/Maybe.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/Data/Maybe.hs b/libraries/base/Data/Maybe.hs index 33721e7..23d393d 100644 --- a/libraries/base/Data/Maybe.hs +++ b/libraries/base/Data/Maybe.hs @@ -87,7 +87,7 @@ catMaybes ls = [x | Just x <- ls] -- | The 'mapMaybe' function is a version of 'map' which can throw -- out elements. In particular, the functional argument returns -- something of type @'Maybe' b at . If this is 'Nothing', no element --- is added on to the result list. If it just @'Just' b@, then @b@ is +-- is added on to the result list. If it is @'Just' b@, then @b@ is -- included in the result list. mapMaybe :: (a -> Maybe b) -> [a] -> [b] mapMaybe _ [] = [] From git at git.haskell.org Tue Nov 18 18:43:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 18:43:23 +0000 (UTC) Subject: [commit: ghc] master: Disable AVX for LLVM 3.2 by default (#9391) (c557f99) Message-ID: <20141118184323.496AD3A303@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c557f991a9fa6f6afad4850e4f5db6a08fa1cb6c/ghc >--------------------------------------------------------------- commit c557f991a9fa6f6afad4850e4f5db6a08fa1cb6c Author: Peter Wortmann Date: Tue Nov 18 12:33:05 2014 -0600 Disable AVX for LLVM 3.2 by default (#9391) Due to a bug LLVM generates a C-like frame pointer prelude for functions that use AVX instructions. This causes programs using the GHC calling convention to crash, therefore we simply disable them. People that want to use AVX should consider upgrading to a more current LLVM version. Signed-off-by: Austin Seipp >--------------------------------------------------------------- c557f991a9fa6f6afad4850e4f5db6a08fa1cb6c compiler/main/DriverPipeline.hs | 16 +++++++++++----- 1 file changed, 11 insertions(+), 5 deletions(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 66c6e97..ed2e906 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1404,6 +1404,11 @@ runPhase (RealPhase LlvmLlc) input_fn dflags output_fn <- phaseOutputFilename next_phase + -- AVX can cause LLVM 3.2 to generate a C-like frame pointer + -- prelude, see #9391 + when (ver == 32 && isAvxEnabled dflags) $ liftIO $ errorMsg dflags $ text + "Note: LLVM 3.2 has known problems with AVX instructions (see trac #9391)" + liftIO $ SysTools.runLlvmLlc dflags ([ SysTools.Option (llvmOpts !! opt_lvl), SysTools.Option $ "-relocation-model=" ++ rmodel, @@ -1413,7 +1418,7 @@ runPhase (RealPhase LlvmLlc) input_fn dflags ++ map SysTools.Option fpOpts ++ map SysTools.Option abiOpts ++ map SysTools.Option sseOpts - ++ map SysTools.Option avxOpts + ++ map SysTools.Option (avxOpts ver) ++ map SysTools.Option avx512Opts ++ map SysTools.Option stackAlignOpts) @@ -1449,10 +1454,11 @@ runPhase (RealPhase LlvmLlc) input_fn dflags | isSseEnabled dflags = ["-mattr=+sse"] | otherwise = [] - avxOpts | isAvx512fEnabled dflags = ["-mattr=+avx512f"] - | isAvx2Enabled dflags = ["-mattr=+avx2"] - | isAvxEnabled dflags = ["-mattr=+avx"] - | otherwise = [] + avxOpts ver | isAvx512fEnabled dflags = ["-mattr=+avx512f"] + | isAvx2Enabled dflags = ["-mattr=+avx2"] + | isAvxEnabled dflags = ["-mattr=+avx"] + | ver == 32 = ["-mattr=-avx"] -- see #9391 + | otherwise = [] avx512Opts = [ "-mattr=+avx512cd" | isAvx512cdEnabled dflags ] ++ From git at git.haskell.org Tue Nov 18 18:43:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 18:43:25 +0000 (UTC) Subject: [commit: ghc] master: Fix detection of GNU gold linker if invoked via gcc with parameters (e7b414a) Message-ID: <20141118184325.DC5A33A337@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e7b414a3cc0e27049f2608f5e0a00c47146cc46d/ghc >--------------------------------------------------------------- commit e7b414a3cc0e27049f2608f5e0a00c47146cc46d Author: Sebastian Dr?ge Date: Tue Nov 18 12:40:20 2014 -0600 Fix detection of GNU gold linker if invoked via gcc with parameters Previously the linker was called without any commandline parameters to detect whether bfd or gold is used. However the -fuse-ld parameter can be used to switch between gold and bfd and should be taken into account here. Trac #9336 Signed-off-by: Austin Seipp >--------------------------------------------------------------- e7b414a3cc0e27049f2608f5e0a00c47146cc46d compiler/main/SysTools.lhs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/main/SysTools.lhs b/compiler/main/SysTools.lhs index 67926f5..c13790a 100644 --- a/compiler/main/SysTools.lhs +++ b/compiler/main/SysTools.lhs @@ -741,7 +741,10 @@ getLinkerInfo' :: DynFlags -> IO LinkerInfo getLinkerInfo' dflags = do let platform = targetPlatform dflags os = platformOS platform - (pgm,_) = pgm_l dflags + (pgm,args0) = pgm_l dflags + args1 = map Option (getOpts dflags opt_l) + args2 = args0 ++ args1 + args3 = filter notNull (map showOpt args2) -- Try to grab the info from the process output. parseLinkerInfo stdo _stde _exitc @@ -792,7 +795,7 @@ getLinkerInfo' dflags = do -- In practice, we use the compiler as the linker here. Pass -- -Wl,--version to get linker version info. (exitc, stdo, stde) <- readProcessEnvWithExitCode pgm - ["-Wl,--version"] + (["-Wl,--version"] ++ args3) en_locale_env -- Split the output by lines to make certain kinds -- of processing easier. In particular, 'clang' and 'gcc' From git at git.haskell.org Tue Nov 18 19:11:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 19:11:49 +0000 (UTC) Subject: [commit: ghc] master: Revert "base: Fix (**) instance for Data.Complex (#8539)" (a736b51) Message-ID: <20141118191149.A910E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a736b517bddaf5271ab7a0989787b120324b19f6/ghc >--------------------------------------------------------------- commit a736b517bddaf5271ab7a0989787b120324b19f6 Author: Austin Seipp Date: Tue Nov 18 13:12:12 2014 -0600 Revert "base: Fix (**) instance for Data.Complex (#8539)" This broke validate due to name shadowing warnings. This reverts commit 1f6b1ab4b6d7203481bfaf374b014972f7756fb2. >--------------------------------------------------------------- a736b517bddaf5271ab7a0989787b120324b19f6 libraries/base/Data/Complex.hs | 16 ---------------- 1 file changed, 16 deletions(-) diff --git a/libraries/base/Data/Complex.hs b/libraries/base/Data/Complex.hs index 756ea67..2baa60b 100644 --- a/libraries/base/Data/Complex.hs +++ b/libraries/base/Data/Complex.hs @@ -138,22 +138,6 @@ instance (RealFloat a) => Floating (Complex a) where where expx = exp x log z = log (magnitude z) :+ phase z - x ** y = case (x,y) of - (_ , (0:+0)) -> 1 :+ 0 - ((0:+0), (re:+_)) - | re > 0 -> 0 :+ 0 - | re < 0 -> inf :+ 0 - | otherwise -> nan :+ nan - ((re:+im), y) - | (isInfinite re || isInfinite im) -> case y of - (exp_re:+_) | exp_re > 0 -> inf :+ 0 - | exp_re < 0 -> 0 :+ 0 - | otherwise -> nan :+ nan - (x, y) -> exp (log x * y) - where - inf = 1/0 - nan = 0/0 - sqrt (0:+0) = 0 sqrt z@(x:+y) = u :+ (if y < 0 then -v else v) where (u,v) = if x < 0 then (v',u') else (u',v') From git at git.haskell.org Wed Nov 19 03:38:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 03:38:44 +0000 (UTC) Subject: [commit: ghc] wip/merge: Add test case for #8144. (218d3ba) Message-ID: <20141119033844.B24103A3A3@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/218d3ba58be366ad38be48c325a9e6728f78ae5c/ghc >--------------------------------------------------------------- commit 218d3ba58be366ad38be48c325a9e6728f78ae5c Author: Niklas Hamb?chen Date: Tue Nov 18 21:10:45 2014 -0600 Add test case for #8144. Based on: https://github.com/nh2/ghc-bug-time-dependent-interface-hashes I verified that this test fails for GHC 7.6.3 and older, and passes for GHC 7.8 and newer. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 218d3ba58be366ad38be48c325a9e6728f78ae5c testsuite/tests/driver/recomp015/Makefile | 32 ++++++++++++++++++++++ testsuite/tests/driver/recomp015/Test.hs | 3 ++ testsuite/tests/driver/recomp015/all.T | 7 +++++ .../tests/driver/recomp015/cabal_macros.h | 0 testsuite/tests/driver/recomp015/recomp014.stdout | 5 ++++ 5 files changed, 47 insertions(+) diff --git a/testsuite/tests/driver/recomp015/Makefile b/testsuite/tests/driver/recomp015/Makefile new file mode 100644 index 0000000..430516d --- /dev/null +++ b/testsuite/tests/driver/recomp015/Makefile @@ -0,0 +1,32 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +# -fforce-recomp makes lots of driver tests trivially pass, so we +# filter it out from $(TEST_HC_OPTS). +TEST_HC_OPTS_NO_RECOMP = $(filter-out -fforce-recomp,$(TEST_HC_OPTS)) + +# Recompilation tests + +clean: + rm -f *.o *.hi + rm -f Test$(exeext) + +# bug #8144 + +# All compilations except the first should print +# compilation IS NOT required + +recomp015: clean + ghc -c Test.hs -optP-include -optPcabal_macros.h + touch cabal_macros.h + ghc -c Test.hs -optP-include -optPcabal_macros.h + touch cabal_macros.h + ghc -c Test.hs -optP-include -optPcabal_macros.h + touch cabal_macros.h + ghc -c Test.hs -optP-include -optPcabal_macros.h + touch cabal_macros.h + ghc -c Test.hs -optP-include -optPcabal_macros.h + touch cabal_macros.h + sleep 2 + ghc -c Test.hs -optP-include -optPcabal_macros.h diff --git a/testsuite/tests/driver/recomp015/Test.hs b/testsuite/tests/driver/recomp015/Test.hs new file mode 100644 index 0000000..5c8df53 --- /dev/null +++ b/testsuite/tests/driver/recomp015/Test.hs @@ -0,0 +1,3 @@ +{-# LANGUAGE CPP #-} + +module Test () where diff --git a/testsuite/tests/driver/recomp015/all.T b/testsuite/tests/driver/recomp015/all.T new file mode 100644 index 0000000..0643030 --- /dev/null +++ b/testsuite/tests/driver/recomp015/all.T @@ -0,0 +1,7 @@ +# Test for #8144, a recompilation bug + +test('recomp015', + [ clean_cmd('$MAKE -s clean') ], + run_command, + ['$MAKE -s --no-print-directory recomp015']) + diff --git a/libraries/base/tests/IO/misc001.stdout b/testsuite/tests/driver/recomp015/cabal_macros.h similarity index 100% copy from libraries/base/tests/IO/misc001.stdout copy to testsuite/tests/driver/recomp015/cabal_macros.h diff --git a/testsuite/tests/driver/recomp015/recomp014.stdout b/testsuite/tests/driver/recomp015/recomp014.stdout new file mode 100644 index 0000000..178cb00 --- /dev/null +++ b/testsuite/tests/driver/recomp015/recomp014.stdout @@ -0,0 +1,5 @@ +compilation IS NOT required +compilation IS NOT required +compilation IS NOT required +compilation IS NOT required +compilation IS NOT required From git at git.haskell.org Wed Nov 19 03:38:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 03:38:49 +0000 (UTC) Subject: [commit: ghc] wip/merge: The test runner now also works under the msys-native Python. (799529f) Message-ID: <20141119033849.E5A093A3A7@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/799529f5408f189648d36bd36032ee829ed512fd/ghc >--------------------------------------------------------------- commit 799529f5408f189648d36bd36032ee829ed512fd Author: Gintautas Miliauskas Date: Mon Sep 22 23:10:56 2014 +0200 The test runner now also works under the msys-native Python. Msys binaries apply heuristics to escape paths in arguments intended for non-msys binaries, which breaks timeout invocations, see #9626. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 799529f5408f189648d36bd36032ee829ed512fd testsuite/driver/testlib.py | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 1549381..6fc86e4 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1780,9 +1780,25 @@ def rawSystem(cmd_and_args): else: return os.spawnv(os.P_WAIT, cmd_and_args[0], cmd_and_args) +# When running under native msys Python, any invocations of non-msys binaries, +# including timeout.exe, will have their arguments munged according to some +# heuristics, which leads to malformed command lines (#9626). The easiest way +# to avoid problems is to invoke through /usr/bin/cmd which sidesteps argument +# munging because it is a native msys application. +def passThroughCmd(cmd_and_args): + args = [] + # cmd needs a Windows-style path for its first argument. + args.append(cmd_and_args[0].replace('/', '\\')) + # Other arguments need to be quoted to deal with spaces. + args.extend(['"%s"' % arg for arg in cmd_and_args[1:]]) + return ["cmd", "/c", " ".join(args)] + # Note that this doesn't handle the timeout itself; it is just used for # commands that have timeout handling built-in. def rawSystemWithTimeout(cmd_and_args): + if config.os == 'mingw32' and sys.executable.startswith('/usr'): + # This is only needed when running under msys python. + cmd_and_args = passThroughCmd(cmd_and_args) r = rawSystem(cmd_and_args) if r == 98: # The python timeout program uses 98 to signal that ^C was pressed From git at git.haskell.org Wed Nov 19 03:38:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 03:38:41 +0000 (UTC) Subject: [commit: ghc] branch 'wip/merge' created Message-ID: <20141119033841.604B63A3A1@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/merge Referencing: 799529f5408f189648d36bd36032ee829ed512fd From git at git.haskell.org Wed Nov 19 03:38:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 03:38:47 +0000 (UTC) Subject: [commit: ghc] wip/merge: rts: remove old-style field designator extension (#9396) (36e3acd) Message-ID: <20141119033847.4D23E3A3A5@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/36e3acdafe29854690659d177c078291bacac9c2/ghc >--------------------------------------------------------------- commit 36e3acdafe29854690659d177c078291bacac9c2 Author: Austin Seipp Date: Tue Nov 18 21:21:47 2014 -0600 rts: remove old-style field designator extension (#9396) Authored-by: jrp Signed-off-by: Austin Seipp >--------------------------------------------------------------- 36e3acdafe29854690659d177c078291bacac9c2 includes/rts/prof/CCS.h | 48 ++++++++++++++++++++++++------------------------ rts/RetainerSet.c | 10 +++++----- 2 files changed, 29 insertions(+), 29 deletions(-) diff --git a/includes/rts/prof/CCS.h b/includes/rts/prof/CCS.h index 85b03f3..74f18b8 100644 --- a/includes/rts/prof/CCS.h +++ b/includes/rts/prof/CCS.h @@ -210,32 +210,32 @@ extern CostCentreStack * RTS_VAR(CCS_LIST); // registered CCS list * Declaring Cost Centres & Cost Centre Stacks. * -------------------------------------------------------------------------- */ -# define CC_DECLARE(cc_ident,name,mod,loc,caf,is_local) \ - is_local CostCentre cc_ident[1] \ - = {{ ccID : 0, \ - label : name, \ - module : mod, \ - srcloc : loc, \ - time_ticks : 0, \ - mem_alloc : 0, \ - link : 0, \ - is_caf : caf \ +# define CC_DECLARE(cc_ident,name,mod,loc,caf,is_local) \ + is_local CostCentre cc_ident[1] \ + = {{ .ccID = 0, \ + .label = name, \ + .module = mod, \ + .srcloc = loc, \ + .time_ticks = 0, \ + .mem_alloc = 0, \ + .link = 0, \ + .is_caf = caf \ }}; -# define CCS_DECLARE(ccs_ident,cc_ident,is_local) \ - is_local CostCentreStack ccs_ident[1] \ - = {{ ccsID : 0, \ - cc : cc_ident, \ - prevStack : NULL, \ - indexTable : NULL, \ - root : NULL, \ - depth : 0, \ - selected : 0, \ - scc_count : 0, \ - time_ticks : 0, \ - mem_alloc : 0, \ - inherited_ticks : 0, \ - inherited_alloc : 0 \ +# define CCS_DECLARE(ccs_ident,cc_ident,is_local) \ + is_local CostCentreStack ccs_ident[1] \ + = {{ .ccsID = 0, \ + .cc = cc_ident, \ + .prevStack = NULL, \ + .indexTable = NULL, \ + .root = NULL, \ + .depth = 0, \ + .selected = 0, \ + .scc_count = 0, \ + .time_ticks = 0, \ + .mem_alloc = 0, \ + .inherited_ticks = 0, \ + .inherited_alloc = 0 \ }}; /* ----------------------------------------------------------------------------- diff --git a/rts/RetainerSet.c b/rts/RetainerSet.c index 1905866..234532a 100644 --- a/rts/RetainerSet.c +++ b/rts/RetainerSet.c @@ -40,11 +40,11 @@ static int nextId; // id of next retainer set * from growing too large. * -------------------------------------------------------------------------- */ RetainerSet rs_MANY = { - num : 0, - hashKey : 0, - link : NULL, - id : 1, - element : {} + .num = 0, + .hashKey = 0, + .link = NULL, + .id = 1, + .element = {} }; /* ----------------------------------------------------------------------------- From git at git.haskell.org Wed Nov 19 04:28:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 04:28:01 +0000 (UTC) Subject: [commit: ghc] wip/merge: add missing instances for Loc and a few missing Eq instances (1ee0034) Message-ID: <20141119042801.37A923A3BD@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/1ee0034f0cac4958412da380018d7814865fac22/ghc >--------------------------------------------------------------- commit 1ee0034f0cac4958412da380018d7814865fac22 Author: Luite Stegeman Date: Tue Nov 18 22:21:44 2014 -0600 add missing instances for Loc and a few missing Eq instances Summary: This adds a few missing instances that can be automatically derived Reviewers: hvr, goldfire, austin Reviewed By: goldfire, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D495 >--------------------------------------------------------------- 1ee0034f0cac4958412da380018d7814865fac22 libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 6d4e5db..284058e 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -877,6 +877,7 @@ data Loc , loc_module :: String , loc_start :: CharPos , loc_end :: CharPos } + deriving( Show, Eq, Data, Typeable, Generic ) type CharPos = (Int, Int) -- ^ Line and character position @@ -951,13 +952,13 @@ data Info | TyVarI -- Scoped type variable Name Type -- What it is bound to - deriving( Show, Data, Typeable, Generic ) + deriving( Show, Eq, Data, Typeable, Generic ) -- | Obtained from 'reifyModule' in the 'Q' Monad. data ModuleInfo = -- | Contains the import list of the module. ModuleInfo [Module] - deriving( Show, Data, Typeable, Generic ) + deriving( Show, Eq, Data, Typeable, Generic ) {- | In 'ClassOpI' and 'DataConI', name of the parent class or type From git at git.haskell.org Wed Nov 19 04:27:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 04:27:50 +0000 (UTC) Subject: [commit: ghc] wip/merge: Turn CoreWriter into a newtype; fix comment (a9ed294) Message-ID: <20141119042750.E12523A3B5@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/a9ed294abfbafb32867345dd20ee9a3a90b4e2c1/ghc >--------------------------------------------------------------- commit a9ed294abfbafb32867345dd20ee9a3a90b4e2c1 Author: David Feuer Date: Tue Nov 18 22:19:46 2014 -0600 Turn CoreWriter into a newtype; fix comment Summary: Turn CoreWriter into a newtype. A comment claimed something is forced before returning, but it's actually not. Change comment to match reality. Reviewers: xich, simonpj, ezyang, austin Reviewed By: ezyang, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D453 >--------------------------------------------------------------- a9ed294abfbafb32867345dd20ee9a3a90b4e2c1 compiler/simplCore/CoreMonad.lhs | 19 +++++++++++-------- 1 file changed, 11 insertions(+), 8 deletions(-) diff --git a/compiler/simplCore/CoreMonad.lhs b/compiler/simplCore/CoreMonad.lhs index 04782f1..0d41d5e 100644 --- a/compiler/simplCore/CoreMonad.lhs +++ b/compiler/simplCore/CoreMonad.lhs @@ -776,10 +776,11 @@ data CoreReader = CoreReader { #endif } -data CoreWriter = CoreWriter { - cw_simpl_count :: !SimplCount - -- Making this strict fixes a nasty space leak - -- See Trac #7702 +-- Note: CoreWriter used to be defined with data, rather than newtype. If it +-- is defined that way again, the cw_simpl_count field, at least, must be +-- strict to avoid a space leak (Trac #7702). +newtype CoreWriter = CoreWriter { + cw_simpl_count :: SimplCount } emptyWriter :: DynFlags -> CoreWriter @@ -808,12 +809,14 @@ instance Monad CoreM where mx >>= f = CoreM $ \s -> do (x, s', w1) <- unCoreM mx s (y, s'', w2) <- unCoreM (f x) s' - let w = w1 `plusWriter` w2 -- forcing w before returning avoids a space leak (Trac #7702) + let w = w1 `plusWriter` w2 return $ seq w (y, s'', w) - + -- forcing w before building the tuple avoids a space leak + -- (Trac #7702) instance A.Applicative CoreM where pure = return (<*>) = ap + (*>) = (>>) instance MonadPlus IO => A.Alternative CoreM where empty = mzero @@ -986,8 +989,8 @@ on Windows. On Windows the GHC library tends to export more than 65536 symbols (see #5292) which overflows the limit of what we can export from the EXE and causes breakage. -(Note that if the GHC exeecutable was dynamically linked this wouldn't be a problem, -because we could share the GHC library it links to.) +(Note that if the GHC executable was dynamically linked this wouldn't be a +problem, because we could share the GHC library it links to.) We are going to try 2. instead. Unfortunately, this means that every plugin will have to say `reinitializeGlobals` before it does anything, but never mind. From git at git.haskell.org Wed Nov 19 04:27:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 04:27:38 +0000 (UTC) Subject: [commit: ghc] wip/merge: rts: remove old-style field designator extension (#9396) (3fa546d) Message-ID: <20141119042738.084E03A3AB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/3fa546d8531d8f1db5d398bb07d7fd42cb753dd9/ghc >--------------------------------------------------------------- commit 3fa546d8531d8f1db5d398bb07d7fd42cb753dd9 Author: Austin Seipp Date: Tue Nov 18 21:21:47 2014 -0600 rts: remove old-style field designator extension (#9396) Authored-by: jrp Signed-off-by: Austin Seipp >--------------------------------------------------------------- 3fa546d8531d8f1db5d398bb07d7fd42cb753dd9 includes/rts/prof/CCS.h | 48 ++++++++++++++++++++++++------------------------ rts/RetainerSet.c | 10 +++++----- 2 files changed, 29 insertions(+), 29 deletions(-) diff --git a/includes/rts/prof/CCS.h b/includes/rts/prof/CCS.h index 85b03f3..74f18b8 100644 --- a/includes/rts/prof/CCS.h +++ b/includes/rts/prof/CCS.h @@ -210,32 +210,32 @@ extern CostCentreStack * RTS_VAR(CCS_LIST); // registered CCS list * Declaring Cost Centres & Cost Centre Stacks. * -------------------------------------------------------------------------- */ -# define CC_DECLARE(cc_ident,name,mod,loc,caf,is_local) \ - is_local CostCentre cc_ident[1] \ - = {{ ccID : 0, \ - label : name, \ - module : mod, \ - srcloc : loc, \ - time_ticks : 0, \ - mem_alloc : 0, \ - link : 0, \ - is_caf : caf \ +# define CC_DECLARE(cc_ident,name,mod,loc,caf,is_local) \ + is_local CostCentre cc_ident[1] \ + = {{ .ccID = 0, \ + .label = name, \ + .module = mod, \ + .srcloc = loc, \ + .time_ticks = 0, \ + .mem_alloc = 0, \ + .link = 0, \ + .is_caf = caf \ }}; -# define CCS_DECLARE(ccs_ident,cc_ident,is_local) \ - is_local CostCentreStack ccs_ident[1] \ - = {{ ccsID : 0, \ - cc : cc_ident, \ - prevStack : NULL, \ - indexTable : NULL, \ - root : NULL, \ - depth : 0, \ - selected : 0, \ - scc_count : 0, \ - time_ticks : 0, \ - mem_alloc : 0, \ - inherited_ticks : 0, \ - inherited_alloc : 0 \ +# define CCS_DECLARE(ccs_ident,cc_ident,is_local) \ + is_local CostCentreStack ccs_ident[1] \ + = {{ .ccsID = 0, \ + .cc = cc_ident, \ + .prevStack = NULL, \ + .indexTable = NULL, \ + .root = NULL, \ + .depth = 0, \ + .selected = 0, \ + .scc_count = 0, \ + .time_ticks = 0, \ + .mem_alloc = 0, \ + .inherited_ticks = 0, \ + .inherited_alloc = 0 \ }}; /* ----------------------------------------------------------------------------- diff --git a/rts/RetainerSet.c b/rts/RetainerSet.c index 1905866..234532a 100644 --- a/rts/RetainerSet.c +++ b/rts/RetainerSet.c @@ -40,11 +40,11 @@ static int nextId; // id of next retainer set * from growing too large. * -------------------------------------------------------------------------- */ RetainerSet rs_MANY = { - num : 0, - hashKey : 0, - link : NULL, - id : 1, - element : {} + .num = 0, + .hashKey = 0, + .link = NULL, + .id = 1, + .element = {} }; /* ----------------------------------------------------------------------------- From git at git.haskell.org Wed Nov 19 04:27:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 04:27:40 +0000 (UTC) Subject: [commit: ghc] wip/merge: Update documentation for "Batch compiler mode" (d8abbba) Message-ID: <20141119042740.9234D3A3AD@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/d8abbba30b751d0aba543ae4129c79aefc48d948/ghc >--------------------------------------------------------------- commit d8abbba30b751d0aba543ae4129c79aefc48d948 Author: Thomas Miedema Date: Tue Nov 18 22:18:43 2014 -0600 Update documentation for "Batch compiler mode" Summary: Since commit 7828bf3ea2ea34e7a3a8662f5f621ef706ffee5c * --make is the default * -c is a mode flag, except when used in combination with --make Also: * -C (generate C code) is only available in unregisterised mode. Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D427 >--------------------------------------------------------------- d8abbba30b751d0aba543ae4129c79aefc48d948 docs/users_guide/flags.xml | 4 ++-- docs/users_guide/using.xml | 23 ++++++++++++++++++----- 2 files changed, 20 insertions(+), 7 deletions(-) diff --git a/docs/users_guide/flags.xml b/docs/users_guide/flags.xml index 33af295..e8218f7 100644 --- a/docs/users_guide/flags.xml +++ b/docs/users_guide/flags.xml @@ -209,8 +209,8 @@ - Do not link - dynamic + Stop after generating object (.o) file + mode - diff --git a/docs/users_guide/using.xml b/docs/users_guide/using.xml index 07d487e..bf4f1c5 100644 --- a/docs/users_guide/using.xml +++ b/docs/users_guide/using.xml @@ -246,6 +246,13 @@ module X where + .hspp + + A file created by the preprocessor. + + + + .hi A Haskell interface file, probably @@ -383,7 +390,7 @@ module X where ghc -E - ghc -c + ghc -C ghc -S ghc -c @@ -395,10 +402,7 @@ module X where This is the traditional batch-compiler mode, in which GHC can compile source files one at a time, or link objects - together into an executable. This mode also applies if - there is no other mode flag specified on the command line, - in which case it means that the specified files should be - compiled and then linked to form a program. See . @@ -617,6 +621,11 @@ ghc Main.hs given on the command line and GHC will include them when linking the executable. + For backward compatibility with existing make scripts, when + used in combination with , the linking phase + is omitted (same as + ). + Note that GHC can only follow dependencies if it has the source file available, so if your program includes a module for which there is no source file, even if you have an object and an @@ -765,6 +774,10 @@ ghc -c Foo.hs option runs just the pre-processing passes of the compiler, dumping the result in a file. + Note: The option is only available when + GHC is built in unregisterised mode. See + for more details. + Overriding the default behaviour for a file From git at git.haskell.org Wed Nov 19 04:27:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 04:27:56 +0000 (UTC) Subject: [commit: ghc] wip/merge: template-haskell: Missing instances for Rational and (). (fc3e8b3) Message-ID: <20141119042756.1472C3A3B9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/fc3e8b3ddb2eef1964e099e3518ca014ae5ff672/ghc >--------------------------------------------------------------- commit fc3e8b3ddb2eef1964e099e3518ca014ae5ff672 Author: Mathieu Boespflug Date: Tue Nov 18 22:21:15 2014 -0600 template-haskell: Missing instances for Rational and (). Test Plan: ./validate Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D492 >--------------------------------------------------------------- fc3e8b3ddb2eef1964e099e3518ca014ae5ff672 docs/users_guide/7.10.1-notes.xml | 5 +++++ libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 8 +++++++- 2 files changed, 12 insertions(+), 1 deletion(-) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 2e509e1..0cf3f61 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -176,6 +176,11 @@ Various features unsupported in quotations were previously silently ignored. These now cause errors. + + + Lift instances were added for + () and Ratio. + diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 48199a4..6d4e5db 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -454,7 +454,10 @@ instance Lift Integer where lift x = return (LitE (IntegerL x)) instance Lift Int where - lift x= return (LitE (IntegerL (fromIntegral x))) + lift x = return (LitE (IntegerL (fromIntegral x))) + +instance Lift Rational where + lift x = return (LitE (RationalL x)) instance Lift Char where lift x = return (LitE (CharL x)) @@ -478,6 +481,9 @@ liftString :: String -> Q Exp -- Used in TcExpr to short-circuit the lifting for strings liftString s = return (LitE (StringL s)) +instance Lift () where + lift () = liftM (ConE (tupleDataName 0)) + instance (Lift a, Lift b) => Lift (a, b) where lift (a, b) = liftM TupE $ sequence [lift a, lift b] From git at git.haskell.org Wed Nov 19 04:27:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 04:27:58 +0000 (UTC) Subject: [commit: ghc] wip/merge: Add remaining s and comments to .mailmap (44c2412) Message-ID: <20141119042758.A20183A3BB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/44c24129ec99d395a06b22e3f2c45ce8d466d95e/ghc >--------------------------------------------------------------- commit 44c24129ec99d395a06b22e3f2c45ce8d466d95e Author: Thomas Miedema Date: Tue Nov 18 22:20:14 2014 -0600 Add remaining s and comments to .mailmap Summary: All done, except for these 2 empty commits: $ git log --author=unknown --use-mailmap --oneline 7e5c2b2 [project @ 2001-12-06 10:17:35 by mbs] Established under cvs. 6456598 [project @ 2000-12-01 10:33:41 by cryder] Initial revision Reviewers: hvr, austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D477 >--------------------------------------------------------------- 44c24129ec99d395a06b22e3f2c45ce8d466d95e .mailmap | 59 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++- 1 file changed, 58 insertions(+), 1 deletion(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 44c24129ec99d395a06b22e3f2c45ce8d466d95e From git at git.haskell.org Wed Nov 19 04:27:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 04:27:35 +0000 (UTC) Subject: [commit: ghc] wip/merge: Add test case for #8144. (6b6f986) Message-ID: <20141119042735.6E06F3A3A9@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/6b6f986975b62e2b7667dc272182136dbe5eb588/ghc >--------------------------------------------------------------- commit 6b6f986975b62e2b7667dc272182136dbe5eb588 Author: Niklas Hamb?chen Date: Tue Nov 18 21:10:45 2014 -0600 Add test case for #8144. Based on: https://github.com/nh2/ghc-bug-time-dependent-interface-hashes I verified that this test fails for GHC 7.6.3 and older, and passes for GHC 7.8 and newer. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 6b6f986975b62e2b7667dc272182136dbe5eb588 testsuite/tests/driver/recomp015/Makefile | 32 ++++++++++++++++++++++ testsuite/tests/driver/recomp015/Test.hs | 3 ++ testsuite/tests/driver/recomp015/all.T | 7 +++++ .../tests/driver/recomp015/cabal_macros.h | 0 testsuite/tests/driver/recomp015/recomp015.stdout | 5 ++++ 5 files changed, 47 insertions(+) diff --git a/testsuite/tests/driver/recomp015/Makefile b/testsuite/tests/driver/recomp015/Makefile new file mode 100644 index 0000000..430516d --- /dev/null +++ b/testsuite/tests/driver/recomp015/Makefile @@ -0,0 +1,32 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +# -fforce-recomp makes lots of driver tests trivially pass, so we +# filter it out from $(TEST_HC_OPTS). +TEST_HC_OPTS_NO_RECOMP = $(filter-out -fforce-recomp,$(TEST_HC_OPTS)) + +# Recompilation tests + +clean: + rm -f *.o *.hi + rm -f Test$(exeext) + +# bug #8144 + +# All compilations except the first should print +# compilation IS NOT required + +recomp015: clean + ghc -c Test.hs -optP-include -optPcabal_macros.h + touch cabal_macros.h + ghc -c Test.hs -optP-include -optPcabal_macros.h + touch cabal_macros.h + ghc -c Test.hs -optP-include -optPcabal_macros.h + touch cabal_macros.h + ghc -c Test.hs -optP-include -optPcabal_macros.h + touch cabal_macros.h + ghc -c Test.hs -optP-include -optPcabal_macros.h + touch cabal_macros.h + sleep 2 + ghc -c Test.hs -optP-include -optPcabal_macros.h diff --git a/testsuite/tests/driver/recomp015/Test.hs b/testsuite/tests/driver/recomp015/Test.hs new file mode 100644 index 0000000..5c8df53 --- /dev/null +++ b/testsuite/tests/driver/recomp015/Test.hs @@ -0,0 +1,3 @@ +{-# LANGUAGE CPP #-} + +module Test () where diff --git a/testsuite/tests/driver/recomp015/all.T b/testsuite/tests/driver/recomp015/all.T new file mode 100644 index 0000000..0643030 --- /dev/null +++ b/testsuite/tests/driver/recomp015/all.T @@ -0,0 +1,7 @@ +# Test for #8144, a recompilation bug + +test('recomp015', + [ clean_cmd('$MAKE -s clean') ], + run_command, + ['$MAKE -s --no-print-directory recomp015']) + diff --git a/libraries/base/tests/IO/misc001.stdout b/testsuite/tests/driver/recomp015/cabal_macros.h similarity index 100% copy from libraries/base/tests/IO/misc001.stdout copy to testsuite/tests/driver/recomp015/cabal_macros.h diff --git a/testsuite/tests/driver/recomp015/recomp015.stdout b/testsuite/tests/driver/recomp015/recomp015.stdout new file mode 100644 index 0000000..178cb00 --- /dev/null +++ b/testsuite/tests/driver/recomp015/recomp015.stdout @@ -0,0 +1,5 @@ +compilation IS NOT required +compilation IS NOT required +compilation IS NOT required +compilation IS NOT required +compilation IS NOT required From git at git.haskell.org Wed Nov 19 04:27:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 04:27:53 +0000 (UTC) Subject: [commit: ghc] wip/merge: Only test for bug #9439 when llvm is installed (3a00157) Message-ID: <20141119042753.7F65B3A3B7@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/3a00157fbfa44d71aff637e12965725ecc3625e5/ghc >--------------------------------------------------------------- commit 3a00157fbfa44d71aff637e12965725ecc3625e5 Author: Thomas Miedema Date: Tue Nov 18 22:23:27 2014 -0600 Only test for bug #9439 when llvm is installed Reviewers: bgamari, austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D500 GHC Trac Issues: #9807 >--------------------------------------------------------------- 3a00157fbfa44d71aff637e12965725ecc3625e5 configure.ac | 103 ++++++++++++++++++++++++++++++----------------------------- 1 file changed, 53 insertions(+), 50 deletions(-) diff --git a/configure.ac b/configure.ac index 7bd599f..5dd3aaa 100644 --- a/configure.ac +++ b/configure.ac @@ -187,56 +187,6 @@ AC_SUBST([WithGhc]) dnl ** Without optimization some INLINE trickery fails for GHCi SRC_CC_OPTS="-O" -dnl ** Bug 9439: Some GHC 7.8 releases had broken LLVM code generator. -dnl Unfortunately we don't know whether the user is going to request a -dnl build with the LLVM backend as this is only given in build.mk. -dnl -dnl Instead, we try to do as much work as possible here, checking -dnl whether -fllvm is the stage 0 compiler's default. If so we -dnl fail. If not, we check whether -fllvm is affected explicitly and -dnl if so set a flag. The build system will later check this flag -dnl after the desired build flags are known. -AC_MSG_CHECKING(whether bootstrap compiler is affected by bug 9439) -echo "main = putStrLn \"%function\"" > conftestghc.hs - -# Check whether LLVM backend is default for this platform -"${WithGhc}" conftestghc.hs 2>&1 >/dev/null -res=`./conftestghc` -if test "x$res" == "x%object" -then - AC_MSG_RESULT(yes) - echo "Buggy bootstrap compiler" - echo "" - echo "The stage 0 compiler $WithGhc is affected by GHC Bug \#9439" - echo "and therefore will miscompile the LLVM backend if -fllvm is" - echo "used." - echo - echo "Please use another bootstrap compiler" - exit 1 -fi - -# -fllvm is not the default, but set a flag so the Makefile can check -# -for it in the build flags later on -"${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null -if test $? == 0 -then - res=`./conftestghc` - if test "x$res" == "x%object" - then - AC_MSG_RESULT(yes) - GHC_LLVM_AFFECTED_BY_9439=1 - elif test "x$res" == "x%function" - then - AC_MSG_RESULT(no) - GHC_LLVM_AFFECTED_BY_9439=0 - else - AC_MSG_WARN(unexpected output $res) - fi -else - AC_MSG_RESULT(failed to compile, assuming no) -fi -AC_SUBST([GHC_LLVM_AFFECTED_BY_9439]) - dnl-------------------------------------------------------------------- dnl * Choose host(/target/build) platform dnl-------------------------------------------------------------------- @@ -593,6 +543,59 @@ dnl -------------------------------------------------------------- dnl * General configuration checks dnl -------------------------------------------------------------- +dnl ** Bug 9439: Some GHC 7.8 releases had broken LLVM code generator. +dnl Unfortunately we don't know whether the user is going to request a +dnl build with the LLVM backend as this is only given in build.mk. +dnl +dnl Instead, we try to do as much work as possible here, checking +dnl whether -fllvm is the stage 0 compiler's default. If so we +dnl fail. If not, we check whether -fllvm is affected explicitly and +dnl if so set a flag. The build system will later check this flag +dnl after the desired build flags are known. +if test -n "$LlcCmd" && test -n "$OptCmd" +then + AC_MSG_CHECKING(whether bootstrap compiler is affected by bug 9439) + echo "main = putStrLn \"%function\"" > conftestghc.hs + + # Check whether LLVM backend is default for this platform + "${WithGhc}" conftestghc.hs 2>&1 >/dev/null + res=`./conftestghc` + if test "x$res" == "x%object" + then + AC_MSG_RESULT(yes) + echo "Buggy bootstrap compiler" + echo "" + echo "The stage 0 compiler $WithGhc is affected by GHC Bug \#9439" + echo "and therefore will miscompile the LLVM backend if -fllvm is" + echo "used." + echo + echo "Please use another bootstrap compiler" + exit 1 + fi + + # -fllvm is not the default, but set a flag so the Makefile can check + # -for it in the build flags later on + "${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null + if test $? == 0 + then + res=`./conftestghc` + if test "x$res" == "x%object" + then + AC_MSG_RESULT(yes) + GHC_LLVM_AFFECTED_BY_9439=1 + elif test "x$res" == "x%function" + then + AC_MSG_RESULT(no) + GHC_LLVM_AFFECTED_BY_9439=0 + else + AC_MSG_WARN(unexpected output $res) + fi + else + AC_MSG_RESULT(failed to compile, assuming no) + fi +fi +AC_SUBST([GHC_LLVM_AFFECTED_BY_9439]) + dnl ** Can the unix package be built? dnl -------------------------------------------------------------- From git at git.haskell.org Wed Nov 19 04:28:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 04:28:03 +0000 (UTC) Subject: [commit: ghc] wip/merge: Filter input to abiHash early (320c2aa) Message-ID: <20141119042803.C41383A3BF@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/320c2aa8bf7b89285fc0cb3f0b532d5444604e37/ghc >--------------------------------------------------------------- commit 320c2aa8bf7b89285fc0cb3f0b532d5444604e37 Author: Mateusz Kowalczyk Date: Tue Nov 18 22:21:03 2014 -0600 Filter input to abiHash early Summary: This is already done near the only call site so why not. It is ugly to see it at 'abiHash' itself. Test Plan: validate Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D491 >--------------------------------------------------------------- 320c2aa8bf7b89285fc0cb3f0b532d5444604e37 ghc/Main.hs | 12 +++++++++--- 1 file changed, 9 insertions(+), 3 deletions(-) diff --git a/ghc/Main.hs b/ghc/Main.hs index c1ee247..4fd7803 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -236,7 +236,7 @@ main' postLoadMode dflags0 args flagWarnings = do StopBefore p -> liftIO (oneShot hsc_env p srcs) DoInteractive -> ghciUI srcs Nothing DoEval exprs -> ghciUI srcs $ Just $ reverse exprs - DoAbiHash -> abiHash srcs + DoAbiHash -> abiHash (map fst srcs) ShowPackages -> liftIO $ showPackages dflags6 liftIO $ dumpFinalStats dflags6 @@ -798,7 +798,13 @@ the package chagnes, so during registration Cabal calls ghc --abi-hash to get a hash of the package's ABI. -} -abiHash :: [(String, Maybe Phase)] -> Ghc () +-- | Print ABI hash of input modules. +-- +-- The resulting hash is the MD5 of the GHC version used (Trac #5328, +-- see 'hiVersion') and of the existing ABI hash from each module (see +-- 'mi_mod_hash'). +abiHash :: [String] -- ^ List of module names + -> Ghc () abiHash strs = do hsc_env <- getSession let dflags = hsc_dflags hsc_env @@ -813,7 +819,7 @@ abiHash strs = do _error -> throwGhcException $ CmdLineError $ showSDoc dflags $ cannotFindInterface dflags modname r - mods <- mapM find_it (map fst strs) + mods <- mapM find_it strs let get_iface modl = loadUserInterface False (text "abiHash") modl ifaces <- initIfaceCheck hsc_env $ mapM get_iface mods From git at git.haskell.org Wed Nov 19 04:27:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 04:27:43 +0000 (UTC) Subject: [commit: ghc] wip/merge: Implement new Foldable methods for HsPatSynDetails (b212e83) Message-ID: <20141119042743.254D83A3AF@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/b212e83770f5de300ef5caf5d8637de3201a5be8/ghc >--------------------------------------------------------------- commit b212e83770f5de300ef5caf5d8637de3201a5be8 Author: David Feuer Date: Tue Nov 18 22:18:57 2014 -0600 Implement new Foldable methods for HsPatSynDetails Summary: Also explicitly define foldl1 and foldr1, which should generally work better with list-specific versions. Reviewers: austin Reviewed By: austin Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D430 >--------------------------------------------------------------- b212e83770f5de300ef5caf5d8637de3201a5be8 compiler/hsSyn/HsBinds.lhs | 21 ++++++++++++++++++++- 1 file changed, 20 insertions(+), 1 deletion(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index bbf6bc2..95ec98e 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -14,6 +14,7 @@ Datatype for: @BindGroup@, @Bind@, @Sig@, @Bind at . -- in module PlaceHolder {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE CPP #-} +{-# LANGUAGE BangPatterns #-} module HsBinds where @@ -41,8 +42,8 @@ import BooleanFormula (BooleanFormula) import Data.Data hiding ( Fixity ) import Data.List import Data.Ord -#if __GLASGOW_HASKELL__ < 709 import Data.Foldable ( Foldable(..) ) +#if __GLASGOW_HASKELL__ < 709 import Data.Traversable ( Traversable(..) ) import Data.Monoid ( mappend ) import Control.Applicative hiding (empty) @@ -807,6 +808,24 @@ instance Foldable HsPatSynDetails where foldMap f (InfixPatSyn left right) = f left `mappend` f right foldMap f (PrefixPatSyn args) = foldMap f args + foldl1 f (InfixPatSyn left right) = left `f` right + foldl1 f (PrefixPatSyn args) = Data.List.foldl1 f args + + foldr1 f (InfixPatSyn left right) = left `f` right + foldr1 f (PrefixPatSyn args) = Data.List.foldr1 f args + +-- TODO: After a few more versions, we should probably use these. +#if __GLASGOW_HASKELL__ >= 709 + length (InfixPatSyn _ _) = 2 + length (PrefixPatSyn args) = Data.List.length args + + null (InfixPatSyn _ _) = False + null (PrefixPatSyn args) = Data.List.null args + + toList (InfixPatSyn left right) = [left, right] + toList (PrefixPatSyn args) = args +#endif + instance Traversable HsPatSynDetails where traverse f (InfixPatSyn left right) = InfixPatSyn <$> f left <*> f right traverse f (PrefixPatSyn args) = PrefixPatSyn <$> traverse f args From git at git.haskell.org Wed Nov 19 04:27:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 04:27:48 +0000 (UTC) Subject: [commit: ghc] wip/merge: Refactor: use System.FilePath.splitSearchPath (d38c824) Message-ID: <20141119042748.557CA3A3B3@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/d38c824ddafa3d7cb3180ad58f852731068efd72/ghc >--------------------------------------------------------------- commit d38c824ddafa3d7cb3180ad58f852731068efd72 Author: Thomas Miedema Date: Tue Nov 18 22:17:47 2014 -0600 Refactor: use System.FilePath.splitSearchPath Summary: To address #2521 ("Trailing colon on GHC_PACKAGE_PATH doesn't work with ghc-pkg"), we were using a custom version of splitSearchPath (e4f46f5de). This solution however caused issue #9698 ("GHC_PACKAGE_PATH should be more lenient for empty paths"). This patch reverts back to System.FilePath.splitSearchPath (fixes #9698) and adresses (#2521) by testing for a trailing search path separators explicitly (instead of implicitly using empty search path elements). Empty paths are now allowed (ignored on Windows, interpreted as current directory on Posix systems), and trailing path separator still tack on the user and system package databases. Also update submodule filepath, which has a version of splitSearchPath which handles quotes in the same way as our custom version did. Test Plan: $ GHC_PACKAGE_PATH=/::/home: ./ghc-pkg list ... db stack: ["/",".","/home","",""] ... Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D414 GHC Trac Issues: #2521, #9698 >--------------------------------------------------------------- d38c824ddafa3d7cb3180ad58f852731068efd72 compiler/main/Packages.lhs | 9 +++------ compiler/utils/Util.lhs | 21 --------------------- libraries/filepath | 2 +- utils/ghc-pkg/Main.hs | 27 ++++----------------------- 4 files changed, 8 insertions(+), 51 deletions(-) diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs index 2f4a4d7..40b5e24 100644 --- a/compiler/main/Packages.lhs +++ b/compiler/main/Packages.lhs @@ -334,13 +334,10 @@ readPackageConfigs dflags = do let base_conf_refs = case e_pkg_path of Left _ -> system_conf_refs Right path - | null (last cs) - -> map PkgConfFile (init cs) ++ system_conf_refs + | not (null path) && isSearchPathSeparator (last path) + -> map PkgConfFile (splitSearchPath (init path)) ++ system_conf_refs | otherwise - -> map PkgConfFile cs - where cs = parseSearchPath path - -- if the path ends in a separator (eg. "/foo/bar:") - -- then we tack on the system paths. + -> map PkgConfFile (splitSearchPath path) let conf_refs = reverse (extraPkgConfs dflags base_conf_refs) -- later packages shadow earlier ones. extraPkgConfs diff --git a/compiler/utils/Util.lhs b/compiler/utils/Util.lhs index aa5f6f9..df293f0 100644 --- a/compiler/utils/Util.lhs +++ b/compiler/utils/Util.lhs @@ -89,7 +89,6 @@ module Util ( Suffix, splitLongestPrefix, escapeSpaces, - parseSearchPath, Direction(..), reslash, makeRelativeTo, @@ -1005,26 +1004,6 @@ type Suffix = String -- * Search path -------------------------------------------------------------- --- | The function splits the given string to substrings --- using the 'searchPathSeparator'. -parseSearchPath :: String -> [FilePath] -parseSearchPath path = split path - where - split :: String -> [String] - split s = - case rest' of - [] -> [chunk] - _:rest -> chunk : split rest - where - chunk = - case chunk' of -#ifdef mingw32_HOST_OS - ('\"':xs@(_:_)) | last xs == '\"' -> init xs -#endif - _ -> chunk' - - (chunk', rest') = break isSearchPathSeparator s - data Direction = Forwards | Backwards reslash :: Direction -> FilePath -> FilePath diff --git a/libraries/filepath b/libraries/filepath index 7011e20..83b6d8c 160000 --- a/libraries/filepath +++ b/libraries/filepath @@ -1 +1 @@ -Subproject commit 7011e20dbe30f96f34f6cfb1fd3f3aad9e7a6534 +Subproject commit 83b6d8c555d278f5bb79cef6661d02bc38e72c1e diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs index a67dbb2..b1c7a4b 100644 --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -600,9 +600,10 @@ getPkgDatabases verbosity modify use_user use_cache expand_vars my_flags = do case e_pkg_path of Left _ -> sys_databases Right path - | last cs == "" -> init cs ++ sys_databases - | otherwise -> cs - where cs = parseSearchPath path + | not (null path) && isSearchPathSeparator (last path) + -> splitSearchPath (init path) ++ sys_databases + | otherwise + -> splitSearchPath path -- The "global" database is always the one at the bottom of the stack. -- This is the database we modify by default. @@ -2006,26 +2007,6 @@ openNewFile dir template = do -- in binary mode. openTempFileWithDefaultPermissions dir template --- | The function splits the given string to substrings --- using 'isSearchPathSeparator'. -parseSearchPath :: String -> [FilePath] -parseSearchPath path = split path - where - split :: String -> [String] - split s = - case rest' of - [] -> [chunk] - _:rest -> chunk : split rest - where - chunk = - case chunk' of -#ifdef mingw32_HOST_OS - ('\"':xs@(_:_)) | last xs == '\"' -> init xs -#endif - _ -> chunk' - - (chunk', rest') = break isSearchPathSeparator s - readUTF8File :: FilePath -> IO String readUTF8File file = do h <- openFile file ReadMode From git at git.haskell.org Wed Nov 19 04:27:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 04:27:45 +0000 (UTC) Subject: [commit: ghc] wip/merge: The test runner now also works under the msys-native Python. (a41ceac) Message-ID: <20141119042745.C0A3F3A3B1@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/a41ceacfe5889c16b3f4ac07ef53aeb81c230743/ghc >--------------------------------------------------------------- commit a41ceacfe5889c16b3f4ac07ef53aeb81c230743 Author: Gintautas Miliauskas Date: Mon Sep 22 23:10:56 2014 +0200 The test runner now also works under the msys-native Python. Msys binaries apply heuristics to escape paths in arguments intended for non-msys binaries, which breaks timeout invocations, see #9626. Signed-off-by: Austin Seipp >--------------------------------------------------------------- a41ceacfe5889c16b3f4ac07ef53aeb81c230743 testsuite/driver/testlib.py | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 1549381..6fc86e4 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1780,9 +1780,25 @@ def rawSystem(cmd_and_args): else: return os.spawnv(os.P_WAIT, cmd_and_args[0], cmd_and_args) +# When running under native msys Python, any invocations of non-msys binaries, +# including timeout.exe, will have their arguments munged according to some +# heuristics, which leads to malformed command lines (#9626). The easiest way +# to avoid problems is to invoke through /usr/bin/cmd which sidesteps argument +# munging because it is a native msys application. +def passThroughCmd(cmd_and_args): + args = [] + # cmd needs a Windows-style path for its first argument. + args.append(cmd_and_args[0].replace('/', '\\')) + # Other arguments need to be quoted to deal with spaces. + args.extend(['"%s"' % arg for arg in cmd_and_args[1:]]) + return ["cmd", "/c", " ".join(args)] + # Note that this doesn't handle the timeout itself; it is just used for # commands that have timeout handling built-in. def rawSystemWithTimeout(cmd_and_args): + if config.os == 'mingw32' and sys.executable.startswith('/usr'): + # This is only needed when running under msys python. + cmd_and_args = passThroughCmd(cmd_and_args) r = rawSystem(cmd_and_args) if r == 98: # The python timeout program uses 98 to signal that ^C was pressed From git at git.haskell.org Wed Nov 19 01:33:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 01:33:15 +0000 (UTC) Subject: [commit: ghc] master: When outputting list of available instances, sort it. (1019e3c) Message-ID: <20141119013315.BD6D83A38F@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1019e3c6f90e32785c6a75726282b7362e921047/ghc >--------------------------------------------------------------- commit 1019e3c6f90e32785c6a75726282b7362e921047 Author: Edward Z. Yang Date: Mon Nov 10 16:25:58 2014 -0800 When outputting list of available instances, sort it. Summary: The intent of this commit is to make test suite cases more stable, so that it doesn't matter what order we load interface files in, the test output doesn't change. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D484 >--------------------------------------------------------------- 1019e3c6f90e32785c6a75726282b7362e921047 compiler/typecheck/TcErrors.lhs | 4 ++-- compiler/types/InstEnv.lhs | 16 ++++++++++++++++ testsuite/tests/annotations/should_fail/annfail10.stderr | 16 +++++++++------- testsuite/tests/ghci.debugger/scripts/break006.stderr | 12 ++++++------ testsuite/tests/ghci.debugger/scripts/print019.stderr | 6 +++--- testsuite/tests/ghci/scripts/Defer02.stderr | 2 +- .../should_fail/overloadedlistsfail01.stderr | 8 ++++---- testsuite/tests/typecheck/should_compile/holes2.stderr | 6 +++--- testsuite/tests/typecheck/should_fail/T7857.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/tcfail008.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail043.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail072.stderr | 5 +++-- testsuite/tests/typecheck/should_fail/tcfail133.stderr | 7 +++---- testsuite/tests/typecheck/should_fail/tcfail181.stderr | 4 ++-- 14 files changed, 56 insertions(+), 38 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1019e3c6f90e32785c6a75726282b7362e921047 From git at git.haskell.org Tue Nov 18 22:27:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 22:27:03 +0000 (UTC) Subject: [commit: ghc] master: Comments only (483eeba) Message-ID: <20141118222703.5A2A23A36F@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/483eeba47c8f761e5a0913c37823b640a624c6fb/ghc >--------------------------------------------------------------- commit 483eeba47c8f761e5a0913c37823b640a624c6fb Author: Simon Peyton Jones Date: Tue Nov 18 22:27:01 2014 +0000 Comments only >--------------------------------------------------------------- 483eeba47c8f761e5a0913c37823b640a624c6fb compiler/typecheck/TcFlatten.lhs | 7 ++++--- compiler/typecheck/TcInteract.lhs | 19 ++----------------- compiler/typecheck/TcSMonad.lhs | 2 -- 3 files changed, 6 insertions(+), 22 deletions(-) diff --git a/compiler/typecheck/TcFlatten.lhs b/compiler/typecheck/TcFlatten.lhs index 2e9c6eb..2d41ff8 100644 --- a/compiler/typecheck/TcFlatten.lhs +++ b/compiler/typecheck/TcFlatten.lhs @@ -813,9 +813,10 @@ flattenExactFamApp_fully fmode tc tys \begin{code} flattenTyVar :: FlattenEnv -> TcTyVar -> TcS (Xi, TcCoercion) -- "Flattening" a type variable means to apply the substitution to it --- The substitution is actually the union of the substitution in the TyBinds --- for the unification variables that have been unified already with the inert --- equalities, see Note [Spontaneously solved in TyBinds] in TcInteract. +-- The substitution is actually the union of +-- * the unifications that have taken place (either before the +-- solver started, or in TcInteract.solveByUnification) +-- * the CTyEqCans held in the inert set -- -- Postcondition: co : xi ~ tv flattenTyVar fmode tv diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 3501a99..6a3eca4 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -761,8 +761,8 @@ solveByUnification :: CtEvidence -> TcTyVar -> Xi -> TcS () -- say that in (a ~ xi), the type variable a does not appear in xi. -- See TcRnTypes.Ct invariants. -- --- Post: tv ~ xi is now in TyBinds, no need to put in inerts as well --- see Note [Spontaneously solved in TyBinds] +-- Post: tv is unified (by side effect) with xi; +-- we often write tv := xi solveByUnification wd tv xi = do { let tv_ty = mkTyVarTy tv ; traceTcS "Sneaky unification:" $ @@ -793,21 +793,6 @@ ppr_kicked 0 = empty ppr_kicked n = parens (int n <+> ptext (sLit "kicked out")) \end{code} -Note [Spontaneously solved in TyBinds] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -When we encounter a constraint ([W] alpha ~ tau) which can be spontaneously solved, -we record the equality on the TyBinds of the TcSMonad. In the past, we used to also -add a /given/ version of the constraint ([G] alpha ~ tau) to the inert -canonicals -- and potentially kick out other equalities that mention alpha. - -Then, the flattener only had to look in the inert equalities during flattening of a -type (TcCanonical.flattenTyVar). - -However it is a bit silly to record these equalities /both/ in the inerts AND the -TyBinds, so we have now eliminated spontaneously solved equalities from the inerts, -and only record them in the TyBinds of the TcS monad. The flattener is now consulting -these binds /and/ the inerts for potentially unsolved or other given equalities. - \begin{code} kickOutRewritable :: CtEvidence -- Flavour of the equality that is -- being added to the inert set diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index cd778cf..d4a5a9a 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -379,8 +379,6 @@ Type-family equations, of form (ev : F tys ~ ty), live in three places data InertCans = IC { inert_eqs :: TyVarEnv EqualCtList -- All CTyEqCans; index is the LHS tyvar - -- Some Refl equalities are also in tcs_ty_binds - -- see Note [Spontaneously solved in TyBinds] in TcInteract , inert_funeqs :: FunEqMap Ct -- All CFunEqCans; index is the whole family head type. From git at git.haskell.org Tue Nov 18 20:16:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:16:09 +0000 (UTC) Subject: [commit: packages/array] wip/rae: Fix #9220 by adding role annotations. (4baaf0b) Message-ID: <20141118201609.C01ED3A337@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array On branch : wip/rae Link : http://git.haskell.org/packages/array.git/commitdiff/4baaf0b6d1e7498f529e41eaa3a065cfa84b078c >--------------------------------------------------------------- commit 4baaf0b6d1e7498f529e41eaa3a065cfa84b078c Author: Richard Eisenberg Date: Fri Nov 7 17:30:58 2014 -0500 Fix #9220 by adding role annotations. >--------------------------------------------------------------- 4baaf0b6d1e7498f529e41eaa3a065cfa84b078c Data/Array/Base.hs | 12 ++++++++++++ Data/Array/IO/Internals.hs | 11 ++++++++++- Data/Array/Storable/Internals.hs | 9 ++++++++- tests/all.T | 2 +- 4 files changed, 31 insertions(+), 3 deletions(-) diff --git a/Data/Array/Base.hs b/Data/Array/Base.hs index 27e69c3..e00a97d 100644 --- a/Data/Array/Base.hs +++ b/Data/Array/Base.hs @@ -1,4 +1,7 @@ {-# LANGUAGE BangPatterns, CPP, RankNTypes, MagicHash, UnboxedTuples, MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, DeriveDataTypeable, UnliftedFFITypes #-} +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} +#endif {-# OPTIONS_HADDOCK hide #-} ----------------------------------------------------------------------------- @@ -402,6 +405,10 @@ instance IArray Arr.Array e where -- data UArray i e = UArray !i !i !Int ByteArray# deriving Typeable +#if __GLASGOW_HASKELL__ >= 708 +-- There are class-based invariants on both parameters. See also #9220. +type role UArray nominal nominal +#endif {-# INLINE unsafeArrayUArray #-} unsafeArrayUArray :: (MArray (STUArray s) e (ST s), Ix i) @@ -985,6 +992,11 @@ instance MArray (STArray s) e (Lazy.ST s) where -- 'STArray' provides. data STUArray s i e = STUArray !i !i !Int (MutableByteArray# s) deriving Typeable +#if __GLASGOW_HASKELL__ >= 708 +-- The "ST" parameter must be nominal for the safety of the ST trick. +-- The other parameters have class constraints. See also #9220. +type role STUArray nominal nominal nominal +#endif instance Eq (STUArray s i e) where STUArray _ _ _ arr1# == STUArray _ _ _ arr2# = diff --git a/Data/Array/IO/Internals.hs b/Data/Array/IO/Internals.hs index 6761e99..1a015d9 100644 --- a/Data/Array/IO/Internals.hs +++ b/Data/Array/IO/Internals.hs @@ -1,4 +1,9 @@ -{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses #-} +{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, + CPP #-} +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} +#endif + {-# OPTIONS_HADDOCK hide #-} ----------------------------------------------------------------------------- -- | @@ -47,6 +52,10 @@ import GHC.IOArray (IOArray(..)) -- newtype IOUArray i e = IOUArray (STUArray RealWorld i e) deriving Typeable +#if __GLASGOW_HASKELL__ >= 708 +-- Both parameters have class-based invariants. See also #9220. +type role IOUArray nominal nominal +#endif instance Eq (IOUArray i e) where IOUArray s1 == IOUArray s2 = s1 == s2 diff --git a/Data/Array/Storable/Internals.hs b/Data/Array/Storable/Internals.hs index c844aae..2e44fc1 100644 --- a/Data/Array/Storable/Internals.hs +++ b/Data/Array/Storable/Internals.hs @@ -1,4 +1,7 @@ -{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, CPP #-} +#if __GLASGOW_HASKELL__ >= 708 +{-# LANGUAGE RoleAnnotations #-} +#endif {-# OPTIONS_HADDOCK hide #-} ----------------------------------------------------------------------------- -- | @@ -28,6 +31,10 @@ import Foreign hiding (newArray) -- |The array type data StorableArray i e = StorableArray !i !i Int !(ForeignPtr e) +#if __GLASGOW_HASKELL__ >= 708 +-- Both parameters have class-based invariants. See also #9220. +type role StorableArray nominal nominal +#endif instance Storable e => MArray StorableArray e IO where getBounds (StorableArray l u _ _) = return (l,u) diff --git a/tests/all.T b/tests/all.T index cd3ae47..c563441 100644 --- a/tests/all.T +++ b/tests/all.T @@ -3,4 +3,4 @@ test('T2120', normal, compile_and_run, ['']) test('largeArray', normal, compile_and_run, ['']) test('array001', extra_clean(['array001.data']), compile_and_run, ['']) -test('T9220', expect_broken(9220), ghci_script, ['T9220.script']) +test('T9220', normal, ghci_script, ['T9220.script']) From git at git.haskell.org Tue Nov 18 20:16:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:16:07 +0000 (UTC) Subject: [commit: packages/array] wip/rae: Test #9220 in libraries/array/tests/T9220 (80a463b) Message-ID: <20141118201607.B9A393A302@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array On branch : wip/rae Link : http://git.haskell.org/packages/array.git/commitdiff/80a463bd57be183af9893553daecd4d0af815d04 >--------------------------------------------------------------- commit 80a463bd57be183af9893553daecd4d0af815d04 Author: Richard Eisenberg Date: Fri Nov 7 17:27:54 2014 -0500 Test #9220 in libraries/array/tests/T9220 >--------------------------------------------------------------- 80a463bd57be183af9893553daecd4d0af815d04 tests/.gitignore | 1 + tests/T9220.script | 4 ++++ tests/T9220.stdout | 42 ++++++++++++++++++++++++++++++++++++++++++ tests/all.T | 1 + 4 files changed, 48 insertions(+) diff --git a/tests/.gitignore b/tests/.gitignore index 95e6531..5052e9c 100644 --- a/tests/.gitignore +++ b/tests/.gitignore @@ -3,6 +3,7 @@ *.hi *.comp.std* *.run.std* +*.normalised *.eventlog *.genscript *.exe diff --git a/tests/T9220.script b/tests/T9220.script new file mode 100644 index 0000000..0254e7d --- /dev/null +++ b/tests/T9220.script @@ -0,0 +1,4 @@ +:info Data.Array.Base.UArray +:info Data.Array.IO.IOUArray +:info Data.Array.ST.STUArray +:info Data.Array.Storable.StorableArray diff --git a/tests/T9220.stdout b/tests/T9220.stdout new file mode 100644 index 0000000..71582f2 --- /dev/null +++ b/tests/T9220.stdout @@ -0,0 +1,42 @@ +type role Data.Array.Base.UArray nominal nominal +data Data.Array.Base.UArray i e + = Data.Array.Base.UArray !i + !i + {-# UNPACK #-}Int + GHC.Prim.ByteArray# + -- Defined in ?Data.Array.Base? +instance (GHC.Arr.Ix ix, Eq e, + Data.Array.Base.IArray Data.Array.Base.UArray e) => + Eq (Data.Array.Base.UArray ix e) + -- Defined in ?Data.Array.Base? +instance (GHC.Arr.Ix ix, Ord e, + Data.Array.Base.IArray Data.Array.Base.UArray e) => + Ord (Data.Array.Base.UArray ix e) + -- Defined in ?Data.Array.Base? +instance (GHC.Arr.Ix ix, Show ix, Show e, + Data.Array.Base.IArray Data.Array.Base.UArray e) => + Show (Data.Array.Base.UArray ix e) + -- Defined in ?Data.Array.Base? +type role Data.Array.IO.Internals.IOUArray nominal nominal +newtype Data.Array.IO.Internals.IOUArray i e + = Data.Array.IO.Internals.IOUArray (Data.Array.Base.STUArray + GHC.Prim.RealWorld i e) + -- Defined in ?Data.Array.IO.Internals? +instance Eq (Data.Array.IO.Internals.IOUArray i e) + -- Defined in ?Data.Array.IO.Internals? +type role Data.Array.Base.STUArray nominal nominal nominal +data Data.Array.Base.STUArray s i e + = Data.Array.Base.STUArray !i + !i + {-# UNPACK #-}Int + (GHC.Prim.MutableByteArray# s) + -- Defined in ?Data.Array.Base? +instance Eq (Data.Array.Base.STUArray s i e) + -- Defined in ?Data.Array.Base? +type role Data.Array.Storable.Internals.StorableArray nominal nominal +data Data.Array.Storable.Internals.StorableArray i e + = Data.Array.Storable.Internals.StorableArray !i + !i + Int + !(GHC.ForeignPtr.ForeignPtr e) + -- Defined in ?Data.Array.Storable.Internals? diff --git a/tests/all.T b/tests/all.T index 73e3b66..cd3ae47 100644 --- a/tests/all.T +++ b/tests/all.T @@ -3,3 +3,4 @@ test('T2120', normal, compile_and_run, ['']) test('largeArray', normal, compile_and_run, ['']) test('array001', extra_clean(['array001.data']), compile_and_run, ['']) +test('T9220', expect_broken(9220), ghci_script, ['T9220.script']) From git at git.haskell.org Tue Nov 18 20:22:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:22:16 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9109 in typecheck/should_fail/T9109 (e476202) Message-ID: <20141118202216.4526C3A353@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/e476202322624457f17081f3527b96636a989988/ghc >--------------------------------------------------------------- commit e476202322624457f17081f3527b96636a989988 Author: Richard Eisenberg Date: Tue Nov 18 15:19:20 2014 -0500 Test #9109 in typecheck/should_fail/T9109 >--------------------------------------------------------------- e476202322624457f17081f3527b96636a989988 testsuite/tests/typecheck/should_fail/T9109.hs | 8 ++++++++ testsuite/tests/typecheck/should_fail/T9109.stderr | 15 +++++++++++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 24 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T9109.hs b/testsuite/tests/typecheck/should_fail/T9109.hs new file mode 100644 index 0000000..725cb66 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9109.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE GADTs #-} + +module T9109 where + +data G a where + GBool :: G Bool + +foo GBool = True diff --git a/testsuite/tests/typecheck/should_fail/T9109.stderr b/testsuite/tests/typecheck/should_fail/T9109.stderr new file mode 100644 index 0000000..5ef2340 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9109.stderr @@ -0,0 +1,15 @@ + +T9109.hs:8:13: + Couldn't match expected type ?t? with actual type ?Bool? + ?t? is untouchable + inside the constraints (t1 ~ Bool) + bound by a pattern with constructor + GBool :: G Bool, + in an equation for ?foo? + at T9109.hs:8:5-9 + ?t? is a rigid type variable bound by + the inferred type of foo :: G t1 -> t at T9109.hs:8:1 + Possible fix: add a type signature for ?foo? + Relevant bindings include foo :: G t1 -> t (bound at T9109.hs:8:1) + In the expression: True + In an equation for ?foo?: foo GBool = True diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 14df71e..28709e8 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -344,3 +344,4 @@ test('T9739', normal, compile_fail, ['']) test('T9774', normal, compile_fail, ['']) test('T9318', normal, compile_fail, ['']) test('T9201', normal, compile_fail, ['']) +test('T9109', normal, compile_fail, ['']) From git at git.haskell.org Tue Nov 18 20:21:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:21:37 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9209 in th/T9209 (c464245) Message-ID: <20141118202137.9D8203A339@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/c464245f4c91986b7115108202845a561606294e/ghc >--------------------------------------------------------------- commit c464245f4c91986b7115108202845a561606294e Author: Richard Eisenberg Date: Mon Nov 3 13:46:58 2014 -0500 Test #9209 in th/T9209 >--------------------------------------------------------------- c464245f4c91986b7115108202845a561606294e testsuite/tests/th/T9209.hs | 5 +++++ testsuite/tests/th/T9209.stderr | 4 ++++ testsuite/tests/th/all.T | 1 + 3 files changed, 10 insertions(+) diff --git a/testsuite/tests/th/T9209.hs b/testsuite/tests/th/T9209.hs new file mode 100644 index 0000000..46740ba --- /dev/null +++ b/testsuite/tests/th/T9209.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T9209 where + +foo = let $( [d| x = 5 |] ) in x diff --git a/testsuite/tests/th/T9209.stderr b/testsuite/tests/th/T9209.stderr new file mode 100644 index 0000000..1f4f3e7 --- /dev/null +++ b/testsuite/tests/th/T9209.stderr @@ -0,0 +1,4 @@ + +T9209.hs:5:11: + Declaration splices are allowed only at the top level: + $([d| x = 5 |]) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 90efcbd..466e925 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -339,3 +339,4 @@ test('T9081', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T8100', normal, compile, ['-v0']) test('T9064', normal, compile, ['-v0']) +test('T9209', expect_broken(9209), compile_fail, ['-v0']) From git at git.haskell.org Tue Nov 18 20:22:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:22:01 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9220 by adding role annotations. (aba5000) Message-ID: <20141118202201.16A473A349@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/aba50001bac3400ff91135b02725fb5b4303e81a/ghc >--------------------------------------------------------------- commit aba50001bac3400ff91135b02725fb5b4303e81a Author: Richard Eisenberg Date: Fri Nov 7 17:34:59 2014 -0500 Fix #9220 by adding role annotations. This includes a submodule update for `array`. There is also an added test in libraries/array/tests/T9220. >--------------------------------------------------------------- aba50001bac3400ff91135b02725fb5b4303e81a libraries/array | 2 +- libraries/base/GHC/Arr.hs | 6 +- libraries/base/GHC/IOArray.hs | 5 +- testsuite/tests/roles/should_compile/all.T | 1 - .../{should_compile => should_fail}/RolesIArray.hs | 0 .../tests/roles/should_fail/RolesIArray.stderr | 100 +++++++++++++++++++++ testsuite/tests/roles/should_fail/all.T | 1 + 7 files changed, 111 insertions(+), 4 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc aba50001bac3400ff91135b02725fb5b4303e81a From git at git.haskell.org Tue Nov 18 20:21:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:21:46 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #7484, checking for good binder names in Convert. (8f70633) Message-ID: <20141118202146.94A463A33F@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/8f7063314050e446e62d69dc0033ea1f5073a38e/ghc >--------------------------------------------------------------- commit 8f7063314050e446e62d69dc0033ea1f5073a38e Author: Richard Eisenberg Date: Mon Nov 3 15:34:53 2014 -0500 Fix #7484, checking for good binder names in Convert. This commit also refactors a bunch of lexeme-oriented code into a new module Lexeme. >--------------------------------------------------------------- 8f7063314050e446e62d69dc0033ea1f5073a38e compiler/basicTypes/Lexeme.hs | 252 ++++++++++++++++++++++++++++++++++++++ compiler/basicTypes/OccName.lhs | 72 +---------- compiler/ghc.cabal.in | 1 + compiler/ghc.mk | 1 + compiler/hsSyn/Convert.lhs | 12 +- compiler/typecheck/TcGenDeriv.lhs | 1 + compiler/typecheck/TcSplice.lhs | 1 + testsuite/tests/th/all.T | 2 +- 8 files changed, 263 insertions(+), 79 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8f7063314050e446e62d69dc0033ea1f5073a38e From git at git.haskell.org Tue Nov 18 20:22:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:22:18 +0000 (UTC) Subject: [commit: ghc] wip/rae: Update manual to get rid of bogus `coerce` example (#9788) (ee543e5) Message-ID: <20141118202218.EC5D63A35B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/ee543e5f27d8c2848ecea387dc694fb75da3fff4/ghc >--------------------------------------------------------------- commit ee543e5f27d8c2848ecea387dc694fb75da3fff4 Author: Richard Eisenberg Date: Tue Nov 18 14:22:30 2014 -0500 Update manual to get rid of bogus `coerce` example (#9788) >--------------------------------------------------------------- ee543e5f27d8c2848ecea387dc694fb75da3fff4 docs/users_guide/using.xml | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/docs/users_guide/using.xml b/docs/users_guide/using.xml index 07d487e..e9df9e4 100644 --- a/docs/users_guide/using.xml +++ b/docs/users_guide/using.xml @@ -910,10 +910,11 @@ GHC.ST.runST :: (forall s. GHC.ST.ST s a) -> a If any of the quantified type variables has a kind that mentions a kind variable, e.g. -ghci> :i Data.Coerce.coerce -coerce :: - forall (k :: BOX) (a :: k) (b :: k). Coercible a b => a -> b - -- Defined in GHC.Prim +ghci> :i Data.Type.Equality.sym +Data.Type.Equality.sym :: + forall (k :: BOX) (a :: k) (b :: k). + (a Data.Type.Equality.:~: b) -> b Data.Type.Equality.:~: a + -- Defined in Data.Type.Equality From git at git.haskell.org Tue Nov 18 20:22:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:22:12 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9201 in typecheck/should_fail/T9201 (91304b9) Message-ID: <20141118202212.E425F3A351@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/91304b94389a6b52fc700f2c8170866369098e3f/ghc >--------------------------------------------------------------- commit 91304b94389a6b52fc700f2c8170866369098e3f Author: Richard Eisenberg Date: Tue Nov 18 13:19:42 2014 -0500 Test #9201 in typecheck/should_fail/T9201 >--------------------------------------------------------------- 91304b94389a6b52fc700f2c8170866369098e3f testsuite/tests/typecheck/should_fail/T9201.hs | 6 ++++++ testsuite/tests/typecheck/should_fail/T9201.stderr | 6 ++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 13 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T9201.hs b/testsuite/tests/typecheck/should_fail/T9201.hs new file mode 100644 index 0000000..7702fa3 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9201.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE PolyKinds, FunctionalDependencies, MultiParamTypeClasses #-} + +module T9201 where + +class MonoidalCCC (f :: x -> y) (d :: y -> y -> *) | f -> d where + ret :: d a (f a) diff --git a/testsuite/tests/typecheck/should_fail/T9201.stderr b/testsuite/tests/typecheck/should_fail/T9201.stderr new file mode 100644 index 0000000..44e338a --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9201.stderr @@ -0,0 +1,6 @@ + +T9201.hs:6:17: + The first argument of ?f? should have kind ?x1?, + but ?a? has kind ?y1? + In the type ?d a (f a)? + In the class declaration for ?MonoidalCCC? diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index b6b5572..14df71e 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -343,3 +343,4 @@ test('T9634', normal, compile_fail, ['']) test('T9739', normal, compile_fail, ['']) test('T9774', normal, compile_fail, ['']) test('T9318', normal, compile_fail, ['']) +test('T9201', normal, compile_fail, ['']) From git at git.haskell.org Tue Nov 18 20:21:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:21:43 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #7484 in th/T7484 (f4be960) Message-ID: <20141118202143.772E73A33D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/f4be9602b311d8bb1a6bbb873a64957ae7d630f0/ghc >--------------------------------------------------------------- commit f4be9602b311d8bb1a6bbb873a64957ae7d630f0 Author: Richard Eisenberg Date: Mon Nov 3 15:33:51 2014 -0500 Test #7484 in th/T7484 >--------------------------------------------------------------- f4be9602b311d8bb1a6bbb873a64957ae7d630f0 testsuite/tests/th/T7484.hs | 7 +++++++ testsuite/tests/th/T7484.stderr | 4 ++++ testsuite/tests/th/all.T | 1 + 3 files changed, 12 insertions(+) diff --git a/testsuite/tests/th/T7484.hs b/testsuite/tests/th/T7484.hs new file mode 100644 index 0000000..b1a9cba --- /dev/null +++ b/testsuite/tests/th/T7484.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T7484 where + +import Language.Haskell.TH + +$( return [ ValD (VarP (mkName "a ")) (NormalB (LitE (IntegerL 5))) [] ] ) diff --git a/testsuite/tests/th/T7484.stderr b/testsuite/tests/th/T7484.stderr new file mode 100644 index 0000000..3ffe123 --- /dev/null +++ b/testsuite/tests/th/T7484.stderr @@ -0,0 +1,4 @@ + +T7484.hs:7:4: + Illegal variable name: ?a ? + When splicing a TH declaration: a = 5 diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index f1acef0..53ee751 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -340,3 +340,4 @@ test('T9066', normal, compile, ['-v0']) test('T8100', normal, compile, ['-v0']) test('T9064', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) +test('T7484', expect_broken(7484), compile_fail, ['-v0']) From git at git.haskell.org Tue Nov 18 20:21:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:21:58 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #1476 by making splice patterns work. (2130d0a) Message-ID: <20141118202158.0F6283A347@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/2130d0a2e8eca4dd5c777ce9a7e47482770e6cf2/ghc >--------------------------------------------------------------- commit 2130d0a2e8eca4dd5c777ce9a7e47482770e6cf2 Author: Richard Eisenberg Date: Tue Nov 4 11:34:53 2014 -0500 Fix #1476 by making splice patterns work. Unfortunately, splice patterns in brackets still do not work because we don't run splices in brackets. Without running a pattern splice, we can't know what variables it binds, so we're stuck. This is still a substantial improvement, and it may be the best we can do. Still must document new behavior. >--------------------------------------------------------------- 2130d0a2e8eca4dd5c777ce9a7e47482770e6cf2 compiler/rename/RnPat.lhs | 10 ++++++---- compiler/rename/RnSplice.lhs | 38 +++++++++++++++++++++++++++++++------- compiler/rename/RnSplice.lhs-boot | 3 ++- testsuite/tests/th/all.T | 2 +- 4 files changed, 40 insertions(+), 13 deletions(-) diff --git a/compiler/rename/RnPat.lhs b/compiler/rename/RnPat.lhs index aa41361..634c99c 100644 --- a/compiler/rename/RnPat.lhs +++ b/compiler/rename/RnPat.lhs @@ -440,10 +440,12 @@ rnPatAndThen mk (TuplePat pats boxed _) ; pats' <- rnLPatsAndThen mk pats ; return (TuplePat pats' boxed []) } -rnPatAndThen _ (SplicePat splice) - = do { -- XXX How to deal with free variables? - ; (pat, _) <- liftCps $ rnSplicePat splice - ; return pat } +rnPatAndThen mk (SplicePat splice) + = do { eith <- liftCpsFV $ rnSplicePat splice + ; case eith of -- See Note [rnSplicePat] in RnSplice + Left not_yet_renamed -> rnPatAndThen mk not_yet_renamed + Right already_renamed -> return already_renamed } + rnPatAndThen mk (QuasiQuotePat qq) = do { pat <- liftCps $ runQuasiQuotePat qq -- Wrap the result of the quasi-quoter in parens so that we don't diff --git a/compiler/rename/RnSplice.lhs b/compiler/rename/RnSplice.lhs index 59c8c62..8918e39 100644 --- a/compiler/rename/RnSplice.lhs +++ b/compiler/rename/RnSplice.lhs @@ -206,13 +206,40 @@ rnSpliceType splice k } ; return (unLoc hs_ty3, fvs) } ----------------------- -rnSplicePat :: HsSplice RdrName -> RnM (Pat Name, FreeVars) +\end{code} + +Note [rnSplicePat] +~~~~~~~~~~~~~~~~~~ +Renaming a pattern splice is a bit tricky, because we need the variables +bound in the pattern to be in scope in the RHS of the pattern. This scope +management is effectively done by using continuation-passing style in +RnPat, through the CpsRn monad. We don't wish to be in that monad here +(it would create import cycles and generally conflict with renaming other +splices), so we really want to return a (Pat RdrName) -- the result of +running the splice -- which can then be further renamed in RnPat, in +the CpsRn monad. + +The problem is that if we're renaming a splice within a bracket, we +*don't* want to run the splice now. We really do just want to rename +it to an HsSplice Name. Of course, then we can't know what variables +are bound within the splice, so pattern splices within brackets aren't +all that useful. + +In any case, when we're done in rnSplicePat, we'll either have a +Pat RdrName (the result of running a top-level splice) or a Pat Name +(the renamed nested splice). Thus, the awkward return type of +rnSplicePat. + +\begin{code} + +-- | Rename a splice pattern. See Note [rnSplicePat] +rnSplicePat :: HsSplice RdrName -> RnM ( Either (Pat RdrName) (Pat Name) + , FreeVars) rnSplicePat splice = rnSpliceGen False run_pat_splice pend_pat_splice splice where pend_pat_splice rn_splice@(HsSplice n e) - = (PendingRnPatSplice (PendSplice n e), SplicePat rn_splice) + = (PendingRnPatSplice (PendSplice n e), Right $ SplicePat rn_splice) run_pat_splice (HsSplice _ expr') = do { expr <- getHooked runRnSpliceHook return >>= ($ expr') @@ -227,10 +254,7 @@ rnSplicePat splice ; pat <- runMetaP zonked_q_expr ; showSplice "pattern" expr (ppr pat) - ; (pat', fvs) <- checkNoErrs $ - rnPat ThPatSplice pat $ \pat' -> return (pat', emptyFVs) - - ; return (unLoc pat', fvs) } + ; return (Left $ unLoc pat, emptyFVs) } ---------------------- rnSpliceDecl :: SpliceDecl RdrName -> RnM (SpliceDecl Name, FreeVars) diff --git a/compiler/rename/RnSplice.lhs-boot b/compiler/rename/RnSplice.lhs-boot index 45a2a10..de6da77 100644 --- a/compiler/rename/RnSplice.lhs-boot +++ b/compiler/rename/RnSplice.lhs-boot @@ -11,6 +11,7 @@ import Kind rnSpliceType :: HsSplice RdrName -> PostTc Name Kind -> RnM (HsType Name, FreeVars) -rnSplicePat :: HsSplice RdrName -> RnM (Pat Name, FreeVars) +rnSplicePat :: HsSplice RdrName -> RnM ( Either (Pat RdrName) (Pat Name) + , FreeVars ) rnSpliceDecl :: SpliceDecl RdrName -> RnM (SpliceDecl Name, FreeVars) \end{code} diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index a636986..e54b257 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -341,5 +341,5 @@ test('T8100', normal, compile, ['-v0']) test('T9064', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) -test('T1476', expect_broken(1476), compile, ['-v0']) +test('T1476', normal, compile, ['-v0']) test('T1476b', normal, compile_fail, ['-v0']) From git at git.haskell.org Tue Nov 18 20:21:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:21:52 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test that nested pattern splices don't scope (#1476). (52eec0e) Message-ID: <20141118202152.D09DF3A343@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/52eec0e46091221ff806d6103af5fff3797c0590/ghc >--------------------------------------------------------------- commit 52eec0e46091221ff806d6103af5fff3797c0590 Author: Richard Eisenberg Date: Tue Nov 4 13:06:56 2014 -0500 Test that nested pattern splices don't scope (#1476). Test case: th/T1476b. >--------------------------------------------------------------- 52eec0e46091221ff806d6103af5fff3797c0590 testsuite/tests/th/T1476b.hs | 10 ++++++++++ testsuite/tests/th/T1476b.stderr | 5 +++++ testsuite/tests/th/all.T | 1 + 3 files changed, 16 insertions(+) diff --git a/testsuite/tests/th/T1476b.hs b/testsuite/tests/th/T1476b.hs new file mode 100644 index 0000000..918a397 --- /dev/null +++ b/testsuite/tests/th/T1476b.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T1476b where + +import Language.Haskell.TH + +baz = [| \ $( return $ VarP $ mkName "x" ) -> x |] + +-- If this test starts passing, nested pattern splices scope correctly. +-- Good for you! Now, update the TH manual accordingly. diff --git a/testsuite/tests/th/T1476b.stderr b/testsuite/tests/th/T1476b.stderr new file mode 100644 index 0000000..65b0814 --- /dev/null +++ b/testsuite/tests/th/T1476b.stderr @@ -0,0 +1,5 @@ + +T1476b.hs:7:47: + Not in scope: ?x? + In the Template Haskell quotation + [| \ $(return $ VarP $ mkName "x") -> x |] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index b23a615..a636986 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -342,3 +342,4 @@ test('T9064', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) test('T1476', expect_broken(1476), compile, ['-v0']) +test('T1476b', normal, compile_fail, ['-v0']) From git at git.haskell.org Tue Nov 18 20:22:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:22:04 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9151 in typecheck/should_compile/T9151. (12c1c99) Message-ID: <20141118202204.2041B3A34B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/12c1c9979424f9f89ae35fa4a690c2221c1f25f6/ghc >--------------------------------------------------------------- commit 12c1c9979424f9f89ae35fa4a690c2221c1f25f6 Author: Richard Eisenberg Date: Wed Nov 12 14:48:25 2014 -0500 Test #9151 in typecheck/should_compile/T9151. This test case should pass right now -- the bug is fixed, presumably by #9200. >--------------------------------------------------------------- 12c1c9979424f9f89ae35fa4a690c2221c1f25f6 testsuite/tests/typecheck/should_compile/T9151.hs | 11 +++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 12 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T9151.hs b/testsuite/tests/typecheck/should_compile/T9151.hs new file mode 100644 index 0000000..351c563 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9151.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE PolyKinds, DataKinds, TypeFamilies, UndecidableInstances #-} + +module T9151 where + +import Data.Proxy + +class PEnum (kproxy :: KProxy a) where + type ToEnum (x :: a) :: Bool + type ToEnum x = TEHelper + +type TEHelper = ToEnum Int diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index ef830d1..ea7d343 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -425,3 +425,4 @@ test('T9708', normal, compile_fail, ['']) test('T9404', normal, compile, ['']) test('T9404b', normal, compile, ['']) test('T7220', normal, compile, ['']) +test('T9151', normal, compile, ['']) From git at git.haskell.org Tue Nov 18 20:22:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:22:06 +0000 (UTC) Subject: [commit: ghc] wip/rae: Add release notes for #8100, #9527, and #9064. (4c07ad0) Message-ID: <20141118202206.BC6863A34D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/4c07ad044ba751372e92bf1e53f66c52d0b41e05/ghc >--------------------------------------------------------------- commit 4c07ad044ba751372e92bf1e53f66c52d0b41e05 Author: Richard Eisenberg Date: Wed Nov 12 15:13:34 2014 -0500 Add release notes for #8100, #9527, and #9064. >--------------------------------------------------------------- 4c07ad044ba751372e92bf1e53f66c52d0b41e05 docs/users_guide/7.10.1-notes.xml | 13 +++++++++++++ 1 file changed, 13 insertions(+) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 4d25ee8..78dbb36 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -157,6 +157,19 @@ use bogus names in your Template Haskell code, this may break your program. + + + All Template Haskell datatypes now have + Generic instances. + + + + Two new declaration forms are now supported: + standalone-deriving declarations and generic method + signatures (written using default in + a class). This means an expansion to the Dec + type. + From git at git.haskell.org Tue Nov 18 20:21:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:21:49 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #1476 in th/T1476 (3e47088) Message-ID: <20141118202149.AC5FB3A341@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/3e470887b7ef27c54fa53ed83287a4f74c694972/ghc >--------------------------------------------------------------- commit 3e470887b7ef27c54fa53ed83287a4f74c694972 Author: Richard Eisenberg Date: Mon Nov 3 20:26:14 2014 -0500 Test #1476 in th/T1476 >--------------------------------------------------------------- 3e470887b7ef27c54fa53ed83287a4f74c694972 testsuite/tests/th/T1476.hs | 10 ++++++++++ testsuite/tests/th/all.T | 1 + 2 files changed, 11 insertions(+) diff --git a/testsuite/tests/th/T1476.hs b/testsuite/tests/th/T1476.hs new file mode 100644 index 0000000..7e3a192 --- /dev/null +++ b/testsuite/tests/th/T1476.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T1476 where + +import Language.Haskell.TH + +foo $( return $ VarP $ mkName "x" ) = x +bar $( [p| x |] ) = x + +baz = [| \ $( return $ VarP $ mkName "x" ) -> $(dyn "x") |] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 31de6ab..b23a615 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -341,3 +341,4 @@ test('T8100', normal, compile, ['-v0']) test('T9064', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) +test('T1476', expect_broken(1476), compile, ['-v0']) From git at git.haskell.org Tue Nov 18 20:21:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:21:40 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9209, by reporting an error instead of panicking on bad splices. (458c220) Message-ID: <20141118202140.5B8603A33B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/458c2205a60ac3c0ab1c85a2fdb2b1700ec9495d/ghc >--------------------------------------------------------------- commit 458c2205a60ac3c0ab1c85a2fdb2b1700ec9495d Author: Richard Eisenberg Date: Mon Nov 3 13:49:59 2014 -0500 Fix #9209, by reporting an error instead of panicking on bad splices. >--------------------------------------------------------------- 458c2205a60ac3c0ab1c85a2fdb2b1700ec9495d compiler/parser/Parser.y | 15 ++++++------ compiler/parser/RdrHsSyn.hs | 57 ++++++++++++++++++++++++++------------------- testsuite/tests/th/all.T | 2 +- 3 files changed, 42 insertions(+), 32 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 2e1b777..39459f8 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -690,12 +690,12 @@ ty_decl :: { LTyClDecl RdrName } inst_decl :: { LInstDecl RdrName } : 'instance' overlap_pragma inst_type where_inst - { let (binds, sigs, _, ats, adts, _) = cvBindsAndSigs (unLoc $4) in - let cid = ClsInstDecl { cid_poly_ty = $3, cid_binds = binds - , cid_sigs = sigs, cid_tyfam_insts = ats - , cid_overlap_mode = $2 - , cid_datafam_insts = adts } - in L (comb3 $1 $3 $4) (ClsInstD { cid_inst = cid }) } + {% do { (binds, sigs, _, ats, adts, _) <- cvBindsAndSigs (unLoc $4) + ; let cid = ClsInstDecl { cid_poly_ty = $3, cid_binds = binds + , cid_sigs = sigs, cid_tyfam_insts = ats + , cid_overlap_mode = $2 + , cid_datafam_insts = adts } + ; return (L (comb3 $1 $3 $4) (ClsInstD { cid_inst = cid })) } } -- type instance declarations | 'type' 'instance' ty_fam_inst_eqn @@ -956,7 +956,8 @@ decllist :: { Located (OrdList (LHsDecl RdrName)) } -- binds :: { Located (HsLocalBinds RdrName) } -- May have implicit parameters -- No type declarations - : decllist { sL1 $1 (HsValBinds (cvBindGroup (unLoc $1))) } + : decllist {% do { val_binds <- cvBindGroup (unLoc $1) + ; return (sL1 $1 (HsValBinds val_binds)) } } | '{' dbinds '}' { sLL $1 $> (HsIPBinds (IPBinds (unLoc $2) emptyTcEvBinds)) } | vocurly dbinds close { L (getLoc $2) (HsIPBinds (IPBinds (unLoc $2) emptyTcEvBinds)) } diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs index 625c4dc..8d58354 100644 --- a/compiler/parser/RdrHsSyn.hs +++ b/compiler/parser/RdrHsSyn.hs @@ -125,8 +125,8 @@ mkClassDecl :: SrcSpan -> P (LTyClDecl RdrName) mkClassDecl loc (L _ (mcxt, tycl_hdr)) fds where_cls - = do { let (binds, sigs, ats, at_insts, _, docs) = cvBindsAndSigs (unLoc where_cls) - cxt = fromMaybe (noLoc []) mcxt + = do { (binds, sigs, ats, at_insts, _, docs) <- cvBindsAndSigs (unLoc where_cls) + ; let cxt = fromMaybe (noLoc []) mcxt ; (cls, tparams) <- checkTyClHdr tycl_hdr ; tyvars <- checkTyVarsP (ptext (sLit "class")) whereDots cls tparams ; at_defs <- mapM (eitherToP . mkATDefault) at_insts @@ -304,36 +304,45 @@ cvTopDecls decls = go (fromOL decls) go (d : ds) = d : go ds -- Declaration list may only contain value bindings and signatures. -cvBindGroup :: OrdList (LHsDecl RdrName) -> HsValBinds RdrName +cvBindGroup :: OrdList (LHsDecl RdrName) -> P (HsValBinds RdrName) cvBindGroup binding - = case cvBindsAndSigs binding of - (mbs, sigs, fam_ds, tfam_insts, dfam_insts, _) - -> ASSERT( null fam_ds && null tfam_insts && null dfam_insts) - ValBindsIn mbs sigs + = do { (mbs, sigs, fam_ds, tfam_insts, dfam_insts, _) <- cvBindsAndSigs binding + ; ASSERT( null fam_ds && null tfam_insts && null dfam_insts) + return $ ValBindsIn mbs sigs } cvBindsAndSigs :: OrdList (LHsDecl RdrName) - -> (LHsBinds RdrName, [LSig RdrName], [LFamilyDecl RdrName] + -> P (LHsBinds RdrName, [LSig RdrName], [LFamilyDecl RdrName] , [LTyFamInstDecl RdrName], [LDataFamInstDecl RdrName], [LDocDecl]) -- Input decls contain just value bindings and signatures -- and in case of class or instance declarations also -- associated type declarations. They might also contain Haddock comments. -cvBindsAndSigs fb = go (fromOL fb) +cvBindsAndSigs fb = go (fromOL fb) where - go [] = (emptyBag, [], [], [], [], []) - go (L l (SigD s) : ds) = (bs, L l s : ss, ts, tfis, dfis, docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L l (ValD b) : ds) = (b' `consBag` bs, ss, ts, tfis, dfis, docs) - where (b', ds') = getMonoBind (L l b) ds - (bs, ss, ts, tfis, dfis, docs) = go ds' - go (L l (TyClD (FamDecl t)) : ds) = (bs, ss, L l t : ts, tfis, dfis, docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L l (InstD (TyFamInstD { tfid_inst = tfi })) : ds) = (bs, ss, ts, L l tfi : tfis, dfis, docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L l (InstD (DataFamInstD { dfid_inst = dfi })) : ds) = (bs, ss, ts, tfis, L l dfi : dfis, docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L l (DocD d) : ds) = (bs, ss, ts, tfis, dfis, (L l d) : docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L _ d : _) = pprPanic "cvBindsAndSigs" (ppr d) + go [] = return (emptyBag, [], [], [], [], []) + go (L l (ValD b) : ds) + = do { (bs, ss, ts, tfis, dfis, docs) <- go ds' + ; return (b' `consBag` bs, ss, ts, tfis, dfis, docs) } + where + (b', ds') = getMonoBind (L l b) ds + go (L l decl : ds) + = do { (bs, ss, ts, tfis, dfis, docs) <- go ds + ; case decl of + SigD s + -> return (bs, L l s : ss, ts, tfis, dfis, docs) + TyClD (FamDecl t) + -> return (bs, ss, L l t : ts, tfis, dfis, docs) + InstD (TyFamInstD { tfid_inst = tfi }) + -> return (bs, ss, ts, L l tfi : tfis, dfis, docs) + InstD (DataFamInstD { dfid_inst = dfi }) + -> return (bs, ss, ts, tfis, L l dfi : dfis, docs) + DocD d + -> return (bs, ss, ts, tfis, dfis, L l d : docs) + SpliceD d + -> parseErrorSDoc l $ + hang (text "Declaration splices are allowed only" <+> + text "at the top level:") + 2 (ppr d) + _ -> pprPanic "cvBindsAndSigs" (ppr decl) } ----------------------------------------------------------------------------- -- Group function bindings into equation groups diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 466e925..f1acef0 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -339,4 +339,4 @@ test('T9081', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T8100', normal, compile, ['-v0']) test('T9064', normal, compile, ['-v0']) -test('T9209', expect_broken(9209), compile_fail, ['-v0']) +test('T9209', normal, compile_fail, ['-v0']) From git at git.haskell.org Tue Nov 18 20:22:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:22:09 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9318 in typecheck/should_fail/T9318 (908d540) Message-ID: <20141118202209.CB41D3A34F@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/908d5404cc781fde0efef1c1e2f4b7b0891f677f/ghc >--------------------------------------------------------------- commit 908d5404cc781fde0efef1c1e2f4b7b0891f677f Author: Richard Eisenberg Date: Tue Nov 18 13:16:01 2014 -0500 Test #9318 in typecheck/should_fail/T9318 >--------------------------------------------------------------- 908d5404cc781fde0efef1c1e2f4b7b0891f677f testsuite/tests/typecheck/should_fail/T9318.hs | 12 ++++++++++++ testsuite/tests/typecheck/should_fail/T9318.stderr | 7 +++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 20 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T9318.hs b/testsuite/tests/typecheck/should_fail/T9318.hs new file mode 100644 index 0000000..3110305 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9318.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE TypeFamilies #-} + +module T9318 where + +type family F x +type instance F Int = Bool + +foo :: F Int -> () +foo True = () + +bar :: F Int -> () +bar 'x' = () diff --git a/testsuite/tests/typecheck/should_fail/T9318.stderr b/testsuite/tests/typecheck/should_fail/T9318.stderr new file mode 100644 index 0000000..963d73e --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9318.stderr @@ -0,0 +1,7 @@ + +T9318.hs:12:5: + Couldn't match type ?Bool? with ?Char? + Expected type: F Int + Actual type: Char + In the pattern: 'x' + In an equation for ?bar?: bar 'x' = () diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 2b128dc..b6b5572 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -342,3 +342,4 @@ test('T9612', normal, compile_fail, ['']) test('T9634', normal, compile_fail, ['']) test('T9739', normal, compile_fail, ['']) test('T9774', normal, compile_fail, ['']) +test('T9318', normal, compile_fail, ['']) From git at git.haskell.org Tue Nov 18 20:21:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Nov 2014 20:21:55 +0000 (UTC) Subject: [commit: ghc] wip/rae: Release notes for #1476, #7484. (e4dc334) Message-ID: <20141118202155.6A0BA3A345@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/e4dc33477e7f523b3f25655068b468deabc2f9d2/ghc >--------------------------------------------------------------- commit e4dc33477e7f523b3f25655068b468deabc2f9d2 Author: Richard Eisenberg Date: Tue Nov 4 12:20:25 2014 -0500 Release notes for #1476, #7484. >--------------------------------------------------------------- e4dc33477e7f523b3f25655068b468deabc2f9d2 docs/users_guide/7.10.1-notes.xml | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 7c1e65a..4d25ee8 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -128,6 +128,10 @@ + Pattern splices now work. + + + reifyInstances now treats unbound type variables as univerally quantified, allowing lookup of, say, the instance for Eq [a]. @@ -146,6 +150,13 @@ Various features unsupported in quotations were previously silently ignored. These now cause errors. + + + Template Haskell is now more pedantic about splicing in + bogus variable names, like those containing whitespace. If you + use bogus names in your Template Haskell code, this may break + your program. + From git at git.haskell.org Wed Nov 19 02:18:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 02:18:19 +0000 (UTC) Subject: [commit: ghc] master: Support for "with" renaming syntax, and output a feature flag. (7c748d9) Message-ID: <20141119021819.C82123A393@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7c748d9fcf12bd16e0de56187fa6fcf3d6dbf39a/ghc >--------------------------------------------------------------- commit 7c748d9fcf12bd16e0de56187fa6fcf3d6dbf39a Author: Edward Z. Yang Date: Mon Aug 11 18:40:13 2014 +0100 Support for "with" renaming syntax, and output a feature flag. Summary: - Feature flag indicates to Cabal that we support thinning and renaming as it needs. - Support -package "base with (Foo as Bar)" which brings the ordinary modules into scope, as well as adding the renamings to scope. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D485 >--------------------------------------------------------------- 7c748d9fcf12bd16e0de56187fa6fcf3d6dbf39a compiler/main/DynFlags.hs | 24 ++++++++++++++---------- compiler/main/Packages.lhs | 18 ++++++------------ docs/users_guide/packages.xml | 15 ++++++++------- testsuite/tests/ghc-api/T9595.hs | 5 ++++- 4 files changed, 32 insertions(+), 30 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7c748d9fcf12bd16e0de56187fa6fcf3d6dbf39a From git at git.haskell.org Wed Nov 19 09:48:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 09:48:30 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Update baseline shift/reduce conflict number (8640fc5) Message-ID: <20141119094830.DB3C13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/8640fc54916d9c2b9381d8ab618af8ae37eb7693/ghc >--------------------------------------------------------------- commit 8640fc54916d9c2b9381d8ab618af8ae37eb7693 Author: Dr. ERDI Gergo Date: Wed Jul 2 19:18:43 2014 +0800 Update baseline shift/reduce conflict number >--------------------------------------------------------------- 8640fc54916d9c2b9381d8ab618af8ae37eb7693 compiler/parser/Parser.y | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 2e1b777..1123375 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -86,6 +86,12 @@ import TysWiredIn ( unitTyCon, unitDataCon, tupleTyCon, tupleCon, nilDataC {- ----------------------------------------------------------------------------- +25 June 2014 + +Conflicts: 47 shift/reduce + 1 reduce/reduce + +----------------------------------------------------------------------------- 12 October 2012 Conflicts: 43 shift/reduce From git at git.haskell.org Wed Nov 19 09:48:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 09:48:33 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add test cases (8ddac31) Message-ID: <20141119094833.CF7443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/8ddac3175d1aea97ec35ce1f32907c9827c97a51/ghc >--------------------------------------------------------------- commit 8ddac3175d1aea97ec35ce1f32907c9827c97a51 Author: Dr. ERDI Gergo Date: Fri Nov 14 16:21:45 2014 +0800 Add test cases >--------------------------------------------------------------- 8ddac3175d1aea97ec35ce1f32907c9827c97a51 testsuite/tests/patsyn/should_compile/T8584-1.hs | 8 ++++++++ testsuite/tests/patsyn/should_compile/T8968-1.hs | 8 ++++++++ testsuite/tests/patsyn/should_compile/all.T | 2 ++ 3 files changed, 18 insertions(+) diff --git a/testsuite/tests/patsyn/should_compile/T8584-1.hs b/testsuite/tests/patsyn/should_compile/T8584-1.hs new file mode 100644 index 0000000..00aeb70 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8584-1.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE PatternSynonyms #-} +module ShouldCompile where + +pattern Single :: () => (Show a) => a -> [a] +pattern Single x = [x] + +-- f :: (Show a) => [a] -> a +foobar (Single x) = x diff --git a/testsuite/tests/patsyn/should_compile/T8968-1.hs b/testsuite/tests/patsyn/should_compile/T8968-1.hs new file mode 100644 index 0000000..f41ed53 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8968-1.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE GADTs, KindSignatures, PatternSynonyms #-} +module ShouldCompile where + +data X :: (* -> *) -> * -> * where + Y :: f a -> X f (Maybe a) + +pattern C :: a -> X Maybe (Maybe a) +pattern C x = Y (Just x) diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index 55e3b83..ed8961d 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -12,3 +12,5 @@ test('T8966', normal, compile, ['']) test('T9023', normal, compile, ['']) test('unboxed-bind-bang', normal, compile, ['']) test('T9732', normal, compile, ['']) +test('T8968-1', normal, compile, ['']) +test('T8584-1', normal, compile, ['']) From git at git.haskell.org Wed Nov 19 09:48:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 09:48:36 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add support for pattern synonym type signatures. Syntax is of the form (17a5e28) Message-ID: <20141119094836.807E33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/17a5e28b2d64a06a7680a199878712dcf79a54eb/ghc >--------------------------------------------------------------- commit 17a5e28b2d64a06a7680a199878712dcf79a54eb Author: Dr. ERDI Gergo Date: Fri Nov 7 19:29:06 2014 +0800 Add support for pattern synonym type signatures. Syntax is of the form pattern P :: (Prov b) => (Req a) => a -> b -> Int -> T a which declares a pattern synonym called `P`, with argument types `a`, `b`, and `Int`, and result type `T a`, with provided context `(Prov b)` and required context `(Req a)`. >--------------------------------------------------------------- 17a5e28b2d64a06a7680a199878712dcf79a54eb compiler/hsSyn/HsBinds.lhs | 51 ++++----- compiler/hsSyn/HsTypes.lhs | 16 +-- compiler/iface/IfaceSyn.lhs | 25 ++--- compiler/iface/IfaceType.lhs | 15 ++- compiler/parser/Parser.y | 51 ++++++--- compiler/parser/RdrHsSyn.hs | 27 +---- compiler/rename/RnBinds.lhs | 42 ++++---- compiler/typecheck/TcBinds.lhs | 50 +++++++-- compiler/typecheck/TcClassDcl.lhs | 4 +- compiler/typecheck/TcPat.lhs | 23 ++++- compiler/typecheck/TcPatSyn.lhs | 195 ++++++++++++++++++++++++++--------- compiler/typecheck/TcPatSyn.lhs-boot | 9 +- 12 files changed, 332 insertions(+), 176 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 17a5e28b2d64a06a7680a199878712dcf79a54eb From git at git.haskell.org Wed Nov 19 10:03:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 10:03:00 +0000 (UTC) Subject: [commit: ghc] master: Reimplement im/export primitives for integer-gmp2 (4224466) Message-ID: <20141119100300.BB0883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/42244668af6d8c1dd6a2d64af90ed57d8ecd8d88/ghc >--------------------------------------------------------------- commit 42244668af6d8c1dd6a2d64af90ed57d8ecd8d88 Author: Herbert Valerio Riedel Date: Tue Nov 18 16:52:02 2014 +0100 Reimplement im/export primitives for integer-gmp2 The import/export operations were available in `integer-gmp-0.5.1` already, but need to be reimplemented from scratch for the `integer-gmp-1.0.0` rewrite. This also adds a few more operations than were previously available for use w/ the `BigNat` type (which will be useful for implementing serialisation for the upcoming `Natural` type) Specifically, the following operations are (re)added (albeit with slightly different type-signatures): - `sizeInBaseBigNat` - `sizeInBaseInteger` - `sizeInBaseWord#` - `exportBigNatToAddr` - `exportIntegerToAddr` - `exportWordToAddr` - `exportBigNatToMutableByteArray` - `exportIntegerToMutableByteArray` - `exportWordToMutableByteArray` - `importBigNatFromAddr` - `importIntegerFromAddr` - `importBigNatFromByteArray` - `importIntegerFromByteArray` NOTE: The `integerGmpInternals` test-case is updated but not yet re-enabled as it contains tests for other primitives which aren't yet reimplemented. This addresses #9281 Reviewed By: austin, duncan Differential Revision: https://phabricator.haskell.org/D480 >--------------------------------------------------------------- 42244668af6d8c1dd6a2d64af90ed57d8ecd8d88 libraries/integer-gmp2/cbits/wrappers.c | 161 +++++++++++++++++++++ .../integer-gmp2/src/GHC/Integer/GMP/Internals.hs | 154 ++++++++++++++++++++ libraries/integer-gmp2/src/GHC/Integer/Type.hs | 99 +++++++++++++ testsuite/tests/lib/integer/integerGmpInternals.hs | 36 +++-- 4 files changed, 431 insertions(+), 19 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 42244668af6d8c1dd6a2d64af90ed57d8ecd8d88 From git at git.haskell.org Wed Nov 19 11:13:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 11:13:49 +0000 (UTC) Subject: [commit: ghc] master: Restore exact old semantics of `decodeFloat` (e2af452) Message-ID: <20141119111349.5C2763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e2af452cd533778c5447719c59429d72bb1fe00d/ghc >--------------------------------------------------------------- commit e2af452cd533778c5447719c59429d72bb1fe00d Author: Herbert Valerio Riedel Date: Wed Nov 19 11:09:33 2014 +0100 Restore exact old semantics of `decodeFloat` `integer-gmp2` uses the new 64bit-based IEEE deconstructing primop introduced in b62bd5ecf3be421778e4835010b6b334e95c5a56. However, the returned values differ for exceptional IEEE values: Previous (expected) semantics: > decodeFloat (-1/0) (-4503599627370496,972) > decodeFloat (1/0) (4503599627370496,972) > decodeFloat (0/0) (-6755399441055744,972) Currently (broken) semantics: > decodeFloat (-1/0 :: Double) (-9223372036854775808,-53) > decodeFloat (1/0 :: Double) (-9223372036854775808,-53) > decodeFloat (0/0 :: Double) (-9223372036854775808,-53) This patch reverts to the old expected semantics. I plan to revisit the implementation during GHC 7.11 development. This should address #9810 Reviewed By: austin, ekmett, luite Differential Revision: https://phabricator.haskell.org/D486 >--------------------------------------------------------------- e2af452cd533778c5447719c59429d72bb1fe00d rts/StgPrimFloat.c | 13 +++++++++++++ testsuite/.gitignore | 1 + testsuite/tests/numeric/should_run/T9810.hs | 25 +++++++++++++++++++++++++ testsuite/tests/numeric/should_run/T9810.stdout | 14 ++++++++++++++ testsuite/tests/numeric/should_run/all.T | 1 + 5 files changed, 54 insertions(+) diff --git a/rts/StgPrimFloat.c b/rts/StgPrimFloat.c index 72a251b..e2eeee5 100644 --- a/rts/StgPrimFloat.c +++ b/rts/StgPrimFloat.c @@ -166,6 +166,8 @@ __decodeDouble_2Int (I_ *man_sign, W_ *man_high, W_ *man_low, I_ *exp, StgDouble StgInt __decodeDouble_Int64 (StgInt64 *const mantissa, const StgDouble dbl) { +#if 0 + // We can't use this yet as-is, see ticket #9810 if (dbl) { int exp = 0; *mantissa = (StgInt64)scalbn(frexp(dbl, &exp), DBL_MANT_DIG); @@ -174,6 +176,17 @@ __decodeDouble_Int64 (StgInt64 *const mantissa, const StgDouble dbl) *mantissa = 0; return 0; } +#else + I_ man_sign = 0; + W_ man_high = 0, man_low = 0; + I_ exp = 0; + + __decodeDouble_2Int (&man_sign, &man_high, &man_low, &exp, dbl); + + *mantissa = ((((StgInt64)man_high << 32) | (StgInt64)man_low) + * (StgInt64)man_sign); + return exp; +#endif } /* Convenient union types for checking the layout of IEEE 754 types - diff --git a/testsuite/.gitignore b/testsuite/.gitignore index a07a376..705306c 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -1035,6 +1035,7 @@ mk/ghcconfig*_inplace_bin_ghc-stage2.exe.mk /tests/numeric/should_run/T7233 /tests/numeric/should_run/T7689 /tests/numeric/should_run/T8726 +/tests/numeric/should_run/T9810 /tests/numeric/should_run/add2 /tests/numeric/should_run/arith001 /tests/numeric/should_run/arith002 diff --git a/testsuite/tests/numeric/should_run/T9810.hs b/testsuite/tests/numeric/should_run/T9810.hs new file mode 100644 index 0000000..b8ce1ba --- /dev/null +++ b/testsuite/tests/numeric/should_run/T9810.hs @@ -0,0 +1,25 @@ +main = do + -- NOTE: the `abs` is to compensate for WAY=optllvm + -- having a positive sign for 0/0 + + putStrLn "## Double ##" + print $ idRational ( 1/0 :: Double) + print $ idRational (-1/0 :: Double) + print $ abs $ idRational ( 0/0 :: Double) + print $ idReencode ( 1/0 :: Double) + print $ idReencode (-1/0 :: Double) + print $ abs $ idReencode ( 0/0 :: Double) + + putStrLn "## Float ##" + print $ idRational ( 1/0 :: Float) + print $ idRational (-1/0 :: Float) + print $ abs $ idRational ( 0/0 :: Float) + print $ idReencode ( 1/0 :: Float) + print $ idReencode (-1/0 :: Float) + print $ abs $ idReencode ( 0/0 :: Float) + where + idRational :: (Real a, Fractional a) => a -> a + idRational = fromRational . toRational + + idReencode :: (RealFloat a) => a -> a + idReencode = uncurry encodeFloat . decodeFloat diff --git a/testsuite/tests/numeric/should_run/T9810.stdout b/testsuite/tests/numeric/should_run/T9810.stdout new file mode 100644 index 0000000..52a7e8f --- /dev/null +++ b/testsuite/tests/numeric/should_run/T9810.stdout @@ -0,0 +1,14 @@ +## Double ## +Infinity +-Infinity +Infinity +Infinity +-Infinity +Infinity +## Float ## +Infinity +-Infinity +Infinity +Infinity +-Infinity +Infinity diff --git a/testsuite/tests/numeric/should_run/all.T b/testsuite/tests/numeric/should_run/all.T index 76181a2..6262279 100644 --- a/testsuite/tests/numeric/should_run/all.T +++ b/testsuite/tests/numeric/should_run/all.T @@ -63,3 +63,4 @@ test('T7233', normal, compile_and_run, ['']) test('NumDecimals', normal, compile_and_run, ['']) test('T8726', normal, compile_and_run, ['']) test('CarryOverflow', omit_ways(['ghci']), compile_and_run, ['']) +test('T9810', normal, compile_and_run, ['']) From git at git.haskell.org Wed Nov 19 11:17:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 11:17:12 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add support for pattern synonym type signatures. Syntax is of the form (34acc90) Message-ID: <20141119111712.B97003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/34acc90ccef765ca6a55b69437a721828a7fba6c/ghc >--------------------------------------------------------------- commit 34acc90ccef765ca6a55b69437a721828a7fba6c Author: Dr. ERDI Gergo Date: Fri Nov 7 19:29:06 2014 +0800 Add support for pattern synonym type signatures. Syntax is of the form pattern P :: (Prov b) => (Req a) => a -> b -> Int -> T a which declares a pattern synonym called `P`, with argument types `a`, `b`, and `Int`, and result type `T a`, with provided context `(Prov b)` and required context `(Req a)`. >--------------------------------------------------------------- 34acc90ccef765ca6a55b69437a721828a7fba6c compiler/hsSyn/HsBinds.lhs | 51 +++--- compiler/hsSyn/HsTypes.lhs | 16 +- compiler/iface/IfaceSyn.lhs | 25 ++- compiler/iface/IfaceType.lhs | 15 +- compiler/parser/Parser.y | 51 ++++-- compiler/parser/RdrHsSyn.hs | 27 +--- compiler/rename/RnBinds.lhs | 42 ++--- compiler/typecheck/TcBinds.lhs | 50 +++++- compiler/typecheck/TcClassDcl.lhs | 4 +- compiler/typecheck/TcPat.lhs | 23 ++- compiler/typecheck/TcPatSyn.lhs | 195 +++++++++++++++++------ compiler/typecheck/TcPatSyn.lhs-boot | 9 +- testsuite/tests/ghci/scripts/T8776.stdout | 2 +- testsuite/tests/patsyn/should_compile/T8584-1.hs | 8 + testsuite/tests/patsyn/should_compile/T8968-1.hs | 8 + testsuite/tests/patsyn/should_compile/all.T | 2 + 16 files changed, 351 insertions(+), 177 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 34acc90ccef765ca6a55b69437a721828a7fba6c From git at git.haskell.org Wed Nov 19 11:17:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 11:17:15 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Update Haddock to new pattern synonym type signature syntax (a265878) Message-ID: <20141119111715.5C3E63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/a2658786cc5bc9f53f93b95c6a9076a13510a883/ghc >--------------------------------------------------------------- commit a2658786cc5bc9f53f93b95c6a9076a13510a883 Author: Dr. ERDI Gergo Date: Wed Nov 19 18:57:33 2014 +0800 Update Haddock to new pattern synonym type signature syntax >--------------------------------------------------------------- a2658786cc5bc9f53f93b95c6a9076a13510a883 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 199936a..3e4e82e 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 199936af5bb902c81f822b2dc57308dc25e18cfc +Subproject commit 3e4e82e6cb82c2836e514284cfb43f8b8be794ab From git at git.haskell.org Wed Nov 19 12:09:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 12:09:01 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add support for pattern synonym type signatures. Syntax is of the form (10bd68e) Message-ID: <20141119120901.448A73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/10bd68e4a63fcee7556064175bf5de7d3bebaa6b/ghc >--------------------------------------------------------------- commit 10bd68e4a63fcee7556064175bf5de7d3bebaa6b Author: Dr. ERDI Gergo Date: Fri Nov 7 19:29:06 2014 +0800 Add support for pattern synonym type signatures. Syntax is of the form pattern P :: (Prov b) => (Req a) => a -> b -> Int -> T a which declares a pattern synonym called `P`, with argument types `a`, `b`, and `Int`, and result type `T a`, with provided context `(Prov b)` and required context `(Req a)`. >--------------------------------------------------------------- 10bd68e4a63fcee7556064175bf5de7d3bebaa6b compiler/hsSyn/HsBinds.lhs | 51 +++--- compiler/hsSyn/HsTypes.lhs | 16 +- compiler/iface/IfaceSyn.lhs | 25 ++- compiler/iface/IfaceType.lhs | 15 +- compiler/parser/Parser.y | 51 ++++-- compiler/parser/RdrHsSyn.hs | 27 +--- compiler/rename/RnBinds.lhs | 42 ++--- compiler/typecheck/TcBinds.lhs | 50 +++++- compiler/typecheck/TcClassDcl.lhs | 4 +- compiler/typecheck/TcPat.lhs | 23 ++- compiler/typecheck/TcPatSyn.lhs | 195 +++++++++++++++++------ compiler/typecheck/TcPatSyn.lhs-boot | 9 +- testsuite/tests/ghci/scripts/T8776.stdout | 2 +- testsuite/tests/patsyn/should_compile/T8584-1.hs | 8 + testsuite/tests/patsyn/should_compile/T8968-1.hs | 8 + testsuite/tests/patsyn/should_compile/all.T | 2 + 16 files changed, 351 insertions(+), 177 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 10bd68e4a63fcee7556064175bf5de7d3bebaa6b From git at git.haskell.org Wed Nov 19 12:09:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 12:09:03 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Update baseline shift/reduce conflict number (e762b6e) Message-ID: <20141119120903.C9C6F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/e762b6e83f4c5f35d218dbb445e85289ef1b4682/ghc >--------------------------------------------------------------- commit e762b6e83f4c5f35d218dbb445e85289ef1b4682 Author: Dr. ERDI Gergo Date: Wed Jul 2 19:18:43 2014 +0800 Update baseline shift/reduce conflict number >--------------------------------------------------------------- e762b6e83f4c5f35d218dbb445e85289ef1b4682 compiler/parser/Parser.y | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 2e1b777..1123375 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -86,6 +86,12 @@ import TysWiredIn ( unitTyCon, unitDataCon, tupleTyCon, tupleCon, nilDataC {- ----------------------------------------------------------------------------- +25 June 2014 + +Conflicts: 47 shift/reduce + 1 reduce/reduce + +----------------------------------------------------------------------------- 12 October 2012 Conflicts: 43 shift/reduce From git at git.haskell.org Wed Nov 19 12:09:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 12:09:06 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Update Haddock to new pattern synonym type signature syntax (e199b05) Message-ID: <20141119120906.5CCD23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/e199b0505173a23cb7d44627dbaaae590ff5d2f2/ghc >--------------------------------------------------------------- commit e199b0505173a23cb7d44627dbaaae590ff5d2f2 Author: Dr. ERDI Gergo Date: Wed Nov 19 19:54:17 2014 +0800 Update Haddock to new pattern synonym type signature syntax >--------------------------------------------------------------- e199b0505173a23cb7d44627dbaaae590ff5d2f2 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 9cdf19b..edd2a3b 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 9cdf19bad54a6cc4b322396fdd06f4c1ee045b22 +Subproject commit edd2a3be44656e763419679bb426a384d9e1a74d From git at git.haskell.org Wed Nov 19 12:09:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 12:09:08 +0000 (UTC) Subject: [commit: ghc] wip/T8584's head updated: Update Haddock to new pattern synonym type signature syntax (e199b05) Message-ID: <20141119120908.AC0343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T8584' now includes: fa75309 Update .mailmap 452d6aa Partially revert 475dd93efa e14a973 Generalize exposed-modules field in installed package database 1854825 Workaround 452d6aa95b7 breaking TrustworthySafe03 609cd28 Update to (unreleased) `deepseq-1.4.0.0` c45e2e2 Fix compilation of `integer-gmp2` with `-O0` a2c0a8d Update validate settings now that containers and process have been updated to handle `-fwarn-trustworthy-safe`. 2a6f193 Fix a bug introduced with allocation counters 0515055 document addDependentFile uses contents, not mtime d997ca8 Don't use absolute paths for perl in validate a520761 Remove outdated TODO in TimeManager bc68ed0 Make listArray fuse df22507 Docs only ce2cc64 Adding dedicated Show instances for SrcSpan/SrcLoc 74a6a8a Change a comment referring falsely to seq 44f1582 Remove optimized package lookup, simplifying code. b9096df Add a note why tcGetInstEnvs is duplicated. aa1c1b2 Build xhtml and haddock only when `HADDOCK_DOCS=YES` 9a20379 Fix ffi023 20226c2 Whitespace only ac1281f Outputable instance for IfaceVectInfo 535644f Add missing semicolon in Schedule.c 1f6b1ab base: Fix (**) instance for Data.Complex (#8539) ddb484c Update comment about C helper for foreign exports (#9713) 87cd37b Fix usage of `find -perm` in aclocal.m4 (#9697) 21f9bc4 mapMaybe: Typo in the comment (#9644) c557f99 Disable AVX for LLVM 3.2 by default (#9391) e7b414a Fix detection of GNU gold linker if invoked via gcc with parameters a736b51 Revert "base: Fix (**) instance for Data.Complex (#8539)" 483eeba Comments only 1019e3c When outputting list of available instances, sort it. 7c748d9 Support for "with" renaming syntax, and output a feature flag. 4224466 Reimplement im/export primitives for integer-gmp2 e2af452 Restore exact old semantics of `decodeFloat` e762b6e Update baseline shift/reduce conflict number 10bd68e Add support for pattern synonym type signatures. Syntax is of the form e199b05 Update Haddock to new pattern synonym type signature syntax From git at git.haskell.org Wed Nov 19 14:47:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 14:47:16 +0000 (UTC) Subject: [commit: ghc] master: Optimise `Identity` instances with `coerce` (4ba884b) Message-ID: <20141119144716.30A3E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4ba884bdd3a9521ea92fcda8f601a7d0f3537bc1/ghc >--------------------------------------------------------------- commit 4ba884bdd3a9521ea92fcda8f601a7d0f3537bc1 Author: Herbert Valerio Riedel Date: Wed Nov 19 11:44:37 2014 +0100 Optimise `Identity` instances with `coerce` This also overrides all optional `Foldable` methods (which would otherwise be default-implemented in terms of `foldMap`) with supposedly optimally minimal implementations. While at it, this also removes the redundant `{-# LANGUAGE CPP #-}`. Reviewed By: austin, dfeuer Differential Revision: https://phabricator.haskell.org/D467 >--------------------------------------------------------------- 4ba884bdd3a9521ea92fcda8f601a7d0f3537bc1 libraries/base/Data/Functor/Identity.hs | 47 ++++++++++++++++++++++++--------- 1 file changed, 34 insertions(+), 13 deletions(-) diff --git a/libraries/base/Data/Functor/Identity.hs b/libraries/base/Data/Functor/Identity.hs index 4058df8..de7f19a 100644 --- a/libraries/base/Data/Functor/Identity.hs +++ b/libraries/base/Data/Functor/Identity.hs @@ -1,5 +1,6 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE AutoDeriveTypeable #-} +{-# LANGUAGE DeriveTraversable #-} + ----------------------------------------------------------------------------- -- | -- Module : Data.Functor.Identity @@ -31,13 +32,14 @@ module Data.Functor.Identity ( ) where import Control.Monad.Fix -import Data.Functor +import Data.Coerce +import Data.Foldable -- | Identity functor and monad. (a non-strict monad) -- -- /Since: 4.8.0.0/ newtype Identity a = Identity { runIdentity :: a } - deriving (Eq, Ord) + deriving (Eq, Ord, Traversable) -- | This instance would be equivalent to the derived instances of the -- 'Identity' newtype if the 'runIdentity' field were removed @@ -54,22 +56,41 @@ instance (Show a) => Show (Identity a) where -- --------------------------------------------------------------------------- -- Identity instances for Functor and Monad -instance Functor Identity where - fmap f m = Identity (f (runIdentity m)) - instance Foldable Identity where - foldMap f (Identity x) = f x + foldMap = coerce + + elem = (. runIdentity) #. (==) + foldl = coerce + foldl' = coerce + foldl1 _ = runIdentity + foldr f z (Identity x) = f x z + foldr' = foldr + foldr1 _ = runIdentity + length _ = 1 + maximum = runIdentity + minimum = runIdentity + null _ = False + product = runIdentity + sum = runIdentity + toList (Identity x) = [x] -instance Traversable Identity where - traverse f (Identity x) = Identity <$> f x +instance Functor Identity where + fmap = coerce instance Applicative Identity where - pure a = Identity a - Identity f <*> Identity x = Identity (f x) + pure = Identity + (<*>) = coerce instance Monad Identity where - return a = Identity a + return = Identity m >>= k = k (runIdentity m) instance MonadFix Identity where - mfix f = Identity (fix (runIdentity . f)) + mfix f = Identity (fix (runIdentity . f)) + + +-- | Internal (non-exported) 'Coercible' helper for 'elem' +-- +-- See Note [Function coercion] in "Data.Foldable" for more details. +(#.) :: Coercible b c => (b -> c) -> (a -> b) -> a -> c +(#.) _f = coerce From git at git.haskell.org Wed Nov 19 19:48:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 19:48:43 +0000 (UTC) Subject: [commit: ghc] wip/merge: template-haskell: Missing instances for Rational and (). (10f9097) Message-ID: <20141119194843.07C003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/10f90970375a53971593fb4dcf52b0242a78eaf8/ghc >--------------------------------------------------------------- commit 10f90970375a53971593fb4dcf52b0242a78eaf8 Author: Mathieu Boespflug Date: Tue Nov 18 22:21:15 2014 -0600 template-haskell: Missing instances for Rational and (). Test Plan: ./validate Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D492 >--------------------------------------------------------------- 10f90970375a53971593fb4dcf52b0242a78eaf8 docs/users_guide/7.10.1-notes.xml | 5 +++++ libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 11 +++++++++-- 2 files changed, 14 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 2e509e1..0cf3f61 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -176,6 +176,11 @@ Various features unsupported in quotations were previously silently ignored. These now cause errors. + + + Lift instances were added for + () and Ratio. + diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 48199a4..9813095 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -1,5 +1,6 @@ {-# LANGUAGE CPP, DeriveDataTypeable, PolymorphicComponents, - RoleAnnotations, DeriveGeneric #-} + RoleAnnotations, DeriveGeneric, TypeSynonymInstances, + FlexibleInstances #-} ----------------------------------------------------------------------------- -- | @@ -454,7 +455,10 @@ instance Lift Integer where lift x = return (LitE (IntegerL x)) instance Lift Int where - lift x= return (LitE (IntegerL (fromIntegral x))) + lift x = return (LitE (IntegerL (fromIntegral x))) + +instance Lift Rational where + lift x = return (LitE (RationalL x)) instance Lift Char where lift x = return (LitE (CharL x)) @@ -478,6 +482,9 @@ liftString :: String -> Q Exp -- Used in TcExpr to short-circuit the lifting for strings liftString s = return (LitE (StringL s)) +instance Lift () where + lift () = return (ConE (tupleDataName 0)) + instance (Lift a, Lift b) => Lift (a, b) where lift (a, b) = liftM TupE $ sequence [lift a, lift b] From git at git.haskell.org Wed Nov 19 19:48:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 19:48:45 +0000 (UTC) Subject: [commit: ghc] wip/merge: Only test for bug #9439 when llvm is installed (de086f5) Message-ID: <20141119194845.8FAD83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/de086f5eac30e81672e5b624c33ae78036cdb6a1/ghc >--------------------------------------------------------------- commit de086f5eac30e81672e5b624c33ae78036cdb6a1 Author: Thomas Miedema Date: Tue Nov 18 22:23:27 2014 -0600 Only test for bug #9439 when llvm is installed Reviewers: bgamari, austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D500 GHC Trac Issues: #9807 >--------------------------------------------------------------- de086f5eac30e81672e5b624c33ae78036cdb6a1 configure.ac | 103 ++++++++++++++++++++++++++++++----------------------------- 1 file changed, 53 insertions(+), 50 deletions(-) diff --git a/configure.ac b/configure.ac index 7bd599f..5dd3aaa 100644 --- a/configure.ac +++ b/configure.ac @@ -187,56 +187,6 @@ AC_SUBST([WithGhc]) dnl ** Without optimization some INLINE trickery fails for GHCi SRC_CC_OPTS="-O" -dnl ** Bug 9439: Some GHC 7.8 releases had broken LLVM code generator. -dnl Unfortunately we don't know whether the user is going to request a -dnl build with the LLVM backend as this is only given in build.mk. -dnl -dnl Instead, we try to do as much work as possible here, checking -dnl whether -fllvm is the stage 0 compiler's default. If so we -dnl fail. If not, we check whether -fllvm is affected explicitly and -dnl if so set a flag. The build system will later check this flag -dnl after the desired build flags are known. -AC_MSG_CHECKING(whether bootstrap compiler is affected by bug 9439) -echo "main = putStrLn \"%function\"" > conftestghc.hs - -# Check whether LLVM backend is default for this platform -"${WithGhc}" conftestghc.hs 2>&1 >/dev/null -res=`./conftestghc` -if test "x$res" == "x%object" -then - AC_MSG_RESULT(yes) - echo "Buggy bootstrap compiler" - echo "" - echo "The stage 0 compiler $WithGhc is affected by GHC Bug \#9439" - echo "and therefore will miscompile the LLVM backend if -fllvm is" - echo "used." - echo - echo "Please use another bootstrap compiler" - exit 1 -fi - -# -fllvm is not the default, but set a flag so the Makefile can check -# -for it in the build flags later on -"${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null -if test $? == 0 -then - res=`./conftestghc` - if test "x$res" == "x%object" - then - AC_MSG_RESULT(yes) - GHC_LLVM_AFFECTED_BY_9439=1 - elif test "x$res" == "x%function" - then - AC_MSG_RESULT(no) - GHC_LLVM_AFFECTED_BY_9439=0 - else - AC_MSG_WARN(unexpected output $res) - fi -else - AC_MSG_RESULT(failed to compile, assuming no) -fi -AC_SUBST([GHC_LLVM_AFFECTED_BY_9439]) - dnl-------------------------------------------------------------------- dnl * Choose host(/target/build) platform dnl-------------------------------------------------------------------- @@ -593,6 +543,59 @@ dnl -------------------------------------------------------------- dnl * General configuration checks dnl -------------------------------------------------------------- +dnl ** Bug 9439: Some GHC 7.8 releases had broken LLVM code generator. +dnl Unfortunately we don't know whether the user is going to request a +dnl build with the LLVM backend as this is only given in build.mk. +dnl +dnl Instead, we try to do as much work as possible here, checking +dnl whether -fllvm is the stage 0 compiler's default. If so we +dnl fail. If not, we check whether -fllvm is affected explicitly and +dnl if so set a flag. The build system will later check this flag +dnl after the desired build flags are known. +if test -n "$LlcCmd" && test -n "$OptCmd" +then + AC_MSG_CHECKING(whether bootstrap compiler is affected by bug 9439) + echo "main = putStrLn \"%function\"" > conftestghc.hs + + # Check whether LLVM backend is default for this platform + "${WithGhc}" conftestghc.hs 2>&1 >/dev/null + res=`./conftestghc` + if test "x$res" == "x%object" + then + AC_MSG_RESULT(yes) + echo "Buggy bootstrap compiler" + echo "" + echo "The stage 0 compiler $WithGhc is affected by GHC Bug \#9439" + echo "and therefore will miscompile the LLVM backend if -fllvm is" + echo "used." + echo + echo "Please use another bootstrap compiler" + exit 1 + fi + + # -fllvm is not the default, but set a flag so the Makefile can check + # -for it in the build flags later on + "${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null + if test $? == 0 + then + res=`./conftestghc` + if test "x$res" == "x%object" + then + AC_MSG_RESULT(yes) + GHC_LLVM_AFFECTED_BY_9439=1 + elif test "x$res" == "x%function" + then + AC_MSG_RESULT(no) + GHC_LLVM_AFFECTED_BY_9439=0 + else + AC_MSG_WARN(unexpected output $res) + fi + else + AC_MSG_RESULT(failed to compile, assuming no) + fi +fi +AC_SUBST([GHC_LLVM_AFFECTED_BY_9439]) + dnl ** Can the unix package be built? dnl -------------------------------------------------------------- From git at git.haskell.org Wed Nov 19 19:48:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 19:48:48 +0000 (UTC) Subject: [commit: ghc] wip/merge: add missing instances for Loc and a few missing Eq instances (8529284) Message-ID: <20141119194848.2601C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/852928451f235f79b7185dd12902425c33f40ba4/ghc >--------------------------------------------------------------- commit 852928451f235f79b7185dd12902425c33f40ba4 Author: Luite Stegeman Date: Tue Nov 18 22:21:44 2014 -0600 add missing instances for Loc and a few missing Eq instances Summary: This adds a few missing instances that can be automatically derived Reviewers: hvr, goldfire, austin Reviewed By: goldfire, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D495 >--------------------------------------------------------------- 852928451f235f79b7185dd12902425c33f40ba4 libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 9813095..8c95045 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -878,6 +878,7 @@ data Loc , loc_module :: String , loc_start :: CharPos , loc_end :: CharPos } + deriving( Show, Eq, Data, Typeable, Generic ) type CharPos = (Int, Int) -- ^ Line and character position @@ -952,13 +953,13 @@ data Info | TyVarI -- Scoped type variable Name Type -- What it is bound to - deriving( Show, Data, Typeable, Generic ) + deriving( Show, Eq, Data, Typeable, Generic ) -- | Obtained from 'reifyModule' in the 'Q' Monad. data ModuleInfo = -- | Contains the import list of the module. ModuleInfo [Module] - deriving( Show, Data, Typeable, Generic ) + deriving( Show, Eq, Data, Typeable, Generic ) {- | In 'ClassOpI' and 'DataConI', name of the parent class or type From git at git.haskell.org Wed Nov 19 22:22:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 22:22:19 +0000 (UTC) Subject: [commit: ghc] wip/merge: configure on Windows now downloads a mingw distribution on the fly if needed. (5338dc5) Message-ID: <20141119222219.4A5783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/5338dc5bbddcb48c6bb1df9bb36b497adaa50d78/ghc >--------------------------------------------------------------- commit 5338dc5bbddcb48c6bb1df9bb36b497adaa50d78 Author: Gintautas Miliauskas Date: Wed Nov 19 16:20:14 2014 -0600 configure on Windows now downloads a mingw distribution on the fly if needed. Summary: Also, migrated away from the rubenvb mingw distribution to a more up-to-date and semi-official mingw-builds. Updated the version of gcc to 4.8.3. This change obviates the need for a ghc-tarballs repository. Also removed use of an embedded perl (also from ghc-tarballs) since it is provided by msys2. Reviewers: austin Reviewed By: austin Subscribers: awson, hvr, thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D339 GHC Trac Issues: #9218 >--------------------------------------------------------------- 5338dc5bbddcb48c6bb1df9bb36b497adaa50d78 .arclint | 2 +- .gitignore | 4 +- configure.ac | 167 +++---- driver/gcc/gcc.c | 4 +- ghc.mk | 5 - mk/config.mk.in | 4 + mk/tree.mk | 1 - packages | 2 - rts/Linker.c | 524 +++++++++++---------- rts/win32/seh_excn.h | 4 + sync-all | 6 - testsuite/tests/driver/shared001.stderr | 1 - .../tests/ghci/linking/ghcilink002.stderr-mingw32 | 1 - .../tests/ghci/linking/ghcilink005.stderr-mingw32 | 1 - testsuite/tests/rts/T5435_dyn_asm.stderr-mingw32 | 1 - testsuite/tests/rts/T5435_dyn_gcc.stderr-mingw32 | 1 - 16 files changed, 364 insertions(+), 364 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5338dc5bbddcb48c6bb1df9bb36b497adaa50d78 From git at git.haskell.org Wed Nov 19 22:44:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 22:44:47 +0000 (UTC) Subject: [commit: ghc] wip/merge: rts: remove old-style field designator extension (#9396) (da4a2ce) Message-ID: <20141119224447.122903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/da4a2ce530213d284ecb39c2d7f592e7ba10a245/ghc >--------------------------------------------------------------- commit da4a2ce530213d284ecb39c2d7f592e7ba10a245 Author: Austin Seipp Date: Tue Nov 18 21:21:47 2014 -0600 rts: remove old-style field designator extension (#9396) Authored-by: jrp Signed-off-by: Austin Seipp >--------------------------------------------------------------- da4a2ce530213d284ecb39c2d7f592e7ba10a245 includes/rts/prof/CCS.h | 48 ++++++++++++++++++++++++------------------------ rts/RetainerSet.c | 10 +++++----- 2 files changed, 29 insertions(+), 29 deletions(-) diff --git a/includes/rts/prof/CCS.h b/includes/rts/prof/CCS.h index 85b03f3..74f18b8 100644 --- a/includes/rts/prof/CCS.h +++ b/includes/rts/prof/CCS.h @@ -210,32 +210,32 @@ extern CostCentreStack * RTS_VAR(CCS_LIST); // registered CCS list * Declaring Cost Centres & Cost Centre Stacks. * -------------------------------------------------------------------------- */ -# define CC_DECLARE(cc_ident,name,mod,loc,caf,is_local) \ - is_local CostCentre cc_ident[1] \ - = {{ ccID : 0, \ - label : name, \ - module : mod, \ - srcloc : loc, \ - time_ticks : 0, \ - mem_alloc : 0, \ - link : 0, \ - is_caf : caf \ +# define CC_DECLARE(cc_ident,name,mod,loc,caf,is_local) \ + is_local CostCentre cc_ident[1] \ + = {{ .ccID = 0, \ + .label = name, \ + .module = mod, \ + .srcloc = loc, \ + .time_ticks = 0, \ + .mem_alloc = 0, \ + .link = 0, \ + .is_caf = caf \ }}; -# define CCS_DECLARE(ccs_ident,cc_ident,is_local) \ - is_local CostCentreStack ccs_ident[1] \ - = {{ ccsID : 0, \ - cc : cc_ident, \ - prevStack : NULL, \ - indexTable : NULL, \ - root : NULL, \ - depth : 0, \ - selected : 0, \ - scc_count : 0, \ - time_ticks : 0, \ - mem_alloc : 0, \ - inherited_ticks : 0, \ - inherited_alloc : 0 \ +# define CCS_DECLARE(ccs_ident,cc_ident,is_local) \ + is_local CostCentreStack ccs_ident[1] \ + = {{ .ccsID = 0, \ + .cc = cc_ident, \ + .prevStack = NULL, \ + .indexTable = NULL, \ + .root = NULL, \ + .depth = 0, \ + .selected = 0, \ + .scc_count = 0, \ + .time_ticks = 0, \ + .mem_alloc = 0, \ + .inherited_ticks = 0, \ + .inherited_alloc = 0 \ }}; /* ----------------------------------------------------------------------------- diff --git a/rts/RetainerSet.c b/rts/RetainerSet.c index 1905866..234532a 100644 --- a/rts/RetainerSet.c +++ b/rts/RetainerSet.c @@ -40,11 +40,11 @@ static int nextId; // id of next retainer set * from growing too large. * -------------------------------------------------------------------------- */ RetainerSet rs_MANY = { - num : 0, - hashKey : 0, - link : NULL, - id : 1, - element : {} + .num = 0, + .hashKey = 0, + .link = NULL, + .id = 1, + .element = {} }; /* ----------------------------------------------------------------------------- From git at git.haskell.org Wed Nov 19 22:44:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 22:44:49 +0000 (UTC) Subject: [commit: ghc] wip/merge: Update documentation for "Batch compiler mode" (3d5f67e) Message-ID: <20141119224449.A506F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/3d5f67e483d340abadbd55cf2c7186cc74cb9ece/ghc >--------------------------------------------------------------- commit 3d5f67e483d340abadbd55cf2c7186cc74cb9ece Author: Thomas Miedema Date: Tue Nov 18 22:18:43 2014 -0600 Update documentation for "Batch compiler mode" Summary: Since commit 7828bf3ea2ea34e7a3a8662f5f621ef706ffee5c * --make is the default * -c is a mode flag, except when used in combination with --make Also: * -C (generate C code) is only available in unregisterised mode. Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D427 >--------------------------------------------------------------- 3d5f67e483d340abadbd55cf2c7186cc74cb9ece docs/users_guide/flags.xml | 4 ++-- docs/users_guide/using.xml | 23 ++++++++++++++++++----- 2 files changed, 20 insertions(+), 7 deletions(-) diff --git a/docs/users_guide/flags.xml b/docs/users_guide/flags.xml index 33af295..e8218f7 100644 --- a/docs/users_guide/flags.xml +++ b/docs/users_guide/flags.xml @@ -209,8 +209,8 @@ - Do not link - dynamic + Stop after generating object (.o) file + mode - diff --git a/docs/users_guide/using.xml b/docs/users_guide/using.xml index 07d487e..bf4f1c5 100644 --- a/docs/users_guide/using.xml +++ b/docs/users_guide/using.xml @@ -246,6 +246,13 @@ module X where + .hspp + + A file created by the preprocessor. + + + + .hi A Haskell interface file, probably @@ -383,7 +390,7 @@ module X where ghc -E - ghc -c + ghc -C ghc -S ghc -c @@ -395,10 +402,7 @@ module X where This is the traditional batch-compiler mode, in which GHC can compile source files one at a time, or link objects - together into an executable. This mode also applies if - there is no other mode flag specified on the command line, - in which case it means that the specified files should be - compiled and then linked to form a program. See . @@ -617,6 +621,11 @@ ghc Main.hs given on the command line and GHC will include them when linking the executable. + For backward compatibility with existing make scripts, when + used in combination with , the linking phase + is omitted (same as + ). + Note that GHC can only follow dependencies if it has the source file available, so if your program includes a module for which there is no source file, even if you have an object and an @@ -765,6 +774,10 @@ ghc -c Foo.hs option runs just the pre-processing passes of the compiler, dumping the result in a file. + Note: The option is only available when + GHC is built in unregisterised mode. See + for more details. + Overriding the default behaviour for a file From git at git.haskell.org Wed Nov 19 22:44:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 22:44:52 +0000 (UTC) Subject: [commit: ghc] wip/merge: The test runner now also works under the msys-native Python. (d8b4e53) Message-ID: <20141119224452.3F8DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/d8b4e531d1290ddfa5926ecf0eff16f7b21b88de/ghc >--------------------------------------------------------------- commit d8b4e531d1290ddfa5926ecf0eff16f7b21b88de Author: Gintautas Miliauskas Date: Mon Sep 22 23:10:56 2014 +0200 The test runner now also works under the msys-native Python. Msys binaries apply heuristics to escape paths in arguments intended for non-msys binaries, which breaks timeout invocations, see #9626. Signed-off-by: Austin Seipp >--------------------------------------------------------------- d8b4e531d1290ddfa5926ecf0eff16f7b21b88de testsuite/driver/testlib.py | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 1549381..6fc86e4 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1780,9 +1780,25 @@ def rawSystem(cmd_and_args): else: return os.spawnv(os.P_WAIT, cmd_and_args[0], cmd_and_args) +# When running under native msys Python, any invocations of non-msys binaries, +# including timeout.exe, will have their arguments munged according to some +# heuristics, which leads to malformed command lines (#9626). The easiest way +# to avoid problems is to invoke through /usr/bin/cmd which sidesteps argument +# munging because it is a native msys application. +def passThroughCmd(cmd_and_args): + args = [] + # cmd needs a Windows-style path for its first argument. + args.append(cmd_and_args[0].replace('/', '\\')) + # Other arguments need to be quoted to deal with spaces. + args.extend(['"%s"' % arg for arg in cmd_and_args[1:]]) + return ["cmd", "/c", " ".join(args)] + # Note that this doesn't handle the timeout itself; it is just used for # commands that have timeout handling built-in. def rawSystemWithTimeout(cmd_and_args): + if config.os == 'mingw32' and sys.executable.startswith('/usr'): + # This is only needed when running under msys python. + cmd_and_args = passThroughCmd(cmd_and_args) r = rawSystem(cmd_and_args) if r == 98: # The python timeout program uses 98 to signal that ^C was pressed From git at git.haskell.org Wed Nov 19 22:44:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 22:44:54 +0000 (UTC) Subject: [commit: ghc] wip/merge: Refactor: use System.FilePath.splitSearchPath (771b043) Message-ID: <20141119224454.E443F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/771b04337345ab98d443a1fac53a3f206da96a12/ghc >--------------------------------------------------------------- commit 771b04337345ab98d443a1fac53a3f206da96a12 Author: Thomas Miedema Date: Tue Nov 18 22:17:47 2014 -0600 Refactor: use System.FilePath.splitSearchPath Summary: To address #2521 ("Trailing colon on GHC_PACKAGE_PATH doesn't work with ghc-pkg"), we were using a custom version of splitSearchPath (e4f46f5de). This solution however caused issue #9698 ("GHC_PACKAGE_PATH should be more lenient for empty paths"). This patch reverts back to System.FilePath.splitSearchPath (fixes #9698) and adresses (#2521) by testing for a trailing search path separators explicitly (instead of implicitly using empty search path elements). Empty paths are now allowed (ignored on Windows, interpreted as current directory on Posix systems), and trailing path separator still tack on the user and system package databases. Also update submodule filepath, which has a version of splitSearchPath which handles quotes in the same way as our custom version did. Test Plan: $ GHC_PACKAGE_PATH=/::/home: ./ghc-pkg list ... db stack: ["/",".","/home","",""] ... Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D414 GHC Trac Issues: #2521, #9698 >--------------------------------------------------------------- 771b04337345ab98d443a1fac53a3f206da96a12 compiler/main/Packages.lhs | 9 +++------ compiler/utils/Util.lhs | 21 --------------------- libraries/filepath | 2 +- utils/ghc-pkg/Main.hs | 27 ++++----------------------- 4 files changed, 8 insertions(+), 51 deletions(-) diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs index 2f4a4d7..40b5e24 100644 --- a/compiler/main/Packages.lhs +++ b/compiler/main/Packages.lhs @@ -334,13 +334,10 @@ readPackageConfigs dflags = do let base_conf_refs = case e_pkg_path of Left _ -> system_conf_refs Right path - | null (last cs) - -> map PkgConfFile (init cs) ++ system_conf_refs + | not (null path) && isSearchPathSeparator (last path) + -> map PkgConfFile (splitSearchPath (init path)) ++ system_conf_refs | otherwise - -> map PkgConfFile cs - where cs = parseSearchPath path - -- if the path ends in a separator (eg. "/foo/bar:") - -- then we tack on the system paths. + -> map PkgConfFile (splitSearchPath path) let conf_refs = reverse (extraPkgConfs dflags base_conf_refs) -- later packages shadow earlier ones. extraPkgConfs diff --git a/compiler/utils/Util.lhs b/compiler/utils/Util.lhs index aa5f6f9..df293f0 100644 --- a/compiler/utils/Util.lhs +++ b/compiler/utils/Util.lhs @@ -89,7 +89,6 @@ module Util ( Suffix, splitLongestPrefix, escapeSpaces, - parseSearchPath, Direction(..), reslash, makeRelativeTo, @@ -1005,26 +1004,6 @@ type Suffix = String -- * Search path -------------------------------------------------------------- --- | The function splits the given string to substrings --- using the 'searchPathSeparator'. -parseSearchPath :: String -> [FilePath] -parseSearchPath path = split path - where - split :: String -> [String] - split s = - case rest' of - [] -> [chunk] - _:rest -> chunk : split rest - where - chunk = - case chunk' of -#ifdef mingw32_HOST_OS - ('\"':xs@(_:_)) | last xs == '\"' -> init xs -#endif - _ -> chunk' - - (chunk', rest') = break isSearchPathSeparator s - data Direction = Forwards | Backwards reslash :: Direction -> FilePath -> FilePath diff --git a/libraries/filepath b/libraries/filepath index 7011e20..83b6d8c 160000 --- a/libraries/filepath +++ b/libraries/filepath @@ -1 +1 @@ -Subproject commit 7011e20dbe30f96f34f6cfb1fd3f3aad9e7a6534 +Subproject commit 83b6d8c555d278f5bb79cef6661d02bc38e72c1e diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs index a67dbb2..b1c7a4b 100644 --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -600,9 +600,10 @@ getPkgDatabases verbosity modify use_user use_cache expand_vars my_flags = do case e_pkg_path of Left _ -> sys_databases Right path - | last cs == "" -> init cs ++ sys_databases - | otherwise -> cs - where cs = parseSearchPath path + | not (null path) && isSearchPathSeparator (last path) + -> splitSearchPath (init path) ++ sys_databases + | otherwise + -> splitSearchPath path -- The "global" database is always the one at the bottom of the stack. -- This is the database we modify by default. @@ -2006,26 +2007,6 @@ openNewFile dir template = do -- in binary mode. openTempFileWithDefaultPermissions dir template --- | The function splits the given string to substrings --- using 'isSearchPathSeparator'. -parseSearchPath :: String -> [FilePath] -parseSearchPath path = split path - where - split :: String -> [String] - split s = - case rest' of - [] -> [chunk] - _:rest -> chunk : split rest - where - chunk = - case chunk' of -#ifdef mingw32_HOST_OS - ('\"':xs@(_:_)) | last xs == '\"' -> init xs -#endif - _ -> chunk' - - (chunk', rest') = break isSearchPathSeparator s - readUTF8File :: FilePath -> IO String readUTF8File file = do h <- openFile file ReadMode From git at git.haskell.org Wed Nov 19 22:44:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 22:44:57 +0000 (UTC) Subject: [commit: ghc] wip/merge: Add remaining s and comments to .mailmap (63e3ea4) Message-ID: <20141119224457.8337F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/63e3ea49d3dffac8b172e16f591be82a0dfada5a/ghc >--------------------------------------------------------------- commit 63e3ea49d3dffac8b172e16f591be82a0dfada5a Author: Thomas Miedema Date: Tue Nov 18 22:20:14 2014 -0600 Add remaining s and comments to .mailmap Summary: All done, except for these 2 empty commits: $ git log --author=unknown --use-mailmap --oneline 7e5c2b2 [project @ 2001-12-06 10:17:35 by mbs] Established under cvs. 6456598 [project @ 2000-12-01 10:33:41 by cryder] Initial revision Reviewers: hvr, austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D477 >--------------------------------------------------------------- 63e3ea49d3dffac8b172e16f591be82a0dfada5a .mailmap | 59 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++- 1 file changed, 58 insertions(+), 1 deletion(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 63e3ea49d3dffac8b172e16f591be82a0dfada5a From git at git.haskell.org Wed Nov 19 22:45:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 22:45:00 +0000 (UTC) Subject: [commit: ghc] wip/merge: Turn CoreWriter into a newtype; fix comment (45ee8c2) Message-ID: <20141119224500.23B9D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/45ee8c2a9f5acad8fd443f28eb46e1f1e4209ea2/ghc >--------------------------------------------------------------- commit 45ee8c2a9f5acad8fd443f28eb46e1f1e4209ea2 Author: David Feuer Date: Tue Nov 18 22:19:46 2014 -0600 Turn CoreWriter into a newtype; fix comment Summary: Turn CoreWriter into a newtype. A comment claimed something is forced before returning, but it's actually not. Change comment to match reality. Reviewers: xich, simonpj, ezyang, austin Reviewed By: ezyang, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D453 >--------------------------------------------------------------- 45ee8c2a9f5acad8fd443f28eb46e1f1e4209ea2 compiler/simplCore/CoreMonad.lhs | 19 +++++++++++-------- 1 file changed, 11 insertions(+), 8 deletions(-) diff --git a/compiler/simplCore/CoreMonad.lhs b/compiler/simplCore/CoreMonad.lhs index 04782f1..0d41d5e 100644 --- a/compiler/simplCore/CoreMonad.lhs +++ b/compiler/simplCore/CoreMonad.lhs @@ -776,10 +776,11 @@ data CoreReader = CoreReader { #endif } -data CoreWriter = CoreWriter { - cw_simpl_count :: !SimplCount - -- Making this strict fixes a nasty space leak - -- See Trac #7702 +-- Note: CoreWriter used to be defined with data, rather than newtype. If it +-- is defined that way again, the cw_simpl_count field, at least, must be +-- strict to avoid a space leak (Trac #7702). +newtype CoreWriter = CoreWriter { + cw_simpl_count :: SimplCount } emptyWriter :: DynFlags -> CoreWriter @@ -808,12 +809,14 @@ instance Monad CoreM where mx >>= f = CoreM $ \s -> do (x, s', w1) <- unCoreM mx s (y, s'', w2) <- unCoreM (f x) s' - let w = w1 `plusWriter` w2 -- forcing w before returning avoids a space leak (Trac #7702) + let w = w1 `plusWriter` w2 return $ seq w (y, s'', w) - + -- forcing w before building the tuple avoids a space leak + -- (Trac #7702) instance A.Applicative CoreM where pure = return (<*>) = ap + (*>) = (>>) instance MonadPlus IO => A.Alternative CoreM where empty = mzero @@ -986,8 +989,8 @@ on Windows. On Windows the GHC library tends to export more than 65536 symbols (see #5292) which overflows the limit of what we can export from the EXE and causes breakage. -(Note that if the GHC exeecutable was dynamically linked this wouldn't be a problem, -because we could share the GHC library it links to.) +(Note that if the GHC executable was dynamically linked this wouldn't be a +problem, because we could share the GHC library it links to.) We are going to try 2. instead. Unfortunately, this means that every plugin will have to say `reinitializeGlobals` before it does anything, but never mind. From git at git.haskell.org Wed Nov 19 22:45:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 22:45:02 +0000 (UTC) Subject: [commit: ghc] wip/merge: template-haskell: Missing instances for Rational and (). (26dab1f) Message-ID: <20141119224502.DEEFC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/26dab1fdf30e0a595b176150a0bca3017f1be844/ghc >--------------------------------------------------------------- commit 26dab1fdf30e0a595b176150a0bca3017f1be844 Author: Mathieu Boespflug Date: Tue Nov 18 22:21:15 2014 -0600 template-haskell: Missing instances for Rational and (). Test Plan: ./validate Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D492 >--------------------------------------------------------------- 26dab1fdf30e0a595b176150a0bca3017f1be844 docs/users_guide/7.10.1-notes.xml | 5 +++++ libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 11 +++++++++-- 2 files changed, 14 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 2e509e1..0cf3f61 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -176,6 +176,11 @@ Various features unsupported in quotations were previously silently ignored. These now cause errors. + + + Lift instances were added for + () and Ratio. + diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 48199a4..9813095 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -1,5 +1,6 @@ {-# LANGUAGE CPP, DeriveDataTypeable, PolymorphicComponents, - RoleAnnotations, DeriveGeneric #-} + RoleAnnotations, DeriveGeneric, TypeSynonymInstances, + FlexibleInstances #-} ----------------------------------------------------------------------------- -- | @@ -454,7 +455,10 @@ instance Lift Integer where lift x = return (LitE (IntegerL x)) instance Lift Int where - lift x= return (LitE (IntegerL (fromIntegral x))) + lift x = return (LitE (IntegerL (fromIntegral x))) + +instance Lift Rational where + lift x = return (LitE (RationalL x)) instance Lift Char where lift x = return (LitE (CharL x)) @@ -478,6 +482,9 @@ liftString :: String -> Q Exp -- Used in TcExpr to short-circuit the lifting for strings liftString s = return (LitE (StringL s)) +instance Lift () where + lift () = return (ConE (tupleDataName 0)) + instance (Lift a, Lift b) => Lift (a, b) where lift (a, b) = liftM TupE $ sequence [lift a, lift b] From git at git.haskell.org Wed Nov 19 22:45:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 22:45:05 +0000 (UTC) Subject: [commit: ghc] wip/merge: Implement new Foldable methods for HsPatSynDetails (9be722a) Message-ID: <20141119224505.A39A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/9be722aaf5d21279f053628d2e13ea3faacf2a45/ghc >--------------------------------------------------------------- commit 9be722aaf5d21279f053628d2e13ea3faacf2a45 Author: David Feuer Date: Tue Nov 18 22:18:57 2014 -0600 Implement new Foldable methods for HsPatSynDetails Summary: Also explicitly define foldl1 and foldr1, which should generally work better with list-specific versions. Reviewers: austin Reviewed By: austin Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D430 >--------------------------------------------------------------- 9be722aaf5d21279f053628d2e13ea3faacf2a45 compiler/hsSyn/HsBinds.lhs | 21 ++++++++++++++++++++- 1 file changed, 20 insertions(+), 1 deletion(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index bbf6bc2..95ec98e 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -14,6 +14,7 @@ Datatype for: @BindGroup@, @Bind@, @Sig@, @Bind at . -- in module PlaceHolder {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE CPP #-} +{-# LANGUAGE BangPatterns #-} module HsBinds where @@ -41,8 +42,8 @@ import BooleanFormula (BooleanFormula) import Data.Data hiding ( Fixity ) import Data.List import Data.Ord -#if __GLASGOW_HASKELL__ < 709 import Data.Foldable ( Foldable(..) ) +#if __GLASGOW_HASKELL__ < 709 import Data.Traversable ( Traversable(..) ) import Data.Monoid ( mappend ) import Control.Applicative hiding (empty) @@ -807,6 +808,24 @@ instance Foldable HsPatSynDetails where foldMap f (InfixPatSyn left right) = f left `mappend` f right foldMap f (PrefixPatSyn args) = foldMap f args + foldl1 f (InfixPatSyn left right) = left `f` right + foldl1 f (PrefixPatSyn args) = Data.List.foldl1 f args + + foldr1 f (InfixPatSyn left right) = left `f` right + foldr1 f (PrefixPatSyn args) = Data.List.foldr1 f args + +-- TODO: After a few more versions, we should probably use these. +#if __GLASGOW_HASKELL__ >= 709 + length (InfixPatSyn _ _) = 2 + length (PrefixPatSyn args) = Data.List.length args + + null (InfixPatSyn _ _) = False + null (PrefixPatSyn args) = Data.List.null args + + toList (InfixPatSyn left right) = [left, right] + toList (PrefixPatSyn args) = args +#endif + instance Traversable HsPatSynDetails where traverse f (InfixPatSyn left right) = InfixPatSyn <$> f left <*> f right traverse f (PrefixPatSyn args) = PrefixPatSyn <$> traverse f args From git at git.haskell.org Wed Nov 19 22:45:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 22:45:08 +0000 (UTC) Subject: [commit: ghc] wip/merge: Filter input to abiHash early (4fab5c7) Message-ID: <20141119224508.3A5AE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/4fab5c73061ea4395ac808de08c23adf2a3fb870/ghc >--------------------------------------------------------------- commit 4fab5c73061ea4395ac808de08c23adf2a3fb870 Author: Mateusz Kowalczyk Date: Tue Nov 18 22:21:03 2014 -0600 Filter input to abiHash early Summary: This is already done near the only call site so why not. It is ugly to see it at 'abiHash' itself. Test Plan: validate Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D491 >--------------------------------------------------------------- 4fab5c73061ea4395ac808de08c23adf2a3fb870 ghc/Main.hs | 12 +++++++++--- 1 file changed, 9 insertions(+), 3 deletions(-) diff --git a/ghc/Main.hs b/ghc/Main.hs index c1ee247..4fd7803 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -236,7 +236,7 @@ main' postLoadMode dflags0 args flagWarnings = do StopBefore p -> liftIO (oneShot hsc_env p srcs) DoInteractive -> ghciUI srcs Nothing DoEval exprs -> ghciUI srcs $ Just $ reverse exprs - DoAbiHash -> abiHash srcs + DoAbiHash -> abiHash (map fst srcs) ShowPackages -> liftIO $ showPackages dflags6 liftIO $ dumpFinalStats dflags6 @@ -798,7 +798,13 @@ the package chagnes, so during registration Cabal calls ghc --abi-hash to get a hash of the package's ABI. -} -abiHash :: [(String, Maybe Phase)] -> Ghc () +-- | Print ABI hash of input modules. +-- +-- The resulting hash is the MD5 of the GHC version used (Trac #5328, +-- see 'hiVersion') and of the existing ABI hash from each module (see +-- 'mi_mod_hash'). +abiHash :: [String] -- ^ List of module names + -> Ghc () abiHash strs = do hsc_env <- getSession let dflags = hsc_dflags hsc_env @@ -813,7 +819,7 @@ abiHash strs = do _error -> throwGhcException $ CmdLineError $ showSDoc dflags $ cannotFindInterface dflags modname r - mods <- mapM find_it (map fst strs) + mods <- mapM find_it strs let get_iface modl = loadUserInterface False (text "abiHash") modl ifaces <- initIfaceCheck hsc_env $ mapM get_iface mods From git at git.haskell.org Wed Nov 19 22:45:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 22:45:10 +0000 (UTC) Subject: [commit: ghc] wip/merge: configure on Windows now downloads a mingw distribution on the fly if needed. (d2b3f49) Message-ID: <20141119224510.D3F023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/d2b3f49be31ce2a9fe0566fc3c9d33e19213d47c/ghc >--------------------------------------------------------------- commit d2b3f49be31ce2a9fe0566fc3c9d33e19213d47c Author: Gintautas Miliauskas Date: Wed Nov 19 16:20:14 2014 -0600 configure on Windows now downloads a mingw distribution on the fly if needed. Summary: Also, migrated away from the rubenvb mingw distribution to a more up-to-date and semi-official mingw-builds. Updated the version of gcc to 4.8.3. This change obviates the need for a ghc-tarballs repository. Also removed use of an embedded perl (also from ghc-tarballs) since it is provided by msys2. Reviewers: austin Reviewed By: austin Subscribers: awson, hvr, thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D339 GHC Trac Issues: #9218 >--------------------------------------------------------------- d2b3f49be31ce2a9fe0566fc3c9d33e19213d47c .arclint | 2 +- .gitignore | 4 +- configure.ac | 167 +++---- driver/gcc/gcc.c | 4 +- ghc.mk | 5 - mk/config.mk.in | 4 + mk/tree.mk | 1 - packages | 2 - rts/Linker.c | 524 +++++++++++---------- rts/win32/seh_excn.h | 4 + sync-all | 6 - testsuite/tests/driver/shared001.stderr | 1 - .../tests/ghci/linking/ghcilink002.stderr-mingw32 | 1 - .../tests/ghci/linking/ghcilink005.stderr-mingw32 | 1 - testsuite/tests/rts/T5435_dyn_asm.stderr-mingw32 | 1 - testsuite/tests/rts/T5435_dyn_gcc.stderr-mingw32 | 1 - 16 files changed, 364 insertions(+), 364 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d2b3f49be31ce2a9fe0566fc3c9d33e19213d47c From git at git.haskell.org Wed Nov 19 22:45:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 22:45:13 +0000 (UTC) Subject: [commit: ghc] wip/merge: Only test for bug #9439 when llvm is installed (ae8d49b) Message-ID: <20141119224513.97A633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/ae8d49bda5843ebb8d4b1811074e4ba548aa1042/ghc >--------------------------------------------------------------- commit ae8d49bda5843ebb8d4b1811074e4ba548aa1042 Author: Thomas Miedema Date: Tue Nov 18 22:23:27 2014 -0600 Only test for bug #9439 when llvm is installed Reviewers: bgamari, austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D500 GHC Trac Issues: #9807 >--------------------------------------------------------------- ae8d49bda5843ebb8d4b1811074e4ba548aa1042 configure.ac | 103 ++++++++++++++++++++++++++++++----------------------------- 1 file changed, 53 insertions(+), 50 deletions(-) diff --git a/configure.ac b/configure.ac index 7bd599f..5dd3aaa 100644 --- a/configure.ac +++ b/configure.ac @@ -187,56 +187,6 @@ AC_SUBST([WithGhc]) dnl ** Without optimization some INLINE trickery fails for GHCi SRC_CC_OPTS="-O" -dnl ** Bug 9439: Some GHC 7.8 releases had broken LLVM code generator. -dnl Unfortunately we don't know whether the user is going to request a -dnl build with the LLVM backend as this is only given in build.mk. -dnl -dnl Instead, we try to do as much work as possible here, checking -dnl whether -fllvm is the stage 0 compiler's default. If so we -dnl fail. If not, we check whether -fllvm is affected explicitly and -dnl if so set a flag. The build system will later check this flag -dnl after the desired build flags are known. -AC_MSG_CHECKING(whether bootstrap compiler is affected by bug 9439) -echo "main = putStrLn \"%function\"" > conftestghc.hs - -# Check whether LLVM backend is default for this platform -"${WithGhc}" conftestghc.hs 2>&1 >/dev/null -res=`./conftestghc` -if test "x$res" == "x%object" -then - AC_MSG_RESULT(yes) - echo "Buggy bootstrap compiler" - echo "" - echo "The stage 0 compiler $WithGhc is affected by GHC Bug \#9439" - echo "and therefore will miscompile the LLVM backend if -fllvm is" - echo "used." - echo - echo "Please use another bootstrap compiler" - exit 1 -fi - -# -fllvm is not the default, but set a flag so the Makefile can check -# -for it in the build flags later on -"${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null -if test $? == 0 -then - res=`./conftestghc` - if test "x$res" == "x%object" - then - AC_MSG_RESULT(yes) - GHC_LLVM_AFFECTED_BY_9439=1 - elif test "x$res" == "x%function" - then - AC_MSG_RESULT(no) - GHC_LLVM_AFFECTED_BY_9439=0 - else - AC_MSG_WARN(unexpected output $res) - fi -else - AC_MSG_RESULT(failed to compile, assuming no) -fi -AC_SUBST([GHC_LLVM_AFFECTED_BY_9439]) - dnl-------------------------------------------------------------------- dnl * Choose host(/target/build) platform dnl-------------------------------------------------------------------- @@ -593,6 +543,59 @@ dnl -------------------------------------------------------------- dnl * General configuration checks dnl -------------------------------------------------------------- +dnl ** Bug 9439: Some GHC 7.8 releases had broken LLVM code generator. +dnl Unfortunately we don't know whether the user is going to request a +dnl build with the LLVM backend as this is only given in build.mk. +dnl +dnl Instead, we try to do as much work as possible here, checking +dnl whether -fllvm is the stage 0 compiler's default. If so we +dnl fail. If not, we check whether -fllvm is affected explicitly and +dnl if so set a flag. The build system will later check this flag +dnl after the desired build flags are known. +if test -n "$LlcCmd" && test -n "$OptCmd" +then + AC_MSG_CHECKING(whether bootstrap compiler is affected by bug 9439) + echo "main = putStrLn \"%function\"" > conftestghc.hs + + # Check whether LLVM backend is default for this platform + "${WithGhc}" conftestghc.hs 2>&1 >/dev/null + res=`./conftestghc` + if test "x$res" == "x%object" + then + AC_MSG_RESULT(yes) + echo "Buggy bootstrap compiler" + echo "" + echo "The stage 0 compiler $WithGhc is affected by GHC Bug \#9439" + echo "and therefore will miscompile the LLVM backend if -fllvm is" + echo "used." + echo + echo "Please use another bootstrap compiler" + exit 1 + fi + + # -fllvm is not the default, but set a flag so the Makefile can check + # -for it in the build flags later on + "${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null + if test $? == 0 + then + res=`./conftestghc` + if test "x$res" == "x%object" + then + AC_MSG_RESULT(yes) + GHC_LLVM_AFFECTED_BY_9439=1 + elif test "x$res" == "x%function" + then + AC_MSG_RESULT(no) + GHC_LLVM_AFFECTED_BY_9439=0 + else + AC_MSG_WARN(unexpected output $res) + fi + else + AC_MSG_RESULT(failed to compile, assuming no) + fi +fi +AC_SUBST([GHC_LLVM_AFFECTED_BY_9439]) + dnl ** Can the unix package be built? dnl -------------------------------------------------------------- From git at git.haskell.org Wed Nov 19 22:45:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 22:45:16 +0000 (UTC) Subject: [commit: ghc] wip/merge: add missing instances for Loc and a few missing Eq instances (7fb7a41) Message-ID: <20141119224516.31E163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/7fb7a41f38657f744f11f93448450137ac9e6a79/ghc >--------------------------------------------------------------- commit 7fb7a41f38657f744f11f93448450137ac9e6a79 Author: Luite Stegeman Date: Tue Nov 18 22:21:44 2014 -0600 add missing instances for Loc and a few missing Eq instances Summary: This adds a few missing instances that can be automatically derived Reviewers: hvr, goldfire, austin Reviewed By: goldfire, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D495 >--------------------------------------------------------------- 7fb7a41f38657f744f11f93448450137ac9e6a79 libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 9813095..8c95045 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -878,6 +878,7 @@ data Loc , loc_module :: String , loc_start :: CharPos , loc_end :: CharPos } + deriving( Show, Eq, Data, Typeable, Generic ) type CharPos = (Int, Int) -- ^ Line and character position @@ -952,13 +953,13 @@ data Info | TyVarI -- Scoped type variable Name Type -- What it is bound to - deriving( Show, Data, Typeable, Generic ) + deriving( Show, Eq, Data, Typeable, Generic ) -- | Obtained from 'reifyModule' in the 'Q' Monad. data ModuleInfo = -- | Contains the import list of the module. ModuleInfo [Module] - deriving( Show, Data, Typeable, Generic ) + deriving( Show, Eq, Data, Typeable, Generic ) {- | In 'ClassOpI' and 'DataConI', name of the parent class or type From git at git.haskell.org Wed Nov 19 22:45:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 22:45:19 +0000 (UTC) Subject: [commit: ghc] wip/merge: Allow -dead_strip linking on platforms with .subsections_via_symbols (2dd80b4) Message-ID: <20141119224519.F2DE83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/2dd80b4b758df51857ccb975d1261882cd79c9cb/ghc >--------------------------------------------------------------- commit 2dd80b4b758df51857ccb975d1261882cd79c9cb Author: Moritz Angermann Date: Wed Nov 19 16:38:22 2014 -0600 Allow -dead_strip linking on platforms with .subsections_via_symbols Summary: This allows to link objects produced with the llvm code generator to be linked with -dead_strip. This applies to at least the iOS cross compiler and OS X compiler. Signed-off-by: Moritz Angermann Test Plan: Create a ffi library and link it with -dead_strip. If the resulting binary does not crash, the patch works as advertised. Reviewers: rwbarton, simonmar, hvr, dterei, mzero, ezyang, austin Reviewed By: dterei, ezyang, austin Subscribers: thomie, mzero, simonmar, ezyang, carter Differential Revision: https://phabricator.haskell.org/D206 >--------------------------------------------------------------- 2dd80b4b758df51857ccb975d1261882cd79c9cb compiler/NOTES | 16 ++++++++++++++++ compiler/llvmGen/LlvmCodeGen/Ppr.hs | 8 +++++++- compiler/nativeGen/PPC/Ppr.hs | 7 +------ compiler/nativeGen/SPARC/Ppr.hs | 7 +------ compiler/nativeGen/X86/Ppr.hs | 7 +------ .../should_compile => llvm/should_run}/Makefile | 0 .../llvm/should_run/subsections_via_symbols/Makefile | 13 +++++++++++++ .../subsections_via_symbols/SubsectionsViaSymbols.hs | 5 +++++ .../tests/llvm/should_run/subsections_via_symbols/all.T | 15 +++++++++++++++ .../subsections_via_symbols-libtool-quiet | 4 ++++ .../subsections_via_symbols/subsections_via_symbols.m | 11 +++++++++++ .../subsections_via_symbols.stderr | 0 .../subsections_via_symbols.stdout | 2 ++ 13 files changed, 76 insertions(+), 19 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2dd80b4b758df51857ccb975d1261882cd79c9cb From git at git.haskell.org Wed Nov 19 22:45:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 22:45:22 +0000 (UTC) Subject: [commit: ghc] wip/merge: make TcRnMonad.lhs respect -ddump-to-file (31f21aa) Message-ID: <20141119224522.97C0A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/31f21aaf5038d533fbf4369aff07a9460d329390/ghc >--------------------------------------------------------------- commit 31f21aaf5038d533fbf4369aff07a9460d329390 Author: Greg Weber Date: Wed Nov 19 16:43:26 2014 -0600 make TcRnMonad.lhs respect -ddump-to-file Summary: allows things such as: -ddump-to-file -ddump-splices Test Plan: compile with flags -ddump-to-file -ddump-splices verify that it does output an extra file Try out other flags. I noticed that with -ddump-tc there is some output going to file and some to stdout. Reviewers: hvr, austin Reviewed By: austin Subscribers: simonpj, thomie, carter Differential Revision: https://phabricator.haskell.org/D460 GHC Trac Issues: #9126 >--------------------------------------------------------------- 31f21aaf5038d533fbf4369aff07a9460d329390 compiler/ghci/RtClosureInspect.hs | 1 + compiler/main/ErrUtils.lhs | 21 ++++-- compiler/typecheck/TcRnDriver.lhs | 6 +- compiler/typecheck/TcRnMonad.lhs | 79 +++++++++++++--------- docs/users_guide/7.10.1-notes.xml | 10 +++ .../tests/indexed-types/should_fail/T8129.stdout | 1 - 6 files changed, 78 insertions(+), 40 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 31f21aaf5038d533fbf4369aff07a9460d329390 From git at git.haskell.org Wed Nov 19 23:03:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 23:03:06 +0000 (UTC) Subject: [commit: ghc] master: rts: remove old-style field designator extension (#9396) (8e0a480) Message-ID: <20141119230306.4D8A83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8e0a480ca655010e67a38aca9b8705ecbd0f0c97/ghc >--------------------------------------------------------------- commit 8e0a480ca655010e67a38aca9b8705ecbd0f0c97 Author: Austin Seipp Date: Tue Nov 18 21:21:47 2014 -0600 rts: remove old-style field designator extension (#9396) Authored-by: jrp Signed-off-by: Austin Seipp >--------------------------------------------------------------- 8e0a480ca655010e67a38aca9b8705ecbd0f0c97 includes/rts/prof/CCS.h | 48 ++++++++++++++++++++++++------------------------ rts/RetainerSet.c | 10 +++++----- 2 files changed, 29 insertions(+), 29 deletions(-) diff --git a/includes/rts/prof/CCS.h b/includes/rts/prof/CCS.h index 85b03f3..74f18b8 100644 --- a/includes/rts/prof/CCS.h +++ b/includes/rts/prof/CCS.h @@ -210,32 +210,32 @@ extern CostCentreStack * RTS_VAR(CCS_LIST); // registered CCS list * Declaring Cost Centres & Cost Centre Stacks. * -------------------------------------------------------------------------- */ -# define CC_DECLARE(cc_ident,name,mod,loc,caf,is_local) \ - is_local CostCentre cc_ident[1] \ - = {{ ccID : 0, \ - label : name, \ - module : mod, \ - srcloc : loc, \ - time_ticks : 0, \ - mem_alloc : 0, \ - link : 0, \ - is_caf : caf \ +# define CC_DECLARE(cc_ident,name,mod,loc,caf,is_local) \ + is_local CostCentre cc_ident[1] \ + = {{ .ccID = 0, \ + .label = name, \ + .module = mod, \ + .srcloc = loc, \ + .time_ticks = 0, \ + .mem_alloc = 0, \ + .link = 0, \ + .is_caf = caf \ }}; -# define CCS_DECLARE(ccs_ident,cc_ident,is_local) \ - is_local CostCentreStack ccs_ident[1] \ - = {{ ccsID : 0, \ - cc : cc_ident, \ - prevStack : NULL, \ - indexTable : NULL, \ - root : NULL, \ - depth : 0, \ - selected : 0, \ - scc_count : 0, \ - time_ticks : 0, \ - mem_alloc : 0, \ - inherited_ticks : 0, \ - inherited_alloc : 0 \ +# define CCS_DECLARE(ccs_ident,cc_ident,is_local) \ + is_local CostCentreStack ccs_ident[1] \ + = {{ .ccsID = 0, \ + .cc = cc_ident, \ + .prevStack = NULL, \ + .indexTable = NULL, \ + .root = NULL, \ + .depth = 0, \ + .selected = 0, \ + .scc_count = 0, \ + .time_ticks = 0, \ + .mem_alloc = 0, \ + .inherited_ticks = 0, \ + .inherited_alloc = 0 \ }}; /* ----------------------------------------------------------------------------- diff --git a/rts/RetainerSet.c b/rts/RetainerSet.c index 1905866..234532a 100644 --- a/rts/RetainerSet.c +++ b/rts/RetainerSet.c @@ -40,11 +40,11 @@ static int nextId; // id of next retainer set * from growing too large. * -------------------------------------------------------------------------- */ RetainerSet rs_MANY = { - num : 0, - hashKey : 0, - link : NULL, - id : 1, - element : {} + .num = 0, + .hashKey = 0, + .link = NULL, + .id = 1, + .element = {} }; /* ----------------------------------------------------------------------------- From git at git.haskell.org Wed Nov 19 23:03:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 23:03:08 +0000 (UTC) Subject: [commit: ghc] master: Filter input to abiHash early (7ef0971) Message-ID: <20141119230308.D6D3F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7ef0971a016d45915d1fa88a308db80a5c9e97ba/ghc >--------------------------------------------------------------- commit 7ef0971a016d45915d1fa88a308db80a5c9e97ba Author: Mateusz Kowalczyk Date: Tue Nov 18 22:21:03 2014 -0600 Filter input to abiHash early Summary: This is already done near the only call site so why not. It is ugly to see it at 'abiHash' itself. Test Plan: validate Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D491 >--------------------------------------------------------------- 7ef0971a016d45915d1fa88a308db80a5c9e97ba ghc/Main.hs | 12 +++++++++--- 1 file changed, 9 insertions(+), 3 deletions(-) diff --git a/ghc/Main.hs b/ghc/Main.hs index c1ee247..4fd7803 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -236,7 +236,7 @@ main' postLoadMode dflags0 args flagWarnings = do StopBefore p -> liftIO (oneShot hsc_env p srcs) DoInteractive -> ghciUI srcs Nothing DoEval exprs -> ghciUI srcs $ Just $ reverse exprs - DoAbiHash -> abiHash srcs + DoAbiHash -> abiHash (map fst srcs) ShowPackages -> liftIO $ showPackages dflags6 liftIO $ dumpFinalStats dflags6 @@ -798,7 +798,13 @@ the package chagnes, so during registration Cabal calls ghc --abi-hash to get a hash of the package's ABI. -} -abiHash :: [(String, Maybe Phase)] -> Ghc () +-- | Print ABI hash of input modules. +-- +-- The resulting hash is the MD5 of the GHC version used (Trac #5328, +-- see 'hiVersion') and of the existing ABI hash from each module (see +-- 'mi_mod_hash'). +abiHash :: [String] -- ^ List of module names + -> Ghc () abiHash strs = do hsc_env <- getSession let dflags = hsc_dflags hsc_env @@ -813,7 +819,7 @@ abiHash strs = do _error -> throwGhcException $ CmdLineError $ showSDoc dflags $ cannotFindInterface dflags modname r - mods <- mapM find_it (map fst strs) + mods <- mapM find_it strs let get_iface modl = loadUserInterface False (text "abiHash") modl ifaces <- initIfaceCheck hsc_env $ mapM get_iface mods From git at git.haskell.org Wed Nov 19 23:03:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 23:03:11 +0000 (UTC) Subject: [commit: ghc] master: Add remaining s and comments to .mailmap (5c09893) Message-ID: <20141119230311.808163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5c098930a56286e5144cb5a24aae3db90ed741bd/ghc >--------------------------------------------------------------- commit 5c098930a56286e5144cb5a24aae3db90ed741bd Author: Thomas Miedema Date: Tue Nov 18 22:20:14 2014 -0600 Add remaining s and comments to .mailmap Summary: All done, except for these 2 empty commits: $ git log --author=unknown --use-mailmap --oneline 7e5c2b2 [project @ 2001-12-06 10:17:35 by mbs] Established under cvs. 6456598 [project @ 2000-12-01 10:33:41 by cryder] Initial revision Reviewers: hvr, austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D477 >--------------------------------------------------------------- 5c098930a56286e5144cb5a24aae3db90ed741bd .mailmap | 59 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++- 1 file changed, 58 insertions(+), 1 deletion(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5c098930a56286e5144cb5a24aae3db90ed741bd From git at git.haskell.org Wed Nov 19 23:03:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 23:03:14 +0000 (UTC) Subject: [commit: ghc] master: Turn CoreWriter into a newtype; fix comment (5db61ea) Message-ID: <20141119230314.0F09B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5db61eac77e1e2532b9c2f3d454a206255687097/ghc >--------------------------------------------------------------- commit 5db61eac77e1e2532b9c2f3d454a206255687097 Author: David Feuer Date: Tue Nov 18 22:19:46 2014 -0600 Turn CoreWriter into a newtype; fix comment Summary: Turn CoreWriter into a newtype. A comment claimed something is forced before returning, but it's actually not. Change comment to match reality. Reviewers: xich, simonpj, ezyang, austin Reviewed By: ezyang, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D453 >--------------------------------------------------------------- 5db61eac77e1e2532b9c2f3d454a206255687097 compiler/simplCore/CoreMonad.lhs | 19 +++++++++++-------- 1 file changed, 11 insertions(+), 8 deletions(-) diff --git a/compiler/simplCore/CoreMonad.lhs b/compiler/simplCore/CoreMonad.lhs index 04782f1..0d41d5e 100644 --- a/compiler/simplCore/CoreMonad.lhs +++ b/compiler/simplCore/CoreMonad.lhs @@ -776,10 +776,11 @@ data CoreReader = CoreReader { #endif } -data CoreWriter = CoreWriter { - cw_simpl_count :: !SimplCount - -- Making this strict fixes a nasty space leak - -- See Trac #7702 +-- Note: CoreWriter used to be defined with data, rather than newtype. If it +-- is defined that way again, the cw_simpl_count field, at least, must be +-- strict to avoid a space leak (Trac #7702). +newtype CoreWriter = CoreWriter { + cw_simpl_count :: SimplCount } emptyWriter :: DynFlags -> CoreWriter @@ -808,12 +809,14 @@ instance Monad CoreM where mx >>= f = CoreM $ \s -> do (x, s', w1) <- unCoreM mx s (y, s'', w2) <- unCoreM (f x) s' - let w = w1 `plusWriter` w2 -- forcing w before returning avoids a space leak (Trac #7702) + let w = w1 `plusWriter` w2 return $ seq w (y, s'', w) - + -- forcing w before building the tuple avoids a space leak + -- (Trac #7702) instance A.Applicative CoreM where pure = return (<*>) = ap + (*>) = (>>) instance MonadPlus IO => A.Alternative CoreM where empty = mzero @@ -986,8 +989,8 @@ on Windows. On Windows the GHC library tends to export more than 65536 symbols (see #5292) which overflows the limit of what we can export from the EXE and causes breakage. -(Note that if the GHC exeecutable was dynamically linked this wouldn't be a problem, -because we could share the GHC library it links to.) +(Note that if the GHC executable was dynamically linked this wouldn't be a +problem, because we could share the GHC library it links to.) We are going to try 2. instead. Unfortunately, this means that every plugin will have to say `reinitializeGlobals` before it does anything, but never mind. From git at git.haskell.org Wed Nov 19 23:03:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 23:03:16 +0000 (UTC) Subject: [commit: ghc] master: Refactor: use System.FilePath.splitSearchPath (6fc78fd) Message-ID: <20141119230316.ADA7C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6fc78fdfa1482a31ed7b586f20c9d7cb592ea944/ghc >--------------------------------------------------------------- commit 6fc78fdfa1482a31ed7b586f20c9d7cb592ea944 Author: Thomas Miedema Date: Tue Nov 18 22:17:47 2014 -0600 Refactor: use System.FilePath.splitSearchPath Summary: To address #2521 ("Trailing colon on GHC_PACKAGE_PATH doesn't work with ghc-pkg"), we were using a custom version of splitSearchPath (e4f46f5de). This solution however caused issue #9698 ("GHC_PACKAGE_PATH should be more lenient for empty paths"). This patch reverts back to System.FilePath.splitSearchPath (fixes #9698) and adresses (#2521) by testing for a trailing search path separators explicitly (instead of implicitly using empty search path elements). Empty paths are now allowed (ignored on Windows, interpreted as current directory on Posix systems), and trailing path separator still tack on the user and system package databases. Also update submodule filepath, which has a version of splitSearchPath which handles quotes in the same way as our custom version did. Test Plan: $ GHC_PACKAGE_PATH=/::/home: ./ghc-pkg list ... db stack: ["/",".","/home","",""] ... Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D414 GHC Trac Issues: #2521, #9698 >--------------------------------------------------------------- 6fc78fdfa1482a31ed7b586f20c9d7cb592ea944 compiler/main/Packages.lhs | 9 +++------ compiler/utils/Util.lhs | 21 --------------------- libraries/filepath | 2 +- utils/ghc-pkg/Main.hs | 27 ++++----------------------- 4 files changed, 8 insertions(+), 51 deletions(-) diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs index 2f4a4d7..40b5e24 100644 --- a/compiler/main/Packages.lhs +++ b/compiler/main/Packages.lhs @@ -334,13 +334,10 @@ readPackageConfigs dflags = do let base_conf_refs = case e_pkg_path of Left _ -> system_conf_refs Right path - | null (last cs) - -> map PkgConfFile (init cs) ++ system_conf_refs + | not (null path) && isSearchPathSeparator (last path) + -> map PkgConfFile (splitSearchPath (init path)) ++ system_conf_refs | otherwise - -> map PkgConfFile cs - where cs = parseSearchPath path - -- if the path ends in a separator (eg. "/foo/bar:") - -- then we tack on the system paths. + -> map PkgConfFile (splitSearchPath path) let conf_refs = reverse (extraPkgConfs dflags base_conf_refs) -- later packages shadow earlier ones. extraPkgConfs diff --git a/compiler/utils/Util.lhs b/compiler/utils/Util.lhs index aa5f6f9..df293f0 100644 --- a/compiler/utils/Util.lhs +++ b/compiler/utils/Util.lhs @@ -89,7 +89,6 @@ module Util ( Suffix, splitLongestPrefix, escapeSpaces, - parseSearchPath, Direction(..), reslash, makeRelativeTo, @@ -1005,26 +1004,6 @@ type Suffix = String -- * Search path -------------------------------------------------------------- --- | The function splits the given string to substrings --- using the 'searchPathSeparator'. -parseSearchPath :: String -> [FilePath] -parseSearchPath path = split path - where - split :: String -> [String] - split s = - case rest' of - [] -> [chunk] - _:rest -> chunk : split rest - where - chunk = - case chunk' of -#ifdef mingw32_HOST_OS - ('\"':xs@(_:_)) | last xs == '\"' -> init xs -#endif - _ -> chunk' - - (chunk', rest') = break isSearchPathSeparator s - data Direction = Forwards | Backwards reslash :: Direction -> FilePath -> FilePath diff --git a/libraries/filepath b/libraries/filepath index 7011e20..83b6d8c 160000 --- a/libraries/filepath +++ b/libraries/filepath @@ -1 +1 @@ -Subproject commit 7011e20dbe30f96f34f6cfb1fd3f3aad9e7a6534 +Subproject commit 83b6d8c555d278f5bb79cef6661d02bc38e72c1e diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs index a67dbb2..b1c7a4b 100644 --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -600,9 +600,10 @@ getPkgDatabases verbosity modify use_user use_cache expand_vars my_flags = do case e_pkg_path of Left _ -> sys_databases Right path - | last cs == "" -> init cs ++ sys_databases - | otherwise -> cs - where cs = parseSearchPath path + | not (null path) && isSearchPathSeparator (last path) + -> splitSearchPath (init path) ++ sys_databases + | otherwise + -> splitSearchPath path -- The "global" database is always the one at the bottom of the stack. -- This is the database we modify by default. @@ -2006,26 +2007,6 @@ openNewFile dir template = do -- in binary mode. openTempFileWithDefaultPermissions dir template --- | The function splits the given string to substrings --- using 'isSearchPathSeparator'. -parseSearchPath :: String -> [FilePath] -parseSearchPath path = split path - where - split :: String -> [String] - split s = - case rest' of - [] -> [chunk] - _:rest -> chunk : split rest - where - chunk = - case chunk' of -#ifdef mingw32_HOST_OS - ('\"':xs@(_:_)) | last xs == '\"' -> init xs -#endif - _ -> chunk' - - (chunk', rest') = break isSearchPathSeparator s - readUTF8File :: FilePath -> IO String readUTF8File file = do h <- openFile file ReadMode From git at git.haskell.org Wed Nov 19 23:03:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 23:03:19 +0000 (UTC) Subject: [commit: ghc] master: template-haskell: Missing instances for Rational and (). (b3df5f6) Message-ID: <20141119230319.4354B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b3df5f6b2562ffec4bb2fb486032903b8de5f475/ghc >--------------------------------------------------------------- commit b3df5f6b2562ffec4bb2fb486032903b8de5f475 Author: Mathieu Boespflug Date: Tue Nov 18 22:21:15 2014 -0600 template-haskell: Missing instances for Rational and (). Test Plan: ./validate Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D492 >--------------------------------------------------------------- b3df5f6b2562ffec4bb2fb486032903b8de5f475 docs/users_guide/7.10.1-notes.xml | 5 +++++ libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 11 +++++++++-- 2 files changed, 14 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 2e509e1..0cf3f61 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -176,6 +176,11 @@ Various features unsupported in quotations were previously silently ignored. These now cause errors. + + + Lift instances were added for + () and Ratio. + diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 48199a4..9813095 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -1,5 +1,6 @@ {-# LANGUAGE CPP, DeriveDataTypeable, PolymorphicComponents, - RoleAnnotations, DeriveGeneric #-} + RoleAnnotations, DeriveGeneric, TypeSynonymInstances, + FlexibleInstances #-} ----------------------------------------------------------------------------- -- | @@ -454,7 +455,10 @@ instance Lift Integer where lift x = return (LitE (IntegerL x)) instance Lift Int where - lift x= return (LitE (IntegerL (fromIntegral x))) + lift x = return (LitE (IntegerL (fromIntegral x))) + +instance Lift Rational where + lift x = return (LitE (RationalL x)) instance Lift Char where lift x = return (LitE (CharL x)) @@ -478,6 +482,9 @@ liftString :: String -> Q Exp -- Used in TcExpr to short-circuit the lifting for strings liftString s = return (LitE (StringL s)) +instance Lift () where + lift () = return (ConE (tupleDataName 0)) + instance (Lift a, Lift b) => Lift (a, b) where lift (a, b) = liftM TupE $ sequence [lift a, lift b] From git at git.haskell.org Wed Nov 19 23:03:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 23:03:21 +0000 (UTC) Subject: [commit: ghc] master: Implement new Foldable methods for HsPatSynDetails (00c1a30) Message-ID: <20141119230321.D53743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/00c1a302a6ca52be42e384311373605d65c090da/ghc >--------------------------------------------------------------- commit 00c1a302a6ca52be42e384311373605d65c090da Author: David Feuer Date: Tue Nov 18 22:18:57 2014 -0600 Implement new Foldable methods for HsPatSynDetails Summary: Also explicitly define foldl1 and foldr1, which should generally work better with list-specific versions. Reviewers: austin Reviewed By: austin Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D430 >--------------------------------------------------------------- 00c1a302a6ca52be42e384311373605d65c090da compiler/hsSyn/HsBinds.lhs | 21 ++++++++++++++++++++- 1 file changed, 20 insertions(+), 1 deletion(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index bbf6bc2..95ec98e 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -14,6 +14,7 @@ Datatype for: @BindGroup@, @Bind@, @Sig@, @Bind at . -- in module PlaceHolder {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE CPP #-} +{-# LANGUAGE BangPatterns #-} module HsBinds where @@ -41,8 +42,8 @@ import BooleanFormula (BooleanFormula) import Data.Data hiding ( Fixity ) import Data.List import Data.Ord -#if __GLASGOW_HASKELL__ < 709 import Data.Foldable ( Foldable(..) ) +#if __GLASGOW_HASKELL__ < 709 import Data.Traversable ( Traversable(..) ) import Data.Monoid ( mappend ) import Control.Applicative hiding (empty) @@ -807,6 +808,24 @@ instance Foldable HsPatSynDetails where foldMap f (InfixPatSyn left right) = f left `mappend` f right foldMap f (PrefixPatSyn args) = foldMap f args + foldl1 f (InfixPatSyn left right) = left `f` right + foldl1 f (PrefixPatSyn args) = Data.List.foldl1 f args + + foldr1 f (InfixPatSyn left right) = left `f` right + foldr1 f (PrefixPatSyn args) = Data.List.foldr1 f args + +-- TODO: After a few more versions, we should probably use these. +#if __GLASGOW_HASKELL__ >= 709 + length (InfixPatSyn _ _) = 2 + length (PrefixPatSyn args) = Data.List.length args + + null (InfixPatSyn _ _) = False + null (PrefixPatSyn args) = Data.List.null args + + toList (InfixPatSyn left right) = [left, right] + toList (PrefixPatSyn args) = args +#endif + instance Traversable HsPatSynDetails where traverse f (InfixPatSyn left right) = InfixPatSyn <$> f left <*> f right traverse f (PrefixPatSyn args) = PrefixPatSyn <$> traverse f args From git at git.haskell.org Wed Nov 19 23:03:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 23:03:24 +0000 (UTC) Subject: [commit: ghc] master: Update documentation for "Batch compiler mode" (66c0513) Message-ID: <20141119230324.7EE5C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/66c05136b7940930b22cb2830f1249f97986f15b/ghc >--------------------------------------------------------------- commit 66c05136b7940930b22cb2830f1249f97986f15b Author: Thomas Miedema Date: Tue Nov 18 22:18:43 2014 -0600 Update documentation for "Batch compiler mode" Summary: Since commit 7828bf3ea2ea34e7a3a8662f5f621ef706ffee5c * --make is the default * -c is a mode flag, except when used in combination with --make Also: * -C (generate C code) is only available in unregisterised mode. Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D427 >--------------------------------------------------------------- 66c05136b7940930b22cb2830f1249f97986f15b docs/users_guide/flags.xml | 4 ++-- docs/users_guide/using.xml | 23 ++++++++++++++++++----- 2 files changed, 20 insertions(+), 7 deletions(-) diff --git a/docs/users_guide/flags.xml b/docs/users_guide/flags.xml index 33af295..e8218f7 100644 --- a/docs/users_guide/flags.xml +++ b/docs/users_guide/flags.xml @@ -209,8 +209,8 @@ - Do not link - dynamic + Stop after generating object (.o) file + mode - diff --git a/docs/users_guide/using.xml b/docs/users_guide/using.xml index 07d487e..bf4f1c5 100644 --- a/docs/users_guide/using.xml +++ b/docs/users_guide/using.xml @@ -246,6 +246,13 @@ module X where + .hspp + + A file created by the preprocessor. + + + + .hi A Haskell interface file, probably @@ -383,7 +390,7 @@ module X where ghc -E - ghc -c + ghc -C ghc -S ghc -c @@ -395,10 +402,7 @@ module X where This is the traditional batch-compiler mode, in which GHC can compile source files one at a time, or link objects - together into an executable. This mode also applies if - there is no other mode flag specified on the command line, - in which case it means that the specified files should be - compiled and then linked to form a program. See . @@ -617,6 +621,11 @@ ghc Main.hs given on the command line and GHC will include them when linking the executable. + For backward compatibility with existing make scripts, when + used in combination with , the linking phase + is omitted (same as + ). + Note that GHC can only follow dependencies if it has the source file available, so if your program includes a module for which there is no source file, even if you have an object and an @@ -765,6 +774,10 @@ ghc -c Foo.hs option runs just the pre-processing passes of the compiler, dumping the result in a file. + Note: The option is only available when + GHC is built in unregisterised mode. See + for more details. + Overriding the default behaviour for a file From git at git.haskell.org Wed Nov 19 23:03:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 23:03:27 +0000 (UTC) Subject: [commit: ghc] master: The test runner now also works under the msys-native Python. (101c62e) Message-ID: <20141119230327.25D083A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/101c62e26286353dd3fac1ef54323529b64c9902/ghc >--------------------------------------------------------------- commit 101c62e26286353dd3fac1ef54323529b64c9902 Author: Gintautas Miliauskas Date: Mon Sep 22 23:10:56 2014 +0200 The test runner now also works under the msys-native Python. Msys binaries apply heuristics to escape paths in arguments intended for non-msys binaries, which breaks timeout invocations, see #9626. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 101c62e26286353dd3fac1ef54323529b64c9902 testsuite/driver/testlib.py | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 1549381..6fc86e4 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1780,9 +1780,25 @@ def rawSystem(cmd_and_args): else: return os.spawnv(os.P_WAIT, cmd_and_args[0], cmd_and_args) +# When running under native msys Python, any invocations of non-msys binaries, +# including timeout.exe, will have their arguments munged according to some +# heuristics, which leads to malformed command lines (#9626). The easiest way +# to avoid problems is to invoke through /usr/bin/cmd which sidesteps argument +# munging because it is a native msys application. +def passThroughCmd(cmd_and_args): + args = [] + # cmd needs a Windows-style path for its first argument. + args.append(cmd_and_args[0].replace('/', '\\')) + # Other arguments need to be quoted to deal with spaces. + args.extend(['"%s"' % arg for arg in cmd_and_args[1:]]) + return ["cmd", "/c", " ".join(args)] + # Note that this doesn't handle the timeout itself; it is just used for # commands that have timeout handling built-in. def rawSystemWithTimeout(cmd_and_args): + if config.os == 'mingw32' and sys.executable.startswith('/usr'): + # This is only needed when running under msys python. + cmd_and_args = passThroughCmd(cmd_and_args) r = rawSystem(cmd_and_args) if r == 98: # The python timeout program uses 98 to signal that ^C was pressed From git at git.haskell.org Wed Nov 19 23:03:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 23:03:29 +0000 (UTC) Subject: [commit: ghc] master: make TcRnMonad.lhs respect -ddump-to-file (33c029f) Message-ID: <20141119230329.CA4113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/33c029faef3b5e486def8f3a7c888dfa9f3d8cca/ghc >--------------------------------------------------------------- commit 33c029faef3b5e486def8f3a7c888dfa9f3d8cca Author: Greg Weber Date: Wed Nov 19 16:43:26 2014 -0600 make TcRnMonad.lhs respect -ddump-to-file Summary: allows things such as: -ddump-to-file -ddump-splices Test Plan: compile with flags -ddump-to-file -ddump-splices verify that it does output an extra file Try out other flags. I noticed that with -ddump-tc there is some output going to file and some to stdout. Reviewers: hvr, austin Reviewed By: austin Subscribers: simonpj, thomie, carter Differential Revision: https://phabricator.haskell.org/D460 GHC Trac Issues: #9126 >--------------------------------------------------------------- 33c029faef3b5e486def8f3a7c888dfa9f3d8cca compiler/ghci/RtClosureInspect.hs | 1 + compiler/main/ErrUtils.lhs | 21 ++++-- compiler/typecheck/TcRnDriver.lhs | 6 +- compiler/typecheck/TcRnMonad.lhs | 79 +++++++++++++--------- docs/users_guide/7.10.1-notes.xml | 10 +++ .../tests/indexed-types/should_fail/T8129.stdout | 1 - 6 files changed, 78 insertions(+), 40 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 33c029faef3b5e486def8f3a7c888dfa9f3d8cca From git at git.haskell.org Wed Nov 19 23:03:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 23:03:32 +0000 (UTC) Subject: [commit: ghc] master: use correct word size for shiftRightLogical and removeOp32 (4dd87c5) Message-ID: <20141119230332.6B3CA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4dd87c5e3ebd0569fdd19695f3e9c82102404a4f/ghc >--------------------------------------------------------------- commit 4dd87c5e3ebd0569fdd19695f3e9c82102404a4f Author: Luite Stegeman Date: Wed Nov 19 17:00:49 2014 -0600 use correct word size for shiftRightLogical and removeOp32 Summary: shiftRightLogical used a host sized Word for the intermediate value, which would produce the wrong result when cross compiling to a target with a different word size than the host. removeOp32 used the preprocessor to bake in word size assumptions, rather than getting the target word size from DynFlags Test Plan: validate Reviewers: hvr, rwbarton, carter, austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D502 GHC Trac Issues: #9736 >--------------------------------------------------------------- 4dd87c5e3ebd0569fdd19695f3e9c82102404a4f compiler/prelude/PrelRules.lhs | 42 ++++++++++++++++++++++++++---------------- 1 file changed, 26 insertions(+), 16 deletions(-) diff --git a/compiler/prelude/PrelRules.lhs b/compiler/prelude/PrelRules.lhs index 1e5f259..0541371 100644 --- a/compiler/prelude/PrelRules.lhs +++ b/compiler/prelude/PrelRules.lhs @@ -124,7 +124,7 @@ primOpRules nm ISllOp = mkPrimOpRule nm 2 [ binaryLit (intOp2 Bits.shiftL) , rightIdentityDynFlags zeroi ] primOpRules nm ISraOp = mkPrimOpRule nm 2 [ binaryLit (intOp2 Bits.shiftR) , rightIdentityDynFlags zeroi ] -primOpRules nm ISrlOp = mkPrimOpRule nm 2 [ binaryLit (intOp2 shiftRightLogical) +primOpRules nm ISrlOp = mkPrimOpRule nm 2 [ binaryLit (intOp2' shiftRightLogical) , rightIdentityDynFlags zeroi ] -- Word operations @@ -150,7 +150,7 @@ primOpRules nm XorOp = mkPrimOpRule nm 2 [ binaryLit (wordOp2 xor) , equalArgs >> retLit zerow ] primOpRules nm NotOp = mkPrimOpRule nm 1 [ unaryLit complementOp , inversePrimOp NotOp ] -primOpRules nm SllOp = mkPrimOpRule nm 2 [ wordShiftRule Bits.shiftL ] +primOpRules nm SllOp = mkPrimOpRule nm 2 [ wordShiftRule (const Bits.shiftL) ] primOpRules nm SrlOp = mkPrimOpRule nm 2 [ wordShiftRule shiftRightLogical ] -- coercions @@ -363,15 +363,24 @@ complementOp _ _ = Nothing intOp2 :: (Integral a, Integral b) => (a -> b -> Integer) -> DynFlags -> Literal -> Literal -> Maybe CoreExpr -intOp2 op dflags (MachInt i1) (MachInt i2) = intResult dflags (fromInteger i1 `op` fromInteger i2) -intOp2 _ _ _ _ = Nothing -- Could find LitLit +intOp2 = intOp2' . const -shiftRightLogical :: Integer -> Int -> Integer +intOp2' :: (Integral a, Integral b) + => (DynFlags -> a -> b -> Integer) + -> DynFlags -> Literal -> Literal -> Maybe CoreExpr +intOp2' op dflags (MachInt i1) (MachInt i2) = + let o = op dflags + in intResult dflags (fromInteger i1 `o` fromInteger i2) +intOp2' _ _ _ _ = Nothing -- Could find LitLit + +shiftRightLogical :: DynFlags -> Integer -> Int -> Integer -- Shift right, putting zeros in rather than sign-propagating as Bits.shiftR would do -- Do this by converting to Word and back. Obviously this won't work for big -- values, but its ok as we use it here -shiftRightLogical x n = fromIntegral (fromInteger x `shiftR` n :: Word) - +shiftRightLogical dflags x n + | wordSizeInBits dflags == 32 = fromIntegral (fromInteger x `shiftR` n :: Word32) + | wordSizeInBits dflags == 64 = fromIntegral (fromInteger x `shiftR` n :: Word64) + | otherwise = panic "shiftRightLogical: unsupported word size" -------------------------- retLit :: (DynFlags -> Literal) -> RuleM CoreExpr @@ -385,8 +394,8 @@ wordOp2 op dflags (MachWord w1) (MachWord w2) = wordResult dflags (fromInteger w1 `op` fromInteger w2) wordOp2 _ _ _ _ = Nothing -- Could find LitLit -wordShiftRule :: (Integer -> Int -> Integer) -> RuleM CoreExpr - -- Shifts take an Int; hence second arg of op is Int +wordShiftRule :: (DynFlags -> Integer -> Int -> Integer) -> RuleM CoreExpr + -- Shifts take an Int; hence third arg of op is Int -- See Note [Guarding against silly shifts] wordShiftRule shift_op = do { dflags <- getDynFlags @@ -398,7 +407,8 @@ wordShiftRule shift_op -> return (mkRuntimeErrorApp rUNTIME_ERROR_ID wordPrimTy ("Bad shift length" ++ show shift_len)) Lit (MachWord x) - -> liftMaybe $ wordResult dflags (x `shift_op` fromInteger shift_len) + -> let op = shift_op dflags + in liftMaybe $ wordResult dflags (x `op` fromInteger shift_len) -- Do the shift at type Integer, but shift length is Int _ -> mzero } @@ -650,13 +660,13 @@ liftLitDynFlags f = do return $ Lit (f dflags lit) removeOp32 :: RuleM CoreExpr -#if WORD_SIZE_IN_BITS == 32 removeOp32 = do - [e] <- getArgs - return e -#else -removeOp32 = mzero -#endif + dflags <- getDynFlags + if wordSizeInBits dflags == 32 + then do + [e] <- getArgs + return e + else mzero getArgs :: RuleM [CoreExpr] getArgs = RuleM $ \_ _ args -> Just args From git at git.haskell.org Wed Nov 19 23:03:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 23:03:35 +0000 (UTC) Subject: [commit: ghc] master: add missing instances for Loc and a few missing Eq instances (b047733) Message-ID: <20141119230335.0FDFE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b047733881cfd4b1d83dd856697c797701ee282a/ghc >--------------------------------------------------------------- commit b047733881cfd4b1d83dd856697c797701ee282a Author: Luite Stegeman Date: Tue Nov 18 22:21:44 2014 -0600 add missing instances for Loc and a few missing Eq instances Summary: This adds a few missing instances that can be automatically derived Reviewers: hvr, goldfire, austin Reviewed By: goldfire, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D495 >--------------------------------------------------------------- b047733881cfd4b1d83dd856697c797701ee282a libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 9813095..8c95045 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -878,6 +878,7 @@ data Loc , loc_module :: String , loc_start :: CharPos , loc_end :: CharPos } + deriving( Show, Eq, Data, Typeable, Generic ) type CharPos = (Int, Int) -- ^ Line and character position @@ -952,13 +953,13 @@ data Info | TyVarI -- Scoped type variable Name Type -- What it is bound to - deriving( Show, Data, Typeable, Generic ) + deriving( Show, Eq, Data, Typeable, Generic ) -- | Obtained from 'reifyModule' in the 'Q' Monad. data ModuleInfo = -- | Contains the import list of the module. ModuleInfo [Module] - deriving( Show, Data, Typeable, Generic ) + deriving( Show, Eq, Data, Typeable, Generic ) {- | In 'ClassOpI' and 'DataConI', name of the parent class or type From git at git.haskell.org Wed Nov 19 23:03:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 23:03:37 +0000 (UTC) Subject: [commit: ghc] master: Only test for bug #9439 when llvm is installed (146dd13) Message-ID: <20141119230337.AF67A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/146dd138e2c3b4ec9b211dcbcedf752aeb79d3d1/ghc >--------------------------------------------------------------- commit 146dd138e2c3b4ec9b211dcbcedf752aeb79d3d1 Author: Thomas Miedema Date: Tue Nov 18 22:23:27 2014 -0600 Only test for bug #9439 when llvm is installed Reviewers: bgamari, austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D500 GHC Trac Issues: #9807 >--------------------------------------------------------------- 146dd138e2c3b4ec9b211dcbcedf752aeb79d3d1 configure.ac | 103 ++++++++++++++++++++++++++++++----------------------------- 1 file changed, 53 insertions(+), 50 deletions(-) diff --git a/configure.ac b/configure.ac index 7bd599f..5dd3aaa 100644 --- a/configure.ac +++ b/configure.ac @@ -187,56 +187,6 @@ AC_SUBST([WithGhc]) dnl ** Without optimization some INLINE trickery fails for GHCi SRC_CC_OPTS="-O" -dnl ** Bug 9439: Some GHC 7.8 releases had broken LLVM code generator. -dnl Unfortunately we don't know whether the user is going to request a -dnl build with the LLVM backend as this is only given in build.mk. -dnl -dnl Instead, we try to do as much work as possible here, checking -dnl whether -fllvm is the stage 0 compiler's default. If so we -dnl fail. If not, we check whether -fllvm is affected explicitly and -dnl if so set a flag. The build system will later check this flag -dnl after the desired build flags are known. -AC_MSG_CHECKING(whether bootstrap compiler is affected by bug 9439) -echo "main = putStrLn \"%function\"" > conftestghc.hs - -# Check whether LLVM backend is default for this platform -"${WithGhc}" conftestghc.hs 2>&1 >/dev/null -res=`./conftestghc` -if test "x$res" == "x%object" -then - AC_MSG_RESULT(yes) - echo "Buggy bootstrap compiler" - echo "" - echo "The stage 0 compiler $WithGhc is affected by GHC Bug \#9439" - echo "and therefore will miscompile the LLVM backend if -fllvm is" - echo "used." - echo - echo "Please use another bootstrap compiler" - exit 1 -fi - -# -fllvm is not the default, but set a flag so the Makefile can check -# -for it in the build flags later on -"${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null -if test $? == 0 -then - res=`./conftestghc` - if test "x$res" == "x%object" - then - AC_MSG_RESULT(yes) - GHC_LLVM_AFFECTED_BY_9439=1 - elif test "x$res" == "x%function" - then - AC_MSG_RESULT(no) - GHC_LLVM_AFFECTED_BY_9439=0 - else - AC_MSG_WARN(unexpected output $res) - fi -else - AC_MSG_RESULT(failed to compile, assuming no) -fi -AC_SUBST([GHC_LLVM_AFFECTED_BY_9439]) - dnl-------------------------------------------------------------------- dnl * Choose host(/target/build) platform dnl-------------------------------------------------------------------- @@ -593,6 +543,59 @@ dnl -------------------------------------------------------------- dnl * General configuration checks dnl -------------------------------------------------------------- +dnl ** Bug 9439: Some GHC 7.8 releases had broken LLVM code generator. +dnl Unfortunately we don't know whether the user is going to request a +dnl build with the LLVM backend as this is only given in build.mk. +dnl +dnl Instead, we try to do as much work as possible here, checking +dnl whether -fllvm is the stage 0 compiler's default. If so we +dnl fail. If not, we check whether -fllvm is affected explicitly and +dnl if so set a flag. The build system will later check this flag +dnl after the desired build flags are known. +if test -n "$LlcCmd" && test -n "$OptCmd" +then + AC_MSG_CHECKING(whether bootstrap compiler is affected by bug 9439) + echo "main = putStrLn \"%function\"" > conftestghc.hs + + # Check whether LLVM backend is default for this platform + "${WithGhc}" conftestghc.hs 2>&1 >/dev/null + res=`./conftestghc` + if test "x$res" == "x%object" + then + AC_MSG_RESULT(yes) + echo "Buggy bootstrap compiler" + echo "" + echo "The stage 0 compiler $WithGhc is affected by GHC Bug \#9439" + echo "and therefore will miscompile the LLVM backend if -fllvm is" + echo "used." + echo + echo "Please use another bootstrap compiler" + exit 1 + fi + + # -fllvm is not the default, but set a flag so the Makefile can check + # -for it in the build flags later on + "${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null + if test $? == 0 + then + res=`./conftestghc` + if test "x$res" == "x%object" + then + AC_MSG_RESULT(yes) + GHC_LLVM_AFFECTED_BY_9439=1 + elif test "x$res" == "x%function" + then + AC_MSG_RESULT(no) + GHC_LLVM_AFFECTED_BY_9439=0 + else + AC_MSG_WARN(unexpected output $res) + fi + else + AC_MSG_RESULT(failed to compile, assuming no) + fi +fi +AC_SUBST([GHC_LLVM_AFFECTED_BY_9439]) + dnl ** Can the unix package be built? dnl -------------------------------------------------------------- From git at git.haskell.org Wed Nov 19 23:03:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 23:03:41 +0000 (UTC) Subject: [commit: ghc] master: Allow -dead_strip linking on platforms with .subsections_via_symbols (53a4742) Message-ID: <20141119230341.5E8363A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/53a4742d037da2bfd00d1d34a8ea0d49d4cdb490/ghc >--------------------------------------------------------------- commit 53a4742d037da2bfd00d1d34a8ea0d49d4cdb490 Author: Moritz Angermann Date: Wed Nov 19 16:38:22 2014 -0600 Allow -dead_strip linking on platforms with .subsections_via_symbols Summary: This allows to link objects produced with the llvm code generator to be linked with -dead_strip. This applies to at least the iOS cross compiler and OS X compiler. Signed-off-by: Moritz Angermann Test Plan: Create a ffi library and link it with -dead_strip. If the resulting binary does not crash, the patch works as advertised. Reviewers: rwbarton, simonmar, hvr, dterei, mzero, ezyang, austin Reviewed By: dterei, ezyang, austin Subscribers: thomie, mzero, simonmar, ezyang, carter Differential Revision: https://phabricator.haskell.org/D206 >--------------------------------------------------------------- 53a4742d037da2bfd00d1d34a8ea0d49d4cdb490 compiler/NOTES | 16 ++++++++++++++++ compiler/llvmGen/LlvmCodeGen/Ppr.hs | 8 +++++++- compiler/nativeGen/PPC/Ppr.hs | 7 +------ compiler/nativeGen/SPARC/Ppr.hs | 7 +------ compiler/nativeGen/X86/Ppr.hs | 7 +------ .../should_compile => llvm/should_run}/Makefile | 0 .../llvm/should_run/subsections_via_symbols/Makefile | 13 +++++++++++++ .../subsections_via_symbols/SubsectionsViaSymbols.hs | 5 +++++ .../tests/llvm/should_run/subsections_via_symbols/all.T | 15 +++++++++++++++ .../subsections_via_symbols-libtool-quiet | 4 ++++ .../subsections_via_symbols/subsections_via_symbols.m | 11 +++++++++++ .../subsections_via_symbols.stderr | 0 .../subsections_via_symbols.stdout | 2 ++ 13 files changed, 76 insertions(+), 19 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 53a4742d037da2bfd00d1d34a8ea0d49d4cdb490 From git at git.haskell.org Wed Nov 19 23:05:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 23:05:57 +0000 (UTC) Subject: [commit: ghc] branch 'wip/merge' deleted Message-ID: <20141119230557.BFCA23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/merge From git at git.haskell.org Wed Nov 19 23:09:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Nov 2014 23:09:45 +0000 (UTC) Subject: [commit: ghc] master: compiler/main: fixes #9776 (80f6fc1) Message-ID: <20141119230945.CE5103A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/80f6fc1769296330687d54179a6dc149f02d6348/ghc >--------------------------------------------------------------- commit 80f6fc1769296330687d54179a6dc149f02d6348 Author: Carlos Tom? Date: Wed Nov 19 17:07:53 2014 -0600 compiler/main: fixes #9776 Test Plan: test T9776 under tests/driver Reviewers: jstolarek, austin Reviewed By: jstolarek, austin Subscribers: jstolarek, thomie, carter Differential Revision: https://phabricator.haskell.org/D503 GHC Trac Issues: #9776 >--------------------------------------------------------------- 80f6fc1769296330687d54179a6dc149f02d6348 compiler/main/CmdLineParser.hs | 3 ++- testsuite/tests/driver/T9776.hs | 1 + testsuite/tests/driver/T9776.stderr | 2 ++ testsuite/tests/driver/all.T | 3 +++ 4 files changed, 8 insertions(+), 1 deletion(-) diff --git a/compiler/main/CmdLineParser.hs b/compiler/main/CmdLineParser.hs index 7d7bbfe..a4b9118 100644 --- a/compiler/main/CmdLineParser.hs +++ b/compiler/main/CmdLineParser.hs @@ -191,8 +191,9 @@ processOneArg opt_kind rest arg args [] -> missingArgErr dash_arg (L _ arg1:args1) -> Right (f arg1, args1) + -- See Trac #9776 SepArg f -> case args of - [] -> unknownFlagErr dash_arg + [] -> missingArgErr dash_arg (L _ arg1:args1) -> Right (f arg1, args1) Prefix f | notNull rest_no_eq -> Right (f rest_no_eq, args) diff --git a/testsuite/tests/driver/T9776.hs b/testsuite/tests/driver/T9776.hs new file mode 100644 index 0000000..28551cf --- /dev/null +++ b/testsuite/tests/driver/T9776.hs @@ -0,0 +1 @@ +module T9776 where diff --git a/testsuite/tests/driver/T9776.stderr b/testsuite/tests/driver/T9776.stderr new file mode 100644 index 0000000..328a105 --- /dev/null +++ b/testsuite/tests/driver/T9776.stderr @@ -0,0 +1,2 @@ +ghc-stage2: on the commandline: missing argument for flag: -frule-check +Usage: For basic information, try the `--help' option. diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T index 7236ec1..f2c58d1 100644 --- a/testsuite/tests/driver/all.T +++ b/testsuite/tests/driver/all.T @@ -406,3 +406,6 @@ test('T9050', normal, build_T9050, []) test('write_interface_oneshot', normal, run_command, ['$MAKE -s --no-print-directory write_interface_oneshot']) test('write_interface_make', normal, run_command, ['$MAKE -s --no-print-directory write_interface_make']) + +test('T9776', normal, compile_fail, ['-frule-check']) + From git at git.haskell.org Thu Nov 20 00:35:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 00:35:59 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Revert "Revert "Revert "rts/base: Fix #9423"" and resolve issue that caused the revert." (b699fd9) Message-ID: <20141120003559.CD39B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/b699fd9abed956af2a785fe653cb9cf8423a8e1c/ghc >--------------------------------------------------------------- commit b699fd9abed956af2a785fe653cb9cf8423a8e1c Author: Austin Seipp Date: Wed Nov 19 17:27:54 2014 -0600 Revert "Revert "Revert "rts/base: Fix #9423"" and resolve issue that caused the revert." This reverts commit 55d2522bd0c48e4c5dac1526cdf53459270baf96. Signed-off-by: Austin Seipp >--------------------------------------------------------------- b699fd9abed956af2a785fe653cb9cf8423a8e1c includes/rts/IOManager.h | 3 +- rts/Capability.c | 19 ----------- rts/Capability.h | 4 --- rts/Linker.c | 1 - rts/posix/Signals.c | 86 +++++++++++++++++++----------------------------- 5 files changed, 34 insertions(+), 79 deletions(-) diff --git a/includes/rts/IOManager.h b/includes/rts/IOManager.h index 7bf2cdf..1c331b9 100644 --- a/includes/rts/IOManager.h +++ b/includes/rts/IOManager.h @@ -26,8 +26,7 @@ void sendIOManagerEvent (HsWord32 event); #else -void setIOManagerControlFd (nat cap_no, int fd); -void setTimerManagerControlFd(int fd); +void setIOManagerControlFd (int fd); void setIOManagerWakeupFd (int fd); #endif diff --git a/rts/Capability.c b/rts/Capability.c index 87c5950..16b71b7 100644 --- a/rts/Capability.c +++ b/rts/Capability.c @@ -27,10 +27,6 @@ #include "STM.h" #include "RtsUtils.h" -#if !defined(mingw32_HOST_OS) -#include "rts/IOManager.h" // for setIOManagerControlFd() -#endif - #include // one global capability, this is the Capability for non-threaded @@ -259,9 +255,6 @@ initCapability( Capability *cap, nat i ) cap->spark_stats.converted = 0; cap->spark_stats.gcd = 0; cap->spark_stats.fizzled = 0; -#if !defined(mingw32_HOST_OS) - cap->io_manager_control_wr_fd = -1; -#endif #endif cap->total_allocated = 0; @@ -1080,15 +1073,3 @@ rtsBool checkSparkCountInvariant (void) } #endif - -#if !defined(mingw32_HOST_OS) -void setIOManagerControlFd(nat cap_no USED_IF_THREADS, int fd USED_IF_THREADS) { -#if defined(THREADED_RTS) - if (cap_no < n_capabilities) { - capabilities[cap_no]->io_manager_control_wr_fd = fd; - } else { - errorBelch("warning: setIOManagerControlFd called with illegal capability number."); - } -#endif -} -#endif diff --git a/rts/Capability.h b/rts/Capability.h index fc2bdb0..f342d92 100644 --- a/rts/Capability.h +++ b/rts/Capability.h @@ -121,10 +121,6 @@ struct Capability_ { // Stats on spark creation/conversion SparkCounters spark_stats; -#if !defined(mingw32_HOST_OS) - // IO manager for this cap - int io_manager_control_wr_fd; -#endif #endif // Total words allocated by this cap since rts start W_ total_allocated; diff --git a/rts/Linker.c b/rts/Linker.c index 124f6cc..ceb6a4f 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -858,7 +858,6 @@ typedef struct _RtsSymbolVal { #if !defined(mingw32_HOST_OS) #define RTS_USER_SIGNALS_SYMBOLS \ SymI_HasProto(setIOManagerControlFd) \ - SymI_HasProto(setTimerManagerControlFd) \ SymI_HasProto(setIOManagerWakeupFd) \ SymI_HasProto(ioManagerWakeup) \ SymI_HasProto(blockUserSignals) \ diff --git a/rts/posix/Signals.c b/rts/posix/Signals.c index a6978e6..f4a8341 100644 --- a/rts/posix/Signals.c +++ b/rts/posix/Signals.c @@ -124,16 +124,12 @@ more_handlers(int sig) // Here's the pipe into which we will send our signals static int io_manager_wakeup_fd = -1; -static int timer_manager_control_wr_fd = -1; +static int io_manager_control_fd = -1; #define IO_MANAGER_WAKEUP 0xff #define IO_MANAGER_DIE 0xfe #define IO_MANAGER_SYNC 0xfd -void setTimerManagerControlFd(int fd) { - timer_manager_control_wr_fd = fd; -} - void setIOManagerWakeupFd (int fd) { @@ -142,9 +138,14 @@ setIOManagerWakeupFd (int fd) io_manager_wakeup_fd = fd; } -/* ----------------------------------------------------------------------------- - * Wake up at least one IO or timer manager HS thread. - * -------------------------------------------------------------------------- */ +void +setIOManagerControlFd (int fd) +{ + // only called when THREADED_RTS, but unconditionally + // compiled here because GHC.Event.Control depends on it. + io_manager_control_fd = fd; +} + void ioManagerWakeup (void) { @@ -166,24 +167,14 @@ ioManagerWakeup (void) void ioManagerDie (void) { - StgWord8 byte = (StgWord8)IO_MANAGER_DIE; - nat i; - int fd; int r; - - if (0 <= timer_manager_control_wr_fd) { - r = write(timer_manager_control_wr_fd, &byte, 1); + // Ask the IO Manager thread to exit + if (io_manager_control_fd >= 0) { + StgWord8 byte = (StgWord8)IO_MANAGER_DIE; + r = write(io_manager_control_fd, &byte, 1); if (r == -1) { sysErrorBelch("ioManagerDie: write"); } - timer_manager_control_wr_fd = -1; - } - - for (i=0; i < n_capabilities; i++) { - fd = capabilities[i]->io_manager_control_wr_fd; - if (0 <= fd) { - r = write(fd, &byte, 1); - if (r == -1) { sysErrorBelch("ioManagerDie: write"); } - capabilities[i]->io_manager_control_wr_fd = -1; - } + io_manager_control_fd = -1; + io_manager_wakeup_fd = -1; } } @@ -198,10 +189,10 @@ ioManagerStart (void) { // Make sure the IO manager thread is running Capability *cap; - if (timer_manager_control_wr_fd < 0 || io_manager_wakeup_fd < 0) { - cap = rts_lock(); + if (io_manager_control_fd < 0 || io_manager_wakeup_fd < 0) { + cap = rts_lock(); ioManagerStartCap(&cap); - rts_unlock(cap); + rts_unlock(cap); } } #endif @@ -229,37 +220,26 @@ generic_handler(int sig USED_IF_THREADS, { #if defined(THREADED_RTS) - StgWord8 buf[sizeof(siginfo_t) + 1]; - int r; + if (io_manager_control_fd != -1) + { + StgWord8 buf[sizeof(siginfo_t) + 1]; + int r; - buf[0] = sig; - if (info == NULL) { - // info may be NULL on Solaris (see #3790) - memset(buf+1, 0, sizeof(siginfo_t)); - } else { - memcpy(buf+1, info, sizeof(siginfo_t)); - } + buf[0] = sig; - if (0 <= timer_manager_control_wr_fd) - { - r = write(timer_manager_control_wr_fd, buf, sizeof(siginfo_t)+1); - if (r == -1 && errno == EAGAIN) { - errorBelch("lost signal due to full pipe: %d\n", sig); - } - } + if (info == NULL) { + // info may be NULL on Solaris (see #3790) + memset(buf+1, 0, sizeof(siginfo_t)); + } else { + memcpy(buf+1, info, sizeof(siginfo_t)); + } - nat i; - int fd; - for (i=0; i < n_capabilities; i++) { - fd = capabilities[i]->io_manager_control_wr_fd; - if (0 <= fd) { - r = write(fd, buf, sizeof(siginfo_t)+1); - if (r == -1 && errno == EAGAIN) { - errorBelch("lost signal due to full pipe: %d\n", sig); - } + r = write(io_manager_control_fd, buf, sizeof(siginfo_t)+1); + if (r == -1 && errno == EAGAIN) + { + errorBelch("lost signal due to full pipe: %d\n", sig); } } - // If the IO manager hasn't told us what the FD of the write end // of its pipe is, there's not much we can do here, so just ignore // the signal.. From git at git.haskell.org Thu Nov 20 00:36:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 00:36:11 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: Revert "Fix base component of #9423" (bfdf6bf) Message-ID: <20141120003611.800A83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/bfdf6bf8f9487aae76cd939c00e6313cd68c208a/base >--------------------------------------------------------------- commit bfdf6bf8f9487aae76cd939c00e6313cd68c208a Author: Austin Seipp Date: Wed Nov 19 17:28:09 2014 -0600 Revert "Fix base component of #9423" This reverts commit fb2cbec8ff8eb21690345aa5673c1936bf560fca. Signed-off-by: Austin Seipp >--------------------------------------------------------------- bfdf6bf8f9487aae76cd939c00e6313cd68c208a GHC/Event/Control.hs | 8 ++++++-- GHC/Event/Manager.hs | 1 - GHC/Event/Thread.hs | 35 ++++++++++++++--------------------- GHC/Event/TimerManager.hs | 1 - 4 files changed, 20 insertions(+), 25 deletions(-) diff --git a/GHC/Event/Control.hs b/GHC/Event/Control.hs index 53a9bc8..2951a6a 100644 --- a/GHC/Event/Control.hs +++ b/GHC/Event/Control.hs @@ -17,7 +17,6 @@ module GHC.Event.Control , readControlMessage -- *** File descriptors , controlReadFd - , controlWriteFd , wakeupReadFd -- ** Control message sending , sendWakeup @@ -92,6 +91,7 @@ newControl shouldRegister = allocaArray 2 $ \fds -> do setCloseOnExec wr return (rd, wr) (ctrl_rd, ctrl_wr) <- createPipe + when shouldRegister $ c_setIOManagerControlFd ctrl_wr #if defined(HAVE_EVENTFD) ev <- throwErrnoIfMinus1 "eventfd" $ c_eventfd 0 0 setNonBlockingFD ev True @@ -200,5 +200,9 @@ foreign import ccall unsafe "sys/eventfd.h eventfd_write" c_eventfd_write :: CInt -> CULLong -> IO CInt #endif -foreign import ccall unsafe "setIOManagerWakeupFd" +-- Used to tell the RTS how it can send messages to the I/O manager. +foreign import ccall "setIOManagerControlFd" + c_setIOManagerControlFd :: CInt -> IO () + +foreign import ccall "setIOManagerWakeupFd" c_setIOManagerWakeupFd :: CInt -> IO () diff --git a/GHC/Event/Manager.hs b/GHC/Event/Manager.hs index e474dc3..14f7098 100644 --- a/GHC/Event/Manager.hs +++ b/GHC/Event/Manager.hs @@ -27,7 +27,6 @@ module GHC.Event.Manager -- * State , callbackTableVar - , emControl -- * Registering interest in I/O events , Event diff --git a/GHC/Event/Thread.hs b/GHC/Event/Thread.hs index c054742..c599047 100644 --- a/GHC/Event/Thread.hs +++ b/GHC/Event/Thread.hs @@ -21,7 +21,6 @@ import Data.List (zipWith3) import Data.Maybe (Maybe(..)) import Data.Tuple (snd) import Foreign.C.Error (eBADF, errnoToIOError) -import Foreign.C.Types (CInt(..), CUInt(..)) import Foreign.Ptr (Ptr) import GHC.Base import GHC.Conc.Sync (TVar, ThreadId, ThreadStatus(..), atomically, forkIO, @@ -33,14 +32,12 @@ import GHC.IO.Exception (ioError) import GHC.IOArray (IOArray, newIOArray, readIOArray, writeIOArray, boundsIOArray) import GHC.MVar (MVar, newEmptyMVar, newMVar, putMVar, takeMVar) -import GHC.Event.Control (controlWriteFd) import GHC.Event.Internal (eventIs, evtClose) import GHC.Event.Manager (Event, EventManager, evtRead, evtWrite, loop, new, registerFd, unregisterFd_) import qualified GHC.Event.Manager as M import qualified GHC.Event.TimerManager as TM import GHC.Num ((-), (+)) -import GHC.Real (fromIntegral) import System.IO.Unsafe (unsafePerformIO) import System.Posix.Types (Fd) @@ -256,11 +253,7 @@ startIOManagerThread :: IOArray Int (Maybe (ThreadId, EventManager)) startIOManagerThread eventManagerArray i = do let create = do !mgr <- new True - !t <- forkOn i $ do - c_setIOManagerControlFd - (fromIntegral i) - (fromIntegral $ controlWriteFd $ M.emControl mgr) - loop mgr + !t <- forkOn i $ loop mgr labelThread t "IOManager" writeIOArray eventManagerArray i (Just (t,mgr)) old <- readIOArray eventManagerArray i @@ -276,7 +269,6 @@ startIOManagerThread eventManagerArray i = do -- the fork, for example. In this case we should clean up -- open pipes and everything else related to the event manager. -- See #4449 - c_setIOManagerControlFd (fromIntegral i) (-1) M.cleanup em create _other -> return () @@ -285,10 +277,8 @@ startTimerManagerThread :: IO () startTimerManagerThread = modifyMVar_ timerManagerThreadVar $ \old -> do let create = do !mgr <- TM.new - c_setTimerManagerControlFd - (fromIntegral $ controlWriteFd $ TM.emControl mgr) writeIORef timerManager $ Just mgr - !t <- forkIO $ TM.loop mgr + !t <- forkIO $ TM.loop mgr `finally` shutdownManagers labelThread t "TimerManager" return $ Just t case old of @@ -306,11 +296,21 @@ startTimerManagerThread = modifyMVar_ timerManagerThreadVar $ \old -> do mem <- readIORef timerManager _ <- case mem of Nothing -> return () - Just em -> do c_setTimerManagerControlFd (-1) - TM.cleanup em + Just em -> TM.cleanup em create _other -> return st +shutdownManagers :: IO () +shutdownManagers = + withMVar ioManagerLock $ \_ -> do + eventManagerArray <- readIORef eventManager + let (_, high) = boundsIOArray eventManagerArray + forM_ [0..high] $ \i -> do + mmgr <- readIOArray eventManagerArray i + case mmgr of + Nothing -> return () + Just (_,mgr) -> M.shutdown mgr + foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool ioManagerCapabilitiesChanged :: IO () @@ -344,10 +344,3 @@ ioManagerCapabilitiesChanged = do Just (_,mgr) <- readIOArray eventManagerArray i tid <- restartPollLoop mgr i writeIOArray eventManagerArray i (Just (tid,mgr)) - --- Used to tell the RTS how it can send messages to the I/O manager. -foreign import ccall unsafe "setIOManagerControlFd" - c_setIOManagerControlFd :: CUInt -> CInt -> IO () - -foreign import ccall unsafe "setTimerManagerControlFd" - c_setTimerManagerControlFd :: CInt -> IO () diff --git a/GHC/Event/TimerManager.hs b/GHC/Event/TimerManager.hs index d8498aa..e52f1a0 100644 --- a/GHC/Event/TimerManager.hs +++ b/GHC/Event/TimerManager.hs @@ -15,7 +15,6 @@ module GHC.Event.TimerManager , new , newWith , newDefaultBackend - , emControl -- * Running , finished From git at git.haskell.org Thu Nov 20 00:36:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 00:36:13 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: Update version to 4.7.0.2 (105a74c) Message-ID: <20141120003613.8A0753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/105a74cda3537caab297070491e4252872438a86/base >--------------------------------------------------------------- commit 105a74cda3537caab297070491e4252872438a86 Author: Austin Seipp Date: Wed Nov 19 17:28:50 2014 -0600 Update version to 4.7.0.2 Signed-off-by: Austin Seipp >--------------------------------------------------------------- 105a74cda3537caab297070491e4252872438a86 base.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/base.cabal b/base.cabal index 8aa8cf7..3a1234e 100644 --- a/base.cabal +++ b/base.cabal @@ -1,5 +1,5 @@ name: base -version: 4.7.0.1 +version: 4.7.0.2 -- GHC 7.6.3 released with 4.7.0.0 license: BSD3 license-file: LICENSE From git at git.haskell.org Thu Nov 20 01:49:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 01:49:42 +0000 (UTC) Subject: [commit: ghc] master: arm64: 64bit iOS and SMP support (#7942) (d87fa34) Message-ID: <20141120014942.927243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d87fa343cd5d298c9fea96d65d05a20929ff97d0/ghc >--------------------------------------------------------------- commit d87fa343cd5d298c9fea96d65d05a20929ff97d0 Author: Luke Iannini Date: Wed Nov 19 17:23:35 2014 -0600 arm64: 64bit iOS and SMP support (#7942) Signed-off-by: Austin Seipp >--------------------------------------------------------------- d87fa343cd5d298c9fea96d65d05a20929ff97d0 aclocal.m4 | 4 +- compiler/cmm/PprC.hs | 1 + compiler/codeGen/CodeGen/Platform.hs | 6 ++ .../CodeGen/Platform/{SPARC.hs => ARM64.hs} | 4 +- compiler/ghc.cabal.in | 1 + compiler/ghc.mk | 1 + compiler/llvmGen/Llvm/PpLlvm.hs | 2 +- compiler/llvmGen/LlvmCodeGen/Ppr.hs | 3 + compiler/main/DriverPipeline.hs | 1 + compiler/utils/Platform.hs | 1 + includes/CodeGen.Platform.hs | 79 +++++++++++++++++++++- includes/stg/MachRegs.h | 2 + includes/stg/RtsMachRegs.h | 1 + includes/stg/SMP.h | 37 +++++++++- rts/StgCRun.c | 32 ++++++--- rts/posix/OSMem.c | 2 +- rts/sm/Storage.c | 4 +- 17 files changed, 160 insertions(+), 21 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d87fa343cd5d298c9fea96d65d05a20929ff97d0 From git at git.haskell.org Thu Nov 20 01:49:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 01:49:45 +0000 (UTC) Subject: [commit: ghc] master: ghc generates more user-friendly error messages (bc2289e) Message-ID: <20141120014945.5594E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bc2289e13d9586be087bd8136943dc35a0130c88/ghc >--------------------------------------------------------------- commit bc2289e13d9586be087bd8136943dc35a0130c88 Author: Mike Izbicki Date: Wed Nov 19 18:29:37 2014 -0600 ghc generates more user-friendly error messages Test Plan: Compiled ghc fine. Opened ghci and fed it invalid code. It gave the improved error messages in response. Reviewers: austin Subscribers: thomie, simonpj, spacekitteh, rwbarton, simonmar, carter Differential Revision: https://phabricator.haskell.org/D201 >--------------------------------------------------------------- bc2289e13d9586be087bd8136943dc35a0130c88 compiler/parser/Lexer.x | 2 ++ compiler/parser/Parser.y | 39 ++++++++++++++++++++++ compiler/typecheck/TcErrors.lhs | 14 +++++++- .../tests/annotations/should_fail/annfail08.stderr | 5 ++- .../tests/deriving/should_fail/drvfail007.stderr | 1 + .../tests/ghci.debugger/scripts/break003.stderr | 4 ++- testsuite/tests/ghci/scripts/Defer02.stderr | 8 +++-- testsuite/tests/mdo/should_fail/mdofail005.stderr | 4 ++- .../parser/should_fail/ParserNoLambdaCase.stderr | 2 +- .../tests/parser/should_fail/readFail020.stderr | 3 +- .../tests/parser/should_fail/readFail040.stderr | 4 ++- testsuite/tests/rebindable/rebindable6.stderr | 3 ++ .../tests/typecheck/should_fail/T2846b.stderr | 4 ++- 13 files changed, 83 insertions(+), 10 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc bc2289e13d9586be087bd8136943dc35a0130c88 From git at git.haskell.org Thu Nov 20 01:49:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 01:49:48 +0000 (UTC) Subject: [commit: ghc] master: Make calling conventions in template haskell Syntax.hs consistent with those in ghc ForeignCall.hs this impliments #9703 from ghc trac (c6e12e6) Message-ID: <20141120014948.91CBC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c6e12e69fa348328d58540a1ea8abed35d0dda32/ghc >--------------------------------------------------------------- commit c6e12e69fa348328d58540a1ea8abed35d0dda32 Author: Luite Stegeman Date: Wed Nov 19 18:38:58 2014 -0600 Make calling conventions in template haskell Syntax.hs consistent with those in ghc ForeignCall.hs this impliments #9703 from ghc trac Test Plan: still needs tests Reviewers: cmsaperstein, ekmett, goldfire, austin Reviewed By: goldfire, austin Subscribers: goldfire, thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D353 GHC Trac Issues: #9703 >--------------------------------------------------------------- c6e12e69fa348328d58540a1ea8abed35d0dda32 compiler/deSugar/DsMeta.hs | 57 +++++++++++++--------- compiler/hsSyn/Convert.lhs | 7 ++- compiler/prelude/ForeignCall.lhs | 1 + libraries/template-haskell/Language/Haskell/TH.hs | 3 +- .../template-haskell/Language/Haskell/TH/Lib.hs | 9 ++-- .../template-haskell/Language/Haskell/TH/Syntax.hs | 3 +- testsuite/tests/th/TH_foreignCallingConventions.hs | 24 +++++++++ .../tests/th/TH_foreignCallingConventions.stderr | 30 ++++++++++++ testsuite/tests/th/all.T | 3 ++ 9 files changed, 106 insertions(+), 31 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c6e12e69fa348328d58540a1ea8abed35d0dda32 From git at git.haskell.org Thu Nov 20 09:44:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 09:44:12 +0000 (UTC) Subject: [commit: ghc] master: Make Data.Functor.Identity trustworthy again (8cbd25a) Message-ID: <20141120094412.391663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8cbd25a49051171da7c73db57ebd87bb0296c2f7/ghc >--------------------------------------------------------------- commit 8cbd25a49051171da7c73db57ebd87bb0296c2f7 Author: Herbert Valerio Riedel Date: Thu Nov 20 09:53:46 2014 +0100 Make Data.Functor.Identity trustworthy again Alas `{-# LANGUAGE Safe #-}` can't be used since `Data.Coerce` isn't "safe". However, we use `coerce` just as an optimisation (see also 4ba884bdd3a9521ea92fcda8f601a7d0f3537bc1 which broke the safe-inferred status of `Data.Functor.Identity`), so this module at least deserves `{-# LANGUAGE Trustworthy #-}`. NOTE: `Data.Functor.Identity` was added to `base` in the context of #9664 Reviewed By: luite Differential Revision: https://phabricator.haskell.org/D507 >--------------------------------------------------------------- 8cbd25a49051171da7c73db57ebd87bb0296c2f7 libraries/base/Data/Functor/Identity.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/libraries/base/Data/Functor/Identity.hs b/libraries/base/Data/Functor/Identity.hs index de7f19a..909de85 100644 --- a/libraries/base/Data/Functor/Identity.hs +++ b/libraries/base/Data/Functor/Identity.hs @@ -1,5 +1,6 @@ {-# LANGUAGE AutoDeriveTypeable #-} {-# LANGUAGE DeriveTraversable #-} +{-# LANGUAGE Trustworthy #-} ----------------------------------------------------------------------------- -- | From git at git.haskell.org Thu Nov 20 10:29:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 10:29:37 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Update shift/reduce conflict number in parser (3b81309) Message-ID: <20141120102937.7CDC03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/3b81309c057fc216afa053d195aaa85ee3a1ba9e/ghc >--------------------------------------------------------------- commit 3b81309c057fc216afa053d195aaa85ee3a1ba9e Author: Dr. ERDI Gergo Date: Thu Nov 20 18:21:30 2014 +0800 Update shift/reduce conflict number in parser >--------------------------------------------------------------- 3b81309c057fc216afa053d195aaa85ee3a1ba9e compiler/parser/Parser.y | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index b6db3a8..6f6422f 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -86,6 +86,18 @@ import TysWiredIn ( unitTyCon, unitDataCon, tupleTyCon, tupleCon, nilDataC {- ----------------------------------------------------------------------------- +20 Nov 2014 + +Conflicts: 60 shift/reduce + 12 reduce/reduce + +----------------------------------------------------------------------------- +25 June 2014 + +Conflicts: 47 shift/reduce + 1 reduce/reduce + +----------------------------------------------------------------------------- 12 October 2012 Conflicts: 43 shift/reduce From git at git.haskell.org Thu Nov 20 10:29:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 10:29:40 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add support for pattern synonym type signatures. Syntax is of the form (d4530b6) Message-ID: <20141120102940.D5AE73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/d4530b69ff9518a091cc1aabb2b75f2e9d5b275c/ghc >--------------------------------------------------------------- commit d4530b69ff9518a091cc1aabb2b75f2e9d5b275c Author: Dr. ERDI Gergo Date: Fri Nov 7 19:29:06 2014 +0800 Add support for pattern synonym type signatures. Syntax is of the form pattern P :: (Prov b) => (Req a) => a -> b -> Int -> T a which declares a pattern synonym called `P`, with argument types `a`, `b`, and `Int`, and result type `T a`, with provided context `(Prov b)` and required context `(Req a)`. >--------------------------------------------------------------- d4530b69ff9518a091cc1aabb2b75f2e9d5b275c compiler/hsSyn/HsBinds.lhs | 51 +++--- compiler/hsSyn/HsTypes.lhs | 16 +- compiler/iface/IfaceSyn.lhs | 25 ++- compiler/iface/IfaceType.lhs | 15 +- compiler/parser/Parser.y | 51 ++++-- compiler/parser/RdrHsSyn.hs | 27 +-- compiler/rename/RnBinds.lhs | 42 +++-- compiler/typecheck/TcBinds.lhs | 50 +++++- compiler/typecheck/TcClassDcl.lhs | 4 +- compiler/typecheck/TcPat.lhs | 23 ++- compiler/typecheck/TcPatSyn.lhs | 195 +++++++++++++++------ compiler/typecheck/TcPatSyn.lhs-boot | 9 +- docs/users_guide/glasgow_exts.xml | 15 +- testsuite/tests/ghci/scripts/T8776.stdout | 2 +- .../patsyn/should_compile/{bidir.hs => T8584-1.hs} | 3 +- testsuite/tests/patsyn/should_compile/T8584-2.hs | 8 + testsuite/tests/patsyn/should_compile/T8584-3.hs | 8 + testsuite/tests/patsyn/should_compile/T8968-1.hs | 8 + testsuite/tests/patsyn/should_compile/T8968-2.hs | 8 + testsuite/tests/patsyn/should_compile/T8968-3.hs | 11 ++ testsuite/tests/patsyn/should_compile/all.T | 6 + utils/haddock | 2 +- 22 files changed, 397 insertions(+), 182 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d4530b69ff9518a091cc1aabb2b75f2e9d5b275c From git at git.haskell.org Thu Nov 20 10:29:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 10:29:43 +0000 (UTC) Subject: [commit: ghc] wip/T8584's head updated: Add support for pattern synonym type signatures. Syntax is of the form (d4530b6) Message-ID: <20141120102943.215B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T8584' now includes: 4ba884b Optimise `Identity` instances with `coerce` 8e0a480 rts: remove old-style field designator extension (#9396) 101c62e The test runner now also works under the msys-native Python. 6fc78fd Refactor: use System.FilePath.splitSearchPath 66c0513 Update documentation for "Batch compiler mode" 00c1a30 Implement new Foldable methods for HsPatSynDetails 5db61ea Turn CoreWriter into a newtype; fix comment 5c09893 Add remaining s and comments to .mailmap 7ef0971 Filter input to abiHash early b3df5f6 template-haskell: Missing instances for Rational and (). b047733 add missing instances for Loc and a few missing Eq instances 146dd13 Only test for bug #9439 when llvm is installed 53a4742 Allow -dead_strip linking on platforms with .subsections_via_symbols 33c029f make TcRnMonad.lhs respect -ddump-to-file 4dd87c5 use correct word size for shiftRightLogical and removeOp32 80f6fc1 compiler/main: fixes #9776 d87fa34 arm64: 64bit iOS and SMP support (#7942) bc2289e ghc generates more user-friendly error messages c6e12e6 Make calling conventions in template haskell Syntax.hs consistent with those in ghc ForeignCall.hs this impliments #9703 from ghc trac 8cbd25a Make Data.Functor.Identity trustworthy again 3b81309 Update shift/reduce conflict number in parser d4530b6 Add support for pattern synonym type signatures. Syntax is of the form From git at git.haskell.org Thu Nov 20 14:41:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 14:41:24 +0000 (UTC) Subject: [commit: ghc] master: Add support for pattern synonym type signatures. Syntax is of the form (cce6318) Message-ID: <20141120144124.6B0863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cce6318e8fdb086a8501a0c81ae1ee02eed67835/ghc >--------------------------------------------------------------- commit cce6318e8fdb086a8501a0c81ae1ee02eed67835 Author: Dr. ERDI Gergo Date: Thu Nov 20 22:38:11 2014 +0800 Add support for pattern synonym type signatures. Syntax is of the form pattern P :: (Prov b) => (Req a) => a -> b -> Int -> T a which declares a pattern synonym called `P`, with argument types `a`, `b`, and `Int`, and result type `T a`, with provided context `(Prov b)` and required context `(Req a)`. The Haddock submodule is also updated to use this new syntax in generated docs. >--------------------------------------------------------------- cce6318e8fdb086a8501a0c81ae1ee02eed67835 compiler/hsSyn/HsBinds.lhs | 51 +++--- compiler/hsSyn/HsTypes.lhs | 16 +- compiler/iface/IfaceSyn.lhs | 25 ++- compiler/iface/IfaceType.lhs | 15 +- compiler/parser/Parser.y | 51 ++++-- compiler/parser/RdrHsSyn.hs | 27 +-- compiler/rename/RnBinds.lhs | 42 +++-- compiler/typecheck/TcBinds.lhs | 50 +++++- compiler/typecheck/TcClassDcl.lhs | 4 +- compiler/typecheck/TcPat.lhs | 23 ++- compiler/typecheck/TcPatSyn.lhs | 195 +++++++++++++++------ compiler/typecheck/TcPatSyn.lhs-boot | 9 +- docs/users_guide/glasgow_exts.xml | 15 +- testsuite/tests/ghci/scripts/T8776.stdout | 2 +- .../patsyn/should_compile/{bidir.hs => T8584-1.hs} | 3 +- testsuite/tests/patsyn/should_compile/T8584-2.hs | 8 + testsuite/tests/patsyn/should_compile/T8584-3.hs | 8 + testsuite/tests/patsyn/should_compile/T8968-1.hs | 8 + testsuite/tests/patsyn/should_compile/T8968-2.hs | 8 + testsuite/tests/patsyn/should_compile/T8968-3.hs | 11 ++ testsuite/tests/patsyn/should_compile/all.T | 6 + utils/haddock | 2 +- 22 files changed, 397 insertions(+), 182 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc cce6318e8fdb086a8501a0c81ae1ee02eed67835 From git at git.haskell.org Thu Nov 20 14:41:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 14:41:26 +0000 (UTC) Subject: [commit: ghc] master's head updated: Add support for pattern synonym type signatures. Syntax is of the form (cce6318) Message-ID: <20141120144126.79D073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: 3b81309 Update shift/reduce conflict number in parser cce6318 Add support for pattern synonym type signatures. Syntax is of the form From git at git.haskell.org Thu Nov 20 17:18:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 17:18:19 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Remove release notes for IO manager bug (8c939b0) Message-ID: <20141120171819.A82193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/8c939b026d34d6454c7b1ebd1587fe6dc54a3d46/ghc >--------------------------------------------------------------- commit 8c939b026d34d6454c7b1ebd1587fe6dc54a3d46 Author: Austin Seipp Date: Thu Nov 20 11:18:55 2014 -0600 Remove release notes for IO manager bug Signed-off-by: Austin Seipp >--------------------------------------------------------------- 8c939b026d34d6454c7b1ebd1587fe6dc54a3d46 docs/users_guide/7.8.4-notes.xml | 7 ------- 1 file changed, 7 deletions(-) diff --git a/docs/users_guide/7.8.4-notes.xml b/docs/users_guide/7.8.4-notes.xml index f6fd304..27e7ee8 100644 --- a/docs/users_guide/7.8.4-notes.xml +++ b/docs/users_guide/7.8.4-notes.xml @@ -98,13 +98,6 @@ type family applications has been fixed (issue #9433). - - - A bug in the IO manager that could cause deadlocks in - combination with forkProcess has been - fixed (issues #9377 and #9284). - - From git at git.haskell.org Thu Nov 20 17:31:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 17:31:09 +0000 (UTC) Subject: [commit: ghc] master: Implement typechecker plugins (64cb496) Message-ID: <20141120173109.621BF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/64cb49686457c233d0f58e5cfa324ad28a5453a3/ghc >--------------------------------------------------------------- commit 64cb49686457c233d0f58e5cfa324ad28a5453a3 Author: Adam Gundry Date: Thu Nov 20 13:32:26 2014 +0000 Implement typechecker plugins Summary: See https://ghc.haskell.org/trac/ghc/wiki/Plugins/TypeChecker This is based on work by Iavor Diatchki and Eric Seidel. Test Plan: validate Reviewers: simonpj, austin Reviewed By: austin Subscribers: gridaphobe, yav, thomie, carter Differential Revision: https://phabricator.haskell.org/D489 Conflicts: docs/users_guide/7.10.1-notes.xml >--------------------------------------------------------------- 64cb49686457c233d0f58e5cfa324ad28a5453a3 compiler/ghc.cabal.in | 2 + compiler/main/DynamicLoading.hs | 49 +++++++++++- compiler/main/GhcPlugins.hs | 7 +- compiler/main/Plugins.hs | 38 +++++++++ compiler/prelude/PrelNames.lhs | 6 +- compiler/simplCore/CoreMonad.lhs | 27 +------ compiler/simplCore/SimplCore.lhs | 52 ++----------- compiler/typecheck/TcInteract.lhs | 142 ++++++++++++++++++++++++++++++++-- compiler/typecheck/TcPluginM.hs | 123 +++++++++++++++++++++++++++++ compiler/typecheck/TcRnDriver.lhs | 48 +++++++++++- compiler/typecheck/TcRnMonad.lhs | 3 +- compiler/typecheck/TcRnTypes.lhs | 80 ++++++++++++++++++- compiler/typecheck/TcRnTypes.lhs-boot | 13 ---- compiler/typecheck/TcSMonad.lhs | 50 +++++++++++- compiler/typecheck/TcTypeNats.hs | 8 ++ docs/users_guide/7.10.1-notes.xml | 9 +++ docs/users_guide/extending_ghc.xml | 65 ++++++++++++++-- 17 files changed, 611 insertions(+), 111 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 64cb49686457c233d0f58e5cfa324ad28a5453a3 From git at git.haskell.org Thu Nov 20 19:06:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 19:06:19 +0000 (UTC) Subject: [commit: ghc] master: Split SynTyCon to SynonymTyCon and FamilyTyCon (696fc4b) Message-ID: <20141120190619.7AD093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/696fc4ba5b36f478d8daec56656ebf7d99e18159/ghc >--------------------------------------------------------------- commit 696fc4ba5b36f478d8daec56656ebf7d99e18159 Author: Jan Stolarek Date: Wed Nov 19 22:03:05 2014 +0100 Split SynTyCon to SynonymTyCon and FamilyTyCon This patch refactors internal representation of type synonyms and type families by splitting them into two separate data constructors of TyCon data type. The main motivation is is that some fields make sense only for type synonyms and some make sense only for type families. This will be even more true with the upcoming injective type families. There is also some refactoring of names to keep the naming constistent. And thus tc_kind field has become tyConKind and tc_roles has become tcRoles. Both changes are not visible from the outside of TyCon module. Updates haddock submodule Reviewers: simonpj Differential Revision: https://phabricator.haskell.org/D508 GHC Trac Issues: #9812 >--------------------------------------------------------------- 696fc4ba5b36f478d8daec56656ebf7d99e18159 compiler/coreSyn/CoreLint.lhs | 3 +- compiler/iface/BuildTyCl.lhs | 26 +- compiler/iface/IfaceSyn.lhs | 86 +++--- compiler/iface/MkIface.lhs | 54 ++-- compiler/iface/TcIface.lhs | 41 ++- compiler/main/GHC.hs | 6 +- compiler/prelude/TysPrim.lhs | 7 +- compiler/stgSyn/StgLint.lhs | 2 +- compiler/typecheck/TcCanonical.lhs | 4 +- compiler/typecheck/TcDeriv.lhs | 3 +- compiler/typecheck/TcErrors.lhs | 4 +- compiler/typecheck/TcFlatten.lhs | 4 +- compiler/typecheck/TcInstDcls.lhs | 4 +- compiler/typecheck/TcInteract.lhs | 6 +- compiler/typecheck/TcRnDriver.lhs | 22 +- compiler/typecheck/TcRnTypes.lhs | 2 +- compiler/typecheck/TcSMonad.lhs | 4 +- compiler/typecheck/TcSimplify.lhs | 4 +- compiler/typecheck/TcSplice.lhs | 2 +- compiler/typecheck/TcTyClsDecls.lhs | 25 +- compiler/typecheck/TcTyDecls.lhs | 2 +- compiler/typecheck/TcType.lhs | 14 +- compiler/typecheck/TcTypeNats.hs | 14 +- compiler/typecheck/TcUnify.lhs | 6 +- compiler/typecheck/TcValidity.lhs | 13 +- compiler/types/FamInstEnv.lhs | 4 +- compiler/types/TyCon.lhs | 460 +++++++++++++++++++------------ compiler/vectorise/Vectorise/Type/Env.hs | 5 +- utils/haddock | 2 +- 29 files changed, 488 insertions(+), 341 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 696fc4ba5b36f478d8daec56656ebf7d99e18159 From git at git.haskell.org Thu Nov 20 19:06:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 19:06:22 +0000 (UTC) Subject: [commit: ghc] master: Kill trailing whitespace (e2f7803) Message-ID: <20141120190622.460033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e2f780367a45e885b8cd3302d0c6d60c38ba40f2/ghc >--------------------------------------------------------------- commit e2f780367a45e885b8cd3302d0c6d60c38ba40f2 Author: Jan Stolarek Date: Thu Nov 20 17:41:10 2014 +0100 Kill trailing whitespace >--------------------------------------------------------------- e2f780367a45e885b8cd3302d0c6d60c38ba40f2 compiler/iface/MkIface.lhs | 0 compiler/typecheck/TcTyClsDecls.lhs | 0 compiler/types/TyCon.lhs | 0 3 files changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Thu Nov 20 21:41:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:41:02 +0000 (UTC) Subject: [commit: packages/array] master's head updated: Fix #9220 by adding role annotations. (4baaf0b) Message-ID: <20141120214102.673433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array Branch 'master' now includes: 80a463b Test #9220 in libraries/array/tests/T9220 4baaf0b Fix #9220 by adding role annotations. From git at git.haskell.org Thu Nov 20 21:41:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:41:17 +0000 (UTC) Subject: [commit: ghc] master: Fix #9209, by reporting an error instead of panicking on bad splices. (5a8ae60) Message-ID: <20141120214117.CEE093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5a8ae60ef9dc52ab04350ffbcf2945c9177eac87/ghc >--------------------------------------------------------------- commit 5a8ae60ef9dc52ab04350ffbcf2945c9177eac87 Author: Richard Eisenberg Date: Mon Nov 3 13:49:59 2014 -0500 Fix #9209, by reporting an error instead of panicking on bad splices. >--------------------------------------------------------------- 5a8ae60ef9dc52ab04350ffbcf2945c9177eac87 compiler/parser/Parser.y | 15 ++++++------ compiler/parser/RdrHsSyn.hs | 57 ++++++++++++++++++++++++++------------------- testsuite/tests/th/all.T | 2 +- 3 files changed, 42 insertions(+), 32 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index eb528c3..4117d06 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -702,12 +702,12 @@ ty_decl :: { LTyClDecl RdrName } inst_decl :: { LInstDecl RdrName } : 'instance' overlap_pragma inst_type where_inst - { let (binds, sigs, _, ats, adts, _) = cvBindsAndSigs (unLoc $4) in - let cid = ClsInstDecl { cid_poly_ty = $3, cid_binds = binds - , cid_sigs = sigs, cid_tyfam_insts = ats - , cid_overlap_mode = $2 - , cid_datafam_insts = adts } - in L (comb3 $1 $3 $4) (ClsInstD { cid_inst = cid }) } + {% do { (binds, sigs, _, ats, adts, _) <- cvBindsAndSigs (unLoc $4) + ; let cid = ClsInstDecl { cid_poly_ty = $3, cid_binds = binds + , cid_sigs = sigs, cid_tyfam_insts = ats + , cid_overlap_mode = $2 + , cid_datafam_insts = adts } + ; return (L (comb3 $1 $3 $4) (ClsInstD { cid_inst = cid })) } } -- type instance declarations | 'type' 'instance' ty_fam_inst_eqn @@ -986,7 +986,8 @@ decllist :: { Located (OrdList (LHsDecl RdrName)) } -- binds :: { Located (HsLocalBinds RdrName) } -- May have implicit parameters -- No type declarations - : decllist { sL1 $1 (HsValBinds (cvBindGroup (unLoc $1))) } + : decllist {% do { val_binds <- cvBindGroup (unLoc $1) + ; return (sL1 $1 (HsValBinds val_binds)) } } | '{' dbinds '}' { sLL $1 $> (HsIPBinds (IPBinds (unLoc $2) emptyTcEvBinds)) } | vocurly dbinds close { L (getLoc $2) (HsIPBinds (IPBinds (unLoc $2) emptyTcEvBinds)) } diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs index e945e43..e57af70 100644 --- a/compiler/parser/RdrHsSyn.hs +++ b/compiler/parser/RdrHsSyn.hs @@ -125,8 +125,8 @@ mkClassDecl :: SrcSpan -> P (LTyClDecl RdrName) mkClassDecl loc (L _ (mcxt, tycl_hdr)) fds where_cls - = do { let (binds, sigs, ats, at_insts, _, docs) = cvBindsAndSigs (unLoc where_cls) - cxt = fromMaybe (noLoc []) mcxt + = do { (binds, sigs, ats, at_insts, _, docs) <- cvBindsAndSigs (unLoc where_cls) + ; let cxt = fromMaybe (noLoc []) mcxt ; (cls, tparams) <- checkTyClHdr tycl_hdr ; tyvars <- checkTyVarsP (ptext (sLit "class")) whereDots cls tparams ; at_defs <- mapM (eitherToP . mkATDefault) at_insts @@ -304,36 +304,45 @@ cvTopDecls decls = go (fromOL decls) go (d : ds) = d : go ds -- Declaration list may only contain value bindings and signatures. -cvBindGroup :: OrdList (LHsDecl RdrName) -> HsValBinds RdrName +cvBindGroup :: OrdList (LHsDecl RdrName) -> P (HsValBinds RdrName) cvBindGroup binding - = case cvBindsAndSigs binding of - (mbs, sigs, fam_ds, tfam_insts, dfam_insts, _) - -> ASSERT( null fam_ds && null tfam_insts && null dfam_insts) - ValBindsIn mbs sigs + = do { (mbs, sigs, fam_ds, tfam_insts, dfam_insts, _) <- cvBindsAndSigs binding + ; ASSERT( null fam_ds && null tfam_insts && null dfam_insts) + return $ ValBindsIn mbs sigs } cvBindsAndSigs :: OrdList (LHsDecl RdrName) - -> (LHsBinds RdrName, [LSig RdrName], [LFamilyDecl RdrName] + -> P (LHsBinds RdrName, [LSig RdrName], [LFamilyDecl RdrName] , [LTyFamInstDecl RdrName], [LDataFamInstDecl RdrName], [LDocDecl]) -- Input decls contain just value bindings and signatures -- and in case of class or instance declarations also -- associated type declarations. They might also contain Haddock comments. -cvBindsAndSigs fb = go (fromOL fb) +cvBindsAndSigs fb = go (fromOL fb) where - go [] = (emptyBag, [], [], [], [], []) - go (L l (SigD s) : ds) = (bs, L l s : ss, ts, tfis, dfis, docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L l (ValD b) : ds) = (b' `consBag` bs, ss, ts, tfis, dfis, docs) - where (b', ds') = getMonoBind (L l b) ds - (bs, ss, ts, tfis, dfis, docs) = go ds' - go (L l (TyClD (FamDecl t)) : ds) = (bs, ss, L l t : ts, tfis, dfis, docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L l (InstD (TyFamInstD { tfid_inst = tfi })) : ds) = (bs, ss, ts, L l tfi : tfis, dfis, docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L l (InstD (DataFamInstD { dfid_inst = dfi })) : ds) = (bs, ss, ts, tfis, L l dfi : dfis, docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L l (DocD d) : ds) = (bs, ss, ts, tfis, dfis, (L l d) : docs) - where (bs, ss, ts, tfis, dfis, docs) = go ds - go (L _ d : _) = pprPanic "cvBindsAndSigs" (ppr d) + go [] = return (emptyBag, [], [], [], [], []) + go (L l (ValD b) : ds) + = do { (bs, ss, ts, tfis, dfis, docs) <- go ds' + ; return (b' `consBag` bs, ss, ts, tfis, dfis, docs) } + where + (b', ds') = getMonoBind (L l b) ds + go (L l decl : ds) + = do { (bs, ss, ts, tfis, dfis, docs) <- go ds + ; case decl of + SigD s + -> return (bs, L l s : ss, ts, tfis, dfis, docs) + TyClD (FamDecl t) + -> return (bs, ss, L l t : ts, tfis, dfis, docs) + InstD (TyFamInstD { tfid_inst = tfi }) + -> return (bs, ss, ts, L l tfi : tfis, dfis, docs) + InstD (DataFamInstD { dfid_inst = dfi }) + -> return (bs, ss, ts, tfis, L l dfi : dfis, docs) + DocD d + -> return (bs, ss, ts, tfis, dfis, L l d : docs) + SpliceD d + -> parseErrorSDoc l $ + hang (text "Declaration splices are allowed only" <+> + text "at the top level:") + 2 (ppr d) + _ -> pprPanic "cvBindsAndSigs" (ppr decl) } ----------------------------------------------------------------------------- -- Group function bindings into equation groups diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index b124fec..6c7b2e5 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -342,4 +342,4 @@ test('T9081', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T8100', normal, compile, ['-v0']) test('T9064', normal, compile, ['-v0']) -test('T9209', expect_broken(9209), compile_fail, ['-v0']) +test('T9209', normal, compile_fail, ['-v0']) From git at git.haskell.org Thu Nov 20 21:41:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:41:20 +0000 (UTC) Subject: [commit: ghc] master: Test #9209 in th/T9209 (6db0f6f) Message-ID: <20141120214120.DEF9A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6db0f6fe40287f16d34d12efae9249d2feb4878a/ghc >--------------------------------------------------------------- commit 6db0f6fe40287f16d34d12efae9249d2feb4878a Author: Richard Eisenberg Date: Mon Nov 3 13:46:58 2014 -0500 Test #9209 in th/T9209 >--------------------------------------------------------------- 6db0f6fe40287f16d34d12efae9249d2feb4878a testsuite/tests/th/T9209.hs | 5 +++++ testsuite/tests/th/T9209.stderr | 4 ++++ testsuite/tests/th/all.T | 1 + 3 files changed, 10 insertions(+) diff --git a/testsuite/tests/th/T9209.hs b/testsuite/tests/th/T9209.hs new file mode 100644 index 0000000..46740ba --- /dev/null +++ b/testsuite/tests/th/T9209.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T9209 where + +foo = let $( [d| x = 5 |] ) in x diff --git a/testsuite/tests/th/T9209.stderr b/testsuite/tests/th/T9209.stderr new file mode 100644 index 0000000..1f4f3e7 --- /dev/null +++ b/testsuite/tests/th/T9209.stderr @@ -0,0 +1,4 @@ + +T9209.hs:5:11: + Declaration splices are allowed only at the top level: + $([d| x = 5 |]) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 43eb438..b124fec 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -342,3 +342,4 @@ test('T9081', normal, compile, ['-v0']) test('T9066', normal, compile, ['-v0']) test('T8100', normal, compile, ['-v0']) test('T9064', normal, compile, ['-v0']) +test('T9209', expect_broken(9209), compile_fail, ['-v0']) From git at git.haskell.org Thu Nov 20 21:41:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:41:24 +0000 (UTC) Subject: [commit: ghc] master: Fix #9220 by adding role annotations. (e394e74) Message-ID: <20141120214124.1A6B63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e394e74df5ca8081c0ffd147d34e788d290fb21a/ghc >--------------------------------------------------------------- commit e394e74df5ca8081c0ffd147d34e788d290fb21a Author: Richard Eisenberg Date: Fri Nov 7 17:34:59 2014 -0500 Fix #9220 by adding role annotations. This includes a submodule update for `array`. There is also an added test in libraries/array/tests/T9220. >--------------------------------------------------------------- e394e74df5ca8081c0ffd147d34e788d290fb21a libraries/array | 2 +- libraries/base/GHC/Arr.hs | 6 +- libraries/base/GHC/IOArray.hs | 5 +- testsuite/tests/roles/should_compile/all.T | 1 - .../{should_compile => should_fail}/RolesIArray.hs | 0 .../tests/roles/should_fail/RolesIArray.stderr | 100 +++++++++++++++++++++ testsuite/tests/roles/should_fail/all.T | 1 + 7 files changed, 111 insertions(+), 4 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e394e74df5ca8081c0ffd147d34e788d290fb21a From git at git.haskell.org Thu Nov 20 21:41:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:41:27 +0000 (UTC) Subject: [commit: ghc] master: Test #9151 in typecheck/should_compile/T9151. (67abfda) Message-ID: <20141120214127.472BC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/67abfdacf5c93cccb0ab780b524591c916b21c3f/ghc >--------------------------------------------------------------- commit 67abfdacf5c93cccb0ab780b524591c916b21c3f Author: Richard Eisenberg Date: Wed Nov 12 14:48:25 2014 -0500 Test #9151 in typecheck/should_compile/T9151. This test case should pass right now -- the bug is fixed, presumably by #9200. >--------------------------------------------------------------- 67abfdacf5c93cccb0ab780b524591c916b21c3f testsuite/tests/typecheck/should_compile/T9151.hs | 11 +++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 12 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T9151.hs b/testsuite/tests/typecheck/should_compile/T9151.hs new file mode 100644 index 0000000..351c563 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9151.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE PolyKinds, DataKinds, TypeFamilies, UndecidableInstances #-} + +module T9151 where + +import Data.Proxy + +class PEnum (kproxy :: KProxy a) where + type ToEnum (x :: a) :: Bool + type ToEnum x = TEHelper + +type TEHelper = ToEnum Int diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index ef830d1..ea7d343 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -425,3 +425,4 @@ test('T9708', normal, compile_fail, ['']) test('T9404', normal, compile, ['']) test('T9404b', normal, compile, ['']) test('T7220', normal, compile, ['']) +test('T9151', normal, compile, ['']) From git at git.haskell.org Thu Nov 20 21:41:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:41:30 +0000 (UTC) Subject: [commit: ghc] master: Add release notes for #8100, #9527, and #9064. (786b62a) Message-ID: <20141120214130.029763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/786b62aa57e4dcc528e2da2f7d0451ab834d655a/ghc >--------------------------------------------------------------- commit 786b62aa57e4dcc528e2da2f7d0451ab834d655a Author: Richard Eisenberg Date: Wed Nov 12 15:13:34 2014 -0500 Add release notes for #8100, #9527, and #9064. >--------------------------------------------------------------- 786b62aa57e4dcc528e2da2f7d0451ab834d655a docs/users_guide/7.10.1-notes.xml | 13 +++++++++++++ 1 file changed, 13 insertions(+) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 5a75cc2..5eb9bae 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -200,6 +200,19 @@ Lift instances were added for () and Ratio. + + + All Template Haskell datatypes now have + Generic instances. + + + + Two new declaration forms are now supported: + standalone-deriving declarations and generic method + signatures (written using default in + a class). This means an expansion to the Dec + type. + From git at git.haskell.org Thu Nov 20 21:41:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:41:33 +0000 (UTC) Subject: [commit: ghc] master: Test #9318 in typecheck/should_fail/T9318 (5eebd99) Message-ID: <20141120214133.56A953A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5eebd990ea7a5bc1937657b101ae83475e20fc7a/ghc >--------------------------------------------------------------- commit 5eebd990ea7a5bc1937657b101ae83475e20fc7a Author: Richard Eisenberg Date: Tue Nov 18 13:16:01 2014 -0500 Test #9318 in typecheck/should_fail/T9318 >--------------------------------------------------------------- 5eebd990ea7a5bc1937657b101ae83475e20fc7a testsuite/tests/typecheck/should_fail/T9318.hs | 12 ++++++++++++ testsuite/tests/typecheck/should_fail/T9318.stderr | 7 +++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 20 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T9318.hs b/testsuite/tests/typecheck/should_fail/T9318.hs new file mode 100644 index 0000000..3110305 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9318.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE TypeFamilies #-} + +module T9318 where + +type family F x +type instance F Int = Bool + +foo :: F Int -> () +foo True = () + +bar :: F Int -> () +bar 'x' = () diff --git a/testsuite/tests/typecheck/should_fail/T9318.stderr b/testsuite/tests/typecheck/should_fail/T9318.stderr new file mode 100644 index 0000000..963d73e --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9318.stderr @@ -0,0 +1,7 @@ + +T9318.hs:12:5: + Couldn't match type ?Bool? with ?Char? + Expected type: F Int + Actual type: Char + In the pattern: 'x' + In an equation for ?bar?: bar 'x' = () diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 2b128dc..b6b5572 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -342,3 +342,4 @@ test('T9612', normal, compile_fail, ['']) test('T9634', normal, compile_fail, ['']) test('T9739', normal, compile_fail, ['']) test('T9774', normal, compile_fail, ['']) +test('T9318', normal, compile_fail, ['']) From git at git.haskell.org Thu Nov 20 21:41:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:41:36 +0000 (UTC) Subject: [commit: ghc] master: Update manual to get rid of bogus `coerce` example (#9788) (113a37b) Message-ID: <20141120214136.0BE933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/113a37b6e39a3b4964ea6d93fd7adf30adb39426/ghc >--------------------------------------------------------------- commit 113a37b6e39a3b4964ea6d93fd7adf30adb39426 Author: Richard Eisenberg Date: Tue Nov 18 14:22:30 2014 -0500 Update manual to get rid of bogus `coerce` example (#9788) >--------------------------------------------------------------- 113a37b6e39a3b4964ea6d93fd7adf30adb39426 docs/users_guide/using.xml | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/docs/users_guide/using.xml b/docs/users_guide/using.xml index bf4f1c5..1f0c029 100644 --- a/docs/users_guide/using.xml +++ b/docs/users_guide/using.xml @@ -923,10 +923,11 @@ GHC.ST.runST :: (forall s. GHC.ST.ST s a) -> a If any of the quantified type variables has a kind that mentions a kind variable, e.g. -ghci> :i Data.Coerce.coerce -coerce :: - forall (k :: BOX) (a :: k) (b :: k). Coercible a b => a -> b - -- Defined in GHC.Prim +ghci> :i Data.Type.Equality.sym +Data.Type.Equality.sym :: + forall (k :: BOX) (a :: k) (b :: k). + (a Data.Type.Equality.:~: b) -> b Data.Type.Equality.:~: a + -- Defined in Data.Type.Equality From git at git.haskell.org Thu Nov 20 21:41:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:41:39 +0000 (UTC) Subject: [commit: ghc] master: Test #9201 in typecheck/should_fail/T9201 (8fea2ac) Message-ID: <20141120214139.4C78A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8fea2acde696f9960ffcf84f512235bbf4b481d6/ghc >--------------------------------------------------------------- commit 8fea2acde696f9960ffcf84f512235bbf4b481d6 Author: Richard Eisenberg Date: Tue Nov 18 13:19:42 2014 -0500 Test #9201 in typecheck/should_fail/T9201 >--------------------------------------------------------------- 8fea2acde696f9960ffcf84f512235bbf4b481d6 testsuite/tests/typecheck/should_fail/T9201.hs | 6 ++++++ testsuite/tests/typecheck/should_fail/T9201.stderr | 6 ++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 13 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T9201.hs b/testsuite/tests/typecheck/should_fail/T9201.hs new file mode 100644 index 0000000..7702fa3 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9201.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE PolyKinds, FunctionalDependencies, MultiParamTypeClasses #-} + +module T9201 where + +class MonoidalCCC (f :: x -> y) (d :: y -> y -> *) | f -> d where + ret :: d a (f a) diff --git a/testsuite/tests/typecheck/should_fail/T9201.stderr b/testsuite/tests/typecheck/should_fail/T9201.stderr new file mode 100644 index 0000000..44e338a --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9201.stderr @@ -0,0 +1,6 @@ + +T9201.hs:6:17: + The first argument of ?f? should have kind ?x1?, + but ?a? has kind ?y1? + In the type ?d a (f a)? + In the class declaration for ?MonoidalCCC? diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index b6b5572..14df71e 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -343,3 +343,4 @@ test('T9634', normal, compile_fail, ['']) test('T9739', normal, compile_fail, ['']) test('T9774', normal, compile_fail, ['']) test('T9318', normal, compile_fail, ['']) +test('T9201', normal, compile_fail, ['']) From git at git.haskell.org Thu Nov 20 21:41:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:41:42 +0000 (UTC) Subject: [commit: ghc] master: Test #9109 in typecheck/should_fail/T9109 (cb41e08) Message-ID: <20141120214142.A4EA03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cb41e08e4ce687356d1345ad6a1aa3555e505a59/ghc >--------------------------------------------------------------- commit cb41e08e4ce687356d1345ad6a1aa3555e505a59 Author: Richard Eisenberg Date: Tue Nov 18 15:19:20 2014 -0500 Test #9109 in typecheck/should_fail/T9109 >--------------------------------------------------------------- cb41e08e4ce687356d1345ad6a1aa3555e505a59 testsuite/tests/typecheck/should_fail/T9109.hs | 8 ++++++++ testsuite/tests/typecheck/should_fail/T9109.stderr | 15 +++++++++++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 24 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T9109.hs b/testsuite/tests/typecheck/should_fail/T9109.hs new file mode 100644 index 0000000..725cb66 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9109.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE GADTs #-} + +module T9109 where + +data G a where + GBool :: G Bool + +foo GBool = True diff --git a/testsuite/tests/typecheck/should_fail/T9109.stderr b/testsuite/tests/typecheck/should_fail/T9109.stderr new file mode 100644 index 0000000..5ef2340 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9109.stderr @@ -0,0 +1,15 @@ + +T9109.hs:8:13: + Couldn't match expected type ?t? with actual type ?Bool? + ?t? is untouchable + inside the constraints (t1 ~ Bool) + bound by a pattern with constructor + GBool :: G Bool, + in an equation for ?foo? + at T9109.hs:8:5-9 + ?t? is a rigid type variable bound by + the inferred type of foo :: G t1 -> t at T9109.hs:8:1 + Possible fix: add a type signature for ?foo? + Relevant bindings include foo :: G t1 -> t (bound at T9109.hs:8:1) + In the expression: True + In an equation for ?foo?: foo GBool = True diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 14df71e..28709e8 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -344,3 +344,4 @@ test('T9739', normal, compile_fail, ['']) test('T9774', normal, compile_fail, ['']) test('T9318', normal, compile_fail, ['']) test('T9201', normal, compile_fail, ['']) +test('T9109', normal, compile_fail, ['']) From git at git.haskell.org Thu Nov 20 21:54:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:54:28 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #7484 in th/T7484 (148f416) Message-ID: <20141120215428.2215F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/148f416e141cea2e125210646457eab79255e750/ghc >--------------------------------------------------------------- commit 148f416e141cea2e125210646457eab79255e750 Author: Richard Eisenberg Date: Mon Nov 3 15:33:51 2014 -0500 Test #7484 in th/T7484 >--------------------------------------------------------------- 148f416e141cea2e125210646457eab79255e750 testsuite/tests/th/T7484.hs | 7 +++++++ testsuite/tests/th/T7484.stderr | 4 ++++ testsuite/tests/th/all.T | 1 + 3 files changed, 12 insertions(+) diff --git a/testsuite/tests/th/T7484.hs b/testsuite/tests/th/T7484.hs new file mode 100644 index 0000000..b1a9cba --- /dev/null +++ b/testsuite/tests/th/T7484.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T7484 where + +import Language.Haskell.TH + +$( return [ ValD (VarP (mkName "a ")) (NormalB (LitE (IntegerL 5))) [] ] ) diff --git a/testsuite/tests/th/T7484.stderr b/testsuite/tests/th/T7484.stderr new file mode 100644 index 0000000..3ffe123 --- /dev/null +++ b/testsuite/tests/th/T7484.stderr @@ -0,0 +1,4 @@ + +T7484.hs:7:4: + Illegal variable name: ?a ? + When splicing a TH declaration: a = 5 diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 6c7b2e5..5109473 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -343,3 +343,4 @@ test('T9066', normal, compile, ['-v0']) test('T8100', normal, compile, ['-v0']) test('T9064', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) +test('T7484', expect_broken(7484), compile_fail, ['-v0']) From git at git.haskell.org Thu Nov 20 21:54:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:54:31 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #7484, checking for good binder names in Convert. (8dcd39b) Message-ID: <20141120215431.5AD3C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/8dcd39b16be5493ffce0808ea55e93743ead63d2/ghc >--------------------------------------------------------------- commit 8dcd39b16be5493ffce0808ea55e93743ead63d2 Author: Richard Eisenberg Date: Mon Nov 3 15:34:53 2014 -0500 Fix #7484, checking for good binder names in Convert. This commit also refactors a bunch of lexeme-oriented code into a new module Lexeme, and includes a submodule update for haddock. >--------------------------------------------------------------- 8dcd39b16be5493ffce0808ea55e93743ead63d2 compiler/basicTypes/Lexeme.hs | 252 ++++++++++++++++++++++++++++++++++++++ compiler/basicTypes/OccName.lhs | 72 +---------- compiler/ghc.cabal.in | 1 + compiler/ghc.mk | 1 + compiler/hsSyn/Convert.lhs | 12 +- compiler/typecheck/TcGenDeriv.lhs | 1 + compiler/typecheck/TcSplice.lhs | 1 + testsuite/tests/th/all.T | 2 +- utils/haddock | 2 +- 9 files changed, 264 insertions(+), 80 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8dcd39b16be5493ffce0808ea55e93743ead63d2 From git at git.haskell.org Thu Nov 20 21:54:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:54:34 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #1476 in th/T1476 (a0913ce) Message-ID: <20141120215434.8401A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/a0913cecac6ec4e4d1e4f3e2a44bd4126ad21b30/ghc >--------------------------------------------------------------- commit a0913cecac6ec4e4d1e4f3e2a44bd4126ad21b30 Author: Richard Eisenberg Date: Mon Nov 3 20:26:14 2014 -0500 Test #1476 in th/T1476 >--------------------------------------------------------------- a0913cecac6ec4e4d1e4f3e2a44bd4126ad21b30 testsuite/tests/th/T1476.hs | 10 ++++++++++ testsuite/tests/th/all.T | 1 + 2 files changed, 11 insertions(+) diff --git a/testsuite/tests/th/T1476.hs b/testsuite/tests/th/T1476.hs new file mode 100644 index 0000000..7e3a192 --- /dev/null +++ b/testsuite/tests/th/T1476.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T1476 where + +import Language.Haskell.TH + +foo $( return $ VarP $ mkName "x" ) = x +bar $( [p| x |] ) = x + +baz = [| \ $( return $ VarP $ mkName "x" ) -> $(dyn "x") |] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 1144156..27cde1b 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -344,3 +344,4 @@ test('T8100', normal, compile, ['-v0']) test('T9064', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) +test('T1476', expect_broken(1476), compile, ['-v0']) From git at git.haskell.org Thu Nov 20 21:54:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:54:37 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #1476 by making splice patterns work. (9716d81) Message-ID: <20141120215437.4CAF03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/9716d8167ffcce1bdd50aa8dc9338d88730c9bd2/ghc >--------------------------------------------------------------- commit 9716d8167ffcce1bdd50aa8dc9338d88730c9bd2 Author: Richard Eisenberg Date: Tue Nov 4 11:34:53 2014 -0500 Fix #1476 by making splice patterns work. Unfortunately, splice patterns in brackets still do not work because we don't run splices in brackets. Without running a pattern splice, we can't know what variables it binds, so we're stuck. This is still a substantial improvement, and it may be the best we can do. Still must document new behavior. >--------------------------------------------------------------- 9716d8167ffcce1bdd50aa8dc9338d88730c9bd2 compiler/rename/RnPat.lhs | 10 ++++++---- compiler/rename/RnSplice.lhs | 38 +++++++++++++++++++++++++++++++------- compiler/rename/RnSplice.lhs-boot | 3 ++- testsuite/tests/th/all.T | 2 +- 4 files changed, 40 insertions(+), 13 deletions(-) diff --git a/compiler/rename/RnPat.lhs b/compiler/rename/RnPat.lhs index aa41361..634c99c 100644 --- a/compiler/rename/RnPat.lhs +++ b/compiler/rename/RnPat.lhs @@ -440,10 +440,12 @@ rnPatAndThen mk (TuplePat pats boxed _) ; pats' <- rnLPatsAndThen mk pats ; return (TuplePat pats' boxed []) } -rnPatAndThen _ (SplicePat splice) - = do { -- XXX How to deal with free variables? - ; (pat, _) <- liftCps $ rnSplicePat splice - ; return pat } +rnPatAndThen mk (SplicePat splice) + = do { eith <- liftCpsFV $ rnSplicePat splice + ; case eith of -- See Note [rnSplicePat] in RnSplice + Left not_yet_renamed -> rnPatAndThen mk not_yet_renamed + Right already_renamed -> return already_renamed } + rnPatAndThen mk (QuasiQuotePat qq) = do { pat <- liftCps $ runQuasiQuotePat qq -- Wrap the result of the quasi-quoter in parens so that we don't diff --git a/compiler/rename/RnSplice.lhs b/compiler/rename/RnSplice.lhs index 59c8c62..8918e39 100644 --- a/compiler/rename/RnSplice.lhs +++ b/compiler/rename/RnSplice.lhs @@ -206,13 +206,40 @@ rnSpliceType splice k } ; return (unLoc hs_ty3, fvs) } ----------------------- -rnSplicePat :: HsSplice RdrName -> RnM (Pat Name, FreeVars) +\end{code} + +Note [rnSplicePat] +~~~~~~~~~~~~~~~~~~ +Renaming a pattern splice is a bit tricky, because we need the variables +bound in the pattern to be in scope in the RHS of the pattern. This scope +management is effectively done by using continuation-passing style in +RnPat, through the CpsRn monad. We don't wish to be in that monad here +(it would create import cycles and generally conflict with renaming other +splices), so we really want to return a (Pat RdrName) -- the result of +running the splice -- which can then be further renamed in RnPat, in +the CpsRn monad. + +The problem is that if we're renaming a splice within a bracket, we +*don't* want to run the splice now. We really do just want to rename +it to an HsSplice Name. Of course, then we can't know what variables +are bound within the splice, so pattern splices within brackets aren't +all that useful. + +In any case, when we're done in rnSplicePat, we'll either have a +Pat RdrName (the result of running a top-level splice) or a Pat Name +(the renamed nested splice). Thus, the awkward return type of +rnSplicePat. + +\begin{code} + +-- | Rename a splice pattern. See Note [rnSplicePat] +rnSplicePat :: HsSplice RdrName -> RnM ( Either (Pat RdrName) (Pat Name) + , FreeVars) rnSplicePat splice = rnSpliceGen False run_pat_splice pend_pat_splice splice where pend_pat_splice rn_splice@(HsSplice n e) - = (PendingRnPatSplice (PendSplice n e), SplicePat rn_splice) + = (PendingRnPatSplice (PendSplice n e), Right $ SplicePat rn_splice) run_pat_splice (HsSplice _ expr') = do { expr <- getHooked runRnSpliceHook return >>= ($ expr') @@ -227,10 +254,7 @@ rnSplicePat splice ; pat <- runMetaP zonked_q_expr ; showSplice "pattern" expr (ppr pat) - ; (pat', fvs) <- checkNoErrs $ - rnPat ThPatSplice pat $ \pat' -> return (pat', emptyFVs) - - ; return (unLoc pat', fvs) } + ; return (Left $ unLoc pat, emptyFVs) } ---------------------- rnSpliceDecl :: SpliceDecl RdrName -> RnM (SpliceDecl Name, FreeVars) diff --git a/compiler/rename/RnSplice.lhs-boot b/compiler/rename/RnSplice.lhs-boot index 45a2a10..de6da77 100644 --- a/compiler/rename/RnSplice.lhs-boot +++ b/compiler/rename/RnSplice.lhs-boot @@ -11,6 +11,7 @@ import Kind rnSpliceType :: HsSplice RdrName -> PostTc Name Kind -> RnM (HsType Name, FreeVars) -rnSplicePat :: HsSplice RdrName -> RnM (Pat Name, FreeVars) +rnSplicePat :: HsSplice RdrName -> RnM ( Either (Pat RdrName) (Pat Name) + , FreeVars ) rnSpliceDecl :: SpliceDecl RdrName -> RnM (SpliceDecl Name, FreeVars) \end{code} diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 3f8ff16..366858e 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -344,5 +344,5 @@ test('T8100', normal, compile, ['-v0']) test('T9064', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) -test('T1476', expect_broken(1476), compile, ['-v0']) +test('T1476', normal, compile, ['-v0']) test('T1476b', normal, compile_fail, ['-v0']) From git at git.haskell.org Thu Nov 20 21:54:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:54:40 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test that nested pattern splices don't scope (#1476). (419c5de) Message-ID: <20141120215440.AB9113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/419c5de91e503457fb88cb6c175f21b9325032e0/ghc >--------------------------------------------------------------- commit 419c5de91e503457fb88cb6c175f21b9325032e0 Author: Richard Eisenberg Date: Tue Nov 4 13:06:56 2014 -0500 Test that nested pattern splices don't scope (#1476). Test case: th/T1476b. >--------------------------------------------------------------- 419c5de91e503457fb88cb6c175f21b9325032e0 testsuite/tests/th/T1476b.hs | 10 ++++++++++ testsuite/tests/th/T1476b.stderr | 5 +++++ testsuite/tests/th/all.T | 1 + 3 files changed, 16 insertions(+) diff --git a/testsuite/tests/th/T1476b.hs b/testsuite/tests/th/T1476b.hs new file mode 100644 index 0000000..918a397 --- /dev/null +++ b/testsuite/tests/th/T1476b.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T1476b where + +import Language.Haskell.TH + +baz = [| \ $( return $ VarP $ mkName "x" ) -> x |] + +-- If this test starts passing, nested pattern splices scope correctly. +-- Good for you! Now, update the TH manual accordingly. diff --git a/testsuite/tests/th/T1476b.stderr b/testsuite/tests/th/T1476b.stderr new file mode 100644 index 0000000..65b0814 --- /dev/null +++ b/testsuite/tests/th/T1476b.stderr @@ -0,0 +1,5 @@ + +T1476b.hs:7:47: + Not in scope: ?x? + In the Template Haskell quotation + [| \ $(return $ VarP $ mkName "x") -> x |] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 27cde1b..3f8ff16 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -345,3 +345,4 @@ test('T9064', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) test('T1476', expect_broken(1476), compile, ['-v0']) +test('T1476b', normal, compile_fail, ['-v0']) From git at git.haskell.org Thu Nov 20 21:54:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:54:43 +0000 (UTC) Subject: [commit: ghc] wip/rae: Release notes for #1476, #7484. (d185e71) Message-ID: <20141120215443.6DEC03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/d185e714fefb0bfda42e7d0fe74216592bdaf1b1/ghc >--------------------------------------------------------------- commit d185e714fefb0bfda42e7d0fe74216592bdaf1b1 Author: Richard Eisenberg Date: Tue Nov 4 12:20:25 2014 -0500 Release notes for #1476, #7484. >--------------------------------------------------------------- d185e714fefb0bfda42e7d0fe74216592bdaf1b1 docs/users_guide/7.10.1-notes.xml | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 5eb9bae..aa6eec5 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -177,6 +177,10 @@ + Pattern splices now work. + + + reifyInstances now treats unbound type variables as univerally quantified, allowing lookup of, say, the instance for Eq [a]. @@ -213,6 +217,13 @@ a class). This means an expansion to the Dec type. + + + Template Haskell is now more pedantic about splicing in + bogus variable names, like those containing whitespace. If you + use bogus names in your Template Haskell code, this may break + your program. + From git at git.haskell.org Thu Nov 20 21:54:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Nov 2014 21:54:46 +0000 (UTC) Subject: [commit: ghc] wip/rae's head updated: Release notes for #1476, #7484. (d185e71) Message-ID: <20141120215446.262CE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/rae' now includes: c65221b includes/Stg.h: define _DEFAULT_SOURCE for glibc-2.20 064c289 Remove a stray Trustworthy flag in ghc. 1f8b4ee Add in `-fwarn-trustworthy-safe` flag. 475dd93 Add `--fwarn-trustworthy-safe` to `-Wall` 8fe2bbe Update userguide for new `-fwarn-trustworthy-safe` flag. 413c747 base: Fix map/coerce comment e73ab54 Make unwords and words fuse somewhat c016e6f base: define `sequence = mapM id` 212a350 Improve `Foldable` instance for `Array` 63a9d93 Fix `integer-gmp2` compilation with GMP 4.x (#9281) 9b30d9d Fix typo in panic message 745c4c0 Binding things matched by an unboxed pattern synonym should require a bang 7f92986 If pattern synonym is bidirectional and its type is some unboxed type T#, generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. Fixes #9732. 5fe872d Apply compulsory unfoldings during desugaring, except for `seq` which is special. See Note [Unfolding while desugaring] for the rationale. faeb0a6 nlHsTyApps: for applying a function both on type- and term-level arguments 6389911 When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments 603b7be Implement amap/coerce for Array (re #9796) fa75309 Update .mailmap 452d6aa Partially revert 475dd93efa e14a973 Generalize exposed-modules field in installed package database 1854825 Workaround 452d6aa95b7 breaking TrustworthySafe03 609cd28 Update to (unreleased) `deepseq-1.4.0.0` c45e2e2 Fix compilation of `integer-gmp2` with `-O0` a2c0a8d Update validate settings now that containers and process have been updated to handle `-fwarn-trustworthy-safe`. 2a6f193 Fix a bug introduced with allocation counters 0515055 document addDependentFile uses contents, not mtime d997ca8 Don't use absolute paths for perl in validate a520761 Remove outdated TODO in TimeManager bc68ed0 Make listArray fuse df22507 Docs only ce2cc64 Adding dedicated Show instances for SrcSpan/SrcLoc 74a6a8a Change a comment referring falsely to seq 44f1582 Remove optimized package lookup, simplifying code. b9096df Add a note why tcGetInstEnvs is duplicated. aa1c1b2 Build xhtml and haddock only when `HADDOCK_DOCS=YES` 9a20379 Fix ffi023 20226c2 Whitespace only ac1281f Outputable instance for IfaceVectInfo 535644f Add missing semicolon in Schedule.c 1f6b1ab base: Fix (**) instance for Data.Complex (#8539) ddb484c Update comment about C helper for foreign exports (#9713) 87cd37b Fix usage of `find -perm` in aclocal.m4 (#9697) 21f9bc4 mapMaybe: Typo in the comment (#9644) c557f99 Disable AVX for LLVM 3.2 by default (#9391) e7b414a Fix detection of GNU gold linker if invoked via gcc with parameters a736b51 Revert "base: Fix (**) instance for Data.Complex (#8539)" 483eeba Comments only 1019e3c When outputting list of available instances, sort it. 7c748d9 Support for "with" renaming syntax, and output a feature flag. 4224466 Reimplement im/export primitives for integer-gmp2 e2af452 Restore exact old semantics of `decodeFloat` 4ba884b Optimise `Identity` instances with `coerce` 8e0a480 rts: remove old-style field designator extension (#9396) 101c62e The test runner now also works under the msys-native Python. 6fc78fd Refactor: use System.FilePath.splitSearchPath 66c0513 Update documentation for "Batch compiler mode" 00c1a30 Implement new Foldable methods for HsPatSynDetails 5db61ea Turn CoreWriter into a newtype; fix comment 5c09893 Add remaining s and comments to .mailmap 7ef0971 Filter input to abiHash early b3df5f6 template-haskell: Missing instances for Rational and (). b047733 add missing instances for Loc and a few missing Eq instances 146dd13 Only test for bug #9439 when llvm is installed 53a4742 Allow -dead_strip linking on platforms with .subsections_via_symbols 33c029f make TcRnMonad.lhs respect -ddump-to-file 4dd87c5 use correct word size for shiftRightLogical and removeOp32 80f6fc1 compiler/main: fixes #9776 d87fa34 arm64: 64bit iOS and SMP support (#7942) bc2289e ghc generates more user-friendly error messages c6e12e6 Make calling conventions in template haskell Syntax.hs consistent with those in ghc ForeignCall.hs this impliments #9703 from ghc trac 8cbd25a Make Data.Functor.Identity trustworthy again 3b81309 Update shift/reduce conflict number in parser cce6318 Add support for pattern synonym type signatures. Syntax is of the form 64cb496 Implement typechecker plugins 696fc4b Split SynTyCon to SynonymTyCon and FamilyTyCon e2f7803 Kill trailing whitespace 6db0f6f Test #9209 in th/T9209 5a8ae60 Fix #9209, by reporting an error instead of panicking on bad splices. e394e74 Fix #9220 by adding role annotations. 67abfda Test #9151 in typecheck/should_compile/T9151. 786b62a Add release notes for #8100, #9527, and #9064. 5eebd99 Test #9318 in typecheck/should_fail/T9318 8fea2ac Test #9201 in typecheck/should_fail/T9201 113a37b Update manual to get rid of bogus `coerce` example (#9788) cb41e08 Test #9109 in typecheck/should_fail/T9109 148f416 Test #7484 in th/T7484 8dcd39b Fix #7484, checking for good binder names in Convert. a0913ce Test #1476 in th/T1476 419c5de Test that nested pattern splices don't scope (#1476). 9716d81 Fix #1476 by making splice patterns work. d185e71 Release notes for #1476, #7484. From git at git.haskell.org Fri Nov 21 03:28:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 03:28:27 +0000 (UTC) Subject: [commit: ghc] master: Don't build old-{time, locale} and haskell{98, 2010} (6efe572) Message-ID: <20141121032827.222443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6efe5729252ea50843e1b04e21c7a3e1769a3434/ghc >--------------------------------------------------------------- commit 6efe5729252ea50843e1b04e21c7a3e1769a3434 Author: Austin Seipp Date: Thu Nov 20 21:29:04 2014 -0600 Don't build old-{time,locale} and haskell{98,2010} Summary: As discussed on ghc-devs at haskell.org and the trac ticket, we're removing these packages from the 7.10 release as they no longer work correctly, and can't easily be made to properly follow the standard as `base` changes over time. This does not remove the packages from the tree, only the build system. https://www.haskell.org/pipermail/ghc-devs/2014-November/007357.html Signed-off-by: Austin Seipp Test Plan: iiam Reviewers: hvr, ekmett Reviewed By: hvr, ekmett Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D510 GHC Trac Issues: #9590 >--------------------------------------------------------------- 6efe5729252ea50843e1b04e21c7a3e1769a3434 ghc.mk | 9 --------- packages | 4 ---- 2 files changed, 13 deletions(-) diff --git a/ghc.mk b/ghc.mk index 1e8ea58..a93628a 100644 --- a/ghc.mk +++ b/ghc.mk @@ -398,7 +398,6 @@ PACKAGES_STAGE1 += array PACKAGES_STAGE1 += deepseq PACKAGES_STAGE1 += bytestring PACKAGES_STAGE1 += containers -PACKAGES_STAGE1 += old-locale ifeq "$(Windows_Host)" "YES" PACKAGES_STAGE1 += Win32 @@ -419,12 +418,6 @@ PACKAGES_STAGE1 += bin-package-db PACKAGES_STAGE1 += hoopl PACKAGES_STAGE1 += transformers -ifneq "$(CrossCompiling)" "YES" -PACKAGES_STAGE2 += old-time -PACKAGES_STAGE2 += haskell98 -PACKAGES_STAGE2 += haskell2010 -endif - ifeq "$(HADDOCK_DOCS)" "YES" PACKAGES_STAGE1 += xhtml endif @@ -1324,7 +1317,6 @@ distclean : clean $(call removeFiles,libraries/process/include/HsProcessConfig.h) $(call removeFiles,libraries/unix/include/HsUnixConfig.h) $(call removeFiles,libraries/time/include/HsTimeConfig.h) - $(call removeFiles,libraries/old-time/include/HsTimeConfig.h) # The library configure scripts also like creating autom4te.cache # directories, so clean them all up. @@ -1353,7 +1345,6 @@ maintainer-clean : distclean $(call removeFiles,libraries/process/include/HsProcessConfig.h.in) $(call removeFiles,libraries/unix/include/HsUnixConfig.h.in) $(call removeFiles,libraries/time/include/HsTimeConfig.h.in) - $(call removeFiles,libraries/old-time/include/HsTimeConfig.h.in) .PHONY: all_libraries diff --git a/packages b/packages index 80b0235..50ad970 100644 --- a/packages +++ b/packages @@ -60,12 +60,8 @@ libraries/deepseq - - ssh://g libraries/directory - - ssh://git at github.com/haskell/directory.git libraries/filepath - - ssh://git at github.com/haskell/filepath.git libraries/haskeline - - https://github.com/judah/haskeline.git -libraries/haskell98 - - - -libraries/haskell2010 - - - libraries/hoopl - - - libraries/hpc - - - -libraries/old-locale - - - -libraries/old-time - - - libraries/pretty - - https://github.com/haskell/pretty.git libraries/process - - ssh://git at github.com/haskell/process.git libraries/terminfo - - https://github.com/judah/terminfo.git From git at git.haskell.org Fri Nov 21 03:32:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 03:32:58 +0000 (UTC) Subject: [commit: ghc] master: Delete old-{time, locale} and haskell{98, 2010} (86dda8f) Message-ID: <20141121033258.5C0933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/86dda8f7adb887eb376a938dd48780e503b53a08/ghc >--------------------------------------------------------------- commit 86dda8f7adb887eb376a938dd48780e503b53a08 Author: Austin Seipp Date: Thu Nov 20 13:30:56 2014 -0600 Delete old-{time,locale} and haskell{98,2010} Summary: Depends on D510. This is the final blow and removes them from the tree completely. Signed-off-by: Austin Seipp Test Plan: I looked really hard but didn't see them. Reviewers: hvr, ekmett Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D511 GHC Trac Issues: #9590 >--------------------------------------------------------------- 86dda8f7adb887eb376a938dd48780e503b53a08 .gitmodules | 16 ---------------- libraries/haskell2010 | 1 - libraries/haskell98 | 1 - libraries/old-locale | 1 - libraries/old-time | 1 - 5 files changed, 20 deletions(-) diff --git a/.gitmodules b/.gitmodules index 66f4f37..662f6d6 100644 --- a/.gitmodules +++ b/.gitmodules @@ -70,14 +70,6 @@ path = libraries/filepath url = ../packages/filepath.git ignore = none -[submodule "libraries/haskell98"] - path = libraries/haskell98 - url = ../packages/haskell98.git - ignore = none -[submodule "libraries/haskell2010"] - path = libraries/haskell2010 - url = ../packages/haskell2010.git - ignore = none [submodule "libraries/hoopl"] path = libraries/hoopl url = ../packages/hoopl.git @@ -86,14 +78,6 @@ path = libraries/hpc url = ../packages/hpc.git ignore = none -[submodule "libraries/old-locale"] - path = libraries/old-locale - url = ../packages/old-locale.git - ignore = none -[submodule "libraries/old-time"] - path = libraries/old-time - url = ../packages/old-time.git - ignore = none [submodule "libraries/process"] path = libraries/process url = ../packages/process.git diff --git a/libraries/haskell2010 b/libraries/haskell2010 deleted file mode 160000 index a21abff..0000000 --- a/libraries/haskell2010 +++ /dev/null @@ -1 +0,0 @@ -Subproject commit a21abff3e385a85e1353aa720516e148865710a1 diff --git a/libraries/haskell98 b/libraries/haskell98 deleted file mode 160000 index cf064d9..0000000 --- a/libraries/haskell98 +++ /dev/null @@ -1 +0,0 @@ -Subproject commit cf064d954c511a2edddb5a55a1984d57ce36c407 diff --git a/libraries/old-locale b/libraries/old-locale deleted file mode 160000 index 6a0f699..0000000 --- a/libraries/old-locale +++ /dev/null @@ -1 +0,0 @@ -Subproject commit 6a0f699014a61c23e84036a6fcce97ecc8562342 diff --git a/libraries/old-time b/libraries/old-time deleted file mode 160000 index 539e4ec..0000000 --- a/libraries/old-time +++ /dev/null @@ -1 +0,0 @@ -Subproject commit 539e4ec39368177b83398f9a3cdf7f63814e883d From git at git.haskell.org Fri Nov 21 04:21:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 04:21:41 +0000 (UTC) Subject: [commit: ghc] master: Hide `Data.OldList` module (e888b94) Message-ID: <20141121042141.486B33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e888b943396c21db74ba2fc69bf3a89e2473ea2b/ghc >--------------------------------------------------------------- commit e888b943396c21db74ba2fc69bf3a89e2473ea2b Author: Herbert Valerio Riedel Date: Thu Nov 20 22:21:06 2014 -0600 Hide `Data.OldList` module Summary: The `Data.OldList` module was originally created in 3daf0023d2dcf7caf85d61f2dc177f8e9421b2fd to provide a way to access the original list-specialised functions from `Data.List`. It was also made an exposed module in order to facilitate adapting the `haskell2010`/`haskell98` packages. However, since the `haskell2010`/`haskell98` packages were dropped, we no longer need to expose `Data.OldList`. Depends on D511 Reviewers: ekmett, austin Reviewed By: ekmett, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D513 >--------------------------------------------------------------- e888b943396c21db74ba2fc69bf3a89e2473ea2b libraries/base/base.cabal | 2 +- libraries/base/changelog.md | 4 ---- libraries/base/tests/foldableArray.hs | 2 +- testsuite/tests/ghci/scripts/ghci008.stdout | 4 ++-- testsuite/tests/module/mod106.hs | 2 +- testsuite/tests/parser/should_fail/readFail003.hs | 2 +- testsuite/tests/rename/should_compile/T7963a.hs | 2 +- testsuite/tests/rename/should_fail/rnfail040.stderr | 2 +- testsuite/tests/simplCore/should_compile/T7360.hs | 2 +- testsuite/tests/typecheck/should_compile/faxen.hs | 2 +- testsuite/tests/typecheck/should_fail/mc21.hs | 4 ++-- testsuite/tests/typecheck/should_fail/mc24.hs | 4 ++-- 12 files changed, 14 insertions(+), 18 deletions(-) diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal index c3f4d28..ca619ca 100644 --- a/libraries/base/base.cabal +++ b/libraries/base/base.cabal @@ -154,7 +154,6 @@ Library Data.List Data.Maybe Data.Monoid - Data.OldList Data.Ord Data.Proxy Data.Ratio @@ -292,6 +291,7 @@ Library other-modules: Control.Monad.ST.Imp Control.Monad.ST.Lazy.Imp + Data.OldList Foreign.ForeignPtr.Imp System.Environment.ExecutablePath diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index c5047ce..f6a5016 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -71,10 +71,6 @@ * Generalise `Control.Monad.{foldM,foldM_}` to `Foldable` - * New module `Data.OldList` containing only list-specialised versions of - the functions from `Data.List` (in other words, `Data.OldList` corresponds - to `base-4.7.0.1`'s `Data.List`) - * `foldr2` (together with `zip` and `zipWith`) is made a bit stricter in the second argument, so that the fusion RULES for it do not change the semantics. (#9596) diff --git a/libraries/base/tests/foldableArray.hs b/libraries/base/tests/foldableArray.hs index 5a5041f..9c87571 100644 --- a/libraries/base/tests/foldableArray.hs +++ b/libraries/base/tests/foldableArray.hs @@ -16,7 +16,7 @@ import Control.DeepSeq #if __GLASGOW_HASKELL__ < 709 import qualified Data.List as L #else -import qualified Data.OldList as L +import qualified GHC.List as L #endif data BadElementException = BadFirst | BadLast deriving (Show, Typeable, Eq) diff --git a/testsuite/tests/ghci/scripts/ghci008.stdout b/testsuite/tests/ghci/scripts/ghci008.stdout index 057e9b2..9d9c26e 100644 --- a/testsuite/tests/ghci/scripts/ghci008.stdout +++ b/testsuite/tests/ghci/scripts/ghci008.stdout @@ -32,5 +32,5 @@ class (RealFrac a, Floating a) => RealFloat a where -- Defined in ?GHC.Float? instance RealFloat Float -- Defined in ?GHC.Float? instance RealFloat Double -- Defined in ?GHC.Float? -Data.OldList.isPrefixOf :: Eq a => [a] -> [a] -> Bool - -- Defined in ?Data.OldList? +base-4.8.0.0:Data.OldList.isPrefixOf :: Eq a => [a] -> [a] -> Bool + -- Defined in ?base-4.8.0.0:Data.OldList? diff --git a/testsuite/tests/module/mod106.hs b/testsuite/tests/module/mod106.hs index b505971..7fae66d 100644 --- a/testsuite/tests/module/mod106.hs +++ b/testsuite/tests/module/mod106.hs @@ -1,7 +1,7 @@ -- !!! local aliases module M where -import qualified Data.OldList as M +import qualified GHC.List as M import qualified Data.Maybe as M x = M.length diff --git a/testsuite/tests/parser/should_fail/readFail003.hs b/testsuite/tests/parser/should_fail/readFail003.hs index 343e1f0..8a60e8e 100644 --- a/testsuite/tests/parser/should_fail/readFail003.hs +++ b/testsuite/tests/parser/should_fail/readFail003.hs @@ -1,6 +1,6 @@ -- !!! Irrefutable patterns + guards module Read003 where -import Data.OldList; import Prelude hiding (null) +import GHC.List; import Prelude hiding (null) ~(a,b,c) | nullity b = a | nullity c = a | otherwise = a diff --git a/testsuite/tests/rename/should_compile/T7963a.hs b/testsuite/tests/rename/should_compile/T7963a.hs index fc8004d..25ac408 100644 --- a/testsuite/tests/rename/should_compile/T7963a.hs +++ b/testsuite/tests/rename/should_compile/T7963a.hs @@ -1,7 +1,7 @@ module T7963a where import Prelude () -import Data.OldList +import GHC.List unlines = concat diff --git a/testsuite/tests/rename/should_fail/rnfail040.stderr b/testsuite/tests/rename/should_fail/rnfail040.stderr index 80fad23..c3faa92 100644 --- a/testsuite/tests/rename/should_fail/rnfail040.stderr +++ b/testsuite/tests/rename/should_fail/rnfail040.stderr @@ -3,7 +3,7 @@ rnfail040.hs:7:12: Conflicting exports for ?nub?: ?module M? exports ?M.nub? imported from ?Data.List? at rnfail040.hs:10:2-22 - (and originally defined in ?Data.OldList?) + (and originally defined in ?base-4.8.0.0:Data.OldList?) ?module M? exports ?T.nub? imported from ?Rnfail040_A? at rnfail040.hs:11:2-24 (and originally defined at Rnfail040_A.hs:2:3-5) diff --git a/testsuite/tests/simplCore/should_compile/T7360.hs b/testsuite/tests/simplCore/should_compile/T7360.hs index 67c5e72..4e4703c 100644 --- a/testsuite/tests/simplCore/should_compile/T7360.hs +++ b/testsuite/tests/simplCore/should_compile/T7360.hs @@ -3,7 +3,7 @@ module T7360 where -import Data.OldList as L +import GHC.List as L data Foo = Foo1 | Foo2 | Foo3 !Int diff --git a/testsuite/tests/typecheck/should_compile/faxen.hs b/testsuite/tests/typecheck/should_compile/faxen.hs index f65ee71..8ad56c6 100644 --- a/testsuite/tests/typecheck/should_compile/faxen.hs +++ b/testsuite/tests/typecheck/should_compile/faxen.hs @@ -6,7 +6,7 @@ module ShouldCompile where -import Data.OldList (null) +import GHC.List (null) import Prelude hiding (null) class HasEmpty a where diff --git a/testsuite/tests/typecheck/should_fail/mc21.hs b/testsuite/tests/typecheck/should_fail/mc21.hs index adb4b91..8c13a66 100644 --- a/testsuite/tests/typecheck/should_fail/mc21.hs +++ b/testsuite/tests/typecheck/should_fail/mc21.hs @@ -3,11 +3,11 @@ {-# OPTIONS_GHC -XMonadComprehensions -XTransformListComp #-} module ShouldFail where import GHC.Exts( the ) -import Data.OldList +import GHC.List data Unorderable = Gnorf | Pinky | Brain -foo = [ Data.OldList.length x +foo = [ GHC.List.length x | x <- [Gnorf, Brain] , then group using take 5 ] diff --git a/testsuite/tests/typecheck/should_fail/mc24.hs b/testsuite/tests/typecheck/should_fail/mc24.hs index 281f4ad..e5d8099 100644 --- a/testsuite/tests/typecheck/should_fail/mc24.hs +++ b/testsuite/tests/typecheck/should_fail/mc24.hs @@ -3,9 +3,9 @@ {-# OPTIONS_GHC -XMonadComprehensions -XTransformListComp #-} module ShouldFail where -import Data.OldList +import GHC.List -foo = [ Data.OldList.length x +foo = [ GHC.List.length x | x <- [1..10] , then group by x using take 2 ] From git at git.haskell.org Fri Nov 21 04:43:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 04:43:56 +0000 (UTC) Subject: [commit: ghc] master: Export scanl' from Data.OldList and Data.List (f60eeb4) Message-ID: <20141121044356.022463A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f60eeb41ab48e73ea49fba64a745ddc4a6b8c085/ghc >--------------------------------------------------------------- commit f60eeb41ab48e73ea49fba64a745ddc4a6b8c085 Author: David Feuer Date: Thu Nov 20 22:38:57 2014 -0600 Export scanl' from Data.OldList and Data.List Summary: Fixes #9368 Reviewers: nomeata, hvr, ekmett, austin Reviewed By: ekmett, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D498 GHC Trac Issues: #9368 >--------------------------------------------------------------- f60eeb41ab48e73ea49fba64a745ddc4a6b8c085 libraries/base/Data/List.hs | 1 + libraries/base/Data/OldList.hs | 1 + libraries/base/changelog.md | 3 +++ 3 files changed, 5 insertions(+) diff --git a/libraries/base/Data/List.hs b/libraries/base/Data/List.hs index 4f99926..7919244 100644 --- a/libraries/base/Data/List.hs +++ b/libraries/base/Data/List.hs @@ -65,6 +65,7 @@ module Data.List -- ** Scans , scanl + , scanl' , scanl1 , scanr , scanr1 diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index 551b8be..eb9f1cc 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -65,6 +65,7 @@ module Data.OldList -- ** Scans , scanl + , scanl' , scanl1 , scanr , scanr1 diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index f6a5016..56bfc31 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -96,6 +96,9 @@ * New module `Data.Functor.Identity` (previously provided by `transformers` package). (#9664) + * Add `scanl'`, a strictly accumulating version of `scanl`, to `Data.List` + and `Data.OldList`. (#9368) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 From git at git.haskell.org Fri Nov 21 04:43:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 04:43:59 +0000 (UTC) Subject: [commit: ghc] master: Add flag `-fwarn-missing-exported-sigs` (067f1e4) Message-ID: <20141121044359.24F7F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/067f1e4f20efc824badbac54da2f9484090cb39b/ghc >--------------------------------------------------------------- commit 067f1e4f20efc824badbac54da2f9484090cb39b Author: Eric Seidel Date: Thu Nov 20 22:39:32 2014 -0600 Add flag `-fwarn-missing-exported-sigs` Summary: add `-fwarn-missing-exported-sigs` to only warn about missing signatures if the name is exported Test Plan: validate, see testsuite/tests/warnings/should_compile/T2526.hs Reviewers: ezyang, austin, thomie Reviewed By: austin, thomie Subscribers: ezyang, thomie, carter Differential Revision: https://phabricator.haskell.org/D482 GHC Trac Issues: #2526 Conflicts: docs/users_guide/7.10.1-notes.xml >--------------------------------------------------------------- 067f1e4f20efc824badbac54da2f9484090cb39b compiler/main/DynFlags.hs | 2 ++ compiler/typecheck/TcHsSyn.lhs | 22 ++++++++++++++++++---- compiler/typecheck/TcRnDriver.lhs | 17 ++++++++++++----- docs/users_guide/7.10.1-notes.xml | 10 ++++++++++ docs/users_guide/flags.xml | 7 +++++++ docs/users_guide/using.xml | 15 +++++++++++++++ testsuite/tests/warnings/should_compile/T2526.hs | 7 +++++++ .../tests/warnings/should_compile/T2526.stderr | 3 +++ testsuite/tests/warnings/should_compile/all.T | 2 ++ 9 files changed, 76 insertions(+), 9 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 067f1e4f20efc824badbac54da2f9484090cb39b From git at git.haskell.org Fri Nov 21 04:44:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 04:44:02 +0000 (UTC) Subject: [commit: ghc] master: Implement #5462 (deriving clause for arbitrary classes) (7ed482d) Message-ID: <20141121044402.D75443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7ed482d909556c1b969185921e27e3fe30c2fe86/ghc >--------------------------------------------------------------- commit 7ed482d909556c1b969185921e27e3fe30c2fe86 Author: Jose Pedro Magalhaes Date: Thu Nov 20 22:41:28 2014 -0600 Implement #5462 (deriving clause for arbitrary classes) Summary: (this has been submitted on behalf on @dreixel) Reviewers: simonpj, hvr, austin Reviewed By: simonpj, austin Subscribers: goldfire, thomie, carter, dreixel Differential Revision: https://phabricator.haskell.org/D476 GHC Trac Issues: #5462 >--------------------------------------------------------------- 7ed482d909556c1b969185921e27e3fe30c2fe86 compiler/basicTypes/BasicTypes.lhs | 1 + compiler/main/DynFlags.hs | 2 + compiler/typecheck/TcDeriv.lhs | 84 ++++++++++++++++----- compiler/typecheck/TcGenDeriv.lhs | 27 ++++++- docs/users_guide/flags.xml | 7 ++ docs/users_guide/glasgow_exts.xml | 26 ++++++- testsuite/tests/driver/T4437.hs | 1 + testsuite/tests/generics/GEnum/Enum.hs | 87 ++++++++++++++++++++++ testsuite/tests/generics/GEq/GEq1A.hs | 3 +- testsuite/tests/generics/T5462No1.hs | 27 +++++++ testsuite/tests/generics/T5462No1.stderr | 20 +++++ testsuite/tests/generics/T5462Yes1.hs | 48 ++++++++++++ testsuite/tests/generics/T5462Yes1.stdout | 1 + testsuite/tests/generics/T5462Yes2.hs | 37 +++++++++ .../T5149.stdout => generics/T5462Yes2.stdout} | 0 testsuite/tests/generics/all.T | 12 ++- testsuite/tests/module/mod53.stderr | 1 + 17 files changed, 357 insertions(+), 27 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7ed482d909556c1b969185921e27e3fe30c2fe86 From git at git.haskell.org Fri Nov 21 05:10:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 05:10:05 +0000 (UTC) Subject: [commit: ghc] branch 'wip/merge' created Message-ID: <20141121051005.62D0D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/merge Referencing: d49f1537714d82df16ca1611d996032b428b5581 From git at git.haskell.org Fri Nov 21 05:10:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 05:10:08 +0000 (UTC) Subject: [commit: ghc] wip/merge: AST changes to prepare for API annotations, for #9628 (d49f153) Message-ID: <20141121051008.2BED63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/d49f1537714d82df16ca1611d996032b428b5581/ghc >--------------------------------------------------------------- commit d49f1537714d82df16ca1611d996032b428b5581 Author: Alan Zimmerman Date: Thu Nov 20 22:55:09 2014 -0600 AST changes to prepare for API annotations, for #9628 Summary: AST changes to prepare for API annotations Add locations to parts of the AST so that API annotations can then be added. The outline of the whole process is captured here https://ghc.haskell.org/trac/ghc/wiki/GhcAstAnnotations Test Plan: sh ./validate Reviewers: austin, simonpj Reviewed By: simonpj Subscribers: thomie, goldfire, carter Differential Revision: https://phabricator.haskell.org/D426 GHC Trac Issues: #9628 Conflicts: compiler/parser/RdrHsSyn.hs >--------------------------------------------------------------- d49f1537714d82df16ca1611d996032b428b5581 compiler/basicTypes/BasicTypes.lhs | 9 +- compiler/deSugar/Check.lhs | 8 +- compiler/deSugar/Coverage.lhs | 11 +- compiler/deSugar/Desugar.lhs | 8 +- compiler/deSugar/DsExpr.lhs | 18 +- compiler/deSugar/DsForeign.lhs | 7 +- compiler/deSugar/DsMeta.hs | 100 +++++----- compiler/deSugar/Match.lhs | 4 +- compiler/deSugar/MatchCon.lhs | 9 +- compiler/hsSyn/Convert.lhs | 55 +++--- compiler/hsSyn/HsBinds.lhs | 11 +- compiler/hsSyn/HsDecls.lhs | 104 +++++++---- compiler/hsSyn/HsExpr.lhs | 14 +- compiler/hsSyn/HsImpExp.lhs | 51 +++--- compiler/hsSyn/HsPat.lhs | 9 +- compiler/hsSyn/HsSyn.lhs | 9 +- compiler/hsSyn/HsTypes.lhs | 21 ++- compiler/hsSyn/HsUtils.lhs | 18 +- compiler/main/HeaderInfo.hs | 3 +- compiler/main/HscMain.hs | 4 +- compiler/main/HscStats.hs | 9 +- compiler/parser/HaddockUtils.hs | 8 +- compiler/parser/Parser.y | 204 +++++++++++---------- compiler/parser/RdrHsSyn.hs | 94 +++++----- compiler/rename/RnBinds.lhs | 25 ++- compiler/rename/RnEnv.lhs | 9 +- compiler/rename/RnExpr.lhs | 12 +- compiler/rename/RnNames.lhs | 129 +++++++------ compiler/rename/RnPat.lhs | 32 ++-- compiler/rename/RnSource.lhs | 126 ++++++------- compiler/rename/RnTypes.lhs | 18 +- compiler/typecheck/TcBinds.lhs | 25 +-- compiler/typecheck/TcDeriv.lhs | 13 +- compiler/typecheck/TcExpr.lhs | 20 +- compiler/typecheck/TcForeign.lhs | 19 +- compiler/typecheck/TcHsSyn.lhs | 26 +-- compiler/typecheck/TcInstDcls.lhs | 9 +- compiler/typecheck/TcPat.lhs | 7 +- compiler/typecheck/TcPatSyn.lhs | 6 +- compiler/typecheck/TcRnDriver.lhs | 6 +- compiler/typecheck/TcRules.lhs | 19 +- compiler/typecheck/TcTyClsDecls.lhs | 129 +++++++++---- compiler/utils/Binary.hs | 38 ++++ ghc/InteractiveUI.hs | 7 +- .../haddock/haddock_examples/haddock.Test.stderr | 6 +- utils/ghctags/Main.hs | 2 +- utils/haddock | 2 +- 47 files changed, 858 insertions(+), 615 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d49f1537714d82df16ca1611d996032b428b5581 From git at git.haskell.org Fri Nov 21 05:50:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 05:50:28 +0000 (UTC) Subject: [commit: ghc] wip/merge: Revert change to alias handling in ppLlvmGlobal introduced in d87fa34, which requires LLVM 3.6. (c6322ee) Message-ID: <20141121055028.6BFB43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/c6322eebea61dd29d0dab698cb89334596851b9d/ghc >--------------------------------------------------------------- commit c6322eebea61dd29d0dab698cb89334596851b9d Author: Luke Iannini Date: Thu Nov 20 21:10:57 2014 -0800 Revert change to alias handling in ppLlvmGlobal introduced in d87fa34, which requires LLVM 3.6. Signed-off-by: Austin Seipp >--------------------------------------------------------------- c6322eebea61dd29d0dab698cb89334596851b9d compiler/llvmGen/Llvm/PpLlvm.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index cdc407c..7307725 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -80,7 +80,7 @@ ppLlvmGlobal (LMGlobal var@(LMGlobalVar _ _ link x a c) dat) = const_link = case c of Global -> ppr link <+> text "global" Constant -> ppr link <+> text "constant" - Alias -> ppr link <+> text "alias" + Alias -> text "alias" <+> ppr link in ppAssignment var $ const_link <+> rhs <> sect <> align $+$ newLine From git at git.haskell.org Fri Nov 21 05:50:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 05:50:31 +0000 (UTC) Subject: [commit: ghc] wip/merge: ghc allow --show-options and --interactive together (417809b) Message-ID: <20141121055031.1C4513A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/merge Link : http://ghc.haskell.org/trac/ghc/changeset/417809baaf7d1fc6a7c708fa195ace277059c3d3/ghc >--------------------------------------------------------------- commit 417809baaf7d1fc6a7c708fa195ace277059c3d3 Author: Lennart Kolmodin Date: Thu Nov 20 23:28:34 2014 -0600 ghc allow --show-options and --interactive together Summary: Previously --show-options showed all options that GHC accepts. Now, it'll only show the options that have effect in non-interactive modes. This change also adds support for using --interactive together with --show-options, making it show all options that have effect in the interactive mode. The CmdLineParser is updated to know about ghc modes, and then each flag is annotated with which mode it has effect. This fixes #9259. Test Plan: Try out --show-options with --interactive on the command line. With and without --interactive should give different results. Reviewers: austin Reviewed By: austin Subscribers: jstolarek, thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D337 GHC Trac Issues: #9259 Conflicts: compiler/main/DynFlags.hs >--------------------------------------------------------------- 417809baaf7d1fc6a7c708fa195ace277059c3d3 compiler/main/CmdLineParser.hs | 28 +- compiler/main/DynFlags.hs | 1186 ++++++++++++++++++++------------------- compiler/main/StaticFlags.hs | 8 +- compiler/typecheck/TcDeriv.lhs | 2 +- ghc/InteractiveUI.hs | 22 +- ghc/Main.hs | 89 +-- testsuite/tests/driver/T4437.hs | 2 +- 7 files changed, 706 insertions(+), 631 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 417809baaf7d1fc6a7c708fa195ace277059c3d3 From git at git.haskell.org Fri Nov 21 06:23:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 06:23:19 +0000 (UTC) Subject: [commit: ghc] master: Unbreak build (fallout from 067f1e4f20e) (27f9c74) Message-ID: <20141121062319.7DF973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/27f9c74630da7ace758c357e6421cc35cb5bebfc/ghc >--------------------------------------------------------------- commit 27f9c74630da7ace758c357e6421cc35cb5bebfc Author: Austin Seipp Date: Fri Nov 21 00:23:40 2014 -0600 Unbreak build (fallout from 067f1e4f20e) Signed-off-by: Austin Seipp >--------------------------------------------------------------- 27f9c74630da7ace758c357e6421cc35cb5bebfc docs/users_guide/7.10.1-notes.xml | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 4b82329..40a5ac0 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -127,7 +127,6 @@ -<<<<<<< HEAD Many more options have learned to respect the . For example you can use with @@ -144,7 +143,9 @@ solver, to add new functionality to GHC's typechecker. See for more details. -======= + + + A new warning flag, has been added. The behavior is similar to @@ -152,7 +153,6 @@ flag exported values. This flag takes precedence over so it can be used in conjunction with . ->>>>>>> 0551cf1... Add flag `-fwarn-missing-exported-sigs` From git at git.haskell.org Fri Nov 21 06:24:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 06:24:30 +0000 (UTC) Subject: [commit: ghc] master: Revert change to alias handling in ppLlvmGlobal introduced in d87fa34, which requires LLVM 3.6. (fec1c30) Message-ID: <20141121062430.D6E4E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fec1c3091b43f316ae7e683ed72b3ec175d9fd6e/ghc >--------------------------------------------------------------- commit fec1c3091b43f316ae7e683ed72b3ec175d9fd6e Author: Luke Iannini Date: Thu Nov 20 21:10:57 2014 -0800 Revert change to alias handling in ppLlvmGlobal introduced in d87fa34, which requires LLVM 3.6. Signed-off-by: Austin Seipp >--------------------------------------------------------------- fec1c3091b43f316ae7e683ed72b3ec175d9fd6e compiler/llvmGen/Llvm/PpLlvm.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index cdc407c..7307725 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -80,7 +80,7 @@ ppLlvmGlobal (LMGlobal var@(LMGlobalVar _ _ link x a c) dat) = const_link = case c of Global -> ppr link <+> text "global" Constant -> ppr link <+> text "constant" - Alias -> ppr link <+> text "alias" + Alias -> text "alias" <+> ppr link in ppAssignment var $ const_link <+> rhs <> sect <> align $+$ newLine From git at git.haskell.org Fri Nov 21 10:08:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 10:08:21 +0000 (UTC) Subject: [commit: ghc] master: Rewrite Note [Deriving any class] (b0dd347) Message-ID: <20141121100821.6A49D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b0dd34756613210873ed940d58027f61a492aeda/ghc >--------------------------------------------------------------- commit b0dd34756613210873ed940d58027f61a492aeda Author: Joachim Breitner Date: Fri Nov 21 11:07:40 2014 +0100 Rewrite Note [Deriving any class] Phrases like ?Currently, you can...? are going to sound strange in a few years; I rephrased the note to sound less like a proposal and more like an explanation. >--------------------------------------------------------------- b0dd34756613210873ed940d58027f61a492aeda compiler/typecheck/TcDeriv.lhs | 32 ++++++++++++++++++-------------- 1 file changed, 18 insertions(+), 14 deletions(-) diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index c76d19e..b561653 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -1172,30 +1172,34 @@ Specifically, we use TcGenDeriv.box_if_necy to box the Int# into an Int Note [Deriving any class] ~~~~~~~~~~~~~~~~~~~~~~~~~ -Currently, you can use a deriving clause, or standalone-deriving declaration, -only for: - * a built-in class like Eq or Show, for which GHC knows how to generate - the instance code - * a newtype, via the "newtype-deriving" mechanism. +Classic uses of a deriving clause, or a standalone-deriving declaration, are +for: + * a built-in class like Eq or Show, for which GHC knows how to generate + the instance code + * a newtype, via the mechanism enabled by GeneralizedNewtypeDeriving -However, with GHC.Generics we can write this: +The DeriveAnyClass extension adds a third way to derive instances, based on +empty instance declarations. + +The canonical use case is in combination with GHC.Generics and default method +signatures. These allow us have have instance declarations be empty, but still +useful, e.g. data T a = ...blah..blah... deriving( Generic ) instance C a => C (T a) -- No 'where' clause -where C is some "random" user-defined class. Usually, an instance decl with no -'where' clause would be pretty useless, but now that we have default method -signatures, in conjunction with deriving( Generic ), the instance can be useful. +where C is some "random" user-defined class. -That in turn leads to a desire to say +This boilerplate code can be replaced by the more compact data T a = ...blah..blah... deriving( Generic, C ) -which is even more compact. That is what DeriveAnyClass implements. This is -not restricted to Generics; any class can be derived, simply giving rise to -an empty instance. +if DeriveAnyClass is enabled. + +This is not restricted to Generics; any class can be derived, simply giving +rise to an empty instance. -The only thing left to answer is how to determine the context (in case of +Unfortunately, it is not clear how to determine the context (in case of standard deriving; in standalone deriving, the user provides the context). GHC uses the same heuristic for figuring out the class context that it uses for Eq in the case of *-kinded classes, and for Functor in the case of From git at git.haskell.org Fri Nov 21 13:02:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:02:55 +0000 (UTC) Subject: [commit: ghc] master: Comments only (eac9bbe) Message-ID: <20141121130255.5AC4C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eac9bbecdcbabdf2e6c7f3b2a14dc9eef0b86515/ghc >--------------------------------------------------------------- commit eac9bbecdcbabdf2e6c7f3b2a14dc9eef0b86515 Author: Simon Peyton Jones Date: Thu Nov 20 17:16:30 2014 +0000 Comments only >--------------------------------------------------------------- eac9bbecdcbabdf2e6c7f3b2a14dc9eef0b86515 compiler/basicTypes/MkId.lhs | 2 +- compiler/main/HscTypes.lhs | 2 +- compiler/rename/RnBinds.lhs | 1 - 3 files changed, 2 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index b32a2b7..de7e4ce 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -360,7 +360,7 @@ dictSelRule val_index n_ty_args _ id_unf _ args %************************************************************************ %* * - Boxing and unboxing + Data constructors %* * %************************************************************************ diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs index 4d1cccb..57a5015 100644 --- a/compiler/main/HscTypes.lhs +++ b/compiler/main/HscTypes.lhs @@ -1573,7 +1573,7 @@ implicitConLikeThings (RealDataCon dc) implicitConLikeThings (PatSynCon {}) = [] -- Pattern synonyms have no implicit Ids; the wrapper and matcher -- are not "implicit"; they are simply new top-level bindings, - -- and they have their own declaration in an interface fiel + -- and they have their own declaration in an interface file implicitClassThings :: Class -> [TyThing] implicitClassThings cl diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index 80239e9..e0f5d0a 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -598,7 +598,6 @@ rnPatSynBind _sig_fn bind@(PSB { psb_id = L _ name {- Note [Pattern synonym wrappers don't yield dependencies] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ - When renaming a pattern synonym that has an explicit wrapper, references in the wrapper definition should not be used when calculating dependencies. For example, consider the following pattern From git at git.haskell.org Fri Nov 21 13:02:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:02:57 +0000 (UTC) Subject: [commit: ghc] master: Rejig builders for pattern synonyms, especially unlifted ones (e876208) Message-ID: <20141121130257.F1BBC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e876208117a34fb58f7f1e470de2f954b3ca303d/ghc >--------------------------------------------------------------- commit e876208117a34fb58f7f1e470de2f954b3ca303d Author: Simon Peyton Jones Date: Fri Nov 21 10:04:09 2014 +0000 Rejig builders for pattern synonyms, especially unlifted ones When a pattern synonym is for an unlifted pattern, its "builder" would naturally be a top-level unlifted binding, which isn't allowed. So we give it an extra Void# argument. Our Plan A involved then making *two* Ids for these builders, with some consequential fuss in the desugarer. This was more pain than I liked, so I've re-jigged it. * There is just one builder for a pattern synonym. * It may have an extra Void# arg, but this decision is signalled by the Bool in the psBuilder field. I did the same for the psMatcher field. Both Bools are serialised into interface files, so there is absolutely no doubt whether that extra Void# argument is required. * I renamed "wrapper" to "builder". We have too may "wrappers" * In order to deal with typecchecking occurrences of P in expressions, I refactored the tcInferId code in TcExpr. All of this allowed me to revert 5fe872 "Apply compulsory unfoldings during desugaring, except for `seq` which is special." which turned out to be a rather messy hack in DsBinds >--------------------------------------------------------------- e876208117a34fb58f7f1e470de2f954b3ca303d compiler/basicTypes/PatSyn.lhs | 207 +++++++++++++++--------------- compiler/deSugar/DsExpr.lhs | 22 +--- compiler/deSugar/DsUtils.lhs | 10 +- compiler/iface/BuildTyCl.lhs | 8 +- compiler/iface/IfaceSyn.lhs | 12 +- compiler/iface/MkIface.lhs | 9 +- compiler/iface/TcIface.lhs | 65 ++-------- compiler/typecheck/TcBinds.lhs | 14 +-- compiler/typecheck/TcExpr.lhs | 162 ++++++++---------------- compiler/typecheck/TcPatSyn.lhs | 237 +++++++++++++++++++++-------------- compiler/typecheck/TcPatSyn.lhs-boot | 4 +- compiler/typecheck/TcRnMonad.lhs | 5 + 12 files changed, 338 insertions(+), 417 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e876208117a34fb58f7f1e470de2f954b3ca303d From git at git.haskell.org Fri Nov 21 13:03:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:03:00 +0000 (UTC) Subject: [commit: ghc] master: Move all the zonk/tidy stuff together into TcMType (refactoring only) (76f5f11) Message-ID: <20141121130300.9C89A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/76f5f11af42700e3a452c5e03e4ee0235cb08bf6/ghc >--------------------------------------------------------------- commit 76f5f11af42700e3a452c5e03e4ee0235cb08bf6 Author: Simon Peyton Jones Date: Fri Nov 21 10:15:04 2014 +0000 Move all the zonk/tidy stuff together into TcMType (refactoring only) >--------------------------------------------------------------- 76f5f11af42700e3a452c5e03e4ee0235cb08bf6 compiler/typecheck/Inst.lhs | 47 --------------------- compiler/typecheck/TcErrors.lhs | 36 ----------------- compiler/typecheck/TcMType.lhs | 90 ++++++++++++++++++++++++++++++++++++++++- 3 files changed, 88 insertions(+), 85 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 76f5f11af42700e3a452c5e03e4ee0235cb08bf6 From git at git.haskell.org Fri Nov 21 13:03:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:03:03 +0000 (UTC) Subject: [commit: ghc] master: Implement full co/contra-variant subsumption checking (fixes Trac #9569) (b685542) Message-ID: <20141121130303.44E9D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b6855422fd532e5988fc98764c5cc47acbefbfb8/ghc >--------------------------------------------------------------- commit b6855422fd532e5988fc98764c5cc47acbefbfb8 Author: Simon Peyton Jones Date: Fri Nov 21 10:58:10 2014 +0000 Implement full co/contra-variant subsumption checking (fixes Trac #9569) This is a pretty big patch, but which substantially iproves the subsumption check. Trac #9569 was the presenting example, showing how type inference could depend rather delicately on eta expansion. But there are other less exotic examples; see Note [Co/contra-variance of subsumption checking] in TcUnify. The driving change is to TcUnify.tcSubType. But also * HsWrapper gets a new constructor WpFun, which behaves very like CoFun: if wrap1 :: exp_arg <= act_arg wrap2 :: act_res <= exp_res then WpFun wrap1 wrap2 : (act_arg -> arg_res) <= (exp_arg -> exp_res) * I generalised TcExp.tcApp to call tcSubType on the result, rather than tcUnifyType. I think this just makes it consistent with everything else, notably tcWrapResult. As usual I ended up doing some follow-on refactoring * AmbigOrigin is gone (in favour of TypeEqOrigin) * Combined BindPatSigCtxt and PatSigCxt into one * Improved a bit of error message generation >--------------------------------------------------------------- b6855422fd532e5988fc98764c5cc47acbefbfb8 compiler/deSugar/DsBinds.lhs | 9 +- compiler/deSugar/Match.lhs | 1 + compiler/typecheck/Inst.lhs | 14 +-- compiler/typecheck/TcBinds.lhs | 23 ++-- compiler/typecheck/TcErrors.lhs | 4 +- compiler/typecheck/TcEvidence.lhs | 42 +++++-- compiler/typecheck/TcExpr.lhs | 8 +- compiler/typecheck/TcHsSyn.lhs | 5 + compiler/typecheck/TcHsType.lhs | 41 ++++--- compiler/typecheck/TcInstDcls.lhs | 6 +- compiler/typecheck/TcPat.lhs | 8 +- compiler/typecheck/TcRnTypes.lhs | 8 -- compiler/typecheck/TcType.lhs | 56 +++++++--- compiler/typecheck/TcUnify.lhs | 223 +++++++++++++++++++++++++++++--------- compiler/typecheck/TcValidity.lhs | 14 +-- 15 files changed, 312 insertions(+), 150 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b6855422fd532e5988fc98764c5cc47acbefbfb8 From git at git.haskell.org Fri Nov 21 13:03:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:03:05 +0000 (UTC) Subject: [commit: ghc] master: Put the decision of when a unification variable can unify with a polytype (073119e) Message-ID: <20141121130305.E8E163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/073119e8e3eff54e64e2f89aa3a00dcf87b36ded/ghc >--------------------------------------------------------------- commit 073119e8e3eff54e64e2f89aa3a00dcf87b36ded Author: Simon Peyton Jones Date: Fri Nov 21 10:59:49 2014 +0000 Put the decision of when a unification variable can unify with a polytype This was being doing independently in two places. Now it's done in one place, TcType.canUnifyWithPolyType >--------------------------------------------------------------- 073119e8e3eff54e64e2f89aa3a00dcf87b36ded compiler/typecheck/TcType.lhs | 40 ++++++++++++++++++++++++++++++---------- compiler/typecheck/TcUnify.lhs | 26 +++----------------------- 2 files changed, 33 insertions(+), 33 deletions(-) diff --git a/compiler/typecheck/TcType.lhs b/compiler/typecheck/TcType.lhs index a9b44ab..5665730 100644 --- a/compiler/typecheck/TcType.lhs +++ b/compiler/typecheck/TcType.lhs @@ -41,6 +41,7 @@ module TcType ( metaTyVarUntouchables, setMetaTyVarUntouchables, metaTyVarUntouchables_maybe, isTouchableMetaTyVar, isTouchableOrFmv, isFloatedTouchableMetaTyVar, + canUnifyWithPolyType, -------------------------------- -- Builders @@ -1202,16 +1203,7 @@ occurCheckExpand dflags tv ty where details = ASSERT2( isTcTyVar tv, ppr tv ) tcTyVarDetails tv - impredicative - = case details of - MetaTv { mtv_info = ReturnTv } -> True - MetaTv { mtv_info = SigTv } -> False - MetaTv { mtv_info = TauTv } -> xopt Opt_ImpredicativeTypes dflags - || isOpenTypeKind (tyVarKind tv) - -- Note [OpenTypeKind accepts foralls] - -- in TcUnify - _other -> True - -- We can have non-meta tyvars in given constraints + impredicative = canUnifyWithPolyType dflags details (tyVarKind tv) -- Check 'ty' is a tyvar, or can be expanded into one go_sig_tv ty@(TyVarTy {}) = OC_OK ty @@ -1259,8 +1251,36 @@ occurCheckExpand dflags tv ty bad | Just ty' <- tcView ty -> go ty' | otherwise -> bad -- Failing that, try to expand a synonym + +canUnifyWithPolyType :: DynFlags -> TcTyVarDetails -> TcKind -> Bool +canUnifyWithPolyType dflags details kind + = case details of + MetaTv { mtv_info = ReturnTv } -> True -- See Note [ReturnTv] + MetaTv { mtv_info = SigTv } -> False + MetaTv { mtv_info = TauTv } -> xopt Opt_ImpredicativeTypes dflags + || isOpenTypeKind kind + -- Note [OpenTypeKind accepts foralls] + _other -> True + -- We can have non-meta tyvars in given constraints \end{code} +Note [OpenTypeKind accepts foralls] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Here is a common paradigm: + foo :: (forall a. a -> a) -> Int + foo = error "urk" +To make this work we need to instantiate 'error' with a polytype. +A similar case is + bar :: Bool -> (forall a. a->a) -> Int + bar True = \x. (x 3) + bar False = error "urk" +Here we need to instantiate 'error' with a polytype. + +But 'error' has an OpenTypeKind type variable, precisely so that +we can instantiate it with Int#. So we also allow such type variables +to be instantiate with foralls. It's a bit of a hack, but seems +straightforward. + %************************************************************************ %* * \subsection{Predicate types} diff --git a/compiler/typecheck/TcUnify.lhs b/compiler/typecheck/TcUnify.lhs index eb39038..966e564 100644 --- a/compiler/typecheck/TcUnify.lhs +++ b/compiler/typecheck/TcUnify.lhs @@ -1011,13 +1011,10 @@ checkTauTvUpdate dflags tv ty _ -> return Nothing | otherwise -> return (Just ty1) } where - info = ASSERT2( isMetaTyVar tv, ppr tv ) metaTyVarInfo tv - -- See Note [ReturnTv] in TcType + details = ASSERT2( isMetaTyVar tv, ppr tv ) tcTyVarDetails tv + info = mtv_info details is_return_tv = case info of { ReturnTv -> True; _ -> False } - - impredicative = xopt Opt_ImpredicativeTypes dflags - || isOpenTypeKind (tyVarKind tv) - -- Note [OpenTypeKind accepts foralls] + impredicative = canUnifyWithPolyType dflags details (tyVarKind tv) defer_me :: TcType -> Bool -- Checks for (a) occurrence of tv @@ -1031,23 +1028,6 @@ checkTauTvUpdate dflags tv ty defer_me (ForAllTy _ ty) = not impredicative || defer_me ty \end{code} -Note [OpenTypeKind accepts foralls] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Here is a common paradigm: - foo :: (forall a. a -> a) -> Int - foo = error "urk" -To make this work we need to instantiate 'error' with a polytype. -A similar case is - bar :: Bool -> (forall a. a->a) -> Int - bar True = \x. (x 3) - bar False = error "urk" -Here we need to instantiate 'error' with a polytype. - -But 'error' has an OpenTypeKind type variable, precisely so that -we can instantiate it with Int#. So we also allow such type variables -to be instantiate with foralls. It's a bit of a hack, but seems -straightforward. - Note [Conservative unification check] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When unifying (tv ~ rhs), w try to avoid creating deferred constraints From git at git.haskell.org Fri Nov 21 13:03:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:03:08 +0000 (UTC) Subject: [commit: ghc] master: Fix a latent promotion bug in TcSimplify.simplifyInfer (16d10ae) Message-ID: <20141121130308.7C7403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/16d10ae04b66a052fd54e30677ce7696dba53580/ghc >--------------------------------------------------------------- commit 16d10ae04b66a052fd54e30677ce7696dba53580 Author: Simon Peyton Jones Date: Fri Nov 21 11:06:12 2014 +0000 Fix a latent promotion bug in TcSimplify.simplifyInfer We weren't promoting enough type variables, with unpredictable consequences. The new code is, if anything, simpler. >--------------------------------------------------------------- 16d10ae04b66a052fd54e30677ce7696dba53580 compiler/typecheck/TcSimplify.lhs | 33 ++++++++++++++++++++------------- 1 file changed, 20 insertions(+), 13 deletions(-) diff --git a/compiler/typecheck/TcSimplify.lhs b/compiler/typecheck/TcSimplify.lhs index 8ec3591..ede529b 100644 --- a/compiler/typecheck/TcSimplify.lhs +++ b/compiler/typecheck/TcSimplify.lhs @@ -344,12 +344,13 @@ simplifyInfer rhs_untch apply_mr name_taus wanteds -- NB: quant_pred_candidates is already the fixpoint of any -- unifications that may have happened - ; zonked_tau_tvs <- TcM.zonkTyVarsAndFV (tyVarsOfTypes (map snd name_taus)) - ; (mono_tvs, qtvs, bound, mr_bites) <- decideQuantification apply_mr quant_pred_candidates zonked_tau_tvs + ; zonked_taus <- mapM (TcM.zonkTcType . snd) name_taus + ; let zonked_tau_tvs = tyVarsOfTypes zonked_taus + ; (promote_tvs, qtvs, bound, mr_bites) <- decideQuantification apply_mr quant_pred_candidates zonked_tau_tvs ; outer_untch <- TcRnMonad.getUntouchables ; runTcSWithEvBinds null_ev_binds_var $ -- runTcS just to get the types right :-( - mapM_ (promoteTyVar outer_untch) (varSetElems (zonked_tau_tvs `intersectVarSet` mono_tvs)) + mapM_ (promoteTyVar outer_untch) (varSetElems promote_tvs) ; let minimal_flat_preds = mkMinimalBySCs bound -- See Note [Minimize by Superclasses] @@ -373,8 +374,9 @@ simplifyInfer rhs_untch apply_mr name_taus wanteds ; traceTc "} simplifyInfer/produced residual implication for quantification" $ vcat [ ptext (sLit "quant_pred_candidates =") <+> ppr quant_pred_candidates + , ptext (sLit "zonked_taus") <+> ppr zonked_taus , ptext (sLit "zonked_tau_tvs=") <+> ppr zonked_tau_tvs - , ptext (sLit "mono_tvs=") <+> ppr mono_tvs + , ptext (sLit "promote_tvs=") <+> ppr promote_tvs , ptext (sLit "bound =") <+> ppr bound , ptext (sLit "minimal_bound =") <+> vcat [ ppr v <+> dcolon <+> ppr (idType v) | v <- minimal_bound_ev_vars] @@ -416,7 +418,7 @@ and the quantified constraints are empty. \begin{code} decideQuantification :: Bool -> [PredType] -> TcTyVarSet - -> TcM ( TcTyVarSet -- Do not quantify over these + -> TcM ( TcTyVarSet -- Promote these , [TcTyVar] -- Do quantify over these , [PredType] -- and these , Bool ) -- Did the MR bite? @@ -424,20 +426,25 @@ decideQuantification :: Bool -> [PredType] -> TcTyVarSet decideQuantification apply_mr constraints zonked_tau_tvs | apply_mr -- Apply the Monomorphism restriction = do { gbl_tvs <- tcGetGlobalTyVars - ; let constrained_tvs = tyVarsOfTypes constraints - mono_tvs = gbl_tvs `unionVarSet` constrained_tvs + ; let mono_tvs = gbl_tvs `unionVarSet` constrained_tvs mr_bites = constrained_tvs `intersectsVarSet` zonked_tau_tvs + promote_tvs = constrained_tvs `unionVarSet` (zonked_tau_tvs `intersectVarSet` gbl_tvs) ; qtvs <- quantifyTyVars mono_tvs zonked_tau_tvs - ; return (mono_tvs, qtvs, [], mr_bites) } + ; traceTc "decideQuantification 1" (vcat [ppr constraints, ppr gbl_tvs, ppr mono_tvs, ppr qtvs]) + ; return (promote_tvs, qtvs, [], mr_bites) } | otherwise = do { gbl_tvs <- tcGetGlobalTyVars - ; let mono_tvs = growThetaTyVars (filter isEqPred constraints) gbl_tvs - poly_qtvs = growThetaTyVars constraints zonked_tau_tvs - `minusVarSet` mono_tvs - theta = filter (quantifyPred poly_qtvs) constraints + ; let mono_tvs = growThetaTyVars (filter isEqPred constraints) gbl_tvs + poly_qtvs = growThetaTyVars constraints zonked_tau_tvs + `minusVarSet` mono_tvs + theta = filter (quantifyPred poly_qtvs) constraints + promote_tvs = mono_tvs `intersectVarSet` (constrained_tvs `unionVarSet` zonked_tau_tvs) ; qtvs <- quantifyTyVars mono_tvs poly_qtvs - ; return (mono_tvs, qtvs, theta, False) } + ; traceTc "decideQuantification 2" (vcat [ppr constraints, ppr gbl_tvs, ppr mono_tvs, ppr poly_qtvs, ppr qtvs, ppr theta]) + ; return (promote_tvs, qtvs, theta, False) } + where + constrained_tvs = tyVarsOfTypes constraints ------------------ quantifyPred :: TyVarSet -- Quantifying over these From git at git.haskell.org Fri Nov 21 13:03:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:03:11 +0000 (UTC) Subject: [commit: ghc] master: Remove TcMType from compiler_stage2_dll0_MODULES (5f39c4d) Message-ID: <20141121130311.1083E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5f39c4de78c4f75423789242423c8eea245a5e75/ghc >--------------------------------------------------------------- commit 5f39c4de78c4f75423789242423c8eea245a5e75 Author: Simon Peyton Jones Date: Fri Nov 21 11:07:57 2014 +0000 Remove TcMType from compiler_stage2_dll0_MODULES I can't say I really understand this DLL-split thing, but the build fails if I don't remove TcMType here. I've put this in a commit on its own, but it's a knock-on effect of the immediately preceding wave of typechecker changes >--------------------------------------------------------------- 5f39c4de78c4f75423789242423c8eea245a5e75 compiler/ghc.mk | 1 - 1 file changed, 1 deletion(-) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index c5b58e9..9716ef2 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -574,7 +574,6 @@ compiler_stage2_dll0_MODULES = \ StringBuffer \ TcEvidence \ TcIface \ - TcMType \ TcRnMonad \ TcRnTypes \ TcType \ From git at git.haskell.org Fri Nov 21 13:03:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:03:13 +0000 (UTC) Subject: [commit: ghc] master: Make the on-the-fly unifier defer forall/forall unification (0f5c163) Message-ID: <20141121130313.A1B2F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0f5c16370de2af82045d6ae8e64a3096241ceff1/ghc >--------------------------------------------------------------- commit 0f5c16370de2af82045d6ae8e64a3096241ceff1 Author: Simon Peyton Jones Date: Fri Nov 21 11:04:28 2014 +0000 Make the on-the-fly unifier defer forall/forall unification This has to be done by the full constraint solver anyway, and it's rare, so there's really no point in doing it twice. This change just deletes some (tricky) code. >--------------------------------------------------------------- 0f5c16370de2af82045d6ae8e64a3096241ceff1 compiler/typecheck/TcUnify.lhs | 26 +------------------------- 1 file changed, 1 insertion(+), 25 deletions(-) diff --git a/compiler/typecheck/TcUnify.lhs b/compiler/typecheck/TcUnify.lhs index 966e564..9e3e68d 100644 --- a/compiler/typecheck/TcUnify.lhs +++ b/compiler/typecheck/TcUnify.lhs @@ -759,11 +759,8 @@ uType origin orig_ty1 orig_ty2 = ASSERT( isDecomposableTyCon tc1 ) go_app (TyConApp tc1 ts1') t1' s2 t2 - go ty1 ty2 - | tcIsForAllTy ty1 || tcIsForAllTy ty2 - = unifySigmaTy origin ty1 ty2 - -- Anything else fails + -- E.g. unifying for-all types, which is relative unusual go ty1 ty2 = uType_defer origin ty1 ty2 -- failWithMisMatch origin ------------------ @@ -771,27 +768,6 @@ uType origin orig_ty1 orig_ty2 = do { co_s <- uType origin s1 s2 -- See Note [Unifying AppTy] ; co_t <- uType origin t1 t2 ; return $ mkTcAppCo co_s co_t } - -unifySigmaTy :: CtOrigin -> TcType -> TcType -> TcM TcCoercion -unifySigmaTy origin ty1 ty2 - = do { let (tvs1, body1) = tcSplitForAllTys ty1 - (tvs2, body2) = tcSplitForAllTys ty2 - - ; defer_or_continue (not (equalLength tvs1 tvs2)) $ do { - (subst1, skol_tvs) <- tcInstSkolTyVars tvs1 - -- Get location from monad, not from tvs1 - ; let tys = mkTyVarTys skol_tvs - phi1 = Type.substTy subst1 body1 - phi2 = Type.substTy (zipTopTvSubst tvs2 tys) body2 - skol_info = UnifyForAllSkol skol_tvs phi1 - - ; (ev_binds, co) <- checkConstraints skol_info skol_tvs [] $ - uType origin phi1 phi2 - - ; return (foldr mkTcForAllCo (TcLetCo ev_binds co) skol_tvs) } } - where - defer_or_continue True _ = uType_defer origin ty1 ty2 - defer_or_continue False m = m \end{code} Note [Care with type applications] From git at git.haskell.org Fri Nov 21 13:03:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:03:16 +0000 (UTC) Subject: [commit: ghc] master: Trac #9222 is actually an ambiguous type, now detected (b82410a) Message-ID: <20141121130316.7FD423A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b82410ab8908f1ec2a6aa14cce62948c92bcbce9/ghc >--------------------------------------------------------------- commit b82410ab8908f1ec2a6aa14cce62948c92bcbce9 Author: Simon Peyton Jones Date: Fri Nov 21 11:16:19 2014 +0000 Trac #9222 is actually an ambiguous type, now detected >--------------------------------------------------------------- b82410ab8908f1ec2a6aa14cce62948c92bcbce9 testsuite/tests/polykinds/T9222.hs | 6 ++++++ testsuite/tests/polykinds/T9222.stderr | 24 ++++++++++++++++++++++++ testsuite/tests/polykinds/all.T | 2 +- 3 files changed, 31 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/polykinds/T9222.hs b/testsuite/tests/polykinds/T9222.hs index df11251..8e46ccb 100644 --- a/testsuite/tests/polykinds/T9222.hs +++ b/testsuite/tests/polykinds/T9222.hs @@ -3,5 +3,11 @@ module T9222 where import Data.Proxy +-- Nov 2014: actually the type of Want is ambiguous if we +-- do the full co/contra thing for subtyping, +-- which we now do +-- So this program is erroneous. (But the original ticket was +-- a crash, and that's still fixed!) + data Want :: (i,j) -> * where Want :: (a ~ '(b,c) => Proxy b) -> Want a diff --git a/testsuite/tests/polykinds/T9222.stderr b/testsuite/tests/polykinds/T9222.stderr new file mode 100644 index 0000000..8e838e7 --- /dev/null +++ b/testsuite/tests/polykinds/T9222.stderr @@ -0,0 +1,24 @@ + +T9222.hs:13:3: + Couldn't match type ?b0? with ?b? + ?b0? is untouchable + inside the constraints (a ~ '(b0, c0)) + bound by the type of the constructor ?Want?: + (a ~ '(b0, c0)) => Proxy b0 + at T9222.hs:13:3 + ?b? is a rigid type variable bound by + the type of the constructor ?Want?: + ((a ~ '(b, c)) => Proxy b) -> Want a + at T9222.hs:13:3 + Expected type: '(b, c) + Actual type: a + In the ambiguity check for the type of the constructor ?Want?: + Want :: forall (k :: BOX) + (k1 :: BOX) + (a :: (,) k k1) + (b :: k) + (c :: k1). + ((a ~ '(b, c)) => Proxy b) -> Want a + To defer the ambiguity check to use sites, enable AllowAmbiguousTypes + In the definition of data constructor ?Want? + In the data declaration for ?Want? diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index 48b0e61..74718ab 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -102,7 +102,7 @@ test('T8705', normal, compile, ['']) test('T8985', normal, compile, ['']) test('T9106', normal, compile_fail, ['']) test('T9144', normal, compile_fail, ['']) -test('T9222', normal, compile, ['']) +test('T9222', normal, compile_fail, ['']) test('T9264', normal, compile, ['']) test('T9263', normal, run_command, ['$MAKE -s --no-print-directory T9263']) test('T9063', normal, compile, ['']) From git at git.haskell.org Fri Nov 21 13:03:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:03:19 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #9318 (5760eb5) Message-ID: <20141121130319.1F4523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5760eb598e0dfa451407195f15072204c15233ed/ghc >--------------------------------------------------------------- commit 5760eb598e0dfa451407195f15072204c15233ed Author: Simon Peyton Jones Date: Fri Nov 21 11:12:16 2014 +0000 Test Trac #9318 >--------------------------------------------------------------- 5760eb598e0dfa451407195f15072204c15233ed testsuite/tests/{typecheck => indexed-types}/should_fail/T9318.hs | 0 testsuite/tests/{typecheck => indexed-types}/should_fail/T9318.stderr | 0 testsuite/tests/indexed-types/should_fail/all.T | 1 + 3 files changed, 1 insertion(+) diff --git a/testsuite/tests/typecheck/should_fail/T9318.hs b/testsuite/tests/indexed-types/should_fail/T9318.hs similarity index 100% copy from testsuite/tests/typecheck/should_fail/T9318.hs copy to testsuite/tests/indexed-types/should_fail/T9318.hs diff --git a/testsuite/tests/typecheck/should_fail/T9318.stderr b/testsuite/tests/indexed-types/should_fail/T9318.stderr similarity index 100% copy from testsuite/tests/typecheck/should_fail/T9318.stderr copy to testsuite/tests/indexed-types/should_fail/T9318.stderr diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index 286360a..998193f 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -131,3 +131,4 @@ test('BadSock', normal, compile_fail, ['']) test('T9580', normal, multimod_compile_fail, ['T9580', '']) test('T9662', normal, compile_fail, ['']) test('T7862', normal, compile_fail, ['']) +test('T9318', normal, compile_fail, ['']) From git at git.haskell.org Fri Nov 21 13:03:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:03:22 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #9569 (230b013) Message-ID: <20141121130322.4E2EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/230b013b654508f77c5d8cec9d4de9b7c86e1370/ghc >--------------------------------------------------------------- commit 230b013b654508f77c5d8cec9d4de9b7c86e1370 Author: Simon Peyton Jones Date: Fri Nov 21 11:22:52 2014 +0000 Test Trac #9569 >--------------------------------------------------------------- 230b013b654508f77c5d8cec9d4de9b7c86e1370 testsuite/tests/polykinds/T9569.hs | 25 ++++++++++++++++++++++ testsuite/tests/polykinds/all.T | 1 + testsuite/tests/typecheck/should_compile/T9569a.hs | 11 ++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 4 files changed, 38 insertions(+) diff --git a/testsuite/tests/polykinds/T9569.hs b/testsuite/tests/polykinds/T9569.hs new file mode 100644 index 0000000..012d61f --- /dev/null +++ b/testsuite/tests/polykinds/T9569.hs @@ -0,0 +1,25 @@ +{-# LANGUAGE RankNTypes, ConstraintKinds, KindSignatures, DataKinds, TypeFamilies #-} +module T9569 where + +import GHC.Prim + +data Proxy (c :: Constraint) + +class Deferrable (c :: Constraint) where + defer :: Proxy c -> (c => a) -> a + +deferPair :: (Deferrable c1, Deferrable c2) => + Proxy (c1,c2) -> ((c1,c2) => a) -> a +deferPair = undefined + +instance (Deferrable c1, Deferrable c2) => Deferrable (c1,c2) where + -- defer p f = deferPair p f -- Succeeds + defer = deferPair -- Fails + +{- + [G] Deferrable c1, Deferrable c2 + + [W] Proxy (c1,c2) -> ((c1,c2) => a) -> a ~ Proxy (c1x,c2x) -> ((c1x,c2x) => ax) -> ax + [w] Deferrable c1x + [w] Deferrable c2x +-} \ No newline at end of file diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index 74718ab..e8e30c0 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -109,3 +109,4 @@ test('T9063', normal, compile, ['']) test('T9200', normal, compile, ['']) test('T9200b', normal, compile_fail, ['']) test('T9750', normal, compile, ['']) +test('T9569', normal, compile, ['']) diff --git a/testsuite/tests/typecheck/should_compile/T9569a.hs b/testsuite/tests/typecheck/should_compile/T9569a.hs new file mode 100644 index 0000000..3205cb1 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9569a.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE RankNTypes #-} +module T9569a where + +g :: (Int -> Int) -> Int +g f = f 4 + +f1 :: (forall a. a -> a) -> Int +f1 = g + +f2 :: (forall a. a -> a) -> Int +f2 x = g x diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index ea7d343..7e825d9 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -419,6 +419,7 @@ test('T8644', normal, compile, ['']) test('T8762', normal, compile, ['']) test('MutRec', normal, compile, ['']) test('T8856', normal, compile, ['']) +test('T9569a', normal, compile, ['']) test('T9117', normal, compile, ['']) test('T9117_2', expect_broken('9117'), compile, ['']) test('T9708', normal, compile_fail, ['']) From git at git.haskell.org Fri Nov 21 13:03:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:03:24 +0000 (UTC) Subject: [commit: ghc] master: Delete duplicated tests (e639120) Message-ID: <20141121130324.DB4B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e6391208347103f8c21a446fbc657e979051db54/ghc >--------------------------------------------------------------- commit e6391208347103f8c21a446fbc657e979051db54 Author: Simon Peyton Jones Date: Fri Nov 21 11:18:10 2014 +0000 Delete duplicated tests >--------------------------------------------------------------- e6391208347103f8c21a446fbc657e979051db54 testsuite/tests/typecheck/should_fail/all.T | 2 -- testsuite/tests/typecheck/should_fail/tcfail192.hs | 11 ----------- testsuite/tests/typecheck/should_fail/tcfail192.stderr | 9 --------- testsuite/tests/typecheck/should_fail/tcfail194.hs | 10 ---------- testsuite/tests/typecheck/should_fail/tcfail194.stderr | 9 --------- 5 files changed, 41 deletions(-) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 28709e8..96396d2 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -178,9 +178,7 @@ test('tcfail188', normal, compile, ['']) test('tcfail189', normal, compile_fail, ['']) test('tcfail190', normal, compile_fail, ['']) test('tcfail191', normal, compile_fail, ['']) -test('tcfail192', normal, compile_fail, ['']) test('tcfail193', normal, compile_fail, ['']) -test('tcfail194', normal, compile_fail, ['']) test('tcfail195', normal, compile_fail, ['']) test('tcfail196', normal, compile_fail, ['']) test('tcfail197', normal, compile_fail, ['']) diff --git a/testsuite/tests/typecheck/should_fail/tcfail192.hs b/testsuite/tests/typecheck/should_fail/tcfail192.hs deleted file mode 100644 index 15de576..0000000 --- a/testsuite/tests/typecheck/should_fail/tcfail192.hs +++ /dev/null @@ -1,11 +0,0 @@ --- Checks that the types of the old binder and the binder --- implicitly introduced by grouping are linked - -{-# OPTIONS_GHC -XTransformListComp #-} - -module ShouldFail where - -foo = [ x + 1 - | x <- ["Hello", "World"] - , then group using take 5 - ] \ No newline at end of file diff --git a/testsuite/tests/typecheck/should_fail/tcfail192.stderr b/testsuite/tests/typecheck/should_fail/tcfail192.stderr deleted file mode 100644 index 412aac6..0000000 --- a/testsuite/tests/typecheck/should_fail/tcfail192.stderr +++ /dev/null @@ -1,9 +0,0 @@ - -tcfail192.hs:10:26: - Couldn't match type ?a? with ?[a]? - ?a? is a rigid type variable bound by - a type expected by the context: [a] -> [[a]] at tcfail192.hs:10:9 - Expected type: [a] -> [[a]] - Actual type: [a] -> [a] - In the expression: take 5 - In a stmt of a list comprehension: then group using take 5 diff --git a/testsuite/tests/typecheck/should_fail/tcfail194.hs b/testsuite/tests/typecheck/should_fail/tcfail194.hs deleted file mode 100644 index 9166b18..0000000 --- a/testsuite/tests/typecheck/should_fail/tcfail194.hs +++ /dev/null @@ -1,10 +0,0 @@ --- Checks that using the "by" clause in a transform requires a function parameter - -{-# OPTIONS_GHC -XTransformListComp #-} - -module ShouldFail where - -import Data.List(take) - -z = [x | x <- [1..10], then take 5 by x] - diff --git a/testsuite/tests/typecheck/should_fail/tcfail194.stderr b/testsuite/tests/typecheck/should_fail/tcfail194.stderr deleted file mode 100644 index eeae9d0..0000000 --- a/testsuite/tests/typecheck/should_fail/tcfail194.stderr +++ /dev/null @@ -1,9 +0,0 @@ - -tcfail194.hs:9:29: - Couldn't match type ?[a0]? with ?a -> t? - Expected type: (a -> t) -> [a] -> [a] - Actual type: [a0] -> [a0] - Relevant bindings include z :: [t] (bound at tcfail194.hs:9:1) - Possible cause: ?take? is applied to too many arguments - In the expression: take 5 - In a stmt of a list comprehension: then take 5 by x From git at git.haskell.org Fri Nov 21 13:03:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:03:27 +0000 (UTC) Subject: [commit: ghc] master: Fix up tests for Trac #7220; the old test really was ambiguous (7b1a856) Message-ID: <20141121130327.CE25A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7b1a8562d9b92547251d0dff23bb3a2de25d4b6f/ghc >--------------------------------------------------------------- commit 7b1a8562d9b92547251d0dff23bb3a2de25d4b6f Author: Simon Peyton Jones Date: Fri Nov 21 11:29:47 2014 +0000 Fix up tests for Trac #7220; the old test really was ambiguous >--------------------------------------------------------------- 7b1a8562d9b92547251d0dff23bb3a2de25d4b6f testsuite/tests/typecheck/should_compile/T7220.hs | 9 ++++---- testsuite/tests/typecheck/should_compile/T7220a.hs | 27 ++++++++++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 33 insertions(+), 4 deletions(-) diff --git a/testsuite/tests/typecheck/should_compile/T7220.hs b/testsuite/tests/typecheck/should_compile/T7220.hs index 36ae54a..bf4df87 100644 --- a/testsuite/tests/typecheck/should_compile/T7220.hs +++ b/testsuite/tests/typecheck/should_compile/T7220.hs @@ -3,25 +3,26 @@ {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE ScopedTypeVariables #-} module Test2 where class C a b | b -> a data A = A -data X = X +data X a = X data Y = Y type family TF b -f :: (forall b. (C a b, TF b ~ Y) => b) -> X +f :: (forall b. (C a b, TF b ~ Y) => b) -> X a f _ = undefined u :: (C A b, TF b ~ Y) => b u = undefined -v :: X -v = (f :: (forall b. (C A b, TF b ~ Y) => b) -> X) u -- This line causes an error (see below) +v :: X A +v = (f :: (forall b. (C A b, TF b ~ Y) => b) -> X A) u -- This line causes an error (see below) {- GHC 7.6.1-rc1 (7.6.0.20120810) rejects this code with the following error message. diff --git a/testsuite/tests/typecheck/should_compile/T7220a.hs b/testsuite/tests/typecheck/should_compile/T7220a.hs new file mode 100644 index 0000000..4739626 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T7220a.hs @@ -0,0 +1,27 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FunctionalDependencies #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE ScopedTypeVariables #-} + +module T7220a where + +class C a b | b -> a + +data X = X +data Y = Y + +type family TF b + +f :: (forall b. (C a b, TF b ~ Y) => b) -> X +-- This type is really ambiguous +-- GHC 7.8 didn't detect that, and accepted the type, but would fail +-- when given g :: +-- g x = f x +-- But it would succeed if you said just +-- g = f +-- Now we fail in all ways! + +f _ = undefined + diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 7e825d9..8acfa4a 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -426,4 +426,5 @@ test('T9708', normal, compile_fail, ['']) test('T9404', normal, compile, ['']) test('T9404b', normal, compile, ['']) test('T7220', normal, compile, ['']) +test('T7220a', normal, compile_fail, ['']) test('T9151', normal, compile, ['']) From git at git.haskell.org Fri Nov 21 13:03:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:03:30 +0000 (UTC) Subject: [commit: ghc] master: Test T2239 actually succeeds without impredicativity, because of the new co/contra subsumption check (1b6988e) Message-ID: <20141121130330.6C3CD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1b6988e773229ed10a12ca157117d12826609c07/ghc >--------------------------------------------------------------- commit 1b6988e773229ed10a12ca157117d12826609c07 Author: Simon Peyton Jones Date: Fri Nov 21 11:31:25 2014 +0000 Test T2239 actually succeeds without impredicativity, because of the new co/contra subsumption check >--------------------------------------------------------------- 1b6988e773229ed10a12ca157117d12826609c07 testsuite/tests/indexed-types/should_fail/T2239.hs | 24 +++++++++++++++---- .../tests/indexed-types/should_fail/T2239.stderr | 28 ---------------------- testsuite/tests/indexed-types/should_fail/all.T | 2 +- 3 files changed, 21 insertions(+), 33 deletions(-) diff --git a/testsuite/tests/indexed-types/should_fail/T2239.hs b/testsuite/tests/indexed-types/should_fail/T2239.hs index 750fdd9..d84ea17 100644 --- a/testsuite/tests/indexed-types/should_fail/T2239.hs +++ b/testsuite/tests/indexed-types/should_fail/T2239.hs @@ -42,10 +42,26 @@ simpleFD = id :: (forall b. MyEq b Bool => b->b) simpleTF = id :: (forall b. b~Bool => b->b) --- These two both involve impredicative instantiation, --- and should fail (in the same way) +-- Actually these two do not involve impredicative instantiation, +-- so they now succeed complexFD = id :: (forall b. MyEq b Bool => b->b) - -> (forall b. MyEq b Bool => b->b) + -> (forall c. MyEq c Bool => c->c) complexTF = id :: (forall b. b~Bool => b->b) - -> (forall b. b~Bool => b->b) + -> (forall c. c~Bool => c->c) + +{- For exmaple, here is how the subsumption check works for complexTF + when type-checking the expression + (id :: (forall b. b~Bool => b->b) -> (forall c. c~Bool => c->c)) + + First, deeply skolemise the type sig, (level 3) before calling + tcExpr on 'id'. Then instantiate id's type: + + b~Bool |-3 alpha[3] -> alpha <= (forall c. c~Bool => c->c) -> b -> b + + Now decompose the -> + + b~Bool |-3 alpha[3] ~ b->b, (forall c. c~Bool => c->c) <= a + + And this is perfectly soluble. alpha is touchable; and c is instantiated. +-} \ No newline at end of file diff --git a/testsuite/tests/indexed-types/should_fail/T2239.stderr b/testsuite/tests/indexed-types/should_fail/T2239.stderr deleted file mode 100644 index a5e5227..0000000 --- a/testsuite/tests/indexed-types/should_fail/T2239.stderr +++ /dev/null @@ -1,28 +0,0 @@ - -T2239.hs:47:13: - Couldn't match type ?b -> b? - with ?forall b1. MyEq b1 Bool => b1 -> b1? - Expected type: (forall b1. MyEq b1 Bool => b1 -> b1) -> b -> b - Actual type: (b -> b) -> b -> b - In the expression: - id :: - (forall b. MyEq b Bool => b -> b) - -> (forall b. MyEq b Bool => b -> b) - In an equation for ?complexFD?: - complexFD - = id :: - (forall b. MyEq b Bool => b -> b) - -> (forall b. MyEq b Bool => b -> b) - -T2239.hs:50:13: - Couldn't match type ?Bool -> Bool? - with ?forall b1. (b1 ~ Bool) => b1 -> b1? - Expected type: (forall b1. (b1 ~ Bool) => b1 -> b1) -> b -> b - Actual type: (b -> b) -> b -> b - In the expression: - id :: - (forall b. b ~ Bool => b -> b) -> (forall b. b ~ Bool => b -> b) - In an equation for ?complexTF?: - complexTF - = id :: - (forall b. b ~ Bool => b -> b) -> (forall b. b ~ Bool => b -> b) diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index 998193f..233dc67 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -61,7 +61,7 @@ test('T3330b', normal, compile_fail, ['']) test('T3330c', normal, compile_fail, ['']) test('T4179', normal, compile_fail, ['']) test('T4254', normal, compile, ['']) -test('T2239', normal, compile_fail, ['']) +test('T2239', normal, compile, ['']) test('T3440', normal, compile_fail, ['']) test('T4485', normal, compile_fail, ['']) test('T4174', normal, compile_fail, ['']) From git at git.haskell.org Fri Nov 21 13:03:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:03:33 +0000 (UTC) Subject: [commit: ghc] master: Wibbles (usually improvements) to error messages (eaccc72) Message-ID: <20141121130333.094EA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eaccc72162194d12a33aa454b57c126bcabcdd5d/ghc >--------------------------------------------------------------- commit eaccc72162194d12a33aa454b57c126bcabcdd5d Author: Simon Peyton Jones Date: Fri Nov 21 11:33:16 2014 +0000 Wibbles (usually improvements) to error messages >--------------------------------------------------------------- eaccc72162194d12a33aa454b57c126bcabcdd5d testsuite/tests/deriving/should_fail/T5287.stderr | 4 +- testsuite/tests/ghci/scripts/Defer02.stderr | 6 ++- testsuite/tests/ghci/scripts/ghci012.stdout | 2 +- .../tests/indexed-types/should_compile/Simple14.hs | 1 + .../indexed-types/should_compile/Simple14.stderr | 29 ++++++------- .../indexed-types/should_fail/NoMatchErr.stderr | 6 +-- .../tests/indexed-types/should_fail/T1897b.stderr | 2 +- .../tests/indexed-types/should_fail/T1900.stderr | 3 +- .../tests/indexed-types/should_fail/T2693.stderr | 12 +++--- .../tests/indexed-types/should_fail/T4093a.stderr | 3 +- .../tests/indexed-types/should_fail/T9036.stderr | 9 ++-- .../tests/indexed-types/should_fail/T9171.stderr | 2 +- testsuite/tests/parser/should_fail/T7848.stderr | 31 +++++++++++++- testsuite/tests/perf/compiler/T5837.stderr | 3 +- .../tests/typecheck/should_compile/T2494.stderr | 0 testsuite/tests/typecheck/should_compile/T3692.hs | 2 +- .../tests/typecheck/should_compile/T9708.stderr | 10 ++--- .../tests/typecheck/should_compile/tc168.stderr | 1 - testsuite/tests/typecheck/should_compile/tc211.hs | 3 ++ .../tests/typecheck/should_compile/tc211.stderr | 50 +++++++++++++++++++--- .../typecheck/should_fail/ContextStack2.stderr | 3 +- .../tests/typecheck/should_fail/T1897a.stderr | 1 - testsuite/tests/typecheck/should_fail/T2414.stderr | 2 +- testsuite/tests/typecheck/should_fail/T2534.stderr | 12 +++--- testsuite/tests/typecheck/should_fail/T3592.stderr | 5 ++- testsuite/tests/typecheck/should_fail/T3613.stderr | 4 +- testsuite/tests/typecheck/should_fail/T5236.stderr | 3 +- testsuite/tests/typecheck/should_fail/T5300.stderr | 18 ++++---- testsuite/tests/typecheck/should_fail/T5691.stderr | 7 +-- testsuite/tests/typecheck/should_fail/T6069.stderr | 18 ++++---- testsuite/tests/typecheck/should_fail/T7279.stderr | 4 +- .../tests/typecheck/should_fail/T8392a.stderr | 3 +- testsuite/tests/typecheck/should_fail/T8883.stderr | 2 +- testsuite/tests/typecheck/should_fail/mc21.stderr | 2 +- testsuite/tests/typecheck/should_fail/mc22.stderr | 2 +- testsuite/tests/typecheck/should_fail/mc23.stderr | 6 +-- testsuite/tests/typecheck/should_fail/mc24.stderr | 5 ++- testsuite/tests/typecheck/should_fail/mc25.stderr | 4 +- .../tests/typecheck/should_fail/tcfail080.stderr | 1 - .../tests/typecheck/should_fail/tcfail097.stderr | 5 ++- .../tests/typecheck/should_fail/tcfail098.stderr | 4 +- .../tests/typecheck/should_fail/tcfail142.stderr | 4 +- .../tests/typecheck/should_fail/tcfail174.stderr | 4 +- .../tests/typecheck/should_fail/tcfail189.stderr | 2 +- .../tests/typecheck/should_fail/tcfail191.stderr | 2 +- 45 files changed, 188 insertions(+), 114 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc eaccc72162194d12a33aa454b57c126bcabcdd5d From git at git.haskell.org Fri Nov 21 13:03:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:03:35 +0000 (UTC) Subject: [commit: ghc] master: Fix Trac #9815 (4ba4cc7) Message-ID: <20141121130335.F2B2A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4ba4cc7aaaf2bff31bc8474c8ba40e1cbe3e3875/ghc >--------------------------------------------------------------- commit 4ba4cc7aaaf2bff31bc8474c8ba40e1cbe3e3875 Author: Simon Peyton Jones Date: Fri Nov 21 13:02:45 2014 +0000 Fix Trac #9815 Dot-dot record-wildcard notation is simply illegal for constructors without any named fields, but that was neither documented nor checked. This patch does so - Make the check in RnPat - Add test T9815 - Fix CmmLayoutStack which was using the illegal form (!) - Document in user manual >--------------------------------------------------------------- 4ba4cc7aaaf2bff31bc8474c8ba40e1cbe3e3875 compiler/cmm/CmmLayoutStack.hs | 6 +++--- compiler/rename/RnPat.lhs | 14 ++++++++++---- docs/users_guide/glasgow_exts.xml | 14 +++++++++++++- testsuite/tests/rename/should_fail/T9815.hs | 6 ++++++ testsuite/tests/rename/should_fail/T9815.stderr | 4 ++++ testsuite/tests/rename/should_fail/all.T | 1 + 6 files changed, 37 insertions(+), 8 deletions(-) diff --git a/compiler/cmm/CmmLayoutStack.hs b/compiler/cmm/CmmLayoutStack.hs index c9399b3..5a2891f 100644 --- a/compiler/cmm/CmmLayoutStack.hs +++ b/compiler/cmm/CmmLayoutStack.hs @@ -415,9 +415,9 @@ handleLastNode dflags procpoints liveness cont_info stackmaps return $ lastCall cont_lbl (wORD_SIZE dflags) ret_args ret_off -- one word of args: the return address - CmmBranch{..} -> handleBranches - CmmCondBranch{..} -> handleBranches - CmmSwitch{..} -> handleBranches + CmmBranch {} -> handleBranches + CmmCondBranch {} -> handleBranches + CmmSwitch {} -> handleBranches where -- Calls and ForeignCalls are handled the same way: diff --git a/compiler/rename/RnPat.lhs b/compiler/rename/RnPat.lhs index aa41361..9d03805 100644 --- a/compiler/rename/RnPat.lhs +++ b/compiler/rename/RnPat.lhs @@ -516,7 +516,7 @@ rnHsRecFields -> HsRecFields RdrName (Located arg) -> RnM ([HsRecField Name (Located arg)], FreeVars) --- This supprisingly complicated pass +-- This surprisingly complicated pass -- a) looks up the field name (possibly using disambiguation) -- b) fills in puns and dot-dot stuff -- When we we've finished, we've renamed the LHS, but not the RHS, @@ -576,7 +576,7 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot }) = return [] rn_dotdot (Just {}) Nothing _flds -- ".." on record update = do { case ctxt of - HsRecFieldUpd -> addErr badDotDot + HsRecFieldUpd -> addErr badDotDotUpd _ -> return () ; return [] } rn_dotdot (Just n) (Just con) flds -- ".." on record construction / pat match @@ -586,6 +586,7 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot }) ; checkErr dd_flag (needFlagDotDot ctxt) ; (rdr_env, lcl_env) <- getRdrEnvs ; con_fields <- lookupConstructorFields con + ; when (null con_fields) (addErr (badDotDotCon con)) ; let present_flds = getFieldIds flds parent_tc = find_tycon rdr_env con @@ -655,8 +656,13 @@ needFlagDotDot :: HsRecFieldContext -> SDoc needFlagDotDot ctxt = vcat [ptext (sLit "Illegal `..' in record") <+> pprRFC ctxt, ptext (sLit "Use RecordWildCards to permit this")] -badDotDot :: SDoc -badDotDot = ptext (sLit "You cannot use `..' in a record update") +badDotDotCon :: Name -> SDoc +badDotDotCon con + = vcat [ ptext (sLit "Illegal `..' notation for constructor") <+> quotes (ppr con) + , nest 2 (ptext (sLit "The constructor has no labelled fields")) ] + +badDotDotUpd :: SDoc +badDotDotUpd = ptext (sLit "You cannot use `..' in a record update") emptyUpdateErr :: SDoc emptyUpdateErr = ptext (sLit "Empty record update") diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 30742b3..a21e677 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -2337,7 +2337,7 @@ More details: Record wildcards in patterns can be mixed with other patterns, including puns -(); for example, in a pattern C {a +(); for example, in a pattern (C {a = 1, b, ..}). Additionally, record wildcards can be used wherever record patterns occur, including in let bindings and at the top-level. For example, the top-level binding @@ -2404,6 +2404,18 @@ and omitting c since the variable c is not in scope (apart from the binding of the record selector c, of course). + + +Record wildcards cannot be used (a) in a record update construct, and (b) for data +constructors that are not declared with record fields. For example: + +f x = x { v=True, .. } -- Illegal (a) + +data T = MkT Int Bool +g = MkT { .. } -- Illegal (b) +h (MkT { .. }) = True -- Illegal (b) + + diff --git a/testsuite/tests/rename/should_fail/T9815.hs b/testsuite/tests/rename/should_fail/T9815.hs new file mode 100644 index 0000000..7d7ae66 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T9815.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE RecordWildCards #-} +module T9815 where + +newtype N = N Int deriving (Show) + +foo = print N{..} diff --git a/testsuite/tests/rename/should_fail/T9815.stderr b/testsuite/tests/rename/should_fail/T9815.stderr new file mode 100644 index 0000000..99f16b6 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T9815.stderr @@ -0,0 +1,4 @@ + +T9815.hs:6:13: + Illegal `..' notation for constructor ?N? + The constructor has no labelled fields diff --git a/testsuite/tests/rename/should_fail/all.T b/testsuite/tests/rename/should_fail/all.T index f2664dc..56d0f87 100644 --- a/testsuite/tests/rename/should_fail/all.T +++ b/testsuite/tests/rename/should_fail/all.T @@ -119,3 +119,4 @@ test('T9177', normal, compile_fail, ['']) test('T9436', normal, compile_fail, ['']) test('T9437', normal, compile_fail, ['']) test('T9077', normal, compile_fail, ['']) +test('T9815', normal, compile_fail, ['']) From git at git.haskell.org Fri Nov 21 13:03:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:03:38 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #8149 (c5a3938) Message-ID: <20141121130338.EC9033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c5a39389ea067b2932961a27f5e4c28e135cf266/ghc >--------------------------------------------------------------- commit c5a39389ea067b2932961a27f5e4c28e135cf266 Author: Simon Peyton Jones Date: Fri Nov 21 13:03:08 2014 +0000 Test Trac #8149 >--------------------------------------------------------------- c5a39389ea067b2932961a27f5e4c28e135cf266 testsuite/tests/rename/should_fail/T8149.hs | 9 +++++++++ testsuite/tests/rename/should_fail/T8149.stderr | 4 ++++ testsuite/tests/rename/should_fail/all.T | 1 + 3 files changed, 14 insertions(+) diff --git a/testsuite/tests/rename/should_fail/T8149.hs b/testsuite/tests/rename/should_fail/T8149.hs new file mode 100644 index 0000000..7bd3519 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T8149.hs @@ -0,0 +1,9 @@ +{-# OPTIONS_GHC -Wall #-} + +module T8149 where + +import Control.Monad.Trans.Writer (WriterT, runWriterT) + +foo :: Bool +foo = runWriterT `seq` True + diff --git a/testsuite/tests/rename/should_fail/T8149.stderr b/testsuite/tests/rename/should_fail/T8149.stderr new file mode 100644 index 0000000..1bb7f0d --- /dev/null +++ b/testsuite/tests/rename/should_fail/T8149.stderr @@ -0,0 +1,4 @@ + +T8149.hs:5:1: Warning: + The import of ?WriterT? + from module ?Control.Monad.Trans.Writer? is redundant diff --git a/testsuite/tests/rename/should_fail/all.T b/testsuite/tests/rename/should_fail/all.T index 56d0f87..4c61a8a 100644 --- a/testsuite/tests/rename/should_fail/all.T +++ b/testsuite/tests/rename/should_fail/all.T @@ -111,6 +111,7 @@ test('T7906', normal, compile_fail, ['']) test('T7937', normal, compile_fail, ['']) test('T7943', normal, compile_fail, ['']) test('T8448', normal, compile_fail, ['']) +test('T8149', normal, compile, ['']) test('T9006', extra_clean(['T9006a.hi', 'T9006a.o']), multimod_compile_fail, ['T9006', '-v0']) From git at git.haskell.org Fri Nov 21 13:29:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 13:29:10 +0000 (UTC) Subject: [commit: ghc] master: Comments only (6d40470) Message-ID: <20141121132910.7E1D63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6d404707e533922c26aebb82cf97565fe773ca60/ghc >--------------------------------------------------------------- commit 6d404707e533922c26aebb82cf97565fe773ca60 Author: Simon Peyton Jones Date: Fri Nov 21 13:29:42 2014 +0000 Comments only >--------------------------------------------------------------- 6d404707e533922c26aebb82cf97565fe773ca60 compiler/typecheck/TcFlatten.lhs | 7 +++++-- compiler/typecheck/TcSMonad.lhs | 30 ++---------------------------- 2 files changed, 7 insertions(+), 30 deletions(-) diff --git a/compiler/typecheck/TcFlatten.lhs b/compiler/typecheck/TcFlatten.lhs index fbb4729..ac68ec9 100644 --- a/compiler/typecheck/TcFlatten.lhs +++ b/compiler/typecheck/TcFlatten.lhs @@ -925,6 +925,9 @@ In effect they become Givens, implemented via the side-effected substitution. Note [An alternative story for the inert substitution] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +(This entire note is just background, left here in case we ever want + to return the the previousl state of affairs) + We used (GHC 7.8) to have this story for the inert substitution inert_eqs * 'a' is not in fvs(ty) @@ -1012,8 +1015,8 @@ Note [eqCanRewrite] tv ~ ty) can be used to rewrite ct2. The EqCanRewrite Property: - * For any a,b in {G,W,D} if a canRewrite b - then a canRewrite a + * For any a,b in {G,W,D} if a eqCanRewrite b + then a eqCanRewrite a This is what guarantees that canonicalisation will terminate. See Note [Applying the inert substitution] diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index b756fbc..44ecc6f 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -328,34 +328,8 @@ The InertCans represents a collection of constraints with the following properti to the CTyEqCan equalities (modulo canRewrite of course; eg a wanted cannot rewrite a given) - * CTyEqCan equalities _do_not_ form an idempotent substitution, but - they are guaranteed to not have any occurs errors. Additional notes: - - - The lack of idempotence of the inert substitution implies - that we must make sure that when we rewrite a constraint we - apply the substitution /recursively/ to the types - involved. Currently the one AND ONLY way in the whole - constraint solver that we rewrite types and constraints wrt - to the inert substitution is TcFlatten/flattenTyVar. - - - In the past we did try to have the inert substitution as - idempotent as possible but this would only be true for - constraints of the same flavor, so in total the inert - substitution could not be idempotent, due to flavor-related - issued. Note [Non-idempotent inert substitution] in TcFlatten - explains what is going on. - - - Whenever a constraint ends up in the worklist we do - recursively apply exhaustively the inert substitution to it - to check for occurs errors. But if an equality is already in - the inert set and we can guarantee that adding a new equality - will not cause the first equality to have an occurs check - then we do not rewrite the inert equality. This happens in - TcInteract, rewriteInertEqsFromInertEq. - - See Note [Delicate equality kick-out] to see which inert - equalities can safely stay in the inert set and which must be - kicked out to be rewritten and re-checked for occurs errors. + * CTyEqCan equalities: see Note [Applying the inert substitution] + in TcFlatten Note [Type family equations] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ From git at git.haskell.org Fri Nov 21 16:18:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 16:18:21 +0000 (UTC) Subject: [commit: ghc] master: Test #7484 in th/T7484 (dbf360a) Message-ID: <20141121161821.E3CE63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dbf360a5264d5d6597e046dcd9b4f49effa91eee/ghc >--------------------------------------------------------------- commit dbf360a5264d5d6597e046dcd9b4f49effa91eee Author: Richard Eisenberg Date: Mon Nov 3 15:33:51 2014 -0500 Test #7484 in th/T7484 >--------------------------------------------------------------- dbf360a5264d5d6597e046dcd9b4f49effa91eee testsuite/tests/th/T7484.hs | 7 +++++++ testsuite/tests/th/T7484.stderr | 4 ++++ testsuite/tests/th/all.T | 1 + 3 files changed, 12 insertions(+) diff --git a/testsuite/tests/th/T7484.hs b/testsuite/tests/th/T7484.hs new file mode 100644 index 0000000..b1a9cba --- /dev/null +++ b/testsuite/tests/th/T7484.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T7484 where + +import Language.Haskell.TH + +$( return [ ValD (VarP (mkName "a ")) (NormalB (LitE (IntegerL 5))) [] ] ) diff --git a/testsuite/tests/th/T7484.stderr b/testsuite/tests/th/T7484.stderr new file mode 100644 index 0000000..3ffe123 --- /dev/null +++ b/testsuite/tests/th/T7484.stderr @@ -0,0 +1,4 @@ + +T7484.hs:7:4: + Illegal variable name: ?a ? + When splicing a TH declaration: a = 5 diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 6c7b2e5..5109473 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -343,3 +343,4 @@ test('T9066', normal, compile, ['-v0']) test('T8100', normal, compile, ['-v0']) test('T9064', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) +test('T7484', expect_broken(7484), compile_fail, ['-v0']) From git at git.haskell.org Fri Nov 21 16:18:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 16:18:24 +0000 (UTC) Subject: [commit: ghc] master: Test #1476 in th/T1476 (adb20a0) Message-ID: <20141121161824.E47183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/adb20a0aec89047af397ef8c3fcde78217e6e5f6/ghc >--------------------------------------------------------------- commit adb20a0aec89047af397ef8c3fcde78217e6e5f6 Author: Richard Eisenberg Date: Mon Nov 3 20:26:14 2014 -0500 Test #1476 in th/T1476 >--------------------------------------------------------------- adb20a0aec89047af397ef8c3fcde78217e6e5f6 testsuite/tests/th/T1476.hs | 10 ++++++++++ testsuite/tests/th/all.T | 1 + 2 files changed, 11 insertions(+) diff --git a/testsuite/tests/th/T1476.hs b/testsuite/tests/th/T1476.hs new file mode 100644 index 0000000..7e3a192 --- /dev/null +++ b/testsuite/tests/th/T1476.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T1476 where + +import Language.Haskell.TH + +foo $( return $ VarP $ mkName "x" ) = x +bar $( [p| x |] ) = x + +baz = [| \ $( return $ VarP $ mkName "x" ) -> $(dyn "x") |] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 1144156..27cde1b 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -344,3 +344,4 @@ test('T8100', normal, compile, ['-v0']) test('T9064', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) +test('T1476', expect_broken(1476), compile, ['-v0']) From git at git.haskell.org Fri Nov 21 16:18:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 16:18:28 +0000 (UTC) Subject: [commit: ghc] master: Fix #7484, checking for good binder names in Convert. (da2fca9) Message-ID: <20141121161828.044F53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/da2fca9e2be8c61c91c034d8c2302d8b1d1e7b41/ghc >--------------------------------------------------------------- commit da2fca9e2be8c61c91c034d8c2302d8b1d1e7b41 Author: Richard Eisenberg Date: Mon Nov 3 15:34:53 2014 -0500 Fix #7484, checking for good binder names in Convert. This commit also refactors a bunch of lexeme-oriented code into a new module Lexeme, and includes a submodule update for haddock. >--------------------------------------------------------------- da2fca9e2be8c61c91c034d8c2302d8b1d1e7b41 compiler/basicTypes/Lexeme.hs | 252 ++++++++++++++++++++++++++++++++++++++ compiler/basicTypes/OccName.lhs | 72 +---------- compiler/ghc.cabal.in | 1 + compiler/ghc.mk | 1 + compiler/hsSyn/Convert.lhs | 12 +- compiler/parser/Lexer.x | 6 + compiler/typecheck/TcGenDeriv.lhs | 1 + compiler/typecheck/TcSplice.lhs | 1 + testsuite/tests/th/all.T | 2 +- utils/haddock | 2 +- 10 files changed, 270 insertions(+), 80 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc da2fca9e2be8c61c91c034d8c2302d8b1d1e7b41 From git at git.haskell.org Fri Nov 21 16:18:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 16:18:30 +0000 (UTC) Subject: [commit: ghc] master: Release notes for #1476, #7484. (1b22d9f) Message-ID: <20141121161830.9980D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1b22d9f288cbf819be90ec42b254fb1b67dded2d/ghc >--------------------------------------------------------------- commit 1b22d9f288cbf819be90ec42b254fb1b67dded2d Author: Richard Eisenberg Date: Tue Nov 4 12:20:25 2014 -0500 Release notes for #1476, #7484. >--------------------------------------------------------------- 1b22d9f288cbf819be90ec42b254fb1b67dded2d docs/users_guide/7.10.1-notes.xml | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 40a5ac0..596ec16 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -187,6 +187,10 @@ + Pattern splices now work. + + + reifyInstances now treats unbound type variables as univerally quantified, allowing lookup of, say, the instance for Eq [a]. @@ -223,6 +227,13 @@ a class). This means an expansion to the Dec type. + + + Template Haskell is now more pedantic about splicing in + bogus variable names, like those containing whitespace. If you + use bogus names in your Template Haskell code, this may break + your program. + From git at git.haskell.org Fri Nov 21 16:18:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 16:18:33 +0000 (UTC) Subject: [commit: ghc] master: Fix #1476 by making splice patterns work. (2346de4) Message-ID: <20141121161833.4C07E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2346de44330a4309b840e26ddd1ded23f92c6f81/ghc >--------------------------------------------------------------- commit 2346de44330a4309b840e26ddd1ded23f92c6f81 Author: Richard Eisenberg Date: Tue Nov 4 11:34:53 2014 -0500 Fix #1476 by making splice patterns work. Unfortunately, splice patterns in brackets still do not work because we don't run splices in brackets. Without running a pattern splice, we can't know what variables it binds, so we're stuck. This is still a substantial improvement, and it may be the best we can do. Still must document new behavior. >--------------------------------------------------------------- 2346de44330a4309b840e26ddd1ded23f92c6f81 compiler/rename/RnPat.lhs | 10 ++++++---- compiler/rename/RnSplice.lhs | 38 +++++++++++++++++++++++++++++++------- compiler/rename/RnSplice.lhs-boot | 3 ++- testsuite/tests/th/all.T | 2 +- 4 files changed, 40 insertions(+), 13 deletions(-) diff --git a/compiler/rename/RnPat.lhs b/compiler/rename/RnPat.lhs index 9d03805..370f6b4 100644 --- a/compiler/rename/RnPat.lhs +++ b/compiler/rename/RnPat.lhs @@ -440,10 +440,12 @@ rnPatAndThen mk (TuplePat pats boxed _) ; pats' <- rnLPatsAndThen mk pats ; return (TuplePat pats' boxed []) } -rnPatAndThen _ (SplicePat splice) - = do { -- XXX How to deal with free variables? - ; (pat, _) <- liftCps $ rnSplicePat splice - ; return pat } +rnPatAndThen mk (SplicePat splice) + = do { eith <- liftCpsFV $ rnSplicePat splice + ; case eith of -- See Note [rnSplicePat] in RnSplice + Left not_yet_renamed -> rnPatAndThen mk not_yet_renamed + Right already_renamed -> return already_renamed } + rnPatAndThen mk (QuasiQuotePat qq) = do { pat <- liftCps $ runQuasiQuotePat qq -- Wrap the result of the quasi-quoter in parens so that we don't diff --git a/compiler/rename/RnSplice.lhs b/compiler/rename/RnSplice.lhs index 59c8c62..8918e39 100644 --- a/compiler/rename/RnSplice.lhs +++ b/compiler/rename/RnSplice.lhs @@ -206,13 +206,40 @@ rnSpliceType splice k } ; return (unLoc hs_ty3, fvs) } ----------------------- -rnSplicePat :: HsSplice RdrName -> RnM (Pat Name, FreeVars) +\end{code} + +Note [rnSplicePat] +~~~~~~~~~~~~~~~~~~ +Renaming a pattern splice is a bit tricky, because we need the variables +bound in the pattern to be in scope in the RHS of the pattern. This scope +management is effectively done by using continuation-passing style in +RnPat, through the CpsRn monad. We don't wish to be in that monad here +(it would create import cycles and generally conflict with renaming other +splices), so we really want to return a (Pat RdrName) -- the result of +running the splice -- which can then be further renamed in RnPat, in +the CpsRn monad. + +The problem is that if we're renaming a splice within a bracket, we +*don't* want to run the splice now. We really do just want to rename +it to an HsSplice Name. Of course, then we can't know what variables +are bound within the splice, so pattern splices within brackets aren't +all that useful. + +In any case, when we're done in rnSplicePat, we'll either have a +Pat RdrName (the result of running a top-level splice) or a Pat Name +(the renamed nested splice). Thus, the awkward return type of +rnSplicePat. + +\begin{code} + +-- | Rename a splice pattern. See Note [rnSplicePat] +rnSplicePat :: HsSplice RdrName -> RnM ( Either (Pat RdrName) (Pat Name) + , FreeVars) rnSplicePat splice = rnSpliceGen False run_pat_splice pend_pat_splice splice where pend_pat_splice rn_splice@(HsSplice n e) - = (PendingRnPatSplice (PendSplice n e), SplicePat rn_splice) + = (PendingRnPatSplice (PendSplice n e), Right $ SplicePat rn_splice) run_pat_splice (HsSplice _ expr') = do { expr <- getHooked runRnSpliceHook return >>= ($ expr') @@ -227,10 +254,7 @@ rnSplicePat splice ; pat <- runMetaP zonked_q_expr ; showSplice "pattern" expr (ppr pat) - ; (pat', fvs) <- checkNoErrs $ - rnPat ThPatSplice pat $ \pat' -> return (pat', emptyFVs) - - ; return (unLoc pat', fvs) } + ; return (Left $ unLoc pat, emptyFVs) } ---------------------- rnSpliceDecl :: SpliceDecl RdrName -> RnM (SpliceDecl Name, FreeVars) diff --git a/compiler/rename/RnSplice.lhs-boot b/compiler/rename/RnSplice.lhs-boot index 45a2a10..de6da77 100644 --- a/compiler/rename/RnSplice.lhs-boot +++ b/compiler/rename/RnSplice.lhs-boot @@ -11,6 +11,7 @@ import Kind rnSpliceType :: HsSplice RdrName -> PostTc Name Kind -> RnM (HsType Name, FreeVars) -rnSplicePat :: HsSplice RdrName -> RnM (Pat Name, FreeVars) +rnSplicePat :: HsSplice RdrName -> RnM ( Either (Pat RdrName) (Pat Name) + , FreeVars ) rnSpliceDecl :: SpliceDecl RdrName -> RnM (SpliceDecl Name, FreeVars) \end{code} diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 3f8ff16..366858e 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -344,5 +344,5 @@ test('T8100', normal, compile, ['-v0']) test('T9064', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) -test('T1476', expect_broken(1476), compile, ['-v0']) +test('T1476', normal, compile, ['-v0']) test('T1476b', normal, compile_fail, ['-v0']) From git at git.haskell.org Fri Nov 21 16:18:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 16:18:36 +0000 (UTC) Subject: [commit: ghc] master: Test that nested pattern splices don't scope (#1476). (d627c5c) Message-ID: <20141121161836.852453A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d627c5cf81fcce05ec160edc5be907297ff05c33/ghc >--------------------------------------------------------------- commit d627c5cf81fcce05ec160edc5be907297ff05c33 Author: Richard Eisenberg Date: Tue Nov 4 13:06:56 2014 -0500 Test that nested pattern splices don't scope (#1476). Test case: th/T1476b. >--------------------------------------------------------------- d627c5cf81fcce05ec160edc5be907297ff05c33 testsuite/tests/th/T1476b.hs | 10 ++++++++++ testsuite/tests/th/T1476b.stderr | 5 +++++ testsuite/tests/th/all.T | 1 + 3 files changed, 16 insertions(+) diff --git a/testsuite/tests/th/T1476b.hs b/testsuite/tests/th/T1476b.hs new file mode 100644 index 0000000..918a397 --- /dev/null +++ b/testsuite/tests/th/T1476b.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T1476b where + +import Language.Haskell.TH + +baz = [| \ $( return $ VarP $ mkName "x" ) -> x |] + +-- If this test starts passing, nested pattern splices scope correctly. +-- Good for you! Now, update the TH manual accordingly. diff --git a/testsuite/tests/th/T1476b.stderr b/testsuite/tests/th/T1476b.stderr new file mode 100644 index 0000000..65b0814 --- /dev/null +++ b/testsuite/tests/th/T1476b.stderr @@ -0,0 +1,5 @@ + +T1476b.hs:7:47: + Not in scope: ?x? + In the Template Haskell quotation + [| \ $(return $ VarP $ mkName "x") -> x |] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 27cde1b..3f8ff16 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -345,3 +345,4 @@ test('T9064', normal, compile, ['-v0']) test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) test('T1476', expect_broken(1476), compile, ['-v0']) +test('T1476b', normal, compile_fail, ['-v0']) From git at git.haskell.org Fri Nov 21 16:18:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 16:18:39 +0000 (UTC) Subject: [commit: ghc] master: Fix #9824 by not warning about unused matches in pattern quotes. (bc05354) Message-ID: <20141121161839.1BE0A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bc05354949dce9d3b56353d3310eb9804d4e17f5/ghc >--------------------------------------------------------------- commit bc05354949dce9d3b56353d3310eb9804d4e17f5 Author: Richard Eisenberg Date: Fri Nov 21 10:33:37 2014 -0500 Fix #9824 by not warning about unused matches in pattern quotes. >--------------------------------------------------------------- bc05354949dce9d3b56353d3310eb9804d4e17f5 compiler/rename/RnPat.lhs | 3 +++ testsuite/tests/th/all.T | 2 +- 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/compiler/rename/RnPat.lhs b/compiler/rename/RnPat.lhs index 370f6b4..d80b05e 100644 --- a/compiler/rename/RnPat.lhs +++ b/compiler/rename/RnPat.lhs @@ -203,6 +203,9 @@ matchNameMaker ctxt = LamMk report_unused -- i.e. when you type 'x <- e' at the GHCi prompt report_unused = case ctxt of StmtCtxt GhciStmtCtxt -> False + -- also, don't warn in pattern quotes, as there + -- is no RHS where the variables can be used! + ThPatQuote -> False _ -> True rnHsSigCps :: HsWithBndrs RdrName (LHsType RdrName) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index e8b8cb6..60b6089 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -346,4 +346,4 @@ test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) test('T1476', normal, compile, ['-v0']) test('T1476b', normal, compile_fail, ['-v0']) -test('T9824', expect_broken(9824), compile, ['-v0']) +test('T9824', normal, compile, ['-v0']) From git at git.haskell.org Fri Nov 21 16:18:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 16:18:42 +0000 (UTC) Subject: [commit: ghc] master: Test #9824 in th/T9824 (3b3944f) Message-ID: <20141121161842.1C2823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3b3944f9a1cf7d89dccf742d7449402cca31ba5a/ghc >--------------------------------------------------------------- commit 3b3944f9a1cf7d89dccf742d7449402cca31ba5a Author: Richard Eisenberg Date: Fri Nov 21 10:31:40 2014 -0500 Test #9824 in th/T9824 >--------------------------------------------------------------- 3b3944f9a1cf7d89dccf742d7449402cca31ba5a testsuite/tests/th/T9824.hs | 6 ++++++ testsuite/tests/th/all.T | 1 + 2 files changed, 7 insertions(+) diff --git a/testsuite/tests/th/T9824.hs b/testsuite/tests/th/T9824.hs new file mode 100644 index 0000000..828c008 --- /dev/null +++ b/testsuite/tests/th/T9824.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# OPTIONS_GHC -fwarn-unused-matches #-} + +module T9824 where + +foo = [p| (x, y) |] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 366858e..e8b8cb6 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -346,3 +346,4 @@ test('T9209', normal, compile_fail, ['-v0']) test('T7484', normal, compile_fail, ['-v0']) test('T1476', normal, compile, ['-v0']) test('T1476b', normal, compile_fail, ['-v0']) +test('T9824', expect_broken(9824), compile, ['-v0']) From git at git.haskell.org Fri Nov 21 16:18:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 16:18:44 +0000 (UTC) Subject: [commit: ghc] master: Update manual for pattern splices (#1476) (cfa574c) Message-ID: <20141121161844.B3E6F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cfa574cea30b411080de5d641309bdf135ed9be5/ghc >--------------------------------------------------------------- commit cfa574cea30b411080de5d641309bdf135ed9be5 Author: Richard Eisenberg Date: Fri Nov 21 10:51:38 2014 -0500 Update manual for pattern splices (#1476) >--------------------------------------------------------------- cfa574cea30b411080de5d641309bdf135ed9be5 docs/users_guide/glasgow_exts.xml | 55 ++++++++++++++++++++++++++++++--------- 1 file changed, 42 insertions(+), 13 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index a21e677..f73a1d9 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -8785,25 +8785,54 @@ h z = z-1 - Binders are lexically scoped. For example, consider the - following code, where a value g of type - Bool -> Q Pat is in scope, having been - imported from another module + Outermost pattern splices may bind variables. By "outermost" here, we refer to + a pattern splice that occurs outside of any quotation brackets. For example, + -y :: Int -y = 7 +mkPat :: Bool -> Q Pat +mkPat True = [p| (x, y) |] +mkPat False = [p| (y, x) |] -f :: Int -> Int -> Int -f n = \ $(g True) -> y+n +-- in another module: +foo :: (Char, String) -> String +foo $(mkPat True) = x : y + +bar :: (String, Char) -> String +bar $(mkPat False) = x : y + + + + + + + + Nested pattern splices do not bind variables. + By "nested" here, we refer to a pattern splice occurring within a + quotation bracket. Continuing the example from the last bullet: + + +baz :: Bool -> Q Exp +baz b = [| quux $(mkPat b) = x + y |] - The y in the right-hand side of - f refers to the top-level y = - 7, even if the pattern splice $(g - n) also generates a binder y. + + would fail with x and y + being out of scope. - Note that a pattern quasiquoter may + The difference in treatment of outermost and nested pattern splices is + because outermost splices are run at compile time. GHC can then use + the result of running the splice when analyzing the expressions within + the pattern's scope. Nested splices, on the other hand, are not + run at compile time; they are run when the bracket is spliced in, sometime later. + Since nested pattern splices may refer to local variables, there is no way for GHC + to know, at splice compile time, what variables are bound, so it binds none. + + + + + + A pattern quasiquoter may generate binders that scope over the right-hand side of a definition because these binders are in scope lexically. For example, given a quasiquoter haskell that From git at git.haskell.org Fri Nov 21 17:25:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 17:25:52 +0000 (UTC) Subject: [commit: ghc] master: AST changes to prepare for API annotations, for #9628 (7927658) Message-ID: <20141121172552.AC3663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7927658ed1dcf557c7dd78e4b9844100521391c8/ghc >--------------------------------------------------------------- commit 7927658ed1dcf557c7dd78e4b9844100521391c8 Author: Alan Zimmerman Date: Fri Nov 21 11:20:06 2014 -0600 AST changes to prepare for API annotations, for #9628 Summary: AST changes to prepare for API annotations Add locations to parts of the AST so that API annotations can then be added. The outline of the whole process is captured here https://ghc.haskell.org/trac/ghc/wiki/GhcAstAnnotations This change updates the haddock submodule. Test Plan: sh ./validate Reviewers: austin, simonpj, Mikolaj Reviewed By: simonpj, Mikolaj Subscribers: thomie, goldfire, carter Differential Revision: https://phabricator.haskell.org/D426 GHC Trac Issues: #9628 >--------------------------------------------------------------- 7927658ed1dcf557c7dd78e4b9844100521391c8 compiler/basicTypes/BasicTypes.lhs | 9 +- compiler/deSugar/Check.lhs | 8 +- compiler/deSugar/Coverage.lhs | 11 +- compiler/deSugar/Desugar.lhs | 8 +- compiler/deSugar/DsExpr.lhs | 18 +- compiler/deSugar/DsForeign.lhs | 7 +- compiler/deSugar/DsMeta.hs | 100 +++++----- compiler/deSugar/Match.lhs | 4 +- compiler/deSugar/MatchCon.lhs | 9 +- compiler/hsSyn/Convert.lhs | 55 +++--- compiler/hsSyn/HsBinds.lhs | 11 +- compiler/hsSyn/HsDecls.lhs | 104 +++++++---- compiler/hsSyn/HsExpr.lhs | 14 +- compiler/hsSyn/HsImpExp.lhs | 51 +++--- compiler/hsSyn/HsPat.lhs | 9 +- compiler/hsSyn/HsSyn.lhs | 9 +- compiler/hsSyn/HsTypes.lhs | 21 ++- compiler/hsSyn/HsUtils.lhs | 18 +- compiler/main/HeaderInfo.hs | 3 +- compiler/main/HscMain.hs | 4 +- compiler/main/HscStats.hs | 9 +- compiler/parser/HaddockUtils.hs | 8 +- compiler/parser/Parser.y | 204 +++++++++++---------- compiler/parser/RdrHsSyn.hs | 95 +++++----- compiler/rename/RnBinds.lhs | 25 ++- compiler/rename/RnEnv.lhs | 9 +- compiler/rename/RnExpr.lhs | 12 +- compiler/rename/RnNames.lhs | 129 +++++++------ compiler/rename/RnPat.lhs | 32 ++-- compiler/rename/RnSource.lhs | 126 ++++++------- compiler/rename/RnTypes.lhs | 18 +- compiler/typecheck/TcBinds.lhs | 25 +-- compiler/typecheck/TcDeriv.lhs | 13 +- compiler/typecheck/TcExpr.lhs | 20 +- compiler/typecheck/TcForeign.lhs | 19 +- compiler/typecheck/TcHsSyn.lhs | 26 +-- compiler/typecheck/TcInstDcls.lhs | 9 +- compiler/typecheck/TcPat.lhs | 7 +- compiler/typecheck/TcPatSyn.lhs | 6 +- compiler/typecheck/TcRnDriver.lhs | 6 +- compiler/typecheck/TcRules.lhs | 19 +- compiler/typecheck/TcTyClsDecls.lhs | 129 +++++++++---- compiler/utils/Binary.hs | 38 ++++ ghc/InteractiveUI.hs | 7 +- .../haddock/haddock_examples/haddock.Test.stderr | 6 +- utils/ghctags/Main.hs | 2 +- utils/haddock | 2 +- 47 files changed, 859 insertions(+), 615 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7927658ed1dcf557c7dd78e4b9844100521391c8 From git at git.haskell.org Fri Nov 21 17:25:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 17:25:57 +0000 (UTC) Subject: [commit: ghc] master: Add API Annotations (803fc5d) Message-ID: <20141121172557.1F08F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/803fc5db31f084b73713342cdceaed5a9c664267/ghc >--------------------------------------------------------------- commit 803fc5db31f084b73713342cdceaed5a9c664267 Author: Alan Zimmerman Date: Fri Nov 21 11:20:13 2014 -0600 Add API Annotations Summary: The final design and discussion is captured at https://ghc.haskell.org/trac/ghc/wiki/GhcAstAnnotations This is a proof of concept implementation of a completely separate annotation structure, populated in the parser,and tied to the AST by means of a virtual "node-key" comprising the surrounding SrcSpan and a value derived from the specific constructor used for the node. The key parts of the design are the following. == The Annotations == In `hsSyn/ApiAnnotation.hs` ```lang=haskell type ApiAnns = (Map.Map ApiAnnKey SrcSpan, Map.Map SrcSpan [Located Token]) type ApiAnnKey = (SrcSpan,AnnKeywordId) -- --------------------------------------------------------------------- -- | Retrieve an annotation based on the @SrcSpan@ of the annotated AST -- element, and the known type of the annotation. getAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> Maybe SrcSpan getAnnotation (anns,_) span ann = Map.lookup (span,ann) anns -- |Retrieve the comments allocated to the current @SrcSpan@ getAnnotationComments :: ApiAnns -> SrcSpan -> [Located Token] getAnnotationComments (_,anns) span = case Map.lookup span anns of Just cs -> cs Nothing -> [] -- | Note: in general the names of these are taken from the -- corresponding token, unless otherwise noted data AnnKeywordId = AnnAs | AnnBang | AnnClass | AnnClose -- ^ } or ] or ) or #) etc | AnnComma | AnnDarrow | AnnData | AnnDcolon .... ``` == Capturing in the lexer/parser == The annotations are captured in the lexer / parser by extending PState to include a field In `parser/Lexer.x` ```lang=haskell data PState = PState { .... annotations :: [(ApiAnnKey,SrcSpan)] -- Annotations giving the locations of 'noise' tokens in the -- source, so that users of the GHC API can do source to -- source conversions. } ``` The lexer exposes a helper function to add an annotation ```lang=haskell addAnnotation :: SrcSpan -> Ann -> SrcSpan -> P () addAnnotation l a v = P $ \s -> POk s { annotations = ((AK l a), v) : annotations s } () ``` The parser also has some helper functions of the form ```lang=haskell type MaybeAnn = Maybe (SrcSpan -> P ()) gl = getLoc gj x = Just (gl x) ams :: Located a -> [MaybeAnn] -> P (Located a) ams a@(L l _) bs = (mapM_ (\a -> a l) $ catMaybes bs) >> return a ``` This allows annotations to be captured in the parser by means of ``` ctypedoc :: { LHsType RdrName } : 'forall' tv_bndrs '.' ctypedoc {% hintExplicitForall (getLoc $1) >> ams (LL $ mkExplicitHsForAllTy $2 (noLoc []) $4) [mj AnnForall $1,mj AnnDot $3] } | context '=>' ctypedoc {% ams (LL $ mkQualifiedHsForAllTy $1 $3) [mj AnnDarrow $2] } | ipvar '::' type {% ams (LL (HsIParamTy (unLoc $1) $3)) [mj AnnDcolon $2] } | typedoc { $1 } ``` == Parse result == ```lang-haskell data HsParsedModule = HsParsedModule { hpm_module :: Located (HsModule RdrName), hpm_src_files :: [FilePath], -- ^ extra source files (e.g. from #includes). The lexer collects -- these from '# ' pragmas, which the C preprocessor -- leaves behind. These files and their timestamps are stored in -- the .hi file, so that we can force recompilation if any of -- them change (#3589) hpm_annotations :: ApiAnns } -- | The result of successful parsing. data ParsedModule = ParsedModule { pm_mod_summary :: ModSummary , pm_parsed_source :: ParsedSource , pm_extra_src_files :: [FilePath] , pm_annotations :: ApiAnns } ``` This diff depends on D426 Test Plan: sh ./validate Reviewers: austin, simonpj, Mikolaj Reviewed By: simonpj, Mikolaj Subscribers: Mikolaj, goldfire, thomie, carter Differential Revision: https://phabricator.haskell.org/D438 GHC Trac Issues: #9628 >--------------------------------------------------------------- 803fc5db31f084b73713342cdceaed5a9c664267 compiler/basicTypes/DataCon.lhs | 3 + compiler/ghc.cabal.in | 1 + compiler/ghc.mk | 2 + compiler/hsSyn/HsBinds.lhs | 46 +- compiler/hsSyn/HsDecls.lhs | 108 +- compiler/hsSyn/HsExpr.lhs | 105 +- compiler/hsSyn/HsImpExp.lhs | 40 +- compiler/hsSyn/HsPat.lhs | 2 + compiler/hsSyn/HsSyn.lhs | 23 +- compiler/hsSyn/HsTypes.lhs | 15 +- compiler/hsSyn/HsUtils.lhs | 8 +- compiler/main/GHC.hs | 16 +- compiler/main/HeaderInfo.hs | 4 +- compiler/main/HscMain.hs | 7 +- compiler/main/HscTypes.lhs | 5 +- compiler/parser/ApiAnnotation.hs | 238 +++ compiler/parser/Lexer.x | 129 +- compiler/parser/Parser.y | 1719 +++++++++++++------- compiler/parser/RdrHsSyn.hs | 8 +- ghc/InteractiveUI.hs | 2 +- testsuite/tests/ghc-api/annotations/.gitignore | 7 + .../tests/ghc-api/annotations/AnnotationLet.hs | 12 + .../tests/ghc-api/annotations/AnnotationTuple.hs | 20 + .../tests/ghc-api/annotations/CommentsTest.hs | 13 + testsuite/tests/ghc-api/annotations/Makefile | 21 + testsuite/tests/ghc-api/annotations/all.T | 4 + testsuite/tests/ghc-api/annotations/annotations.hs | 58 + .../tests/ghc-api/annotations/annotations.stdout | 51 + testsuite/tests/ghc-api/annotations/comments.hs | 64 + .../tests/ghc-api/annotations/comments.stdout | 24 + .../landmines.hs => annotations/parseTree.hs} | 42 +- .../tests/ghc-api/annotations/parseTree.stdout | 122 ++ 32 files changed, 2248 insertions(+), 671 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 803fc5db31f084b73713342cdceaed5a9c664267 From git at git.haskell.org Fri Nov 21 17:31:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 17:31:35 +0000 (UTC) Subject: [commit: ghc] master: Fixes ghci :unset -X so that it doesn't fail to reverse option. (fixes trac #9293) (3e4f49b) Message-ID: <20141121173135.4ED683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3e4f49b04e6e97256b4d34221e209e1051bf06ae/ghc >--------------------------------------------------------------- commit 3e4f49b04e6e97256b4d34221e209e1051bf06ae Author: Muhaimin Ahsan Date: Fri Nov 21 11:31:44 2014 -0600 Fixes ghci :unset -X so that it doesn't fail to reverse option. (fixes trac #9293) Summary: ghci unset could not reverse language extensions. Reviewers: hvr, thomie, austin Reviewed By: hvr, thomie, austin Subscribers: goldfire, hvr, thomie, carter Differential Revision: https://phabricator.haskell.org/D516 GHC Trac Issues: #9293 >--------------------------------------------------------------- 3e4f49b04e6e97256b4d34221e209e1051bf06ae ghc/InteractiveUI.hs | 1 + testsuite/tests/ghci/scripts/{ghci057.hs => T9293.hs} | 1 - testsuite/tests/ghci/scripts/{ghci057.script => T9293.script} | 2 +- testsuite/tests/ghci/scripts/{ghci057.stderr => T9293.stderr} | 0 testsuite/tests/ghci/scripts/{ghci057.stdout => T9293.stdout} | 0 testsuite/tests/ghci/scripts/all.T | 1 + testsuite/tests/safeHaskell/ghci/p12.stderr | 4 ++-- testsuite/tests/safeHaskell/ghci/p5.stderr | 6 +++--- 8 files changed, 8 insertions(+), 7 deletions(-) diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index f5a1bbe..7fdda0b 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -2182,6 +2182,7 @@ unsetOptions str ] no_flag ('-':'f':rest) = return ("-fno-" ++ rest) + no_flag ('-':'X':rest) = return ("-XNo" ++ rest) no_flag f = throwGhcException (ProgramError ("don't know how to reverse " ++ f)) in if (not (null rest3)) diff --git a/testsuite/tests/ghci/scripts/ghci057.hs b/testsuite/tests/ghci/scripts/T9293.hs similarity index 97% copy from testsuite/tests/ghci/scripts/ghci057.hs copy to testsuite/tests/ghci/scripts/T9293.hs index 2a6b836..f7329c9 100644 --- a/testsuite/tests/ghci/scripts/ghci057.hs +++ b/testsuite/tests/ghci/scripts/T9293.hs @@ -1,4 +1,3 @@ module Test where data T a where C :: T Int - diff --git a/testsuite/tests/ghci/scripts/ghci057.script b/testsuite/tests/ghci/scripts/T9293.script similarity index 96% copy from testsuite/tests/ghci/scripts/ghci057.script copy to testsuite/tests/ghci/scripts/T9293.script index 547fce5..c2fbf46 100644 --- a/testsuite/tests/ghci/scripts/ghci057.script +++ b/testsuite/tests/ghci/scripts/T9293.script @@ -9,7 +9,7 @@ data T a where C :: T Int putStrLn "Should work, GADTs is in force from :set" :load ghci057.hs -:set -XNoGADTs +:unset -XGADTs :set putStrLn "Should fail, GADTs is now disabled" diff --git a/testsuite/tests/ghci/scripts/ghci057.stderr b/testsuite/tests/ghci/scripts/T9293.stderr similarity index 100% copy from testsuite/tests/ghci/scripts/ghci057.stderr copy to testsuite/tests/ghci/scripts/T9293.stderr diff --git a/testsuite/tests/ghci/scripts/ghci057.stdout b/testsuite/tests/ghci/scripts/T9293.stdout similarity index 100% copy from testsuite/tests/ghci/scripts/ghci057.stdout copy to testsuite/tests/ghci/scripts/T9293.stdout diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 624f431..12bfebf 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -190,3 +190,4 @@ test('T9181', normal, ghci_script, ['T9181.script']) test('T9086b', normal, ghci_script, ['T9086b.script']) test('T9140', combined_output, ghci_script, ['T9140.script']) test('T9658', normal, ghci_script, ['T9658.script']) +test('T9293', normal, ghci_script_without_flag('-fno-warn-tabs'), ['T9293.script']) diff --git a/testsuite/tests/safeHaskell/ghci/p12.stderr b/testsuite/tests/safeHaskell/ghci/p12.stderr index fc43305..3b259c3 100644 --- a/testsuite/tests/safeHaskell/ghci/p12.stderr +++ b/testsuite/tests/safeHaskell/ghci/p12.stderr @@ -1,7 +1,7 @@ -don't know how to reverse -XSafe +Some flags have not been recognized: -XNoSafe Some flags have not been recognized: -fno-package-trust : Data.ByteString: Can't be safely imported! - The package (bytestring-0.10.1.0) the module resides in isn't trusted. + The package (bytestring-0.10.5.0) the module resides in isn't trusted. diff --git a/testsuite/tests/safeHaskell/ghci/p5.stderr b/testsuite/tests/safeHaskell/ghci/p5.stderr index 3f649f7..7e70988 100644 --- a/testsuite/tests/safeHaskell/ghci/p5.stderr +++ b/testsuite/tests/safeHaskell/ghci/p5.stderr @@ -1,7 +1,7 @@ -don't know how to reverse -XSafe +Some flags have not been recognized: -XNoSafe ghc-stage2: : Incompatible Safe Haskell flags! (Safe, Trustworthy) Usage: For basic information, try the `--help' option. -don't know how to reverse -XTrustworthy +Some flags have not been recognized: -XNoTrustworthy ghc-stage2: : Incompatible Safe Haskell flags! (Safe, Unsafe) Usage: For basic information, try the `--help' option. -don't know how to reverse -XUnsafe +Some flags have not been recognized: -XNoUnsafe From git at git.haskell.org Fri Nov 21 17:32:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 17:32:25 +0000 (UTC) Subject: [commit: ghc] master: Export more Packages functions (3793d3b) Message-ID: <20141121173225.C0D383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3793d3b2b0199e50f6066f948a7c94df0c9f3580/ghc >--------------------------------------------------------------- commit 3793d3b2b0199e50f6066f948a7c94df0c9f3580 Author: Luite Stegeman Date: Fri Nov 21 11:33:00 2014 -0600 Export more Packages functions Summary: This patch exports functions for finding the active package databases and their locations from the Packages module. This allows GHC API clients to use other tools, like Cabal, to gather package information that's not directly available from the binary package db. Reviewers: duncan, austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D514 >--------------------------------------------------------------- 3793d3b2b0199e50f6066f948a7c94df0c9f3580 compiler/main/Packages.lhs | 15 +++++++++++---- 1 file changed, 11 insertions(+), 4 deletions(-) diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs index 40b5e24..2151902 100644 --- a/compiler/main/Packages.lhs +++ b/compiler/main/Packages.lhs @@ -11,6 +11,10 @@ module Packages ( -- * Reading the package config, and processing cmdline args PackageState(preloadPackages), initPackages, + readPackageConfigs, + getPackageConfRefs, + resolvePackageConfig, + readPackageConfig, -- * Querying the package config lookupPackage, @@ -328,6 +332,12 @@ initPackages dflags = do readPackageConfigs :: DynFlags -> IO [PackageConfig] readPackageConfigs dflags = do + conf_refs <- getPackageConfRefs dflags + confs <- liftM catMaybes $ mapM (resolvePackageConfig dflags) conf_refs + liftM concat $ mapM (readPackageConfig dflags) confs + +getPackageConfRefs :: DynFlags -> IO [PkgConfRef] +getPackageConfRefs dflags = do let system_conf_refs = [UserPkgConf, GlobalPkgConf] e_pkg_path <- tryIO (getEnv "GHC_PACKAGE_PATH") @@ -339,13 +349,10 @@ readPackageConfigs dflags = do | otherwise -> map PkgConfFile (splitSearchPath path) - let conf_refs = reverse (extraPkgConfs dflags base_conf_refs) + return $ reverse (extraPkgConfs dflags base_conf_refs) -- later packages shadow earlier ones. extraPkgConfs -- is in the opposite order to the flags on the -- command line. - confs <- liftM catMaybes $ mapM (resolvePackageConfig dflags) conf_refs - - liftM concat $ mapM (readPackageConfig dflags) confs resolvePackageConfig :: DynFlags -> PkgConfRef -> IO (Maybe FilePath) resolvePackageConfig dflags GlobalPkgConf = return $ Just (systemPackageConfig dflags) From git at git.haskell.org Fri Nov 21 17:34:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 17:34:08 +0000 (UTC) Subject: [commit: ghc] master: Add Data.Void to base (re #9814) (a97f90c) Message-ID: <20141121173408.B904B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a97f90cecb6351a6db5a62c1551fcbf079b0acdd/ghc >--------------------------------------------------------------- commit a97f90cecb6351a6db5a62c1551fcbf079b0acdd Author: Herbert Valerio Riedel Date: Fri Nov 21 18:30:14 2014 +0100 Add Data.Void to base (re #9814) This adds the module `Data.Void` (formerly provided by Edward Kmett's `void` package) to `base`. The original Haskell98 compatible implementation has been modified to use modern GHC features (among others this makes use of `EmptyCase` as motivated by #2431), and `vacuousM` was dropped since it's redundant now with the AMP in place. Instances for classes not part of `base` had to be dropped as well. TODO: Documentation could be improved Reviewed By: ekmett, austin Differential Revision: https://phabricator.haskell.org/D506 >--------------------------------------------------------------- a97f90cecb6351a6db5a62c1551fcbf079b0acdd libraries/base/Data/Void.hs | 74 +++++++++++++++++++++++++++++++++++++++++++++ libraries/base/base.cabal | 1 + libraries/base/changelog.md | 3 ++ 3 files changed, 78 insertions(+) diff --git a/libraries/base/Data/Void.hs b/libraries/base/Data/Void.hs new file mode 100644 index 0000000..a4f8778 --- /dev/null +++ b/libraries/base/Data/Void.hs @@ -0,0 +1,74 @@ +{-# LANGUAGE AutoDeriveTypeable #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE EmptyCase #-} +{-# LANGUAGE Safe #-} +{-# LANGUAGE StandaloneDeriving #-} + +----------------------------------------------------------------------------- +-- | +-- Copyright : (C) 2008-2014 Edward Kmett +-- License : BSD-style (see the file libraries/base/LICENSE) +-- +-- Maintainer : Edward Kmett +-- Stability : provisional +-- Portability : portable +-- +-- A logically uninhabited data type, used to indicate that a given +-- term should not exist. +-- +-- /Since: 4.8.0.0/ +---------------------------------------------------------------------------- +module Data.Void + ( Void + , absurd + , vacuous + ) where + +import Control.Exception +import Data.Data +import Data.Ix +import GHC.Generics + +-- | Uninhabited data type +-- +-- /Since: 4.8.0.0/ +data Void deriving (Generic) + +deriving instance Data Void + +instance Eq Void where + _ == _ = True + +instance Ord Void where + compare _ _ = EQ + +-- | Reading a 'Void' value is always a parse error, considering +-- 'Void' as a data type with no constructors. +instance Read Void where + readsPrec _ _ = [] + +instance Show Void where + showsPrec _ = absurd + +instance Ix Void where + range _ = [] + index _ = absurd + inRange _ = absurd + rangeSize _ = 0 + +instance Exception Void + +-- | Since 'Void' values logically don't exist, this witnesses the +-- logical reasoning tool of \"ex falso quodlibet\". +-- +-- /Since: 4.8.0.0/ +absurd :: Void -> a +absurd a = case a of {} + +-- | If 'Void' is uninhabited then any 'Functor' that holds only +-- values of type 'Void' is holding no values. +-- +-- /Since: 4.8.0.0/ +vacuous :: Functor f => f Void -> f a +vacuous = fmap absurd diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal index ca619ca..bde2a29 100644 --- a/libraries/base/base.cabal +++ b/libraries/base/base.cabal @@ -170,6 +170,7 @@ Library Data.Typeable.Internal Data.Unique Data.Version + Data.Void Data.Word Debug.Trace Foreign diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 56bfc31..7825c97 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -83,6 +83,9 @@ * New module `Data.Bifunctor` providing the `Bifunctor(bimap,first,second)` class (previously defined in `bifunctors` package) (#9682) + * New module `Data.Void` providing the canonical uninhabited type `Void` + (previously defined in `void` package) (#9814) + * Update Unicode class definitions to Unicode version 7.0 * Add `Alt`, an `Alternative` wrapper, to `Data.Monoid`. (#9759) From git at git.haskell.org Fri Nov 21 19:24:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 19:24:47 +0000 (UTC) Subject: [commit: ghc] master: Capture original source for literals (c0ad5bc) Message-ID: <20141121192447.BA7113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c0ad5bc03e02ce0d7d545599e4b1a68a6f727f2b/ghc >--------------------------------------------------------------- commit c0ad5bc03e02ce0d7d545599e4b1a68a6f727f2b Author: Alan Zimmerman Date: Fri Nov 21 13:24:30 2014 -0600 Capture original source for literals Summary: Make HsLit and OverLitVal have original source strings, for source to source conversions using the GHC API This is part of the ongoing AST Annotations work, as captured in https://ghc.haskell.org/trac/ghc/wiki/GhcAstAnnotations and https://ghc.haskell.org/trac/ghc/ticket/9628#comment:28 The motivations for the literals is as follows ```lang=haskell x,y :: Int x = 0003 y = 0x04 s :: String s = "\x20" c :: Char c = '\x20' d :: Double d = 0.00 blah = x where charH = '\x41'# intH = 0004# wordH = 005## floatH = 3.20# doubleH = 04.16## x = 1 ``` Test Plan: ./sh validate Reviewers: simonpj, austin Reviewed By: simonpj, austin Subscribers: thomie, goldfire, carter, simonmar Differential Revision: https://phabricator.haskell.org/D412 GHC Trac Issues: #9628 >--------------------------------------------------------------- c0ad5bc03e02ce0d7d545599e4b1a68a6f727f2b compiler/deSugar/Check.lhs | 18 ++- compiler/deSugar/DsMeta.hs | 40 +++--- compiler/deSugar/MatchLit.lhs | 90 +++++++------ compiler/ghc.mk | 2 + compiler/hsSyn/Convert.lhs | 14 +- compiler/hsSyn/HsExpr.lhs | 4 +- compiler/hsSyn/HsLit.lhs | 149 +++++++++++++-------- compiler/hsSyn/HsPat.lhs | 5 +- compiler/hsSyn/HsUtils.lhs | 14 +- compiler/parser/Lexer.x | 61 +++++---- compiler/parser/Parser.y | 71 ++++++---- compiler/parser/RdrHsSyn.hs | 4 +- compiler/rename/RnExpr.lhs | 4 +- compiler/rename/RnPat.lhs | 11 +- compiler/typecheck/Inst.lhs | 6 +- compiler/typecheck/TcBinds.lhs | 3 +- compiler/typecheck/TcExpr.lhs | 3 +- compiler/typecheck/TcGenDeriv.lhs | 30 +++-- compiler/typecheck/TcHsSyn.lhs | 39 +++--- compiler/typecheck/TcInstDcls.lhs | 3 +- compiler/typecheck/TcRnDriver.lhs | 3 +- compiler/typecheck/TcSplice.lhs | 2 +- compiler/typecheck/TcTyClsDecls.lhs | 2 +- .../{landmines => annotations-literals}/.gitignore | 3 +- .../ghc-api/annotations-literals/LiteralsTest.hs | 24 ++++ .../tests/ghc-api/annotations-literals/Makefile | 16 +++ testsuite/tests/ghc-api/annotations-literals/all.T | 2 + .../tests/ghc-api/annotations-literals/literals.hs | 43 ++++++ .../ghc-api/annotations-literals/literals.stdout | 145 ++++++++++++++++++++ .../tests/ghc-api/annotations-literals/parsed.hs | 109 +++++++++++++++ .../ghc-api/annotations-literals/parsed.stdout | 12 ++ 31 files changed, 683 insertions(+), 249 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c0ad5bc03e02ce0d7d545599e4b1a68a6f727f2b From git at git.haskell.org Fri Nov 21 19:50:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 19:50:33 +0000 (UTC) Subject: [commit: ghc] master: Add 'fillBytes' to Foreign.Marshal.Utils. (3583312) Message-ID: <20141121195033.2912D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/35833122da8ddb2c0e7aaee0c9b6089af52e38b1/ghc >--------------------------------------------------------------- commit 35833122da8ddb2c0e7aaee0c9b6089af52e38b1 Author: Alex Petrov Date: Fri Nov 21 19:24:37 2014 +0100 Add 'fillBytes' to Foreign.Marshal.Utils. fillBytes uses 'memset' to fill a memory area with a given byte value. Reviewed By: austin, hvr Differential Revision: https://phabricator.haskell.org/D465 >--------------------------------------------------------------- 35833122da8ddb2c0e7aaee0c9b6089af52e38b1 libraries/base/Foreign/Marshal/Utils.hs | 19 +++++++++++++++++-- libraries/base/changelog.md | 2 ++ 2 files changed, 19 insertions(+), 2 deletions(-) diff --git a/libraries/base/Foreign/Marshal/Utils.hs b/libraries/base/Foreign/Marshal/Utils.hs index 4654e55..c24c249 100644 --- a/libraries/base/Foreign/Marshal/Utils.hs +++ b/libraries/base/Foreign/Marshal/Utils.hs @@ -43,13 +43,18 @@ module Foreign.Marshal.Utils ( -- copyBytes, moveBytes, + + -- ** Filling up memory area with required values + -- + fillBytes, ) where import Data.Maybe import Foreign.Ptr ( Ptr, nullPtr ) import Foreign.Storable ( Storable(poke) ) -import Foreign.C.Types ( CSize(..) ) +import Foreign.C.Types ( CSize(..), CInt(..) ) import Foreign.Marshal.Alloc ( malloc, alloca ) +import Data.Word ( Word8 ) import GHC.Real ( fromIntegral ) import GHC.Num @@ -161,6 +166,16 @@ moveBytes :: Ptr a -> Ptr a -> Int -> IO () moveBytes dest src size = do _ <- memmove dest src (fromIntegral size) return () +-- Filling up memory area with required values +-- ------------------------------------------- + +-- |Fill a given number of bytes in memory area with a byte value. +-- +-- /Since: 4.8.0.0/ +fillBytes :: Ptr a -> Word8 -> Int -> IO () +fillBytes dest char size = do + _ <- memset dest (fromIntegral char) (fromIntegral size) + return () -- auxilliary routines -- ------------------- @@ -169,4 +184,4 @@ moveBytes dest src size = do _ <- memmove dest src (fromIntegral size) -- foreign import ccall unsafe "string.h" memcpy :: Ptr a -> Ptr a -> CSize -> IO (Ptr a) foreign import ccall unsafe "string.h" memmove :: Ptr a -> Ptr a -> CSize -> IO (Ptr a) - +foreign import ccall unsafe "string.h" memset :: Ptr a -> CInt -> CSize -> IO (Ptr a) diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 7825c97..3e110a7 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -102,6 +102,8 @@ * Add `scanl'`, a strictly accumulating version of `scanl`, to `Data.List` and `Data.OldList`. (#9368) + * Add `fillBytes` to `Foreign.Marshal.Utils`. + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 From git at git.haskell.org Fri Nov 21 20:23:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 20:23:24 +0000 (UTC) Subject: [commit: packages/haskell2010] master: Fix deprecation of Foreign.Safe in base 4.8 (37670e7) Message-ID: <20141121202324.CE00C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskell2010 On branch : master Link : http://git.haskell.org/packages/haskell2010.git/commitdiff/37670e7e35a09c94a0af4ccd530198b4ac74420a >--------------------------------------------------------------- commit 37670e7e35a09c94a0af4ccd530198b4ac74420a Author: David Terei Date: Fri Nov 21 11:34:37 2014 -0800 Fix deprecation of Foreign.Safe in base 4.8 >--------------------------------------------------------------- 37670e7e35a09c94a0af4ccd530198b4ac74420a Foreign/Marshal/Array.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Foreign/Marshal/Array.hs b/Foreign/Marshal/Array.hs index 4f8d181..7f45c46 100644 --- a/Foreign/Marshal/Array.hs +++ b/Foreign/Marshal/Array.hs @@ -66,7 +66,7 @@ module Foreign.Marshal.Array ( ) where import qualified "base" Foreign.Marshal.Array as Base import "base" Foreign.Marshal.Array hiding (peekArray) -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 701 && __GLASGOW_HASKELL__ < 709 import "base" Foreign.Safe hiding (peekArray) #else import "base" Foreign hiding (peekArray) From git at git.haskell.org Fri Nov 21 20:55:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 20:55:42 +0000 (UTC) Subject: [commit: ghc] master: Add T7220a.stderr (6265f1c) Message-ID: <20141121205542.0C1743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6265f1c3162a192220ec03d888e1c1ef686b2732/ghc >--------------------------------------------------------------- commit 6265f1c3162a192220ec03d888e1c1ef686b2732 Author: Joachim Breitner Date: Fri Nov 21 21:55:37 2014 +0100 Add T7220a.stderr which presumably was just forgotten when creating the testcase in commit 7b1a856. >--------------------------------------------------------------- 6265f1c3162a192220ec03d888e1c1ef686b2732 testsuite/tests/typecheck/should_compile/T7220a.stderr | 14 ++++++++++++++ 1 file changed, 14 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T7220a.stderr b/testsuite/tests/typecheck/should_compile/T7220a.stderr new file mode 100644 index 0000000..4be503d --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T7220a.stderr @@ -0,0 +1,14 @@ + +T7220a.hs:17:6: + Could not deduce (C a b) + from the context (C a0 b, TF b ~ Y) + bound by the type signature for f :: (C a0 b, TF b ~ Y) => b + at T7220a.hs:17:6-44 + Possible fix: + add (C a b) to the context of + the type signature for f :: (C a0 b, TF b ~ Y) => b + In the ambiguity check for the type signature for ?f?: + f :: forall a. (forall b. (C a b, TF b ~ Y) => b) -> X + To defer the ambiguity check to use sites, enable AllowAmbiguousTypes + In the type signature for ?f?: + f :: (forall b. (C a b, TF b ~ Y) => b) -> X From git at git.haskell.org Fri Nov 21 21:03:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 21:03:23 +0000 (UTC) Subject: [commit: ghc] master: Be consistent with placement of Safe Haskell mode at top of file (2a523eb) Message-ID: <20141121210323.ACD743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2a523ebf091478aea39deef28073320bed628434/ghc >--------------------------------------------------------------- commit 2a523ebf091478aea39deef28073320bed628434 Author: David Terei Date: Wed Nov 19 18:29:51 2014 -0800 Be consistent with placement of Safe Haskell mode at top of file >--------------------------------------------------------------- 2a523ebf091478aea39deef28073320bed628434 libraries/base/Control/Applicative.hs | 2 +- libraries/base/Control/Arrow.hs | 3 ++- libraries/base/Control/Category.hs | 2 +- libraries/base/Data/Foldable.hs | 2 +- libraries/base/Data/Function.hs | 2 +- libraries/base/Data/Functor.hs | 2 +- libraries/base/Data/Functor/Identity.hs | 2 +- libraries/base/Data/List.hs | 2 +- libraries/base/Data/Proxy.hs | 3 ++- libraries/base/Data/Traversable.hs | 2 +- libraries/base/Data/Typeable.hs | 2 +- libraries/base/Data/Typeable/Internal.hs | 2 +- libraries/base/Debug/Trace.hs | 2 +- libraries/base/Foreign/C/Types.hs | 8 ++------ libraries/base/Foreign/Marshal/Alloc.hs | 5 +---- libraries/base/Foreign/Ptr.hs | 8 ++------ libraries/base/Foreign/Storable.hs | 3 +-- libraries/base/GHC/Conc/Windows.hs | 3 ++- libraries/base/GHC/ConsoleHandler.hs | 2 +- libraries/base/GHC/Constants.hs | 2 +- libraries/base/GHC/Environment.hs | 2 +- libraries/base/GHC/Event.hs | 2 +- libraries/base/GHC/Event/Control.hs | 2 +- libraries/base/GHC/Event/IntTable.hs | 3 ++- libraries/base/GHC/Event/Thread.hs | 1 + libraries/base/GHC/Event/Unique.hs | 1 + libraries/base/GHC/Exts.hs | 4 ++-- libraries/base/GHC/Fingerprint.hs-boot | 1 + libraries/base/GHC/Fingerprint/Type.hs | 1 + libraries/base/GHC/IO/Encoding/CodePage/API.hs | 4 +++- libraries/base/GHC/MVar.hs | 4 ++-- libraries/base/GHC/Num.hs | 1 + libraries/base/GHC/PArr.hs | 2 +- libraries/base/GHC/Real.hs | 1 + libraries/base/GHC/ST.hs | 1 + libraries/base/GHC/Stable.hs | 3 ++- libraries/base/GHC/Stats.hsc | 2 +- libraries/base/GHC/Windows.hs | 1 + libraries/base/Text/Printf.hs | 2 +- libraries/ghc-prim/GHC/Debug.hs | 3 ++- 40 files changed, 52 insertions(+), 48 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2a523ebf091478aea39deef28073320bed628434 From git at git.haskell.org Fri Nov 21 21:03:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 21:03:26 +0000 (UTC) Subject: [commit: ghc] master: Update Control.Monad.ST.* for Safe Haskell as now they're safe by default (065d433) Message-ID: <20141121210326.4EEB13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/065d43335c03a47f74b702ea1f64a41ddefeb8d3/ghc >--------------------------------------------------------------- commit 065d43335c03a47f74b702ea1f64a41ddefeb8d3 Author: David Terei Date: Wed Nov 19 17:58:43 2014 -0800 Update Control.Monad.ST.* for Safe Haskell as now they're safe by default >--------------------------------------------------------------- 065d43335c03a47f74b702ea1f64a41ddefeb8d3 libraries/base/Control/Monad/ST.hs | 4 ++-- libraries/base/Control/Monad/ST/Lazy.hs | 4 ++-- libraries/base/Control/Monad/ST/Lazy/Imp.hs | 2 +- libraries/base/Control/Monad/ST/Lazy/Safe.hs | 2 +- libraries/base/Control/Monad/ST/Safe.hs | 2 +- libraries/base/Control/Monad/ST/Strict.hs | 2 ++ libraries/base/Data/STRef/Lazy.hs | 2 +- 7 files changed, 10 insertions(+), 8 deletions(-) diff --git a/libraries/base/Control/Monad/ST.hs b/libraries/base/Control/Monad/ST.hs index 0d2f58b..8313c2d 100644 --- a/libraries/base/Control/Monad/ST.hs +++ b/libraries/base/Control/Monad/ST.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} ----------------------------------------------------------------------------- -- | @@ -31,5 +31,5 @@ module Control.Monad.ST ( stToIO, ) where -import Control.Monad.ST.Safe +import Control.Monad.ST.Imp diff --git a/libraries/base/Control/Monad/ST/Lazy.hs b/libraries/base/Control/Monad/ST/Lazy.hs index c212728..ef2e648 100644 --- a/libraries/base/Control/Monad/ST/Lazy.hs +++ b/libraries/base/Control/Monad/ST/Lazy.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} ----------------------------------------------------------------------------- -- | @@ -30,5 +30,5 @@ module Control.Monad.ST.Lazy ( stToIO, ) where -import Control.Monad.ST.Lazy.Safe +import Control.Monad.ST.Lazy.Imp diff --git a/libraries/base/Control/Monad/ST/Lazy/Imp.hs b/libraries/base/Control/Monad/ST/Lazy/Imp.hs index 80c9fa5..55b28cf 100644 --- a/libraries/base/Control/Monad/ST/Lazy/Imp.hs +++ b/libraries/base/Control/Monad/ST/Lazy/Imp.hs @@ -38,7 +38,7 @@ module Control.Monad.ST.Lazy.Imp ( import Control.Monad.Fix -import qualified Control.Monad.ST.Safe as ST +import qualified Control.Monad.ST as ST import qualified Control.Monad.ST.Unsafe as ST import qualified GHC.ST as GHC.ST diff --git a/libraries/base/Control/Monad/ST/Lazy/Safe.hs b/libraries/base/Control/Monad/ST/Lazy/Safe.hs index 387313f..9f8e606 100644 --- a/libraries/base/Control/Monad/ST/Lazy/Safe.hs +++ b/libraries/base/Control/Monad/ST/Lazy/Safe.hs @@ -18,7 +18,7 @@ -- ----------------------------------------------------------------------------- -module Control.Monad.ST.Lazy.Safe ( +module Control.Monad.ST.Lazy.Safe {-# DEPRECATED "Safe is now the default, please use Control.Monad.ST.Lazy instead" #-} ( -- * The 'ST' monad ST, runST, diff --git a/libraries/base/Control/Monad/ST/Safe.hs b/libraries/base/Control/Monad/ST/Safe.hs index 1e9c981..d100832 100644 --- a/libraries/base/Control/Monad/ST/Safe.hs +++ b/libraries/base/Control/Monad/ST/Safe.hs @@ -18,7 +18,7 @@ -- ----------------------------------------------------------------------------- -module Control.Monad.ST.Safe ( +module Control.Monad.ST.Safe {-# DEPRECATED "Safe is now the default, please use Control.Monad.ST instead" #-} ( -- * The 'ST' Monad ST, -- abstract runST, diff --git a/libraries/base/Control/Monad/ST/Strict.hs b/libraries/base/Control/Monad/ST/Strict.hs index 4e474d9..c858548 100644 --- a/libraries/base/Control/Monad/ST/Strict.hs +++ b/libraries/base/Control/Monad/ST/Strict.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE Safe #-} + ----------------------------------------------------------------------------- -- | -- Module : Control.Monad.ST.Strict diff --git a/libraries/base/Data/STRef/Lazy.hs b/libraries/base/Data/STRef/Lazy.hs index 5134de4..c7c3291 100644 --- a/libraries/base/Data/STRef/Lazy.hs +++ b/libraries/base/Data/STRef/Lazy.hs @@ -23,7 +23,7 @@ module Data.STRef.Lazy ( modifySTRef ) where -import Control.Monad.ST.Lazy.Safe +import Control.Monad.ST.Lazy import qualified Data.STRef as ST newSTRef :: a -> ST s (ST.STRef s a) From git at git.haskell.org Fri Nov 21 21:03:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 21:03:28 +0000 (UTC) Subject: [commit: ghc] master: Improve Safe Haskell bounds for changes to base over time (5f84bd1) Message-ID: <20141121210328.E82E73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5f84bd1d6d08e20c254227fd2f72578b751addbe/ghc >--------------------------------------------------------------- commit 5f84bd1d6d08e20c254227fd2f72578b751addbe Author: David Terei Date: Wed Nov 19 18:02:30 2014 -0800 Improve Safe Haskell bounds for changes to base over time >--------------------------------------------------------------- 5f84bd1d6d08e20c254227fd2f72578b751addbe libraries/base/Control/Concurrent/QSem.hs | 2 +- libraries/base/Control/Concurrent/QSemN.hs | 2 +- libraries/base/Data/Bifunctor.hs | 4 +- libraries/base/Data/Data.hs | 7 ++-- libraries/base/Data/Type/Bool.hs | 1 + libraries/base/Data/Version.hs | 9 ++-- libraries/base/GHC/Char.hs | 2 +- libraries/base/GHC/Event/Control.hs | 2 +- libraries/base/GHC/Fingerprint.hs-boot | 2 +- libraries/base/GHC/IO/Encoding/CodePage/API.hs | 1 + libraries/base/GHC/IP.hs | 1 + libraries/base/GHC/Profiling.hs | 1 + libraries/base/GHC/Stack.hsc | 2 + libraries/base/GHC/TypeLits.hs | 1 + libraries/base/System/Timeout.hs | 2 +- .../tests/safeHaskell/unsafeLibs/BadImport05.hs | 12 ------ .../safeHaskell/unsafeLibs/BadImport05.stderr | 4 -- .../tests/safeHaskell/unsafeLibs/GoodImport02.hs | 10 ++--- .../tests/safeHaskell/unsafeLibs/GoodImport03.hs | 49 +++++++++++++--------- testsuite/tests/safeHaskell/unsafeLibs/all.T | 1 - 20 files changed, 57 insertions(+), 58 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5f84bd1d6d08e20c254227fd2f72578b751addbe From git at git.haskell.org Fri Nov 21 21:03:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 21:03:31 +0000 (UTC) Subject: [commit: ghc] master: Update Foreign.* for Safe Haskell now that they're safe by default (453ce62) Message-ID: <20141121210331.8D01D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/453ce626a32cab3728a640b2299eaeeb30da8862/ghc >--------------------------------------------------------------- commit 453ce626a32cab3728a640b2299eaeeb30da8862 Author: David Terei Date: Wed Nov 19 18:00:11 2014 -0800 Update Foreign.* for Safe Haskell now that they're safe by default >--------------------------------------------------------------- 453ce626a32cab3728a640b2299eaeeb30da8862 compiler/ghci/RtClosureInspect.hs | 4 ++++ compiler/main/InteractiveEval.hs | 4 ++++ compiler/utils/FastString.lhs | 4 ++++ compiler/utils/StringBuffer.lhs | 4 ++++ ghc/InteractiveUI.hs | 4 ++++ libraries/base/Foreign.hs | 2 +- libraries/base/Foreign/ForeignPtr.hs | 4 ++-- libraries/base/Foreign/ForeignPtr/Safe.hs | 2 +- libraries/base/Foreign/Marshal.hs | 18 +++++++++++++----- libraries/base/Foreign/Marshal/Safe.hs | 2 +- libraries/base/Foreign/Safe.hs | 10 +++++----- libraries/base/GHC/IO/Encoding/Iconv.hs | 2 +- libraries/base/GHC/IO/Handle/Internals.hs | 2 +- libraries/base/System/CPUTime.hsc | 2 +- libraries/base/System/Environment.hs | 2 +- 15 files changed, 47 insertions(+), 19 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 453ce626a32cab3728a640b2299eaeeb30da8862 From git at git.haskell.org Fri Nov 21 21:31:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 21:31:54 +0000 (UTC) Subject: [commit: ghc] master: llvmGen: Compatibility with LLVM 3.5 (re #9142) (e16a342) Message-ID: <20141121213154.C24883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e16a342d70b92fc8480793d3ec911853f0c31e44/ghc >--------------------------------------------------------------- commit e16a342d70b92fc8480793d3ec911853f0c31e44 Author: Ben Gamari Date: Fri Nov 21 21:05:25 2014 +0100 llvmGen: Compatibility with LLVM 3.5 (re #9142) Due to changes in LLVM 3.5 aliases now may only refer to definitions. Previously to handle symbols defined outside of the current commpilation unit GHC would emit both an `external` declaration, as well as an alias pointing to it, e.g., @stg_BCO_info = external global i8 @stg_BCO_info$alias = alias private i8* @stg_BCO_info Where references to `stg_BCO_info` will use the alias `stg_BCO_info$alias`. This is not permitted under the new alias behavior, resulting in errors resembling, Alias must point to a definition i8* @"stg_BCO_info$alias" To fix this, we invert the naming relationship between aliases and definitions. That is, now the symbol definition takes the name `@stg_BCO_info$def` and references use the actual name, `@stg_BCO_info`. This means the external symbols can be handled by simply emitting an `external` declaration, @stg_BCO_info = external global i8 Whereas in the case of a forward declaration we emit, @stg_BCO_info = alias private i8* @stg_BCO_info$def Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D155 >--------------------------------------------------------------- e16a342d70b92fc8480793d3ec911853f0c31e44 compiler/llvmGen/Llvm/Types.hs | 3 +- compiler/llvmGen/LlvmCodeGen.hs | 5 +- compiler/llvmGen/LlvmCodeGen/Base.hs | 102 +++++++++++++++++++++++++++++------ compiler/llvmGen/LlvmCodeGen/Data.hs | 10 ++-- compiler/llvmGen/LlvmCodeGen/Ppr.hs | 38 ++++++++++--- 5 files changed, 127 insertions(+), 31 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e16a342d70b92fc8480793d3ec911853f0c31e44 From git at git.haskell.org Fri Nov 21 22:30:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 22:30:53 +0000 (UTC) Subject: [commit: ghc] master: Add displayException method to Exception (#9822) (3222b7a) Message-ID: <20141121223053.49E043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3222b7ae347be092bdd414f7b43bee18861b0e1e/ghc >--------------------------------------------------------------- commit 3222b7ae347be092bdd414f7b43bee18861b0e1e Author: Michael Snoyman Date: Fri Nov 21 23:26:09 2014 +0100 Add displayException method to Exception (#9822) Defaults to using `show` to prevent any breakage of existing code. Also provide a custom implementation for `SomeException` which uses the underlying exception's `displayException`. Differential Revision: https://phabricator.haskell.org/D517 >--------------------------------------------------------------- 3222b7ae347be092bdd414f7b43bee18861b0e1e libraries/base/GHC/Exception.hs | 9 +++++++++ libraries/base/changelog.md | 2 ++ 2 files changed, 11 insertions(+) diff --git a/libraries/base/GHC/Exception.hs b/libraries/base/GHC/Exception.hs index 7a7c8c2..e2b7149 100644 --- a/libraries/base/GHC/Exception.hs +++ b/libraries/base/GHC/Exception.hs @@ -140,9 +140,18 @@ class (Typeable e, Show e) => Exception e where toException = SomeException fromException (SomeException e) = cast e + -- | Render this exception value in a human-friendly manner. + -- + -- Default implementation: @'show'@. + -- + -- /Since: 4.8.0.0/ + displayException :: e -> String + displayException = show + instance Exception SomeException where toException se = se fromException = Just + displayException (SomeException e) = displayException e -- | Throw an exception. Exceptions may be thrown from purely -- functional code, but may only be caught within the 'IO' monad. diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 3e110a7..a5ae8ea 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -104,6 +104,8 @@ * Add `fillBytes` to `Foreign.Marshal.Utils`. + * Add new `displayException` method to `Exception` typeclass. (#9822) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 From git at git.haskell.org Fri Nov 21 22:45:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 22:45:17 +0000 (UTC) Subject: [commit: ghc] master: Add function for size-checked conversion of Integral types (02f8f6a) Message-ID: <20141121224517.3DD3D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/02f8f6ad7bd3d792459a1d33e8d0d57dcf1ea424/ghc >--------------------------------------------------------------- commit 02f8f6ad7bd3d792459a1d33e8d0d57dcf1ea424 Author: Sean Leather Date: Fri Nov 21 23:34:41 2014 +0100 Add function for size-checked conversion of Integral types The new function `Data.Bits.toIntegralSized` provides a similar functionality to `fromIntegral` but adds validation that the argument fits in the result type's size. The implementation of `toIntegralSized` has been derived from `intCastMaybe` (which is part of Herbert Valerio Riedel's `int-cast` package, see http://hackage.haskell.org/package/int-cast) Addresses #9816 Reviewed By: ekmett, austin Differential Revision: https://phabricator.haskell.org/D512 >--------------------------------------------------------------- 02f8f6ad7bd3d792459a1d33e8d0d57dcf1ea424 libraries/base/Data/Bits.hs | 105 +++++++++++++++++++++++++++++++++++++++++++- libraries/base/changelog.md | 3 ++ 2 files changed, 107 insertions(+), 1 deletion(-) diff --git a/libraries/base/Data/Bits.hs b/libraries/base/Data/Bits.hs index fead6fb..b4ab912 100644 --- a/libraries/base/Data/Bits.hs +++ b/libraries/base/Data/Bits.hs @@ -47,7 +47,8 @@ module Data.Bits ( bitDefault, testBitDefault, - popCountDefault + popCountDefault, + toIntegralSized ) where -- Defines the @Bits@ class containing bit-based operations. @@ -60,6 +61,7 @@ import Data.Maybe import GHC.Enum import GHC.Num import GHC.Base +import GHC.Real infixl 8 `shift`, `rotate`, `shiftL`, `shiftR`, `rotateL`, `rotateR` infixl 7 .&. @@ -520,6 +522,82 @@ instance Bits Integer where bitSize _ = error "Data.Bits.bitSize(Integer)" isSigned _ = True +----------------------------------------------------------------------------- + +-- | Attempt to convert an 'Integral' type @a@ to an 'Integral' type @b@ using +-- the size of the types as measured by 'Bits' methods. +-- +-- A simpler version of this function is: +-- +-- > toIntegral :: (Integral a, Integral b) => a -> Maybe b +-- > toIntegral x +-- > | toInteger x == y = Just (fromInteger y) +-- > | otherwise = Nothing +-- > where +-- > y = toInteger x +-- +-- This version requires going through 'Integer', which can be inefficient. +-- However, @toIntegralSized@ is optimized to allow GHC to statically determine +-- the relative type sizes (as measured by 'bitSizeMaybe' and 'isSigned') and +-- avoid going through 'Integer' for many types. (The implementation uses +-- 'fromIntegral', which is itself optimized with rules for @base@ types but may +-- go through 'Integer' for some type pairs.) +-- +-- /Since: 4.8.0.0/ + +toIntegralSized :: (Integral a, Integral b, Bits a, Bits b) => a -> Maybe b +toIntegralSized x -- See Note [toIntegralSized optimization] + | maybe True (<= x) yMinBound + , maybe True (x <=) yMaxBound = Just y + | otherwise = Nothing + where + y = fromIntegral x + + xWidth = bitSizeMaybe x + yWidth = bitSizeMaybe y + + yMinBound + | isBitSubType x y = Nothing + | isSigned x, not (isSigned y) = Just 0 + | isSigned x, isSigned y + , Just yW <- yWidth = Just (negate $ bit (yW-1)) -- Assumes sub-type + | otherwise = Nothing + + yMaxBound + | isBitSubType x y = Nothing + | isSigned x, not (isSigned y) + , Just xW <- xWidth, Just yW <- yWidth + , xW <= yW+1 = Nothing -- Max bound beyond a's domain + | Just yW <- yWidth = if isSigned y + then Just (bit (yW-1)-1) + else Just (bit yW-1) + | otherwise = Nothing +{-# INLINEABLE toIntegralSized #-} + +-- | 'True' if the size of @a@ is @<=@ the size of @b@, where size is measured +-- by 'bitSizeMaybe' and 'isSigned'. +isBitSubType :: (Bits a, Bits b) => a -> b -> Bool +isBitSubType x y + -- Reflexive + | xWidth == yWidth, xSigned == ySigned = True + + -- Every integer is a subset of 'Integer' + | ySigned, Nothing == yWidth = True + | not xSigned, not ySigned, Nothing == yWidth = True + + -- Sub-type relations between fixed-with types + | xSigned == ySigned, Just xW <- xWidth, Just yW <- yWidth = xW <= yW + | not xSigned, ySigned, Just xW <- xWidth, Just yW <- yWidth = xW < yW + + | otherwise = False + where + xWidth = bitSizeMaybe x + xSigned = isSigned x + + yWidth = bitSizeMaybe y + ySigned = isSigned y +{-# INLINE isBitSubType #-} + {- Note [Constant folding for rotate] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The INLINE on the Int instance of rotate enables it to be constant @@ -544,3 +622,28 @@ own to enable constant folding; for example 'shift': 10000000 -> ww_sOb } -} + +-- Note [toIntegralSized optimization] +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- The code in 'toIntegralSized' relies on GHC optimizing away statically +-- decidable branches. +-- +-- If both integral types are statically known, GHC will be able optimize the +-- code significantly (for @-O1@ and better). +-- +-- For instance (as of GHC 7.8.1) the following definitions: +-- +-- > w16_to_i32 = toIntegralSized :: Word16 -> Maybe Int32 +-- > +-- > i16_to_w16 = toIntegralSized :: Int16 -> Maybe Word16 +-- +-- are translated into the following (simplified) /GHC Core/ language: +-- +-- > w16_to_i32 = \x -> Just (case x of _ { W16# x# -> I32# (word2Int# x#) }) +-- > +-- > i16_to_w16 = \x -> case eta of _ +-- > { I16# b1 -> case tagToEnum# (<=# 0 b1) of _ +-- > { False -> Nothing +-- > ; True -> Just (W16# (narrow16Word# (int2Word# b1))) +-- > } +-- > } diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index a5ae8ea..32009db 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -106,6 +106,9 @@ * Add new `displayException` method to `Exception` typeclass. (#9822) + * Add `Data.Bits.toIntegralSized`, a size-checked version of + `fromIntegral`. (#9816) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 From git at git.haskell.org Fri Nov 21 23:05:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 23:05:03 +0000 (UTC) Subject: [commit: ghc] master: ghc: allow --show-options and --interactive together (624a7c5) Message-ID: <20141121230503.1267A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/624a7c5a2eee0c0ba486a45550680052c2c79849/ghc >--------------------------------------------------------------- commit 624a7c5a2eee0c0ba486a45550680052c2c79849 Author: Lennart Kolmodin Date: Fri Nov 21 15:31:54 2014 -0600 ghc: allow --show-options and --interactive together Summary: Previously 'ghc --show-options' showed all options that GHC can possibly accept. With this patch, it'll only show the options that have effect in non-interactive modes. This change also adds support for using 'ghc --interactive --show-options' which previously was disallowed. This command will show all options that have effect in the interactive mode. The CmdLineParser is updated to know about the GHC modes, and then each flag is annotated with which mode it has effect. This fixes #9259. Test Plan: Try out --show-options with --interactive on the command line. With and without --interactive should give different results. Run the test suite, mode001 has been updated to verify this new flag combination. Reviewers: austin, jstolarek Reviewed By: austin, jstolarek Subscribers: jstolarek, thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D337 GHC Trac Issues: #9259 >--------------------------------------------------------------- 624a7c5a2eee0c0ba486a45550680052c2c79849 compiler/main/CmdLineParser.hs | 28 +- compiler/main/DynFlags.hs | 1218 +++++++++++++++++---------------- compiler/main/StaticFlags.hs | 8 +- compiler/typecheck/TcDeriv.lhs | 2 +- docs/users_guide/flags.xml | 20 - docs/users_guide/using.xml | 29 - ghc/InteractiveUI.hs | 22 +- ghc/Main.hs | 92 +-- testsuite/tests/driver/Makefile | 2 + testsuite/tests/driver/T4437.hs | 2 +- testsuite/tests/driver/mode001.stdout | 2 + 11 files changed, 732 insertions(+), 693 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 624a7c5a2eee0c0ba486a45550680052c2c79849 From git at git.haskell.org Fri Nov 21 23:05:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 23:05:06 +0000 (UTC) Subject: [commit: ghc] master: Add -fdefer-typed-holes flag which defers hole errors to runtime. (2cc854b) Message-ID: <20141121230506.80C773A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2cc854b7133e38c7ad1107057931761782d03594/ghc >--------------------------------------------------------------- commit 2cc854b7133e38c7ad1107057931761782d03594 Author: Merijn Verstraaten Date: Fri Nov 21 15:32:38 2014 -0600 Add -fdefer-typed-holes flag which defers hole errors to runtime. Summary: As proposed by Richard on Trac. This patch adds a new flag -fdefer-typed-holes and changes the semantics of the -fno-warn-typed-holes flag. To summarise, by default GHC has typed holes enabled and produces a compile error when it encounters a typed hole. When -fdefer-type-errors OR -fdefer-typed-holes is enabled, hole errors are converted to warnings and result in runtime errors when evaluated. The warning flag -fwarn-typed-holes is on by default. Without -fdefer-type-errors or -fdefer-typed-holes this flag is a no-op, since typed holes are an error under these conditions. If either of the defer flags are enabled (converting typed hole errors into warnings) the -fno-warn-typed-holes flag disables the warnings. This means compilation silently succeeds and evaluating a hole will produce a runtime error. The rationale behind allowing typed holes warnings to be silenced is that tools like Syntastic for vim highlight warnings and hole warnings may be undesirable. Signed-off-by: Merijn Verstraaten Test Plan: validate Reviewers: austin, simonpj, thomie Reviewed By: simonpj, thomie Subscribers: Fuuzetsu, thomie, carter Differential Revision: https://phabricator.haskell.org/D442 GHC Trac Issues: #9497 Conflicts: compiler/main/DynFlags.hs >--------------------------------------------------------------- 2cc854b7133e38c7ad1107057931761782d03594 compiler/main/DynFlags.hs | 22 +++++-- compiler/rename/RnExpr.lhs | 9 +-- compiler/typecheck/TcDeriv.lhs | 2 +- compiler/typecheck/TcErrors.lhs | 74 +++++++++++++++++----- compiler/typecheck/TcRnDriver.lhs | 2 +- docs/users_guide/flags.xml | 25 +++++++- docs/users_guide/glasgow_exts.xml | 53 ++++++++++------ docs/users_guide/using.xml | 34 +++++++--- testsuite/tests/module/mod71.stderr | 11 +++- .../tests/rename/should_fail/rnfail016.stderr | 2 - testsuite/tests/typecheck/should_compile/T9497a.hs | 2 + .../tests/typecheck/should_compile/T9497a.stderr | 6 ++ testsuite/tests/typecheck/should_compile/T9497b.hs | 2 + .../tests/typecheck/should_compile/T9497b.stderr | 0 testsuite/tests/typecheck/should_compile/T9497c.hs | 2 + .../tests/typecheck/should_compile/T9497c.stderr | 0 testsuite/tests/typecheck/should_compile/all.T | 3 + testsuite/tests/typecheck/should_fail/T9497d.hs | 2 + .../tests/typecheck/should_fail/T9497d.stderr | 6 ++ testsuite/tests/typecheck/should_fail/all.T | 1 + testsuite/tests/typecheck/should_run/T9497a-run.hs | 2 + .../tests/typecheck/should_run/T9497a-run.stderr | 7 ++ testsuite/tests/typecheck/should_run/T9497b-run.hs | 2 + .../tests/typecheck/should_run/T9497b-run.stderr | 7 ++ testsuite/tests/typecheck/should_run/T9497c-run.hs | 2 + .../tests/typecheck/should_run/T9497c-run.stderr | 7 ++ testsuite/tests/typecheck/should_run/all.T | 3 + 27 files changed, 226 insertions(+), 62 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2cc854b7133e38c7ad1107057931761782d03594 From git at git.haskell.org Fri Nov 21 23:10:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Nov 2014 23:10:20 +0000 (UTC) Subject: [commit: ghc] master: Deprecate Data.Version.versionTags (#2496) (137b331) Message-ID: <20141121231020.1E60E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/137b33133f49a994e5d147c5b30a8fcfc610eada/ghc >--------------------------------------------------------------- commit 137b33133f49a994e5d147c5b30a8fcfc610eada Author: Thomas Miedema Date: Sat Nov 22 00:03:19 2014 +0100 Deprecate Data.Version.versionTags (#2496) The library submission was accepted: http://www.haskell.org/pipermail/libraries/2014-September/023777.html The T5892ab testcases were changed to use `Data.Tree` instead of `Data.Version` Reviewed By: ekmett Differential Revision: https://phabricator.haskell.org/D395 >--------------------------------------------------------------- 137b33133f49a994e5d147c5b30a8fcfc610eada libraries/base/Data/Version.hs | 2 ++ libraries/base/System/Info.hs | 2 +- testsuite/tests/rename/should_fail/T5892a.hs | 12 ++++++------ testsuite/tests/rename/should_fail/T5892a.stderr | 8 ++++---- testsuite/tests/rename/should_fail/T5892b.hs | 12 ++++++------ testsuite/tests/rename/should_fail/T5892b.stderr | 4 +--- testsuite/tests/rename/should_fail/all.T | 4 ++-- utils/ghc-pkg/Main.hs | 2 +- 8 files changed, 23 insertions(+), 23 deletions(-) diff --git a/libraries/base/Data/Version.hs b/libraries/base/Data/Version.hs index 8a0f9c8..3761d81 100644 --- a/libraries/base/Data/Version.hs +++ b/libraries/base/Data/Version.hs @@ -92,6 +92,8 @@ data Version = -- on the entity that this version applies to. } deriving (Read,Show,Typeable) +{-# DEPRECATED versionTags "See GHC ticket #2496" #-} +-- TODO. Remove all references to versionTags in GHC 7.12 release. instance Eq Version where v1 == v2 = versionBranch v1 == versionBranch v2 diff --git a/libraries/base/System/Info.hs b/libraries/base/System/Info.hs index 1791cdb..c345cf9 100644 --- a/libraries/base/System/Info.hs +++ b/libraries/base/System/Info.hs @@ -29,7 +29,7 @@ import Data.Version -- | The version of 'compilerName' with which the program was compiled -- or is being interpreted. compilerVersion :: Version -compilerVersion = Version {versionBranch=[major, minor], versionTags=[]} +compilerVersion = Version [major, minor] [] where (major, minor) = compilerVersionRaw `divMod` 100 #include "ghcplatform.h" diff --git a/testsuite/tests/rename/should_fail/T5892a.hs b/testsuite/tests/rename/should_fail/T5892a.hs index c0ad989..13d7c3f 100644 --- a/testsuite/tests/rename/should_fail/T5892a.hs +++ b/testsuite/tests/rename/should_fail/T5892a.hs @@ -3,10 +3,10 @@ module T5892a where -import Data.Version ( Version( Version, versionBranch )) --- Not importing its field: versionTags +import Data.Tree ( Tree( Node, rootLabel )) +-- Not importing field 'subForest' -foo :: Version -> Version -foo (Version {..}) -- Pattern match does not bind versionTags - = let versionBranch = [] - in Version {..} -- Hence warning here +foo :: Tree [Int] -> Tree [Int] +foo (Node {..}) -- Pattern match does not bind 'subForest' + = let rootLabel = [] + in Node {..} -- Hence warning here diff --git a/testsuite/tests/rename/should_fail/T5892a.stderr b/testsuite/tests/rename/should_fail/T5892a.stderr index 1600d8f..5e9e4d3 100644 --- a/testsuite/tests/rename/should_fail/T5892a.stderr +++ b/testsuite/tests/rename/should_fail/T5892a.stderr @@ -1,10 +1,10 @@ T5892a.hs:12:8: Warning: - Fields of ?Version? not initialised: Data.Version.versionTags - In the expression: Version {..} - In the expression: let versionBranch = [] in Version {..} + Fields of ?Node? not initialised: Data.Tree.subForest + In the expression: Node {..} + In the expression: let rootLabel = [] in Node {..} In an equation for ?foo?: - foo (Version {..}) = let versionBranch = ... in Version {..} + foo (Node {..}) = let rootLabel = ... in Node {..} : Failing due to -Werror. diff --git a/testsuite/tests/rename/should_fail/T5892b.hs b/testsuite/tests/rename/should_fail/T5892b.hs index 6bcea27..737fd1f 100644 --- a/testsuite/tests/rename/should_fail/T5892b.hs +++ b/testsuite/tests/rename/should_fail/T5892b.hs @@ -1,11 +1,11 @@ {-# LANGUAGE RecordWildCards #-} module T5892b where -import Data.Version ( Version( Version, versionBranch )) --- Not importing its field: versionTags +import Data.Tree ( Tree( Node, rootLabel )) +-- Not importing field 'subForest' -Version{..} = Version [] [] --- Binds versionBranch only +Node{..} = Node [] [] +-- Binds 'rootLabel' only -foo = T5892b.versionBranch -bar = T5892b.versionTags +foo = T5892b.rootLabel +bar = T5892b.subForest diff --git a/testsuite/tests/rename/should_fail/T5892b.stderr b/testsuite/tests/rename/should_fail/T5892b.stderr index 3d25973..994ea78 100644 --- a/testsuite/tests/rename/should_fail/T5892b.stderr +++ b/testsuite/tests/rename/should_fail/T5892b.stderr @@ -1,4 +1,2 @@ -T5892b.hs:11:7: - Not in scope: ?T5892b.versionTags? - Perhaps you meant ?T5892b.versionBranch? (line 7) +T5892b.hs:11:7: Not in scope: ?T5892b.subForest? diff --git a/testsuite/tests/rename/should_fail/all.T b/testsuite/tests/rename/should_fail/all.T index 4c61a8a..d81b743 100644 --- a/testsuite/tests/rename/should_fail/all.T +++ b/testsuite/tests/rename/should_fail/all.T @@ -98,8 +98,8 @@ test('T5657', normal, compile_fail, ['']) test('T5745', extra_clean(['T5745a.hi', 'T5745a.o', 'T5745b.hi', 'T5745b.o']), multimod_compile_fail, ['T5745', '-v0']) -test('T5892a', normal, compile_fail, ['']) -test('T5892b', normal, compile_fail, ['']) +test('T5892a', normal, compile_fail, ['-package containers']) +test('T5892b', normal, compile_fail, ['-package containers']) test('T5951', normal, compile_fail, ['']) test('T6060', normal, compile_fail, ['']) test('T6148', normal, compile_fail, ['']) diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs index b1c7a4b..2b0b4cc 100644 --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -493,7 +493,7 @@ readPackageArg False str = Id `fmap` readGlobPkgId str -- globVersion means "all versions" globVersion :: Version -globVersion = Version{ versionBranch=[], versionTags=["*"] } +globVersion = Version [] ["*"] -- ----------------------------------------------------------------------------- -- Package databases From git at git.haskell.org Sat Nov 22 00:09:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Nov 2014 00:09:52 +0000 (UTC) Subject: [commit: ghc] master: Implement `Natural` number type (re #9818) (8a8cdbb) Message-ID: <20141122000952.941173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8a8cdbbfd855015049526c7945cbe9ccbb152f1e/ghc >--------------------------------------------------------------- commit 8a8cdbbfd855015049526c7945cbe9ccbb152f1e Author: Herbert Valerio Riedel Date: Sat Nov 22 00:15:42 2014 +0100 Implement `Natural` number type (re #9818) This implements a `Natural` type for representing unsigned arbitrary precision integers. When available, `integer-gmp>=1.0.0`'s `BigNat` type is used as building-block to construct `Natural` as an algebraic data-type. Otherwise, `Natural` falls back being a `newtype`-wrapper around `Integer` (as is done in Edward Kmett's `nats` package). The `GHC.Natural` module exposes an internal GHC-specific API, while `Numeric.Natural` provides the official & portable API. Reviewed By: austin, ekmett Differential Revision: https://phabricator.haskell.org/D473 >--------------------------------------------------------------- 8a8cdbbfd855015049526c7945cbe9ccbb152f1e libraries/base/GHC/Natural.hs | 542 +++++++++++++++++++++ libraries/base/Numeric/Natural.hs | 24 + libraries/base/Text/Printf.hs | 5 + libraries/base/base.cabal | 2 + libraries/base/changelog.md | 4 + .../integer-gmp2/src/GHC/Integer/GMP/Internals.hs | 1 + libraries/integer-gmp2/src/GHC/Integer/Type.hs | 1 + 7 files changed, 579 insertions(+) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8a8cdbbfd855015049526c7945cbe9ccbb152f1e From git at git.haskell.org Sat Nov 22 00:19:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Nov 2014 00:19:26 +0000 (UTC) Subject: [commit: ghc] master: Re-center bytes-allocated for `haddock.compiler` (ef5bcc1) Message-ID: <20141122001926.8E1E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ef5bcc16c600f78fb23662c98da2469b4751a6e9/ghc >--------------------------------------------------------------- commit ef5bcc16c600f78fb23662c98da2469b4751a6e9 Author: Herbert Valerio Riedel Date: Sat Nov 22 01:18:22 2014 +0100 Re-center bytes-allocated for `haddock.compiler` This should silence the perf/haddock haddock.compiler [stat not good enough] (normal) test-failure... >--------------------------------------------------------------- ef5bcc16c600f78fb23662c98da2469b4751a6e9 testsuite/tests/perf/haddock/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index f95b782..cb0a235 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -79,7 +79,7 @@ test('haddock.Cabal', test('haddock.compiler', [unless(in_tree_compiler(), skip) ,stats_num_field('bytes allocated', - [(wordsize(64), 30353349160, 10) + [(wordsize(64), 33562468736, 10) # 2012-08-14: 26070600504 (amd64/Linux) # 2012-08-29: 26353100288 (amd64/Linux, new CG) # 2012-09-18: 26882813032 (amd64/Linux) @@ -87,6 +87,7 @@ test('haddock.compiler', # 2014-07-17: 29809571376 (amd64/Linux) general round of updates # 2012-11-27: 28708374824 (amd64/Linux) # 2014-09-10: 30353349160 (amd64/Linux) post-AMP cleanup + # 2014-11-22: 33562468736 (amd64/Linux) ,(platform('i386-unknown-mingw32'), 14328363592, 10) # 2012-10-30: 13773051312 (x86/Windows) # 2013-02-10: 14925262356 (x86/Windows) From git at git.haskell.org Sat Nov 22 00:43:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Nov 2014 00:43:40 +0000 (UTC) Subject: [commit: ghc] branch 'wip/8144' created Message-ID: <20141122004340.2D0D03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/8144 Referencing: a3bf4bfae694572b0bf886fcb1191d066d242aed From git at git.haskell.org Sat Nov 22 00:43:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Nov 2014 00:43:43 +0000 (UTC) Subject: [commit: ghc] wip/8144: Add test case for #8144. (a3bf4bf) Message-ID: <20141122004343.874F33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/8144 Link : http://ghc.haskell.org/trac/ghc/changeset/a3bf4bfae694572b0bf886fcb1191d066d242aed/ghc >--------------------------------------------------------------- commit a3bf4bfae694572b0bf886fcb1191d066d242aed Author: Niklas Hamb?chen Date: Tue Nov 18 21:10:45 2014 -0600 Add test case for #8144. Based on: https://github.com/nh2/ghc-bug-time-dependent-interface-hashes I verified that this test fails for GHC 7.6.3 and older, and passes for GHC 7.8 and newer. Signed-off-by: Austin Seipp >--------------------------------------------------------------- a3bf4bfae694572b0bf886fcb1191d066d242aed testsuite/tests/driver/recomp015/Makefile | 32 ++++++++++++++++++++++ testsuite/tests/driver/recomp015/Test.hs | 3 ++ testsuite/tests/driver/recomp015/all.T | 7 +++++ .../tests/driver/recomp015/cabal_macros.h | 0 testsuite/tests/driver/recomp015/recomp015.stdout | 5 ++++ 5 files changed, 47 insertions(+) diff --git a/testsuite/tests/driver/recomp015/Makefile b/testsuite/tests/driver/recomp015/Makefile new file mode 100644 index 0000000..430516d --- /dev/null +++ b/testsuite/tests/driver/recomp015/Makefile @@ -0,0 +1,32 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +# -fforce-recomp makes lots of driver tests trivially pass, so we +# filter it out from $(TEST_HC_OPTS). +TEST_HC_OPTS_NO_RECOMP = $(filter-out -fforce-recomp,$(TEST_HC_OPTS)) + +# Recompilation tests + +clean: + rm -f *.o *.hi + rm -f Test$(exeext) + +# bug #8144 + +# All compilations except the first should print +# compilation IS NOT required + +recomp015: clean + ghc -c Test.hs -optP-include -optPcabal_macros.h + touch cabal_macros.h + ghc -c Test.hs -optP-include -optPcabal_macros.h + touch cabal_macros.h + ghc -c Test.hs -optP-include -optPcabal_macros.h + touch cabal_macros.h + ghc -c Test.hs -optP-include -optPcabal_macros.h + touch cabal_macros.h + ghc -c Test.hs -optP-include -optPcabal_macros.h + touch cabal_macros.h + sleep 2 + ghc -c Test.hs -optP-include -optPcabal_macros.h diff --git a/testsuite/tests/driver/recomp015/Test.hs b/testsuite/tests/driver/recomp015/Test.hs new file mode 100644 index 0000000..5c8df53 --- /dev/null +++ b/testsuite/tests/driver/recomp015/Test.hs @@ -0,0 +1,3 @@ +{-# LANGUAGE CPP #-} + +module Test () where diff --git a/testsuite/tests/driver/recomp015/all.T b/testsuite/tests/driver/recomp015/all.T new file mode 100644 index 0000000..0643030 --- /dev/null +++ b/testsuite/tests/driver/recomp015/all.T @@ -0,0 +1,7 @@ +# Test for #8144, a recompilation bug + +test('recomp015', + [ clean_cmd('$MAKE -s clean') ], + run_command, + ['$MAKE -s --no-print-directory recomp015']) + diff --git a/libraries/base/tests/IO/misc001.stdout b/testsuite/tests/driver/recomp015/cabal_macros.h similarity index 100% copy from libraries/base/tests/IO/misc001.stdout copy to testsuite/tests/driver/recomp015/cabal_macros.h diff --git a/testsuite/tests/driver/recomp015/recomp015.stdout b/testsuite/tests/driver/recomp015/recomp015.stdout new file mode 100644 index 0000000..178cb00 --- /dev/null +++ b/testsuite/tests/driver/recomp015/recomp015.stdout @@ -0,0 +1,5 @@ +compilation IS NOT required +compilation IS NOT required +compilation IS NOT required +compilation IS NOT required +compilation IS NOT required From git at git.haskell.org Sat Nov 22 09:16:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Nov 2014 09:16:41 +0000 (UTC) Subject: [commit: ghc] master: Revert "Test Trac #9318" (888d75c) Message-ID: <20141122091641.1AABF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/888d75c80bf422cd4d67c44eadce7bdfe5133633/ghc >--------------------------------------------------------------- commit 888d75c80bf422cd4d67c44eadce7bdfe5133633 Author: Herbert Valerio Riedel Date: Sat Nov 22 10:15:29 2014 +0100 Revert "Test Trac #9318" This reverts commit 5760eb598e0dfa451407195f15072204c15233ed because the very same test was already added via 5eebd990ea7a5bc1937657b101ae83475e20fc7a and is causing `./validate` to fail due to "framework failure". >--------------------------------------------------------------- 888d75c80bf422cd4d67c44eadce7bdfe5133633 testsuite/tests/indexed-types/should_fail/T9318.hs | 12 ------------ testsuite/tests/indexed-types/should_fail/T9318.stderr | 7 ------- testsuite/tests/indexed-types/should_fail/all.T | 1 - 3 files changed, 20 deletions(-) diff --git a/testsuite/tests/indexed-types/should_fail/T9318.hs b/testsuite/tests/indexed-types/should_fail/T9318.hs deleted file mode 100644 index 3110305..0000000 --- a/testsuite/tests/indexed-types/should_fail/T9318.hs +++ /dev/null @@ -1,12 +0,0 @@ -{-# LANGUAGE TypeFamilies #-} - -module T9318 where - -type family F x -type instance F Int = Bool - -foo :: F Int -> () -foo True = () - -bar :: F Int -> () -bar 'x' = () diff --git a/testsuite/tests/indexed-types/should_fail/T9318.stderr b/testsuite/tests/indexed-types/should_fail/T9318.stderr deleted file mode 100644 index 963d73e..0000000 --- a/testsuite/tests/indexed-types/should_fail/T9318.stderr +++ /dev/null @@ -1,7 +0,0 @@ - -T9318.hs:12:5: - Couldn't match type ?Bool? with ?Char? - Expected type: F Int - Actual type: Char - In the pattern: 'x' - In an equation for ?bar?: bar 'x' = () diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index 233dc67..93085af 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -131,4 +131,3 @@ test('BadSock', normal, compile_fail, ['']) test('T9580', normal, multimod_compile_fail, ['T9580', '']) test('T9662', normal, compile_fail, ['']) test('T7862', normal, compile_fail, ['']) -test('T9318', normal, compile_fail, ['']) From git at git.haskell.org Sat Nov 22 12:23:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Nov 2014 12:23:36 +0000 (UTC) Subject: [commit: ghc] master: integer-gmp2: export `Word`-counterpart of gcdInt (be7fb7e) Message-ID: <20141122122336.31CD43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/be7fb7e58c70cd9b0a933fb26cd5f2607d6dc4b2/ghc >--------------------------------------------------------------- commit be7fb7e58c70cd9b0a933fb26cd5f2607d6dc4b2 Author: Herbert Valerio Riedel Date: Sat Nov 22 13:18:34 2014 +0100 integer-gmp2: export `Word`-counterpart of gcdInt It's trivial for `integer-gmp2` (#9281) to provide it, and it'll be useful for a future 'Natural'-related commit, as well as providing a `Word` optimised `gcd`-RULE. >--------------------------------------------------------------- be7fb7e58c70cd9b0a933fb26cd5f2607d6dc4b2 libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs | 1 + libraries/integer-gmp2/src/GHC/Integer/Type.hs | 9 ++++++++- 2 files changed, 9 insertions(+), 1 deletion(-) diff --git a/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs b/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs index e319bee..77d73bf 100644 --- a/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs +++ b/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs @@ -118,6 +118,7 @@ module GHC.Integer.GMP.Internals -- * Miscellaneous GMP-provided operations , gcdInt + , gcdWord -- * Import/export functions -- ** Compute size of serialisation diff --git a/libraries/integer-gmp2/src/GHC/Integer/Type.hs b/libraries/integer-gmp2/src/GHC/Integer/Type.hs index b0864f7..48c5ed8 100644 --- a/libraries/integer-gmp2/src/GHC/Integer/Type.hs +++ b/libraries/integer-gmp2/src/GHC/Integer/Type.hs @@ -777,11 +777,18 @@ lcmInteger a b = (aa `quotInteger` (aa `gcdInteger` ab)) `timesInteger` ab -- | Compute greatest common divisor. -- --- Warning: result may become negative if (at least) one argument is 'minBound' +-- __Warning__: result may become negative if (at least) one argument +-- is 'minBound' gcdInt :: Int# -> Int# -> Int# gcdInt x# y# = word2Int# (gcdWord# (int2Word# (absI# x#)) (int2Word# (absI# y#))) +-- | Compute greatest common divisor. +-- +-- /Since: 1.0.0.0/ +gcdWord :: Word# -> Word# -> Word# +gcdWord = gcdWord# + ---------------------------------------------------------------------------- -- BigNat operations From git at git.haskell.org Sat Nov 22 12:23:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Nov 2014 12:23:38 +0000 (UTC) Subject: [commit: ghc] master: Remove reference to `MIN_VERSION_integer_gmp2` (2b71b35) Message-ID: <20141122122338.C0ACC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2b71b355fb1eb559243444f2dc4584e591fddee1/ghc >--------------------------------------------------------------- commit 2b71b355fb1eb559243444f2dc4584e591fddee1 Author: Herbert Valerio Riedel Date: Sat Nov 22 13:22:03 2014 +0100 Remove reference to `MIN_VERSION_integer_gmp2` This is slipped in by accident as part of c774b28f76ee4c220f7c1c9fd81585e0e3af0e8a (re #9281) >--------------------------------------------------------------- 2b71b355fb1eb559243444f2dc4584e591fddee1 libraries/base/GHC/Real.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs index 350420b..a5a35db 100644 --- a/libraries/base/GHC/Real.hs +++ b/libraries/base/GHC/Real.hs @@ -28,7 +28,7 @@ import GHC.Show import {-# SOURCE #-} GHC.Exception( divZeroException, overflowException, ratioZeroDenomException ) #ifdef OPTIMISE_INTEGER_GCD_LCM -# if defined(MIN_VERSION_integer_gmp) || defined(MIN_VERSION_integer_gmp2) +# if defined(MIN_VERSION_integer_gmp) import GHC.Integer.GMP.Internals # else # error unsupported OPTIMISE_INTEGER_GCD_LCM configuration From git at git.haskell.org Sat Nov 22 13:00:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Nov 2014 13:00:44 +0000 (UTC) Subject: [commit: ghc] master: Add gcd/Word RULE-based optimisation (5ea3ee0) Message-ID: <20141122130044.E6B9F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5ea3ee02c7e616235508f1829f8ccfd6047eaf98/ghc >--------------------------------------------------------------- commit 5ea3ee02c7e616235508f1829f8ccfd6047eaf98 Author: Herbert Valerio Riedel Date: Sat Nov 22 13:28:25 2014 +0100 Add gcd/Word RULE-based optimisation This makes use of the `gcdWord` primitive provided by be7fb7e58c70cd9b0a933fb26cd5f2607d6dc4b2 which should make the `Word`-variant of `gcd` as performant as the `Int`-variant. >--------------------------------------------------------------- 5ea3ee02c7e616235508f1829f8ccfd6047eaf98 libraries/base/GHC/Real.hs | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs index a5a35db..c301325 100644 --- a/libraries/base/GHC/Real.hs +++ b/libraries/base/GHC/Real.hs @@ -634,6 +634,15 @@ lcm x y = abs ((x `quot` (gcd x y)) * y) gcdInt' :: Int -> Int -> Int gcdInt' (I# x) (I# y) = I# (gcdInt x y) + +#if MIN_VERSION_integer_gmp(1,0,0) +{-# RULES +"gcd/Word->Word->Word" gcd = gcdWord' + #-} + +gcdWord' :: Word -> Word -> Word +gcdWord' (W# x) (W# y) = W# (gcdWord x y) +#endif #endif integralEnumFrom :: (Integral a, Bounded a) => a -> [a] From git at git.haskell.org Sat Nov 22 14:20:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Nov 2014 14:20:49 +0000 (UTC) Subject: [commit: ghc] master: Add `isValidNatural` predicate (#9818) (4b65376) Message-ID: <20141122142049.2F6CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4b6537677fa9460ca5febe2eb79a2d9d5bdadba2/ghc >--------------------------------------------------------------- commit 4b6537677fa9460ca5febe2eb79a2d9d5bdadba2 Author: Herbert Valerio Riedel Date: Sat Nov 22 14:52:04 2014 +0100 Add `isValidNatural` predicate (#9818) This predicate function encodes the internal `Natural` invariants, and is useful for testsuites or code that directly constructs `Natural` values. C.f. `integer-gmp2`'s `isValidBigNat#` and `isValidInteger#` predicates for testing internal invariants. >--------------------------------------------------------------- 4b6537677fa9460ca5febe2eb79a2d9d5bdadba2 libraries/base/GHC/Natural.hs | 21 +++++++++++++++++++++ 1 file changed, 21 insertions(+) diff --git a/libraries/base/GHC/Natural.hs b/libraries/base/GHC/Natural.hs index 7c362ac..0dead29 100644 --- a/libraries/base/GHC/Natural.hs +++ b/libraries/base/GHC/Natural.hs @@ -35,6 +35,7 @@ module GHC.Natural -- (i.e. which constructors are available) depends on the -- 'Integer' backend used! Natural(..) + , isValidNatural -- * Conversions , wordToNatural , naturalToWordMaybe @@ -87,6 +88,17 @@ data Natural = NatS# GmpLimb# -- ^ in @[0, maxBound::Word]@ deriving (Eq,Ord) -- NB: Order of constructors *must* -- coincide with 'Ord' relation +-- | Test whether all internal invariants are satisfied by 'Natural' value +-- +-- This operation is mostly useful for test-suites and/or code which +-- constructs 'Integer' values directly. +-- +-- /Since: 4.8.0.0/ +isValidNatural :: Natural -> Bool +isValidNatural (NatS# _) = True +isValidNatural (NatJ# bn) = isTrue# (isValidBigNat# bn) + && I# (sizeofBigNat# bn) > 0 + {-# RULES "fromIntegral/Natural->Natural" fromIntegral = id :: Natural -> Natural "fromIntegral/Natural->Integer" fromIntegral = toInteger :: Natural->Integer @@ -397,6 +409,15 @@ naturalToInt (NatJ# bn) = I# (bigNatToInt bn) newtype Natural = Natural Integer -- ^ __Invariant__: non-negative 'Integer' deriving (Eq,Ord,Ix) +-- | Test whether all internal invariants are satisfied by 'Natural' value +-- +-- This operation is mostly useful for test-suites and/or code which +-- constructs 'Integer' values directly. +-- +-- /Since: 4.8.0.0/ +isValidNatural :: Natural -> Bool +isValidNatural (Natural i) = i >= 0 + instance Read Natural where readsPrec d = map (\(n, s) -> (Natural n, s)) . filter ((>= 0) . (\(x,_)->x)) . readsPrec d From git at git.haskell.org Sat Nov 22 14:20:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Nov 2014 14:20:51 +0000 (UTC) Subject: [commit: ghc] master: Implement {gcd, lcm}/Natural optimisation (#9818) (41300b7) Message-ID: <20141122142051.E5D663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/41300b7687c7fc60832f5fa91fce897fc2679ccd/ghc >--------------------------------------------------------------- commit 41300b7687c7fc60832f5fa91fce897fc2679ccd Author: Herbert Valerio Riedel Date: Sat Nov 22 15:03:33 2014 +0100 Implement {gcd,lcm}/Natural optimisation (#9818) This provides the equivalent of the existing `{gcd,lcm}/Integer` optimisations for the `Natural` type, when using the `integer-gmp2` backend. >--------------------------------------------------------------- 41300b7687c7fc60832f5fa91fce897fc2679ccd libraries/base/GHC/Natural.hs | 27 +++++++++++++++++++++++++++ 1 file changed, 27 insertions(+) diff --git a/libraries/base/GHC/Natural.hs b/libraries/base/GHC/Natural.hs index 38a705e..3adfd40 100644 --- a/libraries/base/GHC/Natural.hs +++ b/libraries/base/GHC/Natural.hs @@ -177,6 +177,33 @@ instance Real Natural where toRational (NatS# w) = toRational (W# w) toRational (NatJ# bn) = toRational (Jp# bn) +#if OPTIMISE_INTEGER_GCD_LCM +{-# RULES +"gcd/Natural->Natural->Natural" gcd = gcdNatural +"lcm/Natural->Natural->Natural" lcm = lcmNatural + #-} + +-- | Compute greatest common divisor. +gcdNatural :: Natural -> Natural -> Natural +gcdNatural (NatS# 0##) y = y +gcdNatural x (NatS# 0##) = x +gcdNatural (NatS# 1##) _ = (NatS# 1##) +gcdNatural _ (NatS# 1##) = (NatS# 1##) +gcdNatural (NatJ# x) (NatJ# y) = bigNatToNatural (gcdBigNat x y) +gcdNatural (NatJ# x) (NatS# y) = NatS# (gcdBigNatWord x y) +gcdNatural (NatS# x) (NatJ# y) = NatS# (gcdBigNatWord y x) +gcdNatural (NatS# x) (NatS# y) = NatS# (gcdWord x y) + +-- | compute least common multiplier. +lcmNatural :: Natural -> Natural -> Natural +lcmNatural (NatS# 0##) _ = (NatS# 0##) +lcmNatural _ (NatS# 0##) = (NatS# 0##) +lcmNatural (NatS# 1##) y = y +lcmNatural x (NatS# 1##) = x +lcmNatural x y = (x `quot` (gcdNatural x y)) * y + +#endif + instance Enum Natural where succ n = n `plusNatural` NatS# 1## pred n = n `minusNatural` NatS# 1## From git at git.haskell.org Sat Nov 22 14:20:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Nov 2014 14:20:54 +0000 (UTC) Subject: [commit: ghc] master: Fix `fromInteger` constructing invalid `Natural` (b836139) Message-ID: <20141122142054.8341D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b836139099fc203a8b94849655d7dfb95dd80f4a/ghc >--------------------------------------------------------------- commit b836139099fc203a8b94849655d7dfb95dd80f4a Author: Herbert Valerio Riedel Date: Sat Nov 22 14:56:53 2014 +0100 Fix `fromInteger` constructing invalid `Natural` This fixes a case where `isValidNatural . fromInteger` would be `False`. Re #9818 >--------------------------------------------------------------- b836139099fc203a8b94849655d7dfb95dd80f4a libraries/base/GHC/Natural.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/GHC/Natural.hs b/libraries/base/GHC/Natural.hs index 0dead29..38a705e 100644 --- a/libraries/base/GHC/Natural.hs +++ b/libraries/base/GHC/Natural.hs @@ -158,7 +158,7 @@ instance Read Natural where instance Num Natural where fromInteger (S# i#) | I# i# >= 0 = NatS# (int2Word# i#) - fromInteger (Jp# bn#) = NatJ# bn# + fromInteger (Jp# bn) = bigNatToNatural bn fromInteger _ = throw Underflow (+) = plusNatural From git at git.haskell.org Sat Nov 22 14:20:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Nov 2014 14:20:57 +0000 (UTC) Subject: [commit: ghc] master: Call `popCountBigNat` directly (#9818) (96d29b5) Message-ID: <20141122142057.228CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/96d29b5403bd8a6465a65a39da861f5b9610fc89/ghc >--------------------------------------------------------------- commit 96d29b5403bd8a6465a65a39da861f5b9610fc89 Author: Herbert Valerio Riedel Date: Sat Nov 22 15:09:46 2014 +0100 Call `popCountBigNat` directly (#9818) This calls the `popCountBigNat` primitive directly instead of going through `Integer`'s `popCount`. >--------------------------------------------------------------- 96d29b5403bd8a6465a65a39da861f5b9610fc89 libraries/base/GHC/Natural.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/GHC/Natural.hs b/libraries/base/GHC/Natural.hs index 3adfd40..e9b37b1 100644 --- a/libraries/base/GHC/Natural.hs +++ b/libraries/base/GHC/Natural.hs @@ -332,7 +332,7 @@ instance Bits Natural where rotateR = shiftR popCount (NatS# w) = popCount (W# w) - popCount (NatJ# bn) = popCount (Jp# bn) + popCount (NatJ# bn) = I# (popCountBigNat bn) zeroBits = NatS# 0## From git at git.haskell.org Sun Nov 23 17:51:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Nov 2014 17:51:14 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData2: Use TypeLits in the meta-data encoding of GHC.Generics (950b5f9) Message-ID: <20141123175114.36BC53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData2 Link : http://ghc.haskell.org/trac/ghc/changeset/950b5f9dc6efbb508fbf74f8ec81431f02395820/ghc >--------------------------------------------------------------- commit 950b5f9dc6efbb508fbf74f8ec81431f02395820 Author: Jose Pedro Magalhaes Date: Thu Oct 2 08:38:05 2014 +0100 Use TypeLits in the meta-data encoding of GHC.Generics The following wiki page contains more information about this: https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/GenericDeriving#Amoreconservativefirstapproachtothisproblem >--------------------------------------------------------------- 950b5f9dc6efbb508fbf74f8ec81431f02395820 compiler/prelude/PrelNames.lhs | 59 ++-- compiler/typecheck/TcDeriv.lhs | 64 +---- compiler/typecheck/TcGenDeriv.lhs | 18 +- compiler/typecheck/TcGenGenerics.lhs | 304 +++++--------------- docs/users_guide/glasgow_exts.xml | 30 +- libraries/base/GHC/Generics.hs | 324 ++++++++++++---------- testsuite/tests/generics/GShow/GShow.hs | 4 +- testsuite/tests/generics/GenDerivOutput.stderr | 120 ++++---- testsuite/tests/generics/GenDerivOutput1_0.stderr | 48 ++-- testsuite/tests/generics/GenDerivOutput1_1.stderr | 254 ++++++++--------- 10 files changed, 508 insertions(+), 717 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 950b5f9dc6efbb508fbf74f8ec81431f02395820 From git at git.haskell.org Sun Nov 23 17:51:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Nov 2014 17:51:17 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData2's head updated: Use TypeLits in the meta-data encoding of GHC.Generics (950b5f9) Message-ID: <20141123175117.0E3803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/GenericsMetaData2' now includes: 9a20379 Fix ffi023 20226c2 Whitespace only ac1281f Outputable instance for IfaceVectInfo 535644f Add missing semicolon in Schedule.c 1f6b1ab base: Fix (**) instance for Data.Complex (#8539) ddb484c Update comment about C helper for foreign exports (#9713) 87cd37b Fix usage of `find -perm` in aclocal.m4 (#9697) 21f9bc4 mapMaybe: Typo in the comment (#9644) c557f99 Disable AVX for LLVM 3.2 by default (#9391) e7b414a Fix detection of GNU gold linker if invoked via gcc with parameters a736b51 Revert "base: Fix (**) instance for Data.Complex (#8539)" 483eeba Comments only 1019e3c When outputting list of available instances, sort it. 7c748d9 Support for "with" renaming syntax, and output a feature flag. 4224466 Reimplement im/export primitives for integer-gmp2 e2af452 Restore exact old semantics of `decodeFloat` 4ba884b Optimise `Identity` instances with `coerce` 8e0a480 rts: remove old-style field designator extension (#9396) 101c62e The test runner now also works under the msys-native Python. 6fc78fd Refactor: use System.FilePath.splitSearchPath 66c0513 Update documentation for "Batch compiler mode" 00c1a30 Implement new Foldable methods for HsPatSynDetails 5db61ea Turn CoreWriter into a newtype; fix comment 5c09893 Add remaining s and comments to .mailmap 7ef0971 Filter input to abiHash early b3df5f6 template-haskell: Missing instances for Rational and (). b047733 add missing instances for Loc and a few missing Eq instances 146dd13 Only test for bug #9439 when llvm is installed 53a4742 Allow -dead_strip linking on platforms with .subsections_via_symbols 33c029f make TcRnMonad.lhs respect -ddump-to-file 4dd87c5 use correct word size for shiftRightLogical and removeOp32 80f6fc1 compiler/main: fixes #9776 d87fa34 arm64: 64bit iOS and SMP support (#7942) bc2289e ghc generates more user-friendly error messages c6e12e6 Make calling conventions in template haskell Syntax.hs consistent with those in ghc ForeignCall.hs this impliments #9703 from ghc trac 8cbd25a Make Data.Functor.Identity trustworthy again 3b81309 Update shift/reduce conflict number in parser cce6318 Add support for pattern synonym type signatures. Syntax is of the form 64cb496 Implement typechecker plugins 696fc4b Split SynTyCon to SynonymTyCon and FamilyTyCon e2f7803 Kill trailing whitespace 6db0f6f Test #9209 in th/T9209 5a8ae60 Fix #9209, by reporting an error instead of panicking on bad splices. e394e74 Fix #9220 by adding role annotations. 67abfda Test #9151 in typecheck/should_compile/T9151. 786b62a Add release notes for #8100, #9527, and #9064. 5eebd99 Test #9318 in typecheck/should_fail/T9318 8fea2ac Test #9201 in typecheck/should_fail/T9201 113a37b Update manual to get rid of bogus `coerce` example (#9788) cb41e08 Test #9109 in typecheck/should_fail/T9109 6efe572 Don't build old-{time,locale} and haskell{98,2010} 86dda8f Delete old-{time,locale} and haskell{98,2010} e888b94 Hide `Data.OldList` module f60eeb4 Export scanl' from Data.OldList and Data.List 067f1e4 Add flag `-fwarn-missing-exported-sigs` 7ed482d Implement #5462 (deriving clause for arbitrary classes) 27f9c74 Unbreak build (fallout from 067f1e4f20e) fec1c30 Revert change to alias handling in ppLlvmGlobal introduced in d87fa34, which requires LLVM 3.6. b0dd347 Rewrite Note [Deriving any class] eac9bbe Comments only e876208 Rejig builders for pattern synonyms, especially unlifted ones 76f5f11 Move all the zonk/tidy stuff together into TcMType (refactoring only) b685542 Implement full co/contra-variant subsumption checking (fixes Trac #9569) 073119e Put the decision of when a unification variable can unify with a polytype 0f5c163 Make the on-the-fly unifier defer forall/forall unification 16d10ae Fix a latent promotion bug in TcSimplify.simplifyInfer 5f39c4d Remove TcMType from compiler_stage2_dll0_MODULES 5760eb5 Test Trac #9318 b82410a Trac #9222 is actually an ambiguous type, now detected e639120 Delete duplicated tests 230b013 Test Trac #9569 7b1a856 Fix up tests for Trac #7220; the old test really was ambiguous 1b6988e Test T2239 actually succeeds without impredicativity, because of the new co/contra subsumption check eaccc72 Wibbles (usually improvements) to error messages 4ba4cc7 Fix Trac #9815 c5a3938 Test Trac #8149 6d40470 Comments only dbf360a Test #7484 in th/T7484 da2fca9 Fix #7484, checking for good binder names in Convert. adb20a0 Test #1476 in th/T1476 d627c5c Test that nested pattern splices don't scope (#1476). 2346de4 Fix #1476 by making splice patterns work. 1b22d9f Release notes for #1476, #7484. 3b3944f Test #9824 in th/T9824 bc05354 Fix #9824 by not warning about unused matches in pattern quotes. cfa574c Update manual for pattern splices (#1476) 7927658 AST changes to prepare for API annotations, for #9628 803fc5d Add API Annotations 3e4f49b Fixes ghci :unset -X so that it doesn't fail to reverse option. (fixes trac #9293) 3793d3b Export more Packages functions a97f90c Add Data.Void to base (re #9814) c0ad5bc Capture original source for literals 3583312 Add 'fillBytes' to Foreign.Marshal.Utils. 6265f1c Add T7220a.stderr 065d433 Update Control.Monad.ST.* for Safe Haskell as now they're safe by default 453ce62 Update Foreign.* for Safe Haskell now that they're safe by default 5f84bd1 Improve Safe Haskell bounds for changes to base over time 2a523eb Be consistent with placement of Safe Haskell mode at top of file e16a342 llvmGen: Compatibility with LLVM 3.5 (re #9142) 3222b7a Add displayException method to Exception (#9822) 02f8f6a Add function for size-checked conversion of Integral types 624a7c5 ghc: allow --show-options and --interactive together 2cc854b Add -fdefer-typed-holes flag which defers hole errors to runtime. 137b331 Deprecate Data.Version.versionTags (#2496) 8a8cdbb Implement `Natural` number type (re #9818) ef5bcc1 Re-center bytes-allocated for `haddock.compiler` 888d75c Revert "Test Trac #9318" be7fb7e integer-gmp2: export `Word`-counterpart of gcdInt 2b71b35 Remove reference to `MIN_VERSION_integer_gmp2` 5ea3ee0 Add gcd/Word RULE-based optimisation 4b65376 Add `isValidNatural` predicate (#9818) b836139 Fix `fromInteger` constructing invalid `Natural` 41300b7 Implement {gcd,lcm}/Natural optimisation (#9818) 96d29b5 Call `popCountBigNat` directly (#9818) 950b5f9 Use TypeLits in the meta-data encoding of GHC.Generics From git at git.haskell.org Sun Nov 23 21:02:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Nov 2014 21:02:34 +0000 (UTC) Subject: [commit: ghc] master: Define void using <$ (re #9827) (cc7a735) Message-ID: <20141123210234.ED59A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cc7a735f015510dda6f69d4a48d1b0cdd55856ba/ghc >--------------------------------------------------------------- commit cc7a735f015510dda6f69d4a48d1b0cdd55856ba Author: David Feuer Date: Sun Nov 23 22:00:48 2014 +0100 Define void using <$ (re #9827) `() <$ x` is sometimes better than `fmap (const ()) x` and should never be worse. Reviewed By: ekmett Differential Revision: https://phabricator.haskell.org/D521 >--------------------------------------------------------------- cc7a735f015510dda6f69d4a48d1b0cdd55856ba libraries/base/Data/Functor.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/base/Data/Functor.hs b/libraries/base/Data/Functor.hs index 9db4c8f..c12564f 100644 --- a/libraries/base/Data/Functor.hs +++ b/libraries/base/Data/Functor.hs @@ -23,7 +23,7 @@ module Data.Functor void, ) where -import GHC.Base ( Functor(..), const, flip ) +import GHC.Base ( Functor(..), flip ) -- $setup -- Allow the use of Prelude in doctests. @@ -140,4 +140,4 @@ infixl 4 $> -- 2 -- void :: Functor f => f a -> f () -void = fmap (const ()) +void x = () <$ x From git at git.haskell.org Sun Nov 23 21:23:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Nov 2014 21:23:15 +0000 (UTC) Subject: [commit: ghc] master: Add `Storable` instances for `Complex` and `Ratio` (fb061c1) Message-ID: <20141123212315.2C5DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fb061c193947a7096471486faade1d0db30bc588/ghc >--------------------------------------------------------------- commit fb061c193947a7096471486faade1d0db30bc588 Author: Carter Tazio Schonwald Date: Sun Nov 23 22:08:21 2014 +0100 Add `Storable` instances for `Complex` and `Ratio` The actual type-signatures of the new instances are: instance Storable a => Storable (Complex a) instance (Storable a, Integral a) => Storable (Ratio a) See also https://groups.google.com/d/msg/haskell-core-libraries/mjBSo2CQ3LU/0gwg0QvviOIJ Addresses #9826 Reviewed By: ekmett Differential Revision: https://phabricator.haskell.org/D519 >--------------------------------------------------------------- fb061c193947a7096471486faade1d0db30bc588 libraries/base/Data/Complex.hs | 15 ++++++++++++++ libraries/base/Foreign/Storable.hs | 13 ++++++++++++ libraries/base/changelog.md | 4 ++++ libraries/base/tests/T9826.hs | 24 ++++++++++++++++++++++ .../base/tests/T9826.stdout | 0 libraries/base/tests/all.T | 1 + 6 files changed, 57 insertions(+) diff --git a/libraries/base/Data/Complex.hs b/libraries/base/Data/Complex.hs index 2baa60b..1c06d46 100644 --- a/libraries/base/Data/Complex.hs +++ b/libraries/base/Data/Complex.hs @@ -36,6 +36,8 @@ module Data.Complex import Data.Typeable import Data.Data (Data) +import Foreign (Storable, castPtr, peek, poke, pokeElemOff, peekElemOff, sizeOf, + alignment) infix 6 :+ @@ -171,3 +173,16 @@ instance (RealFloat a) => Floating (Complex a) where asinh z = log (z + sqrt (1+z*z)) acosh z = log (z + (z+1) * sqrt ((z-1)/(z+1))) atanh z = 0.5 * log ((1.0+z) / (1.0-z)) + +instance Storable a => Storable (Complex a) where + sizeOf a = 2 * sizeOf (realPart a) + alignment a = alignment (realPart a) + peek p = do + q <- return $ castPtr p + r <- peek q + i <- peekElemOff q 1 + return (r :+ i) + poke p (r :+ i) = do + q <-return $ (castPtr p) + poke q r + pokeElemOff q 1 i diff --git a/libraries/base/Foreign/Storable.hs b/libraries/base/Foreign/Storable.hs index 35b1b49..52f3eda 100644 --- a/libraries/base/Foreign/Storable.hs +++ b/libraries/base/Foreign/Storable.hs @@ -208,6 +208,19 @@ STORABLE(Int32,SIZEOF_INT32,ALIGNMENT_INT32, STORABLE(Int64,SIZEOF_INT64,ALIGNMENT_INT64, readInt64OffPtr,writeInt64OffPtr) +instance (Storable a, Integral a) => Storable (Ratio a) where + sizeOf _ = 2 * sizeOf (undefined :: a) + alignment _ = alignment (undefined :: a ) + peek p = do + q <- return $ castPtr p + r <- peek q + i <- peekElemOff q 1 + return (r % i) + poke p (r :% i) = do + q <-return $ (castPtr p) + poke q r + pokeElemOff q 1 i + -- XXX: here to avoid orphan instance in GHC.Fingerprint instance Storable Fingerprint where sizeOf _ = 16 diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 881532f..c7de12e 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -113,6 +113,10 @@ representing non-negative arbitrary-precision integers. The `GHC.Natural` module exposes additional GHC-specific primitives. (#9818) + * Add `(Storable a, Integeral a) => Storable (Ratio a)` instance (#9826) + + * Add `Storable a => Storable (Complex a)` instance (#9826) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 diff --git a/libraries/base/tests/T9826.hs b/libraries/base/tests/T9826.hs new file mode 100644 index 0000000..b35ada4 --- /dev/null +++ b/libraries/base/tests/T9826.hs @@ -0,0 +1,24 @@ +{-# LANGUAGE BangPatterns #-} + +module Main where +--import qualified Data.Vector.Storable as V +import Foreign +import Data.Ratio +import Data.Complex + +complexZI :: Complex Int +complexZI = 1 :+ 1 + +ratio23 :: Ratio Int +ratio23 = 1 % 1 + +putter :: Storable a => a -> Ptr a -> IO a +putter v !ptr = do poke ptr v ; peek ptr + +main = + do + !vComplex <- alloca (putter complexZI) + !vRatio <- alloca (putter ratio23) + if vComplex == complexZI && vRatio == ratio23 + then putStrLn "success" + else putStrLn "uh oh, something is wrong with storable" diff --git a/testsuite/tests/codeGen/should_run/StaticArraySize.stdout b/libraries/base/tests/T9826.stdout similarity index 100% copy from testsuite/tests/codeGen/should_run/StaticArraySize.stdout copy to libraries/base/tests/T9826.stdout diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T index fa8ecd3..d4686e5 100644 --- a/libraries/base/tests/all.T +++ b/libraries/base/tests/all.T @@ -178,3 +178,4 @@ test('T9532', normal, compile_and_run, ['']) test('T9586', normal, compile, ['']) test('T9681', normal, compile_fail, ['']) test('T8089', normal, compile_and_run, ['']) +test('T9826',normal, compile_and_run,['']) From git at git.haskell.org Sun Nov 23 21:42:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Nov 2014 21:42:02 +0000 (UTC) Subject: [commit: ghc] master: Install `ghc-gmp.h` C include header file (#9281) (a9a0dd3) Message-ID: <20141123214202.225AE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a9a0dd34dcdfb7309f57bda88435acca14ec54d5/ghc >--------------------------------------------------------------- commit a9a0dd34dcdfb7309f57bda88435acca14ec54d5 Author: Herbert Valerio Riedel Date: Sun Nov 23 10:27:13 2014 +0100 Install `ghc-gmp.h` C include header file (#9281) This is mostly interesting when using the in-tree GMP, as there's no way otherwise to access the in-tree `gmp.h` header file after installation. In case `integer-gmp2` was build against a system-installed GMP library, `ghc-gmp.h` simply contains `#include ` for convenience. Reviewed By: ekmett Differential Revision: https://phabricator.haskell.org/D522 >--------------------------------------------------------------- a9a0dd34dcdfb7309f57bda88435acca14ec54d5 libraries/integer-gmp2/.gitignore | 1 + libraries/integer-gmp2/gmp/ghc-gmp.h | 1 + libraries/integer-gmp2/gmp/ghc.mk | 14 +++++++++++++- libraries/integer-gmp2/integer-gmp.buildinfo.in | 2 +- 4 files changed, 16 insertions(+), 2 deletions(-) diff --git a/libraries/integer-gmp2/.gitignore b/libraries/integer-gmp2/.gitignore index 98b7b18..3f3fc66 100644 --- a/libraries/integer-gmp2/.gitignore +++ b/libraries/integer-gmp2/.gitignore @@ -11,3 +11,4 @@ /gmp/gmp.h /gmp/gmpbuild +/include/ghc-gmp.h diff --git a/libraries/integer-gmp2/gmp/ghc-gmp.h b/libraries/integer-gmp2/gmp/ghc-gmp.h new file mode 100644 index 0000000..3fdb398 --- /dev/null +++ b/libraries/integer-gmp2/gmp/ghc-gmp.h @@ -0,0 +1 @@ +#include diff --git a/libraries/integer-gmp2/gmp/ghc.mk b/libraries/integer-gmp2/gmp/ghc.mk index 298005f..5685917 100644 --- a/libraries/integer-gmp2/gmp/ghc.mk +++ b/libraries/integer-gmp2/gmp/ghc.mk @@ -20,6 +20,7 @@ GMP_DIR := $(patsubst libraries/integer-gmp/gmp/tarball/%-nodoc-patched.tar.bz2, ifneq "$(NO_CLEAN_GMP)" "YES" $(eval $(call clean-target,gmp,,\ + libraries/integer-gmp2/include/ghc-gmp.h \ libraries/integer-gmp2/gmp/config.mk \ libraries/integer-gmp2/gmp/libgmp.a \ libraries/integer-gmp2/gmp/gmp.h \ @@ -75,14 +76,24 @@ HaveFrameworkGMP = NO endif endif +UseIntreeGmp = NO ifneq "$(HaveLibGmp)" "YES" ifneq "$(HaveFrameworkGMP)" "YES" +UseIntreeGmp = YES +endif +endif + +ifeq "$(UseIntreeGmp)" "YES" $(libraries/integer-gmp2_dist-install_depfile_c_asm): libraries/integer-gmp2/gmp/gmp.h gmp_CC_OPTS += -Ilibraries/integer-gmp2/gmp libraries/integer-gmp2_dist-install_EXTRA_OBJS += libraries/integer-gmp2/gmp/objs/*.o -endif +else +$(libraries/integer-gmp2_dist-install_depfile_c_asm): libraries/integer-gmp2/include/ghc-gmp.h + +libraries/integer-gmp2/include/ghc-gmp.h: libraries/integer-gmp2/gmp/ghc-gmp.h + $(CP) $< $@ endif libraries/integer-gmp2_dist-install_EXTRA_CC_OPTS += $(gmp_CC_OPTS) @@ -116,6 +127,7 @@ libraries/integer-gmp2/gmp/libgmp.a libraries/integer-gmp2/gmp/gmp.h: --host=$(HOSTPLATFORM) --build=$(BUILDPLATFORM) $(MAKE) -C libraries/integer-gmp2/gmp/gmpbuild MAKEFLAGS= $(CP) libraries/integer-gmp2/gmp/gmpbuild/gmp.h libraries/integer-gmp2/gmp/ + $(CP) libraries/integer-gmp2/gmp/gmpbuild/gmp.h libraries/integer-gmp2/include/ghc-gmp.h $(CP) libraries/integer-gmp2/gmp/gmpbuild/.libs/libgmp.a libraries/integer-gmp2/gmp/ $(MKDIRHIER) libraries/integer-gmp2/gmp/objs cd libraries/integer-gmp2/gmp/objs && $(AR_STAGE1) x ../libgmp.a diff --git a/libraries/integer-gmp2/integer-gmp.buildinfo.in b/libraries/integer-gmp2/integer-gmp.buildinfo.in index 91b4313..805a425 100644 --- a/libraries/integer-gmp2/integer-gmp.buildinfo.in +++ b/libraries/integer-gmp2/integer-gmp.buildinfo.in @@ -2,4 +2,4 @@ include-dirs: @GMP_INCLUDE_DIRS@ extra-lib-dirs: @GMP_LIB_DIRS@ extra-libraries: @GMP_LIBS@ frameworks: @GMP_FRAMEWORK@ -install-includes: HsIntegerGmp.h +install-includes: HsIntegerGmp.h ghc-gmp.h From git at git.haskell.org Sun Nov 23 21:42:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Nov 2014 21:42:04 +0000 (UTC) Subject: [commit: ghc] master: Persist build-time GMP ver to `HsIntegerGmp.h` (6d1c8ec) Message-ID: <20141123214204.AD7D83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6d1c8ec79adf566d57d2c35aac8ff6635412d108/ghc >--------------------------------------------------------------- commit 6d1c8ec79adf566d57d2c35aac8ff6635412d108 Author: Herbert Valerio Riedel Date: Sun Nov 23 12:21:51 2014 +0100 Persist build-time GMP ver to `HsIntegerGmp.h` This creates the additional macro definitions in `HsIntegerGmp.h` which are useful for 3rd party `integer-gmp`-addon libraries. Here's an example for the definitions created for the in-tree GMP: #define GHC_GMP_INTREE 1 #define GHC_GMP_VERSION_MJ 5 #define GHC_GMP_VERSION_MI 0 #define GHC_GMP_VERSION_PL 4 #define GHC_GMP_VERSION (5 * 10000 + 0 * 100 + 4) And here's an example for a system-installed GMP: #define GHC_GMP_INTREE 0 #define GHC_GMP_VERSION_MJ 6 #define GHC_GMP_VERSION_MI 0 #define GHC_GMP_VERSION_PL 0 #define GHC_GMP_VERSION (6 * 10000 + 0 * 100 + 0) Part of #9281 Reviewed By: ekmett (via D522) >--------------------------------------------------------------- 6d1c8ec79adf566d57d2c35aac8ff6635412d108 libraries/integer-gmp2/configure.ac | 34 ++++++++++++++++++++++-- libraries/integer-gmp2/include/HsIntegerGmp.h.in | 10 +++++++ 2 files changed, 42 insertions(+), 2 deletions(-) diff --git a/libraries/integer-gmp2/configure.ac b/libraries/integer-gmp2/configure.ac index 0794d96..4a9e539 100644 --- a/libraries/integer-gmp2/configure.ac +++ b/libraries/integer-gmp2/configure.ac @@ -1,4 +1,5 @@ -AC_INIT([Haskell integer (GMP)], [0.1], [libraries at haskell.org], [integer]) +AC_INIT([Haskell integer (GMP)], [1.0], [libraries at haskell.org], [integer]) +AC_PREREQ(2.52) # Safety check: Ensure that we are in the correct source directory. AC_CONFIG_SRCDIR([cbits/wrappers.c]) @@ -60,11 +61,36 @@ then LOOK_FOR_GMP_FRAMEWORK fi fi + +AC_MSG_CHECKING([whether to use in-tree GMP]) if test "$HaveFrameworkGMP" = "YES" || test "$HaveLibGmp" = "YES" then + AC_MSG_RESULT([no]) + UseIntreeGmp=0 AC_CHECK_HEADER([gmp.h], , [AC_MSG_ERROR([Cannot find gmp.h])]) + + AC_MSG_CHECKING([GMP version]) + AC_COMPUTE_INT(GhcGmpVerMj, __GNU_MP_VERSION, [#include ], + AC_MSG_ERROR([Unable to get value of __GNU_MP_VERSION])) + AC_COMPUTE_INT(GhcGmpVerMi, __GNU_MP_VERSION_MINOR, [#include ], + AC_MSG_ERROR([Unable to get value of __GNU_MP_VERSION_MINOR])) + AC_COMPUTE_INT(GhcGmpVerPl, __GNU_MP_VERSION_PATCHLEVEL, [#include ], + AC_MSG_ERROR([Unable to get value of __GNU_MP_VERSION_PATCHLEVEL])) + AC_MSG_RESULT([$GhcGmpVerMJ.$GhcGmpVerMI.$GhcGmpVerPL]) + +else + AC_MSG_RESULT([yes]) + UseIntreeGmp=1 + HaveSecurePowm=1 + + AC_MSG_CHECKING([GMP version]) + GhcGmpVerMj=5 + GhcGmpVerMi=0 + GhcGmpVerPl=4 + AC_MSG_RESULT([$GhcGmpVerMj.$GhcGmpVerMi.$GhcGmpVerPl]) fi + dnl-------------------------------------------------------------------- dnl * Make sure we got some form of gmp dnl-------------------------------------------------------------------- @@ -76,11 +102,15 @@ AC_SUBST(GMP_FRAMEWORK) AC_SUBST(HaveLibGmp) AC_SUBST(HaveFrameworkGMP) AC_SUBST(HaveSecurePowm) +AC_SUBST(UseIntreeGmp) +AC_SUBST(GhcGmpVerMj) +AC_SUBST(GhcGmpVerMi) +AC_SUBST(GhcGmpVerPl) AC_CONFIG_FILES([integer-gmp.buildinfo gmp/config.mk include/HsIntegerGmp.h]) dnl-------------------------------------------------------------------- -dnl * Generate the header cbits/GmpDerivedConstants.h +dnl * Generate output files dnl-------------------------------------------------------------------- AC_OUTPUT diff --git a/libraries/integer-gmp2/include/HsIntegerGmp.h.in b/libraries/integer-gmp2/include/HsIntegerGmp.h.in index 11c6467..0637ba3 100644 --- a/libraries/integer-gmp2/include/HsIntegerGmp.h.in +++ b/libraries/integer-gmp2/include/HsIntegerGmp.h.in @@ -3,4 +3,14 @@ #define HAVE_SECURE_POWM @HaveSecurePowm@ +/* Whether GMP is embedded into integer-gmp */ +#define GHC_GMP_INTREE @UseIntreeGmp@ + +/* The following values denote the GMP version used during GHC build-time */ +#define GHC_GMP_VERSION_MJ @GhcGmpVerMj@ +#define GHC_GMP_VERSION_MI @GhcGmpVerMi@ +#define GHC_GMP_VERSION_PL @GhcGmpVerPl@ +#define GHC_GMP_VERSION \ + (@GhcGmpVerMj@ * 10000 + @GhcGmpVerMi@ * 100 + @GhcGmpVerPl@) + #endif /* _HS_INTEGER_GMP_H_ */ From git at git.haskell.org Sun Nov 23 21:46:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Nov 2014 21:46:44 +0000 (UTC) Subject: [commit: ghc] master: Fix minor typo in 6d1c8ec79adf566d57d2c35aac (fd25379) Message-ID: <20141123214644.3206E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fd25379022505d015c7939b3a793b5ffec3167b4/ghc >--------------------------------------------------------------- commit fd25379022505d015c7939b3a793b5ffec3167b4 Author: Herbert Valerio Riedel Date: Sun Nov 23 22:46:47 2014 +0100 Fix minor typo in 6d1c8ec79adf566d57d2c35aac >--------------------------------------------------------------- fd25379022505d015c7939b3a793b5ffec3167b4 libraries/integer-gmp2/configure.ac | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/integer-gmp2/configure.ac b/libraries/integer-gmp2/configure.ac index 4a9e539..0bd9188 100644 --- a/libraries/integer-gmp2/configure.ac +++ b/libraries/integer-gmp2/configure.ac @@ -76,7 +76,7 @@ then AC_MSG_ERROR([Unable to get value of __GNU_MP_VERSION_MINOR])) AC_COMPUTE_INT(GhcGmpVerPl, __GNU_MP_VERSION_PATCHLEVEL, [#include ], AC_MSG_ERROR([Unable to get value of __GNU_MP_VERSION_PATCHLEVEL])) - AC_MSG_RESULT([$GhcGmpVerMJ.$GhcGmpVerMI.$GhcGmpVerPL]) + AC_MSG_RESULT([$GhcGmpVerMj.$GhcGmpVerMi.$GhcGmpVerPl]) else AC_MSG_RESULT([yes]) From git at git.haskell.org Sun Nov 23 23:00:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Nov 2014 23:00:06 +0000 (UTC) Subject: [commit: ghc] master: Update in-tree GMP to version 5.0.4 (41c3545) Message-ID: <20141123230006.5F58D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/41c354593f6b3ef6e039e6416ea933c60e21694e/ghc >--------------------------------------------------------------- commit 41c354593f6b3ef6e039e6416ea933c60e21694e Author: Herbert Valerio Riedel Date: Sun Nov 23 23:41:06 2014 +0100 Update in-tree GMP to version 5.0.4 This is mostly a proof of concept for updating the in-tree GMP via patch files (and therefore w/o introducing new blobs into the Git history). NOTE: The updated GMP 5.0.4 version is only used by the integer-gmp2 backend. >--------------------------------------------------------------- 41c354593f6b3ef6e039e6416ea933c60e21694e libraries/integer-gmp/gmp/tarball/gmp-5.0.4.patch | 1584 +++++++++++++++++++++ libraries/integer-gmp2/gmp/ghc.mk | 1 + 2 files changed, 1585 insertions(+) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 41c354593f6b3ef6e039e6416ea933c60e21694e From git at git.haskell.org Mon Nov 24 11:48:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Nov 2014 11:48:24 +0000 (UTC) Subject: [commit: ghc] master: Try to improve Make dependency for `ghc-gmp.h` (6a13099) Message-ID: <20141124114824.CFB033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6a130992b2afab5f2de87c6c8f98328eb925258c/ghc >--------------------------------------------------------------- commit 6a130992b2afab5f2de87c6c8f98328eb925258c Author: Herbert Valerio Riedel Date: Mon Nov 24 12:01:37 2014 +0100 Try to improve Make dependency for `ghc-gmp.h` This will hopefully workaround an issue where `libraries/integer-gmp2/include/ghc-gmp.h` gets deleted during cleanup but isn't regenerated. This situation is caused by `./validate` cleaning the tree with $make maintainer-clean NO_CLEAN_GMP=YES which doesn't doesn't clean the `gmp/` folder, and so the `include/ghc-gmp.h` file wasn't recreated (as it was previously a side-effect of building the intree GMP). Reviewed By: luite Differential Revision: https://phabricator.haskell.org/D523 >--------------------------------------------------------------- 6a130992b2afab5f2de87c6c8f98328eb925258c libraries/integer-gmp2/gmp/ghc.mk | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/libraries/integer-gmp2/gmp/ghc.mk b/libraries/integer-gmp2/gmp/ghc.mk index 5bc3131..45991d0 100644 --- a/libraries/integer-gmp2/gmp/ghc.mk +++ b/libraries/integer-gmp2/gmp/ghc.mk @@ -84,7 +84,10 @@ endif endif ifeq "$(UseIntreeGmp)" "YES" -$(libraries/integer-gmp2_dist-install_depfile_c_asm): libraries/integer-gmp2/gmp/gmp.h +$(libraries/integer-gmp2_dist-install_depfile_c_asm): libraries/integer-gmp2/gmp/gmp.h libraries/integer-gmp2/include/ghc-gmp.h + +libraries/integer-gmp2/include/ghc-gmp.h: libraries/integer-gmp2/gmp/gmp.h + $(CP) $< $@ gmp_CC_OPTS += -Ilibraries/integer-gmp2/gmp @@ -128,7 +131,6 @@ libraries/integer-gmp2/gmp/libgmp.a libraries/integer-gmp2/gmp/gmp.h: --host=$(HOSTPLATFORM) --build=$(BUILDPLATFORM) $(MAKE) -C libraries/integer-gmp2/gmp/gmpbuild MAKEFLAGS= $(CP) libraries/integer-gmp2/gmp/gmpbuild/gmp.h libraries/integer-gmp2/gmp/ - $(CP) libraries/integer-gmp2/gmp/gmpbuild/gmp.h libraries/integer-gmp2/include/ghc-gmp.h $(CP) libraries/integer-gmp2/gmp/gmpbuild/.libs/libgmp.a libraries/integer-gmp2/gmp/ $(MKDIRHIER) libraries/integer-gmp2/gmp/objs cd libraries/integer-gmp2/gmp/objs && $(AR_STAGE1) x ../libgmp.a From git at git.haskell.org Mon Nov 24 11:48:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Nov 2014 11:48:27 +0000 (UTC) Subject: [commit: ghc] master: Use the `patch` command detected by the top-level `configure` (a7c2972) Message-ID: <20141124114827.6346D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a7c29721535d636fb16ab756b3f44224e04a5113/ghc >--------------------------------------------------------------- commit a7c29721535d636fb16ab756b3f44224e04a5113 Author: Herbert Valerio Riedel Date: Mon Nov 24 12:45:42 2014 +0100 Use the `patch` command detected by the top-level `configure` ...instead of invoking `patch` directly in `integer-gmp2/gmp/ghc.mk` >--------------------------------------------------------------- a7c29721535d636fb16ab756b3f44224e04a5113 libraries/integer-gmp2/gmp/ghc.mk | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/integer-gmp2/gmp/ghc.mk b/libraries/integer-gmp2/gmp/ghc.mk index 45991d0..2d8aacc 100644 --- a/libraries/integer-gmp2/gmp/ghc.mk +++ b/libraries/integer-gmp2/gmp/ghc.mk @@ -113,8 +113,8 @@ libraries/integer-gmp2/gmp/libgmp.a libraries/integer-gmp2/gmp/gmp.h: $(RM) -rf libraries/integer-gmp2/gmp/$(GMP_DIR) libraries/integer-gmp2/gmp/gmpbuild libraries/integer-gmp2/gmp/objs cat $(GMP_TARBALL) | $(BZIP2_CMD) -d | { cd libraries/integer-gmp2/gmp && $(TAR_CMD) -xf - ; } mv libraries/integer-gmp2/gmp/$(GMP_DIR) libraries/integer-gmp2/gmp/gmpbuild - cd libraries/integer-gmp2/gmp && patch -p0 < gmpsrc.patch - cat libraries/integer-gmp/gmp/tarball/gmp-5.0.4.patch | { cd libraries/integer-gmp2/gmp/gmpbuild && patch -p1 ; } + cd libraries/integer-gmp2/gmp && $(PATCH_CMD) -p0 < gmpsrc.patch + cat libraries/integer-gmp/gmp/tarball/gmp-5.0.4.patch | { cd libraries/integer-gmp2/gmp/gmpbuild && $(PATCH_CMD) -p1 ; } chmod +x libraries/integer-gmp2/gmp/ln # Their cmd invocation only works on msys. On cygwin it starts From git at git.haskell.org Mon Nov 24 15:43:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Nov 2014 15:43:24 +0000 (UTC) Subject: [commit: ghc] master: accessors to RTS flag values -- #5364 (1617a10) Message-ID: <20141124154324.9CE373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1617a10aaa75567b776d4a47200ddaa1267771db/ghc >--------------------------------------------------------------- commit 1617a10aaa75567b776d4a47200ddaa1267771db Author: ?mer Sinan A?acan Date: Fri Nov 21 18:58:29 2014 -0600 accessors to RTS flag values -- #5364 Summary: Implementation of #5364. Mostly boilerplate, reading FILE fields is missing. Test Plan: - Get some feedback on missing parts. (FILE fields) - Get some feedback on module name. - Get some feedback on other things. - Get code reviewed. - Make sure test suite is passing. (I haven't run it myself) Reviewers: hvr, austin, ezyang Reviewed By: ezyang Subscribers: ekmett, simonmar, ezyang, carter, thomie Differential Revision: https://phabricator.haskell.org/D306 GHC Trac Issues: #5364 Conflicts: includes/rts/Flags.h >--------------------------------------------------------------- 1617a10aaa75567b776d4a47200ddaa1267771db includes/rts/Flags.h | 78 +++++--- libraries/base/GHC/RTS/Flags.hsc | 408 +++++++++++++++++++++++++++++++++++++++ libraries/base/base.cabal | 2 + libraries/base/cbits/rts.c | 42 ++++ libraries/base/changelog.md | 2 + 5 files changed, 502 insertions(+), 30 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1617a10aaa75567b776d4a47200ddaa1267771db From git at git.haskell.org Mon Nov 24 15:43:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Nov 2014 15:43:27 +0000 (UTC) Subject: [commit: ghc] master: Minor tweaks to API Annotation (bdeab90) Message-ID: <20141124154327.4175F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bdeab901ffda47cb8f4a28ab3880626e8b23b4d6/ghc >--------------------------------------------------------------- commit bdeab901ffda47cb8f4a28ab3880626e8b23b4d6 Author: Alan Zimmerman Date: Mon Nov 24 09:43:45 2014 -0600 Minor tweaks to API Annotation Summary: Add missing Outputable instance for AnnotationComment Update documentation Adjust parser to capture annotations correctly Test Plan: ./validate Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D520 >--------------------------------------------------------------- bdeab901ffda47cb8f4a28ab3880626e8b23b4d6 compiler/hsSyn/HsImpExp.lhs | 13 +++++++------ compiler/parser/ApiAnnotation.hs | 2 ++ compiler/parser/Parser.y | 16 ++++++++-------- testsuite/tests/ghc-api/annotations/annotations.stdout | 4 ++++ testsuite/tests/ghc-api/annotations/parseTree.stdout | 4 ++++ 5 files changed, 25 insertions(+), 14 deletions(-) diff --git a/compiler/hsSyn/HsImpExp.lhs b/compiler/hsSyn/HsImpExp.lhs index b6ec66a..d627591 100644 --- a/compiler/hsSyn/HsImpExp.lhs +++ b/compiler/hsSyn/HsImpExp.lhs @@ -39,16 +39,16 @@ type LImportDecl name = Located (ImportDecl name) data ImportDecl name = ImportDecl { ideclName :: Located ModuleName, -- ^ Module name. - ideclPkgQual :: Maybe FastString, -- ^ Package qualifier. - ideclSource :: Bool, -- ^ True <=> {-# SOURCE #-} import + ideclPkgQual :: Maybe FastString, -- ^ Package qualifier. + ideclSource :: Bool, -- ^ True <=> {-\# SOURCE \#-} import ideclSafe :: Bool, -- ^ True => safe import ideclQualified :: Bool, -- ^ True => qualified ideclImplicit :: Bool, -- ^ True => implicit import (of Prelude) ideclAs :: Maybe ModuleName, -- ^ as Module ideclHiding :: Maybe (Bool, Located [LIE name]) - } -- ^ (True => hiding, names) - -- + } + -- ^ -- 'ApiAnnotation.AnnKeywordId's -- -- - 'ApiAnnotation.AnnImport' @@ -57,6 +57,7 @@ data ImportDecl name -- -- - 'ApiAnnotation.AnnSafe','ApiAnnotation.AnnQualified', -- 'ApiAnnotation.AnnPackageName','ApiAnnotation.AnnAs', + -- 'ApiAnnotation.AnnVal' -- -- - 'ApiAnnotation.AnnHiding','ApiAnnotation.AnnOpen', -- 'ApiAnnotation.AnnClose' attached @@ -130,10 +131,10 @@ type LIE name = Located (IE name) data IE name = IEVar (Located name) -- ^ - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnPattern', - -- 'ApiAnnotation.AnnType' + -- 'ApiAnnotation.AnnType' | IEThingAbs name -- ^ Class/Type (can't tell) -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnPattern', - -- 'ApiAnnotation.AnnType' + -- 'ApiAnnotation.AnnType','ApiAnnotation.AnnVal' | IEThingAll (Located name) -- ^ Class/Type plus all methods/constructors -- -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen', diff --git a/compiler/parser/ApiAnnotation.hs b/compiler/parser/ApiAnnotation.hs index 140cd1d..4640a98 100644 --- a/compiler/parser/ApiAnnotation.hs +++ b/compiler/parser/ApiAnnotation.hs @@ -229,6 +229,8 @@ data AnnotationComment = -- Note: these are based on the Token versions, but the Token type is -- defined in Lexer.x and bringing it in here would create a loop +instance Outputable AnnotationComment where + ppr x = text (show x) -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen', -- 'ApiAnnotation.AnnClose','ApiAnnotation.AnnComma', diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index d9c0991..eb800ba 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -544,7 +544,7 @@ exp_doc :: { OrdList (LIE RdrName) } -- They are built in syntax, always available export :: { OrdList (LIE RdrName) } : qcname_ext export_subspec {% amsu (sLL $1 $> (mkModuleImpExp $1 - (snd $ unLoc $2))) + (snd $ unLoc $2))) (fst $ unLoc $2) } | 'module' modid {% amsu (sLL $1 $> (IEModuleContents $2)) [mj AnnModule $1] } @@ -565,9 +565,9 @@ qcnames :: { [Located RdrName] } -- A reversed list qcname_ext :: { Located RdrName } -- Variable or data constructor -- or tagged type constructor - : qcname { $1 } - | 'type' qcname {% am (mkTypeImpExp (sLL $1 $> (unLoc $2))) - (AnnType, $1) } + : qcname {% ams $1 [mj AnnVal $1] } + | 'type' qcname {% amms (mkTypeImpExp (sLL $1 $> (unLoc $2))) + [mj AnnType $1,mj AnnVal $2] } -- Cannot pull into qcname_ext, as qcname is also used in expression. qcname :: { Located RdrName } -- Variable or data constructor @@ -598,7 +598,7 @@ importdecl :: { LImportDecl RdrName } , ideclAs = unLoc (snd $7) , ideclHiding = unLoc $8 }) ((mj AnnImport $1 : fst $2 ++ fst $3 ++ fst $4 - ++ fst $7) ++ (fst $5)) } + ++ fst $5 ++ fst $7)) } maybe_src :: { ([AddAnn],IsBootInterface) } : '{-# SOURCE' '#-}' { ([mo $1,mc $2],True) } @@ -618,9 +618,9 @@ optqualified :: { ([AddAnn],Bool) } | {- empty -} { ([],False) } maybeas :: { ([AddAnn],Located (Maybe ModuleName)) } - : 'as' modid { ([mj AnnAs $1] - ,sLL $1 $> (Just (unLoc $2))) } - | {- empty -} { ([],noLoc Nothing) } + : 'as' modid { ([mj AnnAs $1,mj AnnVal $2] + ,sLL $1 $> (Just (unLoc $2))) } + | {- empty -} { ([],noLoc Nothing) } maybeimpspec :: { Located (Maybe (Bool, Located [LIE RdrName])) } : impspec { L (gl $1) (Just (unLoc $1)) } diff --git a/testsuite/tests/ghc-api/annotations/annotations.stdout b/testsuite/tests/ghc-api/annotations/annotations.stdout index e0c311e..ddf4f8d 100644 --- a/testsuite/tests/ghc-api/annotations/annotations.stdout +++ b/testsuite/tests/ghc-api/annotations/annotations.stdout @@ -13,12 +13,16 @@ (AK AnnotationLet.hs:1:22-26 AnnOpen = [AnnotationLet.hs:1:22]) +(AK AnnotationLet.hs:1:23-25 AnnVal = [AnnotationLet.hs:1:23-25]) + (AK AnnotationLet.hs:4:1-32 AnnAs = [AnnotationLet.hs:4:28-29]) (AK AnnotationLet.hs:4:1-32 AnnImport = [AnnotationLet.hs:4:1-6]) (AK AnnotationLet.hs:4:1-32 AnnQualified = [AnnotationLet.hs:4:8-16]) +(AK AnnotationLet.hs:4:1-32 AnnVal = [AnnotationLet.hs:4:31-32]) + (AK AnnotationLet.hs:(6,1)-(10,12) AnnEqual = [AnnotationLet.hs:6:5]) (AK AnnotationLet.hs:(6,1)-(10,12) AnnFunId = [AnnotationLet.hs:6:1-3]) diff --git a/testsuite/tests/ghc-api/annotations/parseTree.stdout b/testsuite/tests/ghc-api/annotations/parseTree.stdout index b8b9aa6..ed71b5a 100644 --- a/testsuite/tests/ghc-api/annotations/parseTree.stdout +++ b/testsuite/tests/ghc-api/annotations/parseTree.stdout @@ -25,12 +25,16 @@ (AK AnnotationTuple.hs:2:24-28 AnnOpen = [AnnotationTuple.hs:2:24]) +(AK AnnotationTuple.hs:2:25-27 AnnVal = [AnnotationTuple.hs:2:25-27]) + (AK AnnotationTuple.hs:5:1-32 AnnAs = [AnnotationTuple.hs:5:28-29]) (AK AnnotationTuple.hs:5:1-32 AnnImport = [AnnotationTuple.hs:5:1-6]) (AK AnnotationTuple.hs:5:1-32 AnnQualified = [AnnotationTuple.hs:5:8-16]) +(AK AnnotationTuple.hs:5:1-32 AnnVal = [AnnotationTuple.hs:5:31-32]) + (AK AnnotationTuple.hs:(7,1)-(10,14) AnnEqual = [AnnotationTuple.hs:7:5]) (AK AnnotationTuple.hs:(7,1)-(10,14) AnnFunId = [AnnotationTuple.hs:7:1-3]) From git at git.haskell.org Mon Nov 24 18:02:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Nov 2014 18:02:29 +0000 (UTC) Subject: [commit: ghc] master: Add `--fwarn-trustworthy-safe` to `-Wall` again. (3359133) Message-ID: <20141124180229.571143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/33591335f4bbbe350106276bba4b6cc61f1dda06/ghc >--------------------------------------------------------------- commit 33591335f4bbbe350106276bba4b6cc61f1dda06 Author: David Terei Date: Mon Nov 24 03:34:18 2014 -0500 Add `--fwarn-trustworthy-safe` to `-Wall` again. This redoes part of 475dd93efa which was reversed in 452d6aa95b after breaking validate on windows. >--------------------------------------------------------------- 33591335f4bbbe350106276bba4b6cc61f1dda06 compiler/main/DynFlags.hs | 3 ++- mk/validate-settings.mk | 2 ++ 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 5e3bda9..d6f620f 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -3214,7 +3214,8 @@ minusWallOpts Opt_WarnMissingSigs, Opt_WarnHiShadows, Opt_WarnOrphans, - Opt_WarnUnusedDoBind + Opt_WarnUnusedDoBind, + Opt_WarnTrustworthySafe ] enableGlasgowExts :: DynP () diff --git a/mk/validate-settings.mk b/mk/validate-settings.mk index e06135b..6a85b79 100644 --- a/mk/validate-settings.mk +++ b/mk/validate-settings.mk @@ -169,7 +169,9 @@ libraries/array_dist-install_EXTRA_HC_OPTS += -fno-warn-warnings-deprecations # Turn of trustworthy-safe warning libraries/base_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe libraries/ghc-prim_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe +libraries/process_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe libraries/unix_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe +libraries/Win32_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe # Temporarely disable inline rule shadowing warning libraries/bytestring_dist-install_EXTRA_HC_OPTS += -fno-warn-inline-rule-shadowing From git at git.haskell.org Mon Nov 24 20:25:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Nov 2014 20:25:55 +0000 (UTC) Subject: [commit: ghc] master: Test #7643 in typecheck/should_compile/T7643. (63d2ada) Message-ID: <20141124202555.EF68E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/63d2adaef999258d874a760591e9c9ec3d75aeaf/ghc >--------------------------------------------------------------- commit 63d2adaef999258d874a760591e9c9ec3d75aeaf Author: Richard Eisenberg Date: Mon Nov 24 15:13:53 2014 -0500 Test #7643 in typecheck/should_compile/T7643. >--------------------------------------------------------------- 63d2adaef999258d874a760591e9c9ec3d75aeaf testsuite/tests/typecheck/should_compile/T7643.hs | 11 +++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 12 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T7643.hs b/testsuite/tests/typecheck/should_compile/T7643.hs new file mode 100644 index 0000000..77071d5 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T7643.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE MagicHash, TypeFamilies #-} + +module T7643 where + +import GHC.Exts + +type family T +type instance T = RealWorld + +foo :: () -> State# T +foo _ = unsafeCoerce# realWorld# diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index b16ff43..291d118 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -431,3 +431,4 @@ test('T9151', normal, compile, ['']) test('T9497a', normal, compile, ['-fdefer-typed-holes']) test('T9497b', normal, compile, ['-fdefer-typed-holes -fno-warn-typed-holes']) test('T9497c', normal, compile, ['-fdefer-type-errors -fno-warn-typed-holes']) +test('T7643', normal, compile, ['']) From git at git.haskell.org Mon Nov 24 20:25:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Nov 2014 20:25:59 +0000 (UTC) Subject: [commit: ghc] master: Test #8044 in typecheck/should_fail/T8044 (8459404) Message-ID: <20141124202559.15D473A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8459404b6431e44669f8732b6787c7d6b67b984b/ghc >--------------------------------------------------------------- commit 8459404b6431e44669f8732b6787c7d6b67b984b Author: Richard Eisenberg Date: Mon Nov 24 15:17:15 2014 -0500 Test #8044 in typecheck/should_fail/T8044 >--------------------------------------------------------------- 8459404b6431e44669f8732b6787c7d6b67b984b testsuite/tests/typecheck/should_fail/T8044.hs | 16 ++++++++++++++++ testsuite/tests/typecheck/should_fail/T8044.stderr | 9 +++++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 26 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T8044.hs b/testsuite/tests/typecheck/should_fail/T8044.hs new file mode 100644 index 0000000..0a1ce69 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T8044.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE GADTs, TypeFamilies #-} + +module T8044 where + +data X a where + XInt :: X Int + XBool :: X Bool + XChar :: X Char + +type family Frob a where + Frob Int = Int + Frob x = Char + +frob :: X a -> X (Frob a) +frob XInt = XInt +frob _ = XChar diff --git a/testsuite/tests/typecheck/should_fail/T8044.stderr b/testsuite/tests/typecheck/should_fail/T8044.stderr new file mode 100644 index 0000000..6178ea3 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T8044.stderr @@ -0,0 +1,9 @@ + +T8044.hs:16:13: + Couldn't match type ?Frob a? with ?Char? + Expected type: X (Frob a) + Actual type: X Char + Relevant bindings include + frob :: X a -> X (Frob a) (bound at T8044.hs:15:1) + In the expression: XChar + In an equation for ?frob?: frob _ = XChar diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 81ea3d2..05f77bb 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -344,3 +344,4 @@ test('T9318', normal, compile_fail, ['']) test('T9201', normal, compile_fail, ['']) test('T9109', normal, compile_fail, ['']) test('T9497d', normal, compile_fail, ['-fdefer-type-errors -fno-defer-typed-holes']) +test('T8044', normal, compile_fail, ['']) From git at git.haskell.org Mon Nov 24 20:26:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Nov 2014 20:26:02 +0000 (UTC) Subject: [commit: ghc] master: Test #8031 in th/T8031 (5c35415) Message-ID: <20141124202602.237893A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5c3541548e441456ca6a0dd62caf8acd7fc5cf33/ghc >--------------------------------------------------------------- commit 5c3541548e441456ca6a0dd62caf8acd7fc5cf33 Author: Richard Eisenberg Date: Mon Nov 24 15:24:03 2014 -0500 Test #8031 in th/T8031 >--------------------------------------------------------------- 5c3541548e441456ca6a0dd62caf8acd7fc5cf33 testsuite/tests/th/T8031.hs | 14 ++++++++++++++ testsuite/tests/th/all.T | 1 + 2 files changed, 15 insertions(+) diff --git a/testsuite/tests/th/T8031.hs b/testsuite/tests/th/T8031.hs new file mode 100644 index 0000000..e71f347 --- /dev/null +++ b/testsuite/tests/th/T8031.hs @@ -0,0 +1,14 @@ +{-# LANGUAGE TemplateHaskell, RankNTypes, DataKinds, TypeOperators, PolyKinds, + GADTs #-} + +module T8031 where + +import Data.Proxy + +data SList :: [k] -> * where + SCons :: Proxy h -> Proxy t -> SList (h ': t) + +$( [d| foo :: forall (a :: k). Proxy a + -> forall (b :: [k]). Proxy b + -> SList (a ': b) + foo a b = SCons a b |] ) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 60b6089..8656fcb 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -347,3 +347,4 @@ test('T7484', normal, compile_fail, ['-v0']) test('T1476', normal, compile, ['-v0']) test('T1476b', normal, compile_fail, ['-v0']) test('T9824', normal, compile, ['-v0']) +test('T8031', normal, compile, ['-v0']) From git at git.haskell.org Mon Nov 24 21:49:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Nov 2014 21:49:48 +0000 (UTC) Subject: [commit: ghc] master: Changelog entry and /Since/ for alloc-counter ops (8e82857) Message-ID: <20141124214948.05E0D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8e8285707605bdb3eb77f202733017b25693ccbe/ghc >--------------------------------------------------------------- commit 8e8285707605bdb3eb77f202733017b25693ccbe Author: Herbert Valerio Riedel Date: Mon Nov 24 22:32:23 2014 +0100 Changelog entry and /Since/ for alloc-counter ops See b0534f78a73f972e279eed4447a5687bd6a8308e for more details [skip ci] >--------------------------------------------------------------- 8e8285707605bdb3eb77f202733017b25693ccbe libraries/base/GHC/Conc/Sync.hs | 6 ++++++ libraries/base/GHC/IO/Exception.hs | 2 ++ libraries/base/changelog.md | 9 +++++++++ 3 files changed, 17 insertions(+) diff --git a/libraries/base/GHC/Conc/Sync.hs b/libraries/base/GHC/Conc/Sync.hs index 777fb71..e1dc915 100644 --- a/libraries/base/GHC/Conc/Sync.hs +++ b/libraries/base/GHC/Conc/Sync.hs @@ -193,6 +193,7 @@ instance Ord ThreadId where -- -- Allocation accounting is accurate only to about 4Kbytes. -- +-- /Since: 4.8.0.0/ setAllocationCounter :: Int64 -> IO () setAllocationCounter i = do ThreadId t <- myThreadId @@ -200,6 +201,8 @@ setAllocationCounter i = do -- | Return the current value of the allocation counter for the -- current thread. +-- +-- /Since: 4.8.0.0/ getAllocationCounter :: IO Int64 getAllocationCounter = do ThreadId t <- myThreadId @@ -224,12 +227,15 @@ getAllocationCounter = do -- Compared to using timeouts, allocation limits don't count time -- spent blocked or in foreign calls. -- +-- /Since: 4.8.0.0/ enableAllocationLimit :: IO () enableAllocationLimit = do ThreadId t <- myThreadId rts_enableThreadAllocationLimit t -- | Disable allocation limit processing for the current thread. +-- +-- /Since: 4.8.0.0/ disableAllocationLimit :: IO () disableAllocationLimit = do ThreadId t <- myThreadId diff --git a/libraries/base/GHC/IO/Exception.hs b/libraries/base/GHC/IO/Exception.hs index d0a21b2..f811e5a 100644 --- a/libraries/base/GHC/IO/Exception.hs +++ b/libraries/base/GHC/IO/Exception.hs @@ -102,6 +102,8 @@ instance Show Deadlock where -- |This thread has exceeded its allocation limit. See -- 'GHC.Conc.setAllocationCounter' and -- 'GHC.Conc.enableAllocationLimit'. +-- +-- /Since: 4.8.0.0/ data AllocationLimitExceeded = AllocationLimitExceeded deriving Typeable diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index df3d9d4..df20a58 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -119,6 +119,15 @@ * New module `GHC.RTS.Flags` that provides accessors to runtime flags. + * Expose functions for per-thread allocation counters and limits in `GHC.Conc` + + disableAllocationLimit :: IO () + enableAllocationLimit :: IO () + getAllocationCounter :: IO Int64 + setAllocationCounter :: Int64 -> IO () + + together with a new exception `AllocationLimitExceeded`. + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 From git at git.haskell.org Mon Nov 24 22:09:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Nov 2014 22:09:48 +0000 (UTC) Subject: [commit: ghc] master: Mark `Data.Typeable.Internal` as Trustworthy after consverstation with ekmett & hvr. (e159e08) Message-ID: <20141124220948.50B303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e159e08a5e1c1f9f7b6805f3f0775333104c3d6e/ghc >--------------------------------------------------------------- commit e159e08a5e1c1f9f7b6805f3f0775333104c3d6e Author: David Terei Date: Mon Nov 24 14:26:57 2014 -0500 Mark `Data.Typeable.Internal` as Trustworthy after consverstation with ekmett & hvr. >--------------------------------------------------------------- e159e08a5e1c1f9f7b6805f3f0775333104c3d6e libraries/base/Data/Typeable/Internal.hs | 2 +- testsuite/tests/safeHaskell/unsafeLibs/GoodImport03.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 4c7974a..ccdd059 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE ConstraintKinds #-} diff --git a/testsuite/tests/safeHaskell/unsafeLibs/GoodImport03.hs b/testsuite/tests/safeHaskell/unsafeLibs/GoodImport03.hs index 30da9f5..84e728f 100644 --- a/testsuite/tests/safeHaskell/unsafeLibs/GoodImport03.hs +++ b/testsuite/tests/safeHaskell/unsafeLibs/GoodImport03.hs @@ -56,7 +56,7 @@ import Data.String import Data.Traversable import Data.Tuple import Data.Typeable --- import Data.Typeable.Internal +import Data.Typeable.Internal import Data.Unique import Data.Version import Data.Word From git at git.haskell.org Tue Nov 25 14:37:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Nov 2014 14:37:32 +0000 (UTC) Subject: [commit: ghc] master: Add +RTS -n: divide the nursery into chunks (452eb80) Message-ID: <20141125143732.585623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/452eb80f15fce8665df52bc9facebfafb5b6267b/ghc >--------------------------------------------------------------- commit 452eb80f15fce8665df52bc9facebfafb5b6267b Author: Simon Marlow Date: Fri Nov 21 17:05:58 2014 +0000 Add +RTS -n: divide the nursery into chunks See the documentation for details. >--------------------------------------------------------------- 452eb80f15fce8665df52bc9facebfafb5b6267b docs/users_guide/runtime_control.xml | 36 +++++++++++ includes/rts/Flags.h | 1 + rts/RtsFlags.c | 11 +++- rts/Schedule.c | 6 ++ rts/sm/GC.c | 29 +-------- rts/sm/Sanity.c | 9 ++- rts/sm/Storage.c | 117 ++++++++++++++++++++++++++--------- rts/sm/Storage.h | 4 +- 8 files changed, 155 insertions(+), 58 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 452eb80f15fce8665df52bc9facebfafb5b6267b From git at git.haskell.org Tue Nov 25 14:37:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Nov 2014 14:37:34 +0000 (UTC) Subject: [commit: ghc] master: Document +RTS -xq (65d1c03) Message-ID: <20141125143734.F0AAD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/65d1c0359394dc78551c5fb73a0934aa88b8d9f4/ghc >--------------------------------------------------------------- commit 65d1c0359394dc78551c5fb73a0934aa88b8d9f4 Author: Simon Marlow Date: Tue Nov 25 13:33:51 2014 +0000 Document +RTS -xq >--------------------------------------------------------------- 65d1c0359394dc78551c5fb73a0934aa88b8d9f4 docs/users_guide/runtime_control.xml | 20 ++++++++++++++++++++ 1 file changed, 20 insertions(+) diff --git a/docs/users_guide/runtime_control.xml b/docs/users_guide/runtime_control.xml index 612a441..a55a1fe 100644 --- a/docs/users_guide/runtime_control.xml +++ b/docs/users_guide/runtime_control.xml @@ -323,6 +323,26 @@ $ ./prog -f +RTS -H32m -S -RTS -h foo bar + + + + RTS + option + + + [Default: 100k] This option relates to allocation + limits; for more about this see enableAllocationLimit. + When a thread hits its allocation limit, the RTS throws an + exception to the thread, and the thread gets an additional + quota of allocation before the exception is raised again, + the idea being so that the thread can execute its exception + handlers. The controls the size of + this additional quota. + + + + From git at git.haskell.org Tue Nov 25 14:37:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Nov 2014 14:37:37 +0000 (UTC) Subject: [commit: ghc] master: Make clearNursery free (e22bc0d) Message-ID: <20141125143737.ECF323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e22bc0dedb9e9da0176ad7ce4a74acbefedc7207/ghc >--------------------------------------------------------------- commit e22bc0dedb9e9da0176ad7ce4a74acbefedc7207 Author: Simon Marlow Date: Tue Oct 7 10:30:36 2014 +0100 Make clearNursery free Summary: clearNursery resets all the bd->free pointers of nursery blocks to make the blocks empty. In profiles we've seen clearNursery taking significant amounts of time particularly with large -N and -A values. This patch moves the work of clearNursery to the point at which we actually need the new block, thereby introducing an invariant that blocks to the right of the CurrentNursery pointer still need their bd->free pointer reset. This should make things faster overall, because we don't need to clear blocks that we don't use. Test Plan: validate Reviewers: AndreasVoellmy, ezyang, austin Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D318 >--------------------------------------------------------------- e22bc0dedb9e9da0176ad7ce4a74acbefedc7207 includes/rts/storage/GC.h | 21 ++++++ rts/Capability.h | 6 +- rts/HeapStackCheck.cmm | 5 ++ rts/Schedule.c | 18 ++--- rts/Stats.c | 21 +----- rts/sm/Storage.c | 76 +++++++++++++++++----- rts/sm/Storage.h | 22 ++++++- testsuite/tests/codeGen/should_run/all.T | 1 + testsuite/tests/codeGen/should_run/cgrun074.hs | 24 +++++++ testsuite/tests/codeGen/should_run/cgrun074.stdout | 1 + utils/deriveConstants/DeriveConstants.hs | 1 + 11 files changed, 144 insertions(+), 52 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e22bc0dedb9e9da0176ad7ce4a74acbefedc7207 From git at git.haskell.org Tue Nov 25 17:27:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Nov 2014 17:27:29 +0000 (UTC) Subject: [commit: ghc] master: Update `deepseq` to latest 1.4.0.0 snapshot (5fa0186) Message-ID: <20141125172729.4F9713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5fa018655305a8d9272daf187dd241dee3b606fc/ghc >--------------------------------------------------------------- commit 5fa018655305a8d9272daf187dd241dee3b606fc Author: Herbert Valerio Riedel Date: Tue Nov 25 18:21:41 2014 +0100 Update `deepseq` to latest 1.4.0.0 snapshot This pulls in several `NFData` instances since the last submodule update. >--------------------------------------------------------------- 5fa018655305a8d9272daf187dd241dee3b606fc libraries/deepseq | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/deepseq b/libraries/deepseq index 75ce576..8dc617d 160000 --- a/libraries/deepseq +++ b/libraries/deepseq @@ -1 +1 @@ -Subproject commit 75ce5767488774065025df34cbc80de6f03c4fd1 +Subproject commit 8dc617dad456e16c67b0f629495dcf266a58ab0a From git at git.haskell.org Tue Nov 25 17:27:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Nov 2014 17:27:31 +0000 (UTC) Subject: [commit: ghc] master: Replace `STRICT[12345]` macros by `BangPatterns` (4af5748) Message-ID: <20141125172731.E6F573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4af5748b4589cb5a3c8fc389cc721ebb33260a56/ghc >--------------------------------------------------------------- commit 4af5748b4589cb5a3c8fc389cc721ebb33260a56 Author: Yuri de Wit Date: Tue Nov 25 18:22:34 2014 +0100 Replace `STRICT[12345]` macros by `BangPatterns` This removes the macros `STRICT1()`, `STRICT2()`, `STRICT3()`, `STRICT4()`, and `STRICT5()` CPP macros from `HsVersions.hs` and replaces the few use sites by uses of `BangPatterns`. Reviewed By: hvr Differential Revision: https://phabricator.haskell.org/D525 >--------------------------------------------------------------- 4af5748b4589cb5a3c8fc389cc721ebb33260a56 compiler/HsVersions.h | 8 -------- compiler/utils/BufWrite.hs | 20 +++----------------- compiler/utils/Encoding.hs | 9 +++------ 3 files changed, 6 insertions(+), 31 deletions(-) diff --git a/compiler/HsVersions.h b/compiler/HsVersions.h index 7ba82e1..6d5716d 100644 --- a/compiler/HsVersions.h +++ b/compiler/HsVersions.h @@ -49,13 +49,5 @@ name = Util.globalM (value); #define ASSERTM2(e,msg) do { bool <- e; MASSERT2(bool,msg) } #define WARNM2(e,msg) do { bool <- e; WARN(bool, msg) return () } --- Useful for declaring arguments to be strict -#define STRICT1(f) f a | a `seq` False = undefined -#define STRICT2(f) f a b | a `seq` b `seq` False = undefined -#define STRICT3(f) f a b c | a `seq` b `seq` c `seq` False = undefined -#define STRICT4(f) f a b c d | a `seq` b `seq` c `seq` d `seq` False = undefined -#define STRICT5(f) f a b c d e | a `seq` b `seq` c `seq` d `seq` e `seq` False = undefined -#define STRICT6(f) f a b c d e f | a `seq` b `seq` c `seq` d `seq` e `seq` f `seq` False = undefined - #endif /* HsVersions.h */ diff --git a/compiler/utils/BufWrite.hs b/compiler/utils/BufWrite.hs index 482e9ee..40b9759 100644 --- a/compiler/utils/BufWrite.hs +++ b/compiler/utils/BufWrite.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP #-} +{-# LANGUAGE BangPatterns #-} ----------------------------------------------------------------------------- -- @@ -23,8 +23,6 @@ module BufWrite ( bFlush, ) where -#include "HsVersions.h" - import FastString import FastTypes import FastMutInt @@ -53,12 +51,8 @@ newBufHandle hdl = do buf_size :: Int buf_size = 8192 -#define STRICT2(f) f a b | a `seq` b `seq` False = undefined -#define STRICT3(f) f a b c | a `seq` b `seq` c `seq` False = undefined - bPutChar :: BufHandle -> Char -> IO () -STRICT2(bPutChar) -bPutChar b@(BufHandle buf r hdl) c = do +bPutChar b@(BufHandle buf r hdl) !c = do i <- readFastMutInt r if (i >= buf_size) then do hPutBuf hdl buf buf_size @@ -68,8 +62,7 @@ bPutChar b@(BufHandle buf r hdl) c = do writeFastMutInt r (i+1) bPutStr :: BufHandle -> String -> IO () -STRICT2(bPutStr) -bPutStr (BufHandle buf r hdl) str = do +bPutStr (BufHandle buf r hdl) !str = do i <- readFastMutInt r loop str i where loop _ i | i `seq` False = undefined @@ -124,10 +117,3 @@ bFlush (BufHandle buf r hdl) = do when (i > 0) $ hPutBuf hdl buf i free buf return () - -#if 0 -myPutBuf s hdl buf i = - modifyIOError (\e -> ioeSetErrorString e (ioeGetErrorString e ++ ':':s ++ " (" ++ show buf ++ "," ++ show i ++ ")")) $ - - hPutBuf hdl buf i -#endif diff --git a/compiler/utils/Encoding.hs b/compiler/utils/Encoding.hs index 5c8619b..ae727d2 100644 --- a/compiler/utils/Encoding.hs +++ b/compiler/utils/Encoding.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE BangPatterns, CPP, MagicHash, UnboxedTuples #-} +{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples #-} {-# OPTIONS_GHC -O #-} -- We always optimise this, otherwise performance of a non-optimised -- compiler is severely affected @@ -28,7 +28,6 @@ module Encoding ( zDecodeString ) where -#include "HsVersions.h" import Foreign import Data.Char import Numeric @@ -169,16 +168,14 @@ utf8EncodeChar c ptr = utf8EncodeString :: Ptr Word8 -> String -> IO () utf8EncodeString ptr str = go ptr str - where STRICT2(go) - go _ [] = return () + where go !_ [] = return () go ptr (c:cs) = do ptr' <- utf8EncodeChar c ptr go ptr' cs utf8EncodedLength :: String -> Int utf8EncodedLength str = go 0 str - where STRICT2(go) - go n [] = n + where go !n [] = n go n (c:cs) | ord c > 0 && ord c <= 0x007f = go (n+1) cs | ord c <= 0x07ff = go (n+2) cs From git at git.haskell.org Tue Nov 25 21:42:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Nov 2014 21:42:52 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: Update changelog.md (14c9cb2) Message-ID: <20141125214252.5CAC83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/14c9cb297d4de7828941e41811d0eab4f3754c2d/base >--------------------------------------------------------------- commit 14c9cb297d4de7828941e41811d0eab4f3754c2d Author: Herbert Valerio Riedel Date: Tue Nov 25 22:43:25 2014 +0100 Update changelog.md >--------------------------------------------------------------- 14c9cb297d4de7828941e41811d0eab4f3754c2d changelog.md | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/changelog.md b/changelog.md index bb42c1e..12f3108 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,13 @@ # Changelog for [`base` package](http://hackage.haskell.org/package/base) +## 4.7.0.2 *Dec 2014* + + * Bundled with GHC 7.8.4 + + * Fix performance bug in `Data.List.inits` (#9345) + + * Fix handling of null bytes in `Debug.Trace.trace` (#9395) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 From git at git.haskell.org Tue Nov 25 21:47:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Nov 2014 21:47:40 +0000 (UTC) Subject: [commit: ghc] master: Insert changelog entries for GHC 7.8.4 (fb5baaf) Message-ID: <20141125214740.1F4E73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fb5baaf7d05c2168542a5a442cc9e603d00aa590/ghc >--------------------------------------------------------------- commit fb5baaf7d05c2168542a5a442cc9e603d00aa590 Author: Herbert Valerio Riedel Date: Tue Nov 25 22:47:38 2014 +0100 Insert changelog entries for GHC 7.8.4 [skip ci] >--------------------------------------------------------------- fb5baaf7d05c2168542a5a442cc9e603d00aa590 libraries/base/changelog.md | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index df20a58..07c91a3 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -128,6 +128,14 @@ together with a new exception `AllocationLimitExceeded`. +## 4.7.0.2 *Dec 2014* + + * Bundled with GHC 7.8.4 + + * Fix performance bug in `Data.List.inits` (#9345) + + * Fix handling of null bytes in `Debug.Trace.trace` (#9395) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 From git at git.haskell.org Wed Nov 26 08:05:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Nov 2014 08:05:07 +0000 (UTC) Subject: [commit: ghc] master: Define `Data` instance for `Natural` type (#9818) (4bf055c) Message-ID: <20141126080507.4A66F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4bf055c70d07b98be1e7749e0306e406dfbbc006/ghc >--------------------------------------------------------------- commit 4bf055c70d07b98be1e7749e0306e406dfbbc006 Author: Herbert Valerio Riedel Date: Tue Nov 25 23:23:08 2014 +0100 Define `Data` instance for `Natural` type (#9818) This follows the same style as the other integral `Data` instances defined in the `Data.Data` module. Reviewed By: ekmett Differential Revision: https://phabricator.haskell.org/D526 >--------------------------------------------------------------- 4bf055c70d07b98be1e7749e0306e406dfbbc006 libraries/base/GHC/Natural.hs | 14 ++++++++++++++ 1 file changed, 14 insertions(+) diff --git a/libraries/base/GHC/Natural.hs b/libraries/base/GHC/Natural.hs index e9b37b1..221bc31 100644 --- a/libraries/base/GHC/Natural.hs +++ b/libraries/base/GHC/Natural.hs @@ -67,6 +67,7 @@ import GHC.Enum import GHC.List import Data.Bits +import Data.Data default () @@ -588,3 +589,16 @@ naturalToWordMaybe (Natural i) where maxw = toInteger (maxBound :: Word) #endif + +-- This follows the same style as the other integral 'Data' instances +-- defined in "Data.Data" +naturalType :: DataType +naturalType = mkIntType "Numeric.Natural.Natural" + +instance Data Natural where + toConstr x = mkIntegralConstr naturalType x + gunfold _ z c = case constrRep c of + (IntConstr x) -> z (fromIntegral x) + _ -> error $ "Data.Data.gunfold: Constructor " ++ show c + ++ " is not of type Natural" + dataTypeOf _ = naturalType From git at git.haskell.org Wed Nov 26 13:21:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Nov 2014 13:21:33 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #9834 (cb9bcec) Message-ID: <20141126132133.54E2E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cb9bcecceae5e6df758d0973ed0e496a07d15026/ghc >--------------------------------------------------------------- commit cb9bcecceae5e6df758d0973ed0e496a07d15026 Author: Simon Peyton Jones Date: Wed Nov 26 13:22:05 2014 +0000 Test Trac #9834 >--------------------------------------------------------------- cb9bcecceae5e6df758d0973ed0e496a07d15026 testsuite/tests/typecheck/should_compile/T9834.hs | 23 +++++++ .../tests/typecheck/should_compile/T9834.stderr | 71 ++++++++++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 95 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T9834.hs b/testsuite/tests/typecheck/should_compile/T9834.hs new file mode 100644 index 0000000..c16e395 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9834.hs @@ -0,0 +1,23 @@ +{-# OPTIONS_GHC -fdefer-type-errors #-} +{-# LANGUAGE ImpredicativeTypes #-} + +module T9834 where +import Control.Applicative +import Data.Functor.Identity + +type Nat f g = forall a. f a -> g a + +newtype Comp p q a = Comp (p (q a)) + +liftOuter :: (Functor p, Applicative q) => p a -> (Comp p q) a +liftOuter pa = Comp (pure <$> pa) + +runIdComp :: Functor p => Comp p Identity a -> p a +runIdComp (Comp p) = runIdentity <$> p + +wrapIdComp :: Applicative p => (forall q. Applicative q => Nat (Comp p q) (Comp p q)) -> p a -> p a +wrapIdComp f = runIdComp . f . liftOuter + +class Applicative p => ApplicativeFix p where + afix :: (forall q. Applicative q => (Comp p q) a -> (Comp p q) a) -> p a + afix = wrapIdComp \ No newline at end of file diff --git a/testsuite/tests/typecheck/should_compile/T9834.stderr b/testsuite/tests/typecheck/should_compile/T9834.stderr new file mode 100644 index 0000000..e4372e5 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9834.stderr @@ -0,0 +1,71 @@ + +T9834.hs:23:10: Warning: + Couldn't match type ?p? with ?(->) (p a0)? + ?p? is a rigid type variable bound by + the class declaration for ?ApplicativeFix? at T9834.hs:21:39 + Expected type: (forall (q :: * -> *). + Applicative q => + Comp p q a -> Comp p q a) + -> p a + Actual type: (forall (q :: * -> *). + Applicative q => + Nat (Comp p q) (Comp p q)) + -> p a0 -> p a0 + Relevant bindings include + afix :: (forall (q :: * -> *). + Applicative q => + Comp p q a -> Comp p q a) + -> p a + (bound at T9834.hs:23:3) + In the expression: wrapIdComp + In an equation for ?afix?: afix = wrapIdComp + +T9834.hs:23:10: Warning: + Couldn't match type ?a? with ?p a0? + ?a? is a rigid type variable bound by + the type signature for + afix :: (forall (q :: * -> *). + Applicative q => + Comp p q a -> Comp p q a) + -> p a + at T9834.hs:22:11 + Expected type: (forall (q :: * -> *). + Applicative q => + Comp p q a -> Comp p q a) + -> p a + Actual type: (forall (q :: * -> *). + Applicative q => + Nat (Comp p q) (Comp p q)) + -> p a0 -> p a0 + Relevant bindings include + afix :: (forall (q :: * -> *). + Applicative q => + Comp p q a -> Comp p q a) + -> p a + (bound at T9834.hs:23:3) + In the expression: wrapIdComp + In an equation for ?afix?: afix = wrapIdComp + +T9834.hs:23:10: Warning: + Couldn't match type ?a? with ?a1? + ?a? is a rigid type variable bound by + the type signature for + afix :: (forall (q :: * -> *). + Applicative q => + Comp p q a -> Comp p q a) + -> p a + at T9834.hs:22:11 + ?a1? is a rigid type variable bound by + a type expected by the context: + Applicative q => Comp p q a1 -> Comp p q a1 + at T9834.hs:23:10 + Expected type: Comp p q a1 -> Comp p q a1 + Actual type: Comp p q a -> Comp p q a + Relevant bindings include + afix :: (forall (q :: * -> *). + Applicative q => + Comp p q a -> Comp p q a) + -> p a + (bound at T9834.hs:23:3) + In the expression: wrapIdComp + In an equation for ?afix?: afix = wrapIdComp diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 291d118..e1f4c3f 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -432,3 +432,4 @@ test('T9497a', normal, compile, ['-fdefer-typed-holes']) test('T9497b', normal, compile, ['-fdefer-typed-holes -fno-warn-typed-holes']) test('T9497c', normal, compile, ['-fdefer-type-errors -fno-warn-typed-holes']) test('T7643', normal, compile, ['']) +test('T9834', normal, compile, ['']) From git at git.haskell.org Wed Nov 26 17:10:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Nov 2014 17:10:00 +0000 (UTC) Subject: [commit: ghc] master: Use {bit, popCount}Integer for `Bits Integer` (ed56c02) Message-ID: <20141126171000.96C6C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ed56c023e3e2e3d2a9fe18a17e2131d9a55c69a5/ghc >--------------------------------------------------------------- commit ed56c023e3e2e3d2a9fe18a17e2131d9a55c69a5 Author: Herbert Valerio Riedel Date: Wed Nov 26 18:07:05 2014 +0100 Use {bit,popCount}Integer for `Bits Integer` The primops are implemented in the `integer-gmp2` (#9281) backend and are already used for the `Bits Natural` instance but aren't used yet for the `Bits Integer` instace. This commit fixes that. >--------------------------------------------------------------- ed56c023e3e2e3d2a9fe18a17e2131d9a55c69a5 libraries/base/Data/Bits.hs | 14 ++++++++++++++ 1 file changed, 14 insertions(+) diff --git a/libraries/base/Data/Bits.hs b/libraries/base/Data/Bits.hs index b4ab912..69a0377 100644 --- a/libraries/base/Data/Bits.hs +++ b/libraries/base/Data/Bits.hs @@ -57,12 +57,20 @@ module Data.Bits ( #include "MachDeps.h" +#ifdef MIN_VERSION_integer_gmp +# define HAVE_INTEGER_GMP1 MIN_VERSION_integer_gmp(1,0,0) +#endif + import Data.Maybe import GHC.Enum import GHC.Num import GHC.Base import GHC.Real +#if HAVE_INTEGER_GMP1 +import GHC.Integer.GMP.Internals (bitInteger, popCountInteger) +#endif + infixl 8 `shift`, `rotate`, `shiftL`, `shiftR`, `rotateL`, `rotateR` infixl 7 .&. infixl 6 `xor` @@ -513,8 +521,14 @@ instance Bits Integer where testBit x (I# i) = testBitInteger x i zeroBits = 0 + +#if HAVE_INTEGER_GMP1 + bit (I# i#) = bitInteger i# + popCount x = I# (popCountInteger x) +#else bit = bitDefault popCount = popCountDefault +#endif rotate x i = shift x i -- since an Integer never wraps around From git at git.haskell.org Wed Nov 26 23:16:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Nov 2014 23:16:16 +0000 (UTC) Subject: [commit: ghc] master: configure.ac: fix test == bashism (4897e70) Message-ID: <20141126231616.338FE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4897e7056e7b34c42ba5c0b1fa28ea547b8085b3/ghc >--------------------------------------------------------------- commit 4897e7056e7b34c42ba5c0b1fa28ea547b8085b3 Author: Tuncer Ayaz Date: Wed Nov 26 16:31:53 2014 +0100 configure.ac: fix test == bashism Signed-off-by: Austin Seipp >--------------------------------------------------------------- 4897e7056e7b34c42ba5c0b1fa28ea547b8085b3 configure.ac | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/configure.ac b/configure.ac index 5dd3aaa..ca9f220 100644 --- a/configure.ac +++ b/configure.ac @@ -560,7 +560,7 @@ then # Check whether LLVM backend is default for this platform "${WithGhc}" conftestghc.hs 2>&1 >/dev/null res=`./conftestghc` - if test "x$res" == "x%object" + if test "x$res" = "x%object" then AC_MSG_RESULT(yes) echo "Buggy bootstrap compiler" @@ -576,14 +576,14 @@ then # -fllvm is not the default, but set a flag so the Makefile can check # -for it in the build flags later on "${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null - if test $? == 0 + if test $? = 0 then res=`./conftestghc` - if test "x$res" == "x%object" + if test "x$res" = "x%object" then AC_MSG_RESULT(yes) GHC_LLVM_AFFECTED_BY_9439=1 - elif test "x$res" == "x%function" + elif test "x$res" = "x%function" then AC_MSG_RESULT(no) GHC_LLVM_AFFECTED_BY_9439=0 From git at git.haskell.org Wed Nov 26 23:17:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Nov 2014 23:17:04 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: configure.ac: fix test == bashism (0d5e352) Message-ID: <20141126231704.D929A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/0d5e3521b4135ea06e30b6cc5b819d35cc9cdbaf/ghc >--------------------------------------------------------------- commit 0d5e3521b4135ea06e30b6cc5b819d35cc9cdbaf Author: Tuncer Ayaz Date: Wed Nov 26 16:43:19 2014 +0100 configure.ac: fix test == bashism Signed-off-by: Austin Seipp >--------------------------------------------------------------- 0d5e3521b4135ea06e30b6cc5b819d35cc9cdbaf configure.ac | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/configure.ac b/configure.ac index f455e3d..27322c6 100644 --- a/configure.ac +++ b/configure.ac @@ -199,7 +199,7 @@ echo "main = putStrLn \"%function\"" > conftestghc.hs # Check whether LLVM backend is default for this platform ${WithGhc} conftestghc.hs 2>&1 >/dev/null res=`./conftestghc` -if test "x$res" == "x%object" +if test "x$res" = "x%object" then AC_MSG_RESULT(yes) echo "Buggy bootstrap compiler" @@ -215,14 +215,14 @@ fi # -fllvm is not the default, but set a flag so the Makefile can check # -for it in the build flags later on ${WithGhc} -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null -if test $? == 0 +if test $? = 0 then res=`./conftestghc` - if test "x$res" == "x%object" + if test "x$res" = "x%object" then AC_MSG_RESULT(yes) GHC_LLVM_AFFECTED_BY_9439=1 - elif test "x$res" == "x%function" + elif test "x$res" = "x%function" then AC_MSG_RESULT(no) GHC_LLVM_AFFECTED_BY_9439=0 From git at git.haskell.org Thu Nov 27 01:24:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Nov 2014 01:24:50 +0000 (UTC) Subject: [commit: ghc] master: Cabal submodule update: hole support and tests. (b19845d) Message-ID: <20141127012450.D41B33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b19845db926632c4be7b1e52fe2aa01d26ac3af3/ghc >--------------------------------------------------------------- commit b19845db926632c4be7b1e52fe2aa01d26ac3af3 Author: Edward Z. Yang Date: Mon Nov 17 22:30:35 2014 -0800 Cabal submodule update: hole support and tests. Depends on D485 Summary: Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D487 >--------------------------------------------------------------- b19845db926632c4be7b1e52fe2aa01d26ac3af3 .arclint | 2 +- libraries/Cabal | 2 +- libraries/bin-package-db/GHC/PackageDb.hs | 7 ++++- testsuite/.gitignore | 6 ++++ testsuite/tests/cabal/Makefile | 4 +-- testsuite/tests/cabal/cabal07/Makefile | 21 ++++++++++++++ .../tests/cabal/{cabal05 => cabal07}/Setup.hs | 0 testsuite/tests/cabal/cabal07/all.T | 12 ++++++++ testsuite/tests/cabal/cabal07/cabal07.stderr | 6 ++++ .../tests/cabal/{cabal05 => cabal07}/p/LICENSE | 0 testsuite/tests/cabal/cabal07/p/P.hs | 5 ++++ .../tests/cabal/{cabal06/q => cabal07/p}/Q.hs | 3 +- .../cabal/{cabal06/p-1.0 => cabal07/p}/p.cabal | 4 +-- testsuite/tests/cabal/ghcpkg07.stdout | 5 ++-- testsuite/tests/cabal/sigcabal01/Main.hs | 3 ++ testsuite/tests/cabal/sigcabal01/Makefile | 33 ++++++++++++++++++++++ .../tests/cabal/{cabal05 => sigcabal01}/Setup.hs | 0 .../tests/cabal/{cabal06 => sigcabal01}/all.T | 4 +-- .../tests/cabal/{cabal05 => sigcabal01}/p/LICENSE | 0 testsuite/tests/cabal/sigcabal01/p/Map.hsig | 19 +++++++++++++ .../sigof02/Main.hs => cabal/sigcabal01/p/P.hs} | 4 ++- .../cabal/{cabal06/p-1.0 => sigcabal01/p}/p.cabal | 1 + testsuite/tests/cabal/sigcabal01/sigcabal01.stderr | 2 ++ testsuite/tests/cabal/sigcabal01/sigcabal01.stdout | 5 ++++ utils/ghc-pkg/Main.hs | 2 ++ 25 files changed, 136 insertions(+), 14 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b19845db926632c4be7b1e52fe2aa01d26ac3af3 From git at git.haskell.org Thu Nov 27 01:24:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Nov 2014 01:24:53 +0000 (UTC) Subject: [commit: ghc] master: Change loadSrcInterface to return a list of ModIface (8c7d20d) Message-ID: <20141127012453.6E74D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8c7d20d8c7e63a1123755aae69cfa825c749e9e8/ghc >--------------------------------------------------------------- commit 8c7d20d8c7e63a1123755aae69cfa825c749e9e8 Author: Edward Z. Yang Date: Tue Nov 4 02:13:37 2014 -0800 Change loadSrcInterface to return a list of ModIface Summary: This change is in preparation to support signature imports, which may pull in multiple interface files. At the moment, the list always contains only one element, but in a later patch it may contain more. I also adjusted some error reporting code so that it didn't take the full iface, but just whether or not the iface in question was a boot module. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D436 >--------------------------------------------------------------- 8c7d20d8c7e63a1123755aae69cfa825c749e9e8 compiler/iface/LoadIface.lhs | 50 ++++++++++++++++++++++++++---- compiler/rename/RnEnv.lhs | 7 +++-- compiler/rename/RnNames.lhs | 74 +++++++++++++++++++++++++++----------------- 3 files changed, 94 insertions(+), 37 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8c7d20d8c7e63a1123755aae69cfa825c749e9e8 From git at git.haskell.org Thu Nov 27 01:24:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Nov 2014 01:24:56 +0000 (UTC) Subject: [commit: ghc] master: Inline mkModuleToPkgConfAll into mkModuleToPkgConfGeneric. (7a6fb98) Message-ID: <20141127012456.0196E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7a6fb9833f988f5f48590d3c5d4c7827b1b13fc7/ghc >--------------------------------------------------------------- commit 7a6fb9833f988f5f48590d3c5d4c7827b1b13fc7 Author: Edward Z. Yang Date: Fri Nov 7 13:44:49 2014 -0800 Inline mkModuleToPkgConfAll into mkModuleToPkgConfGeneric. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 7a6fb9833f988f5f48590d3c5d4c7827b1b13fc7 compiler/main/Packages.lhs | 54 +++++++++++++++------------------------------- 1 file changed, 17 insertions(+), 37 deletions(-) diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs index 2151902..8fe1693 100644 --- a/compiler/main/Packages.lhs +++ b/compiler/main/Packages.lhs @@ -988,38 +988,34 @@ mkPackageState dflags pkgs0 preload0 this_package = do -- ----------------------------------------------------------------------------- -- | Makes the mapping from module to package info --- | This function is generic; we instantiate it -mkModuleToPkgConfGeneric - :: forall m e. - -- Empty map, e.g. the initial state of the output - m e - -- How to create an entry in the map based on the calculated information - -> (PackageKey -> ModuleName -> PackageConfig -> ModuleOrigin -> e) - -- How to override the origin of an entry (used for renaming) - -> (e -> ModuleOrigin -> e) - -- How to incorporate a list of entries into the map - -> (m e -> [(ModuleName, e)] -> m e) - -- The proper arguments - -> DynFlags +mkModuleToPkgConfAll + :: DynFlags -> PackageConfigMap -> InstalledPackageIdMap -> VisibilityMap - -> m e -mkModuleToPkgConfGeneric emptyMap sing setOrigins addListTo - dflags pkg_db ipid_map vis_map = + -> ModuleToPkgConfAll +mkModuleToPkgConfAll dflags pkg_db ipid_map vis_map = foldl' extend_modmap emptyMap (eltsUFM pkg_db) where + emptyMap = Map.empty + sing pk m _ = Map.singleton (mkModule pk m) + addListTo = foldl' merge + merge m (k, v) = Map.insertWith (Map.unionWith mappend) k v m + setOrigins m os = fmap (const os) m extend_modmap modmap pkg = addListTo modmap theBindings where - theBindings :: [(ModuleName, e)] + theBindings :: [(ModuleName, Map Module ModuleOrigin)] theBindings | Just (b,rns,_) <- lookupUFM vis_map (packageConfigId pkg) = newBindings b rns | otherwise = newBindings False [] - newBindings :: Bool -> [(ModuleName, ModuleName)] -> [(ModuleName, e)] + newBindings :: Bool + -> [(ModuleName, ModuleName)] + -> [(ModuleName, Map Module ModuleOrigin)] newBindings e rns = es e ++ hiddens ++ map rnBinding rns - rnBinding :: (ModuleName, ModuleName) -> (ModuleName, e) + rnBinding :: (ModuleName, ModuleName) + -> (ModuleName, Map Module ModuleOrigin) rnBinding (orig, new) = (new, setOrigins origEntry fromFlag) where origEntry = case lookupUFM esmap orig of Just r -> r @@ -1027,7 +1023,7 @@ mkModuleToPkgConfGeneric emptyMap sing setOrigins addListTo (text "package flag: could not find module name" <+> ppr orig <+> text "in package" <+> ppr pk))) - es :: Bool -> [(ModuleName, e)] + es :: Bool -> [(ModuleName, Map Module ModuleOrigin)] es e = do -- TODO: signature support ExposedModule m exposedReexport _exposedSignature <- exposed_mods @@ -1040,7 +1036,7 @@ mkModuleToPkgConfGeneric emptyMap sing setOrigins addListTo in (pk', m', pkg', fromReexportedModules e pkg') return (m, sing pk' m' pkg' origin') - esmap :: UniqFM e + esmap :: UniqFM (Map Module ModuleOrigin) esmap = listToUFM (es False) -- parameter here doesn't matter, orig will -- be overwritten @@ -1052,22 +1048,6 @@ mkModuleToPkgConfGeneric emptyMap sing setOrigins addListTo exposed_mods = exposedModules pkg hidden_mods = hiddenModules pkg --- | This is a slow and complete map, which includes information about --- everything, including hidden modules -mkModuleToPkgConfAll - :: DynFlags - -> PackageConfigMap - -> InstalledPackageIdMap - -> VisibilityMap - -> ModuleToPkgConfAll -mkModuleToPkgConfAll = - mkModuleToPkgConfGeneric emptyMap sing setOrigins addListTo - where emptyMap = Map.empty - sing pk m _ = Map.singleton (mkModule pk m) - addListTo = foldl' merge - merge m (k, v) = Map.insertWith (Map.unionWith mappend) k v m - setOrigins m os = fmap (const os) m - -- ----------------------------------------------------------------------------- -- Extracting information from the packages in scope From git at git.haskell.org Thu Nov 27 11:23:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Nov 2014 11:23:31 +0000 (UTC) Subject: [commit: ghc] master: Don't require PatternSynonyms language extension to just use pattern synonyms (see #9838) (d8c437b) Message-ID: <20141127112331.BF2C83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d8c437b37436e150986a7607f574ac2c3a604f40/ghc >--------------------------------------------------------------- commit d8c437b37436e150986a7607f574ac2c3a604f40 Author: Dr. ERDI Gergo Date: Thu Nov 27 19:21:04 2014 +0800 Don't require PatternSynonyms language extension to just use pattern synonyms (see #9838) >--------------------------------------------------------------- d8c437b37436e150986a7607f574ac2c3a604f40 compiler/typecheck/TcPat.lhs | 6 ------ docs/users_guide/glasgow_exts.xml | 4 ++-- .../patsyn/{should_fail/T8961a.hs => should_compile/ImpExp_Exp.hs} | 2 +- .../patsyn/{should_fail/T8961.hs => should_compile/ImpExp_Imp.hs} | 2 +- testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_fail/T8961.stderr | 7 ------- testsuite/tests/patsyn/should_fail/all.T | 1 - 7 files changed, 5 insertions(+), 18 deletions(-) diff --git a/compiler/typecheck/TcPat.lhs b/compiler/typecheck/TcPat.lhs index b7f8d2e..de60fcb 100644 --- a/compiler/typecheck/TcPat.lhs +++ b/compiler/typecheck/TcPat.lhs @@ -828,12 +828,6 @@ tcPatSynPat penv (L con_span _) pat_syn pat_ty arg_pats thing_inside ; prov_dicts' <- newEvVars prov_theta' - -- Using a pattern synonym requires the PatternSynonyms - -- language flag to keep consistent with #2905 - ; patsyns_on <- xoptM Opt_PatternSynonyms - ; checkTc patsyns_on - (ptext (sLit "A pattern match on a pattern synonym requires PatternSynonyms")) - ; let skol_info = case pe_ctxt penv of LamPat mc -> PatSkol (PatSynCon pat_syn) mc LetPat {} -> UnkSkol -- Doesn't matter diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 3d9e45c..5ed99ba 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -877,8 +877,8 @@ y) will not be coalesced. Pattern synonyms are enabled by the flag --XPatternSynonyms, which is required for both -defining them and using them. More information +-XPatternSynonyms, which is required for defining +them, but not for using them. More information and examples of view patterns can be found on the Wiki page. diff --git a/testsuite/tests/patsyn/should_fail/T8961a.hs b/testsuite/tests/patsyn/should_compile/ImpExp_Exp.hs similarity index 58% rename from testsuite/tests/patsyn/should_fail/T8961a.hs rename to testsuite/tests/patsyn/should_compile/ImpExp_Exp.hs index f741d7b..9d18ca3 100644 --- a/testsuite/tests/patsyn/should_fail/T8961a.hs +++ b/testsuite/tests/patsyn/should_compile/ImpExp_Exp.hs @@ -1,4 +1,4 @@ {-# LANGUAGE PatternSynonyms #-} -module T8961a (pattern Single) where +module ImpExp_Exp (pattern Single) where pattern Single x <- [x] diff --git a/testsuite/tests/patsyn/should_fail/T8961.hs b/testsuite/tests/patsyn/should_compile/ImpExp_Imp.hs similarity index 84% rename from testsuite/tests/patsyn/should_fail/T8961.hs rename to testsuite/tests/patsyn/should_compile/ImpExp_Imp.hs index 087c399..a2450e2 100644 --- a/testsuite/tests/patsyn/should_fail/T8961.hs +++ b/testsuite/tests/patsyn/should_compile/ImpExp_Imp.hs @@ -1,6 +1,6 @@ module ShouldFail where -import T8961a +import ImpExp_Exp single :: [a] -> Maybe a single (Single x) = Just x diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index 6a51bf5..c8a88c3 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -18,3 +18,4 @@ test('T8584-3', normal, compile, ['']) test('T8968-1', normal, compile, ['']) test('T8968-2', normal, compile, ['']) test('T8968-3', normal, compile, ['']) +test('ImpExp_Imp', [extra_clean(['ImpExp_Exp.hi', 'ImpExp_Exp.o'])], multimod_compile, ['ImpExp_Imp', '-v0']) diff --git a/testsuite/tests/patsyn/should_fail/T8961.stderr b/testsuite/tests/patsyn/should_fail/T8961.stderr deleted file mode 100644 index a58ee38..0000000 --- a/testsuite/tests/patsyn/should_fail/T8961.stderr +++ /dev/null @@ -1,7 +0,0 @@ -[1 of 2] Compiling T8961a ( T8961a.hs, T8961a.o ) -[2 of 2] Compiling ShouldFail ( T8961.hs, T8961.o ) - -T8961.hs:6:9: - A pattern match on a pattern synonym requires PatternSynonyms - In the pattern: Single x - In an equation for ?single?: single (Single x) = Just x diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index b38776e..de5d6db 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -1,7 +1,6 @@ test('mono', normal, compile_fail, ['']) test('unidir', normal, compile_fail, ['']) test('local', normal, compile_fail, ['']) -test('T8961', normal, multimod_compile_fail, ['T8961','']) test('as-pattern', normal, compile_fail, ['']) test('T9161-1', normal, compile_fail, ['']) test('T9161-2', normal, compile_fail, ['']) From git at git.haskell.org Thu Nov 27 14:24:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Nov 2014 14:24:37 +0000 (UTC) Subject: [commit: ghc] master: Resume reporting incomplete pattern matches for record updates (a67ebbe) Message-ID: <20141127142437.21E293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a67ebbecfb10c91bb2793cb2f7d91f25aa23e493/ghc >--------------------------------------------------------------- commit a67ebbecfb10c91bb2793cb2f7d91f25aa23e493 Author: Simon Peyton Jones Date: Thu Nov 27 14:18:35 2014 +0000 Resume reporting incomplete pattern matches for record updates They were being inadvertently suppressed, even if you said -fwarn-incomplete-record-updates See Trac #5728 >--------------------------------------------------------------- a67ebbecfb10c91bb2793cb2f7d91f25aa23e493 compiler/deSugar/DsExpr.lhs | 5 ++++- compiler/deSugar/Match.lhs | 2 +- 2 files changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/deSugar/DsExpr.lhs b/compiler/deSugar/DsExpr.lhs index 03544bb..c9134c9 100644 --- a/compiler/deSugar/DsExpr.lhs +++ b/compiler/deSugar/DsExpr.lhs @@ -490,7 +490,10 @@ dsExpr expr@(RecordUpd record_expr (HsRecFields { rec_flds = fields }) -- constructor aguments. ; alts <- mapM (mk_alt upd_fld_env) cons_to_upd ; ([discrim_var], matching_code) - <- matchWrapper RecUpd (MG { mg_alts = alts, mg_arg_tys = [in_ty], mg_res_ty = out_ty, mg_origin = Generated }) + <- matchWrapper RecUpd (MG { mg_alts = alts, mg_arg_tys = [in_ty] + , mg_res_ty = out_ty, mg_origin = FromSource }) + -- FromSource is not strictly right, but we + -- want incomplete pattern-match warnings ; return (add_field_binds field_binds' $ bindNonRec discrim_var record_expr' matching_code) } diff --git a/compiler/deSugar/Match.lhs b/compiler/deSugar/Match.lhs index 8bc8a11..3bbb0ec 100644 --- a/compiler/deSugar/Match.lhs +++ b/compiler/deSugar/Match.lhs @@ -79,7 +79,7 @@ matchCheck_really dflags ctx@(DsMatchContext hs_ctx _) vars ty qs ; match vars ty qs } where (pats, eqns_shadow) = check qs - incomplete = incomplete_flag hs_ctx && (notNull pats) + incomplete = incomplete_flag hs_ctx && notNull pats shadow = wopt Opt_WarnOverlappingPatterns dflags && notNull eqns_shadow From git at git.haskell.org Thu Nov 27 14:24:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Nov 2014 14:24:40 +0000 (UTC) Subject: [commit: ghc] master: Don't require ConstraintKinds at usage sites (Trac #9838) (417b874) Message-ID: <20141127142440.4A8683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/417b8746b9d3759a102160c4db882b18ac658a0e/ghc >--------------------------------------------------------------- commit 417b8746b9d3759a102160c4db882b18ac658a0e Author: Simon Peyton Jones Date: Thu Nov 27 14:25:04 2014 +0000 Don't require ConstraintKinds at usage sites (Trac #9838) >--------------------------------------------------------------- 417b8746b9d3759a102160c4db882b18ac658a0e compiler/hsSyn/PlaceHolder.hs | 1 + compiler/typecheck/TcValidity.lhs | 171 +++++++++++++++++++++--------------- testsuite/tests/polykinds/T9838.hs | 9 ++ testsuite/tests/polykinds/T9838a.hs | 8 ++ testsuite/tests/polykinds/all.T | 1 + 5 files changed, 119 insertions(+), 71 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 417b8746b9d3759a102160c4db882b18ac658a0e From git at git.haskell.org Thu Nov 27 14:32:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Nov 2014 14:32:28 +0000 (UTC) Subject: [commit: ghc] master: Trac #6022 is actually fine now (4721167) Message-ID: <20141127143228.794763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4721167a0118e4c8bc6c8266c3357a8a2ac4f4e2/ghc >--------------------------------------------------------------- commit 4721167a0118e4c8bc6c8266c3357a8a2ac4f4e2 Author: Simon Peyton Jones Date: Thu Nov 27 14:32:38 2014 +0000 Trac #6022 is actually fine now >--------------------------------------------------------------- 4721167a0118e4c8bc6c8266c3357a8a2ac4f4e2 testsuite/tests/typecheck/should_fail/T6022.stderr | 10 +++++----- testsuite/tests/typecheck/should_fail/all.T | 2 +- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/testsuite/tests/typecheck/should_fail/T6022.stderr b/testsuite/tests/typecheck/should_fail/T6022.stderr index dffeccf..4408910 100644 --- a/testsuite/tests/typecheck/should_fail/T6022.stderr +++ b/testsuite/tests/typecheck/should_fail/T6022.stderr @@ -1,6 +1,6 @@ -T6022.hs:3:9: - No instance for (Eq ([a] -> a)) arising from a use of `==' - Possible fix: add an instance declaration for (Eq ([a] -> a)) - In the expression: x == head - In an equation for `f': f x = x == head +T6022.hs:3:1: + Non type-variable argument in the constraint: Eq ([a] -> a) + (Use FlexibleContexts to permit this) + When checking that ?f? has the inferred type + f :: forall a. Eq ([a] -> a) => ([a] -> a) -> Bool diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 05f77bb..96c1908 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -274,7 +274,7 @@ test('T5684', normal, compile_fail, ['']) test('T5858', normal, compile_fail, ['']) test('T5957', normal, compile_fail, ['']) test('T6001', normal, compile_fail, ['']) -test('T6022', expect_broken(6022), compile_fail, ['']) +test('T6022', normal, compile_fail, ['']) test('T5853', normal, compile_fail, ['']) test('T6078', normal, compile_fail, ['']) test('FDsFromGivens', normal, compile_fail, ['']) From git at git.haskell.org Thu Nov 27 15:43:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Nov 2014 15:43:36 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #7243 (b61091d) Message-ID: <20141127154336.621093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b61091d3b042305ce21bb00b28a81f903b522394/ghc >--------------------------------------------------------------- commit b61091d3b042305ce21bb00b28a81f903b522394 Author: Simon Peyton Jones Date: Thu Nov 27 15:18:30 2014 +0000 Test Trac #7243 >--------------------------------------------------------------- b61091d3b042305ce21bb00b28a81f903b522394 testsuite/tests/ffi/should_fail/T7243.hs | 4 ++++ testsuite/tests/ffi/should_fail/T7243.stderr | 5 +++++ testsuite/tests/ffi/should_fail/all.T | 2 ++ 3 files changed, 11 insertions(+) diff --git a/testsuite/tests/ffi/should_fail/T7243.hs b/testsuite/tests/ffi/should_fail/T7243.hs new file mode 100644 index 0000000..c9714e4 --- /dev/null +++ b/testsuite/tests/ffi/should_fail/T7243.hs @@ -0,0 +1,4 @@ +module T7243 where + +import Foreign.Ptr +foreign import ccall "wrapper" foo :: IO (FunPtr ()) diff --git a/testsuite/tests/ffi/should_fail/T7243.stderr b/testsuite/tests/ffi/should_fail/T7243.stderr new file mode 100644 index 0000000..727ae0f --- /dev/null +++ b/testsuite/tests/ffi/should_fail/T7243.stderr @@ -0,0 +1,5 @@ + +T7243.hs:4:1: + Unacceptable type in foreign declaration: One argument expected + When checking declaration: + foreign import ccall safe "wrapper" foo :: IO (FunPtr ()) diff --git a/testsuite/tests/ffi/should_fail/all.T b/testsuite/tests/ffi/should_fail/all.T index d1cba3c..78b7007 100644 --- a/testsuite/tests/ffi/should_fail/all.T +++ b/testsuite/tests/ffi/should_fail/all.T @@ -16,3 +16,5 @@ test('ccall_value', normal, compile_fail, ['']) test('capi_value_function', normal, compile_fail, ['']) test('T5664', normal, compile_fail, ['-v0']) test('T7506', normal, compile_fail, ['']) +test('T7243', normal, compile_fail, ['']) + From git at git.haskell.org Thu Nov 27 15:43:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Nov 2014 15:43:39 +0000 (UTC) Subject: [commit: ghc] master: Get the right fixity-env in standalone deriving (Trac #9830) (01f03cb) Message-ID: <20141127154339.AB32A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/01f03cb30426fad1b848051fa142c04c8816a80c/ghc >--------------------------------------------------------------- commit 01f03cb30426fad1b848051fa142c04c8816a80c Author: Simon Peyton Jones Date: Thu Nov 27 15:44:10 2014 +0000 Get the right fixity-env in standalone deriving (Trac #9830) >--------------------------------------------------------------- 01f03cb30426fad1b848051fa142c04c8816a80c compiler/typecheck/TcDeriv.lhs | 25 +++++++++++++++++++++--- compiler/typecheck/TcGenDeriv.lhs | 13 ++++++------ testsuite/tests/deriving/should_run/T9830.hs | 13 ++++++++++++ testsuite/tests/deriving/should_run/T9830.stdout | 4 ++++ testsuite/tests/deriving/should_run/T9830a.hs | 4 ++++ testsuite/tests/deriving/should_run/all.T | 2 +- 6 files changed, 50 insertions(+), 11 deletions(-) diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index 161bb77..76b8423 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -30,6 +30,8 @@ import FamInstEnv import TcHsType import TcMType import TcSimplify +import LoadIface( loadInterfaceForName ) +import Module( getModule, isInteractiveModule ) import RnNames( extendGlobalRdrEnvRn ) import RnBinds @@ -2091,9 +2093,26 @@ genDerivStuff loc clas dfun_name tycon comaux_maybe return (binds, unitBag (DerivFamInst faminst)) | otherwise -- Non-monadic generators - = do dflags <- getDynFlags - fix_env <- getFixityEnv - return (genDerivedBinds dflags fix_env clas loc tycon) + = do { dflags <- getDynFlags + ; fix_env <- getDataConFixityFun tycon + ; return (genDerivedBinds dflags fix_env clas loc tycon) } + +getDataConFixityFun :: TyCon -> TcM (Name -> Fixity) +-- If the TyCon is locally defined, we want the local fixity env; +-- but if it is imported (which happens for standalone deriving) +-- we need to get the fixity env from the interface file +-- c.f. RnEnv.lookupFixity, and Trac #9830 +getDataConFixityFun tc + = do { this_mod <- getModule + ; if nameIsLocalOrFrom this_mod name || isInteractiveModule (nameModule name) + then do { fix_env <- getFixityEnv + ; return (lookupFixity fix_env) } + else do { iface <- loadInterfaceForName doc name + -- Should already be loaded! + ; return (mi_fix_fn iface . nameOccName) } } + where + name = tyConName tc + doc = ptext (sLit "Data con fixities for") <+> ppr name \end{code} Note [Bindings for Generalised Newtype Deriving] diff --git a/compiler/typecheck/TcGenDeriv.lhs b/compiler/typecheck/TcGenDeriv.lhs index f911d16..dda2cf8 100644 --- a/compiler/typecheck/TcGenDeriv.lhs +++ b/compiler/typecheck/TcGenDeriv.lhs @@ -37,7 +37,6 @@ import DataCon import Name import DynFlags -import HscTypes import PrelInfo import FamInstEnv( FamInst ) import MkCore ( eRROR_ID ) @@ -102,7 +101,7 @@ data DerivStuff -- Please add this auxiliary stuff %************************************************************************ \begin{code} -genDerivedBinds :: DynFlags -> FixityEnv -> Class -> SrcSpan -> TyCon +genDerivedBinds :: DynFlags -> (Name -> Fixity) -> Class -> SrcSpan -> TyCon -> (LHsBinds RdrName, BagDerivStuff) genDerivedBinds dflags fix_env clas loc tycon | Just gen_fn <- assocMaybe gen_list (getUnique clas) @@ -951,7 +950,7 @@ These instances are also useful for Read (Either Int Emp), where we want to be able to parse (Left 3) just fine. \begin{code} -gen_Read_binds :: FixityEnv -> SrcSpan -> TyCon -> (LHsBinds RdrName, BagDerivStuff) +gen_Read_binds :: (Name -> Fixity) -> SrcSpan -> TyCon -> (LHsBinds RdrName, BagDerivStuff) gen_Read_binds get_fixity loc tycon = (listToBag [read_prec, default_readlist, default_readlistprec], emptyBag) @@ -1120,7 +1119,7 @@ Example -- the most tightly-binding operator \begin{code} -gen_Show_binds :: FixityEnv -> SrcSpan -> TyCon -> (LHsBinds RdrName, BagDerivStuff) +gen_Show_binds :: (Name -> Fixity) -> SrcSpan -> TyCon -> (LHsBinds RdrName, BagDerivStuff) gen_Show_binds get_fixity loc tycon = (listToBag [shows_prec, show_list], emptyBag) @@ -1216,7 +1215,7 @@ mk_showString_app str = nlHsApp (nlHsVar showString_RDR) (nlHsLit (mkHsString st \end{code} \begin{code} -getPrec :: Bool -> FixityEnv -> Name -> Integer +getPrec :: Bool -> (Name -> Fixity) -> Name -> Integer getPrec is_infix get_fixity nm | not is_infix = appPrecedence | otherwise = getPrecedence get_fixity nm @@ -1226,9 +1225,9 @@ appPrecedence = fromIntegral maxPrecedence + 1 -- One more than the precedence of the most -- tightly-binding operator -getPrecedence :: FixityEnv -> Name -> Integer +getPrecedence :: (Name -> Fixity) -> Name -> Integer getPrecedence get_fixity nm - = case lookupFixity get_fixity nm of + = case get_fixity nm of Fixity x _assoc -> fromIntegral x -- NB: the Report says that associativity is not taken -- into account for either Read or Show; hence we diff --git a/testsuite/tests/deriving/should_run/T9830.hs b/testsuite/tests/deriving/should_run/T9830.hs new file mode 100644 index 0000000..353decc --- /dev/null +++ b/testsuite/tests/deriving/should_run/T9830.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE StandaloneDeriving #-} +module Main where + +import T9830a + +deriving instance (Show a, Show b) => Show (ADT a b) + +main :: IO () +main = do + putStrLn $ "Prec 6: " ++ showsPrec 6 ("test" :?: "show") "" + putStrLn $ "Prec 7: " ++ showsPrec 7 ("test" :?: "show") "" + putStrLn $ "Prec 9: " ++ showsPrec 9 ("test" :?: "show") "" + putStrLn $ "Prec 10: " ++ showsPrec 10 ("test" :?: "show") "" diff --git a/testsuite/tests/deriving/should_run/T9830.stdout b/testsuite/tests/deriving/should_run/T9830.stdout new file mode 100644 index 0000000..7d9bbe5 --- /dev/null +++ b/testsuite/tests/deriving/should_run/T9830.stdout @@ -0,0 +1,4 @@ +Prec 6: "test" :?: "show" +Prec 7: ("test" :?: "show") +Prec 9: ("test" :?: "show") +Prec 10: ("test" :?: "show") diff --git a/testsuite/tests/deriving/should_run/T9830a.hs b/testsuite/tests/deriving/should_run/T9830a.hs new file mode 100644 index 0000000..1b2ef17 --- /dev/null +++ b/testsuite/tests/deriving/should_run/T9830a.hs @@ -0,0 +1,4 @@ +module T9830a where + +infixr 6 :?: +data ADT a b = a :?: b deriving (Eq, Ord, Read) diff --git a/testsuite/tests/deriving/should_run/all.T b/testsuite/tests/deriving/should_run/all.T index 21c1962..58b4903 100644 --- a/testsuite/tests/deriving/should_run/all.T +++ b/testsuite/tests/deriving/should_run/all.T @@ -37,4 +37,4 @@ test('T5712', normal, compile_and_run, ['']) test('T7931', normal, compile_and_run, ['']) test('T8280', normal, compile_and_run, ['']) test('T9576', exit_code(1), compile_and_run, ['']) - +test('T9830', normal, multimod_compile_and_run, ['T9830','-v0']) From git at git.haskell.org Thu Nov 27 20:59:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Nov 2014 20:59:40 +0000 (UTC) Subject: [commit: ghc] master: Embed Git commit id into `ghc --info` output (73e5e2f) Message-ID: <20141127205940.96D253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/73e5e2f8bade2d8b2b1ecae958fe12d0b24591ef/ghc >--------------------------------------------------------------- commit 73e5e2f8bade2d8b2b1ecae958fe12d0b24591ef Author: Herbert Valerio Riedel Date: Thu Nov 27 10:50:51 2014 +0100 Embed Git commit id into `ghc --info` output Since we switched to a Git submodule based GHC Git repo, `ghc.git`'s commit id uniquely identifies the state of the GHC source-tree. So having that information embedded into the `ghc` executable provides valuable information to track accurately (especially when created by buildbots) from which source-tree-state a given `ghc` snapshot (distribution) was generated. So this commit adds a new field `"Project Git commit id"` to the `ghc --info` meta-data containing the `./configure`-time Git commit id as reported by `git rev-parse HEAD`. This field can also be queried with `ghc --print-project-git-commit-id`. For source distributions, the file `GIT_COMMIT_ID` is created (with some sanity checking to detect stale commit ids, as that would render this information rather useless) Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D528 >--------------------------------------------------------------- 73e5e2f8bade2d8b2b1ecae958fe12d0b24591ef .gitignore | 1 + aclocal.m4 | 18 ++++++++++++++++++ compiler/ghc.mk | 2 ++ compiler/main/DynFlags.hs | 1 + configure.ac | 1 + ghc.mk | 18 ++++++++++++++++-- ghc/Main.hs | 1 + mk/project.mk.in | 1 + 8 files changed, 41 insertions(+), 2 deletions(-) diff --git a/.gitignore b/.gitignore index 5a58ed2..7d53060 100644 --- a/.gitignore +++ b/.gitignore @@ -153,3 +153,4 @@ _darcs/ .tm_properties VERSION +GIT_COMMIT_ID diff --git a/aclocal.m4 b/aclocal.m4 index b41bf41..2aa55d7 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1581,11 +1581,29 @@ if test "$RELEASE" = "NO"; then dnl less likely to go wrong. PACKAGE_VERSION=${PACKAGE_VERSION}.`date +%Y%m%d` fi + + AC_MSG_CHECKING([for GHC Git commit id]) + if test -d .git; then + git_commit_id=`git rev-parse HEAD` + if test -n "$git_commit_id" 2>&1 >/dev/null; then true; else + AC_MSG_ERROR([failed to detect revision: check that git is in your path]) + fi + PACKAGE_GIT_COMMIT_ID=$git_commit_id + AC_MSG_RESULT(inferred $PACKAGE_GIT_COMMIT_ID) + elif test -f GIT_COMMIT_ID; then + PACKAGE_GIT_COMMIT_ID=`cat GIT_COMMIT_ID` + AC_MSG_RESULT(given $PACKAGE_GIT_COMMIT_ID) + else + AC_MSG_WARN([cannot determine snapshot revision: no .git directory and no 'GIT_COMMIT_ID' file]) + PACKAGE_GIT_COMMIT_ID="0000000000000000000000000000000000000000" + fi + fi # Some renamings AC_SUBST([ProjectName], [$PACKAGE_NAME]) AC_SUBST([ProjectVersion], [$PACKAGE_VERSION]) +AC_SUBST([ProjectGitCommitId], [$PACKAGE_GIT_COMMIT_ID]) # Split PACKAGE_VERSION into (possibly empty) parts VERSION_MAJOR=`echo $PACKAGE_VERSION | sed 's/^\(@<:@^.@:>@*\)\(\.\{0,1\}\(.*\)\)$/\1'/` diff --git a/compiler/ghc.mk b/compiler/ghc.mk index ffa91a5..2912aab 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -67,6 +67,8 @@ compiler/stage%/build/Config.hs : mk/config.mk mk/project.mk | $$(dir $$@)/. @echo >> $@ @echo 'cProjectName :: String' >> $@ @echo 'cProjectName = "$(ProjectName)"' >> $@ + @echo 'cProjectGitCommitId :: String' >> $@ + @echo 'cProjectGitCommitId = "$(ProjectGitCommitId)"' >> $@ @echo 'cProjectVersion :: String' >> $@ @echo 'cProjectVersion = "$(ProjectVersion)"' >> $@ @echo 'cProjectVersionInt :: String' >> $@ diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index d6f620f..11e5c32 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -3781,6 +3781,7 @@ compilerInfo dflags -- key) : rawSettings dflags ++ [("Project version", cProjectVersion), + ("Project Git commit id", cProjectGitCommitId), ("Booter version", cBooterVersion), ("Stage", cStage), ("Build platform", cBuildPlatformString), diff --git a/configure.ac b/configure.ac index ca9f220..97fdc2f 100644 --- a/configure.ac +++ b/configure.ac @@ -1005,6 +1005,7 @@ echo [" Configure completed successfully. Building GHC version : $ProjectVersion + Git commit id : $ProjectGitCommitId Build platform : $BuildPlatform Host platform : $HostPlatform diff --git a/ghc.mk b/ghc.mk index a93628a..c47104d 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1109,13 +1109,27 @@ SRC_DIST_GHC_DIRS = mk rules docs distrib bindisttest libffi includes \ SRC_DIST_GHC_FILES += \ configure.ac config.guess config.sub configure \ aclocal.m4 README ANNOUNCE HACKING LICENSE Makefile install-sh \ - settings.in VERSION \ + settings.in VERSION GIT_COMMIT_ID \ boot packages ghc.mk VERSION : echo $(ProjectVersion) >VERSION -sdist : VERSION +.PHONY: GIT_COMMIT_ID +GIT_COMMIT_ID: + @if test -d .git && test "`git rev-parse HEAD`" != "$(ProjectGitCommitId)"; then \ + echo "******************************************************************************"; \ + echo "Stale ProjectGitCommitId (=$(ProjectGitCommitId)) detected!"; \ + echo "'git rev-parse HEAD' says: `git rev-parse HEAD`"; \ + echo "Please re-run './configure' before creating source-distribution"; \ + echo "******************************************************************************"; \ + exit 1; \ + fi + @if test -f $@ && test "`cat $@`" = "$(ProjectGitCommitId)"; \ + then echo "$@ needs no update"; \ + else echo "update $@ ($(ProjectGitCommitId))"; echo -n "$(ProjectGitCommitId)" > $@; fi + +sdist : VERSION GIT_COMMIT_ID # Use: # $(call sdist_ghc_file,compiler,stage2,cmm,Foo/Bar,CmmLex,x) diff --git a/ghc/Main.hs b/ghc/Main.hs index d706914..f0539df 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -541,6 +541,7 @@ mode_flags = ] ++ [ defFlag k' (PassFlag (setMode (printSetting k))) | k <- ["Project version", + "Project Git commit id", "Booter version", "Stage", "Build platform", diff --git a/mk/project.mk.in b/mk/project.mk.in index 129b540..a5fe210 100644 --- a/mk/project.mk.in +++ b/mk/project.mk.in @@ -31,6 +31,7 @@ ProjectVersionInt = @ProjectVersionInt@ ProjectPatchLevel = @ProjectPatchLevel@ ProjectPatchLevel1 = @ProjectPatchLevel1@ ProjectPatchLevel2 = @ProjectPatchLevel2@ +ProjectGitCommitId = @ProjectGitCommitId@ ################################################################################ # From git at git.haskell.org Thu Nov 27 22:45:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Nov 2014 22:45:13 +0000 (UTC) Subject: [commit: ghc] master: compiler: add new modules pulling in FunFlags (65cae36) Message-ID: <20141127224513.123C83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/65cae368e2e5fdc537f616ff98a5cffc2e6071e3/ghc >--------------------------------------------------------------- commit 65cae368e2e5fdc537f616ff98a5cffc2e6071e3 Author: Sergei Trofimovich Date: Thu Nov 27 22:08:32 2014 +0000 compiler: add new modules pulling in FunFlags And also sync type signature under '#ifndef GHCI' Tested by setting GhcWithInterpreter = NO Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 65cae368e2e5fdc537f616ff98a5cffc2e6071e3 compiler/ghc.mk | 7 +++---- compiler/rename/RnSplice.lhs | 2 +- 2 files changed, 4 insertions(+), 5 deletions(-) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index 2912aab..640bf75 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -472,6 +472,7 @@ compiler_stage3_SplitObjs = NO compiler_stage2_dll0_START_MODULE = DynFlags compiler_stage2_dll0_MODULES = \ Annotations \ + ApiAnnotation \ Avail \ Bag \ BasicTypes \ @@ -498,6 +499,7 @@ compiler_stage2_dll0_MODULES = \ CoreUnfold \ CoreUtils \ CostCentre \ + Ctype \ DataCon \ Demand \ Digraph \ @@ -539,7 +541,7 @@ compiler_stage2_dll0_MODULES = \ InstEnv \ Kind \ Lexeme \ - ApiAnnotation \ + Lexer \ ListSetOps \ Literal \ LoadIface \ @@ -602,7 +604,6 @@ ifeq "$(GhcWithInterpreter)" "YES" # These files are reacheable from DynFlags # only by GHCi-enabled code (see #9552) compiler_stage2_dll0_MODULES += \ - ApiAnnotation \ Bitmap \ BlockId \ ByteCodeAsm \ @@ -625,13 +626,11 @@ compiler_stage2_dll0_MODULES += \ CodeGen.Platform.SPARC \ CodeGen.Platform.X86 \ CodeGen.Platform.X86_64 \ - Ctype \ FastBool \ Hoopl \ Hoopl.Dataflow \ InteractiveEvalTypes \ MkGraph \ - Lexer \ PprCmm \ PprCmmDecl \ PprCmmExpr \ diff --git a/compiler/rename/RnSplice.lhs b/compiler/rename/RnSplice.lhs index 8918e39..b0c81b0 100644 --- a/compiler/rename/RnSplice.lhs +++ b/compiler/rename/RnSplice.lhs @@ -54,7 +54,7 @@ rnSpliceType e _ = failTH e "Template Haskell type splice" rnSpliceExpr :: Bool -> HsSplice RdrName -> RnM (HsExpr Name, FreeVars) rnSpliceExpr _ e = failTH e "Template Haskell splice" -rnSplicePat :: HsSplice RdrName -> RnM (Pat Name, FreeVars) +rnSplicePat :: HsSplice RdrName -> RnM (Either (Pat RdrName) (Pat Name), FreeVars) rnSplicePat e = failTH e "Template Haskell pattern splice" rnSpliceDecl :: SpliceDecl RdrName -> RnM (SpliceDecl Name, FreeVars) From git at git.haskell.org Fri Nov 28 10:03:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Nov 2014 10:03:32 +0000 (UTC) Subject: [commit: ghc] master: Improve VERSION/GIT_COMMIT_ID handling for sdist (7dd4c12) Message-ID: <20141128100332.54AC23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7dd4c12c608ba7b42e6e453f4db825655716f01d/ghc >--------------------------------------------------------------- commit 7dd4c12c608ba7b42e6e453f4db825655716f01d Author: Herbert Valerio Riedel Date: Fri Nov 28 10:57:18 2014 +0100 Improve VERSION/GIT_COMMIT_ID handling for sdist This makes `VERSION` updating a bit more robust (the file gets only updated if its content would actually change), as well as moving the dependency of `VERSION` and `GIT_COMMIT_ID` to the `sdist-ghc-prep` target, as that's where it's actually needed. This fixes the specialised target `make sdist-ghc` not properly creating/updating the `VERSION` and `GIT_COMMIT_ID` files before creating the ghc source-dist tarball, as well as avoiding stale `VERSION` files. >--------------------------------------------------------------- 7dd4c12c608ba7b42e6e453f4db825655716f01d ghc.mk | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/ghc.mk b/ghc.mk index c47104d..2c9c635 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1112,8 +1112,11 @@ SRC_DIST_GHC_FILES += \ settings.in VERSION GIT_COMMIT_ID \ boot packages ghc.mk -VERSION : - echo $(ProjectVersion) >VERSION +.PHONY: VERSION +VERSION: + @if test -f $@ && test "`cat $@`" = "$(ProjectVersion)"; \ + then echo "$@ needs no update"; \ + else echo "update $@ ($(ProjectVersion))"; echo "$(ProjectVersion)" > $@; fi .PHONY: GIT_COMMIT_ID GIT_COMMIT_ID: @@ -1129,7 +1132,7 @@ GIT_COMMIT_ID: then echo "$@ needs no update"; \ else echo "update $@ ($(ProjectGitCommitId))"; echo -n "$(ProjectGitCommitId)" > $@; fi -sdist : VERSION GIT_COMMIT_ID +sdist-ghc-prep : VERSION GIT_COMMIT_ID # Use: # $(call sdist_ghc_file,compiler,stage2,cmm,Foo/Bar,CmmLex,x) From git at git.haskell.org Fri Nov 28 13:25:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Nov 2014 13:25:49 +0000 (UTC) Subject: [commit: ghc] master: Don't discard a bang on a newtype pattern (Trac #9844) (227a566) Message-ID: <20141128132549.CF3273A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/227a566851f19f5a720c4a86fdb1ff99117325c6/ghc >--------------------------------------------------------------- commit 227a566851f19f5a720c4a86fdb1ff99117325c6 Author: Simon Peyton Jones Date: Fri Nov 28 11:28:15 2014 +0000 Don't discard a bang on a newtype pattern (Trac #9844) We were wrongly simply dropping the bang, in tidy_bang_pat. >--------------------------------------------------------------- 227a566851f19f5a720c4a86fdb1ff99117325c6 compiler/deSugar/Match.lhs | 65 ++++++++++++++++++---- compiler/hsSyn/HsDecls.lhs | 3 +- compiler/hsSyn/HsPat.lhs | 2 +- testsuite/tests/deSugar/should_run/T9844.hs | 17 ++++++ testsuite/tests/deSugar/should_run/T9844.stderr | 2 + .../should_run/T9844.stdout} | 0 testsuite/tests/deSugar/should_run/all.T | 1 + 7 files changed, 77 insertions(+), 13 deletions(-) diff --git a/compiler/deSugar/Match.lhs b/compiler/deSugar/Match.lhs index 3bbb0ec..753c8fd 100644 --- a/compiler/deSugar/Match.lhs +++ b/compiler/deSugar/Match.lhs @@ -35,6 +35,7 @@ import PatSyn import MatchCon import MatchLit import Type +import TyCon( isNewTyCon ) import TysWiredIn import ListSetOps import SrcLoc @@ -292,9 +293,9 @@ match [] ty eqns match vars@(v:_) ty eqns -- Eqns *can* be empty = do { dflags <- getDynFlags - ; -- Tidy the first pattern, generating + -- Tidy the first pattern, generating -- auxiliary bindings if necessary - (aux_binds, tidy_eqns) <- mapAndUnzipM (tidyEqnInfo v) eqns + ; (aux_binds, tidy_eqns) <- mapAndUnzipM (tidyEqnInfo v) eqns -- Group the equations and match each group in turn ; let grouped = groupEquations dflags tidy_eqns @@ -588,13 +589,6 @@ tidy1 _ non_interesting_pat -------------------- tidy_bang_pat :: Id -> SrcSpan -> Pat Id -> DsM (DsWrapper, Pat Id) --- Discard bang around strict pattern -tidy_bang_pat v _ p@(ListPat {}) = tidy1 v p -tidy_bang_pat v _ p@(TuplePat {}) = tidy1 v p -tidy_bang_pat v _ p@(PArrPat {}) = tidy1 v p -tidy_bang_pat v _ p@(ConPatOut {}) = tidy1 v p -tidy_bang_pat v _ p@(LitPat {}) = tidy1 v p - -- Discard par/sig under a bang tidy_bang_pat v _ (ParPat (L l p)) = tidy_bang_pat v l p tidy_bang_pat v _ (SigPatOut (L l p) _) = tidy_bang_pat v l p @@ -604,15 +598,64 @@ tidy_bang_pat v _ (SigPatOut (L l p) _) = tidy_bang_pat v l p tidy_bang_pat v l (AsPat v' p) = tidy1 v (AsPat v' (L l (BangPat p))) tidy_bang_pat v l (CoPat w p t) = tidy1 v (CoPat w (BangPat (L l p)) t) +-- Discard bang around strict pattern +tidy_bang_pat v _ p@(LitPat {}) = tidy1 v p +tidy_bang_pat v _ p@(ListPat {}) = tidy1 v p +tidy_bang_pat v _ p@(TuplePat {}) = tidy1 v p +tidy_bang_pat v _ p@(PArrPat {}) = tidy1 v p + +-- Data/newtype constructors +tidy_bang_pat v l p@(ConPatOut { pat_con = L _ (RealDataCon dc), pat_args = args }) + | isNewTyCon (dataConTyCon dc) -- Newtypes: push bang inwards (Trac #9844) + = tidy1 v (p { pat_args = push_bang_into_newtype_arg l args }) + | otherwise -- Data types: discard the bang + = tidy1 v p + +------------------- -- Default case, leave the bang there: --- VarPat, LazyPat, WildPat, ViewPat, NPat, NPlusKPat +-- VarPat, +-- LazyPat, +-- WildPat, +-- ViewPat, +-- pattern synonyms (ConPatOut with PatSynCon) +-- NPat, +-- NPlusKPat +-- -- For LazyPat, remember that it's semantically like a VarPat -- i.e. !(~p) is not like ~p, or p! (Trac #8952) +-- +-- NB: SigPatIn, ConPatIn should not happen tidy_bang_pat _ l p = return (idDsWrapper, BangPat (L l p)) - -- NB: SigPatIn, ConPatIn should not happen + +------------------- +push_bang_into_newtype_arg :: SrcSpan -> HsConPatDetails Id -> HsConPatDetails Id +-- See Note [Bang patterns and newtypes] +-- We are transforming !(N p) into (N !p) +push_bang_into_newtype_arg l (PrefixCon (arg:args)) + = ASSERT( null args) + PrefixCon [L l (BangPat arg)] +push_bang_into_newtype_arg l (RecCon rf) + | HsRecFields { rec_flds = L lf fld : flds } <- rf + , HsRecField { hsRecFieldArg = arg } <- fld + = ASSERT( null flds) + RecCon (rf { rec_flds = [L lf (fld { hsRecFieldArg = L l (BangPat arg) })] }) +push_bang_into_newtype_arg _ cd + = pprPanic "push_bang_into_newtype_arg" (pprConArgs cd) \end{code} +Note [Bang patterns and newtypes] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +For the pattern !(Just pat) we can discard the bang, because +the pattern is strict anyway. But for !(N pat), where + newtype NT = N Int +we definitely can't discard the bang. Trac #9844. + +So what we do is to push the bang inwards, in the hope that it will +get discarded there. So we transform + !(N pat) into (N !pat) + + \noindent {\bf Previous @matchTwiddled@ stuff:} diff --git a/compiler/hsSyn/HsDecls.lhs b/compiler/hsSyn/HsDecls.lhs index 2cfa959..f4e5a46 100644 --- a/compiler/hsSyn/HsDecls.lhs +++ b/compiler/hsSyn/HsDecls.lhs @@ -990,7 +990,8 @@ pprConDecl (ConDecl { con_names = cons, con_explicit = expl, con_qvars = tvs pprConDecl decl@(ConDecl { con_details = InfixCon ty1 ty2, con_res = ResTyGADT {} }) = pprConDecl (decl { con_details = PrefixCon [ty1,ty2] }) -- In GADT syntax we don't allow infix constructors - -- but the renamer puts them in this form (Note [Infix GADT constructors] in RnSource) + -- so if we ever trip over one (albeit I can't see how that + -- can happen) print it like a prefix one ppr_con_names :: (OutputableBndr name) => [Located name] -> SDoc ppr_con_names [x] = ppr x diff --git a/compiler/hsSyn/HsPat.lhs b/compiler/hsSyn/HsPat.lhs index 32a0339..48c707b 100644 --- a/compiler/hsSyn/HsPat.lhs +++ b/compiler/hsSyn/HsPat.lhs @@ -26,7 +26,7 @@ module HsPat ( isStrictLPat, hsPatNeedsParens, isIrrefutableHsPat, - pprParendLPat + pprParendLPat, pprConArgs ) where import {-# SOURCE #-} HsExpr (SyntaxExpr, LHsExpr, HsSplice, pprLExpr, pprUntypedSplice) diff --git a/testsuite/tests/deSugar/should_run/T9844.hs b/testsuite/tests/deSugar/should_run/T9844.hs new file mode 100644 index 0000000..e06628e --- /dev/null +++ b/testsuite/tests/deSugar/should_run/T9844.hs @@ -0,0 +1,17 @@ +{-# LANGUAGE BangPatterns #-} +module Main where +import Debug.Trace + +newtype N = N Int + +f0 :: N -> Int +f0 n = case n of + !(N _) -> 0 + +f1 :: N -> Int +f1 n = n `seq` case n of + N _ -> 0 + +main = do + print $ f0 (trace "evaluated f0" (N 1)) + print $ f1 (trace "evaluated f1" (N 1)) diff --git a/testsuite/tests/deSugar/should_run/T9844.stderr b/testsuite/tests/deSugar/should_run/T9844.stderr new file mode 100644 index 0000000..c94d12f --- /dev/null +++ b/testsuite/tests/deSugar/should_run/T9844.stderr @@ -0,0 +1,2 @@ +evaluated f0 +evaluated f1 diff --git a/testsuite/tests/simplCore/should_run/T3403.stdout b/testsuite/tests/deSugar/should_run/T9844.stdout similarity index 100% copy from testsuite/tests/simplCore/should_run/T3403.stdout copy to testsuite/tests/deSugar/should_run/T9844.stdout diff --git a/testsuite/tests/deSugar/should_run/all.T b/testsuite/tests/deSugar/should_run/all.T index 233f648..7e1618b 100644 --- a/testsuite/tests/deSugar/should_run/all.T +++ b/testsuite/tests/deSugar/should_run/all.T @@ -41,3 +41,4 @@ test('T5742', normal, compile_and_run, ['']) test('DsLambdaCase', when(compiler_lt('ghc', '7.5'), skip), compile_and_run, ['']) test('DsMultiWayIf', when(compiler_lt('ghc', '7.5'), skip), compile_and_run, ['']) test('T8952', normal, compile_and_run, ['']) +test('T9844', normal, compile_and_run, ['']) From git at git.haskell.org Fri Nov 28 13:25:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Nov 2014 13:25:52 +0000 (UTC) Subject: [commit: ghc] master: Tidy up tracing somewhat (342ebb0) Message-ID: <20141128132552.677C73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/342ebb0450633d6edbf764423586f49beb78facb/ghc >--------------------------------------------------------------- commit 342ebb0450633d6edbf764423586f49beb78facb Author: Simon Peyton Jones Date: Fri Nov 28 11:29:40 2014 +0000 Tidy up tracing somewhat This is a knock-on from the -dump-to-file changes. (I found that -ddump-cs-trace stuff wasn't coming out!) >--------------------------------------------------------------- 342ebb0450633d6edbf764423586f49beb78facb compiler/main/ErrUtils.lhs | 3 + compiler/typecheck/TcRnMonad.lhs | 77 ++++++++++++---------- compiler/typecheck/TcSMonad.lhs | 6 +- testsuite/tests/indexed-types/should_fail/Makefile | 2 +- .../tests/indexed-types/should_fail/T8129.stdout | 1 + 5 files changed, 51 insertions(+), 38 deletions(-) diff --git a/compiler/main/ErrUtils.lhs b/compiler/main/ErrUtils.lhs index c20a731..12f484b 100644 --- a/compiler/main/ErrUtils.lhs +++ b/compiler/main/ErrUtils.lhs @@ -269,6 +269,9 @@ mkDumpDoc hdr doc -- -- When hdr is empty, we print in a more compact format (no separators and -- blank lines) +-- +-- The DumpFlag is used only to choose the filename to use if --dump-to-file is +-- used; it is not used to decide whether to dump the output dumpSDoc :: DynFlags -> PrintUnqualified -> DumpFlag -> String -> SDoc -> IO () dumpSDoc dflags print_unqual flag hdr doc = do let mFile = chooseDumpFile dflags flag diff --git a/compiler/typecheck/TcRnMonad.lhs b/compiler/typecheck/TcRnMonad.lhs index 33fee4f..11a70aa 100644 --- a/compiler/typecheck/TcRnMonad.lhs +++ b/compiler/typecheck/TcRnMonad.lhs @@ -475,54 +475,47 @@ updTcRef = updMutVar \begin{code} traceTc :: String -> SDoc -> TcRn () -traceTc = traceTcN 1 +traceTc herald doc = traceTcN 1 (hang (text herald) 2 doc) -- | Typechecker trace -traceTcN :: Int -> String -> SDoc -> TcRn () -traceTcN level herald doc - = do dflags <- getDynFlags - when (level <= traceLevel dflags && not opt_NoDebugOutput) $ - traceOptTcRn Opt_D_dump_tc_trace $ - hang (text herald) 2 doc +traceTcN :: Int -> SDoc -> TcRn () +traceTcN level doc + = do { dflags <- getDynFlags + ; when (level <= traceLevel dflags) $ + traceOptTcRn Opt_D_dump_tc_trace doc } -traceRn, traceSplice :: SDoc -> TcRn () -traceRn = traceOptTcRn Opt_D_dump_rn_trace -- Renamer Trace -traceSplice = traceOptTcRn Opt_D_dump_splices -- Template Haskell - -traceIf, traceHiDiffs :: SDoc -> TcRnIf m n () -traceIf = traceOptIf Opt_D_dump_if_trace -traceHiDiffs = traceOptIf Opt_D_dump_hi_diffs +traceRn :: SDoc -> TcRn () +traceRn doc = traceOptTcRn Opt_D_dump_rn_trace doc - -traceOptIf :: DumpFlag -> SDoc -> TcRnIf m n () -traceOptIf flag doc - = whenDOptM flag $ -- No RdrEnv available, so qualify everything - do { dflags <- getDynFlags - ; liftIO (putMsg dflags doc) } +traceSplice :: SDoc -> TcRn () +traceSplice doc = traceOptTcRn Opt_D_dump_splices doc -- | Output a doc if the given 'DumpFlag' is set. -- -- By default this logs to stdout -- However, if the `-ddump-to-file` flag is set, -- then this will dump output to a file - --- just a wrapper for 'dumpIfSet_dyn_printer' -- --- does not check opt_NoDebugOutput; --- caller is responsible for than when appropriate +-- Just a wrapper for 'dumpSDoc' traceOptTcRn :: DumpFlag -> SDoc -> TcRn () traceOptTcRn flag doc = do { dflags <- getDynFlags - -- Checking the dynamic flag here is redundant when the flag is set - -- But it avoids extra work when the flag is unset. - ; when (dopt flag dflags) $ do { - ; real_doc <- prettyDoc doc - ; printer <- getPrintUnqualified dflags - ; liftIO $ dumpIfSet_dyn_printer printer dflags flag real_doc - } - } + ; when (dopt flag dflags) (traceTcRn flag doc) + } + +traceTcRn :: DumpFlag -> SDoc -> TcRn () +-- ^ Unconditionally dump some trace output +-- +-- The DumpFlag is used only to set the output filename +-- for --dump-to-file, not to decide whether or not to output +-- That part is done by the caller +traceTcRn flag doc + = do { real_doc <- prettyDoc doc + ; dflags <- getDynFlags + ; printer <- getPrintUnqualified dflags + ; liftIO $ dumpSDoc dflags printer flag "" real_doc } where - -- add current location if opt_PprStyle_Debug + -- Add current location if opt_PprStyle_Debug prettyDoc :: SDoc -> TcRn SDoc prettyDoc doc = if opt_PprStyle_Debug then do { loc <- getSrcSpanM; return $ mkLocMessage SevOutput loc doc } @@ -544,9 +537,25 @@ printForUserTcRn doc -- | Typechecker debug debugDumpTcRn :: SDoc -> TcRn () debugDumpTcRn doc = unless opt_NoDebugOutput $ - traceOptTcRn Opt_D_dump_tc doc + traceOptTcRn Opt_D_dump_tc doc \end{code} +traceIf and traceHiDiffs work in the TcRnIf monad, where no RdrEnv is +available. Alas, they behave inconsistently with the other stuff; +e.g. are unaffected by -dump-to-file. + +\begin{code} +traceIf, traceHiDiffs :: SDoc -> TcRnIf m n () +traceIf = traceOptIf Opt_D_dump_if_trace +traceHiDiffs = traceOptIf Opt_D_dump_hi_diffs + + +traceOptIf :: DumpFlag -> SDoc -> TcRnIf m n () +traceOptIf flag doc + = whenDOptM flag $ -- No RdrEnv available, so qualify everything + do { dflags <- getDynFlags + ; liftIO (putMsg dflags doc) } +\end{code} %************************************************************************ %* * diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index 44ecc6f..4bd3393 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -1096,10 +1096,10 @@ csTraceTcM :: Int -> TcM SDoc -> TcM () -- Constraint-solver tracing, -ddump-cs-trace csTraceTcM trace_level mk_doc = do { dflags <- getDynFlags - ; when ((dopt Opt_D_dump_cs_trace dflags || dopt Opt_D_dump_tc_trace dflags) - && traceLevel dflags >= trace_level) $ + ; when ( (dopt Opt_D_dump_cs_trace dflags || dopt Opt_D_dump_tc_trace dflags) + && trace_level <= traceLevel dflags ) $ do { msg <- mk_doc - ; TcM.debugDumpTcRn msg } } + ; TcM.traceTcRn Opt_D_dump_cs_trace msg } } runTcS :: TcS a -- What to run -> TcM (a, Bag EvBind) diff --git a/testsuite/tests/indexed-types/should_fail/Makefile b/testsuite/tests/indexed-types/should_fail/Makefile index e0738ac..d56889e 100644 --- a/testsuite/tests/indexed-types/should_fail/Makefile +++ b/testsuite/tests/indexed-types/should_fail/Makefile @@ -13,6 +13,6 @@ T8227: # T8129 is trying to ensure that we don't get an # an asertion failure with -ddump-tc-trace T8129: - -'$(TEST_HC)' $(TEST_HC_OPTS) -c -ddump-tc-trace T8129.hs 2> T8129.trace + -'$(TEST_HC)' $(TEST_HC_OPTS) -c -ddump-tc-trace T8129.hs 2> T8129.trace > T8129.trace grep deduce T8129.trace diff --git a/testsuite/tests/indexed-types/should_fail/T8129.stdout b/testsuite/tests/indexed-types/should_fail/T8129.stdout index e8eca18..31d82e5 100644 --- a/testsuite/tests/indexed-types/should_fail/T8129.stdout +++ b/testsuite/tests/indexed-types/should_fail/T8129.stdout @@ -1 +1,2 @@ Could not deduce (C x0 (F x0)) + Could not deduce (C x0 (F x0)) From git at git.haskell.org Fri Nov 28 14:05:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Nov 2014 14:05:01 +0000 (UTC) Subject: [commit: ghc] master: Re-implement `testPrimeInteger` predicate (#9281) (58dcd5c) Message-ID: <20141128140501.17A323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/58dcd5c2e2a94643454296ea0bb109db96bd154f/ghc >--------------------------------------------------------------- commit 58dcd5c2e2a94643454296ea0bb109db96bd154f Author: Herbert Valerio Riedel Date: Fri Nov 28 14:59:50 2014 +0100 Re-implement `testPrimeInteger` predicate (#9281) This also adds `testPrimeWord#` and `testPrimeBigNat` predicates. `testPrimeInteger` has been available since `integer-gmp-0.5.1` (added via f49735486533842cc84df70cafc8d565dffd75db). The `nextPrimeInteger` function is still missing though. >--------------------------------------------------------------- 58dcd5c2e2a94643454296ea0bb109db96bd154f libraries/integer-gmp2/cbits/wrappers.c | 25 +++++++++++++ .../integer-gmp2/src/GHC/Integer/GMP/Internals.hs | 43 ++++++++++++++++++++++ 2 files changed, 68 insertions(+) diff --git a/libraries/integer-gmp2/cbits/wrappers.c b/libraries/integer-gmp2/cbits/wrappers.c index 9aac390..6c188a3 100644 --- a/libraries/integer-gmp2/cbits/wrappers.c +++ b/libraries/integer-gmp2/cbits/wrappers.c @@ -449,3 +449,28 @@ integer_gmp_rscan_nzbyte(const uint8_t *srcptr, return 0; } + +/* wrapper around mpz_probab_prime_p */ +HsInt +integer_gmp_test_prime(const mp_limb_t s[], const mp_size_t sn, const HsInt rep) +{ + if (!sn) return 0; + + const mpz_t sz = {{ + ._mp_alloc = sn, + ._mp_size = sn, + ._mp_d = (mp_limb_t*)s + }}; + + // int mpz_probab_prime_p (const mpz_t n, int reps) + return mpz_probab_prime_p(sz, rep); +} + +/* wrapper around mpz_probab_prime_p */ +HsInt +integer_gmp_test_prime1(const mp_limb_t limb, const HsInt rep) +{ + if (!limb) return 0; + + return integer_gmp_test_prime(&limb, 1, rep); +} diff --git a/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs b/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs index 77d73bf..480866b 100644 --- a/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs +++ b/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs @@ -120,6 +120,11 @@ module GHC.Integer.GMP.Internals , gcdInt , gcdWord + -- * Primality tests + , testPrimeInteger + , testPrimeBigNat + , testPrimeWord# + -- * Import/export functions -- ** Compute size of serialisation , sizeInBaseBigNat @@ -280,3 +285,41 @@ exportWordToMutableByteArray (W# w#) = c_mpn_export1ToMutableByteArray# w# foreign import ccall unsafe "integer_gmp_mpn_export1" c_mpn_export1ToMutableByteArray# :: GmpLimb# -> MutableByteArray# RealWorld -> Word# -> Int# -> IO Word + + +-- | Probalistic Miller-Rabin primality test. +-- +-- \"@'testPrimeInteger' /n/ /k/@\" determines whether @/n/@ is prime +-- and returns one of the following results: +-- +-- * @2#@ is returned if @/n/@ is definitely prime, +-- +-- * @1#@ if @/n/@ is a /probable prime/, or +-- +-- * @0#@ if @/n/@ is definitely not a prime. +-- +-- The @/k/@ argument controls how many test rounds are performed for +-- determining a /probable prime/. For more details, see +-- . +-- +-- /Since: 0.5.1.0/ +{-# NOINLINE testPrimeInteger #-} +testPrimeInteger :: Integer -> Int# -> Int# +testPrimeInteger (S# i#) = testPrimeWord# (int2Word# (absI# i#)) +testPrimeInteger (Jp# n) = testPrimeBigNat n +testPrimeInteger (Jn# n) = testPrimeBigNat n + +-- | Version of 'testPrimeInteger' operating on 'BigNat's +-- +-- /Since: 1.0.0.0/ +testPrimeBigNat :: BigNat -> Int# -> Int# +testPrimeBigNat bn@(BN# ba#) = c_integer_gmp_test_prime# ba# (sizeofBigNat# bn) + +foreign import ccall unsafe "integer_gmp_test_prime" + c_integer_gmp_test_prime# :: ByteArray# -> GmpSize# -> Int# -> Int# + +-- | Version of 'testPrimeInteger' operating on 'Word#'s +-- +-- /Since: 1.0.0.0/ +foreign import ccall unsafe "integer_gmp_test_prime1" + testPrimeWord# :: GmpLimb# -> Int# -> Int# From git at git.haskell.org Fri Nov 28 14:09:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Nov 2014 14:09:50 +0000 (UTC) Subject: [commit: ghc] master: Make the linker API thread-safe (b5e8b3b) Message-ID: <20141128140950.AEAE03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b5e8b3b162b3ff15ae6caf1afc659565365f54a8/ghc >--------------------------------------------------------------- commit b5e8b3b162b3ff15ae6caf1afc659565365f54a8 Author: Simon Marlow Date: Fri Sep 26 20:08:43 2014 +0100 Make the linker API thread-safe We used to be able to rely on the client to use the API in a single-threaded way, but now that the GC calls into the linker to unload objects this isn't a safe assumption. >--------------------------------------------------------------- b5e8b3b162b3ff15ae6caf1afc659565365f54a8 docs/users_guide/7.10.1-notes.xml | 6 ++- rts/CheckUnload.c | 4 ++ rts/Linker.c | 105 +++++++++++++++++++++++++------------- rts/LinkerInternals.h | 4 ++ testsuite/tests/rts/Makefile | 8 +-- testsuite/tests/rts/T2615.hs | 1 + testsuite/tests/rts/rdynamic.hs | 2 + 7 files changed, 89 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b5e8b3b162b3ff15ae6caf1afc659565365f54a8 From git at git.haskell.org Fri Nov 28 14:09:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Nov 2014 14:09:53 +0000 (UTC) Subject: [commit: ghc] master: Add purgeObj() to remove the symbol table entries for an object (9e6e479) Message-ID: <20141128140953.7AC063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9e6e4796437a7fc23e83605a45db9b2663570123/ghc >--------------------------------------------------------------- commit 9e6e4796437a7fc23e83605a45db9b2663570123 Author: Simon Marlow Date: Mon Sep 29 12:49:21 2014 +0100 Add purgeObj() to remove the symbol table entries for an object This allows us to replace an object without actually unloading the old object, which is necessary when we know we have references to the old object so it can't be completely unloaded. Using unloadObj() would cause the GC (CheckUnload) to repeatedly and fruitlessly try to unload the old object. >--------------------------------------------------------------- 9e6e4796437a7fc23e83605a45db9b2663570123 includes/rts/Linker.h | 3 ++ rts/Linker.c | 74 ++++++++++++++++++++++---------- testsuite/tests/rts/linker_unload.c | 37 ++++++++++++++++ testsuite/tests/rts/linker_unload.stdout | 2 +- 4 files changed, 92 insertions(+), 24 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9e6e4796437a7fc23e83605a45db9b2663570123 From git at git.haskell.org Fri Nov 28 16:21:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Nov 2014 16:21:22 +0000 (UTC) Subject: [commit: ghc] master: Re-activate `integerGmpInternals` test (#9281) (2eecf34) Message-ID: <20141128162122.8005A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2eecf348a62c47abd2f5de5f7eac5f7a3a779107/ghc >--------------------------------------------------------------- commit 2eecf348a62c47abd2f5de5f7eac5f7a3a779107 Author: Herbert Valerio Riedel Date: Fri Nov 28 17:13:33 2014 +0100 Re-activate `integerGmpInternals` test (#9281) The `integerGmpInternals` test was disabled in c774b28f76ee4c220f7c1c9fd81585e0e3af0e8a as many of the primitives tested in that test weren't available yet w/ `integer-gmp2`. However, most operations have been reimplemented by now, with the exception of recipModInteger :: Integer -> Integer -> Integer gcdExtInteger :: Integer -> Integer -> (Integer, Integer) powModSecInteger :: Integer -> Integer -> Integer -> Integer powModInteger :: Integer -> Integer -> Integer -> Integer powInteger :: Integer -> Word -> Integer which are still missing, and will (time permitting) be reimplemented over time. >--------------------------------------------------------------- 2eecf348a62c47abd2f5de5f7eac5f7a3a779107 testsuite/tests/lib/integer/all.T | 3 +- testsuite/tests/lib/integer/integerGmpInternals.hs | 78 +++++++++++++++------- 2 files changed, 55 insertions(+), 26 deletions(-) diff --git a/testsuite/tests/lib/integer/all.T b/testsuite/tests/lib/integer/all.T index 5515426..7b5e5f2 100644 --- a/testsuite/tests/lib/integer/all.T +++ b/testsuite/tests/lib/integer/all.T @@ -1,8 +1,7 @@ test('integerBits', normal, compile_and_run, ['']) test('integerConversions', normal, compile_and_run, ['']) -## 'integerGmpInternals' disabled till the extra primitives are re-implemented # skip ghci as it doesn't support unboxed tuples -# test('integerGmpInternals', [reqlib('integer-gmp'), omit_ways('ghci')], compile_and_run, ['']) +test('integerGmpInternals', [reqlib('integer-gmp'), omit_ways('ghci')], compile_and_run, ['']) test('integerConstantFolding', [ extra_clean(['integerConstantFolding.simpl']) , when(compiler_debugged(), expect_broken(8525))], diff --git a/testsuite/tests/lib/integer/integerGmpInternals.hs b/testsuite/tests/lib/integer/integerGmpInternals.hs index c709a22..5db0b09 100644 --- a/testsuite/tests/lib/integer/integerGmpInternals.hs +++ b/testsuite/tests/lib/integer/integerGmpInternals.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE MagicHash, UnboxedTuples #-} +{-# LANGUAGE BangPatterns, CPP, MagicHash, UnboxedTuples #-} module Main (main) where @@ -12,11 +12,58 @@ import GHC.Base import GHC.Integer.GMP.Internals (Integer(S#,Jp#,Jn#)) import qualified GHC.Integer.GMP.Internals as I +-- NOTE: Some of the following operations were provided with +-- integer-gmp-0.5.1, but were not ported to integer-gmp-1.0.0 (yet); +-- so we use naive reference-implementations instead for the meantime +-- in order to keep the reference-output untouched. + +-- FIXME: Lacks GMP2 version +-- stolen from `arithmoi` package +recipModInteger :: Integer -> Integer -> Integer +recipModInteger k 0 = if k == 1 || k == (-1) then k else 0 +recipModInteger k m = case gcdExtInteger k' m' of + (1, u) -> if u < 0 then m' + u else u + _ -> 0 + where + m' = abs m + k' | k >= m' || k < 0 = k `mod` m' + | otherwise = k + +-- FIXME: Lacks GMP2 version gcdExtInteger :: Integer -> Integer -> (Integer, Integer) -gcdExtInteger a b = case I.gcdExtInteger a b of (# a, b #) -> (a,b) +gcdExtInteger a b = (d, u) -- stolen from `arithmoi` package + where + (d, x, y) = eGCD 0 1 1 0 (abs a) (abs b) + u | a < 0 = negate x + | otherwise = x + v | b < 0 = negate y + | otherwise = y + eGCD !n1 o1 !n2 o2 r s + | s == 0 = (r, o1, o2) + | otherwise = case r `quotRem` s of + (q, t) -> eGCD (o1 - q*n1) n1 (o2 - q*n2) n2 s t + +-- FIXME: Lacks GMP2 version +powModSecInteger :: Integer -> Integer -> Integer -> Integer +powModSecInteger = powModInteger + +-- FIXME: Lacks GMP2 version +powModInteger :: Integer -> Integer -> Integer -> Integer +powModInteger b0 e0 m + | e0 >= 0 = go b0 e0 1 + | otherwise = error "non-neg exponent required" + where + go !b e !r + | odd e = go b' e' (r*b `mod` m) + | e == 0 = r + | otherwise = go b' e' r + where + b' = b*b `mod` m + e' = e `unsafeShiftR` 1 -- slightly faster than "e `div` 2" +-- FIXME: Lacks GMP2 version powInteger :: Integer -> Word -> Integer -powInteger b (W# w#) = I.powInteger b w# +powInteger x e = x^e exportInteger :: Integer -> MutableByteArray# RealWorld -> Word# -> Int# -> IO Word exportInteger = I.exportIntegerToMutableByteArray @@ -30,23 +77,6 @@ importInteger = I.importIntegerFromByteArray importIntegerAddr :: Addr# -> Word# -> Int# -> IO Integer importIntegerAddr a l e = I.importIntegerFromAddr a l e -{- Reference implementation for 'powModInteger' - -powModIntegerHs :: Integer -> Integer -> Integer -> Integer -powModIntegerHs b0 e0 m - | e0 >= 0 = go b0 e0 1 - | otherwise = error "non-neg exponent required" - where - go !b e !r - | odd e = go b' e' (r*b `mod` m) - | e == 0 = r - | otherwise = go b' e' r - where - b' = b*b `mod` m - e' = e `unsafeShiftR` 1 -- slightly faster than "e `div` 2" - --} - -- helpers data MBA = MBA { unMBA :: !(MutableByteArray# RealWorld) } data BA = BA { unBA :: !ByteArray# } @@ -78,9 +108,9 @@ freezeByteArray arr = IO $ \s -> case unsafeFreezeByteArray# arr s of (# s, arr ---------------------------------------------------------------------------- main :: IO () main = do - print $ I.powModInteger b e m - print $ I.powModInteger b e (m-1) - print $ I.powModSecInteger b e (m-1) + print $ powModInteger b e m + print $ powModInteger b e (m-1) + print $ powModSecInteger b e (m-1) print $ gcdExtInteger b e print $ gcdExtInteger e b print $ gcdExtInteger x y @@ -88,7 +118,7 @@ main = do print $ powInteger 12345 0 print $ powInteger 12345 1 print $ powInteger 12345 30 - print $ [ (x,i) | x <- [0..71], let i = I.recipModInteger x (2*3*11*11*17*17), i /= 0 ] + print $ [ (x,i) | x <- [0..71], let i = recipModInteger x (2*3*11*11*17*17), i /= 0 ] print $ I.nextPrimeInteger b print $ I.nextPrimeInteger e print $ [ k | k <- [ 0 .. 200 ], S# (I.testPrimeInteger k 25#) `elem` [1,2] ] From git at git.haskell.org Fri Nov 28 16:21:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Nov 2014 16:21:25 +0000 (UTC) Subject: [commit: ghc] master: Re-implement `nextPrimeInteger` predicate (#9281) (8d78311) Message-ID: <20141128162125.354133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8d7831108644584f710515b39b9fc97fbeca7a4c/ghc >--------------------------------------------------------------- commit 8d7831108644584f710515b39b9fc97fbeca7a4c Author: Herbert Valerio Riedel Date: Fri Nov 28 17:12:14 2014 +0100 Re-implement `nextPrimeInteger` predicate (#9281) This also adds `nextPrimeWord#` and `nextPrimeBigNat` predicates. `nextPrimeInteger` has been available since `integer-gmp-0.5.1` (added via f49735486533842cc84df70cafc8d565dffd75db). >--------------------------------------------------------------- 8d7831108644584f710515b39b9fc97fbeca7a4c libraries/integer-gmp2/cbits/wrappers.c | 58 ++++++++++++++++++++++ .../integer-gmp2/src/GHC/Integer/GMP/Internals.hs | 27 ++++++++++ libraries/integer-gmp2/src/GHC/Integer/Type.hs | 17 +++++++ 3 files changed, 102 insertions(+) diff --git a/libraries/integer-gmp2/cbits/wrappers.c b/libraries/integer-gmp2/cbits/wrappers.c index 6c188a3..1621d3b 100644 --- a/libraries/integer-gmp2/cbits/wrappers.c +++ b/libraries/integer-gmp2/cbits/wrappers.c @@ -474,3 +474,61 @@ integer_gmp_test_prime1(const mp_limb_t limb, const HsInt rep) return integer_gmp_test_prime(&limb, 1, rep); } + +/* wrapper around mpz_nextprime() + * + * Stores next prime (relative to {sp,sn}) in {rp,sn}. + * Return value is most significant limb of {rp,sn+1}. + */ +mp_limb_t +integer_gmp_next_prime(mp_limb_t rp[], const mp_limb_t sp[], + const mp_size_t sn) +{ + if (!sn) return 2; + + const mpz_t op = {{ + ._mp_alloc = sn, + ._mp_size = sn, + ._mp_d = (mp_limb_t*)sp + }}; + + mpz_t rop; + mpz_init (rop); + mpz_nextprime (rop, op); + + const mp_size_t rn = rop[0]._mp_size; + + // copy result into {rp,sn} buffer + assert (rn == sn || rn == sn+1); + memcpy(rp, rop[0]._mp_d, sn*sizeof(mp_limb_t)); + const mp_limb_t result = rn>sn ? rop[0]._mp_d[sn] : 0; + + mpz_clear (rop); + + return result; +} + +/* wrapper around mpz_nextprime() + * + * returns next prime modulo 2^GMP_LIMB_BITS + */ +mp_limb_t +integer_gmp_next_prime1(const mp_limb_t limb) +{ + if (limb < 2) return 2; + + const mpz_t op = {{ + ._mp_alloc = 1, + ._mp_size = 1, + ._mp_d = (mp_limb_t*)(&limb) + }}; + + mpz_t rop; + mpz_init (rop); + mpz_nextprime (rop, op); + assert (rop[0]._mp_size > 0); + const mp_limb_t result = rop[0]._mp_d[0]; + mpz_clear (rop); + + return result; +} diff --git a/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs b/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs index 480866b..244dac7 100644 --- a/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs +++ b/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs @@ -125,6 +125,10 @@ module GHC.Integer.GMP.Internals , testPrimeBigNat , testPrimeWord# + , nextPrimeInteger + , nextPrimeBigNat + , nextPrimeWord# + -- * Import/export functions -- ** Compute size of serialisation , sizeInBaseBigNat @@ -323,3 +327,26 @@ foreign import ccall unsafe "integer_gmp_test_prime" -- /Since: 1.0.0.0/ foreign import ccall unsafe "integer_gmp_test_prime1" testPrimeWord# :: GmpLimb# -> Int# -> Int# + + +-- | Compute next prime greater than @/n/@ probalistically. +-- +-- According to the GMP documentation, the underlying function +-- @mpz_nextprime()@ \"uses a probabilistic algorithm to identify +-- primes. For practical purposes it's adequate, the chance of a +-- composite passing will be extremely small.\" +-- +-- /Since: 0.5.1.0/ +{-# NOINLINE nextPrimeInteger #-} +nextPrimeInteger :: Integer -> Integer +nextPrimeInteger (S# i#) + | isTrue# (i# ># 1#) = wordToInteger (nextPrimeWord# (int2Word# i#)) + | True = S# 2# +nextPrimeInteger (Jp# bn) = Jp# (nextPrimeBigNat bn) +nextPrimeInteger (Jn# _) = S# 2# + +-- | Version of 'nextPrimeInteger' operating on 'Word#'s +-- +-- /Since: 1.0.0.0/ +foreign import ccall unsafe "integer_gmp_next_prime1" + nextPrimeWord# :: GmpLimb# -> GmpLimb# diff --git a/libraries/integer-gmp2/src/GHC/Integer/Type.hs b/libraries/integer-gmp2/src/GHC/Integer/Type.hs index 48c5ed8..d771de1 100644 --- a/libraries/integer-gmp2/src/GHC/Integer/Type.hs +++ b/libraries/integer-gmp2/src/GHC/Integer/Type.hs @@ -1684,6 +1684,23 @@ isValidBigNat# (BN# ba#) (# szq#, szr# #) = quotRemInt# sz# GMP_LIMB_BYTES# +-- | Version of 'nextPrimeInteger' operating on 'BigNat's +-- +-- /Since: 1.0.0.0/ +nextPrimeBigNat :: BigNat -> BigNat +nextPrimeBigNat bn@(BN# ba#) = runS $ do + mbn@(MBN# mba#) <- newBigNat# n# + (W# c#) <- liftIO (nextPrime# mba# ba# n#) + case c# of + 0## -> unsafeFreezeBigNat# mbn + _ -> unsafeSnocFreezeBigNat# mbn c# + where + n# = sizeofBigNat# bn + +foreign import ccall unsafe "integer_gmp_next_prime" + nextPrime# :: MutableByteArray# RealWorld -> ByteArray# -> GmpSize# + -> IO GmpLimb + ---------------------------------------------------------------------------- -- monadic combinators for low-level state threading From git at git.haskell.org Fri Nov 28 17:37:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Nov 2014 17:37:25 +0000 (UTC) Subject: [commit: ghc] master: Kind variables in RHS of an associated type instances should be bound on LHS (171101b) Message-ID: <20141128173725.A6B753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/171101beca39befde191baff5027c417bcc709ee/ghc >--------------------------------------------------------------- commit 171101beca39befde191baff5027c417bcc709ee Author: Simon Peyton Jones Date: Fri Nov 28 17:23:08 2014 +0000 Kind variables in RHS of an associated type instances should be bound on LHS This patche fixes Trac #9574. The previous Note [Renaming associated types] in RnTypes appears to me to be wrong; it confused class and instance declarations. I have: * Treated kind and type variables uniformly. Both must be bound on the LHS of an associated type instance. Eg instance C ('KProxy :: KProxy o) where type F 'KProxy = NatTr (Proxy :: o -> *) is illegal because 'o' is not bound on the LHS of the instance. * Moved the Note to RnSource and fixed it up This improves the error message from T7938. However it made the code in T6118 incorrect. We had: instance SingE (a :: Maybe k) where type Demote a = Maybe (Demote (Any :: k)) and that is now rejected, rightly I think. >--------------------------------------------------------------- 171101beca39befde191baff5027c417bcc709ee compiler/rename/RnSource.lhs | 53 +++++++++++++++++----- compiler/rename/RnTypes.lhs | 25 ---------- compiler/typecheck/TcInstDcls.lhs | 14 +----- .../tests/indexed-types/should_fail/T5515.stderr | 4 +- .../tests/indexed-types/should_fail/T7938.stderr | 8 ++-- testsuite/tests/polykinds/T6118.hs | 2 +- testsuite/tests/polykinds/T9574.hs | 18 ++++++++ testsuite/tests/polykinds/T9574.stderr | 4 ++ testsuite/tests/polykinds/all.T | 1 + 9 files changed, 72 insertions(+), 57 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 171101beca39befde191baff5027c417bcc709ee From git at git.haskell.org Fri Nov 28 17:37:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Nov 2014 17:37:28 +0000 (UTC) Subject: [commit: ghc] master: Rename some of the functions in NameSet, to make the uniform with VarSet etc (7460daf) Message-ID: <20141128173728.5E6223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7460dafae3709218af651cb8bc47b5f03d4c25c7/ghc >--------------------------------------------------------------- commit 7460dafae3709218af651cb8bc47b5f03d4c25c7 Author: Simon Peyton Jones Date: Fri Nov 28 17:35:44 2014 +0000 Rename some of the functions in NameSet, to make the uniform with VarSet etc For ages NameSet has used different names, eg. addOneToNameSet rather than extendNameSet nameSetToList rather than nameSetElems etc. Other set-like modules use uniform naming conventions. This patch makes NameSet follow suit. No change in behaviour; this is just renaming. I'm doing this just before the fork so that merging is easier. >--------------------------------------------------------------- 7460dafae3709218af651cb8bc47b5f03d4c25c7 compiler/basicTypes/Avail.hs | 2 +- compiler/basicTypes/MkId.lhs | 2 +- compiler/basicTypes/NameSet.lhs | 44 +++++++++++++-------------- compiler/basicTypes/RdrName.lhs | 6 ++-- compiler/coreSyn/CoreFVs.lhs | 16 +++++----- compiler/deSugar/Coverage.lhs | 2 +- compiler/ghci/ByteCodeAsm.hs | 2 +- compiler/ghci/Linker.hs | 4 +-- compiler/hsSyn/HsUtils.lhs | 12 ++++---- compiler/iface/IfaceSyn.lhs | 2 +- compiler/iface/MkIface.lhs | 18 +++++------ compiler/main/GHC.hs | 2 +- compiler/main/HscTypes.lhs | 2 +- compiler/main/InteractiveEval.hs | 2 +- compiler/rename/RnBinds.lhs | 6 ++-- compiler/rename/RnExpr.lhs | 18 +++++------ compiler/rename/RnNames.lhs | 8 ++--- compiler/rename/RnSource.lhs | 12 ++++---- compiler/typecheck/TcBinds.lhs | 2 +- compiler/typecheck/TcInstDcls.lhs | 2 +- compiler/typecheck/TcRnDriver.lhs | 2 +- compiler/typecheck/TcRnMonad.lhs | 2 +- compiler/typecheck/TcSplice.lhs | 2 +- compiler/typecheck/TcTyDecls.lhs | 6 ++-- compiler/typecheck/TcType.lhs | 32 +++++++++---------- compiler/types/FamInstEnv.lhs | 2 +- compiler/types/TyCon.lhs | 2 +- compiler/vectorise/Vectorise/Monad.hs | 2 +- compiler/vectorise/Vectorise/Type/Classify.hs | 2 +- compiler/vectorise/Vectorise/Type/Env.hs | 2 +- 30 files changed, 109 insertions(+), 109 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7460dafae3709218af651cb8bc47b5f03d4c25c7 From git at git.haskell.org Fri Nov 28 23:17:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Nov 2014 23:17:21 +0000 (UTC) Subject: [commit: ghc] master: Implement Partial Type Signatures (d831b6f) Message-ID: <20141128231721.152283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d831b6f41b3b89dc4a643069d5668c05a20f3c37/ghc >--------------------------------------------------------------- commit d831b6f41b3b89dc4a643069d5668c05a20f3c37 Author: Thomas Winant Date: Fri Nov 28 16:08:10 2014 -0600 Implement Partial Type Signatures Summary: Add support for Partial Type Signatures, i.e. holes in types, see: https://ghc.haskell.org/trac/ghc/wiki/PartialTypeSignatures This requires an update to the Haddock submodule. Test Plan: validate Reviewers: austin, goldfire, simonpj Reviewed By: simonpj Subscribers: thomie, Iceland_jack, dominique.devriese, simonmar, carter, goldfire Differential Revision: https://phabricator.haskell.org/D168 GHC Trac Issues: #9478 >--------------------------------------------------------------- d831b6f41b3b89dc4a643069d5668c05a20f3c37 compiler/deSugar/DsMeta.hs | 10 +- compiler/hsSyn/Convert.lhs | 4 +- compiler/hsSyn/HsBinds.lhs | 13 +- compiler/hsSyn/HsExpr.lhs | 6 +- compiler/hsSyn/HsTypes.lhs | 89 ++++- compiler/hsSyn/HsUtils.lhs | 2 +- compiler/main/DynFlags.hs | 7 + compiler/main/ErrUtils.lhs | 6 +- compiler/main/HscStats.hs | 2 +- compiler/parser/Parser.y | 48 ++- compiler/parser/RdrHsSyn.hs | 308 +++++++++++++++- compiler/rename/RnBinds.lhs | 24 +- compiler/rename/RnExpr.lhs | 10 +- compiler/rename/RnNames.lhs | 2 +- compiler/rename/RnSource.lhs | 5 +- compiler/rename/RnTypes.lhs | 107 +++++- compiler/typecheck/TcBinds.lhs | 161 ++++++-- compiler/typecheck/TcCanonical.lhs | 12 +- compiler/typecheck/TcClassDcl.lhs | 6 +- compiler/typecheck/TcEnv.lhs | 37 +- compiler/typecheck/TcErrors.lhs | 47 ++- compiler/typecheck/TcExpr.lhs | 14 +- compiler/typecheck/TcGenDeriv.lhs | 13 +- compiler/typecheck/TcHsSyn.lhs | 2 +- compiler/typecheck/TcHsType.lhs | 37 +- compiler/typecheck/TcInstDcls.lhs | 6 +- compiler/typecheck/TcMType.lhs | 68 +++- compiler/typecheck/TcPat.lhs | 27 +- compiler/typecheck/TcPatSyn.lhs | 7 +- compiler/typecheck/TcRnDriver.lhs | 4 +- compiler/typecheck/TcRnMonad.lhs | 19 + compiler/typecheck/TcRnTypes.lhs | 27 +- compiler/typecheck/TcRules.lhs | 2 +- compiler/typecheck/TcSMonad.lhs | 2 +- compiler/typecheck/TcTyClsDecls.lhs | 2 +- compiler/typecheck/TcType.lhs | 17 +- compiler/typecheck/TcValidity.lhs | 4 +- compiler/types/Type.lhs | 7 +- compiler/types/TypeRep.lhs | 25 +- docs/users_guide/flags.xml | 25 ++ docs/users_guide/glasgow_exts.xml | 287 +++++++++++++++ docs/users_guide/using.xml | 18 + testsuite/tests/driver/T4437.hs | 4 +- .../tests/{annotations => partial-sigs}/Makefile | 0 testsuite/tests/partial-sigs/should_compile/ADT.hs | 7 + .../tests/partial-sigs/should_compile/ADT.stderr | 9 + .../tests/partial-sigs/should_compile/AddAndOr1.hs | 7 + .../partial-sigs/should_compile/AddAndOr1.stderr | 7 + .../tests/partial-sigs/should_compile/AddAndOr2.hs | 7 + .../partial-sigs/should_compile/AddAndOr2.stderr | 7 + .../tests/partial-sigs/should_compile/AddAndOr3.hs | 7 + .../partial-sigs/should_compile/AddAndOr3.stderr | 7 + .../tests/partial-sigs/should_compile/AddAndOr4.hs | 7 + .../partial-sigs/should_compile/AddAndOr4.stderr | 7 + .../tests/partial-sigs/should_compile/AddAndOr5.hs | 7 + .../partial-sigs/should_compile/AddAndOr5.stderr | 7 + .../tests/partial-sigs/should_compile/AddAndOr6.hs | 7 + .../partial-sigs/should_compile/AddAndOr6.stderr | 7 + .../partial-sigs/should_compile/BoolToBool.hs | 5 + .../partial-sigs/should_compile/BoolToBool.stderr | 7 + .../partial-sigs/should_compile/Defaulting1MROn.hs | 6 + .../should_compile/Defaulting1MROn.stderr | 7 + .../should_compile/Defaulting2MROff.hs | 6 + .../should_compile/Defaulting2MROff.stderr | 7 + .../partial-sigs/should_compile/Defaulting2MROn.hs | 6 + .../should_compile/Defaulting2MROn.stderr | 7 + .../tests/partial-sigs/should_compile/Either.hs | 5 + .../partial-sigs/should_compile/Either.stderr | 7 + .../should_compile/EqualityConstraint.hs | 5 + .../should_compile/EqualityConstraint.stderr | 7 + .../tests/partial-sigs/should_compile/Every.hs | 6 + .../tests/partial-sigs/should_compile/Every.stderr | 7 + .../partial-sigs/should_compile/EveryNamed.hs | 6 + .../partial-sigs/should_compile/EveryNamed.stderr | 7 + .../partial-sigs/should_compile/ExpressionSig.hs | 5 + .../should_compile/ExpressionSig.stderr | 7 + .../should_compile/ExpressionSigNamed.hs | 6 + .../should_compile/ExpressionSigNamed.stderr | 7 + .../should_compile/ExtraConstraints1.hs | 17 + .../should_compile/ExtraConstraints1.stderr | 11 + .../should_compile/ExtraConstraints2.hs | 8 + .../should_compile/ExtraConstraints2.stderr | 7 + .../should_compile/ExtraConstraints3.hs | 405 +++++++++++++++++++++ .../should_compile/ExtraConstraints3.stderr | 234 ++++++++++++ .../partial-sigs/should_compile/ExtraNumAMROff.hs | 6 + .../should_compile/ExtraNumAMROff.stderr | 7 + .../partial-sigs/should_compile/ExtraNumAMROn.hs | 6 + .../should_compile/ExtraNumAMROn.stderr | 7 + .../tests/partial-sigs/should_compile/Forall1.hs | 5 + .../partial-sigs/should_compile/Forall1.stderr | 7 + .../tests/partial-sigs/should_compile/GenNamed.hs | 5 + .../partial-sigs/should_compile/GenNamed.stderr | 7 + .../partial-sigs/should_compile/HigherRank1.hs | 5 + .../partial-sigs/should_compile/HigherRank1.stderr | 7 + .../partial-sigs/should_compile/HigherRank2.hs | 5 + .../partial-sigs/should_compile/HigherRank2.stderr | 7 + .../should_compile/LocalDefinitionBug.hs | 29 ++ .../should_compile/LocalDefinitionBug.stderr | 7 + .../should_compile/Makefile | 0 .../tests/partial-sigs/should_compile/Meltdown.hs | 25 ++ .../partial-sigs/should_compile/Meltdown.stderr | 18 + .../partial-sigs/should_compile/MonoLocalBinds.hs | 14 + .../should_compile/MonoLocalBinds.stderr | 7 + .../partial-sigs/should_compile/NamedTyVar.hs | 5 + .../partial-sigs/should_compile/NamedTyVar.stderr | 7 + .../should_compile/ParensAroundContext.hs | 5 + .../should_compile/ParensAroundContext.stderr | 7 + .../tests/partial-sigs/should_compile/PatBind.hs | 5 + .../partial-sigs/should_compile/PatBind.stderr | 7 + .../tests/partial-sigs/should_compile/PatBind2.hs | 5 + .../partial-sigs/should_compile/PatBind2.stderr | 7 + .../partial-sigs/should_compile/PatternSig.hs | 5 + .../partial-sigs/should_compile/PatternSig.stderr | 7 + .../tests/partial-sigs/should_compile/Recursive.hs | 11 + .../partial-sigs/should_compile/Recursive.stderr | 9 + .../should_compile/ScopedNamedWildcards.hs | 10 + .../should_compile/ScopedNamedWildcards.stderr | 7 + .../should_compile/ScopedNamedWildcardsGood.hs | 13 + .../should_compile/ScopedNamedWildcardsGood.stderr | 7 + .../tests/partial-sigs/should_compile/ShowNamed.hs | 5 + .../partial-sigs/should_compile/ShowNamed.stderr | 7 + .../tests/partial-sigs/should_compile/SimpleGen.hs | 5 + .../partial-sigs/should_compile/SimpleGen.stderr | 7 + .../tests/partial-sigs/should_compile/SkipMany.hs | 10 + .../partial-sigs/should_compile/SkipMany.stderr | 12 + .../should_compile/SomethingShowable.hs | 6 + .../should_compile/SomethingShowable.stderr | 7 + .../tests/partial-sigs/should_compile/Uncurry.hs | 5 + .../partial-sigs/should_compile/Uncurry.stderr | 7 + .../partial-sigs/should_compile/UncurryNamed.hs | 5 + .../should_compile/UncurryNamed.stderr | 7 + .../WarningWildcardInstantiations.hs | 9 + .../WarningWildcardInstantiations.stderr | 48 +++ testsuite/tests/partial-sigs/should_compile/all.T | 48 +++ .../should_fail/AnnotatedConstraint.hs | 11 + .../should_fail/AnnotatedConstraint.stderr | 7 + .../should_fail/AnnotatedConstraintNotForgotten.hs | 15 + .../AnnotatedConstraintNotForgotten.stderr | 5 + .../partial-sigs/should_fail/Defaulting1MROff.hs | 6 + .../should_fail/Defaulting1MROff.stderr | 6 + .../ExtraConstraintsWildcardNotEnabled.hs | 8 + .../ExtraConstraintsWildcardNotEnabled.stderr | 5 + .../should_fail/ExtraConstraintsWildcardNotLast.hs | 5 + .../ExtraConstraintsWildcardNotLast.stderr | 6 + .../ExtraConstraintsWildcardNotPresent.hs | 13 + .../ExtraConstraintsWildcardNotPresent.stderr | 6 + .../tests/partial-sigs/should_fail/Forall1Bad.hs | 9 + .../partial-sigs/should_fail/Forall1Bad.stderr | 5 + .../InstantiatedNamedWildcardsInConstraints.hs | 5 + .../InstantiatedNamedWildcardsInConstraints.stderr | 13 + .../should_fail}/Makefile | 0 .../should_fail/NamedExtraConstraintsWildcard.hs | 5 + .../NamedExtraConstraintsWildcard.stderr | 5 + .../should_fail/NamedWildcardsEnabled.hs | 5 + .../should_fail/NamedWildcardsEnabled.stderr | 10 + .../should_fail/NamedWildcardsNotEnabled.hs | 7 + .../should_fail/NamedWildcardsNotEnabled.stderr | 21 ++ .../should_fail/NamedWildcardsNotInMonotype.hs | 5 + .../should_fail/NamedWildcardsNotInMonotype.stderr | 6 + .../should_fail/NestedExtraConstraintsWildcard.hs | 5 + .../NestedExtraConstraintsWildcard.stderr | 6 + .../NestedNamedExtraConstraintsWildcard.hs | 5 + .../NestedNamedExtraConstraintsWildcard.stderr | 5 + .../should_fail/PartialClassMethodSignature.hs | 6 + .../should_fail/PartialClassMethodSignature.stderr | 5 + .../should_fail/PartialTypeSignaturesDisabled.hs | 5 + .../PartialTypeSignaturesDisabled.stderr | 10 + .../should_fail/ScopedNamedWildcardsBad.hs | 11 + .../should_fail/ScopedNamedWildcardsBad.stderr | 5 + .../tests/partial-sigs/should_fail/TidyClash.hs | 9 + .../partial-sigs/should_fail/TidyClash.stderr | 16 + .../tests/partial-sigs/should_fail/TidyClash2.hs | 5 + .../partial-sigs/should_fail/TidyClash2.stderr | 54 +++ .../should_fail/UnnamedConstraintWildcard1.hs | 5 + .../should_fail/UnnamedConstraintWildcard1.stderr | 5 + .../should_fail/UnnamedConstraintWildcard2.hs | 5 + .../should_fail/UnnamedConstraintWildcard2.stderr | 5 + .../partial-sigs/should_fail/WildcardInADT1.hs | 4 + .../partial-sigs/should_fail/WildcardInADT1.stderr | 4 + .../partial-sigs/should_fail/WildcardInADT2.hs | 4 + .../partial-sigs/should_fail/WildcardInADT2.stderr | 4 + .../partial-sigs/should_fail/WildcardInADT3.hs | 4 + .../partial-sigs/should_fail/WildcardInADT3.stderr | 4 + .../should_fail/WildcardInADTContext1.hs | 4 + .../should_fail/WildcardInADTContext1.stderr | 7 + .../should_fail/WildcardInADTContext2.hs | 4 + .../should_fail/WildcardInADTContext2.stderr | 7 + .../partial-sigs/should_fail/WildcardInDefault.hs | 4 + .../should_fail/WildcardInDefault.stderr | 4 + .../partial-sigs/should_fail/WildcardInDeriving.hs | 5 + .../should_fail/WildcardInDeriving.stderr | 4 + .../should_fail/WildcardInForeignExport.hs | 7 + .../should_fail/WildcardInForeignExport.stderr | 5 + .../should_fail/WildcardInForeignImport.hs | 6 + .../should_fail/WildcardInForeignImport.stderr | 5 + .../partial-sigs/should_fail/WildcardInGADT1.hs | 5 + .../should_fail/WildcardInGADT1.stderr | 4 + .../partial-sigs/should_fail/WildcardInGADT2.hs | 5 + .../should_fail/WildcardInGADT2.stderr | 4 + .../should_fail/WildcardInInstanceHead.hs | 8 + .../should_fail/WildcardInInstanceHead.stderr | 4 + .../partial-sigs/should_fail/WildcardInNewtype.hs | 7 + .../should_fail/WildcardInNewtype.stderr | 4 + .../should_fail/WildcardInPatSynSig.hs | 5 + .../should_fail/WildcardInPatSynSig.stderr | 5 + .../should_fail/WildcardInTypeFamilyInstanceLHS.hs | 8 + .../WildcardInTypeFamilyInstanceLHS.stderr | 4 + .../should_fail/WildcardInTypeFamilyInstanceRHS.hs | 8 + .../WildcardInTypeFamilyInstanceRHS.stderr | 4 + .../should_fail/WildcardInTypeSynonymLHS.hs | 4 + .../should_fail/WildcardInTypeSynonymLHS.stderr | 6 + .../should_fail/WildcardInTypeSynonymRHS.hs | 4 + .../should_fail/WildcardInTypeSynonymRHS.stderr | 4 + .../should_fail/WildcardInstantiations.hs | 9 + .../should_fail/WildcardInstantiations.stderr | 45 +++ .../should_fail/WildcardsInPatternAndExprSig.hs | 4 + .../WildcardsInPatternAndExprSig.stderr | 74 ++++ testsuite/tests/partial-sigs/should_fail/all.T | 42 +++ utils/haddock | 2 +- 219 files changed, 3384 insertions(+), 237 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d831b6f41b3b89dc4a643069d5668c05a20f3c37 From git at git.haskell.org Sat Nov 29 06:50:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Nov 2014 06:50:37 +0000 (UTC) Subject: [commit: ghc] branch 'wip/pattern-synonym-sig-backport' created Message-ID: <20141129065037.3D5F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/pattern-synonym-sig-backport Referencing: abc0160d3d423c0ea5645a3ac469066459387ef8 From git at git.haskell.org Sat Nov 29 06:50:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Nov 2014 06:50:39 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonym-sig-backport: Update pattern synonym type signature syntax to that used in GHC 7.10 (abc0160) Message-ID: <20141129065039.D59A93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/pattern-synonym-sig-backport Link : http://ghc.haskell.org/trac/ghc/changeset/abc0160d3d423c0ea5645a3ac469066459387ef8/ghc >--------------------------------------------------------------- commit abc0160d3d423c0ea5645a3ac469066459387ef8 Author: Dr. ERDI Gergo Date: Sat Nov 29 14:46:53 2014 +0800 Update pattern synonym type signature syntax to that used in GHC 7.10 >--------------------------------------------------------------- abc0160d3d423c0ea5645a3ac469066459387ef8 compiler/hsSyn/HsBinds.lhs | 39 ++++++++++++++++++--------------------- compiler/iface/IfaceSyn.lhs | 17 +++++------------ 2 files changed, 23 insertions(+), 33 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index 2261a89..769836a 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -704,34 +704,31 @@ ppr_sig (SpecSig var ty inl) = pragBrackets (pprSpec (unLoc var) (ppr ty) i ppr_sig (InlineSig var inl) = pragBrackets (ppr inl <+> pprPrefixOcc (unLoc var)) ppr_sig (SpecInstSig ty) = pragBrackets (ptext (sLit "SPECIALIZE instance") <+> ppr ty) ppr_sig (MinimalSig bf) = pragBrackets (pprMinimalSig bf) -ppr_sig (PatSynSig name arg_tys ty prov req) - = pprPatSynSig (unLoc name) False args (ppr ty) (pprCtx prov) (pprCtx req) +ppr_sig (PatSynSig name args pat_ty prov req) + = pprPatSynSig (unLoc name) empty + (pprCtx prov) (pprCtx req) + (ppr ty) where - args = fmap ppr arg_tys + arg_tys = case args of + PrefixPatSyn arg_tys -> arg_tys + InfixPatSyn left_ty right_ty -> [left_ty, right_ty] + ty = Data.List.foldr (\t1 t2 -> noLoc (HsFunTy t1 t2)) pat_ty arg_tys pprCtx lctx = case unLoc lctx of [] -> Nothing ctx -> Just (pprHsContextNoArrow ctx) -pprPatSynSig :: (OutputableBndr a) - => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> Maybe SDoc -> Maybe SDoc -> SDoc -pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta - = sep [ ptext (sLit "pattern") - , thetaOpt prov_theta, name_and_args - , colon - , thetaOpt req_theta, rhs_ty - ] +pprPatSynSig :: (OutputableBndr name) + => name -> SDoc -> Maybe SDoc -> Maybe SDoc -> SDoc -> SDoc +pprPatSynSig ident tvs prov req ty + = ptext (sLit "pattern") <+> pprPrefixOcc ident <+> dcolon <+> + tvs <+> context <+> ty where - name_and_args = case args of - PrefixPatSyn arg_tys -> - pprPrefixOcc ident <+> sep arg_tys - InfixPatSyn left_ty right_ty -> - left_ty <+> pprInfixOcc ident <+> right_ty - - -- TODO: support explicit foralls - thetaOpt = maybe empty (<+> darrow) - - colon = if is_bidir then dcolon else dcolon -- TODO + context = case (prov, req) of + (Nothing, Nothing) -> empty + (Nothing, Just req) -> parens empty <+> darrow <+> req <+> darrow + (Just prov, Nothing) -> prov <+> darrow + (Just prov, Just req) -> prov <+> darrow <+> req <+> darrow instance OutputableBndr name => Outputable (FixitySig name) where ppr (FixitySig name fixity) = sep [ppr fixity, pprInfixOcc (unLoc name)] diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index a7f1780..c06aacc 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -1104,22 +1104,15 @@ pprIfaceDecl (IfaceAxiom {ifName = name, ifTyCon = tycon, ifAxBranches = branche = hang (ptext (sLit "axiom") <+> ppr name <> dcolon) 2 (vcat $ map (pprAxBranch $ Just tycon) branches) -pprIfaceDecl (IfacePatSyn { ifName = name, ifPatWrapper = wrapper, +pprIfaceDecl (IfacePatSyn { ifName = name, ifPatWrapper = _wrapper, ifPatIsInfix = is_infix, ifPatUnivTvs = _univ_tvs, ifPatExTvs = _ex_tvs, ifPatProvCtxt = prov_ctxt, ifPatReqCtxt = req_ctxt, - ifPatArgs = args, - ifPatTy = ty }) - = pprPatSynSig name has_wrap args' ty' (pprCtxt prov_ctxt) (pprCtxt req_ctxt) + ifPatArgs = arg_tys, + ifPatTy = pat_ty }) + = pprPatSynSig name empty (pprCtxt prov_ctxt) (pprCtxt req_ctxt) (pprIfaceType ty) where - has_wrap = isJust wrapper - args' = case (is_infix, args) of - (True, [left_ty, right_ty]) -> - InfixPatSyn (pprParendIfaceType left_ty) (pprParendIfaceType right_ty) - (_, tys) -> - PrefixPatSyn (map pprParendIfaceType tys) - - ty' = pprParendIfaceType ty + ty = foldr IfaceFunTy pat_ty arg_tys pprCtxt [] = Nothing pprCtxt ctxt = Just $ pprIfaceContext ctxt From git at git.haskell.org Sat Nov 29 06:53:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Nov 2014 06:53:22 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonym-sig-backport: Update pattern synonym type signature syntax to that used in GHC 7.10 (b638fd7) Message-ID: <20141129065322.6D18C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/pattern-synonym-sig-backport Link : http://ghc.haskell.org/trac/ghc/changeset/b638fd74564458c2bab8550ec904c50de16d0427/ghc >--------------------------------------------------------------- commit b638fd74564458c2bab8550ec904c50de16d0427 Author: Dr. ERDI Gergo Date: Sat Nov 29 14:51:30 2014 +0800 Update pattern synonym type signature syntax to that used in GHC 7.10 >--------------------------------------------------------------- b638fd74564458c2bab8550ec904c50de16d0427 compiler/hsSyn/HsBinds.lhs | 39 ++++++++++++++++++--------------------- compiler/iface/IfaceSyn.lhs | 17 +++++------------ docs/users_guide/glasgow_exts.xml | 4 ++-- 3 files changed, 25 insertions(+), 35 deletions(-) diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index 2261a89..769836a 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -704,34 +704,31 @@ ppr_sig (SpecSig var ty inl) = pragBrackets (pprSpec (unLoc var) (ppr ty) i ppr_sig (InlineSig var inl) = pragBrackets (ppr inl <+> pprPrefixOcc (unLoc var)) ppr_sig (SpecInstSig ty) = pragBrackets (ptext (sLit "SPECIALIZE instance") <+> ppr ty) ppr_sig (MinimalSig bf) = pragBrackets (pprMinimalSig bf) -ppr_sig (PatSynSig name arg_tys ty prov req) - = pprPatSynSig (unLoc name) False args (ppr ty) (pprCtx prov) (pprCtx req) +ppr_sig (PatSynSig name args pat_ty prov req) + = pprPatSynSig (unLoc name) empty + (pprCtx prov) (pprCtx req) + (ppr ty) where - args = fmap ppr arg_tys + arg_tys = case args of + PrefixPatSyn arg_tys -> arg_tys + InfixPatSyn left_ty right_ty -> [left_ty, right_ty] + ty = Data.List.foldr (\t1 t2 -> noLoc (HsFunTy t1 t2)) pat_ty arg_tys pprCtx lctx = case unLoc lctx of [] -> Nothing ctx -> Just (pprHsContextNoArrow ctx) -pprPatSynSig :: (OutputableBndr a) - => a -> Bool -> HsPatSynDetails SDoc -> SDoc -> Maybe SDoc -> Maybe SDoc -> SDoc -pprPatSynSig ident is_bidir args rhs_ty prov_theta req_theta - = sep [ ptext (sLit "pattern") - , thetaOpt prov_theta, name_and_args - , colon - , thetaOpt req_theta, rhs_ty - ] +pprPatSynSig :: (OutputableBndr name) + => name -> SDoc -> Maybe SDoc -> Maybe SDoc -> SDoc -> SDoc +pprPatSynSig ident tvs prov req ty + = ptext (sLit "pattern") <+> pprPrefixOcc ident <+> dcolon <+> + tvs <+> context <+> ty where - name_and_args = case args of - PrefixPatSyn arg_tys -> - pprPrefixOcc ident <+> sep arg_tys - InfixPatSyn left_ty right_ty -> - left_ty <+> pprInfixOcc ident <+> right_ty - - -- TODO: support explicit foralls - thetaOpt = maybe empty (<+> darrow) - - colon = if is_bidir then dcolon else dcolon -- TODO + context = case (prov, req) of + (Nothing, Nothing) -> empty + (Nothing, Just req) -> parens empty <+> darrow <+> req <+> darrow + (Just prov, Nothing) -> prov <+> darrow + (Just prov, Just req) -> prov <+> darrow <+> req <+> darrow instance OutputableBndr name => Outputable (FixitySig name) where ppr (FixitySig name fixity) = sep [ppr fixity, pprInfixOcc (unLoc name)] diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index a7f1780..c06aacc 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -1104,22 +1104,15 @@ pprIfaceDecl (IfaceAxiom {ifName = name, ifTyCon = tycon, ifAxBranches = branche = hang (ptext (sLit "axiom") <+> ppr name <> dcolon) 2 (vcat $ map (pprAxBranch $ Just tycon) branches) -pprIfaceDecl (IfacePatSyn { ifName = name, ifPatWrapper = wrapper, +pprIfaceDecl (IfacePatSyn { ifName = name, ifPatWrapper = _wrapper, ifPatIsInfix = is_infix, ifPatUnivTvs = _univ_tvs, ifPatExTvs = _ex_tvs, ifPatProvCtxt = prov_ctxt, ifPatReqCtxt = req_ctxt, - ifPatArgs = args, - ifPatTy = ty }) - = pprPatSynSig name has_wrap args' ty' (pprCtxt prov_ctxt) (pprCtxt req_ctxt) + ifPatArgs = arg_tys, + ifPatTy = pat_ty }) + = pprPatSynSig name empty (pprCtxt prov_ctxt) (pprCtxt req_ctxt) (pprIfaceType ty) where - has_wrap = isJust wrapper - args' = case (is_infix, args) of - (True, [left_ty, right_ty]) -> - InfixPatSyn (pprParendIfaceType left_ty) (pprParendIfaceType right_ty) - (_, tys) -> - PrefixPatSyn (map pprParendIfaceType tys) - - ty' = pprParendIfaceType ty + ty = foldr IfaceFunTy pat_ty arg_tys pprCtxt [] = Nothing pprCtxt ctxt = Just $ pprIfaceContext ctxt diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index f56bb89..a0957e4 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -1037,7 +1037,7 @@ bidirectional. The syntax for unidirectional pattern synonyms is: it is assigned a pattern type of the form - pattern CProv => P t1 t2 ... tN :: CReq => t + pattern P :: CProv => CReq => t1 -> t2 -> ... -> tN -> t where CProv and @@ -1074,7 +1074,7 @@ the pattern type of ExNumPat is -pattern (Show b) => ExNumPat b :: (Num a, Eq a) => T a +pattern ExNumPat :: (Show b) => (Num a, Eq a) => b -> T a From git at git.haskell.org Sat Nov 29 07:42:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Nov 2014 07:42:11 +0000 (UTC) Subject: [commit: ghc] master: Update submodule 'haddock' to render 'pattern' as a keyword (f0df243) Message-ID: <20141129074211.483DD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f0df243d9b6a37628a992c5d1b16c44fe8b2c894/ghc >--------------------------------------------------------------- commit f0df243d9b6a37628a992c5d1b16c44fe8b2c894 Author: Dr. ERDI Gergo Date: Sat Nov 29 15:39:48 2014 +0800 Update submodule 'haddock' to render 'pattern' as a keyword >--------------------------------------------------------------- f0df243d9b6a37628a992c5d1b16c44fe8b2c894 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 1a9dcfe..b94ab90 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 1a9dcfef033dd66514015d4a942ba67d21f95482 +Subproject commit b94ab9034367f51b978904d60f2604db10abbd9f From git at git.haskell.org Sat Nov 29 08:32:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Nov 2014 08:32:11 +0000 (UTC) Subject: [commit: ghc] master: Minor refactoring of static C initializers (447f592) Message-ID: <20141129083211.2E2123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/447f592697fef04d1e19a2045ec707cfcd1eb59f/ghc >--------------------------------------------------------------- commit 447f592697fef04d1e19a2045ec707cfcd1eb59f Author: Herbert Valerio Riedel Date: Sat Nov 29 09:30:46 2014 +0100 Minor refactoring of static C initializers >--------------------------------------------------------------- 447f592697fef04d1e19a2045ec707cfcd1eb59f libraries/integer-gmp2/cbits/wrappers.c | 42 ++++++++++----------------------- 1 file changed, 13 insertions(+), 29 deletions(-) diff --git a/libraries/integer-gmp2/cbits/wrappers.c b/libraries/integer-gmp2/cbits/wrappers.c index 1621d3b..520c412 100644 --- a/libraries/integer-gmp2/cbits/wrappers.c +++ b/libraries/integer-gmp2/cbits/wrappers.c @@ -36,6 +36,10 @@ typedef unsigned long int mp_bitcnt_t; # error (SIZEOF_HSWORD*8) != WORD_SIZE_IN_BITS #endif +// Turn a (const) {xp,xn} pair into static initializer +#define CONST_MPZ_INIT(xp,xn) \ + {{ ._mp_alloc = 0, ._mp_size = (xn), ._mp_d = (mp_limb_t*)(xp) }} + /* Perform arithmetic right shift on MPNs (multi-precision naturals) * * pre-conditions: @@ -132,7 +136,8 @@ integer_gmp_mpn_lshift (mp_limb_t rp[], const mp_limb_t sp[], } } -/* +/* Convert bignum to a `double`, truncating if necessary + * (i.e. rounding towards zero). * * sign of mp_size_t argument controls sign of converted double */ @@ -146,17 +151,13 @@ integer_gmp_mpn_get_d (const mp_limb_t sp[], const mp_size_t sn, if (sn == 1 && sp[0] == 0) return 0.0; - __mpz_struct const mpz = { - ._mp_alloc = abs(sn), - ._mp_size = sn, - ._mp_d = (mp_limb_t*)sp - }; + const mpz_t mpz = CONST_MPZ_INIT(sp, sn); if (!exponent) - return mpz_get_d(&mpz); + return mpz_get_d(mpz); long e = 0; - double d = mpz_get_d_2exp (&e, &mpz); + double d = mpz_get_d_2exp (&e, mpz); // TODO: over/underflow handling? return ldexp(d, e+exponent); @@ -212,17 +213,8 @@ integer_gmp_mpn_gcd(mp_limb_t r[], // the cost of a few additional temporary buffer allocations in // C-land. - const mpz_t op1 = {{ - ._mp_alloc = xn, - ._mp_size = xn, - ._mp_d = (mp_limb_t*)x0 - }}; - - const mpz_t op2 = {{ - ._mp_alloc = yn, - ._mp_size = yn, - ._mp_d = (mp_limb_t*)y0 - }}; + const mpz_t op1 = CONST_MPZ_INIT(x0, xn); + const mpz_t op2 = CONST_MPZ_INIT(y0, yn); mpz_t rop; mpz_init (rop); @@ -299,11 +291,7 @@ integer_gmp_mpn_sizeinbase(const mp_limb_t s[], const mp_size_t sn, if (!sn) return 1; - const mpz_t zs = {{ - ._mp_alloc = sn, - ._mp_size = sn, - ._mp_d = (mp_limb_t*)s - }}; + const mpz_t zs = CONST_MPZ_INIT(s, sn); return mpz_sizeinbase(zs, base); } @@ -326,11 +314,7 @@ integer_gmp_mpn_export(const mp_limb_t s[], const mp_size_t sn, if (!sn || (sn == 1 && !s[0])) return 0; - const mpz_t zs = {{ - ._mp_alloc = sn, - ._mp_size = sn, - ._mp_d = (mp_limb_t*)s - }}; + const mpz_t zs = CONST_MPZ_INIT(s, sn); size_t written = 0; From git at git.haskell.org Sat Nov 29 17:34:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Nov 2014 17:34:07 +0000 (UTC) Subject: [commit: ghc] master: Fix testsuite failures after the PartialTypeSignatures merge (d108a19) Message-ID: <20141129173407.06F9C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d108a19cf6cd802c30ff1fa2758dd6aa8c049ad0/ghc >--------------------------------------------------------------- commit d108a19cf6cd802c30ff1fa2758dd6aa8c049ad0 Author: Thomas Winant Date: Sat Nov 29 11:34:36 2014 -0600 Fix testsuite failures after the PartialTypeSignatures merge Summary: Properly detect insoluble wanteds This used to be correct, but was recently incorrectly refactored. Reviewers: austin, hvr Reviewed By: austin, hvr Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D531 >--------------------------------------------------------------- d108a19cf6cd802c30ff1fa2758dd6aa8c049ad0 compiler/typecheck/TcRnTypes.lhs | 16 ++++++++++------ 1 file changed, 10 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index e14733c..cc9a769 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -49,7 +49,7 @@ module TcRnTypes( isEmptyCts, isCTyEqCan, isCFunEqCan, isCDictCan_Maybe, isCFunEqCan_maybe, isCIrredEvCan, isCNonCanonical, isWantedCt, isDerivedCt, - isGivenCt, isHoleCt, isTypedHoleCt, + isGivenCt, isHoleCt, isTypedHoleCt, isPartialTypeSigCt, ctEvidence, ctLoc, ctPred, mkNonCanonical, mkNonCanonicalCt, ctEvPred, ctEvLoc, ctEvTerm, ctEvCoercion, ctEvId, ctEvCheckDepth, @@ -1248,6 +1248,10 @@ isHoleCt _ = False isTypedHoleCt :: Ct -> Bool isTypedHoleCt (CHoleCan { cc_hole = ExprHole }) = True isTypedHoleCt _ = False + +isPartialTypeSigCt :: Ct -> Bool +isPartialTypeSigCt (CHoleCan { cc_hole = TypeHole }) = True +isPartialTypeSigCt _ = False \end{code} \begin{code} @@ -1331,11 +1335,11 @@ isEmptyWC (WC { wc_flat = f, wc_impl = i, wc_insol = n }) = isEmptyBag f && isEmptyBag i && isEmptyBag n insolubleWC :: WantedConstraints -> Bool --- True if there are any insoluble constraints in the wanted bag -insolubleWC wc = not (isEmptyBag (filterBag isTypedHoleCt (wc_insol wc))) --- TODOT actually, a wildcard constraint (CHoleCan originating from a wildcard --- in a partial type signature) is not insulible. --- insolubleWC wc = not (isEmptyBag (wc_insol wc)) +-- True if there are any insoluble constraints in the wanted bag. Ignore +-- constraints arising from PartialTypeSignatures to solve as much of the +-- constraints as possible before reporting the holes. +insolubleWC wc = not (isEmptyBag (filterBag (not . isPartialTypeSigCt) + (wc_insol wc))) || anyBag ic_insol (wc_impl wc) andWC :: WantedConstraints -> WantedConstraints -> WantedConstraints From git at git.haskell.org Sat Nov 29 17:39:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Nov 2014 17:39:35 +0000 (UTC) Subject: [commit: ghc] master: More static C initializer refactoring (a809eab) Message-ID: <20141129173935.5F8DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a809eaba4bab96e94f2dc8fe6b617c5c6f8fd565/ghc >--------------------------------------------------------------- commit a809eaba4bab96e94f2dc8fe6b617c5c6f8fd565 Author: Herbert Valerio Riedel Date: Sat Nov 29 09:53:15 2014 +0100 More static C initializer refactoring A few instances were missed in 447f592697fef04d1e19a2045ec707cfcd1eb59f Moreover, be more paranoid when testing for zero values, and try harder to avoid passing denormalized zero `mpz_t`-values into GMP functions. >--------------------------------------------------------------- a809eaba4bab96e94f2dc8fe6b617c5c6f8fd565 libraries/integer-gmp2/cbits/wrappers.c | 52 ++++++++++++++++++--------------- 1 file changed, 29 insertions(+), 23 deletions(-) diff --git a/libraries/integer-gmp2/cbits/wrappers.c b/libraries/integer-gmp2/cbits/wrappers.c index 520c412..a1a78e0 100644 --- a/libraries/integer-gmp2/cbits/wrappers.c +++ b/libraries/integer-gmp2/cbits/wrappers.c @@ -1,3 +1,12 @@ +/* + * `integer-gmp` GMP FFI wrappers + * + * Copyright (c) 2014, Herbert Valerio Riedel + * + * BSD3 licensed, see ../LICENSE file for details + * + */ + #define _ISOC99_SOURCE #include @@ -40,6 +49,13 @@ typedef unsigned long int mp_bitcnt_t; #define CONST_MPZ_INIT(xp,xn) \ {{ ._mp_alloc = 0, ._mp_size = (xn), ._mp_d = (mp_limb_t*)(xp) }} +// Test if {sp,sn} represents a zero value +static inline int +mp_limb_zero_p(const mp_limb_t sp[], mp_size_t sn) +{ + return !sn || ((sn == 1 || sn == -1) && !sp[0]); +} + /* Perform arithmetic right shift on MPNs (multi-precision naturals) * * pre-conditions: @@ -145,10 +161,7 @@ HsDouble integer_gmp_mpn_get_d (const mp_limb_t sp[], const mp_size_t sn, const HsInt exponent) { - if (sn == 0) - return 0.0; // should not happen - - if (sn == 1 && sp[0] == 0) + if (mp_limb_zero_p(sp, sn)) return 0.0; const mpz_t mpz = CONST_MPZ_INIT(sp, sn); @@ -289,7 +302,7 @@ integer_gmp_mpn_sizeinbase(const mp_limb_t s[], const mp_size_t sn, { assert (2 <= base && base <= 256); - if (!sn) return 1; + if (mp_limb_zero_p(s,sn)) return 1; const mpz_t zs = CONST_MPZ_INIT(s, sn); @@ -311,8 +324,7 @@ integer_gmp_mpn_export(const mp_limb_t s[], const mp_size_t sn, /* TODO: implement w/o GMP, c.f. 'integer_gmp_mpn_import()' */ assert (msbf == 0 || msbf == 1); - if (!sn || (sn == 1 && !s[0])) - return 0; + if (mp_limb_zero_p(s,sn)) return 0; const mpz_t zs = CONST_MPZ_INIT(s, sn); @@ -438,13 +450,9 @@ integer_gmp_rscan_nzbyte(const uint8_t *srcptr, HsInt integer_gmp_test_prime(const mp_limb_t s[], const mp_size_t sn, const HsInt rep) { - if (!sn) return 0; + if (mp_limb_zero_p(s,sn)) return 0; - const mpz_t sz = {{ - ._mp_alloc = sn, - ._mp_size = sn, - ._mp_d = (mp_limb_t*)s - }}; + const mpz_t sz = CONST_MPZ_INIT(s, sn); // int mpz_probab_prime_p (const mpz_t n, int reps) return mpz_probab_prime_p(sz, rep); @@ -468,13 +476,15 @@ mp_limb_t integer_gmp_next_prime(mp_limb_t rp[], const mp_limb_t sp[], const mp_size_t sn) { + assert (sn>=0); + if (!sn) return 2; + if (sn == 1 && sp[0] < 2) { + rp[0] = 2; + return 0; + } - const mpz_t op = {{ - ._mp_alloc = sn, - ._mp_size = sn, - ._mp_d = (mp_limb_t*)sp - }}; + const mpz_t op = CONST_MPZ_INIT(sp, sn); mpz_t rop; mpz_init (rop); @@ -501,11 +511,7 @@ integer_gmp_next_prime1(const mp_limb_t limb) { if (limb < 2) return 2; - const mpz_t op = {{ - ._mp_alloc = 1, - ._mp_size = 1, - ._mp_d = (mp_limb_t*)(&limb) - }}; + const mpz_t op = CONST_MPZ_INIT(&limb, 1); mpz_t rop; mpz_init (rop); From git at git.haskell.org Sat Nov 29 17:46:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Nov 2014 17:46:01 +0000 (UTC) Subject: [commit: ghc] master: Implement `GHC.Natural.powModNatural` (#9818) (859680f) Message-ID: <20141129174601.40FDD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/859680f6fe952ecbef3395fa4f299530d0f10c58/ghc >--------------------------------------------------------------- commit 859680f6fe952ecbef3395fa4f299530d0f10c58 Author: Herbert Valerio Riedel Date: Sat Nov 29 13:02:42 2014 +0100 Implement `GHC.Natural.powModNatural` (#9818) This makes use of the `powMod*` primitives provided by `integer-gmp-1.0.0`. This is the `Natural`-version of the related `GHC.Integer.GMP.Internals.powModInteger` operation. The fallback implementation uses a square and multiply algorithm, compared to which the optimized GMP-based implementation needs much less allocations due to in-place mutation during the computation. >--------------------------------------------------------------- 859680f6fe952ecbef3395fa4f299530d0f10c58 libraries/base/GHC/Natural.hs | 40 ++++++++++++++++++++++++++++++++++++++++ 1 file changed, 40 insertions(+) diff --git a/libraries/base/GHC/Natural.hs b/libraries/base/GHC/Natural.hs index 221bc31..3519bcf 100644 --- a/libraries/base/GHC/Natural.hs +++ b/libraries/base/GHC/Natural.hs @@ -41,6 +41,8 @@ module GHC.Natural , naturalToWordMaybe -- * Checked subtraction , minusNaturalMaybe + -- * Modular arithmetic + , powModNatural ) where #include "MachDeps.h" @@ -410,6 +412,10 @@ bigNatToNatural bn | isTrue# (isNullBigNat# bn) = throw Underflow | otherwise = NatJ# bn +naturalToBigNat :: Natural -> BigNat +naturalToBigNat (NatS# w#) = wordToBigNat w# +naturalToBigNat (NatJ# bn) = bn + -- | Convert 'Int' to 'Natural'. -- Throws 'Underflow' when passed a negative 'Int'. intToNatural :: Int -> Natural @@ -602,3 +608,37 @@ instance Data Natural where _ -> error $ "Data.Data.gunfold: Constructor " ++ show c ++ " is not of type Natural" dataTypeOf _ = naturalType + +-- | \"@'powModNatural' /b/ /e/ /m/@\" computes base @/b/@ raised to +-- exponent @/e/@ modulo @/m/@. +-- +-- /Since: 4.8.0.0/ +powModNatural :: Natural -> Natural -> Natural -> Natural +#if HAVE_GMP_BIGNAT +powModNatural _ _ (NatS# 0##) = throw DivideByZero +powModNatural _ _ (NatS# 1##) = NatS# 0## +powModNatural _ (NatS# 0##) _ = NatS# 1## +powModNatural (NatS# 0##) _ _ = NatS# 0## +powModNatural (NatS# 1##) _ _ = NatS# 1## +powModNatural (NatS# b) (NatS# e) (NatS# m) = NatS# (powModWord b e m) +powModNatural b e (NatS# m) + = NatS# (powModBigNatWord (naturalToBigNat b) (naturalToBigNat e) m) +powModNatural b e (NatJ# m) + = bigNatToNatural (powModBigNat (naturalToBigNat b) (naturalToBigNat e) m) +#else +-- Portable reference fallback implementation +powModNatural _ _ 0 = throw DivideByZero +powModNatural _ _ 1 = 0 +powModNatural _ 0 _ = 1 +powModNatural 0 _ _ = 0 +powModNatural 1 _ _ = 1 +powModNatural b0 e0 m = go b0 e0 1 + where + go !b e !r + | odd e = go b' e' (r*b `mod` m) + | e == 0 = r + | otherwise = go b' e' r + where + b' = b*b `mod` m + e' = e `unsafeShiftR` 1 -- slightly faster than "e `div` 2" +#endif From git at git.haskell.org Sat Nov 29 17:46:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Nov 2014 17:46:03 +0000 (UTC) Subject: [commit: ghc] master: Re-implement `powModInteger` (#9281) (d0d4674) Message-ID: <20141129174603.D30D33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d0d4674281a80e4148a82f833948c2b4c3051eab/ghc >--------------------------------------------------------------- commit d0d4674281a80e4148a82f833948c2b4c3051eab Author: Herbert Valerio Riedel Date: Sat Nov 29 12:18:25 2014 +0100 Re-implement `powModInteger` (#9281) This also exposes the following type-specialised modular exponentiation variants of `powModInteger` useful for implementing a `powModNatural` operation. powModBigNat :: BigNat -> BigNat -> BigNat -> BigNat powModBigNatWord :: BigNat -> BigNat -> Word# -> Word# powModWord :: Word# -> Word# -> Word# -> Word# `powModInteger` has been available since `integer-gmp-0.5.1` (added via 4d516855241b70eb687d95e3c121428de885e83e) >--------------------------------------------------------------- d0d4674281a80e4148a82f833948c2b4c3051eab libraries/integer-gmp2/cbits/wrappers.c | 89 +++++++++++++++ libraries/integer-gmp2/include/HsIntegerGmp.h.in | 2 - .../integer-gmp2/src/GHC/Integer/GMP/Internals.hs | 5 + libraries/integer-gmp2/src/GHC/Integer/Type.hs | 120 +++++++++++++++++++++ testsuite/tests/lib/integer/integerGmpInternals.hs | 13 +-- 5 files changed, 215 insertions(+), 14 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d0d4674281a80e4148a82f833948c2b4c3051eab From git at git.haskell.org Sat Nov 29 17:49:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Nov 2014 17:49:06 +0000 (UTC) Subject: [commit: ghc] master: Re-implement `recipModInteger` (#9281) (83c4843) Message-ID: <20141129174906.1749A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/83c48438c800986c537d3cae682d53ee8ed326ed/ghc >--------------------------------------------------------------- commit 83c48438c800986c537d3cae682d53ee8ed326ed Author: Herbert Valerio Riedel Date: Sat Nov 29 14:34:41 2014 +0100 Re-implement `recipModInteger` (#9281) This also exposes the following two type-specialised modular exponentiation variants of `recipModInteger` useful for implementing a `recipModNatural` operation. recipModBigNat :: BigNat -> BigNat -> BigNat recipModWord :: Word# -> Word# -> Word# `recipModInteger` has been available since `integer-gmp-0.5.1` (added via 4d516855241b70eb687d95e3c121428de885e83e) >--------------------------------------------------------------- 83c48438c800986c537d3cae682d53ee8ed326ed libraries/integer-gmp2/cbits/wrappers.c | 72 ++++++++++++++++++++++ .../integer-gmp2/src/GHC/Integer/GMP/Internals.hs | 4 ++ libraries/integer-gmp2/src/GHC/Integer/Type.hs | 47 ++++++++++++++ testsuite/tests/lib/integer/integerGmpInternals.hs | 11 +--- 4 files changed, 124 insertions(+), 10 deletions(-) diff --git a/libraries/integer-gmp2/cbits/wrappers.c b/libraries/integer-gmp2/cbits/wrappers.c index 52920ec..3023816 100644 --- a/libraries/integer-gmp2/cbits/wrappers.c +++ b/libraries/integer-gmp2/cbits/wrappers.c @@ -611,3 +611,75 @@ integer_gmp_powm_word(const mp_limb_t b0, // base { return integer_gmp_powm1(&b0, !!b0, &e0, !!e0, m0); } + + +/* wrapper around mpz_invert() + * + * Store '(1/X) mod abs(M)' in {rp,rn} + * + * rp must have allocated mn limbs; This function's return value is + * the actual number rn (0 < rn <= mn) of limbs written to the rp limb-array. + * + * Returns 0 if inverse does not exist. + */ +mp_size_t +integer_gmp_invert(mp_limb_t rp[], // result + const mp_limb_t xp[], const mp_size_t xn, // base + const mp_limb_t mp[], const mp_size_t mn) // mod +{ + if (mp_limb_zero_p(xp,xn) + || mp_limb_zero_p(mp,mn) + || ((mn == 1 || mn == -1) && mp[0] == 1)) { + rp[0] = 0; + return 1; + } + + const mpz_t x = CONST_MPZ_INIT(xp, xn); + const mpz_t m = CONST_MPZ_INIT(mp, mn); + + mpz_t r; + mpz_init (r); + + const int inv_exists = mpz_invert(r, x, m); + + const mp_size_t rn = inv_exists ? r[0]._mp_size : 0; + + if (rn) { + assert(0 < rn && rn <= mn); + memcpy(rp, r[0]._mp_d, rn*sizeof(mp_limb_t)); + } + + mpz_clear (r); + + if (!rn) { + rp[0] = 0; + return 1; + } + + return rn; +} + + +/* Version of integer_gmp_invert() operating on single limbs */ +mp_limb_t +integer_gmp_invert_word(const mp_limb_t x0, const mp_limb_t m0) +{ + if (!x0 || m0<=1) return 0; + if (x0 == 1) return 1; + + const mpz_t x = CONST_MPZ_INIT(&x0, 1); + const mpz_t m = CONST_MPZ_INIT(&m0, 1); + + mpz_t r; + mpz_init (r); + + const int inv_exists = mpz_invert(r, x, m); + const mp_size_t rn = inv_exists ? r[0]._mp_size : 0; + + assert (rn == 0 || rn == 1); + const mp_limb_t r0 = rn ? r[0]._mp_d[0] : 0; + + mpz_clear (r); + + return r0; +} diff --git a/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs b/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs index f7b9513..9559755 100644 --- a/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs +++ b/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs @@ -47,6 +47,7 @@ module GHC.Integer.GMP.Internals , lcmInteger , sqrInteger , powModInteger + , recipModInteger -- ** Additional conversion operations to 'Integer' , wordToNegInteger @@ -98,6 +99,8 @@ module GHC.Integer.GMP.Internals , powModBigNat , powModBigNatWord + , recipModBigNat + -- ** 'BigNat' logic operations , shiftRBigNat , shiftLBigNat @@ -124,6 +127,7 @@ module GHC.Integer.GMP.Internals , gcdInt , gcdWord , powModWord + , recipModWord -- * Primality tests , testPrimeInteger diff --git a/libraries/integer-gmp2/src/GHC/Integer/Type.hs b/libraries/integer-gmp2/src/GHC/Integer/Type.hs index 8fe1d15..6284917 100644 --- a/libraries/integer-gmp2/src/GHC/Integer/Type.hs +++ b/libraries/integer-gmp2/src/GHC/Integer/Type.hs @@ -1340,6 +1340,53 @@ foreign import ccall unsafe "integer_gmp_powm1" integer_gmp_powm1# :: ByteArray# -> GmpSize# -> ByteArray# -> GmpSize# -> GmpLimb# -> GmpLimb# + +-- | \"@'recipModInteger' /x/ /m/@\" computes the inverse of @/x/@ modulo @/m/@. If +-- the inverse exists, the return value @/y/@ will satisfy @0 < /y/ < +-- abs(/m/)@, otherwise the result is @0 at . +-- +-- /Since: 0.5.1.0/ +{-# NOINLINE recipModInteger #-} +recipModInteger :: Integer -> Integer -> Integer +recipModInteger (S# x#) (S# m#) + | isTrue# (x# >=# 0#) + = wordToInteger (recipModWord (int2Word# x#) (int2Word# (absI# m#))) +recipModInteger x m = bigNatToInteger (recipModSBigNat x' m') + where + x' = integerToSBigNat x + m' = absSBigNat (integerToSBigNat m) + +-- | Version of 'recipModInteger' operating on 'BigNat's +-- +-- /Since: 1.0.0.0/ +recipModBigNat :: BigNat -> BigNat -> BigNat +recipModBigNat x m = inline recipModSBigNat (PosBN x) m + +-- | Version of 'recipModInteger' operating on 'Word#'s +-- +-- /Since: 1.0.0.0/ +foreign import ccall unsafe "integer_gmp_invert_word" + recipModWord :: GmpLimb# -> GmpLimb# -> GmpLimb# + +-- internal non-exported helper +recipModSBigNat :: SBigNat -> BigNat -> BigNat +recipModSBigNat x m@(BN# m#) = runS $ do + r@(MBN# r#) <- newBigNat# mn# + I# rn_# <- liftIO (integer_gmp_invert# r# x# xn# m# mn#) + let rn# = narrowGmpSize# rn_# + case rn# ==# mn# of + 0# -> unsafeShrinkFreezeBigNat# r rn# + _ -> unsafeFreezeBigNat# r + where + !(BN# x#) = absSBigNat x + xn# = ssizeofSBigNat# x + mn# = sizeofBigNat# m + +foreign import ccall unsafe "integer_gmp_invert" + integer_gmp_invert# :: MutableByteArray# RealWorld + -> ByteArray# -> GmpSize# + -> ByteArray# -> GmpSize# -> IO GmpSize + ---------------------------------------------------------------------------- -- Conversions to/from floating point diff --git a/testsuite/tests/lib/integer/integerGmpInternals.hs b/testsuite/tests/lib/integer/integerGmpInternals.hs index d281b73..2f49a75 100644 --- a/testsuite/tests/lib/integer/integerGmpInternals.hs +++ b/testsuite/tests/lib/integer/integerGmpInternals.hs @@ -17,17 +17,8 @@ import qualified GHC.Integer.GMP.Internals as I -- so we use naive reference-implementations instead for the meantime -- in order to keep the reference-output untouched. --- FIXME: Lacks GMP2 version --- stolen from `arithmoi` package recipModInteger :: Integer -> Integer -> Integer -recipModInteger k 0 = if k == 1 || k == (-1) then k else 0 -recipModInteger k m = case gcdExtInteger k' m' of - (1, u) -> if u < 0 then m' + u else u - _ -> 0 - where - m' = abs m - k' | k >= m' || k < 0 = k `mod` m' - | otherwise = k +recipModInteger = I.recipModInteger -- FIXME: Lacks GMP2 version gcdExtInteger :: Integer -> Integer -> (Integer, Integer) From git at git.haskell.org Sat Nov 29 17:51:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Nov 2014 17:51:04 +0000 (UTC) Subject: [commit: ghc] master: Reimplement `gcdExtInteger` (#9281) (c0e0ca4) Message-ID: <20141129175104.BD4683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c0e0ca4d9d5ed47a5e9c88eeab9b538bc76a4eb5/ghc >--------------------------------------------------------------- commit c0e0ca4d9d5ed47a5e9c88eeab9b538bc76a4eb5 Author: Herbert Valerio Riedel Date: Sat Nov 29 17:19:05 2014 +0100 Reimplement `gcdExtInteger` (#9281) `gcdExtInteger` has been available since `integer-gmp-0.5.1` (added via 71e29584603cff38e7b83d3eb28b248362569d61) >--------------------------------------------------------------- c0e0ca4d9d5ed47a5e9c88eeab9b538bc76a4eb5 libraries/integer-gmp2/cbits/wrappers.c | 66 ++++++++++++++++++++++ .../integer-gmp2/src/GHC/Integer/GMP/Internals.hs | 1 + libraries/integer-gmp2/src/GHC/Integer/Type.hs | 48 ++++++++++++++++ testsuite/tests/lib/integer/integerGmpInternals.hs | 12 +--- 4 files changed, 116 insertions(+), 11 deletions(-) diff --git a/libraries/integer-gmp2/cbits/wrappers.c b/libraries/integer-gmp2/cbits/wrappers.c index 3023816..0557ff7 100644 --- a/libraries/integer-gmp2/cbits/wrappers.c +++ b/libraries/integer-gmp2/cbits/wrappers.c @@ -56,6 +56,24 @@ mp_limb_zero_p(const mp_limb_t sp[], mp_size_t sn) return !sn || ((sn == 1 || sn == -1) && !sp[0]); } +static inline mp_size_t +mp_size_abs(const mp_size_t x) +{ + return x>=0 ? x : -x; +} + +static inline mp_size_t +mp_size_min(const mp_size_t x, const mp_size_t y) +{ + return x Integer -> (# Integer, Integer #) +gcdExtInteger a b = case gcdExtSBigNat a' b' of + (# g, s #) -> let !g' = bigNatToInteger g + !s' = sBigNatToInteger s + in (# g', s' #) + where + a' = integerToSBigNat a + b' = integerToSBigNat b + +-- internal helper +gcdExtSBigNat :: SBigNat -> SBigNat -> (# BigNat, SBigNat #) +gcdExtSBigNat x y = case runS go of (g,s) -> (# g, s #) + where + go = do + g@(MBN# g#) <- newBigNat# gn0# + s@(MBN# s#) <- newBigNat# (absI# xn#) + I# ssn_# <- liftIO (integer_gmp_gcdext# s# g# x# xn# y# yn#) + let ssn# = narrowGmpSize# ssn_# + sn# = absI# ssn# + s' <- unsafeShrinkFreezeBigNat# s sn# + g' <- unsafeRenormFreezeBigNat# g + case ssn# >=# 0# of + 0# -> return ( g', NegBN s' ) + _ -> return ( g', PosBN s' ) + + !(BN# x#) = absSBigNat x + !(BN# y#) = absSBigNat y + xn# = ssizeofSBigNat# x + yn# = ssizeofSBigNat# y + + gn0# = minI# (absI# xn#) (absI# yn#) + ---------------------------------------------------------------------------- -- modular exponentiation @@ -1446,6 +1485,11 @@ foreign import ccall unsafe "integer_gmp_mpn_gcd" c_mpn_gcd# :: MutableByteArray# s -> ByteArray# -> GmpSize# -> ByteArray# -> GmpSize# -> IO GmpSize +foreign import ccall unsafe "integer_gmp_gcdext" + integer_gmp_gcdext# :: MutableByteArray# s -> MutableByteArray# s + -> ByteArray# -> GmpSize# + -> ByteArray# -> GmpSize# -> IO GmpSize + -- mp_limb_t mpn_add_1 (mp_limb_t *rp, const mp_limb_t *s1p, mp_size_t n, -- mp_limb_t s2limb) foreign import ccall unsafe "gmp.h __gmpn_add_1" @@ -1952,3 +1996,7 @@ sgnI# x# = (x# ># 0#) -# (x# <# 0#) cmpI# :: Int# -> Int# -> Int# cmpI# x# y# = (x# ># y#) -# (x# <# y#) + +minI# :: Int# -> Int# -> Int# +minI# x# y# | isTrue# (x# <=# y#) = x# + | True = y# diff --git a/testsuite/tests/lib/integer/integerGmpInternals.hs b/testsuite/tests/lib/integer/integerGmpInternals.hs index 2f49a75..628f8e0 100644 --- a/testsuite/tests/lib/integer/integerGmpInternals.hs +++ b/testsuite/tests/lib/integer/integerGmpInternals.hs @@ -22,17 +22,7 @@ recipModInteger = I.recipModInteger -- FIXME: Lacks GMP2 version gcdExtInteger :: Integer -> Integer -> (Integer, Integer) -gcdExtInteger a b = (d, u) -- stolen from `arithmoi` package - where - (d, x, y) = eGCD 0 1 1 0 (abs a) (abs b) - u | a < 0 = negate x - | otherwise = x - v | b < 0 = negate y - | otherwise = y - eGCD !n1 o1 !n2 o2 r s - | s == 0 = (r, o1, o2) - | otherwise = case r `quotRem` s of - (q, t) -> eGCD (o1 - q*n1) n1 (o2 - q*n2) n2 s t +gcdExtInteger a b = case I.gcdExtInteger a b of (# g, s #) -> (g, s) -- FIXME: Lacks GMP2 version powModSecInteger :: Integer -> Integer -> Integer -> Integer From git at git.haskell.org Sun Nov 30 09:37:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Nov 2014 09:37:38 +0000 (UTC) Subject: [commit: ghc] branch 'ghc-instvis' created Message-ID: <20141130093738.1FD4B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : ghc-instvis Referencing: 4c834fdddf4d44d12039da4d6a2c63a660975b95 From git at git.haskell.org Sun Nov 30 09:37:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Nov 2014 09:37:42 +0000 (UTC) Subject: [commit: ghc] ghc-instvis: Filter instance visibility based on set of visible orphans, fixes #2182. (4c834fd) Message-ID: <20141130093742.0A0653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-instvis Link : http://ghc.haskell.org/trac/ghc/changeset/4c834fdddf4d44d12039da4d6a2c63a660975b95/ghc >--------------------------------------------------------------- commit 4c834fdddf4d44d12039da4d6a2c63a660975b95 Author: Edward Z. Yang Date: Mon Nov 17 21:23:52 2014 -0800 Filter instance visibility based on set of visible orphans, fixes #2182. Summary: Amazingly, the fix for this very old bug is quite simple: when type-checking, maintain a set of "visible orphan modules" based on the orphans list of modules which we explicitly imported. When we import an instance and it is an orphan, we check if it is in the visible modules set, and if not, ignore it. A little bit of refactoring for when orphan-hood is calculated happens so that we always know if an instance is an orphan or not. For GHCi, we preinitialize the visible modules set based on the list of interactive imports which are active. Future work: Cache the visible orphan modules set for GHCi, rather than recomputing it every type-checking round. (But it's tricky what to do when you /remove/ a module: you need a data structure a little more complicated than just a set of modules.) Signed-off-by: Edward Z. Yang Test Plan: new tests and validate Reviewers: simonpj, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D488 GHC Trac Issues: #2182 >--------------------------------------------------------------- 4c834fdddf4d44d12039da4d6a2c63a660975b95 compiler/basicTypes/Module.lhs | 7 +- compiler/iface/IfaceSyn.lhs | 7 +- compiler/iface/MkIface.lhs | 55 +++------ compiler/iface/TcIface.lhs | 5 +- compiler/main/HscTypes.lhs | 10 +- compiler/typecheck/FunDeps.lhs | 4 +- compiler/typecheck/Inst.lhs | 13 +- compiler/typecheck/TcEnv.lhs | 8 +- compiler/typecheck/TcPluginM.hs | 2 +- compiler/typecheck/TcRnDriver.lhs | 22 +++- compiler/typecheck/TcRnMonad.lhs | 9 +- compiler/typecheck/TcRnTypes.lhs | 5 + compiler/typecheck/TcSMonad.lhs | 2 +- compiler/types/InstEnv.lhs | 137 ++++++++++++++++++--- compiler/vectorise/Vectorise/Env.hs | 9 +- compiler/vectorise/Vectorise/Monad.hs | 7 +- testsuite/tests/driver/Makefile | 5 + testsuite/tests/driver/T2182.hs | 6 + testsuite/tests/driver/T2182.stderr | 28 +++++ testsuite/tests/driver/T2182_A.hs | 4 + testsuite/tests/driver/all.T | 1 + .../tests/ghci.debugger/scripts/break006.stderr | 22 ++-- .../tests/ghci.debugger/scripts/print019.stderr | 12 +- testsuite/tests/ghci/scripts/T2182ghci.script | 49 ++++++++ testsuite/tests/ghci/scripts/T2182ghci.stderr | 30 +++++ testsuite/tests/ghci/scripts/T2182ghci.stdout | 22 ++++ testsuite/tests/ghci/scripts/T2182ghci2.script | 15 +++ testsuite/tests/ghci/scripts/T2182ghci2.stderr | 10 ++ testsuite/tests/ghci/scripts/T2182ghci2.stdout | 4 + testsuite/tests/ghci/scripts/T2182ghci_A.hs | 4 + testsuite/tests/ghci/scripts/T2182ghci_B.hs | 2 + testsuite/tests/ghci/scripts/T2182ghci_C.hs | 2 + testsuite/tests/ghci/scripts/all.T | 2 + testsuite/tests/typecheck/should_fail/T5095.stderr | 7 ++ 34 files changed, 429 insertions(+), 98 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4c834fdddf4d44d12039da4d6a2c63a660975b95 From git at git.haskell.org Sun Nov 30 09:37:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Nov 2014 09:37:44 +0000 (UTC) Subject: [commit: ghc] ghc-instvis: Special case interactive package key for mkQualPackage. (46c53d5) Message-ID: <20141130093744.9D7863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-instvis Link : http://ghc.haskell.org/trac/ghc/changeset/46c53d5ce5a1d00f29ffea0c3741d972e4beab97/ghc >--------------------------------------------------------------- commit 46c53d5ce5a1d00f29ffea0c3741d972e4beab97 Author: Edward Z. Yang Date: Tue Nov 18 04:17:57 2014 -0800 Special case interactive package key for mkQualPackage. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 46c53d5ce5a1d00f29ffea0c3741d972e4beab97 compiler/main/HscTypes.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs index 0c73c14..bb3fd38 100644 --- a/compiler/main/HscTypes.lhs +++ b/compiler/main/HscTypes.lhs @@ -1494,7 +1494,7 @@ mkQualModule dflags mod -- with a package key if the package ID would be ambiguous. mkQualPackage :: DynFlags -> QueryQualifyPackage mkQualPackage dflags pkg_key - | pkg_key == mainPackageKey + | pkg_key == mainPackageKey || pkg_key == interactivePackageKey -- Skip the lookup if it's main, since it won't be in the package -- database! = False From git at git.haskell.org Sun Nov 30 09:37:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Nov 2014 09:37:56 +0000 (UTC) Subject: [commit: ghc] master's head updated: Filter instance visibility based on set of visible orphans, fixes #2182. (4c834fd) Message-ID: <20141130093756.233003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: 46c53d5 Special case interactive package key for mkQualPackage. 4c834fd Filter instance visibility based on set of visible orphans, fixes #2182. From git at git.haskell.org Sun Nov 30 18:01:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Nov 2014 18:01:33 +0000 (UTC) Subject: [commit: ghc] master: Shorten long lines in DynFlags, add details to ghci usage guide. (6d47ab3) Message-ID: <20141130180133.4FA1F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6d47ab3ab3684c4245bdccd97d19db83887aae9c/ghc >--------------------------------------------------------------- commit 6d47ab3ab3684c4245bdccd97d19db83887aae9c Author: Lennart Kolmodin Date: Sun Nov 30 11:58:17 2014 -0600 Shorten long lines in DynFlags, add details to ghci usage guide. Summary: Shorten long lines in DynFlags. Describe --show-options in ghci usage guide. Reviewers: jstolarek, austin Reviewed By: jstolarek, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D532 GHC Trac Issues: #9259 >--------------------------------------------------------------- 6d47ab3ab3684c4245bdccd97d19db83887aae9c compiler/main/DynFlags.hs | 894 ++++++++++++++++++++++++++-------------------- driver/ghci-usage.txt | 3 + 2 files changed, 504 insertions(+), 393 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6d47ab3ab3684c4245bdccd97d19db83887aae9c From git at git.haskell.org Sun Nov 30 18:01:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Nov 2014 18:01:36 +0000 (UTC) Subject: [commit: ghc] master: More Tweaks for API Anotations (ed85d7e) Message-ID: <20141130180136.017CE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ed85d7e1ab0384bf00729b9b2fd1ef6bf25caebc/ghc >--------------------------------------------------------------- commit ed85d7e1ab0384bf00729b9b2fd1ef6bf25caebc Author: Alan Zimmerman Date: Sun Nov 30 11:58:31 2014 -0600 More Tweaks for API Anotations Summary: Attaching semis to preceding AST element, not following Test Plan: sh ./validate Reviewers: hvr, austin Reviewed By: austin Subscribers: cactus, thomie, carter Differential Revision: https://phabricator.haskell.org/D529 >--------------------------------------------------------------- ed85d7e1ab0384bf00729b9b2fd1ef6bf25caebc compiler/hsSyn/HsBinds.lhs | 20 +++-- compiler/hsSyn/HsTypes.lhs | 2 + compiler/parser/ApiAnnotation.hs | 1 + compiler/parser/Parser.y | 91 +++++++++++++++------- compiler/parser/RdrHsSyn.hs | 4 +- .../tests/ghc-api/annotations/annotations.stdout | 6 +- .../tests/ghc-api/annotations/comments.stdout | 7 +- .../tests/ghc-api/annotations/parseTree.stdout | 10 +-- 8 files changed, 94 insertions(+), 47 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ed85d7e1ab0384bf00729b9b2fd1ef6bf25caebc From git at git.haskell.org Sun Nov 30 18:01:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Nov 2014 18:01:39 +0000 (UTC) Subject: [commit: ghc] master: Add bash completion and README (643635e) Message-ID: <20141130180139.210693A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/643635ea1d779054e1bb3b1825cd7894c5748811/ghc >--------------------------------------------------------------- commit 643635ea1d779054e1bb3b1825cd7894c5748811 Author: Lennart Kolmodin Date: Sun Nov 30 11:59:59 2014 -0600 Add bash completion and README Summary: The bash completion is simple but works both for ghc and ghci. The README explains to the user what they have to do to get it working (hopefully nothing). Test Plan: Follow the README, then enjoy the cli completion in your terminal! Reviewers: austin Subscribers: thomie, carter, jstolarek Differential Revision: https://phabricator.haskell.org/D536 GHC Trac Issues: #9005 >--------------------------------------------------------------- 643635ea1d779054e1bb3b1825cd7894c5748811 completion/README | 43 ++++++++++++++++++++++++++++++++++++++ completion/ghc.bash | 60 +++++++++++++++++++++++++++++++++++++++++++++++++++++ 2 files changed, 103 insertions(+) diff --git a/completion/README b/completion/README new file mode 100644 index 0000000..18b171c --- /dev/null +++ b/completion/README @@ -0,0 +1,43 @@ +======================================== +Glasgow Haskell Compiler Bash Completion +======================================== + +Depending on how you've installed GHC, there are different ways to turn +on the bash completion. With a bit of luck, your OS distribution has already +setup everything and it's already working! But since you're reading this file, +we assume that was not the case. Read on! + + +Option 1: Using your OS distribution's tools +-------------------------------------------- + +This should work if you installed GHC using the package manager of your *nix +distribution. You need the 'bash-completion' package from your package manager +(likely already installed), and something like this in your ~/.bashrc file; + + if [ -f /usr/share/bash-completion/bash_completion ]; then + . /usr/share/bash-completion/bash_completion + elif [ -f /etc/bash_completion ]; then + . /etc/bash_completion + fi + +When you installed GHC using your OS distribution's package manager it should +have copied the bash completion file to the right directory. +Open a new terminal and try it out! + + +Option 2: Without OS distribution support +----------------------------------------- + +Maybe your OS distribution doesn't support GHC's bash completion, maybe +you've installed your own build of GHC. In either case, you can still have +bash completion! You can even use GHC's bash completion without the +'bash-completion' package. Here are the steps; + + 1) Copy the ghc.bash file somewhere (eg. ~/ghc.bash) or use it directly from + the source directory. + 2) Add the following to your ~/.bashrc; + + source ~/ghc.bash + +That's it! diff --git a/completion/ghc.bash b/completion/ghc.bash new file mode 100755 index 0000000..af5bf9b --- /dev/null +++ b/completion/ghc.bash @@ -0,0 +1,60 @@ +# ======================================== +# Glasgow Haskell Compiler Bash Completion +# ======================================== +# +# For how to use the GHC bash completion, see the README. +# +# This file implements bash completion for both GHC and GHCi. +# +# - We use GHC's --show-options to get a list of the available +# flags. It is aware that some flags are used for GHC, and others for GHCi. +# - We understand when the argument; +# * has to be a directory name (eg. following -hidir) +# * cannot be completed (eg. following -e) +# +# Future work; +# - Some flags needs their argument after an equal sign; +# eg. -fmax-simplifier-iterations=N +# Currently the flag will be completed without knowledge of +# the required argument. +# - Complete package names/ids. +# eg. -package-id should list valid package-ids +# - The +RTS flags are not supported. +# +RTS should list valid RTS flags. + +_ghc () +{ + local completions=`$1 --show-options` + local cur="${COMP_WORDS[COMP_CWORD]}" + local prev="${COMP_WORDS[COMP_CWORD-1]}" + + # Complete the current flag based on the previous flag. + case "$prev" in + -hidir|-odir|-stubdir|-dumpdir|-outputdir|-tmpdir|-hpcdir|-dylib-install-name|-framework-path) + # Complete only with directory names. + compopt -o dirnames + return 0 + ;; + -package-name|-package|-hide-package|-ignore-package|-trust|-distrust) + # Should complete package names. Not implemented. + # To do this well, ghc has to be invoked with --show-packages with all + # package related flags the user has provided. + return 0 + ;; + -e|-x|-hcsuf|-hisuf|-osuf|-framework) + # Do nothing. Next argument is not a flag. + return 0 + ;; + esac + + # Look at the current flag. + if [[ "$cur" == -* ]]; then + # All GHC flags start with a dash, so we want to see this before we start + # suggesting flags. Otherwise we would complete flags when the user might + # want to type a file name. + COMPREPLY=( $( compgen -W "$completions -x" -- "$cur" ) ) + fi +} + +complete -F _ghc -o default ghc +complete -F _ghc -o default ghci From git at git.haskell.org Sun Nov 30 18:01:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Nov 2014 18:01:41 +0000 (UTC) Subject: [commit: ghc] master: Fix obscure problem with using the system linker (#8935) (383733b) Message-ID: <20141130180141.C26E63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/383733b9191a36e2d3f757700842dbc3855911d9/ghc >--------------------------------------------------------------- commit 383733b9191a36e2d3f757700842dbc3855911d9 Author: Peter Trommler Date: Sun Nov 30 12:00:39 2014 -0600 Fix obscure problem with using the system linker (#8935) Summary: In a statically linked GHCi symbol `environ` resolves to NULL when called from a Haskell script. When resolving symbols in a Haskell script we need to search the executable program and its dependent (DT_NEEDED) shared libraries first and then search the loaded libraries. We want to be able to override functions in loaded libraries later. Libraries must be opened with local scope (RTLD_LOCAL) and not global. The latter adds all symbols to the executable program's symbols where they are then searched in loading order. We want reverse loading order. When libraries are loaded with local scope the dynamic linker cannot use symbols in that library when resolving the dependencies in another shared library. This changes the way files compiled to object code must be linked into temporary shared libraries. We link with the last temporary shared library created so far if it exists. Since each temporary shared library is linked to the previous temporary shared library the dynamic linker finds the latest definition of a symbol by following the dependency chain. See also Note [RTLD_LOCAL] for a summary of the problem and solution. Cherry-picked commit 2f8b4c Changed linker argument ordering On some ELF systems GNU ld (and others?) default to --as-needed and the order of libraries in the link matters. The last temporary shared library, must appear before all other libraries. Switching the position of extra_ld_inputs and lib_path_objs does that. Fixes #8935 and #9186 Reviewers: austin, hvr, rwbarton, simonmar Reviewed By: simonmar Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D349 GHC Trac Issues: #8935, #9186, #9480 >--------------------------------------------------------------- 383733b9191a36e2d3f757700842dbc3855911d9 compiler/ghci/Linker.hs | 74 ++++++++++++++++++++++++++++++++-------------- compiler/main/SysTools.lhs | 3 +- rts/Linker.c | 43 +++++++++++++++++++++------ 3 files changed, 87 insertions(+), 33 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 383733b9191a36e2d3f757700842dbc3855911d9 From git at git.haskell.org Sun Nov 30 19:17:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Nov 2014 19:17:52 +0000 (UTC) Subject: [commit: ghc] master: compiler: unlit profiling/ modules (aede9f0) Message-ID: <20141130191752.BDD623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aede9f09e68504cc38037318a018d9185c232215/ghc >--------------------------------------------------------------- commit aede9f09e68504cc38037318a018d9185c232215 Author: Austin Seipp Date: Sun Nov 30 13:05:45 2014 -0600 compiler: unlit profiling/ modules Summary: Signed-off-by: Austin Seipp Test Plan: `./validate` Reviewers: hvr Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D537 >--------------------------------------------------------------- aede9f09e68504cc38037318a018d9185c232215 compiler/profiling/{CostCentre.lhs => CostCentre.hs} | 2 -- compiler/profiling/{SCCfinal.lhs => SCCfinal.hs} | 6 +----- 2 files changed, 1 insertion(+), 7 deletions(-) diff --git a/compiler/profiling/CostCentre.lhs b/compiler/profiling/CostCentre.hs similarity index 99% rename from compiler/profiling/CostCentre.lhs rename to compiler/profiling/CostCentre.hs index 8a6ed04..cce8394 100644 --- a/compiler/profiling/CostCentre.lhs +++ b/compiler/profiling/CostCentre.hs @@ -1,4 +1,3 @@ -\begin{code} {-# LANGUAGE BangPatterns, DeriveDataTypeable #-} module CostCentre ( CostCentre(..), CcName, IsCafCC(..), @@ -325,4 +324,3 @@ instance Binary CostCentre where -- ok, because we only need the SrcSpan when declaring the -- CostCentre in the original module, it is not used by importing -- modules. -\end{code} diff --git a/compiler/profiling/SCCfinal.lhs b/compiler/profiling/SCCfinal.hs similarity index 98% rename from compiler/profiling/SCCfinal.lhs rename to compiler/profiling/SCCfinal.hs index f9dc4a3..9ad5b5f 100644 --- a/compiler/profiling/SCCfinal.lhs +++ b/compiler/profiling/SCCfinal.hs @@ -1,7 +1,4 @@ -% -% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 -% -\begin{code} +-- (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 {-# LANGUAGE CPP #-} ----------------------------------------------------------------------------- @@ -281,4 +278,3 @@ collectCCS ccs = MassageM $ \_mod_name (local_ccs, extern_ccs, ccss) -> ASSERT(not (noCCSAttached ccs)) ((local_ccs, extern_ccs, ccs : ccss), ()) -\end{code} From git at git.haskell.org Sun Nov 30 19:17:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Nov 2014 19:17:55 +0000 (UTC) Subject: [commit: ghc] master: compiler: fix trac issue #8815 (780b061) Message-ID: <20141130191755.5FA2A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/780b061ce2aea4722d1a5d0e46fd4ed8ee2641d6/ghc >--------------------------------------------------------------- commit 780b061ce2aea4722d1a5d0e46fd4ed8ee2641d6 Author: Sivaram Balakrishnan Date: Sun Nov 30 13:05:56 2014 -0600 compiler: fix trac issue #8815 Summary: This patch changes the error message as suggested in trac issue #8815 comments. Reviewers: jstolarek, austin Reviewed By: jstolarek, austin Subscribers: jstolarek, thomie, carter Differential Revision: https://phabricator.haskell.org/D533 GHC Trac Issues: #8815 >--------------------------------------------------------------- 780b061ce2aea4722d1a5d0e46fd4ed8ee2641d6 compiler/typecheck/TcPat.lhs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcPat.lhs b/compiler/typecheck/TcPat.lhs index 3b7b5df..58e8bae 100644 --- a/compiler/typecheck/TcPat.lhs +++ b/compiler/typecheck/TcPat.lhs @@ -796,7 +796,8 @@ tcDataConPat penv (L con_span con_name) data_con pat_ty arg_pats thing_inside ; gadts_on <- xoptM Opt_GADTs ; families_on <- xoptM Opt_TypeFamilies ; checkTc (no_equalities || gadts_on || families_on) - (ptext (sLit "A pattern match on a GADT requires GADTs or TypeFamilies")) + (text "A pattern match on a GADT requires the" <+> + text "GADTs or TypeFamilies language extension") -- Trac #2905 decided that a *pattern-match* of a GADT -- should require the GADT language flag. -- Re TypeFamilies see also #7156 From git at git.haskell.org Sun Nov 30 19:44:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Nov 2014 19:44:43 +0000 (UTC) Subject: [commit: ghc] master: Update docs: instance visibility bug is no more. (9ece13d) Message-ID: <20141130194443.327E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9ece13d6e7aa4760b6db34f96d0d375628c135c2/ghc >--------------------------------------------------------------- commit 9ece13d6e7aa4760b6db34f96d0d375628c135c2 Author: Edward Z. Yang Date: Sun Nov 30 11:45:08 2014 -0800 Update docs: instance visibility bug is no more. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 9ece13d6e7aa4760b6db34f96d0d375628c135c2 docs/users_guide/bugs.xml | 11 ----------- 1 file changed, 11 deletions(-) diff --git a/docs/users_guide/bugs.xml b/docs/users_guide/bugs.xml index f9dfaae..2d6fc65 100644 --- a/docs/users_guide/bugs.xml +++ b/docs/users_guide/bugs.xml @@ -584,17 +584,6 @@ Loading package javavm ... linking ... WARNING: Overflown relocation field (# re your package into two or more .o's, along the lines of how the "base" package does it. - - - - GHCi does not keep careful track of what instance - declarations are 'in scope' if they come from other - packages. Instead, all instance declarations that GHC has - seen in other packages are all available at the prompt, - whether or not the instance really ought to be in visible - given the current set of modules in scope. - - From git at git.haskell.org Sun Nov 30 21:57:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Nov 2014 21:57:51 +0000 (UTC) Subject: [commit: ghc] master: Unlit compiler/cmm/ module(s) (0c48750) Message-ID: <20141130215751.93D8F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0c48750a97360ff70f35c660cbf6bc53f277b227/ghc >--------------------------------------------------------------- commit 0c48750a97360ff70f35c660cbf6bc53f277b227 Author: Herbert Valerio Riedel Date: Sun Nov 30 15:58:29 2014 -0600 Unlit compiler/cmm/ module(s) Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D540 >--------------------------------------------------------------- 0c48750a97360ff70f35c660cbf6bc53f277b227 compiler/cmm/{SMRep.lhs => SMRep.hs} | 55 +++++++++++++++--------------------- 1 file changed, 23 insertions(+), 32 deletions(-) diff --git a/compiler/cmm/SMRep.lhs b/compiler/cmm/SMRep.hs similarity index 93% rename from compiler/cmm/SMRep.lhs rename to compiler/cmm/SMRep.hs index 53c9d0a..ca272fc 100644 --- a/compiler/cmm/SMRep.lhs +++ b/compiler/cmm/SMRep.hs @@ -1,11 +1,8 @@ -% -% (c) The University of Glasgow 2006 -% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 -% - -Storage manager representation of closures +-- (c) The University of Glasgow 2006 +-- (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 +-- +-- Storage manager representation of closures -\begin{code} {-# LANGUAGE CPP,GeneralizedNewtypeDeriving #-} module SMRep ( @@ -61,16 +58,15 @@ import FastString import Data.Char( ord ) import Data.Word import Data.Bits -\end{code} - -%************************************************************************ -%* * +{- +************************************************************************ +* * Words and bytes -%* * -%************************************************************************ +* * +************************************************************************ +-} -\begin{code} -- | Word offset, or word count type WordOff = Int @@ -98,11 +94,7 @@ wordsToBytes dflags n = fromIntegral (wORD_SIZE dflags) * n bytesToWordsRoundUp :: DynFlags -> ByteOff -> WordOff bytesToWordsRoundUp dflags n = (n + word_size - 1) `quot` word_size where word_size = wORD_SIZE dflags -\end{code} - -StgWord is a type representing an StgWord on the target platform. - -\begin{code} +-- StgWord is a type representing an StgWord on the target platform. -- A Word64 is large enough to hold a Word for either a 32bit or 64bit platform newtype StgWord = StgWord Word64 deriving (Eq, Bits) @@ -148,15 +140,15 @@ hALF_WORD_SIZE :: DynFlags -> ByteOff hALF_WORD_SIZE dflags = platformWordSize (targetPlatform dflags) `shiftR` 1 hALF_WORD_SIZE_IN_BITS :: DynFlags -> Int hALF_WORD_SIZE_IN_BITS dflags = platformWordSize (targetPlatform dflags) `shiftL` 2 -\end{code} -%************************************************************************ -%* * +{- +************************************************************************ +* * \subsubsection[SMRep-datatype]{@SMRep at ---storage manager representation} -%* * -%************************************************************************ +* * +************************************************************************ +-} -\begin{code} -- | A description of the layout of a closure. Corresponds directly -- to the closure types in includes/rts/storage/ClosureTypes.h. data SMRep @@ -478,8 +470,8 @@ rET_SMALL = RET_SMALL rET_BIG = RET_BIG aRG_GEN = ARG_GEN aRG_GEN_BIG = ARG_GEN_BIG -\end{code} +{- Note [Static NoCaf constructors] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If we know that a top-level binding 'x' is not Caffy (ie no CAFs are @@ -492,13 +484,13 @@ Currently we don't do this; instead we treat nullary constructors as non-Caffy, and the others as potentially Caffy. -%************************************************************************ -%* * +************************************************************************ +* * Pretty printing of SMRep and friends -%* * -%************************************************************************ +* * +************************************************************************ +-} -\begin{code} instance Outputable ClosureTypeInfo where ppr = pprTypeInfo @@ -552,4 +544,3 @@ stringToWord8s s = map (fromIntegral . ord) s pprWord8String :: [Word8] -> SDoc -- Debug printing. Not very clever right now. pprWord8String ws = text (show ws) -\end{code} From git at git.haskell.org Sun Nov 30 21:59:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Nov 2014 21:59:26 +0000 (UTC) Subject: [commit: ghc] master: Unlit AsmCodeGen.lhs (7ad3846) Message-ID: <20141130215926.2BE3A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7ad384604652b87b68d32bdaff4ef7f94daf9d35/ghc >--------------------------------------------------------------- commit 7ad384604652b87b68d32bdaff4ef7f94daf9d35 Author: Herbert Valerio Riedel Date: Sun Nov 30 22:56:16 2014 +0100 Unlit AsmCodeGen.lhs Fwiw, this wasn't really a proper .lhs to begin with... >--------------------------------------------------------------- 7ad384604652b87b68d32bdaff4ef7f94daf9d35 compiler/nativeGen/{AsmCodeGen.lhs => AsmCodeGen.hs} | 4 ---- 1 file changed, 4 deletions(-) diff --git a/compiler/nativeGen/AsmCodeGen.lhs b/compiler/nativeGen/AsmCodeGen.hs similarity index 99% rename from compiler/nativeGen/AsmCodeGen.lhs rename to compiler/nativeGen/AsmCodeGen.hs index 56c18ea..a2ef91c 100644 --- a/compiler/nativeGen/AsmCodeGen.lhs +++ b/compiler/nativeGen/AsmCodeGen.hs @@ -6,7 +6,6 @@ -- -- ----------------------------------------------------------------------------- -\begin{code} {-# LANGUAGE BangPatterns, CPP, GADTs, ScopedTypeVariables, UnboxedTuples #-} module AsmCodeGen ( nativeCodeGen ) where @@ -1039,6 +1038,3 @@ cmmExprNative referenceKind expr = do other -> return other - -\end{code} -