From git at git.haskell.org Wed Oct 1 09:45:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 09:45:18 +0000 (UTC) Subject: [commit: hsc2hs] master: Improve the implementation of stringify (0cb9781) Message-ID: <20141001094518.6BDCA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hsc2hs On branch : master Link : http://git.haskell.org/hsc2hs.git/commitdiff/0cb9781b9f9eb7590ad8594e0b7a0cd886c127cb >--------------------------------------------------------------- commit 0cb9781b9f9eb7590ad8594e0b7a0cd886c127cb Author: David Feuer Date: Wed Oct 1 11:41:24 2014 +0200 Improve the implementation of stringify The new version should be faster and allocate considerably less. It's also at least as simple as the old version. >--------------------------------------------------------------- 0cb9781b9f9eb7590ad8594e0b7a0cd886c127cb CrossCodegen.hs | 26 +++++++++++++++----------- 1 file changed, 15 insertions(+), 11 deletions(-) diff --git a/CrossCodegen.hs b/CrossCodegen.hs index db9b124..5a62d05 100644 --- a/CrossCodegen.hs +++ b/CrossCodegen.hs @@ -384,7 +384,9 @@ binarySearch z nonNegative l u = do mid = (l+u+1) `div` 2 inTopHalf <- compareConst z (GreaterOrEqual $ (if nonNegative then Unsigned else Signed) mid) let (l',u') = if inTopHalf then (mid,u) else (l,(mid-1)) - assert (mid > l && mid <= u && u > l && u' >= l' && u' - l' < u - l && u' <= u && l' >= l) + assert (l < mid && mid <= u && -- l < mid <= u + l <= l' && l' <= u' && u' <= u && -- l <= l' <= u' <= u + u'-l' < u-l) -- |u' - l'| < |u - l| (binarySearch z nonNegative l' u') -- Establishes bounds on the unknown integer. By searching increasingly @@ -426,17 +428,19 @@ haskellize (firstLetter:next) = toLower firstLetter : loop False next loop _ ('_':as) = loop True as loop upper (a:as) = (if upper then toUpper a else toLower a) : loop False as --- For #{enum} codegen; in normal hsc2hs, any whitespace in the enum types & constructors --- will be mangled by the C preprocessor. This mimics the same mangling. +-- For #{enum} codegen; in normal hsc2hs, any whitespace in the enum types & +-- constructors will be mangled by the C preprocessor. This mimics the same +-- mangling. stringify :: String -> String -stringify s = reverse . dropWhile isSpace . reverse -- drop trailing space - . dropWhile isSpace -- drop leading space - . compressSpaces -- replace each span of - -- whitespace with a single space - $ s - where compressSpaces [] = [] - compressSpaces (a:as) | isSpace a = ' ' : compressSpaces (dropWhile isSpace as) - compressSpaces (a:as) = a : compressSpaces as +-- Spec: stringify = unwords . words +stringify xs = go False (dropWhile isSpace xs) + where + go _haveSpace [] = [] + go haveSpace (x:xs) + | isSpace x = go True xs + | otherwise = if haveSpace + then ' ' : x : go False xs + else x : go False xs computeEnum :: ZCursor Token -> TestMonad String computeEnum z@(ZCursor (Special _ _ enumText) _ _) = From git at git.haskell.org Wed Oct 1 09:45:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 09:45:20 +0000 (UTC) Subject: [commit: hsc2hs] master: Change hsc2hs maintainer to ghc-devs@haskell.org (52cdee2) Message-ID: <20141001094520.7176B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hsc2hs On branch : master Link : http://git.haskell.org/hsc2hs.git/commitdiff/52cdee2ee9ae3c3a860b8cc81cf88b169289bd95 >--------------------------------------------------------------- commit 52cdee2ee9ae3c3a860b8cc81cf88b169289bd95 Author: Joachim Breitner Date: Wed Oct 1 11:44:49 2014 +0200 Change hsc2hs maintainer to ghc-devs at haskell.org as cvs-fptools at haskell.org doesn?t seem to exist any more. >--------------------------------------------------------------- 52cdee2ee9ae3c3a860b8cc81cf88b169289bd95 hsc2hs.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hsc2hs.cabal b/hsc2hs.cabal index 123be3a..2eee52a 100644 --- a/hsc2hs.cabal +++ b/hsc2hs.cabal @@ -5,7 +5,7 @@ Build-Depends: base, directory, process License: BSD3 License-File: LICENSE Author: Marcin Kowalczyk -Maintainer: cvs-fptools at haskell.org +Maintainer: ghc-devs at haskell.org Synopsis: A preprocessor that helps with writing Haskell bindings to C code Description: The hsc2hs program can be used to automate some parts of the From git at git.haskell.org Wed Oct 1 09:46:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 09:46:24 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate-T9654' created Message-ID: <20141001094624.AFE763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/validate-T9654 Referencing: eb35cad2d6fcfd0ca99b5a2591b3573ad95c255c From git at git.haskell.org Wed Oct 1 09:46:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 09:46:27 +0000 (UTC) Subject: [commit: ghc] wip/validate-T9654: Update hsc2hs submodule (eb35cad) Message-ID: <20141001094627.75A7E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/validate-T9654 Link : http://ghc.haskell.org/trac/ghc/changeset/eb35cad2d6fcfd0ca99b5a2591b3573ad95c255c/ghc >--------------------------------------------------------------- commit eb35cad2d6fcfd0ca99b5a2591b3573ad95c255c Author: Joachim Breitner Date: Wed Oct 1 11:45:44 2014 +0200 Update hsc2hs submodule to get David?s code improvements (#9654). >--------------------------------------------------------------- eb35cad2d6fcfd0ca99b5a2591b3573ad95c255c utils/hsc2hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/hsc2hs b/utils/hsc2hs index af92e43..52cdee2 160000 --- a/utils/hsc2hs +++ b/utils/hsc2hs @@ -1 +1 @@ -Subproject commit af92e439369b7a3bb7d0476243af9b5622b7a48f +Subproject commit 52cdee2ee9ae3c3a860b8cc81cf88b169289bd95 From git at git.haskell.org Wed Oct 1 10:02:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 10:02:31 +0000 (UTC) Subject: [commit: hsc2hs] master: Make the code -Werror safe (286dd5d) Message-ID: <20141001100231.F2E863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hsc2hs On branch : master Link : http://git.haskell.org/hsc2hs.git/commitdiff/286dd5d6bf83115404ec6e9e194711554390e976 >--------------------------------------------------------------- commit 286dd5d6bf83115404ec6e9e194711554390e976 Author: Joachim Breitner Date: Wed Oct 1 12:02:11 2014 +0200 Make the code -Werror safe >--------------------------------------------------------------- 286dd5d6bf83115404ec6e9e194711554390e976 CrossCodegen.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/CrossCodegen.hs b/CrossCodegen.hs index 5a62d05..687f5be 100644 --- a/CrossCodegen.hs +++ b/CrossCodegen.hs @@ -433,7 +433,7 @@ haskellize (firstLetter:next) = toLower firstLetter : loop False next -- mangling. stringify :: String -> String -- Spec: stringify = unwords . words -stringify xs = go False (dropWhile isSpace xs) +stringify = go False . dropWhile isSpace where go _haveSpace [] = [] go haveSpace (x:xs) From git at git.haskell.org Wed Oct 1 10:03:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 10:03:01 +0000 (UTC) Subject: [commit: ghc] wip/validate-T9654: Update hsc2hs submodule (5d16c4d) Message-ID: <20141001100301.8F9F53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/validate-T9654 Link : http://ghc.haskell.org/trac/ghc/changeset/5d16c4d92a483ee07323689447c16189dfaa7f63/ghc >--------------------------------------------------------------- commit 5d16c4d92a483ee07323689447c16189dfaa7f63 Author: Joachim Breitner Date: Wed Oct 1 11:45:44 2014 +0200 Update hsc2hs submodule to get David?s code improvements (#9654). >--------------------------------------------------------------- 5d16c4d92a483ee07323689447c16189dfaa7f63 utils/hsc2hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/hsc2hs b/utils/hsc2hs index af92e43..286dd5d 160000 --- a/utils/hsc2hs +++ b/utils/hsc2hs @@ -1 +1 @@ -Subproject commit af92e439369b7a3bb7d0476243af9b5622b7a48f +Subproject commit 286dd5d6bf83115404ec6e9e194711554390e976 From git at git.haskell.org Wed Oct 1 10:47:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 10:47:35 +0000 (UTC) Subject: [commit: ghc] master's head updated: Update hsc2hs submodule (5d16c4d) Message-ID: <20141001104735.71D2B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: 5d16c4d Update hsc2hs submodule From git at git.haskell.org Wed Oct 1 10:47:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 10:47:40 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate-T9654' deleted Message-ID: <20141001104740.8840F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/validate-T9654 From git at git.haskell.org Wed Oct 1 11:57:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 11:57:02 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Better printing for TcTyVars in dump style (a333a46) Message-ID: <20141001115702.178DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/a333a462273792207ee5c062ede330270aabf77c/ghc >--------------------------------------------------------------- commit a333a462273792207ee5c062ede330270aabf77c Author: Simon Peyton Jones Date: Tue Sep 30 21:28:15 2014 +0100 Better printing for TcTyVars in dump style >--------------------------------------------------------------- a333a462273792207ee5c062ede330270aabf77c 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 Wed Oct 1 11:57:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 11:57:04 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Another traceTc debug trace (c7b6d41) Message-ID: <20141001115704.A85B83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/c7b6d418d3a85b0d73b32d2d6eba45b17216b5f3/ghc >--------------------------------------------------------------- commit c7b6d418d3a85b0d73b32d2d6eba45b17216b5f3 Author: Simon Peyton Jones Date: Tue Sep 30 21:29:18 2014 +0100 Another traceTc debug trace >--------------------------------------------------------------- c7b6d418d3a85b0d73b32d2d6eba45b17216b5f3 compiler/typecheck/Flattening-notes | 36 ++++++++++++++++++++++++------------ compiler/typecheck/Inst.lhs | 7 ++++++- 2 files changed, 30 insertions(+), 13 deletions(-) diff --git a/compiler/typecheck/Flattening-notes b/compiler/typecheck/Flattening-notes index f31d3b4..a945d03 100644 --- a/compiler/typecheck/Flattening-notes +++ b/compiler/typecheck/Flattening-notes @@ -11,6 +11,8 @@ ToDo: * TcCanonical re-orients, so TcInteract should not do so. (TwoWay, OneWay) +* Check orientation (isFlattenTyVar) in canEqTyVarTyVar + * No need to zonk now we are unflattening @@ -20,22 +22,10 @@ ToDo: They are all CFunEqCans, CTyEqCans * Update Note [Preparing inert set for implications] - -* indexed_types/should_compile/T3826 - -* remove level from FlatSkol -- not needed now they always - come from current level - -* remove the (b) CFunEqCan in simpl_loop - -* remove fe_rewrite_same - * remove/rewrite TcMType Note [Unflattening while zonking] * Consider individual data tpyes for CFunEqCan etc -* Check orientation (isFlattenTyVar) in canEqTyVarTyVar - ---------------------- Outer given is rewritten by an inner given, then there must have been an inner given equality, hence the ?given-eq? flag will be true anyway. @@ -67,6 +57,28 @@ We want: alpha := beta (which might unlock something else). So rewriting wanted ---------------------------------------- +indexed-types/should_failt/T4179 + +after solving + [W] fuv_1 ~ fuv_2 + [W] A3 (FCon x) ~ fuv_1 (CFunEqCan) + [W] A3 (x (aoa -> fuv_2)) ~ fuv_2 (CFunEqCan) + +---------------------------------------- +indexed-types/should_fail/T7729a + +a) [W] BasePrimMonad (Rand m) ~ m1 +b) [W] tt m1 ~ BasePrimMonad (Rand m) + +---> process (b) first + BasePrimMonad (Ramd m) ~ fuv_atH + fuv_atH ~ tt m1 + +---> now process (a) + m1 ~ s_atH ~ tt m1 -- An obscure occurs check + + +---------------------------------------- typecheck/TcTypeNatSimple Original constraint diff --git a/compiler/typecheck/Inst.lhs b/compiler/typecheck/Inst.lhs index ed77706..758081e 100644 --- a/compiler/typecheck/Inst.lhs +++ b/compiler/typecheck/Inst.lhs @@ -169,7 +169,12 @@ deeplyInstantiate orig ty | Just (arg_tys, tvs, theta, rho) <- tcDeepSplitSigmaTy_maybe ty = do { (_, tys, subst) <- tcInstTyVars tvs ; ids1 <- newSysLocalIds (fsLit "di") (substTys subst arg_tys) - ; wrap1 <- instCall orig tys (substTheta subst theta) + ; let theta' = substTheta subst theta + ; wrap1 <- instCall orig tys theta' + ; traceTc "Instantiating (deply)" (vcat [ ppr ty + , text "with" <+> ppr tys + , text "args:" <+> ppr ids1 + , text "theta:" <+> ppr theta' ]) ; (wrap2, rho2) <- deeplyInstantiate orig (substTy subst rho) ; return (mkWpLams ids1 <.> wrap2 From git at git.haskell.org Wed Oct 1 11:57:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 11:57:07 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: More flatten-skolem progress (24c9c7c) Message-ID: <20141001115707.43DC83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/24c9c7ccf0c1c3cbf0651d3967c5b22d461032c2/ghc >--------------------------------------------------------------- commit 24c9c7ccf0c1c3cbf0651d3967c5b22d461032c2 Author: Simon Peyton Jones Date: Tue Sep 30 21:31:32 2014 +0100 More flatten-skolem progress >--------------------------------------------------------------- 24c9c7ccf0c1c3cbf0651d3967c5b22d461032c2 compiler/typecheck/TcCanonical.lhs | 121 ++++++++++++++----------- compiler/typecheck/TcInteract.lhs | 176 ++++++++++++++----------------------- compiler/typecheck/TcMType.lhs | 81 ++++------------- compiler/typecheck/TcSMonad.lhs | 2 +- compiler/typecheck/TcSimplify.lhs | 15 ++-- compiler/typecheck/TcType.lhs | 32 ++++--- 6 files changed, 182 insertions(+), 245 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 24c9c7ccf0c1c3cbf0651d3967c5b22d461032c2 From git at git.haskell.org Wed Oct 1 11:57:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 11:57:09 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Print traceTc stuff in dump-style (ec85cf2) Message-ID: <20141001115709.C9A0A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/ec85cf2add0e351ec0ed445d6f291360f476114c/ghc >--------------------------------------------------------------- commit ec85cf2add0e351ec0ed445d6f291360f476114c Author: Simon Peyton Jones Date: Tue Sep 30 21:31:56 2014 +0100 Print traceTc stuff in dump-style >--------------------------------------------------------------- ec85cf2add0e351ec0ed445d6f291360f476114c compiler/typecheck/TcRnMonad.lhs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcRnMonad.lhs b/compiler/typecheck/TcRnMonad.lhs index 7243749..0c4bf0a 100644 --- a/compiler/typecheck/TcRnMonad.lhs +++ b/compiler/typecheck/TcRnMonad.lhs @@ -499,9 +499,10 @@ traceOptTcRn flag doc = whenDOptM flag $ do ; 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 + ; liftIO (debugTraceMsg dflags 0 doc) } +-- ; rdr_env <- getGlobalRdrEnv +-- ; liftIO (printInfoForUser dflags (mkPrintUnqualified dflags rdr_env) doc) } debugDumpTcRn :: SDoc -> TcRn () debugDumpTcRn doc | opt_NoDebugOutput = return () From git at git.haskell.org Wed Oct 1 11:57:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 11:57:12 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Error message wibbles (ebcc037) Message-ID: <20141001115712.6AE133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/ebcc0372523c20e4917b1e59f4e445338b423cc0/ghc >--------------------------------------------------------------- commit ebcc0372523c20e4917b1e59f4e445338b423cc0 Author: Simon Peyton Jones Date: Tue Sep 30 21:32:48 2014 +0100 Error message wibbles >--------------------------------------------------------------- ebcc0372523c20e4917b1e59f4e445338b423cc0 .../tests/indexed-types/should_fail/T7729a.hs | 38 ++++++++++++++++++++-- .../tests/indexed-types/should_fail/T7729a.stderr | 20 +++--------- testsuite/tests/typecheck/should_compile/tc231.hs | 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 ++++---- testsuite/tests/typecheck/should_run/T5751.hs | 2 +- testsuite/tests/typecheck/should_run/tcrun036.hs | 12 +++---- 8 files changed, 66 insertions(+), 43 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 ebcc0372523c20e4917b1e59f4e445338b423cc0 From git at git.haskell.org Wed Oct 1 11:57:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 11:57:15 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: More flatten-skolem progress (0d2ce1d) Message-ID: <20141001115715.0E3093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/0d2ce1ddae9cb8400b3d228a73023019cbe4f789/ghc >--------------------------------------------------------------- commit 0d2ce1ddae9cb8400b3d228a73023019cbe4f789 Author: Simon Peyton Jones Date: Wed Oct 1 12:54:27 2014 +0100 More flatten-skolem progress >--------------------------------------------------------------- 0d2ce1ddae9cb8400b3d228a73023019cbe4f789 compiler/typecheck/Flattening-notes | 2 ++ compiler/typecheck/TcEvidence.lhs | 23 +++++++++++++++++++++++ compiler/typecheck/TcRnTypes.lhs | 2 ++ compiler/typecheck/TcSMonad.lhs | 19 ++++++++++++------- 4 files changed, 39 insertions(+), 7 deletions(-) diff --git a/compiler/typecheck/Flattening-notes b/compiler/typecheck/Flattening-notes index a945d03..da8441a 100644 --- a/compiler/typecheck/Flattening-notes +++ b/compiler/typecheck/Flattening-notes @@ -1,5 +1,7 @@ ToDo: +* ctev_loc should have a decent name ctEvLoc + * Float only CTyEqCans. kind-incompatible things should be CNonCanonical, so they won't float and generate a duplicate kind-unify message diff --git a/compiler/typecheck/TcEvidence.lhs b/compiler/typecheck/TcEvidence.lhs index 3b2a3d6..d0481c8 100644 --- a/compiler/typecheck/TcEvidence.lhs +++ b/compiler/typecheck/TcEvidence.lhs @@ -28,6 +28,7 @@ module TcEvidence ( mkTcAxiomRuleCo, tcCoercionKind, coVarsOfTcCo, isEqVar, mkTcCoVarCo, isTcReflCo, getTcCoVar_maybe, + tcLiftCoSubst, tcCoercionRole, eqVarRole ) where #include "HsVersions.h" @@ -339,6 +340,28 @@ coVarsOfTcCo tc_co get_bndrs :: Bag EvBind -> VarSet get_bndrs = foldrBag (\ (EvBind b _) bs -> extendVarSet bs b) emptyVarSet + +tcLiftCoSubst :: TcTyVar -> TcCoercion -> TcType -> TcCoercion +-- Substitute the_tv -> the_co in the given type, at Nominal role +-- Like Coercion.liftCoSubst, but for TcCoercion, and +-- specialised for Nominal role +tcLiftCoSubst the_tv the_co ty + = ASSERT( tcCoercionRole the_co == Nominal ) + go ty + where + go ty@(TyVarTy tv) + | tv == the_tv = the_co + | otherwise = TcRefl Nominal ty + go ty@(LitTy {}) = TcRefl Nominal ty + + go (AppTy ty1 ty2) = mkTcAppCo (go ty1) (go ty2) + go (FunTy ty1 ty2) = mkTcFunCo Nominal (go ty1) (go ty2) + go (TyConApp tc tys) = mkTcTyConAppCo Nominal tc (map go tys) + -- We are building a Nominal coercion, so the TyCon's + -- args must all be Nominal coercions too, regardless + -- of the TyCon's arg rules (c.f. Coercion.tyConRolesX) + go ty@(ForAllTy _ _) = pprPanic "tcLiftCoSubst" (ppr ty) + -- Substituting under a for-all is awkward \end{code} Pretty printing diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index d5315d2..584115f 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -960,6 +960,8 @@ data Ct | CFunEqCan { -- F xis ~ fsk -- Invariant: * isSynFamilyTyCon cc_fun -- * typeKind (F xis) `subKind` typeKind xi + -- * always Nominal role + -- * always Given or Watned, never Derived -- See Note [Kind orientation for CFunEqCan] cc_ev :: CtEvidence, -- See Note [Ct/evidence invariant] cc_fun :: TyCon, -- A type function diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index 25b22e9..b05368f 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -687,21 +687,22 @@ getInertUnsolved unflatten_funeq :: DynFlags -> Ct -> TcS Cts -> TcS Cts unflatten_funeq dflags (CFunEqCan { cc_fun = tc, cc_tyargs = xis - , cc_fsk = tv, cc_ev = ev }) rest + , cc_fsk = fsk, cc_ev = ev }) rest | isGiven ev -- tv should be a FlatSkol; zonking will eliminate it = rest | otherwise -- A flatten meta-tv; we now fix its final -- value, and then zonking will eliminate it - = do { unsolved <- rest + = ASSERT( isWanted ev ) -- CFunEqCans are never Derived + do { unsolved <- rest ; fn_app <- wrapTcS (TcM.zonkTcType (mkTyConApp tc xis)) - ; case occurCheckExpand dflags tv fn_app of + ; case occurCheckExpand dflags fsk fn_app of OC_OK fn_app' -> -- Normal case: unflatten do { let evterm = EvCoercion (mkTcNomReflCo fn_app') evvar = ctev_evar ev ; setEvBind evvar evterm - ; wrapTcS (TcM.writeMetaTyVar tv fn_app') + ; wrapTcS (TcM.writeMetaTyVar fsk fn_app') -- Write directly into the mutable tyvar -- Flatten meta-vars are born locally and -- die locally @@ -709,9 +710,13 @@ getInertUnsolved _ -> -- Occurs check; don't unflatten, instead turn it into a NonCanonical -- Don't forget to get rid ofthe - do { tv_ty <- newFlexiTcSTy (tyVarKind tv) - ; wrapTcS (TcM.writeMetaTyVar tv tv_ty) - ; return (unsolved `extendCts` mkNonCanonical ev) } } + do { tv_ty <- newFlexiTcSTy (tyVarKind fsk) + ; let fn_app' = substTyWith [fsk] [tv_ty] fn_app + ; wrapTcS (TcM.writeMetaTyVar fsk fn_app') + ; new_ev <- newWantedEvVarNC (ctev_loc ev) (mkEqPred fn_app' tv_ty) + -- w' :: F tau[alpha] ~ alpha + ; setEvBind (ctEvId ev) (EvCoercion (tcLiftCoSubst fsk (ctEvCoercion new_ev) fn_app)) + ; return (unsolved `extendCts` mkNonCanonical new_ev) } } unflatten_funeq _ other_ct _ = pprPanic "unflatten_funeq" (ppr other_ct) From git at git.haskell.org Wed Oct 1 13:05:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 13:05:22 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate-T9495' created Message-ID: <20141001130522.5E6093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/validate-T9495 Referencing: 914342c1ed282ea2d9bdd54d69a455372557d846 From git at git.haskell.org Wed Oct 1 13:05:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 13:05:24 +0000 (UTC) Subject: [commit: ghc] wip/validate-T9495: Make foldr2 a bit more strict (914342c) Message-ID: <20141001130524.E4F843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/validate-T9495 Link : http://ghc.haskell.org/trac/ghc/changeset/914342c1ed282ea2d9bdd54d69a455372557d846/ghc >--------------------------------------------------------------- commit 914342c1ed282ea2d9bdd54d69a455372557d846 Author: David Feuer Date: Wed Oct 1 15:02:33 2014 +0200 Make foldr2 a bit more strict in order to make its RULES semantics preserving. This fixes #9495. >--------------------------------------------------------------- 914342c1ed282ea2d9bdd54d69a455372557d846 docs/users_guide/bugs.xml | 9 ++++++++- libraries/base/GHC/List.lhs | 43 +++++++++++++++++++++++++++++-------------- libraries/base/changelog.md | 4 ++++ 3 files changed, 41 insertions(+), 15 deletions(-) diff --git a/docs/users_guide/bugs.xml b/docs/users_guide/bugs.xml index dba0d86..f9dfaae 100644 --- a/docs/users_guide/bugs.xml +++ b/docs/users_guide/bugs.xml @@ -291,7 +291,14 @@ checking for duplicates. The reason for this is efficiency, pure and simple. if you get stuck on it. - + + zip and zipWith semantics + zip and zipWith can give + less defined results than the Report specifies in certain cases. This deviation + is needed to allow more opportunities for list fusion. In particular, + termination of the left list cannot be used to avoid hitting bottom in the + right list. See the documentation for details. + Reading integers diff --git a/libraries/base/GHC/List.lhs b/libraries/base/GHC/List.lhs index ffcc8ab..8c8e4bb 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -646,7 +646,7 @@ xs !! (I# n0) | isTrue# (n0 <# 0#) = error "Prelude.(!!): negative index\n" foldr2 :: (a -> b -> c -> c) -> c -> [a] -> [b] -> c foldr2 k z = go where - go [] _ys = z + go [] ys = ys `seq` z -- see #9495 for the seq go _xs [] = z go (x:xs) (y:ys) = k x y (go xs ys) {-# INLINE [0] foldr2 #-} @@ -670,16 +670,6 @@ foldr2_right k _z y r (x:xs) = k x y (r xs) #-} \end{code} -The foldr2/right rule isn't exactly right, because it changes -the strictness of foldr2 (and thereby zip) - -E.g. main = print (null (zip nonobviousNil (build undefined))) - where nonobviousNil = f 3 - f n = if n == 0 then [] else f (n-1) - -I'm going to leave it though. - - Zips for larger tuples are in the List module. \begin{code} @@ -687,10 +677,22 @@ Zips for larger tuples are in the List module. -- | 'zip' takes two lists and returns a list of corresponding pairs. -- If one input list is short, excess elements of the longer list are -- discarded. +-- +-- NOTE: GHC's implementation of @zip@ deviates slightly from the +-- standard. In particular, Haskell 98 and Haskell 2010 require that +-- @zip [x1,x2,...,xn] (y1:y2:...:yn:_|_) = [(x1,y1),(x2,y2),...,(xn,yn)]@ +-- In GHC, however, +-- @zip [x1,x2,...,xn] (y1:y2:...:yn:_|_) = (x1,y1):(x2,y2):...:(xn,yn):_|_@ +-- That is, you cannot use termination of the left list to avoid hitting +-- bottom in the right list. + +-- This deviation is necessary to make fusion with 'build' in the right +-- list preserve semantics. {-# NOINLINE [1] zip #-} zip :: [a] -> [b] -> [(a,b)] +zip [] bs = bs `seq` [] -- see #9495 for the seq +zip _as [] = [] zip (a:as) (b:bs) = (a,b) : zip as bs -zip _ _ = [] {-# INLINE [0] zipFB #-} zipFB :: ((a, b) -> c -> d) -> a -> b -> c -> d @@ -723,10 +725,23 @@ zip3 _ _ _ = [] -- as the first argument, instead of a tupling function. -- For example, @'zipWith' (+)@ is applied to two lists to produce the -- list of corresponding sums. +-- +-- NOTE: GHC's implementation of @zipWith@ deviates slightly from the +-- standard. In particular, Haskell 98 and Haskell 2010 require that +-- @zipWith (,) [x1,x2,...,xn] (y1:y2:...:yn:_|_) = [(x1,y1),(x2,y2),...,(xn,yn)]@ +-- In GHC, however, +-- @zipWith (,) [x1,x2,...,xn] (y1:y2:...:yn:_|_) = (x1,y1):(x2,y2):...:(xn,yn):_|_@ +-- That is, you cannot use termination of the left list to avoid hitting +-- bottom in the right list. + +-- This deviation is necessary to make fusion with 'build' in the right +-- list preserve semantics. + {-# NOINLINE [1] zipWith #-} zipWith :: (a->b->c) -> [a]->[b]->[c] -zipWith f (a:as) (b:bs) = f a b : zipWith f as bs -zipWith _ _ _ = [] +zipWith _f [] bs = bs `seq` [] -- see #9495 for the seq +zipWith _f _as [] = [] +zipWith f (a:as) (b:bs) = f a b : zipWith f as bs -- zipWithFB must have arity 2 since it gets two arguments in the "zipWith" -- rule; it might not get inlined otherwise diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 7b168fe..7529782 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -73,6 +73,10 @@ 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) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 From git at git.haskell.org Wed Oct 1 13:26:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 13:26:28 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate-T9355' created Message-ID: <20141001132628.C8E643A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/validate-T9355 Referencing: 3fe0d83b5ef3684df7fa9c0435f666c918c95ae3 From git at git.haskell.org Wed Oct 1 13:26:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 13:26:31 +0000 (UTC) Subject: [commit: ghc] wip/validate-T9355: Make scanr a good producer and consumer (3fe0d83) Message-ID: <20141001132631.5CD9C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/validate-T9355 Link : http://ghc.haskell.org/trac/ghc/changeset/3fe0d83b5ef3684df7fa9c0435f666c918c95ae3/ghc >--------------------------------------------------------------- commit 3fe0d83b5ef3684df7fa9c0435f666c918c95ae3 Author: David Feuer Date: Wed Oct 1 15:24:43 2014 +0200 Make scanr a good producer and consumer This fixes #9355. >--------------------------------------------------------------- 3fe0d83b5ef3684df7fa9c0435f666c918c95ae3 libraries/base/GHC/List.lhs | 17 +++++++++++++++++ libraries/base/changelog.md | 2 ++ 2 files changed, 19 insertions(+) diff --git a/libraries/base/GHC/List.lhs b/libraries/base/GHC/List.lhs index 8c8e4bb..b5c461d 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -229,11 +229,28 @@ foldr1 _ [] = errorEmptyList "foldr1" -- -- > head (scanr f z xs) == foldr f z xs. +{-# NOINLINE [1] scanr #-} scanr :: (a -> b -> b) -> b -> [a] -> [b] scanr _ q0 [] = [q0] scanr f q0 (x:xs) = f x q : qs where qs@(q:_) = scanr f q0 xs +{-# INLINE [0] strictUncurryScanr #-} +strictUncurryScanr :: (a -> b -> c) -> (a, b) -> c +strictUncurryScanr f pair = case pair of + (x, y) -> f x y + +{-# INLINE [0] scanrFB #-} +scanrFB f c = \x (r, est) -> (f x r, r `c` est) + +{-# RULES +"scanr" [~1] forall f q0 ls . scanr f q0 ls = + build (\c n -> strictUncurryScanr c (foldr (scanrFB f c) (q0,n) ls)) +"scanrList" [1] forall f q0 ls . + strictUncurryScanr (:) (foldr (scanrFB f (:)) (q0,[]) ls) = + scanr f q0 ls + #-} + -- | 'scanr1' is a variant of 'scanr' that has no starting value argument. scanr1 :: (a -> a -> a) -> [a] -> [a] diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 7529782..c594c2f 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -77,6 +77,8 @@ second argument, so that the fusion RULES for it do not change the semantics. (#9596) + * `scanr` now takes part in list fusion (#9355) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 From git at git.haskell.org Wed Oct 1 13:40:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 13:40:06 +0000 (UTC) Subject: [commit: ghc] master: Fix bogus comment (8d04eb2) Message-ID: <20141001134006.EA4BE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8d04eb272b7bb9ffa6d7d5157a76199a19aa6b34/ghc >--------------------------------------------------------------- commit 8d04eb272b7bb9ffa6d7d5157a76199a19aa6b34 Author: Simon Peyton Jones Date: Wed Oct 1 10:08:58 2014 +0100 Fix bogus comment >--------------------------------------------------------------- 8d04eb272b7bb9ffa6d7d5157a76199a19aa6b34 compiler/simplCore/Simplify.lhs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/simplCore/Simplify.lhs b/compiler/simplCore/Simplify.lhs index 09a2bef..ae2c6ea 100644 --- a/compiler/simplCore/Simplify.lhs +++ b/compiler/simplCore/Simplify.lhs @@ -2316,8 +2316,8 @@ missingAlt env case_bndr _ cont prepareCaseCont :: SimplEnv -> [InAlt] -> SimplCont -> SimplM (SimplEnv, - SimplCont, -- Non-dupable part - SimplCont) -- Dupable part + SimplCont, -- Dupable part + SimplCont) -- Non-dupable part -- We are considering -- K[case _ of { p1 -> r1; ...; pn -> rn }] -- where K is some enclosing continuation for the case From git at git.haskell.org Wed Oct 1 13:40:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 13:40:09 +0000 (UTC) Subject: [commit: ghc] master: Don't use newSysLocal etc for Coercible (1c10b4f) Message-ID: <20141001134009.8422E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1c10b4f9a881a2ca88514990c969108efd65927a/ghc >--------------------------------------------------------------- commit 1c10b4f9a881a2ca88514990c969108efd65927a Author: Simon Peyton Jones Date: Wed Oct 1 14:39:42 2014 +0100 Don't use newSysLocal etc for Coercible The code is smaller and simpler now. Thanks to Richard for raising the question. >--------------------------------------------------------------- 1c10b4f9a881a2ca88514990c969108efd65927a compiler/typecheck/TcInteract.lhs | 88 +++++++++++++++++---------------------- 1 file changed, 38 insertions(+), 50 deletions(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 04122f9..747eb91 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -20,7 +20,7 @@ import Var import TcType import PrelNames (knownNatClassName, knownSymbolClassName, ipClassNameKey ) import TysWiredIn ( coercibleClass ) -import Id( idType, mkSysLocalM ) +import Id( idType ) import Class import TyCon import DataCon @@ -47,7 +47,7 @@ import VarEnv import Control.Monad( when, unless, forM ) import Pair (Pair(..)) import Unique( hasKey ) -import FastString ( sLit, fsLit ) +import FastString ( sLit ) import DynFlags import Util \end{code} @@ -1964,56 +1964,38 @@ getCoercibleInst loc ty1 ty2 ; return $ GenInst [] ev_term } -- Coercible NT a (see case 3 in [Coercible Instances]) - | Just (rep_tc, concTy, ntCo) <- tcInstNewTyConTF_maybe famenv ty1 + | Just (rep_tc, conc_ty, nt_co) <- tcInstNewTyConTF_maybe famenv ty1 , dataConsInScope rdr_env rep_tc -- Do not look at all tyConsOfTyCon = do { markDataConsAsUsed rdr_env rep_tc - ; ct_ev <- requestCoercible loc concTy ty2 - ; local_var <- mkSysLocalM (fsLit "coev") $ mkCoerciblePred concTy ty2 - ; let binds = EvBinds (unitBag (EvBind local_var (getEvTerm ct_ev))) - tcCo = TcLetCo binds (ntCo `mkTcTransCo` mkTcCoVarCo local_var) - ; return $ GenInst (freshGoals [ct_ev]) (EvCoercion tcCo) } + ; (new_goals, residual_co) <- requestCoercible loc conc_ty ty2 + ; let final_co = nt_co `mkTcTransCo` residual_co + -- nt_co :: ty1 ~R conc_ty + -- residual_co :: conc_ty ~R ty2 + ; return $ GenInst new_goals (EvCoercion final_co) } -- Coercible a NT (see case 3 in [Coercible Instances]) - | Just (rep_tc, concTy, ntCo) <- tcInstNewTyConTF_maybe famenv ty2 + | Just (rep_tc, conc_ty, nt_co) <- tcInstNewTyConTF_maybe famenv ty2 , dataConsInScope rdr_env rep_tc -- Do not look at all tyConsOfTyCon = do { markDataConsAsUsed rdr_env rep_tc - ; ct_ev <- requestCoercible loc ty1 concTy - ; local_var <- mkSysLocalM (fsLit "coev") $ mkCoerciblePred ty1 concTy - ; let binds = EvBinds (unitBag (EvBind local_var (getEvTerm ct_ev))) - tcCo = TcLetCo binds $ - mkTcCoVarCo local_var `mkTcTransCo` mkTcSymCo ntCo - ; return $ GenInst (freshGoals [ct_ev]) (EvCoercion tcCo) } + ; (new_goals, residual_co) <- requestCoercible loc ty1 conc_ty + ; let final_co = residual_co `mkTcTransCo` mkTcSymCo nt_co + ; return $ GenInst new_goals (EvCoercion final_co) } -- Coercible (D ty1 ty2) (D ty1' ty2') (see case 4 in [Coercible Instances]) - | Just (tc1,tyArgs1) <- splitTyConApp_maybe ty1, - Just (tc2,tyArgs2) <- splitTyConApp_maybe ty2, - tc1 == tc2, - nominalArgsAgree tc1 tyArgs1 tyArgs2 - = do -- We want evidence for all type arguments of role R - arg_stuff <- forM (zip3 (tyConRoles tc1) tyArgs1 tyArgs2) $ \(r,ta1,ta2) -> - case r of Nominal -> do - return - ( Nothing - , Nothing - , mkTcNomReflCo ta1 {- == ta2, due to nominalArgsAgree -} - ) - Representational -> do - ct_ev <- requestCoercible loc ta1 ta2 - local_var <- mkSysLocalM (fsLit "coev") $ mkCoerciblePred ta1 ta2 - return - ( freshGoal ct_ev - , Just (EvBind local_var (getEvTerm ct_ev)) - , mkTcCoVarCo local_var - ) - Phantom -> do - return - ( Nothing - , Nothing - , TcPhantomCo ta1 ta2) - let (arg_new, arg_binds, arg_cos) = unzip3 arg_stuff - binds = EvBinds (listToBag (catMaybes arg_binds)) - tcCo = TcLetCo binds (mkTcTyConAppCo Representational tc1 arg_cos) - return $ GenInst (catMaybes arg_new) (EvCoercion tcCo) + | Just (tc1,tyArgs1) <- splitTyConApp_maybe ty1 + , Just (tc2,tyArgs2) <- splitTyConApp_maybe ty2 + , tc1 == tc2 + , nominalArgsAgree tc1 tyArgs1 tyArgs2 + = do { -- We want evidence for all type arguments of role R + arg_stuff <- forM (zip3 (tyConRoles tc1) tyArgs1 tyArgs2) $ \ (r,ta1,ta2) -> + case r of + Representational -> requestCoercible loc ta1 ta2 + Phantom -> return ([], TcPhantomCo ta1 ta2) + Nominal -> return ([], mkTcNomReflCo ta1) + -- ta1 == ta2, due to nominalArgsAgree + ; let (new_goals_s, arg_cos) = unzip arg_stuff + final_co = mkTcTyConAppCo Representational tc1 arg_cos + ; return $ GenInst (concat new_goals_s) (EvCoercion final_co) } -- Cannot solve this one | otherwise @@ -2041,12 +2023,18 @@ markDataConsAsUsed rdr_env tc = addUsedRdrNamesTcS , not (null gres) , Imported (imp_spec:_) <- [gre_prov (head gres)] ] -requestCoercible :: CtLoc -> TcType -> TcType -> TcS MaybeNew -requestCoercible loc ty1 ty2 = - ASSERT2( typeKind ty1 `tcEqKind` typeKind ty2, ppr ty1 <+> ppr ty2) - newWantedEvVarNonrec loc' (mkCoerciblePred ty1 ty2) - where loc' = bumpCtLocDepth CountConstraints loc - +requestCoercible :: CtLoc -> TcType -> TcType + -> TcS ( [CtEvidence] -- Fresh goals to solve + , TcCoercion ) -- Coercion witnessing (Coercible t1 t2) +requestCoercible loc ty1 ty2 + = ASSERT2( typeKind ty1 `tcEqKind` typeKind ty2, ppr ty1 <+> ppr ty2) + do { mb_ev <- newWantedEvVarNonrec loc' (mkCoerciblePred ty1 ty2) + ; case mb_ev of + Fresh ev -> return ( [ev], evTermCoercion (ctEvTerm ev) ) + Cached ev_tm -> return ( [], evTermCoercion ev_tm ) } + -- Evidence for a Coercible constraint is always a coercion t1 ~R t2 + where + loc' = bumpCtLocDepth CountConstraints loc \end{code} Note [Coercible Instances] From git at git.haskell.org Wed Oct 1 13:40:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 13:40:12 +0000 (UTC) Subject: [commit: ghc] master: Comments about the let/app invariant (04ded40) Message-ID: <20141001134012.12FCA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/04ded40857fdaeea1e48bb39da54f1a5e9f91570/ghc >--------------------------------------------------------------- commit 04ded40857fdaeea1e48bb39da54f1a5e9f91570 Author: Simon Peyton Jones Date: Wed Oct 1 14:39:00 2014 +0100 Comments about the let/app invariant >--------------------------------------------------------------- 04ded40857fdaeea1e48bb39da54f1a5e9f91570 compiler/coreSyn/MkCore.lhs | 29 ++++++++++++++++++----------- 1 file changed, 18 insertions(+), 11 deletions(-) diff --git a/compiler/coreSyn/MkCore.lhs b/compiler/coreSyn/MkCore.lhs index 6987f06..81f0533 100644 --- a/compiler/coreSyn/MkCore.lhs +++ b/compiler/coreSyn/MkCore.lhs @@ -129,8 +129,8 @@ mkCoreLets binds body = foldr mkCoreLet body binds -- | Construct an expression which represents the application of one expression -- to the other mkCoreApp :: CoreExpr -> CoreExpr -> CoreExpr --- Check the invariant that the arg of an App is ok-for-speculation if unlifted --- See CoreSyn Note [CoreSyn let/app invariant] +-- Respects the let/app invariant by building a case expression where necessary +-- See CoreSyn Note [CoreSyn let/app invariant] mkCoreApp fun (Type ty) = App fun (Type ty) mkCoreApp fun (Coercion co) = App fun (Coercion co) mkCoreApp fun arg = ASSERT2( isFunTy fun_ty, ppr fun $$ ppr arg ) @@ -141,18 +141,21 @@ mkCoreApp fun arg = ASSERT2( isFunTy fun_ty, ppr fun $$ ppr arg ) -- | Construct an expression which represents the application of a number of -- expressions to another. The leftmost expression in the list is applied first +-- Respects the let/app invariant by building a case expression where necessary +-- See CoreSyn Note [CoreSyn let/app invariant] mkCoreApps :: CoreExpr -> [CoreExpr] -> CoreExpr -- Slightly more efficient version of (foldl mkCoreApp) mkCoreApps orig_fun orig_args = go orig_fun (exprType orig_fun) orig_args where - go fun _ [] = fun - go fun fun_ty (Type ty : args) = go (App fun (Type ty)) (applyTy fun_ty ty) args + go fun _ [] = fun + go fun fun_ty (Type ty : args) = go (App fun (Type ty)) (applyTy fun_ty ty) args go fun fun_ty (Coercion co : args) = go (App fun (Coercion co)) (applyCo fun_ty co) args - go fun fun_ty (arg : args) = ASSERT2( isFunTy fun_ty, ppr fun_ty $$ ppr orig_fun $$ ppr orig_args ) - go (mk_val_app fun arg arg_ty res_ty) res_ty args - where - (arg_ty, res_ty) = splitFunTy fun_ty + go fun fun_ty (arg : args) = ASSERT2( isFunTy fun_ty, ppr fun_ty $$ ppr orig_fun + $$ ppr orig_args ) + go (mk_val_app fun arg arg_ty res_ty) res_ty args + where + (arg_ty, res_ty) = splitFunTy fun_ty -- | Construct an expression which represents the application of a number of -- expressions to that of a data constructor expression. The leftmost expression @@ -160,13 +163,16 @@ mkCoreApps orig_fun orig_args mkCoreConApps :: DataCon -> [CoreExpr] -> CoreExpr mkCoreConApps con args = mkCoreApps (Var (dataConWorkId con)) args ------------ mk_val_app :: CoreExpr -> CoreExpr -> Type -> Type -> CoreExpr -mk_val_app fun arg arg_ty _ -- See Note [CoreSyn let/app invariant] +-- Build an application (e1 e2), +-- or a strict binding (case e2 of x -> e1 x) +-- using the latter when necessary to respect the let/app invariant +-- See Note [CoreSyn let/app invariant] +mk_val_app fun arg arg_ty res_ty | not (needsCaseBinding arg_ty arg) = App fun arg -- The vastly common case -mk_val_app fun arg arg_ty res_ty + | otherwise = Case arg arg_id res_ty [(DEFAULT,[],App fun (Var arg_id))] where arg_id = mkWildValBinder arg_ty @@ -179,6 +185,7 @@ mk_val_app fun arg arg_ty res_ty -- is if you take apart this case expression, and pass a -- fragmet of it as the fun part of a 'mk_val_app'. +----------- mkWildEvBinder :: PredType -> EvVar mkWildEvBinder pred = mkWildValBinder pred From git at git.haskell.org Wed Oct 1 13:43:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 13:43:46 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate-T9502' created Message-ID: <20141001134346.A734C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/validate-T9502 Referencing: 5bda348b3e27a59fe9ec6ed86a89e3e0eff3f257 From git at git.haskell.org Wed Oct 1 13:43:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 13:43:49 +0000 (UTC) Subject: [commit: ghc] wip/validate-T9502: Make mapAccumL a good consumer (5bda348) Message-ID: <20141001134349.57DF53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/validate-T9502 Link : http://ghc.haskell.org/trac/ghc/changeset/5bda348b3e27a59fe9ec6ed86a89e3e0eff3f257/ghc >--------------------------------------------------------------- commit 5bda348b3e27a59fe9ec6ed86a89e3e0eff3f257 Author: David Feuer Date: Wed Oct 1 15:42:27 2014 +0200 Make mapAccumL a good consumer This fixes #9502. >--------------------------------------------------------------- 5bda348b3e27a59fe9ec6ed86a89e3e0eff3f257 libraries/base/Data/OldList.hs | 17 +++++++++++++++++ libraries/base/changelog.md | 2 +- 2 files changed, 18 insertions(+), 1 deletion(-) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index fe0f38e..9b6a431 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -481,11 +481,28 @@ mapAccumL :: (acc -> x -> (acc, y)) -- Function of elt of input list -> acc -- Initial accumulator -> [x] -- Input list -> (acc, [y]) -- Final accumulator and result list +{-# NOINLINE [1] mapAccumL #-} mapAccumL _ s [] = (s, []) mapAccumL f s (x:xs) = (s'',y:ys) where (s', y ) = f s x (s'',ys) = mapAccumL f s' xs +{-# RULES +"mapAccumL" [~1] forall f s xs . mapAccumL f s xs = foldr (mapAccumLF f) pairWithNil xs s +"mapAccumLList" [1] forall f s xs . foldr (mapAccumLF f) pairWithNil xs s = mapAccumL f s xs + #-} + +pairWithNil :: acc -> (acc, [y]) +{-# INLINE [0] pairWithNil #-} +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 + (s'', ys) = r s' + in (s'', y:ys) + + -- | The 'mapAccumR' function behaves like a combination of 'map' and -- 'foldr'; it applies a function to each element of a list, passing -- an accumulating parameter from right to left, and returning a final diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index c594c2f..09b749a 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -77,7 +77,7 @@ second argument, so that the fusion RULES for it do not change the semantics. (#9596) - * `scanr` now takes part in list fusion (#9355) + * `scanr` and `mapAccumL` now take part in list fusion (#9355, #9502) ## 4.7.0.1 *Jul 2014* From git at git.haskell.org Wed Oct 1 13:46:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 13:46:50 +0000 (UTC) Subject: [commit: ghc] wip/validate-T9355: Make scanr a good producer and consumer (7fdedf0) Message-ID: <20141001134650.943933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/validate-T9355 Link : http://ghc.haskell.org/trac/ghc/changeset/7fdedf05b2d267dda6549e71d5a9da23110c3881/ghc >--------------------------------------------------------------- commit 7fdedf05b2d267dda6549e71d5a9da23110c3881 Author: David Feuer Date: Wed Oct 1 15:24:43 2014 +0200 Make scanr a good producer and consumer This fixes #9355. >--------------------------------------------------------------- 7fdedf05b2d267dda6549e71d5a9da23110c3881 libraries/base/GHC/List.lhs | 18 ++++++++++++++++++ libraries/base/changelog.md | 2 ++ 2 files changed, 20 insertions(+) diff --git a/libraries/base/GHC/List.lhs b/libraries/base/GHC/List.lhs index 8c8e4bb..51f68ab 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -229,11 +229,29 @@ foldr1 _ [] = errorEmptyList "foldr1" -- -- > head (scanr f z xs) == foldr f z xs. +{-# NOINLINE [1] scanr #-} scanr :: (a -> b -> b) -> b -> [a] -> [b] scanr _ q0 [] = [q0] scanr f q0 (x:xs) = f x q : qs where qs@(q:_) = scanr f q0 xs +{-# INLINE [0] strictUncurryScanr #-} +strictUncurryScanr :: (a -> b -> c) -> (a, b) -> c +strictUncurryScanr f pair = case pair of + (x, y) -> f x y + +{-# INLINE [0] scanrFB #-} +scanrFB :: (a -> b -> b) -> (b -> c -> c) -> a -> (b, c) -> (b, c) +scanrFB f c = \x (r, est) -> (f x r, r `c` est) + +{-# RULES +"scanr" [~1] forall f q0 ls . scanr f q0 ls = + build (\c n -> strictUncurryScanr c (foldr (scanrFB f c) (q0,n) ls)) +"scanrList" [1] forall f q0 ls . + strictUncurryScanr (:) (foldr (scanrFB f (:)) (q0,[]) ls) = + scanr f q0 ls + #-} + -- | 'scanr1' is a variant of 'scanr' that has no starting value argument. scanr1 :: (a -> a -> a) -> [a] -> [a] diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 7529782..c594c2f 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -77,6 +77,8 @@ second argument, so that the fusion RULES for it do not change the semantics. (#9596) + * `scanr` now takes part in list fusion (#9355) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 From git at git.haskell.org Wed Oct 1 13:47:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 13:47:07 +0000 (UTC) Subject: [commit: ghc] wip/validate-T9502: Make mapAccumL a good consumer (6680f4f) Message-ID: <20141001134707.F23223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/validate-T9502 Link : http://ghc.haskell.org/trac/ghc/changeset/6680f4fdebf23c1d8e443f2c658e3bc3ab43f295/ghc >--------------------------------------------------------------- commit 6680f4fdebf23c1d8e443f2c658e3bc3ab43f295 Author: David Feuer Date: Wed Oct 1 15:42:27 2014 +0200 Make mapAccumL a good consumer This fixes #9502. >--------------------------------------------------------------- 6680f4fdebf23c1d8e443f2c658e3bc3ab43f295 libraries/base/Data/OldList.hs | 17 +++++++++++++++++ libraries/base/changelog.md | 2 +- 2 files changed, 18 insertions(+), 1 deletion(-) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index fe0f38e..9b6a431 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -481,11 +481,28 @@ mapAccumL :: (acc -> x -> (acc, y)) -- Function of elt of input list -> acc -- Initial accumulator -> [x] -- Input list -> (acc, [y]) -- Final accumulator and result list +{-# NOINLINE [1] mapAccumL #-} mapAccumL _ s [] = (s, []) mapAccumL f s (x:xs) = (s'',y:ys) where (s', y ) = f s x (s'',ys) = mapAccumL f s' xs +{-# RULES +"mapAccumL" [~1] forall f s xs . mapAccumL f s xs = foldr (mapAccumLF f) pairWithNil xs s +"mapAccumLList" [1] forall f s xs . foldr (mapAccumLF f) pairWithNil xs s = mapAccumL f s xs + #-} + +pairWithNil :: acc -> (acc, [y]) +{-# INLINE [0] pairWithNil #-} +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 + (s'', ys) = r s' + in (s'', y:ys) + + -- | The 'mapAccumR' function behaves like a combination of 'map' and -- 'foldr'; it applies a function to each element of a list, passing -- an accumulating parameter from right to left, and returning a final diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index c594c2f..09b749a 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -77,7 +77,7 @@ second argument, so that the fusion RULES for it do not change the semantics. (#9596) - * `scanr` now takes part in list fusion (#9355) + * `scanr` and `mapAccumL` now take part in list fusion (#9355, #9502) ## 4.7.0.1 *Jul 2014* From git at git.haskell.org Wed Oct 1 13:47:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 13:47:10 +0000 (UTC) Subject: [commit: ghc] wip/validate-T9502's head updated: Make mapAccumL a good consumer (6680f4f) Message-ID: <20141001134710.1E4003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/validate-T9502' now includes: 7fdedf0 Make scanr a good producer and consumer 6680f4f Make mapAccumL a good consumer From git at git.haskell.org Wed Oct 1 13:58:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 13:58:32 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate-T9536' created Message-ID: <20141001135832.C2F063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/validate-T9536 Referencing: 1bc83b8a3d5ac01357d42b14d513312e98e2bb29 From git at git.haskell.org Wed Oct 1 13:58:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 13:58:35 +0000 (UTC) Subject: [commit: ghc] wip/validate-T9536: Fusion rule for "foldr k z (x:build g)" (1bc83b8) Message-ID: <20141001135835.5883F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/validate-T9536 Link : http://ghc.haskell.org/trac/ghc/changeset/1bc83b8a3d5ac01357d42b14d513312e98e2bb29/ghc >--------------------------------------------------------------- commit 1bc83b8a3d5ac01357d42b14d513312e98e2bb29 Author: David Feuer Date: Wed Oct 1 15:57:27 2014 +0200 Fusion rule for "foldr k z (x:build g)" There seem to be various issues with general fold/cons and even cons/build rules, but it seems pretty clear to me that the simple fold/cons/build rule is a good idea. It doesn't do much for nofib allocation, but it seems to improve some other analyses and speed several benchmarks up. Implements #9536. >--------------------------------------------------------------- 1bc83b8a3d5ac01357d42b14d513312e98e2bb29 libraries/base/GHC/Base.lhs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/libraries/base/GHC/Base.lhs b/libraries/base/GHC/Base.lhs index 8b51c07..f9d01b5 100644 --- a/libraries/base/GHC/Base.lhs +++ b/libraries/base/GHC/Base.lhs @@ -788,6 +788,9 @@ augment g xs = g (:) xs "foldr/single" forall k z x. foldr k z [x] = k x z "foldr/nil" forall k z. foldr k z [] = z +"foldr/cons/build" forall k z x (g::forall b. (a->b->b) -> b -> b) . + foldr k z (x:build g) = k x (g k z) + "augment/build" forall (g::forall b. (a->b->b) -> b -> b) (h::forall b. (a->b->b) -> b -> b) . augment g (build h) = build (\c n -> g c (h c n)) From git at git.haskell.org Wed Oct 1 14:00:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 14:00:42 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate-T9546' created Message-ID: <20141001140042.E21803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/validate-T9546 Referencing: 18dc7324765b04781158d2a97b6bdbd07812bff4 From git at git.haskell.org Wed Oct 1 14:00:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 14:00:45 +0000 (UTC) Subject: [commit: ghc] wip/validate-T9546: Make filterM a good consumer (18dc732) Message-ID: <20141001140045.74A043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/validate-T9546 Link : http://ghc.haskell.org/trac/ghc/changeset/18dc7324765b04781158d2a97b6bdbd07812bff4/ghc >--------------------------------------------------------------- commit 18dc7324765b04781158d2a97b6bdbd07812bff4 Author: David Feuer Date: Wed Oct 1 15:59:39 2014 +0200 Make filterM a good consumer analogously to mapM. Fixes #9546. >--------------------------------------------------------------- 18dc7324765b04781158d2a97b6bdbd07812bff4 libraries/base/Control/Monad.hs | 12 +++++++----- libraries/base/changelog.md | 3 ++- 2 files changed, 9 insertions(+), 6 deletions(-) diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs index 619a2ba..db46dea 100644 --- a/libraries/base/Control/Monad.hs +++ b/libraries/base/Control/Monad.hs @@ -93,12 +93,14 @@ guard False = empty -- | This generalizes the list-based 'filter' function. +{-# INLINE filterM #-} filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a] -filterM _ [] = return [] -filterM p (x:xs) = do - flg <- p x - ys <- filterM p xs - return (if flg then x:ys else ys) +filterM p = foldr go (return []) + where + go x r = do + flg <- p x + ys <- r + return (if flg then x:ys else ys) infixr 1 <=<, >=> diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 09b749a..f7d8b1c 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -77,7 +77,8 @@ second argument, so that the fusion RULES for it do not change the semantics. (#9596) - * `scanr` and `mapAccumL` now take part in list fusion (#9355, #9502) + * `scanr`, `mapAccumL` and `filterM` now take part in list fusion (#9355, + #9502, #9546) ## 4.7.0.1 *Jul 2014* From git at git.haskell.org Wed Oct 1 14:03:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 14:03:29 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate-T9561' created Message-ID: <20141001140329.3F18B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/validate-T9561 Referencing: 7599458dc577535377e45ae7ae0993d93cdab8ad From git at git.haskell.org Wed Oct 1 14:03:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 14:03:31 +0000 (UTC) Subject: [commit: ghc] wip/validate-T9561: Simplify mergeSATInfo by using zipWith (7599458) Message-ID: <20141001140331.C33EB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/validate-T9561 Link : http://ghc.haskell.org/trac/ghc/changeset/7599458dc577535377e45ae7ae0993d93cdab8ad/ghc >--------------------------------------------------------------- commit 7599458dc577535377e45ae7ae0993d93cdab8ad Author: David Feuer Date: Wed Oct 1 16:02:45 2014 +0200 Simplify mergeSATInfo by using zipWith Closes #9561. >--------------------------------------------------------------- 7599458dc577535377e45ae7ae0993d93cdab8ad compiler/simplCore/SAT.lhs | 27 ++++++++++++++++++--------- 1 file changed, 18 insertions(+), 9 deletions(-) diff --git a/compiler/simplCore/SAT.lhs b/compiler/simplCore/SAT.lhs index f973c35..bd5b718 100644 --- a/compiler/simplCore/SAT.lhs +++ b/compiler/simplCore/SAT.lhs @@ -139,15 +139,24 @@ pprStaticness NotStatic = ptext (sLit "NS") mergeSATInfo :: SATInfo -> SATInfo -> SATInfo -mergeSATInfo [] _ = [] -mergeSATInfo _ [] = [] -mergeSATInfo (NotStatic:statics) (_:apps) = NotStatic : mergeSATInfo statics apps -mergeSATInfo (_:statics) (NotStatic:apps) = NotStatic : mergeSATInfo statics apps -mergeSATInfo ((Static (VarApp v)):statics) ((Static (VarApp v')):apps) = (if v == v' then Static (VarApp v) else NotStatic) : mergeSATInfo statics apps -mergeSATInfo ((Static (TypeApp t)):statics) ((Static (TypeApp t')):apps) = (if t `eqType` t' then Static (TypeApp t) else NotStatic) : mergeSATInfo statics apps -mergeSATInfo ((Static (CoApp c)):statics) ((Static (CoApp c')):apps) = (if c `coreEqCoercion` c' then Static (CoApp c) else NotStatic) : mergeSATInfo statics apps -mergeSATInfo l r = pprPanic "mergeSATInfo" $ ptext (sLit "Left:") <> pprSATInfo l <> ptext (sLit ", ") - <> ptext (sLit "Right:") <> pprSATInfo r +mergeSATInfo l r = zipWith mergeSA l r + where + mergeSA NotStatic _ = NotStatic + mergeSA _ NotStatic = NotStatic + mergeSA (Static (VarApp v)) (Static (VarApp v')) + | v == v' = Static (VarApp v) + | otherwise = NotStatic + mergeSA (Static (TypeApp t)) (Static (TypeApp t')) + | t `eqType` t' = Static (TypeApp t) + | otherwise = NotStatic + mergeSA (Static (CoApp c)) (Static (CoApp c')) + | c `coreEqCoercion` c' = Static (CoApp c) + | otherwise = NotStatic + mergeSA _ _ = pprPanic "mergeSATInfo" $ + ptext (sLit "Left:") + <> pprSATInfo l <> ptext (sLit ", ") + <> ptext (sLit "Right:") + <> pprSATInfo r mergeIdSATInfo :: IdSATInfo -> IdSATInfo -> IdSATInfo mergeIdSATInfo = plusUFM_C mergeSATInfo From git at git.haskell.org Wed Oct 1 14:33:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 14:33:38 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Better printing of dump messages (0ce6d34) Message-ID: <20141001143338.90AD93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/0ce6d34dcada4bfbb9dcd0e8b334e438620a1a93/ghc >--------------------------------------------------------------- commit 0ce6d34dcada4bfbb9dcd0e8b334e438620a1a93 Author: Simon Peyton Jones Date: Wed Oct 1 15:33:13 2014 +0100 Better printing of dump messages >--------------------------------------------------------------- 0ce6d34dcada4bfbb9dcd0e8b334e438620a1a93 compiler/coreSyn/CorePrep.lhs | 4 ++-- compiler/deSugar/Desugar.lhs | 7 +++--- compiler/main/ErrUtils.lhs | 39 +++++++++++++++++++------------- compiler/main/TidyPgm.lhs | 8 ++++--- compiler/nativeGen/AsmCodeGen.lhs | 8 +++---- compiler/simplCore/CoreMonad.lhs | 47 ++++++++++++++++++++++++++++----------- compiler/simplCore/SimplCore.lhs | 33 ++++++++++++++------------- compiler/simplCore/Simplify.lhs | 5 +++-- compiler/typecheck/TcDeriv.lhs | 4 ++-- compiler/typecheck/TcRnDriver.lhs | 2 +- compiler/typecheck/TcRnMonad.lhs | 23 +++++++++---------- compiler/utils/Outputable.lhs | 30 ++++++++++++++++--------- 12 files changed, 126 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 0ce6d34dcada4bfbb9dcd0e8b334e438620a1a93 From git at git.haskell.org Wed Oct 1 14:33:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 14:33:41 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Error message wibbles (5064c32) Message-ID: <20141001143341.4A8F93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/5064c32a9b242e2c79ecf34ce0cec8c795965ac2/ghc >--------------------------------------------------------------- commit 5064c32a9b242e2c79ecf34ce0cec8c795965ac2 Author: Simon Peyton Jones Date: Wed Oct 1 15:33:25 2014 +0100 Error message wibbles >--------------------------------------------------------------- 5064c32a9b242e2c79ecf34ce0cec8c795965ac2 .../tests/deSugar/should_compile/T2431.stderr | 9 +-- testsuite/tests/gadt/gadt7.stderr | 6 +- .../indexed-types/should_fail/NoMatchErr.stderr | 2 +- .../tests/indexed-types/should_fail/T1897b.stderr | 2 +- .../tests/indexed-types/should_fail/T2544.stderr | 2 +- .../tests/indexed-types/should_fail/T9036.stderr | 2 +- .../tests/numeric/should_compile/T7116.stdout | 28 +++---- testsuite/tests/polykinds/T7438.stderr | 6 +- .../tests/roles/should_compile/Roles13.stderr | 14 ++-- .../tests/simplCore/should_compile/EvalTest.stdout | 2 +- .../tests/simplCore/should_compile/T3717.stderr | 8 +- .../tests/simplCore/should_compile/T3772.stdout | 18 ++--- .../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 | 24 ++---- .../tests/simplCore/should_compile/T7360.stderr | 20 ++--- .../tests/simplCore/should_compile/T7785.stderr | 2 +- .../tests/simplCore/should_compile/T7865.stdout | 8 +- .../tests/simplCore/should_compile/T8832.stdout | 20 ++--- .../tests/simplCore/should_compile/T8848.stderr | 18 ++--- .../tests/simplCore/should_compile/T9400.stderr | 30 ++++---- .../tests/simplCore/should_compile/rule2.stderr | 2 +- .../simplCore/should_compile/spec-inline.stderr | 87 ++++++++++------------ 27 files changed, 175 insertions(+), 214 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 5064c32a9b242e2c79ecf34ce0cec8c795965ac2 From git at git.haskell.org Wed Oct 1 15:54:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 15:54:37 +0000 (UTC) Subject: [commit: ghc] master: Update Win32 submodule to avoid potential -Werror failure (864bed7) Message-ID: <20141001155437.62B573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/864bed729eaee9531ada4ba1c869c676893f51bd/ghc >--------------------------------------------------------------- commit 864bed729eaee9531ada4ba1c869c676893f51bd Author: Herbert Valerio Riedel Date: Wed Oct 1 17:53:14 2014 +0200 Update Win32 submodule to avoid potential -Werror failure >--------------------------------------------------------------- 864bed729eaee9531ada4ba1c869c676893f51bd libraries/Win32 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Win32 b/libraries/Win32 index c51e81a..a955d59 160000 --- a/libraries/Win32 +++ b/libraries/Win32 @@ -1 +1 @@ -Subproject commit c51e81a43cd5e9540453bd5ca6da8992245a4774 +Subproject commit a955d59c48f8b3bdab7eeea29660d98b0d44343b From git at git.haskell.org Wed Oct 1 16:21:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 16:21:21 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate-T9561' deleted Message-ID: <20141001162121.18A793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/validate-T9561 From git at git.haskell.org Wed Oct 1 16:21:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 16:21:23 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate-T9495' deleted Message-ID: <20141001162123.199E53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/validate-T9495 From git at git.haskell.org Wed Oct 1 16:21:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 16:21:25 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate-T9502' deleted Message-ID: <20141001162125.1A71F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/validate-T9502 From git at git.haskell.org Wed Oct 1 16:21:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 16:21:27 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate-T9355' deleted Message-ID: <20141001162127.1C0333A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/validate-T9355 From git at git.haskell.org Wed Oct 1 16:21:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 16:21:29 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate-T9546' deleted Message-ID: <20141001162129.1D7E93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/validate-T9546 From git at git.haskell.org Wed Oct 1 16:21:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 16:21:31 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate-T9536' deleted Message-ID: <20141001162131.1E60B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/validate-T9536 From git at git.haskell.org Wed Oct 1 16:21:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 16:21:33 +0000 (UTC) Subject: [commit: ghc] master: Make scanr a good producer and consumer (4e1dfc3) Message-ID: <20141001162133.BD6F43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4e1dfc3767167dddd0e151a2df8305b12aa0f49c/ghc >--------------------------------------------------------------- commit 4e1dfc3767167dddd0e151a2df8305b12aa0f49c Author: David Feuer Date: Wed Oct 1 15:24:43 2014 +0200 Make scanr a good producer and consumer This fixes #9355. >--------------------------------------------------------------- 4e1dfc3767167dddd0e151a2df8305b12aa0f49c libraries/base/GHC/List.lhs | 18 ++++++++++++++++++ libraries/base/changelog.md | 2 ++ 2 files changed, 20 insertions(+) diff --git a/libraries/base/GHC/List.lhs b/libraries/base/GHC/List.lhs index 8c8e4bb..51f68ab 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -229,11 +229,29 @@ foldr1 _ [] = errorEmptyList "foldr1" -- -- > head (scanr f z xs) == foldr f z xs. +{-# NOINLINE [1] scanr #-} scanr :: (a -> b -> b) -> b -> [a] -> [b] scanr _ q0 [] = [q0] scanr f q0 (x:xs) = f x q : qs where qs@(q:_) = scanr f q0 xs +{-# INLINE [0] strictUncurryScanr #-} +strictUncurryScanr :: (a -> b -> c) -> (a, b) -> c +strictUncurryScanr f pair = case pair of + (x, y) -> f x y + +{-# INLINE [0] scanrFB #-} +scanrFB :: (a -> b -> b) -> (b -> c -> c) -> a -> (b, c) -> (b, c) +scanrFB f c = \x (r, est) -> (f x r, r `c` est) + +{-# RULES +"scanr" [~1] forall f q0 ls . scanr f q0 ls = + build (\c n -> strictUncurryScanr c (foldr (scanrFB f c) (q0,n) ls)) +"scanrList" [1] forall f q0 ls . + strictUncurryScanr (:) (foldr (scanrFB f (:)) (q0,[]) ls) = + scanr f q0 ls + #-} + -- | 'scanr1' is a variant of 'scanr' that has no starting value argument. scanr1 :: (a -> a -> a) -> [a] -> [a] diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 7529782..c594c2f 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -77,6 +77,8 @@ second argument, so that the fusion RULES for it do not change the semantics. (#9596) + * `scanr` now takes part in list fusion (#9355) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 From git at git.haskell.org Wed Oct 1 16:21:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 16:21:36 +0000 (UTC) Subject: [commit: ghc] master: Make mapAccumL a good consumer (d41dd03) Message-ID: <20141001162136.692D03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d41dd03fdf0ef723ca31f5a11f07a54a15d2cbc0/ghc >--------------------------------------------------------------- commit d41dd03fdf0ef723ca31f5a11f07a54a15d2cbc0 Author: David Feuer Date: Wed Oct 1 15:42:27 2014 +0200 Make mapAccumL a good consumer This fixes #9502. >--------------------------------------------------------------- d41dd03fdf0ef723ca31f5a11f07a54a15d2cbc0 libraries/base/Data/OldList.hs | 17 +++++++++++++++++ libraries/base/changelog.md | 2 +- 2 files changed, 18 insertions(+), 1 deletion(-) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index fe0f38e..9b6a431 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -481,11 +481,28 @@ mapAccumL :: (acc -> x -> (acc, y)) -- Function of elt of input list -> acc -- Initial accumulator -> [x] -- Input list -> (acc, [y]) -- Final accumulator and result list +{-# NOINLINE [1] mapAccumL #-} mapAccumL _ s [] = (s, []) mapAccumL f s (x:xs) = (s'',y:ys) where (s', y ) = f s x (s'',ys) = mapAccumL f s' xs +{-# RULES +"mapAccumL" [~1] forall f s xs . mapAccumL f s xs = foldr (mapAccumLF f) pairWithNil xs s +"mapAccumLList" [1] forall f s xs . foldr (mapAccumLF f) pairWithNil xs s = mapAccumL f s xs + #-} + +pairWithNil :: acc -> (acc, [y]) +{-# INLINE [0] pairWithNil #-} +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 + (s'', ys) = r s' + in (s'', y:ys) + + -- | The 'mapAccumR' function behaves like a combination of 'map' and -- 'foldr'; it applies a function to each element of a list, passing -- an accumulating parameter from right to left, and returning a final diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index c594c2f..09b749a 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -77,7 +77,7 @@ second argument, so that the fusion RULES for it do not change the semantics. (#9596) - * `scanr` now takes part in list fusion (#9355) + * `scanr` and `mapAccumL` now take part in list fusion (#9355, #9502) ## 4.7.0.1 *Jul 2014* From git at git.haskell.org Wed Oct 1 16:21:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 16:21:38 +0000 (UTC) Subject: [commit: ghc] master: Fusion rule for "foldr k z (x:build g)" (7893210) Message-ID: <20141001162138.F314B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/789321098f86fd3c4483b24372f8938f89b12312/ghc >--------------------------------------------------------------- commit 789321098f86fd3c4483b24372f8938f89b12312 Author: David Feuer Date: Wed Oct 1 15:57:27 2014 +0200 Fusion rule for "foldr k z (x:build g)" There seem to be various issues with general fold/cons and even cons/build rules, but it seems pretty clear to me that the simple fold/cons/build rule is a good idea. It doesn't do much for nofib allocation, but it seems to improve some other analyses and speed several benchmarks up. Implements #9536. >--------------------------------------------------------------- 789321098f86fd3c4483b24372f8938f89b12312 libraries/base/GHC/Base.lhs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/libraries/base/GHC/Base.lhs b/libraries/base/GHC/Base.lhs index 8b51c07..f9d01b5 100644 --- a/libraries/base/GHC/Base.lhs +++ b/libraries/base/GHC/Base.lhs @@ -788,6 +788,9 @@ augment g xs = g (:) xs "foldr/single" forall k z x. foldr k z [x] = k x z "foldr/nil" forall k z. foldr k z [] = z +"foldr/cons/build" forall k z x (g::forall b. (a->b->b) -> b -> b) . + foldr k z (x:build g) = k x (g k z) + "augment/build" forall (g::forall b. (a->b->b) -> b -> b) (h::forall b. (a->b->b) -> b -> b) . augment g (build h) = build (\c n -> g c (h c n)) From git at git.haskell.org Wed Oct 1 16:21:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 16:21:41 +0000 (UTC) Subject: [commit: ghc] master: Make foldr2 a bit more strict (488e95b) Message-ID: <20141001162141.9719C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/488e95b433d4f7568aa89622c729e64aa3b6520d/ghc >--------------------------------------------------------------- commit 488e95b433d4f7568aa89622c729e64aa3b6520d Author: David Feuer Date: Wed Oct 1 15:02:33 2014 +0200 Make foldr2 a bit more strict in order to make its RULES semantics preserving. This fixes #9495. >--------------------------------------------------------------- 488e95b433d4f7568aa89622c729e64aa3b6520d docs/users_guide/bugs.xml | 9 ++++++++- libraries/base/GHC/List.lhs | 43 +++++++++++++++++++++++++++++-------------- libraries/base/changelog.md | 4 ++++ 3 files changed, 41 insertions(+), 15 deletions(-) diff --git a/docs/users_guide/bugs.xml b/docs/users_guide/bugs.xml index dba0d86..f9dfaae 100644 --- a/docs/users_guide/bugs.xml +++ b/docs/users_guide/bugs.xml @@ -291,7 +291,14 @@ checking for duplicates. The reason for this is efficiency, pure and simple. if you get stuck on it. - + + zip and zipWith semantics + zip and zipWith can give + less defined results than the Report specifies in certain cases. This deviation + is needed to allow more opportunities for list fusion. In particular, + termination of the left list cannot be used to avoid hitting bottom in the + right list. See the documentation for details. + Reading integers diff --git a/libraries/base/GHC/List.lhs b/libraries/base/GHC/List.lhs index ffcc8ab..8c8e4bb 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -646,7 +646,7 @@ xs !! (I# n0) | isTrue# (n0 <# 0#) = error "Prelude.(!!): negative index\n" foldr2 :: (a -> b -> c -> c) -> c -> [a] -> [b] -> c foldr2 k z = go where - go [] _ys = z + go [] ys = ys `seq` z -- see #9495 for the seq go _xs [] = z go (x:xs) (y:ys) = k x y (go xs ys) {-# INLINE [0] foldr2 #-} @@ -670,16 +670,6 @@ foldr2_right k _z y r (x:xs) = k x y (r xs) #-} \end{code} -The foldr2/right rule isn't exactly right, because it changes -the strictness of foldr2 (and thereby zip) - -E.g. main = print (null (zip nonobviousNil (build undefined))) - where nonobviousNil = f 3 - f n = if n == 0 then [] else f (n-1) - -I'm going to leave it though. - - Zips for larger tuples are in the List module. \begin{code} @@ -687,10 +677,22 @@ Zips for larger tuples are in the List module. -- | 'zip' takes two lists and returns a list of corresponding pairs. -- If one input list is short, excess elements of the longer list are -- discarded. +-- +-- NOTE: GHC's implementation of @zip@ deviates slightly from the +-- standard. In particular, Haskell 98 and Haskell 2010 require that +-- @zip [x1,x2,...,xn] (y1:y2:...:yn:_|_) = [(x1,y1),(x2,y2),...,(xn,yn)]@ +-- In GHC, however, +-- @zip [x1,x2,...,xn] (y1:y2:...:yn:_|_) = (x1,y1):(x2,y2):...:(xn,yn):_|_@ +-- That is, you cannot use termination of the left list to avoid hitting +-- bottom in the right list. + +-- This deviation is necessary to make fusion with 'build' in the right +-- list preserve semantics. {-# NOINLINE [1] zip #-} zip :: [a] -> [b] -> [(a,b)] +zip [] bs = bs `seq` [] -- see #9495 for the seq +zip _as [] = [] zip (a:as) (b:bs) = (a,b) : zip as bs -zip _ _ = [] {-# INLINE [0] zipFB #-} zipFB :: ((a, b) -> c -> d) -> a -> b -> c -> d @@ -723,10 +725,23 @@ zip3 _ _ _ = [] -- as the first argument, instead of a tupling function. -- For example, @'zipWith' (+)@ is applied to two lists to produce the -- list of corresponding sums. +-- +-- NOTE: GHC's implementation of @zipWith@ deviates slightly from the +-- standard. In particular, Haskell 98 and Haskell 2010 require that +-- @zipWith (,) [x1,x2,...,xn] (y1:y2:...:yn:_|_) = [(x1,y1),(x2,y2),...,(xn,yn)]@ +-- In GHC, however, +-- @zipWith (,) [x1,x2,...,xn] (y1:y2:...:yn:_|_) = (x1,y1):(x2,y2):...:(xn,yn):_|_@ +-- That is, you cannot use termination of the left list to avoid hitting +-- bottom in the right list. + +-- This deviation is necessary to make fusion with 'build' in the right +-- list preserve semantics. + {-# NOINLINE [1] zipWith #-} zipWith :: (a->b->c) -> [a]->[b]->[c] -zipWith f (a:as) (b:bs) = f a b : zipWith f as bs -zipWith _ _ _ = [] +zipWith _f [] bs = bs `seq` [] -- see #9495 for the seq +zipWith _f _as [] = [] +zipWith f (a:as) (b:bs) = f a b : zipWith f as bs -- zipWithFB must have arity 2 since it gets two arguments in the "zipWith" -- rule; it might not get inlined otherwise diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 7b168fe..7529782 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -73,6 +73,10 @@ 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) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 From git at git.haskell.org Wed Oct 1 16:21:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 16:21:44 +0000 (UTC) Subject: [commit: ghc] master: Make filterM a good consumer (96a4062) Message-ID: <20141001162144.3F9AE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/96a4062a7e7587592829c045b3b12c755cc8e329/ghc >--------------------------------------------------------------- commit 96a4062a7e7587592829c045b3b12c755cc8e329 Author: David Feuer Date: Wed Oct 1 15:59:39 2014 +0200 Make filterM a good consumer analogously to mapM. Fixes #9546. >--------------------------------------------------------------- 96a4062a7e7587592829c045b3b12c755cc8e329 libraries/base/Control/Monad.hs | 12 +++++++----- libraries/base/changelog.md | 3 ++- 2 files changed, 9 insertions(+), 6 deletions(-) diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs index 619a2ba..db46dea 100644 --- a/libraries/base/Control/Monad.hs +++ b/libraries/base/Control/Monad.hs @@ -93,12 +93,14 @@ guard False = empty -- | This generalizes the list-based 'filter' function. +{-# INLINE filterM #-} filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a] -filterM _ [] = return [] -filterM p (x:xs) = do - flg <- p x - ys <- filterM p xs - return (if flg then x:ys else ys) +filterM p = foldr go (return []) + where + go x r = do + flg <- p x + ys <- r + return (if flg then x:ys else ys) infixr 1 <=<, >=> diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 09b749a..f7d8b1c 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -77,7 +77,8 @@ second argument, so that the fusion RULES for it do not change the semantics. (#9596) - * `scanr` and `mapAccumL` now take part in list fusion (#9355, #9502) + * `scanr`, `mapAccumL` and `filterM` now take part in list fusion (#9355, + #9502, #9546) ## 4.7.0.1 *Jul 2014* From git at git.haskell.org Wed Oct 1 16:21:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 16:21:46 +0000 (UTC) Subject: [commit: ghc] master: Simplify mergeSATInfo by using zipWith (93b8d0f) Message-ID: <20141001162146.CF27C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/93b8d0fd63cf8e00ca37c1ce76b93d4ee1fc56f8/ghc >--------------------------------------------------------------- commit 93b8d0fd63cf8e00ca37c1ce76b93d4ee1fc56f8 Author: David Feuer Date: Wed Oct 1 16:02:45 2014 +0200 Simplify mergeSATInfo by using zipWith Closes #9561. >--------------------------------------------------------------- 93b8d0fd63cf8e00ca37c1ce76b93d4ee1fc56f8 compiler/simplCore/SAT.lhs | 27 ++++++++++++++++++--------- 1 file changed, 18 insertions(+), 9 deletions(-) diff --git a/compiler/simplCore/SAT.lhs b/compiler/simplCore/SAT.lhs index f973c35..bd5b718 100644 --- a/compiler/simplCore/SAT.lhs +++ b/compiler/simplCore/SAT.lhs @@ -139,15 +139,24 @@ pprStaticness NotStatic = ptext (sLit "NS") mergeSATInfo :: SATInfo -> SATInfo -> SATInfo -mergeSATInfo [] _ = [] -mergeSATInfo _ [] = [] -mergeSATInfo (NotStatic:statics) (_:apps) = NotStatic : mergeSATInfo statics apps -mergeSATInfo (_:statics) (NotStatic:apps) = NotStatic : mergeSATInfo statics apps -mergeSATInfo ((Static (VarApp v)):statics) ((Static (VarApp v')):apps) = (if v == v' then Static (VarApp v) else NotStatic) : mergeSATInfo statics apps -mergeSATInfo ((Static (TypeApp t)):statics) ((Static (TypeApp t')):apps) = (if t `eqType` t' then Static (TypeApp t) else NotStatic) : mergeSATInfo statics apps -mergeSATInfo ((Static (CoApp c)):statics) ((Static (CoApp c')):apps) = (if c `coreEqCoercion` c' then Static (CoApp c) else NotStatic) : mergeSATInfo statics apps -mergeSATInfo l r = pprPanic "mergeSATInfo" $ ptext (sLit "Left:") <> pprSATInfo l <> ptext (sLit ", ") - <> ptext (sLit "Right:") <> pprSATInfo r +mergeSATInfo l r = zipWith mergeSA l r + where + mergeSA NotStatic _ = NotStatic + mergeSA _ NotStatic = NotStatic + mergeSA (Static (VarApp v)) (Static (VarApp v')) + | v == v' = Static (VarApp v) + | otherwise = NotStatic + mergeSA (Static (TypeApp t)) (Static (TypeApp t')) + | t `eqType` t' = Static (TypeApp t) + | otherwise = NotStatic + mergeSA (Static (CoApp c)) (Static (CoApp c')) + | c `coreEqCoercion` c' = Static (CoApp c) + | otherwise = NotStatic + mergeSA _ _ = pprPanic "mergeSATInfo" $ + ptext (sLit "Left:") + <> pprSATInfo l <> ptext (sLit ", ") + <> ptext (sLit "Right:") + <> pprSATInfo r mergeIdSATInfo :: IdSATInfo -> IdSATInfo -> IdSATInfo mergeIdSATInfo = plusUFM_C mergeSATInfo From git at git.haskell.org Wed Oct 1 20:01:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 20:01:31 +0000 (UTC) Subject: [commit: ghc] master: First stab at making ./validate less verbose (bcbb045) Message-ID: <20141001200131.37BFF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bcbb045469df987389ab791633c75f2e05c151a8/ghc >--------------------------------------------------------------- commit bcbb045469df987389ab791633c75f2e05c151a8 Author: Austin Seipp Date: Wed Oct 1 15:01:25 2014 -0500 First stab at making ./validate less verbose Summary: When we run `./validate`, we are typically given an incredibly large heap of information, a large majority of which isn't really necessary. In particular, we don't really care about what `make` is doing, nor `ghc` itself most of the time. This reduces some of the output by making `./validate` quietier. By running: $ ./validate --quiet you'll enable `V=0` in the build, suppressing compiler messages, and you will suppress `make` commands by running `make` in 'silent mode'. It also runs the testsuite with `VERBOSE=2` to avoid extra lines. This alone makes quite a difference for build log sizes. Furthermore, by making the build logs less verbose, life is easier for systems like Harbormaster and Travis-CI, which dislike dealing with logs that are 10k lines or more. Signed-off-by: Austin Seipp Test Plan: iiam Reviewers: hvr, nomeata, ezyang Reviewed By: ezyang Subscribers: simonmar, ezyang, carter, thomie Projects: #ghc Differential Revision: https://phabricator.haskell.org/D298 >--------------------------------------------------------------- bcbb045469df987389ab791633c75f2e05c151a8 validate | 28 +++++++++++++++++++++++++--- 1 file changed, 25 insertions(+), 3 deletions(-) diff --git a/validate b/validate index 8ea9eac..c6e6d69 100755 --- a/validate +++ b/validate @@ -38,6 +38,7 @@ testsuite_only=0 hpc=NO speed=NORMAL use_dph=0 +be_quiet=0 while [ $# -gt 0 ] do @@ -66,6 +67,9 @@ do --dph) use_dph=1 ;; + --quiet) + be_quiet=1 + ;; --help) show_help exit 0;; @@ -128,9 +132,17 @@ fi if type gmake > /dev/null 2> /dev/null then - make="gmake" + if [ $be_quiet -eq 1 ]; then + make="gmake -s" + else + make="gmake" + fi else - make="make" + if [ $be_quiet -eq 1 ]; then + make="make -s" + else + make="make" + fi fi if [ $testsuite_only -eq 0 ]; then @@ -158,6 +170,11 @@ echo "Validating=YES" > mk/are-validating.mk echo "ValidateSpeed=$speed" >> mk/are-validating.mk echo "ValidateHpc=$hpc" >> mk/are-validating.mk +if [ $be_quiet -eq 1 ]; then + echo "V=0" >> mk/are-validating.mk # Less gunk + echo "GhcHcOpts=" >> mk/are-validating.mk # Remove -Rghc-timing +fi + if [ $use_dph -eq 1 ]; then echo "BUILD_DPH=YES" >> mk/are-validating.mk else @@ -221,7 +238,12 @@ FAST) ;; esac -$make $MAKE_TEST_TARGET stage=2 $BINDIST THREADS=$threads 2>&1 | tee testlog +verbosity=3 +if [ $be_quiet -eq 1 ]; then + verbosity=2 +fi + +$make $MAKE_TEST_TARGET stage=2 $BINDIST VERBOSE=$verbosity THREADS=$threads 2>&1 | tee testlog check_packages post-testsuite From git at git.haskell.org Wed Oct 1 20:50:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 20:50:21 +0000 (UTC) Subject: [commit: ghc] master: update cabal submodule to fix build failure on Solaris (15f661c) Message-ID: <20141001205021.CCDCF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/15f661cc7b40f1e956ba31b844b6713b31e5e9e8/ghc >--------------------------------------------------------------- commit 15f661cc7b40f1e956ba31b844b6713b31e5e9e8 Author: Karel Gardas Date: Wed Oct 1 22:48:13 2014 +0200 update cabal submodule to fix build failure on Solaris >--------------------------------------------------------------- 15f661cc7b40f1e956ba31b844b6713b31e5e9e8 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 02dc4a7..bb7e8f8 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 02dc4a7d84ba900be241a32a8ff9de22e6c67d12 +Subproject commit bb7e8f8b0170deb9c0486b10f4a9898503427d9f From git at git.haskell.org Wed Oct 1 21:29:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 21:29:52 +0000 (UTC) Subject: [commit: ghc] master: rts/includes: Fix up .dir-locals.el (f3b5e16) Message-ID: <20141001212952.E5A1F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f3b5e162232a75f61919f6cb7fc9ddbdeea9bede/ghc >--------------------------------------------------------------- commit f3b5e162232a75f61919f6cb7fc9ddbdeea9bede Author: Austin Seipp Date: Wed Oct 1 16:28:46 2014 -0500 rts/includes: Fix up .dir-locals.el After 23bb90460, these were slightly busted for `c-mode`. Signed-off-by: Austin Seipp >--------------------------------------------------------------- f3b5e162232a75f61919f6cb7fc9ddbdeea9bede includes/.dir-locals.el | 19 ++++++++++--------- rts/.dir-locals.el | 19 ++++++++++--------- 2 files changed, 20 insertions(+), 18 deletions(-) diff --git a/includes/.dir-locals.el b/includes/.dir-locals.el index c97af77..9e13ffa 100644 --- a/includes/.dir-locals.el +++ b/includes/.dir-locals.el @@ -1,12 +1,13 @@ ;;; Directory Local Variables ;;; See Info node `(emacs) Directory Variables' for more information. -((c-mode - (fill-column . 80)) - (emacs-lisp-mode - (buffer-file-coding-system . utf-8-unix) - (c-basic-offset . 4) - (indent-tabs-mode))) - - - +;; Default mode settings: no tabs, 80 column, UTF8 +((nil + (indent-tabs-mode . nil) + (fill-column . 80) + (buffer-file-coding-system . utf-8-unix)) + + ;; c-mode settings: 'Allman' BSD style, 4 space indents + (c-mode + (c-file-style . "BSD") + (c-basic-offset . 4))) diff --git a/rts/.dir-locals.el b/rts/.dir-locals.el index c97af77..9e13ffa 100644 --- a/rts/.dir-locals.el +++ b/rts/.dir-locals.el @@ -1,12 +1,13 @@ ;;; Directory Local Variables ;;; See Info node `(emacs) Directory Variables' for more information. -((c-mode - (fill-column . 80)) - (emacs-lisp-mode - (buffer-file-coding-system . utf-8-unix) - (c-basic-offset . 4) - (indent-tabs-mode))) - - - +;; Default mode settings: no tabs, 80 column, UTF8 +((nil + (indent-tabs-mode . nil) + (fill-column . 80) + (buffer-file-coding-system . utf-8-unix)) + + ;; c-mode settings: 'Allman' BSD style, 4 space indents + (c-mode + (c-file-style . "BSD") + (c-basic-offset . 4))) From git at git.haskell.org Wed Oct 1 21:37:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 21:37:42 +0000 (UTC) Subject: [commit: ghc] master: [ci skip] compiler: Kill last remaining tabs in CallArity (3a549ba) Message-ID: <20141001213742.9F88A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3a549ba309ecbc0328585d8d737d3b2a04d5682d/ghc >--------------------------------------------------------------- commit 3a549ba309ecbc0328585d8d737d3b2a04d5682d Author: Austin Seipp Date: Wed Oct 1 16:34:11 2014 -0500 [ci skip] compiler: Kill last remaining tabs in CallArity Signed-off-by: Austin Seipp >--------------------------------------------------------------- 3a549ba309ecbc0328585d8d737d3b2a04d5682d compiler/simplCore/CallArity.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs index 9dcb616..bead230 100644 --- a/compiler/simplCore/CallArity.hs +++ b/compiler/simplCore/CallArity.hs @@ -24,9 +24,9 @@ import Control.Arrow ( first, second ) {- %************************************************************************ -%* * +%* * Call Arity Analyis -%* * +%* * %************************************************************************ Note [Call Arity: The goal] From git at git.haskell.org Wed Oct 1 21:37:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 21:37:45 +0000 (UTC) Subject: [commit: ghc] master: [ci skip] Kill tabs in md5.h (ca3089d) Message-ID: <20141001213745.330B33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ca3089db9375d524ea0d9f4792d91c9f683a0079/ghc >--------------------------------------------------------------- commit ca3089db9375d524ea0d9f4792d91c9f683a0079 Author: Austin Seipp Date: Wed Oct 1 16:35:39 2014 -0500 [ci skip] Kill tabs in md5.h Signed-off-by: Austin Seipp >--------------------------------------------------------------- ca3089db9375d524ea0d9f4792d91c9f683a0079 compiler/utils/md5.h | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/utils/md5.h b/compiler/utils/md5.h index 8d375df..10c8dab 100644 --- a/compiler/utils/md5.h +++ b/compiler/utils/md5.h @@ -8,9 +8,9 @@ typedef HsWord32 word32; typedef HsWord8 byte; struct MD5Context { - word32 buf[4]; - word32 bytes[2]; - word32 in[16]; + word32 buf[4]; + word32 bytes[2]; + word32 in[16]; }; void MD5Init(struct MD5Context *context); From git at git.haskell.org Wed Oct 1 21:37:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 21:37:47 +0000 (UTC) Subject: [commit: ghc] master: [ci skip] Kill unused count_bytes script (53a2d46) Message-ID: <20141001213747.BA89F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/53a2d46d185bcffe005e84b4e7acf6b196f2329e/ghc >--------------------------------------------------------------- commit 53a2d46d185bcffe005e84b4e7acf6b196f2329e Author: Austin Seipp Date: Wed Oct 1 16:36:59 2014 -0500 [ci skip] Kill unused count_bytes script Signed-off-by: Austin Seipp >--------------------------------------------------------------- 53a2d46d185bcffe005e84b4e7acf6b196f2329e compiler/count_bytes | 43 ------------------------------------------- 1 file changed, 43 deletions(-) diff --git a/compiler/count_bytes b/compiler/count_bytes deleted file mode 100644 index 4b8aa37..0000000 --- a/compiler/count_bytes +++ /dev/null @@ -1,43 +0,0 @@ -#!/usr/bin/env perl -# -%DirCount = (); -%ModCount = (); - -foreach $f ( @ARGV ) { - die "Not an .lhs file: $f\n" if $f !~ /\.lhs$/; - $f =~ s/\.lhs$/.o/; - - $f_size = `size $f`; - die "Size failed?\n" if $? != 0; - - if ( $f_size =~ /(\S+)\s*(\S+)\s*(\S+)\s*(\d+)\s*(\S+)/ ) { - $totsz = $4; - - if ( $f =~ /(.*)\/(.*)/ ) { - local($dir) = $1; - local($mod) = $2; - $DirCount{$dir} += $totsz; - $ModCount{$mod} += $totsz; - } else { - print STDERR "not counted in a directory: $f\n"; - $ModCount{$f} += $totsz; - } - } else { - die "Can't figure out size: $f_size\n"; - } -} - -# print the info -$tot = 0; -foreach $d (sort (keys %DirCount)) { - printf "%-20s %6d\n", $d, $DirCount{$d}; - $tot += $DirCount{$d}; -} -printf "\n%-20s %6d\n\n\n", 'TOTAL:', $tot; - -$tot = 0; -foreach $m (sort (keys %ModCount)) { - printf "%-20s %6d\n", $m, $ModCount{$m}; - $tot += $ModCount{$m}; -} -printf "\n%-20s %6d\n", 'TOTAL:', $tot; From git at git.haskell.org Wed Oct 1 21:38:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 21:38:52 +0000 (UTC) Subject: [commit: ghc] master: Use dropWhileEndLE p instead of reverse . dropWhile p . reverse (2a88568) Message-ID: <20141001213852.BFDB53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2a8856884de7d476e26b4ffa829ccb3a14d6f63e/ghc >--------------------------------------------------------------- commit 2a8856884de7d476e26b4ffa829ccb3a14d6f63e Author: David Feuer Date: Wed Oct 1 23:34:29 2014 +0200 Use dropWhileEndLE p instead of reverse . dropWhile p . reverse Summary: Using `dropWhileEndLE` tends to be faster and easier to read than the `reverse . dropWhile p . reverse` idiom. This also cleans up some other, nearby, messes. Fix #9616 (incorrect number formatting potentially leading to incorrect numbers in output). Test Plan: Run validate Reviewers: thomie, rwbarton, nomeata, austin Reviewed By: nomeata, austin Subscribers: simonmar, ezyang, carter, thomie Projects: #ghc Differential Revision: https://phabricator.haskell.org/D259 GHC Trac Issues: #9623, #9616 Conflicts: compiler/basicTypes/OccName.lhs >--------------------------------------------------------------- 2a8856884de7d476e26b4ffa829ccb3a14d6f63e compiler/basicTypes/OccName.lhs | 2 +- compiler/utils/Util.lhs | 16 +++++++++++++++- libraries/base/GHC/Windows.hs | 3 ++- utils/hpc/HpcMarkup.hs | 25 +++++++++++++++++++------ utils/hpc/HpcUtils.hs | 4 ++++ 5 files changed, 41 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/OccName.lhs b/compiler/basicTypes/OccName.lhs index 1f1fda8..0010ad3 100644 --- a/compiler/basicTypes/OccName.lhs +++ b/compiler/basicTypes/OccName.lhs @@ -833,7 +833,7 @@ tidyOccName env occ@(OccName occ_sp fs) Nothing -> (addToUFM env fs 1, occ) where base :: String -- Drop trailing digits (see Note [TidyOccEnv]) - base = reverse (dropWhile isDigit (reverse (unpackFS fs))) + base = dropWhileEndLE isDigit (unpackFS fs) find n = case lookupUFM env new_fs of diff --git a/compiler/utils/Util.lhs b/compiler/utils/Util.lhs index 7292b4a..aa5f6f9 100644 --- a/compiler/utils/Util.lhs +++ b/compiler/utils/Util.lhs @@ -23,6 +23,8 @@ module Util ( mapAndUnzip, mapAndUnzip3, mapAccumL2, nOfThem, filterOut, partitionWith, splitEithers, + dropWhileEndLE, + foldl1', foldl2, count, all2, lengthExceeds, lengthIs, lengthAtLeast, @@ -593,6 +595,18 @@ dropTail n xs go _ _ = [] -- Stop when ys runs out -- It'll always run out before xs does +-- dropWhile from the end of a list. This is similar to Data.List.dropWhileEnd, +-- but is lazy in the elements and strict in the spine. For reasonably short lists, +-- such as path names and typical lines of text, dropWhileEndLE is generally +-- faster than dropWhileEnd. Its advantage is magnified when the predicate is +-- expensive--using dropWhileEndLE isSpace to strip the space off a line of text +-- is generally much faster than using dropWhileEnd isSpace for that purpose. +-- Specification: dropWhileEndLE p = reverse . dropWhile p . reverse +-- Pay attention to the short-circuit (&&)! The order of its arguments is the only +-- difference between dropWhileEnd and dropWhileEndLE. +dropWhileEndLE :: (a -> Bool) -> [a] -> [a] +dropWhileEndLE p = foldr (\x r -> if null r && p x then [] else x:r) [] + snocView :: [a] -> Maybe ([a],a) -- Split off the last element snocView [] = Nothing @@ -651,7 +665,7 @@ cmpList cmp (a:as) (b:bs) \begin{code} removeSpaces :: String -> String -removeSpaces = reverse . dropWhile isSpace . reverse . dropWhile isSpace +removeSpaces = dropWhileEndLE isSpace . dropWhile isSpace \end{code} %************************************************************************ diff --git a/libraries/base/GHC/Windows.hs b/libraries/base/GHC/Windows.hs index 0a57fc3..83f83df 100644 --- a/libraries/base/GHC/Windows.hs +++ b/libraries/base/GHC/Windows.hs @@ -69,6 +69,7 @@ import GHC.Base import GHC.IO import GHC.Num import System.IO.Error +import Util import qualified Numeric @@ -120,7 +121,7 @@ errCodeToIOError fn_name err_code = do -- XXX we should really do this directly. let errno = c_maperrno_func err_code - let msg' = reverse $ dropWhile isSpace $ reverse msg -- drop trailing \n + let msg' = dropWhileEndLE isSpace msg -- drop trailing \n ioerror = errnoToIOError fn_name errno Nothing Nothing `ioeSetErrorString` msg' return ioerror diff --git a/utils/hpc/HpcMarkup.hs b/utils/hpc/HpcMarkup.hs index 8fd9e42..c294b6a 100644 --- a/utils/hpc/HpcMarkup.hs +++ b/utils/hpc/HpcMarkup.hs @@ -140,6 +140,16 @@ charEncodingTag = "" +-- Add characters to the left of a string until it is at least as +-- large as requested. +padLeft :: Int -> Char -> String -> String +padLeft n c str = go n str + where + -- If the string is already long enough, stop traversing it. + go 0 _ = str + go k [] = replicate k c ++ str + go k (_:xs) = go (k-1) xs + genHtmlFromMod :: String -> Flags @@ -210,8 +220,7 @@ genHtmlFromMod dest_dir flags tix theFunTotals invertOutput = do content <- readFileFromPath (hpcError markup_plugin) origFile theHsPath let content' = markup tabStop info content - let show' = reverse . take 5 . (++ " ") . reverse . show - let addLine n xs = "" ++ show' n ++ " " ++ xs + let addLine n xs = "" ++ padLeft 5 ' ' (show n) ++ " " ++ xs let addLines = unlines . map (uncurry addLine) . zip [1 :: Int ..] . lines let fileName = modName0 ++ ".hs.html" putStrLn $ "Writing: " ++ fileName @@ -363,10 +372,14 @@ openTick (TopLevelDecl True 1) openTick (TopLevelDecl True n0) = "-- entered " ++ showBigNum n0 ++ " times" ++ openTopDecl where showBigNum n | n <= 9999 = show n - | otherwise = showBigNum' (n `div` 1000) ++ "," ++ showWith (n `mod` 1000) + | otherwise = case n `quotRem` 1000 of + (q, r) -> showBigNum' q ++ "," ++ showWith r showBigNum' n | n <= 999 = show n - | otherwise = showBigNum' (n `div` 1000) ++ "," ++ showWith (n `mod` 1000) - showWith n = take 3 $ reverse $ ("000" ++) $ reverse $ show n + | otherwise = case n `quotRem` 1000 of + (q, r) -> showBigNum' q ++ "," ++ showWith r + showWith n = padLeft 3 '0' $ show n + + closeTick :: String closeTick = "" @@ -462,7 +475,7 @@ instance Monoid ModuleSummary where writeFileUsing :: String -> String -> IO () writeFileUsing filename text = do - let dest_dir = reverse . dropWhile (\ x -> x /= '/') . reverse $ filename + let dest_dir = dropWhileEndLE (\ x -> x /= '/') $ filename -- We need to check for the dest_dir each time, because we use sub-dirs for -- packages, and a single .tix file might contain information about diff --git a/utils/hpc/HpcUtils.hs b/utils/hpc/HpcUtils.hs index 5655f83..73d9cd3 100644 --- a/utils/hpc/HpcUtils.hs +++ b/utils/hpc/HpcUtils.hs @@ -3,6 +3,10 @@ module HpcUtils where import Trace.Hpc.Util import qualified Data.Map as Map +dropWhileEndLE :: (a -> Bool) -> [a] -> [a] +-- Spec: dropWhileEndLE p = reverse . dropWhileEnd . reverse +dropWhileEndLE p = foldr (\x r -> if null r && p x then [] else x:r) [] + -- turns \n into ' ' -- | grab's the text behind a HpcPos; grabHpcPos :: Map.Map Int String -> HpcPos -> String From git at git.haskell.org Wed Oct 1 21:41:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 1 Oct 2014 21:41:38 +0000 (UTC) Subject: [commit: ghc] master: Basic Python 3 support for testsuite driver (Trac #9184) (084d241) Message-ID: <20141001214138.137713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/084d241b316bfa12e41fc34cae993ca276bf0730/ghc >--------------------------------------------------------------- commit 084d241b316bfa12e41fc34cae993ca276bf0730 Author: Krzysztof Gogolewski Date: Wed Oct 1 23:41:27 2014 +0200 Basic Python 3 support for testsuite driver (Trac #9184) Summary: Most of the changes is adaptation of old Python 2 only code. My priority was not breaking Python 2, and so I avoided bigger changes to the driver. In particular, under Python 3 the output is a str and buffering cannot be disabled. To test, define PYTHON=python3 in testsuite/mk/boilerplate.mk. Thanks to aspidites who provided the initial patch. Test Plan: validate under 2 and 3 Reviewers: hvr, simonmar, thomie, austin Reviewed By: thomie, austin Subscribers: aspidites, thomie, simonmar, ezyang, carter Differential Revision: https://phabricator.haskell.org/D233 GHC Trac Issues: #9184 >--------------------------------------------------------------- 084d241b316bfa12e41fc34cae993ca276bf0730 testsuite/config/ghc | 22 ++-- testsuite/driver/runtests.py | 67 ++++++----- testsuite/driver/testlib.py | 185 ++++++++++++++--------------- testsuite/driver/testutil.py | 34 ------ testsuite/tests/ffi/should_run/all.T | 10 +- testsuite/tests/ghci/prog004/prog004.T | 4 +- testsuite/tests/numeric/should_run/all.T | 8 +- testsuite/tests/perf/compiler/all.T | 2 +- testsuite/tests/plugins/all.T | 4 +- testsuite/tests/th/TH_spliceViewPat/test.T | 6 +- testsuite/tests/th/all.T | 6 +- testsuite/tests/typecheck/should_run/all.T | 4 +- testsuite/timeout/calibrate | 2 +- testsuite/timeout/timeout.py | 2 +- utils/fingerprint/fingerprint.py | 8 +- 15 files changed, 169 insertions(+), 195 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 084d241b316bfa12e41fc34cae993ca276bf0730 From git at git.haskell.org Thu Oct 2 06:10:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 06:10:51 +0000 (UTC) Subject: [commit: ghc] master: Use LinkerInternals.h for exitLinker. (644c76a) Message-ID: <20141002061051.82C033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/644c76a3574a623fa5d2a9a28d8e6fc971aca901/ghc >--------------------------------------------------------------- commit 644c76a3574a623fa5d2a9a28d8e6fc971aca901 Author: Edward Z. Yang Date: Tue Sep 9 12:03:48 2014 -0700 Use LinkerInternals.h for exitLinker. Part of remove HEAP_ALLOCED patch set (#8199) Summary: Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonmar, austin Subscribers: simonmar, ezyang, carter, thomie Differential Revision: https://phabricator.haskell.org/D262 GHC Trac Issues: #8199 >--------------------------------------------------------------- 644c76a3574a623fa5d2a9a28d8e6fc971aca901 rts/RtsStartup.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/RtsStartup.c b/rts/RtsStartup.c index 0d0267a..98a43c0 100644 --- a/rts/RtsStartup.c +++ b/rts/RtsStartup.c @@ -36,7 +36,7 @@ #include "Timer.h" #include "Globals.h" #include "FileLock.h" -void exitLinker( void ); // there is no Linker.h file to include +#include "LinkerInternals.h" #if defined(PROFILING) # include "ProfHeap.h" From git at git.haskell.org Thu Oct 2 06:10:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 06:10:54 +0000 (UTC) Subject: [commit: ghc] master: Place static closures in their own section. (b23ba2a) Message-ID: <20141002061054.34F173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b23ba2a7d612c6b466521399b33fe9aacf5c4f75/ghc >--------------------------------------------------------------- commit b23ba2a7d612c6b466521399b33fe9aacf5c4f75 Author: Edward Z. Yang Date: Mon Aug 26 13:34:15 2013 -0700 Place static closures in their own section. Summary: The primary reason for doing this is assisting debuggability: if static closures are all in the same section, they are guaranteed to be adjacent to one another. This will help later when we add some code that takes section start/end and uses this to sanity-check the sections. Part of remove HEAP_ALLOCED patch set (#8199) Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonmar, austin Subscribers: simonmar, ezyang, carter, thomie Differential Revision: https://phabricator.haskell.org/D263 GHC Trac Issues: #8199 >--------------------------------------------------------------- b23ba2a7d612c6b466521399b33fe9aacf5c4f75 compiler/cmm/Cmm.hs | 1 + compiler/cmm/CmmParse.y | 2 +- compiler/cmm/PprCmmDecl.hs | 1 + compiler/codeGen/StgCmmBind.hs | 4 ++-- compiler/codeGen/StgCmmCon.hs | 2 +- compiler/codeGen/StgCmmUtils.hs | 6 ++++++ compiler/llvmGen/LlvmCodeGen/Data.hs | 1 + compiler/nativeGen/PPC/Ppr.hs | 1 + compiler/nativeGen/SPARC/Ppr.hs | 1 + compiler/nativeGen/X86/Ppr.hs | 4 ++++ 10 files changed, 19 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 b23ba2a7d612c6b466521399b33fe9aacf5c4f75 From git at git.haskell.org Thu Oct 2 06:10:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 06:10:56 +0000 (UTC) Subject: [commit: ghc] master: BC-breaking changes to C-- CLOSURE syntax. (3b5a840) Message-ID: <20141002061056.D7DC13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3b5a840bba375c4c4c11ccfeb283f84c3a1ef22c/ghc >--------------------------------------------------------------- commit 3b5a840bba375c4c4c11ccfeb283f84c3a1ef22c Author: Edward Z. Yang Date: Mon Aug 26 14:52:37 2013 -0700 BC-breaking changes to C-- CLOSURE syntax. Summary: Previously, there were two variants of CLOSURE in C--: - Top-level CLOSURE(foo_closure, foo, lits...), which defines a new static closure and gives it a name, and - Array CLOSURE(foo, lits...), which was used for the static char and integer arrays. They used the same name, were confusing, and didn't even generate the correct internal label representation! So now, we have two new forms: - Top-level CLOSURE(foo, lits...) which automatically generates foo_closure (along with foo_info, which we were doing already) - Array ANONYMOUS_CLOSURE(foo, lits...) which doesn't generate a foo_closure identifier. Part of remove HEAP_ALLOCED patch set (#8199) Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonmar, austin Subscribers: simonmar, ezyang, carter, thomie Differential Revision: https://phabricator.haskell.org/D264 GHC Trac Issues: #8199 >--------------------------------------------------------------- 3b5a840bba375c4c4c11ccfeb283f84c3a1ef22c compiler/cmm/CLabel.hs | 4 ++-- compiler/cmm/CmmLex.x | 2 ++ compiler/cmm/CmmParse.y | 17 +++++++++-------- rts/StgMiscClosures.cmm | 20 ++++++++++---------- 4 files changed, 23 insertions(+), 20 deletions(-) diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs index 0f2c0ae..c5afa09 100644 --- a/compiler/cmm/CLabel.hs +++ b/compiler/cmm/CLabel.hs @@ -333,9 +333,9 @@ data CmmLabelInfo | CmmEntry -- ^ misc rts entry points, suffix _entry | CmmRetInfo -- ^ misc rts ret info tables, suffix _info | CmmRet -- ^ misc rts return points, suffix _ret - | CmmData -- ^ misc rts data bits, eg CHARLIKE_closure + | CmmData -- ^ misc rts data bits | CmmCode -- ^ misc rts code - | CmmClosure -- ^ closures eg CHARLIKE_closure + | CmmClosure -- ^ misc rts closures, suffix _closure | CmmPrimCall -- ^ a prim call to some hand written Cmm code deriving (Eq, Ord) diff --git a/compiler/cmm/CmmLex.x b/compiler/cmm/CmmLex.x index f56db7b..dfbb751 100644 --- a/compiler/cmm/CmmLex.x +++ b/compiler/cmm/CmmLex.x @@ -135,6 +135,7 @@ data CmmToken | CmmT_Ne | CmmT_BoolAnd | CmmT_BoolOr + | CmmT_ANONYMOUS_CLOSURE | CmmT_CLOSURE | CmmT_INFO_TABLE | CmmT_INFO_TABLE_RET @@ -218,6 +219,7 @@ name span buf len = reservedWordsFM = listToUFM $ map (\(x, y) -> (mkFastString x, y)) [ + ( "ANONYMOUS_CLOSURE", CmmT_ANONYMOUS_CLOSURE ), ( "CLOSURE", CmmT_CLOSURE ), ( "INFO_TABLE", CmmT_INFO_TABLE ), ( "INFO_TABLE_RET", CmmT_INFO_TABLE_RET ), diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index db6cc49..3bd0053 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -300,6 +300,7 @@ import Data.Maybe '||' { L _ (CmmT_BoolOr) } 'CLOSURE' { L _ (CmmT_CLOSURE) } + 'ANONYMOUS_CLOSURE'{ L _ (CmmT_ANONYMOUS_CLOSURE) } 'INFO_TABLE' { L _ (CmmT_INFO_TABLE) } 'INFO_TABLE_RET'{ L _ (CmmT_INFO_TABLE_RET) } 'INFO_TABLE_FUN'{ L _ (CmmT_INFO_TABLE_FUN) } @@ -369,10 +370,10 @@ cmmtop :: { CmmParse () } : cmmproc { $1 } | cmmdata { $1 } | decl { $1 } - | 'CLOSURE' '(' NAME ',' NAME lits ')' ';' + | 'CLOSURE' '(' NAME lits ')' ';' {% withThisPackage $ \pkg -> - do lits <- sequence $6; - staticClosure pkg $3 $5 (map getLit lits) } + do lits <- sequence $4; + staticClosure pkg $3 (map getLit lits) } -- The only static closures in the RTS are dummy closures like -- stg_END_TSO_QUEUE_closure and stg_dummy_ret. We don't need @@ -411,7 +412,7 @@ static :: { CmmParse [CmmStatic] } | typenot8 '[' INT ']' ';' { return [CmmUninitialised (widthInBytes (typeWidth $1) * fromIntegral $3)] } - | 'CLOSURE' '(' NAME lits ')' + | 'ANONYMOUS_CLOSURE' '(' NAME lits ')' { do { lits <- sequence $4 ; dflags <- getDynFlags ; return $ map CmmStaticLit $ @@ -1101,11 +1102,11 @@ profilingInfo dflags desc_str ty_str else ProfilingInfo (stringToWord8s desc_str) (stringToWord8s ty_str) -staticClosure :: PackageKey -> FastString -> FastString -> [CmmLit] -> CmmParse () -staticClosure pkg cl_label info payload +staticClosure :: PackageKey -> FastString -> [CmmLit] -> CmmParse () +staticClosure pkg label payload = do dflags <- getDynFlags - let lits = mkStaticClosure dflags (mkCmmInfoLabel pkg info) dontCareCCS payload [] [] [] - code $ emitStaticClosure (mkCmmDataLabel pkg cl_label) lits + let lits = mkStaticClosure dflags (mkCmmInfoLabel pkg label) dontCareCCS payload [] [] [] + code $ emitStaticClosure (mkCmmClosureLabel pkg label) lits foreignCall :: String diff --git a/rts/StgMiscClosures.cmm b/rts/StgMiscClosures.cmm index 42ef39e..85ecb5e 100644 --- a/rts/StgMiscClosures.cmm +++ b/rts/StgMiscClosures.cmm @@ -457,7 +457,7 @@ INFO_TABLE_CONSTR(stg_C_FINALIZER_LIST,1,4,0,CONSTR,"C_FINALIZER_LIST","C_FINALI INFO_TABLE_CONSTR(stg_NO_FINALIZER,0,0,0,CONSTR_NOCAF_STATIC,"NO_FINALIZER","NO_FINALIZER") { foreign "C" barf("NO_FINALIZER object entered!") never returns; } -CLOSURE(stg_NO_FINALIZER_closure,stg_NO_FINALIZER); +CLOSURE(stg_NO_FINALIZER); /* ---------------------------------------------------------------------------- Stable Names are unlifted too. @@ -516,13 +516,13 @@ INFO_TABLE_CONSTR(stg_END_STM_CHUNK_LIST,0,0,0,CONSTR_NOCAF_STATIC,"END_STM_CHUN INFO_TABLE_CONSTR(stg_NO_TREC,0,0,0,CONSTR_NOCAF_STATIC,"NO_TREC","NO_TREC") { foreign "C" barf("NO_TREC object entered!") never returns; } -CLOSURE(stg_END_STM_WATCH_QUEUE_closure,stg_END_STM_WATCH_QUEUE); +CLOSURE(stg_END_STM_WATCH_QUEUE); -CLOSURE(stg_END_INVARIANT_CHECK_QUEUE_closure,stg_END_INVARIANT_CHECK_QUEUE); +CLOSURE(stg_END_INVARIANT_CHECK_QUEUE); -CLOSURE(stg_END_STM_CHUNK_LIST_closure,stg_END_STM_CHUNK_LIST); +CLOSURE(stg_END_STM_CHUNK_LIST); -CLOSURE(stg_NO_TREC_closure,stg_NO_TREC); +CLOSURE(stg_NO_TREC); /* ---------------------------------------------------------------------------- Messages @@ -553,7 +553,7 @@ INFO_TABLE_CONSTR(stg_MSG_NULL,1,0,0,PRIM,"MSG_NULL","MSG_NULL") INFO_TABLE_CONSTR(stg_END_TSO_QUEUE,0,0,0,CONSTR_NOCAF_STATIC,"END_TSO_QUEUE","END_TSO_QUEUE") { foreign "C" barf("END_TSO_QUEUE object entered!") never returns; } -CLOSURE(stg_END_TSO_QUEUE_closure,stg_END_TSO_QUEUE); +CLOSURE(stg_END_TSO_QUEUE); /* ---------------------------------------------------------------------------- GCD_CAF @@ -572,7 +572,7 @@ INFO_TABLE_CONSTR(stg_GCD_CAF,0,0,0,CONSTR_NOCAF_STATIC,"GCD_CAF","GCD_CAF") INFO_TABLE_CONSTR(stg_STM_AWOKEN,0,0,0,CONSTR_NOCAF_STATIC,"STM_AWOKEN","STM_AWOKEN") { foreign "C" barf("STM_AWOKEN object entered!") never returns; } -CLOSURE(stg_STM_AWOKEN_closure,stg_STM_AWOKEN); +CLOSURE(stg_STM_AWOKEN); /* ---------------------------------------------------------------------------- Arrays @@ -638,7 +638,7 @@ INFO_TABLE( stg_dummy_ret, 0, 0, CONSTR_NOCAF_STATIC, "DUMMY_RET", "DUMMY_RET") { return (); } -CLOSURE(stg_dummy_ret_closure,stg_dummy_ret); +CLOSURE(stg_dummy_ret); /* ---------------------------------------------------------------------------- MVAR_TSO_QUEUE @@ -673,8 +673,8 @@ INFO_TABLE_CONSTR(stg_MVAR_TSO_QUEUE,2,0,0,PRIM,"MVAR_TSO_QUEUE","MVAR_TSO_QUEUE #endif -#define CHARLIKE_HDR(n) CLOSURE(Char_hash_static_info, n) -#define INTLIKE_HDR(n) CLOSURE(Int_hash_static_info, n) +#define CHARLIKE_HDR(n) ANONYMOUS_CLOSURE(Char_hash_static_info, n) +#define INTLIKE_HDR(n) ANONYMOUS_CLOSURE(Int_hash_static_info, n) /* put these in the *data* section, since the garbage collector relies * on the fact that static closures live in the data section. From git at git.haskell.org Thu Oct 2 06:10:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 06:10:59 +0000 (UTC) Subject: [commit: ghc] master: Properly generate info tables for static closures in C--. (178eb90) Message-ID: <20141002061059.8B45E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/178eb9060f369b216f3f401196e28eab4af5624d/ghc >--------------------------------------------------------------- commit 178eb9060f369b216f3f401196e28eab4af5624d Author: Edward Z. Yang Date: Wed Aug 28 22:07:07 2013 -0700 Properly generate info tables for static closures in C--. Summary: Previously, we assumed all objects declared in C-- were not-static, even ones which were CONSTR_NOCAF_STATIC. This used to be harmless, but now we need this information to be correct. Part of remove HEAP_ALLOCED patch set (#8199) Depends on D264 Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonmar, austin Subscribers: simonmar, ezyang, carter, thomie Differential Revision: https://phabricator.haskell.org/D265 GHC Trac Issues: #8199 >--------------------------------------------------------------- 178eb9060f369b216f3f401196e28eab4af5624d compiler/cmm/CmmParse.y | 3 ++- compiler/cmm/SMRep.lhs | 5 +++-- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 3bd0053..31b1198 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -496,7 +496,8 @@ info :: { CmmParse (CLabel, Maybe CmmInfoTable, [LocalReg]) } ty = Constr (fromIntegral $9) -- Tag (stringToWord8s $13) rep = mkRTSRep (fromIntegral $11) $ - mkHeapRep dflags False (fromIntegral $5) + mkHeapRep dflags (fromIntegral $11 == cONSTR_NOCAF_STATIC) + (fromIntegral $5) (fromIntegral $7) ty return (mkCmmEntryLabel pkg $3, Just $ CmmInfoTable { cit_lbl = mkCmmInfoLabel pkg $3 diff --git a/compiler/cmm/SMRep.lhs b/compiler/cmm/SMRep.lhs index 53c9d0a..1d0b9b0 100644 --- a/compiler/cmm/SMRep.lhs +++ b/compiler/cmm/SMRep.lhs @@ -41,7 +41,7 @@ module SMRep ( -- ** RTS closure types rtsClosureType, rET_SMALL, rET_BIG, - aRG_GEN, aRG_GEN_BIG, + aRG_GEN, aRG_GEN_BIG, cONSTR_NOCAF_STATIC, -- ** Arrays card, cardRoundUp, cardTableSizeB, cardTableSizeW, @@ -473,11 +473,12 @@ rtsClosureType rep _ -> panic "rtsClosureType" -- We export these ones -rET_SMALL, rET_BIG, aRG_GEN, aRG_GEN_BIG :: Int +rET_SMALL, rET_BIG, aRG_GEN, aRG_GEN_BIG, cONSTR_NOCAF_STATIC :: Int rET_SMALL = RET_SMALL rET_BIG = RET_BIG aRG_GEN = ARG_GEN aRG_GEN_BIG = ARG_GEN_BIG +cONSTR_NOCAF_STATIC = CONSTR_NOCAF_STATIC \end{code} Note [Static NoCaf constructors] From git at git.haskell.org Thu Oct 2 06:11:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 06:11:02 +0000 (UTC) Subject: [commit: ghc] master: Rename _closure to _static_closure, apply naming consistently. (3567207) Message-ID: <20141002061102.AEE393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/35672072b4091d6f0031417bc160c568f22d0469/ghc >--------------------------------------------------------------- commit 35672072b4091d6f0031417bc160c568f22d0469 Author: Edward Z. Yang Date: Mon Aug 26 15:23:15 2013 -0700 Rename _closure to _static_closure, apply naming consistently. Summary: In preparation for indirecting all references to closures, we rename _closure to _static_closure to ensure any old code will get an undefined symbol error. In order to reference a closure foobar_closure (which is now undefined), you should instead use STATIC_CLOSURE(foobar). For convenience, a number of these old identifiers are macro'd. Across C-- and C (Windows and otherwise), there were differing conventions on whether or not foobar_closure or &foobar_closure was the address of the closure. Now, all foobar_closure references are addresses, and no & is necessary. CHARLIKE/INTLIKE were not changed, simply alpha-renamed. Part of remove HEAP_ALLOCED patch set (#8199) Depends on D265 Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonmar, austin Subscribers: simonmar, ezyang, carter, thomie Differential Revision: https://phabricator.haskell.org/D267 GHC Trac Issues: #8199 >--------------------------------------------------------------- 35672072b4091d6f0031417bc160c568f22d0469 compiler/cmm/CLabel.hs | 4 +- compiler/deSugar/DsForeign.lhs | 6 +- compiler/ghci/ByteCodeLink.lhs | 4 +- compiler/main/DriverPipeline.hs | 4 +- driver/utils/dynwrapper.c | 2 +- ghc/GhciMonad.hs | 6 +- includes/Cmm.h | 1 + includes/Rts.h | 1 + includes/RtsAPI.h | 12 ++-- includes/rts/StaticClosures.h | 34 +++++++++++ includes/rts/storage/ClosureMacros.h | 5 +- includes/rts/storage/TSO.h | 2 +- includes/stg/MiscClosures.h | 30 +++++----- libraries/integer-gmp/cbits/gmp-wrappers.cmm | 4 +- rts/Exception.cmm | 6 +- rts/Interpreter.c | 2 +- rts/Linker.c | 4 +- rts/Prelude.h | 86 +++++++++++++++------------- rts/PrimOps.cmm | 8 +-- rts/RaiseAsync.c | 4 +- rts/RetainerProfile.c | 2 +- rts/STM.c | 4 +- rts/STM.h | 8 +-- rts/StgMiscClosures.cmm | 4 +- rts/Weak.c | 6 +- rts/package.conf.in | 72 +++++++++++------------ rts/posix/Signals.c | 4 +- rts/sm/Storage.c | 4 +- rts/win32/libHSbase.def | 34 +++++------ testsuite/tests/rts/rdynamic.hs | 2 +- 30 files changed, 203 insertions(+), 162 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 35672072b4091d6f0031417bc160c568f22d0469 From git at git.haskell.org Thu Oct 2 07:02:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 07:02:38 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: More progress (1ddb047) Message-ID: <20141002070238.ED6A43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/1ddb047d743595f01a5aa2630fc23f8cc4e348ce/ghc >--------------------------------------------------------------- commit 1ddb047d743595f01a5aa2630fc23f8cc4e348ce Author: Simon Peyton Jones Date: Thu Oct 2 08:02:19 2014 +0100 More progress >--------------------------------------------------------------- 1ddb047d743595f01a5aa2630fc23f8cc4e348ce compiler/basicTypes/SrcLoc.lhs | 80 ++++++++++++---------- compiler/deSugar/DsBinds.lhs | 20 ++++++ compiler/ghci/Debugger.hs | 1 + compiler/main/DynFlags.hs | 12 ---- compiler/main/ErrUtils.lhs | 26 ++++--- compiler/simplCore/SimplMonad.lhs | 1 + compiler/typecheck/TcDeriv.lhs | 6 +- compiler/typecheck/TcErrors.lhs | 15 ++-- compiler/typecheck/TcInstDcls.lhs | 25 ++++--- compiler/typecheck/TcRnMonad.lhs | 26 +++---- compiler/utils/Outputable.lhs | 51 +++++++------- .../indexed-types/should_compile/T3208b.stderr | 7 +- .../tests/indexed-types/should_fail/T2627b.hs | 10 ++- testsuite/tests/roles/should_compile/T8958.stderr | 15 ++-- .../simplCore/should_compile/T8832.stdout-ws-32 | 16 ++--- testsuite/tests/th/T3319.stderr | 0 testsuite/tests/th/T3600.stderr | 0 testsuite/tests/th/T5217.stderr | 18 ++--- testsuite/tests/th/T5290.stderr | 6 +- testsuite/tests/th/T5508.stderr | 8 +-- testsuite/tests/th/TH_PromotedTuple.stderr | 6 +- .../tests/typecheck/should_compile/tc231.stderr | 2 +- testsuite/tests/typecheck/should_fail/T8142.stderr | 2 +- 23 files changed, 190 insertions(+), 163 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 1ddb047d743595f01a5aa2630fc23f8cc4e348ce From git at git.haskell.org Thu Oct 2 16:04:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 16:04:56 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: MOre progress (a5fb4ba) Message-ID: <20141002160456.49FA73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/a5fb4ba4fc38d1b76549e49d3fcbf6b4e44ae0d2/ghc >--------------------------------------------------------------- commit a5fb4ba4fc38d1b76549e49d3fcbf6b4e44ae0d2 Author: Simon Peyton Jones Date: Thu Oct 2 16:37:58 2014 +0100 MOre progress >--------------------------------------------------------------- a5fb4ba4fc38d1b76549e49d3fcbf6b4e44ae0d2 compiler/basicTypes/SrcLoc.lhs | 29 ++-- compiler/ghci/RtClosureInspect.hs | 10 +- compiler/typecheck/FamInst.lhs | 13 +- compiler/typecheck/Inst.lhs | 6 +- compiler/typecheck/TcCanonical.lhs | 152 ++++++++++++--------- compiler/typecheck/TcDeriv.lhs | 4 +- compiler/typecheck/TcExpr.lhs | 18 +-- compiler/typecheck/TcGenDeriv.lhs | 2 +- compiler/typecheck/TcGenGenerics.lhs | 1 + compiler/typecheck/TcInteract.lhs | 65 ++++++++- compiler/typecheck/TcMType.lhs | 106 +++++++------- compiler/typecheck/TcPat.lhs | 17 +-- compiler/typecheck/TcRnTypes.lhs | 69 ++++------ compiler/typecheck/TcSMonad.lhs | 79 +++++++---- compiler/typecheck/TcSimplify.lhs | 4 +- testsuite/tests/gadt/T3169.stderr | 4 +- .../indexed-types/should_compile/T3208b.stderr | 6 +- .../indexed-types/should_fail/GADTwrong1.stderr | 7 +- .../indexed-types/should_fail/NoMatchErr.stderr | 5 +- .../indexed-types/should_fail/Overlap9.stderr | 5 +- .../tests/indexed-types/should_fail/T1897b.stderr | 6 +- .../tests/indexed-types/should_fail/T1900.stderr | 5 +- .../tests/indexed-types/should_fail/T2544.stderr | 6 +- .../tests/indexed-types/should_fail/T2664.stderr | 10 +- .../tests/indexed-types/should_fail/T4179.stderr | 9 +- .../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 | 5 +- .../tests/indexed-types/should_fail/T8518.stderr | 13 +- .../tests/indexed-types/should_fail/T9036.stderr | 4 +- testsuite/tests/th/T5290.stderr | 6 +- testsuite/tests/th/T5508.stderr | 8 +- testsuite/tests/th/TH_PromotedTuple.stderr | 6 +- 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_fail/T1899.stderr | 10 +- testsuite/tests/typecheck/should_fail/T2688.stderr | 5 +- testsuite/tests/typecheck/should_fail/T7453.stderr | 14 +- testsuite/tests/typecheck/should_fail/T8142.stderr | 6 +- .../tests/typecheck/should_fail/tcfail068.stderr | 33 +---- .../tests/typecheck/should_fail/tcfail131.stderr | 5 +- 45 files changed, 403 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 a5fb4ba4fc38d1b76549e49d3fcbf6b4e44ae0d2 From git at git.haskell.org Thu Oct 2 16:04:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 16:04:59 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 (d709d73) Message-ID: <20141002160459.EDF633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/d709d7317d39fc42c51dd9761fc0866dfcd25aa6/ghc >--------------------------------------------------------------- commit d709d7317d39fc42c51dd9761fc0866dfcd25aa6 Merge: a5fb4ba 3567207 Author: Simon Peyton Jones Date: Thu Oct 2 16:40:13 2014 +0100 Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 Conflicts: compiler/typecheck/TcInteract.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 d709d7317d39fc42c51dd9761fc0866dfcd25aa6 From git at git.haskell.org Thu Oct 2 16:05:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 16:05:02 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14's head updated: Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 (d709d73) Message-ID: <20141002160502.44E433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/new-flatten-skolems-Aug14' now includes: 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. a5fb4ba MOre progress d709d73 Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 From git at git.haskell.org Thu Oct 2 16:51:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 16:51:11 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Esablish the flattening invariant for CTyEqCan (e94d2ab) Message-ID: <20141002165111.A3A1D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/e94d2ab2b23a494bb47ac25b2a1fbeb46739f3c4/ghc >--------------------------------------------------------------- commit e94d2ab2b23a494bb47ac25b2a1fbeb46739f3c4 Author: Simon Peyton Jones Date: Thu Oct 2 17:50:48 2014 +0100 Esablish the flattening invariant for CTyEqCan >--------------------------------------------------------------- e94d2ab2b23a494bb47ac25b2a1fbeb46739f3c4 compiler/typecheck/TcCanonical.lhs | 37 +++++++++++++++++++++++-------------- 1 file changed, 23 insertions(+), 14 deletions(-) diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index fd07c5c..79f1eb1 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -458,10 +458,16 @@ data FlattenEnv = FE { fe_mode :: FlattenMode , fe_ev :: CtEvidence } -data FlattenMode - = FM_FlattenAll -- Flatten all type functions - | FM_Avoid TcTyVar -- Flatten type functions to avoid this type variable - | FM_SubstOnly -- See Note [Flattening under a forall] +data FlattenMode -- Postcondition for all three: inert wrt the type substitution + = FM_FlattenAll -- Postcondition: function-free + + | FM_Avoid TcTyVar Bool -- Postcondition: + -- * tyvar is only mentioned in result under a rigid path + -- e.g. [a] is ok, but F a won't happen + -- * If flat_top is True, top level is not a function application + -- (but under type constructors is ok e.g. [F a]) + + | FM_SubstOnly -- See Note [Flattening under a forall] -- Flatten a bunch of types all at once. flattenMany :: FlattenEnv -> [Type] -> TcS ([Xi], [TcCoercion]) @@ -522,11 +528,13 @@ flatten fmode (TyConApp tc tys) -- For * a normal data type application -- * data family application - -- * type synonym application whose RHS does not mention type families - -- See Note [Flattening synonyms] -- we just recursively flatten the arguments. - | otherwise - = flattenTyConApp fmode tc tys + | otherwise -- Switch off the flat_top bit in FM_Avoid + , let fmode' = case fmode of + FE { fe_mode = FM_Avoid tv _ } + -> fmode { fe_mode = FM_Avoid tv False } + _ -> fmode + = flattenTyConApp fmode' tc tys flatten fmode ty@(ForAllTy {}) -- We allow for-alls when, but only when, no type function @@ -605,11 +613,11 @@ flattenExactFamApp fmode tc tys ; return ( mkTyConApp tc xis , mkTcTyConAppCo Nominal tc cos ) } - FM_Avoid tv -> do { (xis, cos) <- flattenMany fmode tys - ; if tv `elemVarSet` tyVarsOfTypes xis - then flattenExactFamApp_fully fmode tc tys - else return ( mkTyConApp tc xis - , mkTcTyConAppCo Nominal tc cos ) } + FM_Avoid tv flat_top -> do { (xis, cos) <- flattenMany fmode tys + ; if flat_top || tv `elemVarSet` tyVarsOfTypes xis + then flattenExactFamApp_fully fmode tc tys + else return ( mkTyConApp tc xis + , mkTcTyConAppCo Nominal tc cos ) } FM_FlattenAll -> flattenExactFamApp_fully fmode tc tys flattenExactFamApp_fully fmode tc tys @@ -1157,7 +1165,8 @@ canEqTyVar ev swapped tv1 ty2 ps_ty2 -- ev :: tv ~ s2 Nothing -> return Stop Just new_ev -> can_eq_nc new_ev ty1 ty1 ty2 ps_ty2 } - Left tv1' -> do { let fmode = FE { fe_ev = ev, fe_mode = FM_Avoid tv1' } + Left tv1' -> do { let fmode = FE { fe_ev = ev, fe_mode = FM_Avoid tv1' True } + -- Flatten the RHS less vigorously, to avoid gratuitous ; (xi2, co2) <- flatten fmode ps_ty2 -- co2 :: xi2 ~ ps_ty2 -- Use ps_ty2 to preserve type synonyms if poss ; dflags <- getDynFlags From git at git.haskell.org Thu Oct 2 18:45:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 18:45:14 +0000 (UTC) Subject: [commit: ghc] branch 'wip/GenericsMetaData' created Message-ID: <20141002184514.D6AD43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/GenericsMetaData Referencing: 2d86279d666196b925a67d49848c519abf82c05d From git at git.haskell.org Thu Oct 2 18:45:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 18:45:17 +0000 (UTC) Subject: [commit: ghc] wip/GenericsMetaData: Start working on improving the metadata of GHC.Generics (2d86279) Message-ID: <20141002184517.889F63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/GenericsMetaData Link : http://ghc.haskell.org/trac/ghc/changeset/2d86279d666196b925a67d49848c519abf82c05d/ghc >--------------------------------------------------------------- commit 2d86279d666196b925a67d49848c519abf82c05d Author: Jose Pedro Magalhaes Date: Thu Oct 2 08:38:05 2014 +0100 Start working on improving the metadata of GHC.Generics >--------------------------------------------------------------- 2d86279d666196b925a67d49848c519abf82c05d compiler/prelude/PrelNames.lhs | 70 ++++++++++--- compiler/typecheck/TcGenGenerics.lhs | 88 +++++++++++++--- libraries/base/GHC/Generics.hs | 192 ++++++++++++++++++++++++++++------- 3 files changed, 283 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 2d86279d666196b925a67d49848c519abf82c05d From git at git.haskell.org Thu Oct 2 19:51:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 19:51:47 +0000 (UTC) Subject: [commit: ghc] master: Revert "Use dropWhileEndLE p instead of reverse . dropWhile p . reverse" (d6d5c12) Message-ID: <20141002195147.CAC1D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d6d5c127b86dc186b25add2843cb83fc12e72a85/ghc >--------------------------------------------------------------- commit d6d5c127b86dc186b25add2843cb83fc12e72a85 Author: Austin Seipp Date: Thu Oct 2 14:51:34 2014 -0500 Revert "Use dropWhileEndLE p instead of reverse . dropWhile p . reverse" This reverts commit 2a8856884de7d476e26b4ffa829ccb3a14d6f63e. >--------------------------------------------------------------- d6d5c127b86dc186b25add2843cb83fc12e72a85 compiler/basicTypes/OccName.lhs | 2 +- compiler/utils/Util.lhs | 16 +--------------- libraries/base/GHC/Windows.hs | 3 +-- utils/hpc/HpcMarkup.hs | 25 ++++++------------------- utils/hpc/HpcUtils.hs | 4 ---- 5 files changed, 9 insertions(+), 41 deletions(-) diff --git a/compiler/basicTypes/OccName.lhs b/compiler/basicTypes/OccName.lhs index 0010ad3..1f1fda8 100644 --- a/compiler/basicTypes/OccName.lhs +++ b/compiler/basicTypes/OccName.lhs @@ -833,7 +833,7 @@ tidyOccName env occ@(OccName occ_sp fs) Nothing -> (addToUFM env fs 1, occ) where base :: String -- Drop trailing digits (see Note [TidyOccEnv]) - base = dropWhileEndLE isDigit (unpackFS fs) + base = reverse (dropWhile isDigit (reverse (unpackFS fs))) find n = case lookupUFM env new_fs of diff --git a/compiler/utils/Util.lhs b/compiler/utils/Util.lhs index aa5f6f9..7292b4a 100644 --- a/compiler/utils/Util.lhs +++ b/compiler/utils/Util.lhs @@ -23,8 +23,6 @@ module Util ( mapAndUnzip, mapAndUnzip3, mapAccumL2, nOfThem, filterOut, partitionWith, splitEithers, - dropWhileEndLE, - foldl1', foldl2, count, all2, lengthExceeds, lengthIs, lengthAtLeast, @@ -595,18 +593,6 @@ dropTail n xs go _ _ = [] -- Stop when ys runs out -- It'll always run out before xs does --- dropWhile from the end of a list. This is similar to Data.List.dropWhileEnd, --- but is lazy in the elements and strict in the spine. For reasonably short lists, --- such as path names and typical lines of text, dropWhileEndLE is generally --- faster than dropWhileEnd. Its advantage is magnified when the predicate is --- expensive--using dropWhileEndLE isSpace to strip the space off a line of text --- is generally much faster than using dropWhileEnd isSpace for that purpose. --- Specification: dropWhileEndLE p = reverse . dropWhile p . reverse --- Pay attention to the short-circuit (&&)! The order of its arguments is the only --- difference between dropWhileEnd and dropWhileEndLE. -dropWhileEndLE :: (a -> Bool) -> [a] -> [a] -dropWhileEndLE p = foldr (\x r -> if null r && p x then [] else x:r) [] - snocView :: [a] -> Maybe ([a],a) -- Split off the last element snocView [] = Nothing @@ -665,7 +651,7 @@ cmpList cmp (a:as) (b:bs) \begin{code} removeSpaces :: String -> String -removeSpaces = dropWhileEndLE isSpace . dropWhile isSpace +removeSpaces = reverse . dropWhile isSpace . reverse . dropWhile isSpace \end{code} %************************************************************************ diff --git a/libraries/base/GHC/Windows.hs b/libraries/base/GHC/Windows.hs index 83f83df..0a57fc3 100644 --- a/libraries/base/GHC/Windows.hs +++ b/libraries/base/GHC/Windows.hs @@ -69,7 +69,6 @@ import GHC.Base import GHC.IO import GHC.Num import System.IO.Error -import Util import qualified Numeric @@ -121,7 +120,7 @@ errCodeToIOError fn_name err_code = do -- XXX we should really do this directly. let errno = c_maperrno_func err_code - let msg' = dropWhileEndLE isSpace msg -- drop trailing \n + let msg' = reverse $ dropWhile isSpace $ reverse msg -- drop trailing \n ioerror = errnoToIOError fn_name errno Nothing Nothing `ioeSetErrorString` msg' return ioerror diff --git a/utils/hpc/HpcMarkup.hs b/utils/hpc/HpcMarkup.hs index c294b6a..8fd9e42 100644 --- a/utils/hpc/HpcMarkup.hs +++ b/utils/hpc/HpcMarkup.hs @@ -140,16 +140,6 @@ charEncodingTag = "" --- Add characters to the left of a string until it is at least as --- large as requested. -padLeft :: Int -> Char -> String -> String -padLeft n c str = go n str - where - -- If the string is already long enough, stop traversing it. - go 0 _ = str - go k [] = replicate k c ++ str - go k (_:xs) = go (k-1) xs - genHtmlFromMod :: String -> Flags @@ -220,7 +210,8 @@ genHtmlFromMod dest_dir flags tix theFunTotals invertOutput = do content <- readFileFromPath (hpcError markup_plugin) origFile theHsPath let content' = markup tabStop info content - let addLine n xs = "" ++ padLeft 5 ' ' (show n) ++ " " ++ xs + let show' = reverse . take 5 . (++ " ") . reverse . show + let addLine n xs = "" ++ show' n ++ " " ++ xs let addLines = unlines . map (uncurry addLine) . zip [1 :: Int ..] . lines let fileName = modName0 ++ ".hs.html" putStrLn $ "Writing: " ++ fileName @@ -372,14 +363,10 @@ openTick (TopLevelDecl True 1) openTick (TopLevelDecl True n0) = "-- entered " ++ showBigNum n0 ++ " times" ++ openTopDecl where showBigNum n | n <= 9999 = show n - | otherwise = case n `quotRem` 1000 of - (q, r) -> showBigNum' q ++ "," ++ showWith r + | otherwise = showBigNum' (n `div` 1000) ++ "," ++ showWith (n `mod` 1000) showBigNum' n | n <= 999 = show n - | otherwise = case n `quotRem` 1000 of - (q, r) -> showBigNum' q ++ "," ++ showWith r - showWith n = padLeft 3 '0' $ show n - - + | otherwise = showBigNum' (n `div` 1000) ++ "," ++ showWith (n `mod` 1000) + showWith n = take 3 $ reverse $ ("000" ++) $ reverse $ show n closeTick :: String closeTick = "" @@ -475,7 +462,7 @@ instance Monoid ModuleSummary where writeFileUsing :: String -> String -> IO () writeFileUsing filename text = do - let dest_dir = dropWhileEndLE (\ x -> x /= '/') $ filename + let dest_dir = reverse . dropWhile (\ x -> x /= '/') . reverse $ filename -- We need to check for the dest_dir each time, because we use sub-dirs for -- packages, and a single .tix file might contain information about diff --git a/utils/hpc/HpcUtils.hs b/utils/hpc/HpcUtils.hs index 73d9cd3..5655f83 100644 --- a/utils/hpc/HpcUtils.hs +++ b/utils/hpc/HpcUtils.hs @@ -3,10 +3,6 @@ module HpcUtils where import Trace.Hpc.Util import qualified Data.Map as Map -dropWhileEndLE :: (a -> Bool) -> [a] -> [a] --- Spec: dropWhileEndLE p = reverse . dropWhileEnd . reverse -dropWhileEndLE p = foldr (\x r -> if null r && p x then [] else x:r) [] - -- turns \n into ' ' -- | grab's the text behind a HpcPos; grabHpcPos :: Map.Map Int String -> HpcPos -> String From git at git.haskell.org Thu Oct 2 20:14:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 20:14:23 +0000 (UTC) Subject: [commit: ghc] master: Use dropWhileEndLE p instead of reverse . dropWhile p . reverse (9bf5228) Message-ID: <20141002201423.836D23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9bf5228fdc1937f44901a945553eea3cb0f14faa/ghc >--------------------------------------------------------------- commit 9bf5228fdc1937f44901a945553eea3cb0f14faa Author: David Feuer Date: Wed Oct 1 23:34:29 2014 +0200 Use dropWhileEndLE p instead of reverse . dropWhile p . reverse Summary: Using `dropWhileEndLE` tends to be faster and easier to read than the `reverse . dropWhile p . reverse` idiom. This also cleans up some other, nearby, messes. Fix #9616 (incorrect number formatting potentially leading to incorrect numbers in output). Test Plan: Run validate Reviewers: thomie, rwbarton, nomeata, austin Reviewed By: nomeata, austin Subscribers: simonmar, ezyang, carter, thomie Projects: #ghc Differential Revision: https://phabricator.haskell.org/D259 GHC Trac Issues: #9623, #9616 Conflicts: compiler/basicTypes/OccName.lhs >--------------------------------------------------------------- 9bf5228fdc1937f44901a945553eea3cb0f14faa compiler/basicTypes/OccName.lhs | 2 +- compiler/utils/Util.lhs | 16 +++++++++++++++- libraries/base/GHC/Windows.hs | 3 ++- utils/hpc/HpcMarkup.hs | 25 +++++++++++++++++++------ utils/hpc/HpcUtils.hs | 4 ++++ 5 files changed, 41 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/OccName.lhs b/compiler/basicTypes/OccName.lhs index 1f1fda8..0010ad3 100644 --- a/compiler/basicTypes/OccName.lhs +++ b/compiler/basicTypes/OccName.lhs @@ -833,7 +833,7 @@ tidyOccName env occ@(OccName occ_sp fs) Nothing -> (addToUFM env fs 1, occ) where base :: String -- Drop trailing digits (see Note [TidyOccEnv]) - base = reverse (dropWhile isDigit (reverse (unpackFS fs))) + base = dropWhileEndLE isDigit (unpackFS fs) find n = case lookupUFM env new_fs of diff --git a/compiler/utils/Util.lhs b/compiler/utils/Util.lhs index 7292b4a..aa5f6f9 100644 --- a/compiler/utils/Util.lhs +++ b/compiler/utils/Util.lhs @@ -23,6 +23,8 @@ module Util ( mapAndUnzip, mapAndUnzip3, mapAccumL2, nOfThem, filterOut, partitionWith, splitEithers, + dropWhileEndLE, + foldl1', foldl2, count, all2, lengthExceeds, lengthIs, lengthAtLeast, @@ -593,6 +595,18 @@ dropTail n xs go _ _ = [] -- Stop when ys runs out -- It'll always run out before xs does +-- dropWhile from the end of a list. This is similar to Data.List.dropWhileEnd, +-- but is lazy in the elements and strict in the spine. For reasonably short lists, +-- such as path names and typical lines of text, dropWhileEndLE is generally +-- faster than dropWhileEnd. Its advantage is magnified when the predicate is +-- expensive--using dropWhileEndLE isSpace to strip the space off a line of text +-- is generally much faster than using dropWhileEnd isSpace for that purpose. +-- Specification: dropWhileEndLE p = reverse . dropWhile p . reverse +-- Pay attention to the short-circuit (&&)! The order of its arguments is the only +-- difference between dropWhileEnd and dropWhileEndLE. +dropWhileEndLE :: (a -> Bool) -> [a] -> [a] +dropWhileEndLE p = foldr (\x r -> if null r && p x then [] else x:r) [] + snocView :: [a] -> Maybe ([a],a) -- Split off the last element snocView [] = Nothing @@ -651,7 +665,7 @@ cmpList cmp (a:as) (b:bs) \begin{code} removeSpaces :: String -> String -removeSpaces = reverse . dropWhile isSpace . reverse . dropWhile isSpace +removeSpaces = dropWhileEndLE isSpace . dropWhile isSpace \end{code} %************************************************************************ diff --git a/libraries/base/GHC/Windows.hs b/libraries/base/GHC/Windows.hs index 0a57fc3..83f83df 100644 --- a/libraries/base/GHC/Windows.hs +++ b/libraries/base/GHC/Windows.hs @@ -69,6 +69,7 @@ import GHC.Base import GHC.IO import GHC.Num import System.IO.Error +import Util import qualified Numeric @@ -120,7 +121,7 @@ errCodeToIOError fn_name err_code = do -- XXX we should really do this directly. let errno = c_maperrno_func err_code - let msg' = reverse $ dropWhile isSpace $ reverse msg -- drop trailing \n + let msg' = dropWhileEndLE isSpace msg -- drop trailing \n ioerror = errnoToIOError fn_name errno Nothing Nothing `ioeSetErrorString` msg' return ioerror diff --git a/utils/hpc/HpcMarkup.hs b/utils/hpc/HpcMarkup.hs index 8fd9e42..c294b6a 100644 --- a/utils/hpc/HpcMarkup.hs +++ b/utils/hpc/HpcMarkup.hs @@ -140,6 +140,16 @@ charEncodingTag = "" +-- Add characters to the left of a string until it is at least as +-- large as requested. +padLeft :: Int -> Char -> String -> String +padLeft n c str = go n str + where + -- If the string is already long enough, stop traversing it. + go 0 _ = str + go k [] = replicate k c ++ str + go k (_:xs) = go (k-1) xs + genHtmlFromMod :: String -> Flags @@ -210,8 +220,7 @@ genHtmlFromMod dest_dir flags tix theFunTotals invertOutput = do content <- readFileFromPath (hpcError markup_plugin) origFile theHsPath let content' = markup tabStop info content - let show' = reverse . take 5 . (++ " ") . reverse . show - let addLine n xs = "" ++ show' n ++ " " ++ xs + let addLine n xs = "" ++ padLeft 5 ' ' (show n) ++ " " ++ xs let addLines = unlines . map (uncurry addLine) . zip [1 :: Int ..] . lines let fileName = modName0 ++ ".hs.html" putStrLn $ "Writing: " ++ fileName @@ -363,10 +372,14 @@ openTick (TopLevelDecl True 1) openTick (TopLevelDecl True n0) = "-- entered " ++ showBigNum n0 ++ " times" ++ openTopDecl where showBigNum n | n <= 9999 = show n - | otherwise = showBigNum' (n `div` 1000) ++ "," ++ showWith (n `mod` 1000) + | otherwise = case n `quotRem` 1000 of + (q, r) -> showBigNum' q ++ "," ++ showWith r showBigNum' n | n <= 999 = show n - | otherwise = showBigNum' (n `div` 1000) ++ "," ++ showWith (n `mod` 1000) - showWith n = take 3 $ reverse $ ("000" ++) $ reverse $ show n + | otherwise = case n `quotRem` 1000 of + (q, r) -> showBigNum' q ++ "," ++ showWith r + showWith n = padLeft 3 '0' $ show n + + closeTick :: String closeTick = "" @@ -462,7 +475,7 @@ instance Monoid ModuleSummary where writeFileUsing :: String -> String -> IO () writeFileUsing filename text = do - let dest_dir = reverse . dropWhile (\ x -> x /= '/') . reverse $ filename + let dest_dir = dropWhileEndLE (\ x -> x /= '/') $ filename -- We need to check for the dest_dir each time, because we use sub-dirs for -- packages, and a single .tix file might contain information about diff --git a/utils/hpc/HpcUtils.hs b/utils/hpc/HpcUtils.hs index 5655f83..73d9cd3 100644 --- a/utils/hpc/HpcUtils.hs +++ b/utils/hpc/HpcUtils.hs @@ -3,6 +3,10 @@ module HpcUtils where import Trace.Hpc.Util import qualified Data.Map as Map +dropWhileEndLE :: (a -> Bool) -> [a] -> [a] +-- Spec: dropWhileEndLE p = reverse . dropWhileEnd . reverse +dropWhileEndLE p = foldr (\x r -> if null r && p x then [] else x:r) [] + -- turns \n into ' ' -- | grab's the text behind a HpcPos; grabHpcPos :: Map.Map Int String -> HpcPos -> String From git at git.haskell.org Thu Oct 2 20:34:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 20:34:53 +0000 (UTC) Subject: [commit: ghc] master: rts/PrimOps.cmm: follow '_static_closure' update (eb191ab) Message-ID: <20141002203453.7CD943A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eb191ab6c85f4b668a6e9151dcecaf1f1e7ec7c2/ghc >--------------------------------------------------------------- commit eb191ab6c85f4b668a6e9151dcecaf1f1e7ec7c2 Author: Sergei Trofimovich Date: Thu Oct 2 21:30:26 2014 +0100 rts/PrimOps.cmm: follow '_static_closure' update Caught by UNREG build failure: rts_dist_HC rts/dist/build/PrimOps.o /tmp/ghc8613_0/ghc8613_2.hc: In function 'cf8_entry': /tmp/ghc8613_0/ghc8613_2.hc:1942:13: error: 'base_ControlziExceptionziBase_nestedAtomically_static_closure' undeclared (first use in this function) R1.w = (W_)&base_ControlziExceptionziBase_nestedAtomically_static_closure; ^ Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- eb191ab6c85f4b668a6e9151dcecaf1f1e7ec7c2 rts/PrimOps.cmm | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm index eb3ce28..a0e744b 100644 --- a/rts/PrimOps.cmm +++ b/rts/PrimOps.cmm @@ -28,7 +28,7 @@ import pthread_mutex_lock; import pthread_mutex_unlock; #endif -import base_ControlziExceptionziBase_nestedAtomically_closure; +import base_ControlziExceptionziBase_nestedAtomically_static_closure; import EnterCriticalSection; import LeaveCriticalSection; import ghczmprim_GHCziTypes_False_static_closure; From git at git.haskell.org Thu Oct 2 21:32:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 21:32:16 +0000 (UTC) Subject: [commit: ghc] master: Really fix dropWhileEndLE commit (eb35339) Message-ID: <20141002213216.EA4EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eb3533997e33602007a1a1a760a72bfcb4fba3ee/ghc >--------------------------------------------------------------- commit eb3533997e33602007a1a1a760a72bfcb4fba3ee Author: Joachim Breitner Date: Thu Oct 2 23:31:06 2014 +0200 Really fix dropWhileEndLE commit which I fixed before, but failed to pass -a to "git commit --amend" >--------------------------------------------------------------- eb3533997e33602007a1a1a760a72bfcb4fba3ee libraries/base/GHC/Windows.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/libraries/base/GHC/Windows.hs b/libraries/base/GHC/Windows.hs index 83f83df..6b23019 100644 --- a/libraries/base/GHC/Windows.hs +++ b/libraries/base/GHC/Windows.hs @@ -69,7 +69,6 @@ import GHC.Base import GHC.IO import GHC.Num import System.IO.Error -import Util import qualified Numeric @@ -121,7 +120,7 @@ errCodeToIOError fn_name err_code = do -- XXX we should really do this directly. let errno = c_maperrno_func err_code - let msg' = dropWhileEndLE isSpace msg -- drop trailing \n + let msg' = dropWhileEnd isSpace msg -- drop trailing \n ioerror = errnoToIOError fn_name errno Nothing Nothing `ioeSetErrorString` msg' return ioerror From git at git.haskell.org Thu Oct 2 21:44:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 21:44:19 +0000 (UTC) Subject: [commit: ghc] wip/dph-fix: Update primitive, vector, and dph. (146b56d) Message-ID: <20141002214419.19B743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/dph-fix Link : http://ghc.haskell.org/trac/ghc/changeset/146b56dd4f4dddcf5d0d13c347ca4b0d3f3e8d73/ghc >--------------------------------------------------------------- commit 146b56dd4f4dddcf5d0d13c347ca4b0d3f3e8d73 Author: Geoffrey Mainland Date: Wed Aug 27 22:33:44 2014 -0400 Update primitive, vector, and dph. >--------------------------------------------------------------- 146b56dd4f4dddcf5d0d13c347ca4b0d3f3e8d73 libraries/dph | 2 +- libraries/primitive | 2 +- libraries/vector | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/dph b/libraries/dph index 3ebad52..33eb2fb 160000 --- a/libraries/dph +++ b/libraries/dph @@ -1 +1 @@ -Subproject commit 3ebad521cd1e3b5573d97b483305ca465a9cba69 +Subproject commit 33eb2fb7e178c18f2afd0d537d791d021ff75231 diff --git a/libraries/primitive b/libraries/primitive index be63ee1..dc35ce5 160000 --- a/libraries/primitive +++ b/libraries/primitive @@ -1 +1 @@ -Subproject commit be63ee15d961dc1b08bc8853b9ff97708551ef36 +Subproject commit dc35ce5ef62fd3ca2e67d6db6ef8f5eeb683b06c diff --git a/libraries/vector b/libraries/vector index a6049ab..c0308f1 160000 --- a/libraries/vector +++ b/libraries/vector @@ -1 +1 @@ -Subproject commit a6049abce040713e9a5f175887cf70d12b9057c6 +Subproject commit c0308f1c4f57859d9a8b10d504afe56eebbb27c5 From git at git.haskell.org Thu Oct 2 21:44:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 21:44:21 +0000 (UTC) Subject: [commit: ghc] wip/dph-fix: Make Applicative-Monad fixes for tests. (daf3c22) Message-ID: <20141002214421.B7E8E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/dph-fix Link : http://ghc.haskell.org/trac/ghc/changeset/daf3c2255a2aa7661937648e2f42fd1e8f64f8df/ghc >--------------------------------------------------------------- commit daf3c2255a2aa7661937648e2f42fd1e8f64f8df Author: Geoffrey Mainland Date: Thu Oct 2 17:39:34 2014 -0400 Make Applicative-Monad fixes for tests. >--------------------------------------------------------------- daf3c2255a2aa7661937648e2f42fd1e8f64f8df testsuite/tests/array/should_run/arr016.hs | 8 ++++++-- testsuite/tests/codeGen/should_run/CopySmallArrayStressTest.hs | 2 +- testsuite/tests/codeGen/should_run/cgrun068.hs | 2 +- 3 files changed, 8 insertions(+), 4 deletions(-) diff --git a/testsuite/tests/array/should_run/arr016.hs b/testsuite/tests/array/should_run/arr016.hs index 055e660..0e8e2bf 100644 --- a/testsuite/tests/array/should_run/arr016.hs +++ b/testsuite/tests/array/should_run/arr016.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE ScopedTypeVariables, DatatypeContexts #-} +{-# LANGUAGE ScopedTypeVariables #-} module Main where @@ -151,7 +151,7 @@ instance Show (a -> b) where { show _ = "" } ------------------------------------------------------------------------------ -data (Ix a) => Array a b = MkArray (a,a) (a -> b) deriving () +data Array a b = MkArray (a,a) (a -> b) deriving () array :: (Ix a) => (a,a) -> [(a,b)] -> Array a b array b ivs = @@ -259,6 +259,10 @@ generate n rnd (Gen m) = m size rnd' instance Functor Gen where fmap f m = m >>= return . f +instance Applicative Gen where + pure = return + (<*>) = liftM2 id + instance Monad Gen where return a = Gen (\n r -> a) Gen m >>= k = diff --git a/testsuite/tests/codeGen/should_run/CopySmallArrayStressTest.hs b/testsuite/tests/codeGen/should_run/CopySmallArrayStressTest.hs index 7243fad..05a84df 100644 --- a/testsuite/tests/codeGen/should_run/CopySmallArrayStressTest.hs +++ b/testsuite/tests/codeGen/should_run/CopySmallArrayStressTest.hs @@ -361,7 +361,7 @@ cloneMArraySlow !marr !off n = -- Utilities for simplifying RNG passing newtype Rng s a = Rng { unRng :: StateT StdGen (ST s) a } - deriving Monad + deriving (Functor, Applicative, Monad) -- Same as 'randomR', but using the RNG state kept in the 'Rng' monad. rnd :: Random a => (a, a) -> Rng s a diff --git a/testsuite/tests/codeGen/should_run/cgrun068.hs b/testsuite/tests/codeGen/should_run/cgrun068.hs index 69a8b27..00d1249 100644 --- a/testsuite/tests/codeGen/should_run/cgrun068.hs +++ b/testsuite/tests/codeGen/should_run/cgrun068.hs @@ -361,7 +361,7 @@ cloneMArraySlow !marr !off n = -- Utilities for simplifying RNG passing newtype Rng s a = Rng { unRng :: StateT StdGen (ST s) a } - deriving Monad + deriving (Functor, Applicative, Monad) -- Same as 'randomR', but using the RNG state kept in the 'Rng' monad. rnd :: Random a => (a, a) -> Rng s a From git at git.haskell.org Thu Oct 2 21:44:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 21:44:25 +0000 (UTC) Subject: [commit: ghc] wip/dph-fix's head updated: Make Applicative-Monad fixes for tests. (daf3c22) Message-ID: <20141002214425.452FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/dph-fix' now includes: 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. 146b56d Update primitive, vector, and dph. daf3c22 Make Applicative-Monad fixes for tests. From git at git.haskell.org Thu Oct 2 21:45:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 21:45:02 +0000 (UTC) Subject: [commit: packages/dph] wip/dph-fix: More Applicative-Monad fixes. (df2204c) Message-ID: <20141002214502.F41DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/dph On branch : wip/dph-fix Link : http://git.haskell.org/packages/dph.git/commitdiff/df2204c1c3d17e03c37b565349fe1af6854964e3 >--------------------------------------------------------------- commit df2204c1c3d17e03c37b565349fe1af6854964e3 Author: Geoffrey Mainland Date: Wed Aug 27 15:45:54 2014 -0400 More Applicative-Monad fixes. >--------------------------------------------------------------- df2204c1c3d17e03c37b565349fe1af6854964e3 dph-lifted-base/Data/Array/Parallel/PArray/Reference.hs | 2 +- dph-lifted-boxed/Data/Array/Parallel/PArray.hs | 2 +- .../Data/Array/Parallel/Unlifted/Distributed/Primitive/DistST.hs | 1 + 3 files changed, 3 insertions(+), 2 deletions(-) diff --git a/dph-lifted-base/Data/Array/Parallel/PArray/Reference.hs b/dph-lifted-base/Data/Array/Parallel/PArray/Reference.hs index a98ffdc..3bcf736 100644 --- a/dph-lifted-base/Data/Array/Parallel/PArray/Reference.hs +++ b/dph-lifted-base/Data/Array/Parallel/PArray/Reference.hs @@ -55,7 +55,7 @@ import Data.Array.Parallel.Base (Tag) import Data.Vector (Vector) import qualified Data.Array.Parallel.Unlifted as U import qualified Data.Vector as V -import Control.Monad hiding ( empty ) +import Control.Monad import Prelude hiding ( replicate, length, concat , enumFromTo diff --git a/dph-lifted-boxed/Data/Array/Parallel/PArray.hs b/dph-lifted-boxed/Data/Array/Parallel/PArray.hs index 3b6b6f1..d19b795 100644 --- a/dph-lifted-boxed/Data/Array/Parallel/PArray.hs +++ b/dph-lifted-boxed/Data/Array/Parallel/PArray.hs @@ -59,7 +59,7 @@ import Data.Vector (Vector) import qualified Data.Array.Parallel.Unlifted as U import qualified Data.Array.Parallel.Array as A import qualified Data.Vector as V -import Control.Monad hiding (empty) +import Control.Monad import GHC.Exts (Int(I#), (+#)) import qualified Prelude as P import Prelude hiding diff --git a/dph-prim-par/Data/Array/Parallel/Unlifted/Distributed/Primitive/DistST.hs b/dph-prim-par/Data/Array/Parallel/Unlifted/Distributed/Primitive/DistST.hs index cdabbda..4349df4 100644 --- a/dph-prim-par/Data/Array/Parallel/Unlifted/Distributed/Primitive/DistST.hs +++ b/dph-prim-par/Data/Array/Parallel/Unlifted/Distributed/Primitive/DistST.hs @@ -31,6 +31,7 @@ import Data.Array.Parallel.Unlifted.Distributed.Primitive.DT import Data.Array.Parallel.Unlifted.Distributed.Primitive.Gang import Data.Array.Parallel.Unlifted.Distributed.Data.Tuple import Data.Array.Parallel.Base (ST, runST) +import Control.Applicative (Applicative(..)) import Control.Monad (liftM, ap) From git at git.haskell.org Thu Oct 2 21:45:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 21:45:05 +0000 (UTC) Subject: [commit: packages/dph] wip/dph-fix: Update for base 4.8. (33eb2fb) Message-ID: <20141002214505.07EA13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/dph On branch : wip/dph-fix Link : http://git.haskell.org/packages/dph.git/commitdiff/33eb2fb7e178c18f2afd0d537d791d021ff75231 >--------------------------------------------------------------- commit 33eb2fb7e178c18f2afd0d537d791d021ff75231 Author: Geoffrey Mainland Date: Thu Oct 2 15:47:36 2014 -0400 Update for base 4.8. >--------------------------------------------------------------- 33eb2fb7e178c18f2afd0d537d791d021ff75231 dph-base/dph-base.cabal | 2 +- dph-lifted-base/dph-lifted-base.cabal | 2 +- dph-lifted-boxed/dph-lifted-boxed.cabal | 2 +- dph-lifted-copy/dph-lifted-copy.cabal | 2 +- dph-lifted-vseg/dph-lifted-vseg.cabal | 2 +- dph-prim-interface/dph-prim-interface.cabal | 2 +- dph-prim-par/dph-prim-par.cabal | 2 +- dph-prim-seq/dph-prim-seq.cabal | 2 +- 8 files changed, 8 insertions(+), 8 deletions(-) diff --git a/dph-base/dph-base.cabal b/dph-base/dph-base.cabal index aec2cd6..c9bca30 100644 --- a/dph-base/dph-base.cabal +++ b/dph-base/dph-base.cabal @@ -49,7 +49,7 @@ Library -funbox-strict-fields -fcpr-off Build-Depends: - base == 4.7.*, + base == 4.8.*, ghc-prim == 0.3.*, array == 0.5.*, random == 1.0.*, diff --git a/dph-lifted-base/dph-lifted-base.cabal b/dph-lifted-base/dph-lifted-base.cabal index 0927430..a897fb9 100644 --- a/dph-lifted-base/dph-lifted-base.cabal +++ b/dph-lifted-base/dph-lifted-base.cabal @@ -53,7 +53,7 @@ Library -fno-warn-orphans Build-Depends: - base == 4.7.*, + base == 4.8.*, ghc == 7.*, array == 0.5.*, random == 1.0.*, diff --git a/dph-lifted-boxed/dph-lifted-boxed.cabal b/dph-lifted-boxed/dph-lifted-boxed.cabal index 49d2d6d..33b755f 100644 --- a/dph-lifted-boxed/dph-lifted-boxed.cabal +++ b/dph-lifted-boxed/dph-lifted-boxed.cabal @@ -60,7 +60,7 @@ Library False Build-Depends: - base == 4.7.*, + base == 4.8.*, ghc == 7.*, array == 0.5.*, pretty == 1.1.*, diff --git a/dph-lifted-copy/dph-lifted-copy.cabal b/dph-lifted-copy/dph-lifted-copy.cabal index c87e41d..ffa5577 100644 --- a/dph-lifted-copy/dph-lifted-copy.cabal +++ b/dph-lifted-copy/dph-lifted-copy.cabal @@ -62,7 +62,7 @@ Library -fno-warn-missing-signatures Build-Depends: - base == 4.7.*, + base == 4.8.*, ghc == 7.*, array == 0.5.*, random == 1.0.*, diff --git a/dph-lifted-vseg/dph-lifted-vseg.cabal b/dph-lifted-vseg/dph-lifted-vseg.cabal index 37f9c6c..1764648 100644 --- a/dph-lifted-vseg/dph-lifted-vseg.cabal +++ b/dph-lifted-vseg/dph-lifted-vseg.cabal @@ -93,7 +93,7 @@ Library -fno-warn-orphans Build-Depends: - base == 4.7.*, + base == 4.8.*, ghc == 7.*, array == 0.5.*, random == 1.0.*, diff --git a/dph-prim-interface/dph-prim-interface.cabal b/dph-prim-interface/dph-prim-interface.cabal index 156a1b1..22f8937 100644 --- a/dph-prim-interface/dph-prim-interface.cabal +++ b/dph-prim-interface/dph-prim-interface.cabal @@ -34,7 +34,7 @@ Library -funbox-strict-fields -fcpr-off Build-Depends: - base == 4.7.*, + base == 4.8.*, random == 1.0.*, dph-base == 0.8.*, vector == 0.11.* diff --git a/dph-prim-par/dph-prim-par.cabal b/dph-prim-par/dph-prim-par.cabal index 27ffa3a..3cbacba 100644 --- a/dph-prim-par/dph-prim-par.cabal +++ b/dph-prim-par/dph-prim-par.cabal @@ -75,7 +75,7 @@ Library -fcpr-off -Wall Build-Depends: - base == 4.7.*, + base == 4.8.*, random == 1.0.*, vector == 0.11.*, old-time == 1.1.*, diff --git a/dph-prim-seq/dph-prim-seq.cabal b/dph-prim-seq/dph-prim-seq.cabal index c8f67db..6e5bb4a 100644 --- a/dph-prim-seq/dph-prim-seq.cabal +++ b/dph-prim-seq/dph-prim-seq.cabal @@ -60,7 +60,7 @@ Library -funbox-strict-fields -fcpr-off Build-Depends: - base == 4.7.*, + base == 4.8.*, random == 1.0.*, vector == 0.11.*, primitive == 0.5.*, From git at git.haskell.org Thu Oct 2 21:45:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 21:45:07 +0000 (UTC) Subject: [commit: packages/dph] wip/dph-fix: Adapt to new version of the vector library. (e92f421) Message-ID: <20141002214507.148323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/dph On branch : wip/dph-fix Link : http://git.haskell.org/packages/dph.git/commitdiff/e92f421955e6801f8e4a9d4db74cf07bf15e64eb >--------------------------------------------------------------- commit e92f421955e6801f8e4a9d4db74cf07bf15e64eb Author: Geoffrey Mainland Date: Sun Oct 28 18:06:16 2012 +0000 Adapt to new version of the vector library. >--------------------------------------------------------------- e92f421955e6801f8e4a9d4db74cf07bf15e64eb dph-base/dph-base.cabal | 2 +- dph-examples/dph-examples.cabal | 40 ++--- dph-lifted-base/dph-lifted-base.cabal | 2 +- dph-lifted-boxed/dph-lifted-boxed.cabal | 2 +- dph-lifted-copy/dph-lifted-copy.cabal | 2 +- .../Data/Array/Parallel/PArray/PData/Tuple7.hs | 25 +-- dph-lifted-vseg/dph-lifted-vseg.cabal | 3 +- dph-prim-interface/dph-prim-interface.cabal | 2 +- .../Array/Parallel/Unlifted/Parallel/Segmented.hs | 17 +- dph-prim-par/dph-prim-par.cabal | 3 +- .../Array/Parallel/Unlifted/Sequential/Basics.hs | 2 +- .../Array/Parallel/Unlifted/Sequential/USel.hs | 10 +- .../Array/Parallel/Unlifted/Sequential/Vector.hs | 43 ++--- .../Data/Array/Parallel/Unlifted/Stream/Elems.hs | 17 +- .../Data/Array/Parallel/Unlifted/Stream/Ixs.hs | 15 +- .../Data/Array/Parallel/Unlifted/Stream/Locked.hs | 195 +++++++++++---------- .../Array/Parallel/Unlifted/Stream/Segmented.hs | 126 ++++++------- .../Array/Parallel/Unlifted/Stream/Segments.hs | 23 +-- .../Data/Array/Parallel/Unlifted/Stream/Swallow.hs | 43 ++--- dph-prim-seq/dph-prim-seq.cabal | 2 +- 20 files changed, 296 insertions(+), 278 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 e92f421955e6801f8e4a9d4db74cf07bf15e64eb From git at git.haskell.org Thu Oct 2 21:45:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 21:45:50 +0000 (UTC) Subject: [commit: packages/dph] master's head updated: Update for base 4.8. (33eb2fb) Message-ID: <20141002214550.2128A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/dph Branch 'master' now includes: df2204c More Applicative-Monad fixes. e92f421 Adapt to new version of the vector library. 33eb2fb Update for base 4.8. From git at git.haskell.org Thu Oct 2 22:25:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 2 Oct 2014 22:25:33 +0000 (UTC) Subject: [commit: ghc] master: arclint: Don't complain about tabs unless it's inside the diff. (2b59c7a) Message-ID: <20141002222533.4889D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2b59c7ac3f23dd229ddff20d991528ac742dfd24/ghc >--------------------------------------------------------------- commit 2b59c7ac3f23dd229ddff20d991528ac742dfd24 Author: Edward Z. Yang Date: Thu Oct 2 15:01:47 2014 -0700 arclint: Don't complain about tabs unless it's inside the diff. Summary: Signed-off-by: Edward Z. Yang Test Plan: none Reviewers: austin Subscribers: simonmar, ezyang, carter, thomie Differential Revision: https://phabricator.haskell.org/D303 >--------------------------------------------------------------- 2b59c7ac3f23dd229ddff20d991528ac742dfd24 .arclint | 16 ++++++++++++---- 1 file changed, 12 insertions(+), 4 deletions(-) diff --git a/.arclint b/.arclint index f798015..1310973 100644 --- a/.arclint +++ b/.arclint @@ -16,25 +16,33 @@ "type": "text", "include": ["(\\.(l?hs(-boot)?|x|y\\.pp)(\\.in)?$)"], "severity": { - "5": "disabled" + "5": "disabled", + "2": "warning" } }, "c": { "type": "text", - "include": ["(\\.(c|h)(\\.in)?$)"] + "include": ["(\\.(c|h)(\\.in)?$)"], + "severity": { + "2": "warning" + } }, "text-xml": { "type": "text", "include": "(\\.xml$)", "severity": { "5": "disabled", - "3": "disabled" + "3": "disabled", + "2": "warning" } }, "shell": { "type": "text", "include": [ "(\\.sh$)" ], - "text.max-line-length": 200 + "text.max-line-length": 200, + "severity": { + "2": "warning" + } }, "makefiles": { "type": "text", From git at git.haskell.org Fri Oct 3 07:32:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 3 Oct 2014 07:32:54 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: More progress (ad1ad63) Message-ID: <20141003073254.E8ABF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/ad1ad633aabd35750aff91d7051a5ab82ffabc15/ghc >--------------------------------------------------------------- commit ad1ad633aabd35750aff91d7051a5ab82ffabc15 Author: Simon Peyton Jones Date: Thu Oct 2 23:09:40 2014 +0100 More progress There is a mysterious point in TcInteract.kick_out that I must discuss with Dimitrios >--------------------------------------------------------------- ad1ad633aabd35750aff91d7051a5ab82ffabc15 compiler/typecheck/TcInteract.lhs | 6 ++- compiler/typecheck/TcSMonad.lhs | 12 ++++-- .../tests/indexed-types/should_fail/T7729.stderr | 8 +--- .../tests/indexed-types/should_fail/T8518.stderr | 15 -------- .../tests/typecheck/should_fail/ContextStack2.hs | 44 ++++++++++++++++++++++ .../typecheck/should_fail/ContextStack2.stderr | 5 +-- .../typecheck/should_fail/FDsFromGivens.stderr | 6 ++- testsuite/tests/typecheck/should_fail/T5853.stderr | 23 +++++------ .../tests/typecheck/should_fail/T7748a.stderr | 11 ++++-- testsuite/tests/typecheck/should_fail/T8142.stderr | 4 +- testsuite/tests/typecheck/should_fail/T8450.hs | 3 ++ testsuite/tests/typecheck/should_fail/T8450.stderr | 8 +--- .../tests/typecheck/should_fail/tcfail201.stderr | 9 +++-- 13 files changed, 95 insertions(+), 59 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 ad1ad633aabd35750aff91d7051a5ab82ffabc15 From git at git.haskell.org Fri Oct 3 07:32:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 3 Oct 2014 07:32:57 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 (e42db2e) Message-ID: <20141003073257.D04E63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/e42db2e21f908af0dc7c0cd5f293b445609eaf0f/ghc >--------------------------------------------------------------- commit e42db2e21f908af0dc7c0cd5f293b445609eaf0f Merge: ad1ad63 eb35339 Author: Simon Peyton Jones Date: Thu Oct 2 23:10:16 2014 +0100 Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 >--------------------------------------------------------------- e42db2e21f908af0dc7c0cd5f293b445609eaf0f libraries/base/GHC/Windows.hs | 3 +-- rts/PrimOps.cmm | 2 +- 2 files changed, 2 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Oct 3 07:32:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 3 Oct 2014 07:32:59 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14's head updated: Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 (e42db2e) Message-ID: <20141003073259.ED3323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/new-flatten-skolems-Aug14' 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 ad1ad63 More progress e42db2e Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 From git at git.haskell.org Fri Oct 3 09:13:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 3 Oct 2014 09:13:49 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Refactoring around newClsInst (1754d0b) Message-ID: <20141003091349.8FED33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/1754d0b30b75508acb889822c0dd2db7ae83e332/ghc >--------------------------------------------------------------- commit 1754d0b30b75508acb889822c0dd2db7ae83e332 Author: Simon Peyton Jones Date: Fri Oct 3 10:13:28 2014 +0100 Refactoring around newClsInst >--------------------------------------------------------------- 1754d0b30b75508acb889822c0dd2db7ae83e332 compiler/typecheck/FamInst.lhs | 9 ++------- compiler/typecheck/Inst.lhs | 34 ++++++++++++++++++++++++++------ compiler/typecheck/TcDeriv.lhs | 41 +++++++++++++++------------------------ compiler/typecheck/TcInstDcls.lhs | 11 ++--------- compiler/typecheck/TcMType.lhs | 11 ++++++++++- 5 files changed, 58 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 1754d0b30b75508acb889822c0dd2db7ae83e332 From git at git.haskell.org Fri Oct 3 09:13:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 3 Oct 2014 09:13:52 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Wibble (154716c) Message-ID: <20141003091352.438C93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/154716cb0f90c1741435a4895b35c4e2dfc50aa1/ghc >--------------------------------------------------------------- commit 154716cb0f90c1741435a4895b35c4e2dfc50aa1 Author: Simon Peyton Jones Date: Fri Oct 3 10:13:38 2014 +0100 Wibble >--------------------------------------------------------------- 154716cb0f90c1741435a4895b35c4e2dfc50aa1 testsuite/tests/indexed-types/should_compile/T3208b.stderr | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/indexed-types/should_compile/T3208b.stderr b/testsuite/tests/indexed-types/should_compile/T3208b.stderr index 5fe1a33..08f8812 100644 --- a/testsuite/tests/indexed-types/should_compile/T3208b.stderr +++ b/testsuite/tests/indexed-types/should_compile/T3208b.stderr @@ -1,11 +1,17 @@ T3208b.hs:15:10: - Could not deduce (OTerm o0 ~ STerm o0) + Could not deduce (OTerm o0 ~ OTerm a) from the context (OTerm a ~ STerm a, OBJECT a, SUBST a) bound by the type signature for fce' :: (OTerm a ~ STerm a, OBJECT a, SUBST a) => a -> c at T3208b.hs:14:9-56 + NB: ?OTerm? is a type function, and may not be injective The type variable ?o0? is ambiguous + Expected type: STerm o0 + Actual type: OTerm o0 + Relevant bindings include + f :: a (bound at T3208b.hs:15:6) + fce' :: a -> c (bound at T3208b.hs:15:1) In the expression: fce (apply f) In an equation for ?fce'?: fce' f = fce (apply f) From git at git.haskell.org Fri Oct 3 13:26:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 3 Oct 2014 13:26:00 +0000 (UTC) Subject: [commit: ghc] master: Comments only (instances for Proxy are lazy) (582217f) Message-ID: <20141003132600.766B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/582217fc25167afa0111c398aca65727a9dd9b6e/ghc >--------------------------------------------------------------- commit 582217fc25167afa0111c398aca65727a9dd9b6e Author: Reid Barton Date: Fri Oct 3 09:02:45 2014 -0400 Comments only (instances for Proxy are lazy) >--------------------------------------------------------------- 582217fc25167afa0111c398aca65727a9dd9b6e libraries/base/Data/Proxy.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/libraries/base/Data/Proxy.hs b/libraries/base/Data/Proxy.hs index 38a43b0..3ead549 100644 --- a/libraries/base/Data/Proxy.hs +++ b/libraries/base/Data/Proxy.hs @@ -34,6 +34,10 @@ data Proxy t = Proxy -- There are no instances for this because it is intended at the kind level only data KProxy (t :: *) = KProxy +-- It's common to use (undefined :: Proxy t) and (Proxy :: Proxy t) +-- interchangeably, so all of these instances are hand-written to be +-- lazy in Proxy arguments. + instance Eq (Proxy s) where _ == _ = True From git at git.haskell.org Fri Oct 3 17:59:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 3 Oct 2014 17:59:31 +0000 (UTC) Subject: [commit: ghc] master: Revert "Basic Python 3 support for testsuite driver (Trac #9184)" (e4a597f) Message-ID: <20141003175931.3E2093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e4a597f2f527ba0cd15cb51dda15cb51871c984e/ghc >--------------------------------------------------------------- commit e4a597f2f527ba0cd15cb51dda15cb51871c984e Author: Krzysztof Gogolewski Date: Fri Oct 3 19:18:38 2014 +0200 Revert "Basic Python 3 support for testsuite driver (Trac #9184)" This reverts commit 084d241b316bfa12e41fc34cae993ca276bf0730. This is a possible culprit of Windows breakage reported at ghc-devs. >--------------------------------------------------------------- e4a597f2f527ba0cd15cb51dda15cb51871c984e testsuite/config/ghc | 22 ++-- testsuite/driver/runtests.py | 67 +++++------ testsuite/driver/testlib.py | 185 +++++++++++++++-------------- testsuite/driver/testutil.py | 34 ++++++ testsuite/tests/ffi/should_run/all.T | 10 +- testsuite/tests/ghci/prog004/prog004.T | 4 +- testsuite/tests/numeric/should_run/all.T | 8 +- testsuite/tests/perf/compiler/all.T | 2 +- testsuite/tests/plugins/all.T | 4 +- testsuite/tests/th/TH_spliceViewPat/test.T | 6 +- testsuite/tests/th/all.T | 6 +- testsuite/tests/typecheck/should_run/all.T | 4 +- testsuite/timeout/calibrate | 2 +- testsuite/timeout/timeout.py | 2 +- utils/fingerprint/fingerprint.py | 8 +- 15 files changed, 195 insertions(+), 169 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 e4a597f2f527ba0cd15cb51dda15cb51871c984e From git at git.haskell.org Fri Oct 3 17:59:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 3 Oct 2014 17:59:33 +0000 (UTC) Subject: [commit: ghc] master: Restore spaces instead of tabs, caused by revert of Python 3 (4977efc) Message-ID: <20141003175933.D37FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4977efce74d0cbeb625dca7813954f9a2377aa20/ghc >--------------------------------------------------------------- commit 4977efce74d0cbeb625dca7813954f9a2377aa20 Author: Krzysztof Gogolewski Date: Fri Oct 3 19:56:00 2014 +0200 Restore spaces instead of tabs, caused by revert of Python 3 The git hook does not allow to reinsert tabs. >--------------------------------------------------------------- 4977efce74d0cbeb625dca7813954f9a2377aa20 testsuite/tests/ghci/prog004/prog004.T | 4 ++-- testsuite/tests/plugins/all.T | 4 ++-- testsuite/tests/th/TH_spliceViewPat/test.T | 6 +++--- 3 files changed, 7 insertions(+), 7 deletions(-) diff --git a/testsuite/tests/ghci/prog004/prog004.T b/testsuite/tests/ghci/prog004/prog004.T index ed17afd..4b6ee13 100644 --- a/testsuite/tests/ghci/prog004/prog004.T +++ b/testsuite/tests/ghci/prog004/prog004.T @@ -1,8 +1,8 @@ setTestOpts(only_compiler_types(['ghc'])) def f(name, opts): - if not ('ghci' in config.run_ways): - opts.skip = 1 + if not ('ghci' in config.run_ways): + opts.skip = 1 setTestOpts(f) test('ghciprog004', diff --git a/testsuite/tests/plugins/all.T b/testsuite/tests/plugins/all.T index 7e5f9b4..8b2256a 100644 --- a/testsuite/tests/plugins/all.T +++ b/testsuite/tests/plugins/all.T @@ -1,6 +1,6 @@ def f(name, opts): - if (ghc_with_interpreter == 0): - opts.skip = 1 + if (ghc_with_interpreter == 0): + opts.skip = 1 setTestOpts(f) setTestOpts(when(compiler_lt('ghc', '7.1'), skip)) diff --git a/testsuite/tests/th/TH_spliceViewPat/test.T b/testsuite/tests/th/TH_spliceViewPat/test.T index c08e7cb..21fdff3 100644 --- a/testsuite/tests/th/TH_spliceViewPat/test.T +++ b/testsuite/tests/th/TH_spliceViewPat/test.T @@ -1,7 +1,7 @@ def f(name, opts): - opts.extra_hc_opts = '-XTemplateHaskell -package template-haskell' - if (ghc_with_interpreter == 0): - opts.skip = 1 + opts.extra_hc_opts = '-XTemplateHaskell -package template-haskell' + if (ghc_with_interpreter == 0): + opts.skip = 1 setTestOpts(f) setTestOpts(only_compiler_types(['ghc'])) From git at git.haskell.org Fri Oct 3 21:13:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 3 Oct 2014 21:13:04 +0000 (UTC) Subject: [commit: ghc] master: Check for staticclosures section in Windows linker. (2fc0c6c) Message-ID: <20141003211304.3E6843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2fc0c6cf594731f343b4f8a5b3ecf9e72db4c3c0/ghc >--------------------------------------------------------------- commit 2fc0c6cf594731f343b4f8a5b3ecf9e72db4c3c0 Author: Edward Z. Yang Date: Fri Oct 3 14:12:51 2014 -0700 Check for staticclosures section in Windows linker. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 2fc0c6cf594731f343b4f8a5b3ecf9e72db4c3c0 rts/Linker.c | 1 + 1 file changed, 1 insertion(+) diff --git a/rts/Linker.c b/rts/Linker.c index 9897557..97b64ea 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -4163,6 +4163,7 @@ ocGetNames_PEi386 ( ObjectCode* oc ) 0==strcmp(".rodata",(char*)secname)) kind = SECTIONKIND_CODE_OR_RODATA; if (0==strcmp(".data",(char*)secname) || + 0==strcmp(".staticclosures",(char*)secname) || 0==strcmp(".bss",(char*)secname)) kind = SECTIONKIND_RWDATA; if (0==strcmp(".ctors", (char*)secname)) From git at git.haskell.org Fri Oct 3 22:06:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 3 Oct 2014 22:06:03 +0000 (UTC) Subject: [commit: ghc] master: Fix typo in section name: no leading period. (e8dac6d) Message-ID: <20141003220603.4F02A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e8dac6dc60beea863c3a5daded68f5157ab546fb/ghc >--------------------------------------------------------------- commit e8dac6dc60beea863c3a5daded68f5157ab546fb Author: Edward Z. Yang Date: Fri Oct 3 15:05:50 2014 -0700 Fix typo in section name: no leading period. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- e8dac6dc60beea863c3a5daded68f5157ab546fb rts/Linker.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/Linker.c b/rts/Linker.c index 97b64ea..e74d647 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -4163,7 +4163,7 @@ ocGetNames_PEi386 ( ObjectCode* oc ) 0==strcmp(".rodata",(char*)secname)) kind = SECTIONKIND_CODE_OR_RODATA; if (0==strcmp(".data",(char*)secname) || - 0==strcmp(".staticclosures",(char*)secname) || + 0==strcmp("staticclosures",(char*)secname) || 0==strcmp(".bss",(char*)secname)) kind = SECTIONKIND_RWDATA; if (0==strcmp(".ctors", (char*)secname)) From git at git.haskell.org Sat Oct 4 18:27:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 4 Oct 2014 18:27:30 +0000 (UTC) Subject: [commit: ghc] branch 'wip/python3-new' created Message-ID: <20141004182730.10CB83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/python3-new Referencing: b1aa203bb31a9c0edd3fe76b4d38ad7fce2b15f4 From git at git.haskell.org Sat Oct 4 18:27:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 4 Oct 2014 18:27:32 +0000 (UTC) Subject: [commit: ghc] wip/python3-new: Testsuite driver: Fix findTFiles for Python 3 (8d95768) Message-ID: <20141004182732.9B7BC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/python3-new Link : http://ghc.haskell.org/trac/ghc/changeset/8d95768c80baf47526d08b89e3beba24233fb448/ghc >--------------------------------------------------------------- commit 8d95768c80baf47526d08b89e3beba24233fb448 Author: Krzysztof Gogolewski Date: Sat Oct 4 19:22:04 2014 +0200 Testsuite driver: Fix findTFiles for Python 3 Previous version broke Windows build. I'm unhappy about this code, but at least it no longer appends lists in O(n^2)... >--------------------------------------------------------------- 8d95768c80baf47526d08b89e3beba24233fb448 testsuite/driver/testlib.py | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index e3562f7..397ff3b 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -2041,14 +2041,17 @@ def pretest_cleanup(name): # not interested in the return code # ----------------------------------------------------------------------------- -# Return a list of all the files ending in '.T' below the directory dir. +# Return a list of all the files ending in '.T' below directories roots. def findTFiles(roots): - return concat(map(findTFiles_,roots)) + # It would be better to use os.walk, but that + # gives backslashes on Windows, which trip the + # testsuite later :-( + return [filename for root in roots for filename in findTFiles_(root)] def findTFiles_(path): if os.path.isdir(path): - paths = map(lambda x, p=path: p + '/' + x, os.listdir(path)) + paths = [path + '/' + x for x in os.listdir(path)] return findTFiles(paths) elif path[-2:] == '.T': return [path] From git at git.haskell.org Sat Oct 4 18:27:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 4 Oct 2014 18:27:35 +0000 (UTC) Subject: [commit: ghc] wip/python3-new: Restore Python 3 support (Trac #9184) (b1aa203) Message-ID: <20141004182735.36D5F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/python3-new Link : http://ghc.haskell.org/trac/ghc/changeset/b1aa203bb31a9c0edd3fe76b4d38ad7fce2b15f4/ghc >--------------------------------------------------------------- commit b1aa203bb31a9c0edd3fe76b4d38ad7fce2b15f4 Author: Krzysztof Gogolewski Date: Sat Oct 4 20:05:08 2014 +0200 Restore Python 3 support (Trac #9184) This reverts commit e4a597f2f527ba0cd15cb51dda15cb51871c984e. Conflicts: testsuite/driver/testlib.py >--------------------------------------------------------------- b1aa203bb31a9c0edd3fe76b4d38ad7fce2b15f4 testsuite/config/ghc | 22 ++-- testsuite/driver/runtests.py | 67 +++++++----- testsuite/driver/testlib.py | 168 +++++++++++++++-------------- testsuite/driver/testutil.py | 34 ------ testsuite/tests/ffi/should_run/all.T | 10 +- testsuite/tests/numeric/should_run/all.T | 8 +- testsuite/tests/perf/compiler/all.T | 2 +- testsuite/tests/th/all.T | 6 +- testsuite/tests/typecheck/should_run/all.T | 4 +- testsuite/timeout/calibrate | 2 +- testsuite/timeout/timeout.py | 2 +- utils/fingerprint/fingerprint.py | 8 +- 12 files changed, 156 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 b1aa203bb31a9c0edd3fe76b4d38ad7fce2b15f4 From git at git.haskell.org Sat Oct 4 20:29:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 4 Oct 2014 20:29:26 +0000 (UTC) Subject: [commit: ghc] master: ghc.mk: fix list for dll-split on GHCi-less builds (2a8ea47) Message-ID: <20141004202926.DA1813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2a8ea4745d6ff79d6ce17961a64d9013243fc3c6/ghc >--------------------------------------------------------------- commit 2a8ea4745d6ff79d6ce17961a64d9013243fc3c6 Author: Sergei Trofimovich Date: Sat Oct 4 20:48:22 2014 +0100 ghc.mk: fix list for dll-split on GHCi-less builds To reproduce build failure it's enough to try to build GHC on amd64 with the following setup: $ cat mk/build.mk # for #9552 GhcWithInterpreter = NO It gives: Reachable modules from DynFlags out of date Please fix compiler/ghc.mk, or building DLLs on Windows may break (#7780) Redundant modules: Bitmap BlockId ... dll-split among other things makes sure all mentioned modules are used by DynFlags. '#ifdef GHCI' keeps is from happening. Patch moves those 42 modules under 'GhcWithInterpreter' guard. Fixes Issue #9552 Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 2a8ea4745d6ff79d6ce17961a64d9013243fc3c6 compiler/ghc.mk | 90 ++++++++++++++++++++++++++++++--------------------------- 1 file changed, 48 insertions(+), 42 deletions(-) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index 05c935f..8e00149 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -467,36 +467,15 @@ compiler_stage2_dll0_MODULES = \ BasicTypes \ BinIface \ Binary \ - Bitmap \ - BlockId \ BooleanFormula \ BreakArray \ BufWrite \ BuildTyCl \ - ByteCodeAsm \ - ByteCodeInstr \ - ByteCodeItbls \ - CLabel \ Class \ CmdLineParser \ - Cmm \ - CmmCallConv \ - CmmExpr \ - CmmInfo \ - CmmMachOp \ - CmmNode \ CmmType \ - CmmUtils \ CoAxiom \ ConLike \ - CodeGen.Platform \ - CodeGen.Platform.ARM \ - CodeGen.Platform.NoRegs \ - CodeGen.Platform.PPC \ - CodeGen.Platform.PPC_Darwin \ - CodeGen.Platform.SPARC \ - CodeGen.Platform.X86 \ - CodeGen.Platform.X86_64 \ Coercion \ Config \ Constants \ @@ -520,7 +499,6 @@ compiler_stage2_dll0_MODULES = \ Exception \ ExtsCompat46 \ FamInstEnv \ - FastBool \ FastFunctions \ FastMutInt \ FastString \ @@ -530,8 +508,6 @@ compiler_stage2_dll0_MODULES = \ FiniteMap \ ForeignCall \ Hooks \ - Hoopl \ - Hoopl.Dataflow \ HsBinds \ HsDecls \ HsDoc \ @@ -551,14 +527,12 @@ compiler_stage2_dll0_MODULES = \ IfaceSyn \ IfaceType \ InstEnv \ - InteractiveEvalTypes \ Kind \ ListSetOps \ Literal \ LoadIface \ Maybes \ MkCore \ - MkGraph \ MkId \ Module \ MonadUtils \ @@ -578,9 +552,6 @@ compiler_stage2_dll0_MODULES = \ PipelineMonad \ Platform \ PlatformConstants \ - PprCmm \ - PprCmmDecl \ - PprCmmExpr \ PprCore \ PrelInfo \ PrelNames \ @@ -588,23 +559,10 @@ compiler_stage2_dll0_MODULES = \ Pretty \ PrimOp \ RdrName \ - Reg \ - RegClass \ Rules \ - SMRep \ Serialized \ SrcLoc \ StaticFlags \ - StgCmmArgRep \ - StgCmmClosure \ - StgCmmEnv \ - StgCmmLayout \ - StgCmmMonad \ - StgCmmProf \ - StgCmmTicky \ - StgCmmUtils \ - StgSyn \ - Stream \ StringBuffer \ TcEvidence \ TcIface \ @@ -628,6 +586,54 @@ compiler_stage2_dll0_MODULES = \ VarEnv \ VarSet +ifeq "$(GhcWithInterpreter)" "YES" +# These files are reacheable from DynFlags +# only by GHCi-enabled code (see #9552) +compiler_stage2_dll0_MODULES += \ + Bitmap \ + BlockId \ + ByteCodeAsm \ + ByteCodeInstr \ + ByteCodeItbls \ + CLabel \ + Cmm \ + CmmCallConv \ + CmmExpr \ + CmmInfo \ + CmmMachOp \ + CmmNode \ + CmmUtils \ + CodeGen.Platform \ + CodeGen.Platform.ARM \ + CodeGen.Platform.NoRegs \ + CodeGen.Platform.PPC \ + CodeGen.Platform.PPC_Darwin \ + CodeGen.Platform.SPARC \ + CodeGen.Platform.X86 \ + CodeGen.Platform.X86_64 \ + FastBool \ + Hoopl \ + Hoopl.Dataflow \ + InteractiveEvalTypes \ + MkGraph \ + PprCmm \ + PprCmmDecl \ + PprCmmExpr \ + Reg \ + RegClass \ + SMRep \ + StgCmmArgRep \ + StgCmmClosure \ + StgCmmEnv \ + StgCmmLayout \ + StgCmmMonad \ + StgCmmProf \ + StgCmmTicky \ + StgCmmUtils \ + StgSyn \ + Stream +endif + compiler_stage2_dll0_HS_OBJS = \ $(patsubst %,compiler/stage2/build/%.$(dyn_osuf),$(subst .,/,$(compiler_stage2_dll0_MODULES))) From git at git.haskell.org Sun Oct 5 20:45:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 5 Oct 2014 20:45:36 +0000 (UTC) Subject: [commit: ghc] master: Implement `MIN_VERSION_GLASGOW_HASKELL()` macro (3549c95) Message-ID: <20141005204536.ADF813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3549c952b535803270872adaf87262f2df0295a4/ghc >--------------------------------------------------------------- commit 3549c952b535803270872adaf87262f2df0295a4 Author: Herbert Valerio Riedel Date: Sun Oct 5 22:35:22 2014 +0200 Implement `MIN_VERSION_GLASGOW_HASKELL()` macro This exposes the `cProjectPatchLevel{1,2}` value at the CPP level to allow it to be used in CPP conditionals. Concretely, GHC 7.10.2.20150623 would result in #define __GLASGOW_HASKELL__ 710 #define __GLASGOW_HASKELL_PATCHLEVEL1__ 2 #define __GLASGOW_HASKELL_PATCHLEVEL2__ 20150623 while GHC 7.10.3 results in #define __GLASGOW_HASKELL__ 710 #define __GLASGOW_HASKELL_PATCHLEVEL1__ 3 and finally GHC 7.9.20141009 results in #define __GLASGOW_HASKELL__ 709 #define __GLASGOW_HASKELL_PATCHLEVEL1__ 20141009 As it's error-prone to properly express CPP conditionals for testing GHC multi-component versions, a new macro `MIN_VERSION_GLASGOW_HASKELL()` is provided (also via the new CPP include file `ghcversion.h`) Finally, in order to make it easier to define the new CPP macro `MIN_VERSION_GLASGOW_HASKELL()`, a new default-included `include/ghcversion.h` is used for the new CPP definitions. Reviewed By: ekmett, austin, #ghc Differential Revision: https://phabricator.haskell.org/D66 >--------------------------------------------------------------- 3549c952b535803270872adaf87262f2df0295a4 .gitignore | 1 + aclocal.m4 | 7 ++++ compiler/ghc.mk | 4 +++ compiler/main/DriverPipeline.hs | 28 +++++++++++---- docs/users_guide/phases.xml | 79 +++++++++++++++++++++++++++++++++++++++++ ghc.mk | 1 + includes/ghc.mk | 39 +++++++++++++++++--- mk/project.mk.in | 2 ++ 8 files changed, 150 insertions(+), 11 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 3549c952b535803270872adaf87262f2df0295a4 From git at git.haskell.org Sun Oct 5 21:11:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 5 Oct 2014 21:11:17 +0000 (UTC) Subject: [commit: ghc] master: rts: unrust 'libbfd' debug symbols parser (cb0a503) Message-ID: <20141005211117.E957E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cb0a503a44bf016de3d9042906c6ac0c0821ffea/ghc >--------------------------------------------------------------- commit cb0a503a44bf016de3d9042906c6ac0c0821ffea Author: Sergei Trofimovich Date: Sun Oct 5 21:20:39 2014 +0100 rts: unrust 'libbfd' debug symbols parser Summary: Patch does the following: - fixes detection of working libbfd on modern linux platforms (where bfd_uncompress_section_contents is a macro) - disables 'bfd' by default and adds '--enable-bfd-debug' configure option. As bfd's ABI is unstable the feature is primarily useful by ghc hackers. Not done (subject for another patch): - one-time bfd object memory leak in DEBUG_LoadSymbols - in '-dynamic' mode debugging symbols are loaded only for current executable, not all libraries it is linked against. Fixes Issue #8790 Signed-off-by: Sergei Trofimovich Test Plan: built unregisterised ghc on amd64 and ran './hello +RTS -Di' there Reviewers: simonmar, austin Reviewed By: simonmar, austin Subscribers: thomie, simonmar, ezyang, carter Differential Revision: https://phabricator.haskell.org/D193 GHC Trac Issues: #8790 >--------------------------------------------------------------- cb0a503a44bf016de3d9042906c6ac0c0821ffea aclocal.m4 | 49 +++++++++++++++++++++++++++++++++++++++++++++++++ configure.ac | 7 ++----- rts/Printer.c | 15 ++++++++++++--- rts/RtsStartup.c | 6 ++++++ 4 files changed, 69 insertions(+), 8 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index a98691e..0db231d 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2215,4 +2215,53 @@ $2=$HS_CPP_ARGS ]) +# FP_BFD_SUPPORT() +# ---------------------- +# whether to use libbfd for debugging RTS +AC_DEFUN([FP_BFD_SUPPORT], [ + AC_ARG_ENABLE(bfd-debug, + [AC_HELP_STRING([--enable-bfd-debug], + [Enable symbol resolution for -debug rts ('+RTS -Di') via binutils' libbfd [default=no]])], + [ + # don't pollute general LIBS environment + save_LIBS="$LIBS" + AC_CHECK_HEADERS([bfd.h]) + dnl ** check whether this machine has BFD and libiberty installed (used for debugging) + dnl the order of these tests matters: bfd needs libiberty + AC_CHECK_LIB(iberty, xmalloc) + dnl 'bfd_init' is a rare non-macro in libbfd + AC_CHECK_LIB(bfd, bfd_init) + + AC_TRY_LINK([#include ], + [ + /* mimic our rts/Printer.c */ + bfd* abfd; + const char * name; + char **matching; + + name = "some.executable"; + bfd_init(); + abfd = bfd_openr(name, "default"); + bfd_check_format_matches (abfd, bfd_object, &matching); + { + long storage_needed; + storage_needed = bfd_get_symtab_upper_bound (abfd); + } + { + asymbol **symbol_table; + long number_of_symbols; + symbol_info info; + + number_of_symbols = bfd_canonicalize_symtab (abfd, symbol_table); + bfd_get_symbol_info(abfd,symbol_table[0],&info); + } + ], + [],dnl bfd seems to work + [AC_MSG_ERROR([can't use 'bfd' library])]) + LIBS="$save_LIBS" + ], + [] + ) +]) + # LocalWords: fi diff --git a/configure.ac b/configure.ac index e7a0774..7b59f78 100644 --- a/configure.ac +++ b/configure.ac @@ -753,7 +753,7 @@ dnl off_t, because it will affect the result of that test. AC_SYS_LARGEFILE dnl ** check for specific header (.h) files that we are interested in -AC_CHECK_HEADERS([bfd.h ctype.h dirent.h dlfcn.h errno.h fcntl.h grp.h limits.h locale.h nlist.h pthread.h pwd.h signal.h sys/param.h sys/mman.h sys/resource.h sys/select.h sys/time.h sys/timeb.h sys/timers.h sys/times.h sys/utsname.h sys/wait.h termios.h time.h utime.h windows.h winsock.h sched.h]) +AC_CHECK_HEADERS([ctype.h dirent.h dlfcn.h errno.h fcntl.h grp.h limits.h locale.h nlist.h pthread.h pwd.h signal.h sys/param.h sys/mman.h sys/resource.h sys/select.h sys/time.h sys/timeb.h sys/timers.h sys/times.h sys/utsname.h sys/wait.h termios.h time.h utime.h windows.h winsock.h sched.h]) dnl sys/cpuset.h needs sys/param.h to be included first on FreeBSD 9.1; #7708 AC_CHECK_HEADERS([sys/cpuset.h], [], [], @@ -846,10 +846,7 @@ then AC_DEFINE([HAVE_LIBM], [1], [Define to 1 if you need to link with libm]) fi -dnl ** check whether this machine has BFD and libiberty installed (used for debugging) -dnl the order of these tests matters: bfd needs libiberty -AC_CHECK_LIB(iberty, xmalloc) -AC_CHECK_LIB(bfd, bfd_uncompress_section_contents) +FP_BFD_SUPPORT dnl ################################################################ dnl Check for libraries diff --git a/rts/Printer.c b/rts/Printer.c index 3d77e83..9bc2984 100644 --- a/rts/Printer.c +++ b/rts/Printer.c @@ -7,6 +7,8 @@ * ---------------------------------------------------------------------------*/ #include "PosixSource.h" +#include "ghcconfig.h" + #include "Rts.h" #include "rts/Bytecodes.h" /* for InstrPtr */ @@ -664,8 +666,16 @@ const char *lookupGHCName( void *addr ) disabling this for now. */ #ifdef USING_LIBBFD - -#include +# define PACKAGE 1 +# define PACKAGE_VERSION 1 +/* Those PACKAGE_* defines are workarounds for bfd: + * https://sourceware.org/bugzilla/show_bug.cgi?id=14243 + * ghc's build system filter PACKAGE_* values out specifically to avoid clashes + * with user's autoconf-based Cabal packages. + * It's a shame checks for unrelated fields instead of actually used + * macros. + */ +# include /* Fairly ad-hoc piece of code that seems to filter out a lot of * rubbish like the obj-splitting symbols @@ -733,7 +743,6 @@ extern void DEBUG_LoadSymbols( char *name ) for( i = 0; i != number_of_symbols; ++i ) { symbol_info info; bfd_get_symbol_info(abfd,symbol_table[i],&info); - /*debugBelch("\t%c\t0x%x \t%s\n",info.type,(nat)info.value,info.name); */ if (isReal(info.type, info.name)) { num_real_syms += 1; } diff --git a/rts/RtsStartup.c b/rts/RtsStartup.c index 98a43c0..5e6f9fa 100644 --- a/rts/RtsStartup.c +++ b/rts/RtsStartup.c @@ -19,6 +19,7 @@ #include "RtsFlags.h" #include "RtsUtils.h" #include "Prelude.h" +#include "Printer.h" /* DEBUG_LoadSymbols */ #include "Schedule.h" /* initScheduler */ #include "Stats.h" /* initStats */ #include "STM.h" /* initSTM */ @@ -162,6 +163,11 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config) rts_config.rts_opts_enabled, rts_config.rts_opts, rts_config.rts_hs_main); } +#ifdef DEBUG + /* load debugging symbols for current binary */ + DEBUG_LoadSymbols((*argv)[0]); +#endif /* DEBUG */ + /* Initialise the stats department, phase 1 */ initStats1(); From git at git.haskell.org Mon Oct 6 21:04:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 6 Oct 2014 21:04:44 +0000 (UTC) Subject: [commit: ghc] branch 'wip/oneShot' created Message-ID: <20141006210444.0AEF23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/oneShot Referencing: 0d35a3bd7456b975236e1ac875824f5915fd7e72 From git at git.haskell.org Mon Oct 6 21:04:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 6 Oct 2014 21:04:46 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Add GHC.Prim.oneShot (4a31d97) Message-ID: <20141006210446.A7A8B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/4a31d97d1f9ef8618f99d3b3dcc6bf0f80f0ab49/ghc >--------------------------------------------------------------- commit 4a31d97d1f9ef8618f99d3b3dcc6bf0f80f0ab49 Author: Joachim Breitner Date: Sun Jan 26 11:36:23 2014 +0000 Add GHC.Prim.oneShot Conflicts: compiler/basicTypes/MkId.lhs >--------------------------------------------------------------- 4a31d97d1f9ef8618f99d3b3dcc6bf0f80f0ab49 compiler/basicTypes/MkId.lhs | 17 +++++++++++++++-- compiler/prelude/PrelNames.lhs | 3 ++- 2 files changed, 17 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index bf1c199..05dcdd5 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -135,7 +135,8 @@ ghcPrimIds seqId, magicDictId, coerceId, - proxyHashId + proxyHashId, + oneShotId ] \end{code} @@ -1016,7 +1017,7 @@ another gun with which to shoot yourself in the foot. \begin{code} lazyIdName, unsafeCoerceName, nullAddrName, seqName, realWorldName, voidPrimIdName, coercionTokenName, - magicDictName, coerceName, proxyName, dollarName :: Name + 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 @@ -1028,6 +1029,7 @@ magicDictName = mkWiredInIdName gHC_PRIM (fsLit "magicDict") magicDict coerceName = mkWiredInIdName gHC_PRIM (fsLit "coerce") coerceKey coerceId proxyName = mkWiredInIdName gHC_PRIM (fsLit "proxy#") proxyHashKey proxyHashId dollarName = mkWiredInIdName gHC_BASE (fsLit "$") dollarIdKey dollarId +oneShotName = mkWiredInIdName gHC_PRIM (fsLit "oneShot") oneShotKey oneShotId \end{code} \begin{code} @@ -1119,6 +1121,17 @@ lazyId = pcMiscPrelId lazyIdName ty info info = noCafIdInfo ty = mkForAllTys [alphaTyVar] (mkFunTy alphaTy alphaTy) +oneShotId :: Id +oneShotId = pcMiscPrelId oneShotName ty info + where + info = noCafIdInfo `setInlinePragInfo` alwaysInlinePragma + `setUnfoldingInfo` mkCompulsoryUnfolding rhs + ty = mkForAllTys [alphaTyVar, betaTyVar] (mkFunTy fun_ty fun_ty) + fun_ty = mkFunTy alphaTy betaTy + [body, x] = mkTemplateLocals [fun_ty, alphaTy] + x' = setOneShotLambda x + rhs = mkLams [alphaTyVar, betaTyVar, body, x'] $ Var body `App` Var x + -------------------------------------------------------------------------------- magicDictId :: Id -- See Note [magicDictId magic] diff --git a/compiler/prelude/PrelNames.lhs b/compiler/prelude/PrelNames.lhs index a182e9b..fc9883f 100644 --- a/compiler/prelude/PrelNames.lhs +++ b/compiler/prelude/PrelNames.lhs @@ -1716,10 +1716,11 @@ rootMainKey, runMainKey :: Unique rootMainKey = mkPreludeMiscIdUnique 101 runMainKey = mkPreludeMiscIdUnique 102 -thenIOIdKey, lazyIdKey, assertErrorIdKey :: Unique +thenIOIdKey, lazyIdKey, assertErrorIdKey, oneShotKey :: Unique thenIOIdKey = mkPreludeMiscIdUnique 103 lazyIdKey = mkPreludeMiscIdUnique 104 assertErrorIdKey = mkPreludeMiscIdUnique 105 +oneShotKey = mkPreludeMiscIdUnique 106 breakpointIdKey, breakpointCondIdKey, breakpointAutoIdKey, breakpointJumpIdKey, breakpointCondJumpIdKey, From git at git.haskell.org Mon Oct 6 21:04:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 6 Oct 2014 21:04:49 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Add oneShot demo file (0d35a3b) Message-ID: <20141006210449.9B8923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/0d35a3bd7456b975236e1ac875824f5915fd7e72/ghc >--------------------------------------------------------------- commit 0d35a3bd7456b975236e1ac875824f5915fd7e72 Author: Joachim Breitner Date: Mon Oct 6 23:04:02 2014 +0200 Add oneShot demo file (if you remove {-# GHC_OPTIONS -fno-call-arity #-} then both functions have the same Core). Obviously, this patch is not meant to be merged. >--------------------------------------------------------------- 0d35a3bd7456b975236e1ac875824f5915fd7e72 OneShotTest.hs | 19 +++++++++++++++++++ 1 file changed, 19 insertions(+) diff --git a/OneShotTest.hs b/OneShotTest.hs new file mode 100644 index 0000000..852450e --- /dev/null +++ b/OneShotTest.hs @@ -0,0 +1,19 @@ +{-# GHC_OPTIONS -fno-call-arity #-} + +module OneShotTest (fooA, fooB) where + +import GHC.Prim (oneShot) + +foldlA, foldlB :: (x -> a -> a) -> a -> [x] -> a + +foldlA k a xs = foldr (\v f a -> f (v `k` a)) id xs a + +foldlB k a xs = foldr (\v f -> oneShot (\ a -> f (v `k` a))) id xs a + +f :: Int -> Bool +f 0 = True +f 1 = False +{-# NOINLINE f #-} + +fooA = foldlA (+) 0 . filter f +fooB = foldlB (+) 0 . filter f From git at git.haskell.org Mon Oct 6 21:05:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 6 Oct 2014 21:05:45 +0000 (UTC) Subject: [commit: ghc] master: testsuite: fix tcrun036 build against Prelude/Main 'traverse' clash (6a36636) Message-ID: <20141006210545.370D73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6a36636489682a885f5be59ff1cb0372e23a19db/ghc >--------------------------------------------------------------- commit 6a36636489682a885f5be59ff1cb0372e23a19db Author: Sergei Trofimovich Date: Mon Oct 6 21:43:42 2014 +0100 testsuite: fix tcrun036 build against Prelude/Main 'traverse' clash Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 6a36636489682a885f5be59ff1cb0372e23a19db testsuite/tests/typecheck/should_run/tcrun036.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/testsuite/tests/typecheck/should_run/tcrun036.hs b/testsuite/tests/typecheck/should_run/tcrun036.hs index cef36a6..64fffb7 100644 --- a/testsuite/tests/typecheck/should_run/tcrun036.hs +++ b/testsuite/tests/typecheck/should_run/tcrun036.hs @@ -21,6 +21,8 @@ module Main where +import Prelude hiding (traverse) + class Catalog c where traverse :: c -> Viewer -> IO () From git at git.haskell.org Mon Oct 6 21:05:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 6 Oct 2014 21:05:47 +0000 (UTC) Subject: [commit: ghc] master: testsuite: fix T5751 build failure (AMP) (a1b5391) Message-ID: <20141006210547.CF1303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a1b539142d7853bc02c36f1b3e8d489a9864f0e9/ghc >--------------------------------------------------------------- commit a1b539142d7853bc02c36f1b3e8d489a9864f0e9 Author: Sergei Trofimovich Date: Mon Oct 6 21:46:26 2014 +0100 testsuite: fix T5751 build failure (AMP) Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- a1b539142d7853bc02c36f1b3e8d489a9864f0e9 testsuite/tests/typecheck/should_run/T5751.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/typecheck/should_run/T5751.hs b/testsuite/tests/typecheck/should_run/T5751.hs index f620d8f..cf11421 100644 --- a/testsuite/tests/typecheck/should_run/T5751.hs +++ b/testsuite/tests/typecheck/should_run/T5751.hs @@ -12,7 +12,7 @@ class XMLGenerator m where genElement :: (Maybe String, String) -> m () newtype IdentityT m a = IdentityT { runIdentityT :: m a } - deriving (Monad, MonadIO) + deriving (Functor, Applicative, Monad, MonadIO) instance (MonadIO m) => (XMLGenerator (IdentityT m)) where genElement _ = liftIO $ putStrLn "in genElement" From git at git.haskell.org Mon Oct 6 21:05:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 6 Oct 2014 21:05:50 +0000 (UTC) Subject: [commit: ghc] master: testsuite: fix T1735_Help/State.hs build failure (AMP) (b30b185) Message-ID: <20141006210550.646E83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b30b185e5c653dfed948d71ce2336be70be3b418/ghc >--------------------------------------------------------------- commit b30b185e5c653dfed948d71ce2336be70be3b418 Author: Sergei Trofimovich Date: Mon Oct 6 21:55:02 2014 +0100 testsuite: fix T1735_Help/State.hs build failure (AMP) Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- b30b185e5c653dfed948d71ce2336be70be3b418 testsuite/tests/typecheck/should_run/T1735_Help/State.hs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/testsuite/tests/typecheck/should_run/T1735_Help/State.hs b/testsuite/tests/typecheck/should_run/T1735_Help/State.hs index 7b048eb..d696af7 100644 --- a/testsuite/tests/typecheck/should_run/T1735_Help/State.hs +++ b/testsuite/tests/typecheck/should_run/T1735_Help/State.hs @@ -1,6 +1,9 @@ module T1735_Help.State where +import Control.Monad (ap, liftM) + + newtype StateT s m a = StateT { runStateT :: s -> m (a,s) } instance Monad m => Monad (StateT s m) where @@ -10,6 +13,13 @@ instance Monad m => Monad (StateT s m) where runStateT (k a) s' fail str = StateT $ \_ -> fail str +instance Monad m => Functor (StateT s m) where + fmap = liftM + +instance Monad m => Applicative (StateT s m) where + pure = return + (<*>) = ap + get :: Monad m => StateT s m s get = StateT $ \s -> return (s, s) From git at git.haskell.org Mon Oct 6 21:05:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 6 Oct 2014 21:05:52 +0000 (UTC) Subject: [commit: ghc] master: testsuite: fix seward-space-leak build aganst Prelude/Main 'traverse' clash (6ecf19c) Message-ID: <20141006210552.EBE483A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6ecf19c61221bddf5df3ee54f24daa90c91bdd71/ghc >--------------------------------------------------------------- commit 6ecf19c61221bddf5df3ee54f24daa90c91bdd71 Author: Sergei Trofimovich Date: Mon Oct 6 22:01:14 2014 +0100 testsuite: fix seward-space-leak build aganst Prelude/Main 'traverse' clash Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 6ecf19c61221bddf5df3ee54f24daa90c91bdd71 testsuite/tests/programs/seward-space-leak/Main.lhs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/testsuite/tests/programs/seward-space-leak/Main.lhs b/testsuite/tests/programs/seward-space-leak/Main.lhs index 327118d..6c3f9f9 100644 --- a/testsuite/tests/programs/seward-space-leak/Main.lhs +++ b/testsuite/tests/programs/seward-space-leak/Main.lhs @@ -64,6 +64,8 @@ Collector: APPEL HeapSize: 4,194,304 (bytes) > module Main where +> import Prelude hiding (traverse) + %============================================================ %============================================================ From git at git.haskell.org Tue Oct 7 08:17:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 08:17:43 +0000 (UTC) Subject: [commit: ghc] master: Use correct precedence when printing contexts with class operators (48089cc) Message-ID: <20141007081743.44FD03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/48089ccf4f1f239b3268b2cb52b8aa0f7356485b/ghc >--------------------------------------------------------------- commit 48089ccf4f1f239b3268b2cb52b8aa0f7356485b 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 >--------------------------------------------------------------- 48089ccf4f1f239b3268b2cb52b8aa0f7356485b compiler/types/TypeRep.lhs | 5 ++++- 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 | 2 +- testsuite/tests/polykinds/T7230.stderr | 3 ++- testsuite/tests/roles/should_compile/Roles3.stderr | 2 +- testsuite/tests/typecheck/should_fail/ContextStack2.stderr | 2 +- 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 | 4 ++-- 19 files changed, 32 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 48089ccf4f1f239b3268b2cb52b8aa0f7356485b From git at git.haskell.org Tue Oct 7 08:17:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 08:17:46 +0000 (UTC) Subject: [commit: ghc] master: Merge branch 'master' of http://git.haskell.org/ghc (85aba49) Message-ID: <20141007081746.405DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/85aba4961a533bfb3f26314d854de19b781093ac/ghc >--------------------------------------------------------------- commit 85aba4961a533bfb3f26314d854de19b781093ac Merge: 48089cc 6ecf19c Author: Simon Peyton Jones Date: Tue Oct 7 08:03:58 2014 +0100 Merge branch 'master' of http://git.haskell.org/ghc >--------------------------------------------------------------- 85aba4961a533bfb3f26314d854de19b781093ac .gitignore | 1 + aclocal.m4 | 56 +++++++ compiler/ghc.mk | 94 ++++++----- compiler/main/DriverPipeline.hs | 28 +++- configure.ac | 7 +- docs/users_guide/phases.xml | 79 +++++++++ ghc.mk | 1 + includes/ghc.mk | 39 ++++- libraries/base/Data/Proxy.hs | 4 + mk/project.mk.in | 2 + rts/Linker.c | 1 + rts/Printer.c | 15 +- rts/RtsStartup.c | 6 + testsuite/config/ghc | 22 ++- testsuite/driver/runtests.py | 67 ++++---- testsuite/driver/testlib.py | 185 +++++++++++---------- testsuite/driver/testutil.py | 34 ++++ testsuite/tests/ffi/should_run/all.T | 10 +- testsuite/tests/numeric/should_run/all.T | 8 +- testsuite/tests/perf/compiler/all.T | 2 +- .../tests/programs/seward-space-leak/Main.lhs | 2 + testsuite/tests/th/all.T | 6 +- .../tests/typecheck/should_run/T1735_Help/State.hs | 10 ++ testsuite/tests/typecheck/should_run/T5751.hs | 2 +- testsuite/tests/typecheck/should_run/all.T | 4 +- testsuite/tests/typecheck/should_run/tcrun036.hs | 2 + testsuite/timeout/calibrate | 2 +- testsuite/timeout/timeout.py | 2 +- utils/fingerprint/fingerprint.py | 8 +- 29 files changed, 475 insertions(+), 224 deletions(-) From git at git.haskell.org Tue Oct 7 08:49:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 08:49:19 +0000 (UTC) Subject: [commit: ghc] master: Fix a typo in an error message (3c5648a) Message-ID: <20141007084919.2BBE83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3c5648afff13e9f6e94dea4094cc3a3fb97baeea/ghc >--------------------------------------------------------------- commit 3c5648afff13e9f6e94dea4094cc3a3fb97baeea Author: Gabor Greif Date: Tue Oct 7 10:20:08 2014 +0200 Fix a typo in an error message >--------------------------------------------------------------- 3c5648afff13e9f6e94dea4094cc3a3fb97baeea 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 a4a7b29..aca9e51 100644 --- a/compiler/typecheck/TcTyClsDecls.lhs +++ b/compiler/typecheck/TcTyClsDecls.lhs @@ -1703,7 +1703,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 Tue Oct 7 11:37:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 11:37:23 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Make travis happy (a28f9da) Message-ID: <20141007113723.CCD593A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/a28f9da6c66ee722f5f9a796dbff0037262f5a61/ghc >--------------------------------------------------------------- commit a28f9da6c66ee722f5f9a796dbff0037262f5a61 Author: Joachim Breitner Date: Tue Oct 7 13:37:23 2014 +0200 Make travis happy >--------------------------------------------------------------- a28f9da6c66ee722f5f9a796dbff0037262f5a61 libraries/base/GHC/Event/Manager.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/Event/Manager.hs b/libraries/base/GHC/Event/Manager.hs index 2041379..29edd97 100644 --- a/libraries/base/GHC/Event/Manager.hs +++ b/libraries/base/GHC/Event/Manager.hs @@ -167,10 +167,10 @@ newDefaultBackend = error "no back end for this platform" -- | Create a new event manager. new :: Bool -> IO EventManager -new oneShot = newWith oneShot =<< newDefaultBackend +new isOneShot = newWith isOneShot =<< newDefaultBackend newWith :: Bool -> Backend -> IO EventManager -newWith oneShot be = do +newWith isOneShot be = do iofds <- fmap (listArray (0, callbackArraySize-1)) $ replicateM callbackArraySize (newMVar =<< IT.new 8) ctrl <- newControl False @@ -187,7 +187,7 @@ newWith oneShot be = do , emState = state , emUniqueSource = us , emControl = ctrl - , emOneShot = oneShot + , emOneShot = isOneShot , emLock = lockVar } registerControlFd mgr (controlReadFd ctrl) evtRead From git at git.haskell.org Tue Oct 7 12:37:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 12:37:56 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Don't freshen the dfun tyvars in newClsInst (a58aca0) Message-ID: <20141007123756.05A633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/a58aca000a60dc9db73231c1fbabc7ee72c5c324/ghc >--------------------------------------------------------------- commit a58aca000a60dc9db73231c1fbabc7ee72c5c324 Author: Simon Peyton Jones Date: Tue Oct 7 13:37:30 2014 +0100 Don't freshen the dfun tyvars in newClsInst (they scope over the binds; show up when compiling GHC.Ord) >--------------------------------------------------------------- a58aca000a60dc9db73231c1fbabc7ee72c5c324 compiler/typecheck/Inst.lhs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/compiler/typecheck/Inst.lhs b/compiler/typecheck/Inst.lhs index 058772f..7ec127c 100644 --- a/compiler/typecheck/Inst.lhs +++ b/compiler/typecheck/Inst.lhs @@ -415,11 +415,10 @@ newClsInst overlap_mode dfun_name tvs theta clas tys = do { (subst, tvs') <- freshenTyVarBndrs tvs -- Be sure to freshen those type variables, -- so they are sure not to appear in any lookup - ; let theta' = substTheta subst theta - tys' = substTys subst tys - dfun = mkDictFunId dfun_name tvs' theta' clas tys' - -- We don't really need to substitute in the dfun's type, - -- but it avoids gratuitous differences if we do so + ; let tys' = substTys subst tys + dfun = mkDictFunId dfun_name tvs theta clas tys + -- We don't substitute in the dfun's type, + -- because those tvs may scope over the bindings ; oflag <- getOverlapFlag overlap_mode ; return (mkLocalInstance dfun oflag tvs' clas tys') } From git at git.haskell.org Tue Oct 7 12:37:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 12:37:58 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Comments (2c516a3) Message-ID: <20141007123758.8FB7D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/2c516a30894bd6be8b9ec882f2e7d2f25feeac40/ghc >--------------------------------------------------------------- commit 2c516a30894bd6be8b9ec882f2e7d2f25feeac40 Author: Simon Peyton Jones Date: Tue Oct 7 13:37:40 2014 +0100 Comments >--------------------------------------------------------------- 2c516a30894bd6be8b9ec882f2e7d2f25feeac40 compiler/typecheck/TcInteract.lhs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 703facf..4948692 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -902,7 +902,10 @@ equality (b ~ phi) in two cases and can subsequently unify. (2) If the new tyvar appears in the RHS of the inert - AND the inert cannot rewrite the work item + AND the work item is strong enough to rewrite the inert + + AND not (the inert can rewrite the work item) <--------------------------------- + Work item: [G] a ~ b Inert: [W] b ~ [a] Now at this point the work item cannot be further rewritten by the @@ -919,6 +922,8 @@ equality (b ~ phi) in two cases necessarily idemopotent. See Note [Non-idempotent inert substitution] in TcCanonical. + Work item: [G] a ~ Int + Inert: [G] b ~ [a] See also Note [Detailed InertCans Invariants] Note [Avoid double unifications] From git at git.haskell.org Tue Oct 7 13:52:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 13:52:51 +0000 (UTC) Subject: [commit: ghc] master: Remove RAWCPP_FLAGS (460eebe) Message-ID: <20141007135251.754AA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/460eebec65811c6a7bbe11645df322dda868e80d/ghc >--------------------------------------------------------------- commit 460eebec65811c6a7bbe11645df322dda868e80d Author: Thomas Miedema Date: Tue Oct 7 08:47:52 2014 -0500 Remove RAWCPP_FLAGS Summary: #9094 mentions to "remove the RAW_CPP bits from the ghc build system because they're not longer needed", "once the CPP settings ticket is merged #8683" #8683 was merged with 34f7e9a3c99850859901ca74370f55f1d4e2279a, Phab:D26. Test Plan: harbormaster Reviewers: carter, austin Reviewed By: austin Subscribers: simonmar, ezyang, carter Differential Revision: https://phabricator.haskell.org/D240 GHC Trac Issues: #9094 >--------------------------------------------------------------- 460eebec65811c6a7bbe11645df322dda868e80d compiler/ghc.mk | 4 ++-- mk/config.mk.in | 9 --------- rules/manual-package-config.mk | 4 ++-- 3 files changed, 4 insertions(+), 13 deletions(-) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index 0f98960..b5f5dbc 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -263,10 +263,10 @@ compiler_CPP_OPTS += ${GhcCppOpts} define preprocessCompilerFiles # $0 = stage compiler/stage$1/build/Parser.y: compiler/parser/Parser.y.pp - $$(CPP) $$(RAWCPP_FLAGS) -P $$(compiler_CPP_OPTS) -x c $$< | grep -v '^#pragma GCC' > $$@ + $$(CPP) -P $$(compiler_CPP_OPTS) -x c $$< | grep -v '^#pragma GCC' > $$@ compiler/stage$1/build/primops.txt: compiler/prelude/primops.txt.pp compiler/stage$1/$$(PLATFORM_H) - $$(CPP) $$(RAWCPP_FLAGS) -P $$(compiler_CPP_OPTS) -Icompiler/stage$1 -x c $$< | grep -v '^#pragma GCC' > $$@ + $$(CPP) -P $$(compiler_CPP_OPTS) -Icompiler/stage$1 -x c $$< | grep -v '^#pragma GCC' > $$@ compiler/stage$1/build/primop-data-decl.hs-incl: compiler/stage$1/build/primops.txt $$$$(genprimopcode_INPLACE) "$$(genprimopcode_INPLACE)" --data-decl < $$< > $$@ diff --git a/mk/config.mk.in b/mk/config.mk.in index 392237f..4d860ec 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -626,15 +626,6 @@ CP = cp # It's not easy to separate the CPP program from its flags, as # AC_PROG_CPP defines CPP as "/usr/bin/gcc -E" CPP = @CPP@ @CPPFLAGS@ -# -# RAWCPP_FLAGS are the flags to give to cpp (viz, gcc -E) to persuade it to -# behave plausibly on Haskell sources. -# -# Clang in particular is a bit more annoying, so we suppress some warnings. -RAWCPP_FLAGS = -undef -traditional -ifeq "$(CC_CLANG_BACKEND)" "1" -RAWCPP_FLAGS += -Wno-invalid-pp-token -Wno-unicode -Wno-trigraphs -endif FIND = @FindCmd@ diff --git a/rules/manual-package-config.mk b/rules/manual-package-config.mk index 10629aa..56eea70 100644 --- a/rules/manual-package-config.mk +++ b/rules/manual-package-config.mk @@ -16,7 +16,7 @@ $(call trace, manual-package-config($1)) $(call profStart, manual-package-config($1)) $1/dist/package.conf.inplace : $1/package.conf.in $$$$(ghc-pkg_INPLACE) | $$$$(dir $$$$@)/. - $$(CPP) $$(RAWCPP_FLAGS) -P \ + $$(CPP) -P \ -DTOP='"$$(TOP)"' \ $$($1_PACKAGE_CPP_OPTS) \ -x c $$(addprefix -I,$$(GHC_INCLUDE_DIRS)) $$< -o $$@.raw @@ -29,7 +29,7 @@ $1/dist/package.conf.inplace : $1/package.conf.in $$$$(ghc-pkg_INPLACE) | $$$$(d # "make install", so we declare it as phony .PHONY: $1/dist/package.conf.install $1/dist/package.conf.install: | $$$$(dir $$$$@)/. - $$(CPP) $$(RAWCPP_FLAGS) -P \ + $$(CPP) -P \ -DINSTALLING \ -DLIB_DIR='"$$(if $$(filter YES,$$(RelocatableBuild)),$$$$topdir,$$(ghclibdir))"' \ -DINCLUDE_DIR='"$$(if $$(filter YES,$$(RelocatableBuild)),$$$$topdir,$$(ghclibdir))/include"' \ From git at git.haskell.org Tue Oct 7 13:52:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 13:52:54 +0000 (UTC) Subject: [commit: ghc] master: Delete __GLASGOW_HASKELL__ ifdefs for stage0 < 7.6. (b3e5a7b) Message-ID: <20141007135254.26AEA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b3e5a7b50428edc07d11ef4db316c20029f7a3df/ghc >--------------------------------------------------------------- commit b3e5a7b50428edc07d11ef4db316c20029f7a3df Author: Thomas Miedema Date: Tue Oct 7 08:48:06 2014 -0500 Delete __GLASGOW_HASKELL__ ifdefs for stage0 < 7.6. Summary: My understanding is that ghc 7.10 should be buildable with the last 3 versions of ghc, i.e 7.6, 7.8 and 7.10 itself. Test Plan: x Reviewers: austin Reviewed By: austin Subscribers: hvr, simonmar, ezyang, carter, thomie Differential Revision: https://phabricator.haskell.org/D254 >--------------------------------------------------------------- b3e5a7b50428edc07d11ef4db316c20029f7a3df ghc/hschooks.c | 4 ---- libraries/base/tests/enum01.hs | 3 --- libraries/base/tests/enum02.hs | 3 --- libraries/base/tests/enum03.hs | 3 --- libraries/base/tests/list001.hs | 3 --- testsuite/tests/arityanal/Main.hs | 19 ------------------- testsuite/tests/concurrent/should_run/conc024.hs | 3 --- testsuite/tests/concurrent/should_run/conc029.hs | 3 --- testsuite/tests/concurrent/should_run/conc030.hs | 3 --- testsuite/tests/concurrent/should_run/conc034.hs | 4 ---- .../concurrent/should_run/foreignInterruptible.hs | 3 --- testsuite/tests/driver/T2464.hs | 3 --- testsuite/tests/dynlibs/T4464B.c | 4 ---- testsuite/tests/ghci.debugger/HappyTest.hs | 10 ---------- testsuite/tests/numeric/should_run/T7014.hs | 3 --- testsuite/tests/rts/testblockalloc.c | 4 ---- 16 files changed, 75 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 b3e5a7b50428edc07d11ef4db316c20029f7a3df From git at git.haskell.org Tue Oct 7 13:52:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 13:52:56 +0000 (UTC) Subject: [commit: ghc] master: Remove unused hashName declaration (2ee2527) Message-ID: <20141007135256.B00FC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2ee252783b732649f6075b769bd6b964e3823400/ghc >--------------------------------------------------------------- commit 2ee252783b732649f6075b769bd6b964e3823400 Author: Jack Henahan Date: Tue Oct 7 08:48:18 2014 -0500 Remove unused hashName declaration Summary: With the exception of the todo added in 2012, this function has been untouched since 2007. It is not used anywhere else in GHC, so it appears to be safe to remove. The accompanying comment refers to hashExpr, which I couldn't find anywhere in the sources, either. Test Plan: Removed declaration and export. Compiler built succesfully. No test cases exist to fail, and no other module appears to use it. Reviewers: thomie, austin Reviewed By: thomie, austin Subscribers: simonmar, ezyang, carter, thomie Differential Revision: https://phabricator.haskell.org/D261 >--------------------------------------------------------------- 2ee252783b732649f6075b769bd6b964e3823400 compiler/basicTypes/Name.lhs | 7 +------ 1 file changed, 1 insertion(+), 6 deletions(-) diff --git a/compiler/basicTypes/Name.lhs b/compiler/basicTypes/Name.lhs index 0647c60..c4f10fb 100644 --- a/compiler/basicTypes/Name.lhs +++ b/compiler/basicTypes/Name.lhs @@ -49,7 +49,7 @@ module Name ( nameUnique, setNameUnique, nameOccName, nameModule, nameModule_maybe, tidyNameOcc, - hashName, localiseName, + localiseName, mkLocalisedOccName, nameSrcLoc, nameSrcSpan, pprNameDefnLoc, pprDefinedAt, @@ -349,11 +349,6 @@ mkLocalisedOccName this_mod mk_occ name = mk_occ origin (nameOccName name) %************************************************************************ \begin{code} -hashName :: Name -> Int -- ToDo: should really be Word -hashName name = getKey (nameUnique name) + 1 - -- The +1 avoids keys with lots of zeros in the ls bits, which - -- interacts badly with the cheap and cheerful multiplication in - -- hashExpr cmpName :: Name -> Name -> Ordering cmpName n1 n2 = iBox (n_uniq n1) `compare` iBox (n_uniq n2) From git at git.haskell.org Tue Oct 7 13:53:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 13:53:00 +0000 (UTC) Subject: [commit: ghc] master: Add support for LINE pragma in template-haskell (adcb9db) Message-ID: <20141007135300.17AE73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/adcb9dbc0bfb6a7dd3f4f746e2f8cd620745db75/ghc >--------------------------------------------------------------- commit adcb9dbc0bfb6a7dd3f4f746e2f8cd620745db75 Author: Eric Mertens Date: Tue Oct 7 08:48:37 2014 -0500 Add support for LINE pragma in template-haskell Summary: Provide a way to generate {-# LINE #-} pragmas when generating Decs in Template Haskell. This allows more meaningful line numbers to be reported in compile-time errors for dynamically generated code. Test Plan: Run test suite Reviewers: austin, hvr Reviewed By: austin Subscribers: hvr, simonmar, ezyang, carter, thomie Differential Revision: https://phabricator.haskell.org/D299 >--------------------------------------------------------------- adcb9dbc0bfb6a7dd3f4f746e2f8cd620745db75 compiler/hsSyn/Convert.lhs | 97 +++++++++++++--------- docs/users_guide/7.10.1-notes.xml | 3 +- docs/users_guide/glasgow_exts.xml | 5 ++ libraries/template-haskell/Language/Haskell/TH.hs | 1 + .../template-haskell/Language/Haskell/TH/Lib.hs | 3 + .../template-haskell/Language/Haskell/TH/Ppr.hs | 2 + .../template-haskell/Language/Haskell/TH/Syntax.hs | 1 + testsuite/tests/th/TH_linePragma.hs | 11 +++ testsuite/tests/th/TH_linePragma.stderr | 2 + testsuite/tests/th/all.T | 2 + 10 files changed, 87 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 adcb9dbc0bfb6a7dd3f4f746e2f8cd620745db75 From git at git.haskell.org Tue Oct 7 13:53:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 13:53:02 +0000 (UTC) Subject: [commit: ghc] master: Fix configure check for 9439 bug (1ec9113) Message-ID: <20141007135302.A9E053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1ec91133bbdfa018be3d203551818691f1c9e14d/ghc >--------------------------------------------------------------- commit 1ec91133bbdfa018be3d203551818691f1c9e14d Author: Yuras Shumovich Date: Tue Oct 7 08:49:13 2014 -0500 Fix configure check for 9439 bug Summary: We should escape path to ghc.On wondows usually ghc comes from HP, which is installed somewhere in "...\Haskell Platform\..." Note space in the middle. Test Plan: not necessary Reviewers: rwbarton, hvr, austin Reviewed By: rwbarton, hvr, austin Subscribers: rwbarton, simonmar, ezyang, carter, thomie Projects: #ghc Differential Revision: https://phabricator.haskell.org/D304 >--------------------------------------------------------------- 1ec91133bbdfa018be3d203551818691f1c9e14d configure.ac | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/configure.ac b/configure.ac index 7b59f78..f992c0d 100644 --- a/configure.ac +++ b/configure.ac @@ -200,7 +200,7 @@ 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 +"${WithGhc}" conftestghc.hs 2>&1 >/dev/null res=`./conftestghc` if test "x$res" == "x%object" then @@ -217,7 +217,7 @@ 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 +"${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null if test $? == 0 then res=`./conftestghc` From git at git.haskell.org Tue Oct 7 13:53:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 13:53:05 +0000 (UTC) Subject: [commit: ghc] master: configure in base: add msys to windows check (1f92420) Message-ID: <20141007135305.47C793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1f924208b3d85ed115c16f40ad9fc2f729fbb344/ghc >--------------------------------------------------------------- commit 1f924208b3d85ed115c16f40ad9fc2f729fbb344 Author: Yuras Shumovich Date: Tue Oct 7 08:49:25 2014 -0500 configure in base: add msys to windows check Summary: I'm building ghc on windows x86 under msys2, and found that libraries/base/configure isn't able to detect msys as windows platform. I'm not 100% sure it is the right solution. Probably I have local misconfiguration somewhere. So feel free to reject. Test Plan: not necessary Reviewers: austin Reviewed By: austin Subscribers: simonmar, ezyang, carter, thomie Projects: #ghc Differential Revision: https://phabricator.haskell.org/D305 >--------------------------------------------------------------- 1f924208b3d85ed115c16f40ad9fc2f729fbb344 libraries/base/configure.ac | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/configure.ac b/libraries/base/configure.ac index 06e8a5d..4835a2b 100644 --- a/libraries/base/configure.ac +++ b/libraries/base/configure.ac @@ -16,7 +16,7 @@ AC_PROG_CC() AC_MSG_CHECKING(for WINDOWS platform) case $host in - *mingw32*|*mingw64*|*cygwin*) + *mingw32*|*mingw64*|*cygwin*|*msys*) WINDOWS=YES;; *) WINDOWS=NO;; From git at git.haskell.org Tue Oct 7 13:53:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 13:53:07 +0000 (UTC) Subject: [commit: ghc] master: Clean up and remove todo. (9ebbdf3) Message-ID: <20141007135307.D530E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9ebbdf3fa5d0d34d8b42fbd3e79ac2a1cfa9272d/ghc >--------------------------------------------------------------- commit 9ebbdf3fa5d0d34d8b42fbd3e79ac2a1cfa9272d Author: Joel Burget Date: Tue Oct 7 08:51:13 2014 -0500 Clean up and remove todo. Summary: The code is equivalent, just formatted nicely and without the enthusiastic message to clean it up. Test Plan: None Reviewers: austin Reviewed By: austin Subscribers: simonmar, ezyang, carter, thomie Differential Revision: https://phabricator.haskell.org/D307 >--------------------------------------------------------------- 9ebbdf3fa5d0d34d8b42fbd3e79ac2a1cfa9272d compiler/basicTypes/Module.lhs | 2 +- compiler/ghci/ByteCodeLink.lhs | 43 ++++++++++++++++++++++-------------------- 2 files changed, 24 insertions(+), 21 deletions(-) diff --git a/compiler/basicTypes/Module.lhs b/compiler/basicTypes/Module.lhs index d403c87..edd2986 100644 --- a/compiler/basicTypes/Module.lhs +++ b/compiler/basicTypes/Module.lhs @@ -46,7 +46,7 @@ module Module wiredInPackageKeys, -- * The Module type - Module, + Module(Module), modulePackageKey, moduleName, pprModule, mkModule, diff --git a/compiler/ghci/ByteCodeLink.lhs b/compiler/ghci/ByteCodeLink.lhs index af31dc1..9656dfb 100644 --- a/compiler/ghci/ByteCodeLink.lhs +++ b/compiler/ghci/ByteCodeLink.lhs @@ -257,25 +257,28 @@ linkFail who what , " glasgow-haskell-bugs at haskell.org" ]) --- HACKS!!! ToDo: cleaner -nameToCLabel :: Name -> String{-suffix-} -> String -nameToCLabel n suffix - = if pkgid /= mainPackageKey - then package_part ++ '_': qual_name - else qual_name - where - pkgid = modulePackageKey mod - mod = ASSERT( isExternalName n ) nameModule n - package_part = zString (zEncodeFS (packageKeyFS (modulePackageKey mod))) - module_part = zString (zEncodeFS (moduleNameFS (moduleName mod))) - occ_part = zString (zEncodeFS (occNameFS (nameOccName n))) - qual_name = module_part ++ '_':occ_part ++ '_':suffix - - -primopToCLabel :: PrimOp -> String{-suffix-} -> String -primopToCLabel primop suffix - = let str = "ghczmprim_GHCziPrimopWrappers_" ++ zString (zEncodeFS (occNameFS (primOpOcc primop))) ++ '_':suffix - in --trace ("primopToCLabel: " ++ str) - str + +nameToCLabel :: Name -> String -> String +nameToCLabel n suffix = label where + encodeZ = zString . zEncodeFS + (Module pkgKey modName) = ASSERT( isExternalName n ) nameModule n + packagePart = encodeZ (packageKeyFS pkgKey) + modulePart = encodeZ (moduleNameFS modName) + occPart = encodeZ (occNameFS (nameOccName n)) + + label = concat + [ if pkgKey == mainPackageKey then "" else packagePart ++ "_" + , modulePart + , '_':occPart + , '_':suffix + ] + + +primopToCLabel :: PrimOp -> String -> String +primopToCLabel primop suffix = concat + [ "ghczmprim_GHCziPrimopWrappers_" + , zString (zEncodeFS (occNameFS (primOpOcc primop))) + , '_':suffix + ] \end{code} From git at git.haskell.org Tue Oct 7 13:53:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 13:53:10 +0000 (UTC) Subject: [commit: ghc] master: Fix closing parenthesis (205b103) Message-ID: <20141007135310.867B13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/205b103215edfb7597fe009e8a74c11699f048fa/ghc >--------------------------------------------------------------- commit 205b103215edfb7597fe009e8a74c11699f048fa Author: Matt Kraai Date: Tue Oct 7 08:51:30 2014 -0500 Fix closing parenthesis Reviewers: rwbarton, austin Reviewed By: rwbarton, austin Subscribers: rwbarton, thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D309 >--------------------------------------------------------------- 205b103215edfb7597fe009e8a74c11699f048fa driver/ghc.mk | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/driver/ghc.mk b/driver/ghc.mk index c93c611..11db9f7 100644 --- a/driver/ghc.mk +++ b/driver/ghc.mk @@ -10,7 +10,7 @@ # # ----------------------------------------------------------------------------- -$(eval $(call all-target,driver,$(INPLACE_LIB)/ghc-usage.txt) $(INPLACE_LIB)/ghci-usage.txt) +$(eval $(call all-target,driver,$(INPLACE_LIB)/ghc-usage.txt $(INPLACE_LIB)/ghci-usage.txt)) $(INPLACE_LIB)/ghc-usage.txt: driver/ghc-usage.txt cp $< $@ From git at git.haskell.org Tue Oct 7 18:52:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 18:52:47 +0000 (UTC) Subject: [commit: ghc] master: Make scanl fuse; add scanl' (d45693a) Message-ID: <20141007185247.4D7CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d45693a5384460d22a6437b9cda463b4ec4b6a37/ghc >--------------------------------------------------------------- commit d45693a5384460d22a6437b9cda463b4ec4b6a37 Author: David Feuer Date: Tue Oct 7 20:51:25 2014 +0200 Make scanl fuse; add scanl' Summary: Make scanl a good producer and a good consumer for fold/build fusion. Add strictly-accumulating scanl', which is required for Data.List.inits. Reviewers: nomeata, austin Reviewed By: austin Subscribers: spacekitteh, thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D314 GHC Trac Issues: #9356 >--------------------------------------------------------------- d45693a5384460d22a6437b9cda463b4ec4b6a37 libraries/base/GHC/List.lhs | 89 +++++++++++++++++++++++++++++++++++++++++++-- 1 file changed, 85 insertions(+), 4 deletions(-) diff --git a/libraries/base/GHC/List.lhs b/libraries/base/GHC/List.lhs index 51f68ab..6137249 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -22,7 +22,7 @@ module GHC.List ( map, (++), filter, concat, head, last, tail, init, uncons, null, length, (!!), - foldl, scanl, scanl1, foldr, foldr1, scanr, scanr1, + foldl, scanl, scanl1, scanl', foldr, foldr1, scanr, scanr1, iterate, repeat, replicate, cycle, take, drop, splitAt, takeWhile, dropWhile, span, break, reverse, and, or, @@ -200,10 +200,33 @@ foldl k z0 xs = foldr (\(v::a) (fn::b->b) (z::b) -> fn (k z v)) (id :: b -> b) x -- -- > last (scanl f z xs) == foldl f z xs. +-- This peculiar arrangement is necessary to prevent scanl being rewritten in +-- its own right-hand side. +{-# NOINLINE [1] scanl #-} scanl :: (b -> a -> b) -> b -> [a] -> [b] -scanl f q ls = q : (case ls of - [] -> [] - x:xs -> scanl f (f q x) xs) +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) + +-- Note [scanl rewrite rules] +{-# RULES +"scanl" [~1] forall f a bs . scanl f a bs = + build (\c n -> a `c` foldr (scanlFB f c) (constScanl n) bs a) +"scanlList" [1] forall f (a::a) bs . + foldr (scanlFB f (:)) (constScanl []) bs a = tail (scanl f a bs) + #-} + +{-# 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' + +{-# INLINE [0] constScanl #-} +constScanl :: a -> b -> a +constScanl = const + -- | 'scanl1' is a variant of 'scanl' that has no starting value argument: -- @@ -213,6 +236,64 @@ scanl1 :: (a -> a -> a) -> [a] -> [a] scanl1 f (x:xs) = scanl f x xs scanl1 _ [] = [] +-- | 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 `seq` q : (case ls of + [] -> [] + x:xs -> scanlGo' f (f q x) xs) + +-- Note [scanl rewrite rules] +{-# RULES +"scanl'" [~1] forall f a bs . scanl' f a bs = + build (\c n -> a `c` foldr (scanlFB' f c) (flipSeqScanl' n) bs a) +"scanlList'" [1] forall f a bs . + foldr (scanlFB' f (:)) (flipSeqScanl' []) bs a = tail (scanl' f a bs) + #-} + +{-# 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' `seq` b' `c` g b' + +{-# INLINE [0] flipSeqScanl' #-} +flipSeqScanl' :: a -> b -> a +flipSeqScanl' = flip seq + +{- +Note [scanl rewrite rules] +~~~~~~~~~~~~~~~~~~~~~~~~~~ + +In most cases, when we rewrite a form to one that can fuse, we try to rewrite it +back to the original form if it does not fuse. For scanl, we do something a +little different. In particular, we rewrite + +scanl f a bs + +to + +build (\c n -> a `c` foldr (scanlFB f c) (constScanl n) bs a) + +When build is inlined, this becomes + +a : foldr (scanlFB f (:)) (constScanl []) bs a + +To rewrite this form back to scanl, we would need a rule that looked like + +forall f a bs. a : foldr (scanlFB f (:)) (constScanl []) bs a = scanl f a bs + +The problem with this rule is that it has (:) at its head. This would have the +effect of changing the way the inliner looks at (:), not only here but +everywhere. In most cases, this makes no difference, but in some cases it +causes it to come to a different decision about whether to inline something. +Based on nofib benchmarks, this is bad for performance. Therefore, we instead +match on everything past the :, which is just the tail of scanl. +-} + -- foldr, foldr1, scanr, and scanr1 are the right-to-left duals of the -- above functions. From git at git.haskell.org Tue Oct 7 19:25:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 19:25:22 +0000 (UTC) Subject: [commit: ghc] master: Code size micro-optimizations in the X86 backend (bdb0c43) Message-ID: <20141007192522.150BB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bdb0c43c7991da3856e3a89db57c9ea78d61f55f/ghc >--------------------------------------------------------------- commit bdb0c43c7991da3856e3a89db57c9ea78d61f55f Author: Reid Barton Date: Tue Oct 7 09:24:15 2014 -0400 Code size micro-optimizations in the X86 backend Summary: Carter Schonwald suggested looking for opportunities to replace instructions in GHC's output by equivalent ones that are shorter, as recommended by the Intel optimization manuals. This patch reduces the module sizes as reported by nofib by about 1.5% on x86_64. Test Plan: Built an i386 cross-compiler and ran the test suite; the same (rather large) set of tests failed before and after this commit. Will let Harbormaster validate on x86_64. Reviewers: austin Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D320 >--------------------------------------------------------------- bdb0c43c7991da3856e3a89db57c9ea78d61f55f compiler/nativeGen/X86/Ppr.hs | 35 ++++++++++++++++++++++++++++++++++- 1 file changed, 34 insertions(+), 1 deletion(-) diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs index 7f8f296..fcefce3 100644 --- a/compiler/nativeGen/X86/Ppr.hs +++ b/compiler/nativeGen/X86/Ppr.hs @@ -522,6 +522,13 @@ pprInstr (RELOAD slot reg) pprUserReg reg] -} +-- Replace 'mov $0x0,%reg' by 'xor %reg,%reg', which is smaller and cheaper. +-- The code generator catches most of these already, but not all. +pprInstr (MOV size (OpImm (ImmInt 0)) dst@(OpReg _)) + = pprInstr (XOR size' dst dst) + where size' = case size of + II64 -> II32 -- 32-bit version is equivalent, and smaller + _ -> size pprInstr (MOV size src dst) = pprSizeOpOp (sLit "mov") size src dst @@ -582,6 +589,14 @@ pprInstr (SUB_CC size src dst) however, cannot be used to determine if the upper half of the result is non-zero." So there. -} + +-- Use a 32-bit instruction when possible as it saves a byte. +-- Notably, extracting the tag bits of a pointer has this form. +-- TODO: we could save a byte in a subsequent CMP instruction too, +-- but need something like a peephole pass for this +pprInstr (AND II64 src@(OpImm (ImmInteger mask)) dst) + | 0 <= mask && mask < 0xffffffff + = pprInstr (AND II32 src dst) pprInstr (AND size src dst) = pprSizeOpOp (sLit "and") size src dst pprInstr (OR size src dst) = pprSizeOpOp (sLit "or") size src dst @@ -618,7 +633,25 @@ pprInstr (CMP size src dst) is_float FF80 = True is_float _ = False -pprInstr (TEST size src dst) = pprSizeOpOp (sLit "test") size src dst +pprInstr (TEST size src dst) = sdocWithPlatform $ \platform -> + let size' = case (src,dst) of + -- Match instructions like 'test $0x3,%esi' or 'test $0x7,%rbx'. + -- We can replace them by equivalent, but smaller instructions + -- by reducing the size of the immediate operand as far as possible. + -- (We could handle masks larger than a single byte too, + -- but it would complicate the code considerably + -- and tag checks are by far the most common case.) + (OpImm (ImmInteger mask), OpReg dstReg) + | 0 <= mask && mask < 256 -> minSizeOfReg platform dstReg + _ -> size + in pprSizeOpOp (sLit "test") size' src dst + where + minSizeOfReg platform (RegReal (RealRegSingle i)) + | target32Bit platform && i <= 3 = II8 -- al, bl, cl, dl + | target32Bit platform && i <= 7 = II16 -- si, di, bp, sp + | not (target32Bit platform) && i <= 15 = II8 -- al .. r15b + minSizeOfReg _ _ = size -- other + pprInstr (PUSH size op) = pprSizeOp (sLit "push") size op pprInstr (POP size op) = pprSizeOp (sLit "pop") size op From git at git.haskell.org Tue Oct 7 20:54:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 20:54:04 +0000 (UTC) Subject: [commit: ghc] master: testsuite: T5486 requires integer-gmp internals (ffde9d2) Message-ID: <20141007205404.BFBEC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ffde9d21243b73af53e8632776397519cd720aca/ghc >--------------------------------------------------------------- commit ffde9d21243b73af53e8632776397519cd720aca Author: Sergei Trofimovich Date: Tue Oct 7 21:49:19 2014 +0100 testsuite: T5486 requires integer-gmp internals Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- ffde9d21243b73af53e8632776397519cd720aca testsuite/tests/llvm/should_compile/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/llvm/should_compile/all.T b/testsuite/tests/llvm/should_compile/all.T index 5e5ca53..e915419 100644 --- a/testsuite/tests/llvm/should_compile/all.T +++ b/testsuite/tests/llvm/should_compile/all.T @@ -7,7 +7,7 @@ setTestOpts(f) test('T5054', reqlib('hmatrix'), compile, ['-package hmatrix']) test('T5054_2', reqlib('hmatrix'), compile, ['-package hmatrix']) -test('T5486', normal, compile, ['']) +test('T5486', reqlib('integer-gmp'), compile, ['']) test('T5681', normal, compile, ['']) test('T6158', [reqlib('vector'), reqlib('primitive')], compile, ['-package vector -package primitive']) test('T7571', cmm_src, compile, ['']) From git at git.haskell.org Tue Oct 7 21:27:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 21:27:32 +0000 (UTC) Subject: [commit: ghc] master: Bump haddock.base perf numbers (e87135c) Message-ID: <20141007212732.5E2243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e87135cea5975023863a337665696d130ce6feb4/ghc >--------------------------------------------------------------- commit e87135cea5975023863a337665696d130ce6feb4 Author: Reid Barton Date: Tue Oct 7 16:27:41 2014 -0400 Bump haddock.base perf numbers We were so close to the max that the test failed if the pathname to the GHC repository was more than a few dozen characters, causing the haddock.base test to fail on Phab but not locally. >--------------------------------------------------------------- e87135cea5975023863a337665696d130ce6feb4 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 5c8275b..c5a1729 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -5,7 +5,7 @@ test('haddock.base', [unless(in_tree_compiler(), skip) ,stats_num_field('bytes allocated', - [(wordsize(64), 7901230808, 5) + [(wordsize(64), 8322584616, 5) # 2012-08-14: 5920822352 (amd64/Linux) # 2012-09-20: 5829972376 (amd64/Linux) # 2012-10-08: 5902601224 (amd64/Linux) @@ -20,6 +20,7 @@ test('haddock.base', # 2014-08-08: 7946284944 (x86_64/Linux - Haddock updates to attoparsec-0.12.1.0) # 2014-09-09: 8354439016 (x86_64/Linux - Applicative/Monad changes, according to Austin) # 2014-09-10: 7901230808 (x86_64/Linux - Applicative/Monad changes, according to Joachim) + # 2014-10-07: 8322584616 (x86_64/Linux) ,(platform('i386-unknown-mingw32'), 3746792812, 5) # 2013-02-10: 3358693084 (x86/Windows) # 2013-11-13: 3097751052 (x86/Windows, 64bit machine) From git at git.haskell.org Tue Oct 7 22:01:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 7 Oct 2014 22:01:23 +0000 (UTC) Subject: [commit: ghc] master: Use Data.Map.mergeWithKey (6f2eca1) Message-ID: <20141007220123.7D10F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6f2eca11b064c8e888badb8942a8fa4ba0fa7524/ghc >--------------------------------------------------------------- commit 6f2eca11b064c8e888badb8942a8fa4ba0fa7524 Author: Joachim Breitner Date: Tue Oct 7 17:07:36 2014 +0200 Use Data.Map.mergeWithKey Summary: now that we can rely on having containers > 0.5. Reviewers: austin Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D321 >--------------------------------------------------------------- 6f2eca11b064c8e888badb8942a8fa4ba0fa7524 compiler/ghc.cabal.in | 2 +- compiler/utils/UniqFM.lhs | 7 ------- 2 files changed, 1 insertion(+), 8 deletions(-) diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index fc3517a..0932749 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -49,7 +49,7 @@ Library process >= 1 && < 1.3, bytestring >= 0.9 && < 0.11, time < 1.6, - containers >= 0.1 && < 0.6, + containers >= 0.5 && < 0.6, array >= 0.1 && < 0.6, filepath >= 1 && < 1.4, hpc, diff --git a/compiler/utils/UniqFM.lhs b/compiler/utils/UniqFM.lhs index c941ce8..3ea97e4 100644 --- a/compiler/utils/UniqFM.lhs +++ b/compiler/utils/UniqFM.lhs @@ -265,18 +265,11 @@ plusUFM (UFM x) (UFM y) = UFM (M.union y x) plusUFM_C f (UFM x) (UFM y) = UFM (M.unionWith f x y) plusUFM_CD f (UFM xm) dx (UFM ym) dy -{- -The following implementation should be used as soon as we can expect -containers-0.5; presumably from GHC 7.9 on: = UFM $ M.mergeWithKey (\_ x y -> Just (x `f` y)) (M.map (\x -> x `f` dy)) (M.map (\y -> dx `f` y)) xm ym --} - = UFM $ M.intersectionWith f xm ym - `M.union` M.map (\x -> x `f` dy) xm - `M.union` M.map (\y -> dx `f` y) ym minusUFM (UFM x) (UFM y) = UFM (M.difference x y) intersectUFM (UFM x) (UFM y) = UFM (M.intersection x y) intersectUFM_C f (UFM x) (UFM y) = UFM (M.intersectionWith f x y) From git at git.haskell.org Wed Oct 8 05:21:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 8 Oct 2014 05:21:45 +0000 (UTC) Subject: [commit: ghc] master: Initial commit of the Backpack manual [skip ci] (21dff57) Message-ID: <20141008052145.1720E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/21dff57244376131c902501f447e52cad1aaaf74/ghc >--------------------------------------------------------------- commit 21dff57244376131c902501f447e52cad1aaaf74 Author: Edward Z. Yang Date: Tue Oct 7 23:20:33 2014 -0600 Initial commit of the Backpack manual [skip ci] Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 21dff57244376131c902501f447e52cad1aaaf74 docs/backpack/Makefile | 5 + docs/backpack/backpack-manual.tex | 325 ++++++++++++++++++++++++++++++++++++++ 2 files changed, 330 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 21dff57244376131c902501f447e52cad1aaaf74 From git at git.haskell.org Wed Oct 8 05:38:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 8 Oct 2014 05:38:50 +0000 (UTC) Subject: [commit: ghc] master: Update some out-of-date things in Backpack implementation doc [skip ci] (21389bc) Message-ID: <20141008053850.1B7383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/21389bc98568ce0d8d26fd039dea29203c29a663/ghc >--------------------------------------------------------------- commit 21389bc98568ce0d8d26fd039dea29203c29a663 Author: Edward Z. Yang Date: Tue Oct 7 23:38:48 2014 -0600 Update some out-of-date things in Backpack implementation doc [skip ci] Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 21389bc98568ce0d8d26fd039dea29203c29a663 docs/backpack/backpack-impl.tex | 63 +++++++++++++++++++++++------------------ 1 file changed, 36 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 21389bc98568ce0d8d26fd039dea29203c29a663 From git at git.haskell.org Wed Oct 8 06:53:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 8 Oct 2014 06:53:29 +0000 (UTC) Subject: [commit: ghc] master: Make Data.List.takeWhile fuse: fix #9132 (d14d3f9) Message-ID: <20141008065329.AA7B43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d14d3f92d55a352db7faf62939127060716c4694/ghc >--------------------------------------------------------------- commit d14d3f92d55a352db7faf62939127060716c4694 Author: Joachim Breitner Date: Wed Oct 8 08:53:26 2014 +0200 Make Data.List.takeWhile fuse: fix #9132 Summary: Rewrites takeWhile to a build/foldr form; fuses repeated applications of takeWhile. Reviewers: nomeata, austin Reviewed By: nomeata Subscribers: thomie, carter, ezyang, simonmar Projects: #ghc Differential Revision: https://phabricator.haskell.org/D322 GHC Trac Issues: #9132 >--------------------------------------------------------------- d14d3f92d55a352db7faf62939127060716c4694 libraries/base/GHC/List.lhs | 20 ++++++++++++++++++++ 1 file changed, 20 insertions(+) diff --git a/libraries/base/GHC/List.lhs b/libraries/base/GHC/List.lhs index 6137249..7792eed 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -400,12 +400,32 @@ cycle xs = xs' where xs' = xs ++ xs' -- > takeWhile (< 0) [1,2,3] == [] -- +{-# NOINLINE [1] takeWhile #-} takeWhile :: (a -> Bool) -> [a] -> [a] takeWhile _ [] = [] takeWhile p (x:xs) | p x = x : takeWhile p xs | otherwise = [] +{-# INLINE [0] takeWhileFB #-} +takeWhileFB :: (a -> Bool) -> (a -> b -> b) -> b -> a -> b -> b +takeWhileFB p c n = \x r -> if p x then x `c` r else n + +-- The takeWhileFB rule is similar to the filterFB rule. It works like this: +-- takeWhileFB q (takeWhileFB p c n) n = +-- \x r -> if q x then (takeWhileFB p c n) x r else n = +-- \x r -> if q x then (\x' r' -> if p x' then x' `c` r' else n) x r else n = +-- \x r -> if q x then (if p x then x `c` r else n) else n = +-- \x r -> if q x && p x then x `c` r else n = +-- takeWhileFB (\x -> q x && p x) c n +{-# RULES +"takeWhile" [~1] forall p xs. takeWhile p xs = + build (\c n -> foldr (takeWhileFB p c n) n xs) +"takeWhileList" [1] forall p. foldr (takeWhileFB p (:) []) [] = takeWhile p +"takeWhileFB" forall c n p q. takeWhileFB q (takeWhileFB p c n) n = + takeWhileFB (\x -> q x && p x) c n + #-} + -- | 'dropWhile' @p xs@ returns the suffix remaining after 'takeWhile' @p xs@: -- -- > dropWhile (< 3) [1,2,3,4,5,1,2,3] == [3,4,5,1,2,3] From git at git.haskell.org Wed Oct 8 07:41:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 8 Oct 2014 07:41:40 +0000 (UTC) Subject: [commit: ghc] master: Update T4801 perf numbers (eb6b04c) Message-ID: <20141008074140.4F21A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eb6b04c0beaa43581344f1995c3b7bbdcd867ae5/ghc >--------------------------------------------------------------- commit eb6b04c0beaa43581344f1995c3b7bbdcd867ae5 Author: Joachim Breitner Date: Wed Oct 8 09:41:35 2014 +0200 Update T4801 perf numbers >--------------------------------------------------------------- eb6b04c0beaa43581344f1995c3b7bbdcd867ae5 testsuite/tests/perf/compiler/all.T | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index a7783a4..bb6478b 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -171,7 +171,7 @@ test('T4801', # expected value: 58 (amd64/OS X) # 13/01/2014 - 70 (wordsize(32), 30, 20), - (wordsize(64), 55, 20)]), + (wordsize(64), 62, 20)]), # prev: 50 (amd64/Linux) # 19/10/2012: 64 (amd64/Linux) # (^ REASON UNKNOWN!) @@ -180,6 +180,7 @@ test('T4801', # 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?) compiler_stats_num_field('bytes allocated', [(platform('x86_64-apple-darwin'), 464872776, 5), @@ -189,11 +190,12 @@ test('T4801', # prev: 185669232 (x86/OSX) # 2014-01-22: 211198056 (x86/Linux) # 2014-09-03: 185242032 (Windows laptop) - (wordsize(64), 362939272, 10)]), + (wordsize(64), 382056344, 10)]), # prev: 360243576 (amd64/Linux) # 19/10/2012: 447190832 (amd64/Linux) (-fPIC turned on) # 19/10/2012: 392409984 (amd64/Linux) (-fPIC turned off) # 2014-04-08: 362939272 (amd64/Linux) cumulation of various smaller improvements over recent commits + # 2014-10-08: 382056344 (amd64/Linux) stricter foldr2 488e95b ################################### # deactivated for now, as this metric became to volatile recently From git at git.haskell.org Wed Oct 8 08:08:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 8 Oct 2014 08:08:12 +0000 (UTC) Subject: [commit: ghc] master: Preemptive performance number updates (0ed9a27) Message-ID: <20141008080812.6E3183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0ed9a2779a2adf0347088134fdb9f60ae9f2735b/ghc >--------------------------------------------------------------- commit 0ed9a2779a2adf0347088134fdb9f60ae9f2735b Author: Joachim Breitner Date: Wed Oct 8 10:07:39 2014 +0200 Preemptive performance number updates >--------------------------------------------------------------- 0ed9a2779a2adf0347088134fdb9f60ae9f2735b testsuite/tests/perf/compiler/all.T | 9 ++++++--- testsuite/tests/perf/haddock/all.T | 3 ++- 2 files changed, 8 insertions(+), 4 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index bb6478b..1afcf88 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -404,7 +404,7 @@ test('T5321FD', # (increase due to new codegen) # 2014-07-31: 211699816 (Windows) (-11%) # (due to better optCoercion, 5e7406d9, #9233) - (wordsize(64), 426960992, 10)]) + (wordsize(64), 410895536, 10)]) # prev: 418306336 # 29/08/2012: 492905640 # (increase due to new codegen) @@ -416,6 +416,8 @@ test('T5321FD', # (with -8%, still in range, hence cause not known) # 2014-07-17: 426960992 (-11% of previous value) # (due to better optCoercion, 5e7406d9, #9233) + # 2014-10-08 410895536 + # (various changes; biggest improvements due to 949ad67 and FastString package ids) ], compile,['']) @@ -446,14 +448,15 @@ 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), 73639840, 10)]) + (wordsize(64), 75765728, 10)]) # sample: 3926235424 (amd64/Linux, 15/2/2012) # 2012-10-02 81879216 # 2012-09-20 87254264 amd64/Linux # 2013-09-18 90587232 amd64/Linux # 2013-11-21 86795752 amd64/Linux, GND via Coercible and counters # for constraints solving - # 2041-08-29 73639840 amd64/Linux, w/w for INLINABLE things + # 2014-08-29 73639840 amd64/Linux, w/w for INLINABLE things + # 2014-10-08 73639840 amd64/Linux, Burning Bridges and other small changes ], compile_fail,['-ftype-function-depth=50']) diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index c5a1729..f95b782 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -41,7 +41,7 @@ test('haddock.base', test('haddock.Cabal', [unless(in_tree_compiler(), skip) ,stats_num_field('bytes allocated', - [(wordsize(64), 5840893376, 5) + [(wordsize(64), 6019839624, 5) # 2012-08-14: 3255435248 (amd64/Linux) # 2012-08-29: 3324606664 (amd64/Linux, new codegen) # 2012-10-08: 3373401360 (amd64/Linux) @@ -58,6 +58,7 @@ test('haddock.Cabal', # 2014-09-09: 4660249216 (x86_64/Linux - Applicative/Monad changes according to Austin) # 2014-09-10: 4500376192 (x86_64/Linux - Applicative/Monad changes according to Joachim) # 2014-09-24: 5840893376 (x86_64/Linux - Cabal update) + # 2014-10-04: 6019839624 (x86_64/Linux - Burning Bridges, Cabal update) ,(platform('i386-unknown-mingw32'), 2052220292, 5) # 2012-10-30: 1733638168 (x86/Windows) From git at git.haskell.org Wed Oct 8 12:57:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 8 Oct 2014 12:57:26 +0000 (UTC) Subject: [commit: ghc] master: Make the linker more robust to errors (5300099) Message-ID: <20141008125726.E915E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5300099edf106c1f5938c0793bd6ca199a0eebf0/ghc >--------------------------------------------------------------- commit 5300099edf106c1f5938c0793bd6ca199a0eebf0 Author: Simon Marlow Date: Wed Oct 1 13:15:05 2014 +0100 Make the linker more robust to errors Summary: When linking fails because there was a problem with the supplied object file, then we should not barf() or exit, we should emit a suitable error message and return an error code to the caller. We should also free all memory that might have been allocated during linking, and generally not do any damage. This patch fixes most common instances of this problem. Test Plan: validate Reviewers: rwbarton, austin, ezyang Reviewed By: ezyang Subscribers: simonmar, ezyang, carter, thomie Differential Revision: https://phabricator.haskell.org/D294 >--------------------------------------------------------------- 5300099edf106c1f5938c0793bd6ca199a0eebf0 includes/rts/Linker.h | 2 +- rts/Linker.c | 380 +++++++++++++++++++++++------------- testsuite/tests/rts/Makefile | 50 ++++- testsuite/tests/rts/all.T | 17 ++ testsuite/tests/rts/linker_error.c | 66 +++++++ testsuite/tests/rts/linker_error2.c | 6 + testsuite/tests/rts/linker_error3.c | 6 + testsuite/tests/rts/linker_unload.c | 4 +- 8 files changed, 388 insertions(+), 143 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 5300099edf106c1f5938c0793bd6ca199a0eebf0 From git at git.haskell.org Wed Oct 8 20:14:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 8 Oct 2014 20:14:22 +0000 (UTC) Subject: [commit: ghc] branch 'wip/tc-plugins' created Message-ID: <20141008201422.600653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/tc-plugins Referencing: 1dcdde11f6a697d4c528a8adbe11fac65a8982e2 From git at git.haskell.org Wed Oct 8 20:14:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 8 Oct 2014 20:14:25 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Make some hooks for external plugins to the type-checker. (7166ae2) Message-ID: <20141008201425.0CC2C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/7166ae25c5303f68505779038dd524093dee2e82/ghc >--------------------------------------------------------------- commit 7166ae25c5303f68505779038dd524093dee2e82 Author: Iavor S. Diatchki Date: Tue Oct 7 17:28:48 2014 -0700 Make some hooks for external plugins to the type-checker. >--------------------------------------------------------------- 7166ae25c5303f68505779038dd524093dee2e82 compiler/main/DynFlags.hs | 20 +++++++++----- compiler/prelude/PrelNames.lhs | 9 ++++++- compiler/simplCore/SimplCore.lhs | 3 ++- compiler/typecheck/TcRnDriver.lhs | 57 ++++++++++++++++++++++++++++++++++++--- compiler/typecheck/TcRnMonad.lhs | 20 +++++++++++--- compiler/typecheck/TcRnTypes.lhs | 30 +++++++++++++++++++-- 6 files changed, 122 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 7166ae25c5303f68505779038dd524093dee2e82 From git at git.haskell.org Wed Oct 8 20:14:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 8 Oct 2014 20:14:27 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Redo the methods of `TcPlugin`. (1dcdde1) Message-ID: <20141008201427.C39443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/1dcdde11f6a697d4c528a8adbe11fac65a8982e2/ghc >--------------------------------------------------------------- commit 1dcdde11f6a697d4c528a8adbe11fac65a8982e2 Author: Iavor S. Diatchki Date: Wed Oct 8 13:13:35 2014 -0700 Redo the methods of `TcPlugin`. >--------------------------------------------------------------- 1dcdde11f6a697d4c528a8adbe11fac65a8982e2 compiler/typecheck/TcRnTypes.lhs | 25 ++++++++++++++++++++++--- 1 file changed, 22 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index 95efad9..4e85ba3 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -75,7 +75,7 @@ module TcRnTypes( canRewrite, canRewriteOrSame, -- Constraint solver plugins - TcPlugin(..), TcSolveResult(..), + TcPlugin(..), TcPluginResult(..), -- Pretty printing pprEvVarTheta, pprWantedsWithLocs, @@ -1935,11 +1935,30 @@ Constraint Solver Plugins \begin{code} data TcPlugin = TcPlugin - { tcPluginSolve :: [Ct] -> [Ct] -> IO ([TcSolveResult], [Ct]) + { tcPluginSolve :: [Ct] -> [Ct] -> IO TcPluginResult , tcPluginStop :: IO () + -- ^ Exit the solver. + -- The solver should not be used after this is called. } -data TcSolveResult = Stuck | Impossible | Simplified EvTerm + +data TcPluginResult + = TcPluginContradiction {- inconsistent -} [Ct] + {- all others -} [Ct] + {- ^ There is no model for the constraints. + The two lists partition the original constraints, + with the first one being the conflicting constraints, + and the second the other constraints. -} + + | TcPluginNewWork [Ct] + -- ^ New work (facts that will hold in all models) + + | TcPluginSolved {- solved -} [(EvTerm,Ct)] + {- not solved -} [Ct] + -- ^ We managed to solve some of the constrints. + -- The solved constraints (with evidence) are in the first list. + -- The unsolved constraints are in the second one. + \end{code} From git at git.haskell.org Thu Oct 9 07:38:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 07:38:16 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: arclint: Don't complain about tabs unless it's inside the diff. (077b553) Message-ID: <20141009073816.867373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/077b5533128914d25f87ba15ac3db1a98e3d749c/ghc >--------------------------------------------------------------- commit 077b5533128914d25f87ba15ac3db1a98e3d749c Author: Edward Z. Yang Date: Thu Oct 2 15:01:47 2014 -0700 arclint: Don't complain about tabs unless it's inside the diff. Summary: Signed-off-by: Edward Z. Yang Test Plan: none Reviewers: austin Subscribers: simonmar, ezyang, carter, thomie Differential Revision: https://phabricator.haskell.org/D303 >--------------------------------------------------------------- 077b5533128914d25f87ba15ac3db1a98e3d749c .arclint | 16 ++++++++++++---- 1 file changed, 12 insertions(+), 4 deletions(-) diff --git a/.arclint b/.arclint index f798015..1310973 100644 --- a/.arclint +++ b/.arclint @@ -16,25 +16,33 @@ "type": "text", "include": ["(\\.(l?hs(-boot)?|x|y\\.pp)(\\.in)?$)"], "severity": { - "5": "disabled" + "5": "disabled", + "2": "warning" } }, "c": { "type": "text", - "include": ["(\\.(c|h)(\\.in)?$)"] + "include": ["(\\.(c|h)(\\.in)?$)"], + "severity": { + "2": "warning" + } }, "text-xml": { "type": "text", "include": "(\\.xml$)", "severity": { "5": "disabled", - "3": "disabled" + "3": "disabled", + "2": "warning" } }, "shell": { "type": "text", "include": [ "(\\.sh$)" ], - "text.max-line-length": 200 + "text.max-line-length": 200, + "severity": { + "2": "warning" + } }, "makefiles": { "type": "text", From git at git.haskell.org Thu Oct 9 07:38:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 07:38:19 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Comments only (instances for Proxy are lazy) (97e8f38) Message-ID: <20141009073819.493353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/97e8f38bc88541f98481319ebc1c2569011e2ff4/ghc >--------------------------------------------------------------- commit 97e8f38bc88541f98481319ebc1c2569011e2ff4 Author: Reid Barton Date: Fri Oct 3 09:02:45 2014 -0400 Comments only (instances for Proxy are lazy) >--------------------------------------------------------------- 97e8f38bc88541f98481319ebc1c2569011e2ff4 libraries/base/Data/Proxy.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/libraries/base/Data/Proxy.hs b/libraries/base/Data/Proxy.hs index 38a43b0..3ead549 100644 --- a/libraries/base/Data/Proxy.hs +++ b/libraries/base/Data/Proxy.hs @@ -34,6 +34,10 @@ data Proxy t = Proxy -- There are no instances for this because it is intended at the kind level only data KProxy (t :: *) = KProxy +-- It's common to use (undefined :: Proxy t) and (Proxy :: Proxy t) +-- interchangeably, so all of these instances are hand-written to be +-- lazy in Proxy arguments. + instance Eq (Proxy s) where _ == _ = True From git at git.haskell.org Thu Oct 9 07:38:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 07:38:21 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Revert "Basic Python 3 support for testsuite driver (Trac #9184)" (542b9c3) Message-ID: <20141009073821.DB0F73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/542b9c3589e803c101398621e516a7bba424a90e/ghc >--------------------------------------------------------------- commit 542b9c3589e803c101398621e516a7bba424a90e Author: Krzysztof Gogolewski Date: Fri Oct 3 19:18:38 2014 +0200 Revert "Basic Python 3 support for testsuite driver (Trac #9184)" This reverts commit 084d241b316bfa12e41fc34cae993ca276bf0730. This is a possible culprit of Windows breakage reported at ghc-devs. >--------------------------------------------------------------- 542b9c3589e803c101398621e516a7bba424a90e testsuite/config/ghc | 22 ++-- testsuite/driver/runtests.py | 67 +++++------ testsuite/driver/testlib.py | 185 +++++++++++++++-------------- testsuite/driver/testutil.py | 34 ++++++ testsuite/tests/ffi/should_run/all.T | 10 +- testsuite/tests/ghci/prog004/prog004.T | 4 +- testsuite/tests/numeric/should_run/all.T | 8 +- testsuite/tests/perf/compiler/all.T | 2 +- testsuite/tests/plugins/all.T | 4 +- testsuite/tests/th/TH_spliceViewPat/test.T | 6 +- testsuite/tests/th/all.T | 6 +- testsuite/tests/typecheck/should_run/all.T | 4 +- testsuite/timeout/calibrate | 2 +- testsuite/timeout/timeout.py | 2 +- utils/fingerprint/fingerprint.py | 8 +- 15 files changed, 195 insertions(+), 169 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 542b9c3589e803c101398621e516a7bba424a90e From git at git.haskell.org Thu Oct 9 07:38:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 07:38:24 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Restore spaces instead of tabs, caused by revert of Python 3 (474d320) Message-ID: <20141009073824.923143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/474d3201f902eef99c8d283996eacf3457365cfe/ghc >--------------------------------------------------------------- commit 474d3201f902eef99c8d283996eacf3457365cfe Author: Krzysztof Gogolewski Date: Fri Oct 3 19:56:00 2014 +0200 Restore spaces instead of tabs, caused by revert of Python 3 The git hook does not allow to reinsert tabs. >--------------------------------------------------------------- 474d3201f902eef99c8d283996eacf3457365cfe testsuite/tests/ghci/prog004/prog004.T | 4 ++-- testsuite/tests/plugins/all.T | 4 ++-- testsuite/tests/th/TH_spliceViewPat/test.T | 6 +++--- 3 files changed, 7 insertions(+), 7 deletions(-) diff --git a/testsuite/tests/ghci/prog004/prog004.T b/testsuite/tests/ghci/prog004/prog004.T index ed17afd..4b6ee13 100644 --- a/testsuite/tests/ghci/prog004/prog004.T +++ b/testsuite/tests/ghci/prog004/prog004.T @@ -1,8 +1,8 @@ setTestOpts(only_compiler_types(['ghc'])) def f(name, opts): - if not ('ghci' in config.run_ways): - opts.skip = 1 + if not ('ghci' in config.run_ways): + opts.skip = 1 setTestOpts(f) test('ghciprog004', diff --git a/testsuite/tests/plugins/all.T b/testsuite/tests/plugins/all.T index 7e5f9b4..8b2256a 100644 --- a/testsuite/tests/plugins/all.T +++ b/testsuite/tests/plugins/all.T @@ -1,6 +1,6 @@ def f(name, opts): - if (ghc_with_interpreter == 0): - opts.skip = 1 + if (ghc_with_interpreter == 0): + opts.skip = 1 setTestOpts(f) setTestOpts(when(compiler_lt('ghc', '7.1'), skip)) diff --git a/testsuite/tests/th/TH_spliceViewPat/test.T b/testsuite/tests/th/TH_spliceViewPat/test.T index c08e7cb..21fdff3 100644 --- a/testsuite/tests/th/TH_spliceViewPat/test.T +++ b/testsuite/tests/th/TH_spliceViewPat/test.T @@ -1,7 +1,7 @@ def f(name, opts): - opts.extra_hc_opts = '-XTemplateHaskell -package template-haskell' - if (ghc_with_interpreter == 0): - opts.skip = 1 + opts.extra_hc_opts = '-XTemplateHaskell -package template-haskell' + if (ghc_with_interpreter == 0): + opts.skip = 1 setTestOpts(f) setTestOpts(only_compiler_types(['ghc'])) From git at git.haskell.org Thu Oct 9 07:38:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 07:38:27 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Check for staticclosures section in Windows linker. (9b5d230) Message-ID: <20141009073827.4162E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/9b5d230275afea084c35aa50bc010e259d50eb7c/ghc >--------------------------------------------------------------- commit 9b5d230275afea084c35aa50bc010e259d50eb7c Author: Edward Z. Yang Date: Fri Oct 3 14:12:51 2014 -0700 Check for staticclosures section in Windows linker. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 9b5d230275afea084c35aa50bc010e259d50eb7c rts/Linker.c | 1 + 1 file changed, 1 insertion(+) diff --git a/rts/Linker.c b/rts/Linker.c index 9897557..97b64ea 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -4163,6 +4163,7 @@ ocGetNames_PEi386 ( ObjectCode* oc ) 0==strcmp(".rodata",(char*)secname)) kind = SECTIONKIND_CODE_OR_RODATA; if (0==strcmp(".data",(char*)secname) || + 0==strcmp(".staticclosures",(char*)secname) || 0==strcmp(".bss",(char*)secname)) kind = SECTIONKIND_RWDATA; if (0==strcmp(".ctors", (char*)secname)) From git at git.haskell.org Thu Oct 9 07:38:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 07:38:29 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Fix typo in section name: no leading period. (39a3adf6) Message-ID: <20141009073829.DD8143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/39a3adf6fe6ebcf49c685f7ee3de92a1348280f8/ghc >--------------------------------------------------------------- commit 39a3adf6fe6ebcf49c685f7ee3de92a1348280f8 Author: Edward Z. Yang Date: Fri Oct 3 15:05:50 2014 -0700 Fix typo in section name: no leading period. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 39a3adf6fe6ebcf49c685f7ee3de92a1348280f8 rts/Linker.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/Linker.c b/rts/Linker.c index 97b64ea..e74d647 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -4163,7 +4163,7 @@ ocGetNames_PEi386 ( ObjectCode* oc ) 0==strcmp(".rodata",(char*)secname)) kind = SECTIONKIND_CODE_OR_RODATA; if (0==strcmp(".data",(char*)secname) || - 0==strcmp(".staticclosures",(char*)secname) || + 0==strcmp("staticclosures",(char*)secname) || 0==strcmp(".bss",(char*)secname)) kind = SECTIONKIND_RWDATA; if (0==strcmp(".ctors", (char*)secname)) From git at git.haskell.org Thu Oct 9 07:38:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 07:38:32 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: ghc.mk: fix list for dll-split on GHCi-less builds (db8ebc1) Message-ID: <20141009073832.8F21C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/db8ebc11955bf66760d40e942e49732f1eef9ab2/ghc >--------------------------------------------------------------- commit db8ebc11955bf66760d40e942e49732f1eef9ab2 Author: Sergei Trofimovich Date: Sat Oct 4 20:48:22 2014 +0100 ghc.mk: fix list for dll-split on GHCi-less builds To reproduce build failure it's enough to try to build GHC on amd64 with the following setup: $ cat mk/build.mk # for #9552 GhcWithInterpreter = NO It gives: Reachable modules from DynFlags out of date Please fix compiler/ghc.mk, or building DLLs on Windows may break (#7780) Redundant modules: Bitmap BlockId ... dll-split among other things makes sure all mentioned modules are used by DynFlags. '#ifdef GHCI' keeps is from happening. Patch moves those 42 modules under 'GhcWithInterpreter' guard. Fixes Issue #9552 Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- db8ebc11955bf66760d40e942e49732f1eef9ab2 compiler/ghc.mk | 90 ++++++++++++++++++++++++++++++--------------------------- 1 file changed, 48 insertions(+), 42 deletions(-) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index 05c935f..8e00149 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -467,36 +467,15 @@ compiler_stage2_dll0_MODULES = \ BasicTypes \ BinIface \ Binary \ - Bitmap \ - BlockId \ BooleanFormula \ BreakArray \ BufWrite \ BuildTyCl \ - ByteCodeAsm \ - ByteCodeInstr \ - ByteCodeItbls \ - CLabel \ Class \ CmdLineParser \ - Cmm \ - CmmCallConv \ - CmmExpr \ - CmmInfo \ - CmmMachOp \ - CmmNode \ CmmType \ - CmmUtils \ CoAxiom \ ConLike \ - CodeGen.Platform \ - CodeGen.Platform.ARM \ - CodeGen.Platform.NoRegs \ - CodeGen.Platform.PPC \ - CodeGen.Platform.PPC_Darwin \ - CodeGen.Platform.SPARC \ - CodeGen.Platform.X86 \ - CodeGen.Platform.X86_64 \ Coercion \ Config \ Constants \ @@ -520,7 +499,6 @@ compiler_stage2_dll0_MODULES = \ Exception \ ExtsCompat46 \ FamInstEnv \ - FastBool \ FastFunctions \ FastMutInt \ FastString \ @@ -530,8 +508,6 @@ compiler_stage2_dll0_MODULES = \ FiniteMap \ ForeignCall \ Hooks \ - Hoopl \ - Hoopl.Dataflow \ HsBinds \ HsDecls \ HsDoc \ @@ -551,14 +527,12 @@ compiler_stage2_dll0_MODULES = \ IfaceSyn \ IfaceType \ InstEnv \ - InteractiveEvalTypes \ Kind \ ListSetOps \ Literal \ LoadIface \ Maybes \ MkCore \ - MkGraph \ MkId \ Module \ MonadUtils \ @@ -578,9 +552,6 @@ compiler_stage2_dll0_MODULES = \ PipelineMonad \ Platform \ PlatformConstants \ - PprCmm \ - PprCmmDecl \ - PprCmmExpr \ PprCore \ PrelInfo \ PrelNames \ @@ -588,23 +559,10 @@ compiler_stage2_dll0_MODULES = \ Pretty \ PrimOp \ RdrName \ - Reg \ - RegClass \ Rules \ - SMRep \ Serialized \ SrcLoc \ StaticFlags \ - StgCmmArgRep \ - StgCmmClosure \ - StgCmmEnv \ - StgCmmLayout \ - StgCmmMonad \ - StgCmmProf \ - StgCmmTicky \ - StgCmmUtils \ - StgSyn \ - Stream \ StringBuffer \ TcEvidence \ TcIface \ @@ -628,6 +586,54 @@ compiler_stage2_dll0_MODULES = \ VarEnv \ VarSet +ifeq "$(GhcWithInterpreter)" "YES" +# These files are reacheable from DynFlags +# only by GHCi-enabled code (see #9552) +compiler_stage2_dll0_MODULES += \ + Bitmap \ + BlockId \ + ByteCodeAsm \ + ByteCodeInstr \ + ByteCodeItbls \ + CLabel \ + Cmm \ + CmmCallConv \ + CmmExpr \ + CmmInfo \ + CmmMachOp \ + CmmNode \ + CmmUtils \ + CodeGen.Platform \ + CodeGen.Platform.ARM \ + CodeGen.Platform.NoRegs \ + CodeGen.Platform.PPC \ + CodeGen.Platform.PPC_Darwin \ + CodeGen.Platform.SPARC \ + CodeGen.Platform.X86 \ + CodeGen.Platform.X86_64 \ + FastBool \ + Hoopl \ + Hoopl.Dataflow \ + InteractiveEvalTypes \ + MkGraph \ + PprCmm \ + PprCmmDecl \ + PprCmmExpr \ + Reg \ + RegClass \ + SMRep \ + StgCmmArgRep \ + StgCmmClosure \ + StgCmmEnv \ + StgCmmLayout \ + StgCmmMonad \ + StgCmmProf \ + StgCmmTicky \ + StgCmmUtils \ + StgSyn \ + Stream +endif + compiler_stage2_dll0_HS_OBJS = \ $(patsubst %,compiler/stage2/build/%.$(dyn_osuf),$(subst .,/,$(compiler_stage2_dll0_MODULES))) From git at git.haskell.org Thu Oct 9 07:38:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 07:38:35 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Implement `MIN_VERSION_GLASGOW_HASKELL()` macro (3bac93c) Message-ID: <20141009073835.49BCE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/3bac93cdcac55b498ba57029d5c006d15e319c6e/ghc >--------------------------------------------------------------- commit 3bac93cdcac55b498ba57029d5c006d15e319c6e Author: Herbert Valerio Riedel Date: Sun Oct 5 22:35:22 2014 +0200 Implement `MIN_VERSION_GLASGOW_HASKELL()` macro This exposes the `cProjectPatchLevel{1,2}` value at the CPP level to allow it to be used in CPP conditionals. Concretely, GHC 7.10.2.20150623 would result in #define __GLASGOW_HASKELL__ 710 #define __GLASGOW_HASKELL_PATCHLEVEL1__ 2 #define __GLASGOW_HASKELL_PATCHLEVEL2__ 20150623 while GHC 7.10.3 results in #define __GLASGOW_HASKELL__ 710 #define __GLASGOW_HASKELL_PATCHLEVEL1__ 3 and finally GHC 7.9.20141009 results in #define __GLASGOW_HASKELL__ 709 #define __GLASGOW_HASKELL_PATCHLEVEL1__ 20141009 As it's error-prone to properly express CPP conditionals for testing GHC multi-component versions, a new macro `MIN_VERSION_GLASGOW_HASKELL()` is provided (also via the new CPP include file `ghcversion.h`) Finally, in order to make it easier to define the new CPP macro `MIN_VERSION_GLASGOW_HASKELL()`, a new default-included `include/ghcversion.h` is used for the new CPP definitions. Reviewed By: ekmett, austin, #ghc Differential Revision: https://phabricator.haskell.org/D66 >--------------------------------------------------------------- 3bac93cdcac55b498ba57029d5c006d15e319c6e .gitignore | 1 + aclocal.m4 | 7 ++++ compiler/ghc.mk | 4 +++ compiler/main/DriverPipeline.hs | 28 +++++++++++---- docs/users_guide/phases.xml | 79 +++++++++++++++++++++++++++++++++++++++++ ghc.mk | 1 + includes/ghc.mk | 39 +++++++++++++++++--- mk/project.mk.in | 2 ++ 8 files changed, 150 insertions(+), 11 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 3bac93cdcac55b498ba57029d5c006d15e319c6e From git at git.haskell.org Thu Oct 9 07:38:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 07:38:37 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: rts: unrust 'libbfd' debug symbols parser (2085656) Message-ID: <20141009073837.E0BAE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/208565692ef402f48dc219028818608c9795f82a/ghc >--------------------------------------------------------------- commit 208565692ef402f48dc219028818608c9795f82a Author: Sergei Trofimovich Date: Sun Oct 5 21:20:39 2014 +0100 rts: unrust 'libbfd' debug symbols parser Summary: Patch does the following: - fixes detection of working libbfd on modern linux platforms (where bfd_uncompress_section_contents is a macro) - disables 'bfd' by default and adds '--enable-bfd-debug' configure option. As bfd's ABI is unstable the feature is primarily useful by ghc hackers. Not done (subject for another patch): - one-time bfd object memory leak in DEBUG_LoadSymbols - in '-dynamic' mode debugging symbols are loaded only for current executable, not all libraries it is linked against. Fixes Issue #8790 Signed-off-by: Sergei Trofimovich Test Plan: built unregisterised ghc on amd64 and ran './hello +RTS -Di' there Reviewers: simonmar, austin Reviewed By: simonmar, austin Subscribers: thomie, simonmar, ezyang, carter Differential Revision: https://phabricator.haskell.org/D193 GHC Trac Issues: #8790 >--------------------------------------------------------------- 208565692ef402f48dc219028818608c9795f82a aclocal.m4 | 49 +++++++++++++++++++++++++++++++++++++++++++++++++ configure.ac | 7 ++----- rts/Printer.c | 15 ++++++++++++--- rts/RtsStartup.c | 6 ++++++ 4 files changed, 69 insertions(+), 8 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index a98691e..0db231d 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2215,4 +2215,53 @@ $2=$HS_CPP_ARGS ]) +# FP_BFD_SUPPORT() +# ---------------------- +# whether to use libbfd for debugging RTS +AC_DEFUN([FP_BFD_SUPPORT], [ + AC_ARG_ENABLE(bfd-debug, + [AC_HELP_STRING([--enable-bfd-debug], + [Enable symbol resolution for -debug rts ('+RTS -Di') via binutils' libbfd [default=no]])], + [ + # don't pollute general LIBS environment + save_LIBS="$LIBS" + AC_CHECK_HEADERS([bfd.h]) + dnl ** check whether this machine has BFD and libiberty installed (used for debugging) + dnl the order of these tests matters: bfd needs libiberty + AC_CHECK_LIB(iberty, xmalloc) + dnl 'bfd_init' is a rare non-macro in libbfd + AC_CHECK_LIB(bfd, bfd_init) + + AC_TRY_LINK([#include ], + [ + /* mimic our rts/Printer.c */ + bfd* abfd; + const char * name; + char **matching; + + name = "some.executable"; + bfd_init(); + abfd = bfd_openr(name, "default"); + bfd_check_format_matches (abfd, bfd_object, &matching); + { + long storage_needed; + storage_needed = bfd_get_symtab_upper_bound (abfd); + } + { + asymbol **symbol_table; + long number_of_symbols; + symbol_info info; + + number_of_symbols = bfd_canonicalize_symtab (abfd, symbol_table); + bfd_get_symbol_info(abfd,symbol_table[0],&info); + } + ], + [],dnl bfd seems to work + [AC_MSG_ERROR([can't use 'bfd' library])]) + LIBS="$save_LIBS" + ], + [] + ) +]) + # LocalWords: fi diff --git a/configure.ac b/configure.ac index e7a0774..7b59f78 100644 --- a/configure.ac +++ b/configure.ac @@ -753,7 +753,7 @@ dnl off_t, because it will affect the result of that test. AC_SYS_LARGEFILE dnl ** check for specific header (.h) files that we are interested in -AC_CHECK_HEADERS([bfd.h ctype.h dirent.h dlfcn.h errno.h fcntl.h grp.h limits.h locale.h nlist.h pthread.h pwd.h signal.h sys/param.h sys/mman.h sys/resource.h sys/select.h sys/time.h sys/timeb.h sys/timers.h sys/times.h sys/utsname.h sys/wait.h termios.h time.h utime.h windows.h winsock.h sched.h]) +AC_CHECK_HEADERS([ctype.h dirent.h dlfcn.h errno.h fcntl.h grp.h limits.h locale.h nlist.h pthread.h pwd.h signal.h sys/param.h sys/mman.h sys/resource.h sys/select.h sys/time.h sys/timeb.h sys/timers.h sys/times.h sys/utsname.h sys/wait.h termios.h time.h utime.h windows.h winsock.h sched.h]) dnl sys/cpuset.h needs sys/param.h to be included first on FreeBSD 9.1; #7708 AC_CHECK_HEADERS([sys/cpuset.h], [], [], @@ -846,10 +846,7 @@ then AC_DEFINE([HAVE_LIBM], [1], [Define to 1 if you need to link with libm]) fi -dnl ** check whether this machine has BFD and libiberty installed (used for debugging) -dnl the order of these tests matters: bfd needs libiberty -AC_CHECK_LIB(iberty, xmalloc) -AC_CHECK_LIB(bfd, bfd_uncompress_section_contents) +FP_BFD_SUPPORT dnl ################################################################ dnl Check for libraries diff --git a/rts/Printer.c b/rts/Printer.c index 3d77e83..9bc2984 100644 --- a/rts/Printer.c +++ b/rts/Printer.c @@ -7,6 +7,8 @@ * ---------------------------------------------------------------------------*/ #include "PosixSource.h" +#include "ghcconfig.h" + #include "Rts.h" #include "rts/Bytecodes.h" /* for InstrPtr */ @@ -664,8 +666,16 @@ const char *lookupGHCName( void *addr ) disabling this for now. */ #ifdef USING_LIBBFD - -#include +# define PACKAGE 1 +# define PACKAGE_VERSION 1 +/* Those PACKAGE_* defines are workarounds for bfd: + * https://sourceware.org/bugzilla/show_bug.cgi?id=14243 + * ghc's build system filter PACKAGE_* values out specifically to avoid clashes + * with user's autoconf-based Cabal packages. + * It's a shame checks for unrelated fields instead of actually used + * macros. + */ +# include /* Fairly ad-hoc piece of code that seems to filter out a lot of * rubbish like the obj-splitting symbols @@ -733,7 +743,6 @@ extern void DEBUG_LoadSymbols( char *name ) for( i = 0; i != number_of_symbols; ++i ) { symbol_info info; bfd_get_symbol_info(abfd,symbol_table[i],&info); - /*debugBelch("\t%c\t0x%x \t%s\n",info.type,(nat)info.value,info.name); */ if (isReal(info.type, info.name)) { num_real_syms += 1; } diff --git a/rts/RtsStartup.c b/rts/RtsStartup.c index 98a43c0..5e6f9fa 100644 --- a/rts/RtsStartup.c +++ b/rts/RtsStartup.c @@ -19,6 +19,7 @@ #include "RtsFlags.h" #include "RtsUtils.h" #include "Prelude.h" +#include "Printer.h" /* DEBUG_LoadSymbols */ #include "Schedule.h" /* initScheduler */ #include "Stats.h" /* initStats */ #include "STM.h" /* initSTM */ @@ -162,6 +163,11 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config) rts_config.rts_opts_enabled, rts_config.rts_opts, rts_config.rts_hs_main); } +#ifdef DEBUG + /* load debugging symbols for current binary */ + DEBUG_LoadSymbols((*argv)[0]); +#endif /* DEBUG */ + /* Initialise the stats department, phase 1 */ initStats1(); From git at git.haskell.org Thu Oct 9 07:38:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 07:38:40 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: More progress (refactoring StopAndContinue) (3b2757f) Message-ID: <20141009073840.968E43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/3b2757f6ab09d3dc527f532681340ca7fb39aa37/ghc >--------------------------------------------------------------- commit 3b2757f6ab09d3dc527f532681340ca7fb39aa37 Author: Simon Peyton Jones Date: Thu Oct 9 08:37:35 2014 +0100 More progress (refactoring StopAndContinue) >--------------------------------------------------------------- 3b2757f6ab09d3dc527f532681340ca7fb39aa37 compiler/typecheck/Flattening-notes | 2 + compiler/typecheck/TcCanonical.lhs | 199 ++++++++++++++--------------------- compiler/typecheck/TcInteract.lhs | 201 ++++++++++++++++++------------------ compiler/typecheck/TcSMonad.lhs | 189 ++++++++++++++++++++------------- compiler/typecheck/TcSimplify.lhs | 3 +- 5 files changed, 295 insertions(+), 299 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 3b2757f6ab09d3dc527f532681340ca7fb39aa37 From git at git.haskell.org Thu Oct 9 11:38:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 11:38:30 +0000 (UTC) Subject: [commit: ghc] wip/T8584: WIP #STASH (3edf642) Message-ID: <20141009113830.90A983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/3edf64208381523c67f47d11afe00192d4378e44/ghc >--------------------------------------------------------------- commit 3edf64208381523c67f47d11afe00192d4378e44 Author: Dr. ERDI Gergo Date: Thu Oct 9 19:37:26 2014 +0800 WIP #STASH >--------------------------------------------------------------- 3edf64208381523c67f47d11afe00192d4378e44 compiler/rename/RnBinds.lhs | 0 compiler/typecheck/TcBinds.lhs | 18 ++++--- compiler/typecheck/TcPatSyn.lhs | 117 ++++++++++++++++++++++++++++------------ 3 files changed, 95 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 3edf64208381523c67f47d11afe00192d4378e44 From git at git.haskell.org Thu Oct 9 13:38:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 13:38:09 +0000 (UTC) Subject: [commit: ghc] wip/T8584: WIP #STASH (1b0e1ea) Message-ID: <20141009133809.9A2433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/1b0e1eaa869d834be10813ebf775e8378e615153/ghc >--------------------------------------------------------------- commit 1b0e1eaa869d834be10813ebf775e8378e615153 Author: Dr. ERDI Gergo Date: Thu Oct 9 21:37:05 2014 +0800 WIP #STASH >--------------------------------------------------------------- 1b0e1eaa869d834be10813ebf775e8378e615153 compiler/rename/RnBinds.lhs | 0 compiler/typecheck/TcBinds.lhs | 18 ++++--- compiler/typecheck/TcPatSyn.lhs | 111 +++++++++++++++++++++++++++++----------- 3 files changed, 92 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 1b0e1eaa869d834be10813ebf775e8378e615153 From git at git.haskell.org Thu Oct 9 16:05:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 16:05:33 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: More progress (22a8a36) Message-ID: <20141009160533.A31373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/22a8a36a74d4856268097a5cbc2f1e5822da7a21/ghc >--------------------------------------------------------------- commit 22a8a36a74d4856268097a5cbc2f1e5822da7a21 Author: Simon Peyton Jones Date: Thu Oct 9 17:05:27 2014 +0100 More progress >--------------------------------------------------------------- 22a8a36a74d4856268097a5cbc2f1e5822da7a21 compiler/typecheck/TcCanonical.lhs | 20 ++++++- compiler/typecheck/TcInteract.lhs | 15 +++-- compiler/typecheck/TcSMonad.lhs | 64 +++++++++------------- testsuite/tests/gadt/gadt7.stderr | 6 +- .../indexed-types/should_compile/T3017.stderr | 2 +- .../indexed-types/should_compile/T3208b.stderr | 6 +- .../indexed-types/should_fail/NoMatchErr.stderr | 2 +- .../indexed-types/should_fail/SimpleFail16.stderr | 3 +- .../tests/indexed-types/should_fail/T1897b.stderr | 2 +- .../tests/indexed-types/should_fail/T2544.stderr | 4 +- testsuite/tests/indexed-types/should_fail/T2664.hs | 17 ++++++ .../tests/indexed-types/should_fail/T2664.stderr | 18 +++--- .../tests/indexed-types/should_fail/T7010.stderr | 2 +- .../tests/indexed-types/should_fail/T9036.stderr | 2 +- testsuite/tests/perf/compiler/T5837.hs | 14 +++++ testsuite/tests/polykinds/T7438.stderr | 6 +- .../typecheck/should_compile/TcTypeNatSimple.hs | 5 +- .../typecheck/should_fail/FrozenErrorTests.stderr | 12 ++-- testsuite/tests/typecheck/should_fail/T5853.stderr | 26 +++++---- testsuite/tests/typecheck/should_fail/T7453.stderr | 11 ++-- 20 files changed, 137 insertions(+), 100 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 22a8a36a74d4856268097a5cbc2f1e5822da7a21 From git at git.haskell.org Thu Oct 9 16:27:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 16:27:40 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Merge branch 'wip/new-flatten-skolems-Aug14' into wip/tc-plugins (dabf464) Message-ID: <20141009162740.35F0F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/dabf464a9ee327b7a77f96b7196b924eeeb11449/ghc >--------------------------------------------------------------- commit dabf464a9ee327b7a77f96b7196b924eeeb11449 Merge: 1dcdde1 2c516a3 Author: Iavor S. Diatchki Date: Wed Oct 8 16:10:13 2014 -0700 Merge branch 'wip/new-flatten-skolems-Aug14' into wip/tc-plugins Conflicts: testsuite/tests/typecheck/should_fail/ContextStack2.stderr testsuite/tests/typecheck/should_fail/FrozenErrorTests.stderr testsuite/tests/typecheck/should_run/T5751.hs >--------------------------------------------------------------- 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 dabf464a9ee327b7a77f96b7196b924eeeb11449 From git at git.haskell.org Thu Oct 9 16:27:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 16:27:42 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Hook-in the plugins with the constraint solve in TcInteract (09e74f4) Message-ID: <20141009162742.C21FF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/09e74f4545cb37b1263217ac513191d20fc16939/ghc >--------------------------------------------------------------- commit 09e74f4545cb37b1263217ac513191d20fc16939 Author: Iavor S. Diatchki Date: Wed Oct 8 16:10:51 2014 -0700 Hook-in the plugins with the constraint solve in TcInteract >--------------------------------------------------------------- 09e74f4545cb37b1263217ac513191d20fc16939 compiler/typecheck/TcInteract.lhs | 74 ++++++++++++++++++++++++++++++++++++++- compiler/typecheck/TcSMonad.lhs | 15 ++++++++ 2 files changed, 88 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 4948692..a881a40 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -118,12 +118,84 @@ solveInteract cts do { sel <- selectNextWorkItem max_depth ; case sel of NoWorkRemaining -- Done, successfuly (modulo frozen) - -> return () + -> do more_work <- runTcPlugins + when more_work (solve_loop max_depth) + MaxDepthExceeded cnt ct -- Failure, depth exceeded -> wrapErrTcS $ solverDepthErrorTcS cnt (ctEvidence ct) NextWorkItem ct -- More work, loop around! -> do { runSolverPipeline thePipeline ct; solve_loop max_depth } } + +-- | Try to make progress using type-checker plugings. +-- Returns 'True' if we added some extra work to the work queue. +runTcPlugins :: TcS Bool +runTcPlugins = + do gblEnv <- getGblEnv + case tcg_tc_plugins gblEnv of + [] -> return False + plugins -> + do has_new_works <- mapM runPlugin plugins + return (or has_new_works) + where + runPlugin p = + do iSet <- getTcSInerts + let iCans = inert_cans iSet + iEqs = concat (varEnvElts (inert_eqs iCans)) + iFunEqs = funEqsToList (inert_funeqs iCans) + allCts = iEqs ++ iFunEqs + (derived,other) = partition isDerivedCt allCts + (wanted,given) = partition isWantedCt other + + -- We use this to remove some constraints. + -- 'survived' should be the sub-set of constraints that + -- remains inert. + restoreICans survived = + do let iCans1 = iCans { inert_eqs = emptyVarEnv + , inert_funeqs = emptyFunEqs } + iCans2 = foldl addInertCan iCans1 derived + iCans3 = foldl addInertCan iCans2 survived + setInertCans iCans3 + + result <- tcPluginIO $ tcPluginSolve p given wanted + case result of + + TcPluginContradiction bad_cts ok_cts -> + do restoreICans ok_cts + mapM_ emitInsoluble bad_cts + return False + + TcPluginNewWork new_cts -> + case removeKnownCts iCans new_cts of + [] -> return False + new_work -> + do updWorkListTcS (extendWorkListCts new_work) + return True + + TcPluginSolved solved_cts other_cts -> + case solved_cts of + [] -> return False -- Fast common case + _ -> do restoreICans other_cts + let setEv (ev,ct) = setEvBind (ctev_evar (cc_ev ct)) ev + mapM_ setEv solved_cts + return False + + removeKnownCts origIcans = filter (not . isKnownCt origIcans) + isKnownCt origIcans ct = + case ct of + + CFunEqCan { cc_fun = f, cc_tyargs = ts } -> + case findFunEq (inert_funeqs origIcans) f ts of + Just _ -> True + _ -> False + + CTyEqCan { cc_tyvar = x, cc_rhs = t } -> + not $ any (eqType t . cc_rhs) $ findTyEqs (inert_eqs origIcans) x + + _ -> panic "TcPlugin returned not a TyEq or FunEq constraint" + + + type WorkItem = Ct type SimplifierStage = WorkItem -> TcS StopOrContinue diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index 0f7fff8..c5d1b59 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -77,6 +77,7 @@ module TcSMonad ( findDict, findDictsByClass, addDict, addDictsByClass, delDict, partitionDicts, + emptyFunEqs, funEqsToList, findFunEq, findTyEqs, findFunEqsByTyCon, findFunEqs, partitionFunEqs, sizeFunEqMap, @@ -90,6 +91,8 @@ module TcSMonad ( getDefaultInfo, getDynFlags, getGlobalRdrEnvTcS, + tcPluginIO, + matchFam, checkWellStagedDFun, pprEq -- Smaller utils, re-exported from TcM @@ -2013,3 +2016,15 @@ deferTcSForAllEq role loc (tvs1,body1) (tvs2,body2) } \end{code} + +External Type-checker Plugins +----------------------------- + +\begin{code} +-- | Execute an IO action needed by an external plugin. +tcPluginIO :: IO a -> TcS a +tcPluginIO m = TcS (\_ -> liftIO m) +\end{code} + + + From git at git.haskell.org Thu Oct 9 16:27:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 16:27:45 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Export type-constructors (93117d3) Message-ID: <20141009162745.814223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/93117d3bb8593b96e98041d381cd343d5e2043b7/ghc >--------------------------------------------------------------- commit 93117d3bb8593b96e98041d381cd343d5e2043b7 Author: Iavor S. Diatchki Date: Thu Oct 9 09:25:21 2014 -0700 Export type-constructors >--------------------------------------------------------------- 93117d3bb8593b96e98041d381cd343d5e2043b7 compiler/typecheck/TcTypeNats.hs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/compiler/typecheck/TcTypeNats.hs b/compiler/typecheck/TcTypeNats.hs index 37fc6e0..8f02c9a 100644 --- a/compiler/typecheck/TcTypeNats.hs +++ b/compiler/typecheck/TcTypeNats.hs @@ -2,6 +2,14 @@ module TcTypeNats ( typeNatTyCons , typeNatCoAxiomRules , BuiltInSynFamily(..) + + , typeNatAddTyCon + , typeNatMulTyCon + , typeNatExpTyCon + , typeNatLeqTyCon + , typeNatSubTyCon + , typeNatCmpTyCon + , typeSymbolCmpTyCon ) where import Type From git at git.haskell.org Thu Oct 9 16:27:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 16:27:47 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins's head updated: Export type-constructors (93117d3) Message-ID: <20141009162747.E3AAB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/tc-plugins' now includes: 8e893b1 Simon PJ work in progress on re-architecting flatten-skolems 8596f14 More work in progress d6660a4 Comment wibble d4316a4 Add flattening notes c19b6a3 More wip on flatten-skolems 84b3463 More wip on flatten-skolems 88a007c More progress 286637a More progress a74611b Merge branch 'master' into wip/new-flatten-skolems-Aug14 9b5c9af More flatten-skolem progress c5f6308 Merge branch 'wip/new-flatten-skolems-Aug14' of https://git.haskell.org/ghc into wip/new-flatten-skolems-Aug14 8505aca More progress on flatten-skolems fc0694c Wibbles a333a46 Better printing for TcTyVars in dump style c7b6d41 Another traceTc debug trace 24c9c7c More flatten-skolem progress ec85cf2 Print traceTc stuff in dump-style ebcc037 Error message wibbles 0d2ce1d More flatten-skolem progress 0ce6d34 Better printing of dump messages 5064c32 Error message wibbles 1ddb047 More progress a5fb4ba MOre progress d709d73 Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 e94d2ab Esablish the flattening invariant for CTyEqCan ad1ad63 More progress e42db2e Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 1754d0b Refactoring around newClsInst 154716c Wibble a58aca0 Don't freshen the dfun tyvars in newClsInst 2c516a3 Comments dabf464 Merge branch 'wip/new-flatten-skolems-Aug14' into wip/tc-plugins 09e74f4 Hook-in the plugins with the constraint solve in TcInteract 93117d3 Export type-constructors From git at git.haskell.org Thu Oct 9 17:18:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 17:18:00 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Improve method for running plugins. (34573cd) Message-ID: <20141009171800.995F13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/34573cd5cdd910e8aef10e30b0fd6a8a21f55267/ghc >--------------------------------------------------------------- commit 34573cd5cdd910e8aef10e30b0fd6a8a21f55267 Author: Iavor S. Diatchki Date: Thu Oct 9 10:16:49 2014 -0700 Improve method for running plugins. Instead of trying to manually filter out known constraints, we leave it to GHC to do its usual thing. To avoid looping, we need to know if running the solver pipeline modified the inert set: if the inert set was changed, then we re-run the plugins, otherwise we are done so we stop. >--------------------------------------------------------------- 34573cd5cdd910e8aef10e30b0fd6a8a21f55267 compiler/typecheck/TcInteract.lhs | 132 ++++++++++++++++---------------------- 1 file changed, 57 insertions(+), 75 deletions(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index a881a40..f54e408 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -111,89 +111,70 @@ solveInteract cts = {-# SCC "solveInteract" #-} withWorkList cts $ do { dyn_flags <- getDynFlags - ; solve_loop (maxSubGoalDepth dyn_flags) } + ; solve_loop False (maxSubGoalDepth dyn_flags) } where - solve_loop max_depth + solve_loop inertsModified max_depth = {-# SCC "solve_loop" #-} do { sel <- selectNextWorkItem max_depth ; case sel of - NoWorkRemaining -- Done, successfuly (modulo frozen) - -> do more_work <- runTcPlugins - when more_work (solve_loop max_depth) + + NoWorkRemaining + | inertsModified -> + do gblEnv <- getGblEnv + mapM_ runTcPlugin (tcg_tc_plugins gblEnv) + solve_loop False max_depth + + -- Done, successfuly (modulo frozen) + | otherwise -> return () + MaxDepthExceeded cnt ct -- Failure, depth exceeded -> wrapErrTcS $ solverDepthErrorTcS cnt (ctEvidence ct) + NextWorkItem ct -- More work, loop around! - -> do { runSolverPipeline thePipeline ct; solve_loop max_depth } } + -> do { changes <- runSolverPipeline thePipeline ct + ; let newMod = changes || inertsModified + ; newMod `seq` solve_loop newMod max_depth } } -- | Try to make progress using type-checker plugings. --- Returns 'True' if we added some extra work to the work queue. -runTcPlugins :: TcS Bool -runTcPlugins = - do gblEnv <- getGblEnv - case tcg_tc_plugins gblEnv of - [] -> return False - plugins -> - do has_new_works <- mapM runPlugin plugins - return (or has_new_works) - where - runPlugin p = - do iSet <- getTcSInerts - let iCans = inert_cans iSet - iEqs = concat (varEnvElts (inert_eqs iCans)) - iFunEqs = funEqsToList (inert_funeqs iCans) - allCts = iEqs ++ iFunEqs - (derived,other) = partition isDerivedCt allCts - (wanted,given) = partition isWantedCt other - - -- We use this to remove some constraints. - -- 'survived' should be the sub-set of constraints that - -- remains inert. - restoreICans survived = - do let iCans1 = iCans { inert_eqs = emptyVarEnv - , inert_funeqs = emptyFunEqs } - iCans2 = foldl addInertCan iCans1 derived - iCans3 = foldl addInertCan iCans2 survived - setInertCans iCans3 - - result <- tcPluginIO $ tcPluginSolve p given wanted - case result of - - TcPluginContradiction bad_cts ok_cts -> - do restoreICans ok_cts - mapM_ emitInsoluble bad_cts - return False - - TcPluginNewWork new_cts -> - case removeKnownCts iCans new_cts of - [] -> return False - new_work -> - do updWorkListTcS (extendWorkListCts new_work) - return True - - TcPluginSolved solved_cts other_cts -> - case solved_cts of - [] -> return False -- Fast common case - _ -> do restoreICans other_cts - let setEv (ev,ct) = setEvBind (ctev_evar (cc_ev ct)) ev - mapM_ setEv solved_cts - return False - - removeKnownCts origIcans = filter (not . isKnownCt origIcans) - isKnownCt origIcans ct = - case ct of - - CFunEqCan { cc_fun = f, cc_tyargs = ts } -> - case findFunEq (inert_funeqs origIcans) f ts of - Just _ -> True - _ -> False - - CTyEqCan { cc_tyvar = x, cc_rhs = t } -> - not $ any (eqType t . cc_rhs) $ findTyEqs (inert_eqs origIcans) x - - _ -> panic "TcPlugin returned not a TyEq or FunEq constraint" - +-- The plugin is provided with only with CTyEq and CFunEq constraints. +runTcPlugin :: TcPlugin -> TcS () +runTcPlugin p = + do iSet <- getTcSInerts + let iCans = inert_cans iSet + iEqs = concat (varEnvElts (inert_eqs iCans)) + iFunEqs = funEqsToList (inert_funeqs iCans) + allCts = iEqs ++ iFunEqs + (derived,other) = partition isDerivedCt allCts + (wanted,given) = partition isWantedCt other + + -- We use this to remove some constraints. + -- 'survived' should be the sub-set of constraints that + -- remains inert. + restoreICans survived = + do let iCans1 = iCans { inert_eqs = emptyVarEnv + , inert_funeqs = emptyFunEqs } + iCans2 = foldl addInertCan iCans1 derived + iCans3 = foldl addInertCan iCans2 survived + setInertCans iCans3 + + result <- tcPluginIO $ tcPluginSolve p given wanted + case result of + + TcPluginContradiction bad_cts ok_cts -> + do restoreICans ok_cts + mapM_ emitInsoluble bad_cts + + TcPluginNewWork new_cts -> + updWorkListTcS (extendWorkListCts new_cts) + + TcPluginSolved solved_cts other_cts -> + case solved_cts of + [] -> return () -- Fast common case + _ -> do restoreICans other_cts + let setEv (ev,ct) = setEvBind (ctev_evar (cc_ev ct)) ev + mapM_ setEv solved_cts type WorkItem = Ct @@ -225,7 +206,7 @@ selectNextWorkItem max_depth runSolverPipeline :: [(String,SimplifierStage)] -- The pipeline -> WorkItem -- The work item - -> TcS () + -> TcS Bool -- Did we modify the inert set -- Run this item down the pipeline, leaving behind new work and inerts runSolverPipeline pipeline workItem = do { initial_is <- getTcSInerts @@ -240,13 +221,14 @@ runSolverPipeline pipeline workItem ; case final_res of Stop -> do { traceTcS "End solver pipeline (discharged) }" (ptext (sLit "inerts = ") <+> ppr final_is) - ; return () } + ; return False } ContinueWith ct -> do { traceFireTcS ct (ptext (sLit "Kept as inert")) ; traceTcS "End solver pipeline (not discharged) }" $ vcat [ ptext (sLit "final_item = ") <+> ppr ct , pprTvBndrs (varSetElems $ tyVarsOfCt ct) , ptext (sLit "inerts = ") <+> ppr final_is] - ; insertInertItemTcS ct } + ; insertInertItemTcS ct + ; return True } } where run_pipeline :: [(String,SimplifierStage)] -> StopOrContinue -> TcS StopOrContinue run_pipeline [] res = return res From git at git.haskell.org Thu Oct 9 23:02:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 23:02:11 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Fix-up the boot file, to match the declaratoins in the module. (b34a313) Message-ID: <20141009230211.BC1AD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/b34a3138e98d3241bb2fa8269f5eeebb4f1a2d65/ghc >--------------------------------------------------------------- commit b34a3138e98d3241bb2fa8269f5eeebb4f1a2d65 Author: Iavor S. Diatchki Date: Thu Oct 9 15:36:27 2014 -0700 Fix-up the boot file, to match the declaratoins in the module. >--------------------------------------------------------------- b34a3138e98d3241bb2fa8269f5eeebb4f1a2d65 compiler/typecheck/TcRnTypes.lhs-boot | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcRnTypes.lhs-boot b/compiler/typecheck/TcRnTypes.lhs-boot index 36c43fc..8a5ee15 100644 --- a/compiler/typecheck/TcRnTypes.lhs-boot +++ b/compiler/typecheck/TcRnTypes.lhs-boot @@ -3,9 +3,9 @@ module TcRnTypes where import IOEnv -type TcM a = TcRn a -type TcRn a = TcRnIf TcGblEnv TcLclEnv a -type TcRnIf a b c = IOEnv (Env a b) c +type TcM = TcRn +type TcRn = TcRnIf TcGblEnv TcLclEnv +type TcRnIf a b = IOEnv (Env a b) data Env a b data TcGblEnv From git at git.haskell.org Thu Oct 9 23:02:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 23:02:14 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Split-out the type of TcSMonad into a separate module TcSTypes. (9215da8) Message-ID: <20141009230214.C60DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/9215da81a190dfabc4fa598012aa93c937f0aaf2/ghc >--------------------------------------------------------------- commit 9215da81a190dfabc4fa598012aa93c937f0aaf2 Author: Iavor S. Diatchki Date: Thu Oct 9 15:40:36 2014 -0700 Split-out the type of TcSMonad into a separate module TcSTypes. We do this, because we'd like to mention the type `TcS` in `TcRnTypes`. The reason for this is that type-checker plugins are stored in the global environment of `TcM`, which is defined in `TcRnTypes`. If `TcRnTypes` depends on the whole of `TcSMonad`, then we have to add very many dependencies to `gc.mk` (see note about building DLLs on Windows). For this reason, we split-up TcSMonad in twp parts: `TcSTypes`, which has relatively few dependencies, and `TcSMonad`, which contains most of the code. `TcSMonad` was getting quite large anyway, so hopefully this is OK. >--------------------------------------------------------------- 9215da81a190dfabc4fa598012aa93c937f0aaf2 compiler/ghc.cabal.in | 1 + compiler/typecheck/TcSMonad.lhs | 350 +----------------------------------- compiler/typecheck/TcSTypes.hs | 385 ++++++++++++++++++++++++++++++++++++++++ 3 files changed, 387 insertions(+), 349 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 9215da81a190dfabc4fa598012aa93c937f0aaf2 From git at git.haskell.org Thu Oct 9 23:02:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 9 Oct 2014 23:02:17 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Change type of type-checker plugins to give access to type-checking monads. (a3f13e4) Message-ID: <20141009230217.DE2F43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/a3f13e49feccaae4070f18c57de33275d2841f7a/ghc >--------------------------------------------------------------- commit a3f13e49feccaae4070f18c57de33275d2841f7a Author: Iavor S. Diatchki Date: Thu Oct 9 16:02:07 2014 -0700 Change type of type-checker plugins to give access to type-checking monads. >--------------------------------------------------------------- a3f13e49feccaae4070f18c57de33275d2841f7a compiler/ghc.mk | 1 + compiler/typecheck/TcInteract.lhs | 6 +++--- compiler/typecheck/TcRnDriver.lhs | 12 +++--------- compiler/typecheck/TcRnMonad.lhs | 28 +++++++++++++++++++++++----- compiler/typecheck/TcRnTypes.lhs | 23 +++++++++++++++-------- compiler/typecheck/TcSTypes.hs-boot | 7 +++++++ 6 files changed, 52 insertions(+), 25 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 a3f13e49feccaae4070f18c57de33275d2841f7a From git at git.haskell.org Fri Oct 10 00:29:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 10 Oct 2014 00:29:43 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Change plugin interface: allow solving and improvement in the same step. (9aff205) Message-ID: <20141010002943.BE5F43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/9aff20599ccbebd3f4077d8f1091be041241ee16/ghc >--------------------------------------------------------------- commit 9aff20599ccbebd3f4077d8f1091be041241ee16 Author: Iavor S. Diatchki Date: Thu Oct 9 17:29:43 2014 -0700 Change plugin interface: allow solving and improvement in the same step. >--------------------------------------------------------------- 9aff20599ccbebd3f4077d8f1091be041241ee16 compiler/typecheck/TcInteract.lhs | 17 ++++++++--------- compiler/typecheck/TcRnTypes.lhs | 16 +++------------- 2 files changed, 11 insertions(+), 22 deletions(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index dc599e5..6d0bfcf 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -166,15 +166,14 @@ runTcPlugin solver = do restoreICans ok_cts mapM_ emitInsoluble bad_cts - TcPluginNewWork new_cts -> - updWorkListTcS (extendWorkListCts new_cts) - - TcPluginSolved solved_cts other_cts -> - case solved_cts of - [] -> return () -- Fast common case - _ -> do restoreICans other_cts - let setEv (ev,ct) = setEvBind (ctev_evar (cc_ev ct)) ev - mapM_ setEv solved_cts + -- other_cts should include both givens and wanteds. + TcPluginOk solved_cts other_cts new_cts -> + do case solved_cts of + [] -> return () -- Fast common case + _ -> do restoreICans other_cts + let setEv (ev,ct) = setEvBind (ctev_evar (cc_ev ct)) ev + mapM_ setEv solved_cts + updWorkListTcS (extendWorkListCts new_cts) type WorkItem = Ct diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index 4bc12f6..aa54941 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -1938,20 +1938,10 @@ data TcPlugin = forall s. TcPlugin data TcPluginResult = TcPluginContradiction {- inconsistent -} [Ct] {- all others -} [Ct] - {- ^ There is no model for the constraints. - The two lists partition the original constraints, - with the first one being the conflicting constraints, - and the second the other constraints. -} - - | TcPluginNewWork [Ct] - -- ^ New work (facts that will hold in all models) - - | TcPluginSolved {- solved -} [(EvTerm,Ct)] - {- not solved -} [Ct] - -- ^ We managed to solve some of the constrints. - -- The solved constraints (with evidence) are in the first list. - -- The unsolved constraints are in the second one. + | TcPluginOk {- solved, non-empty -} [(EvTerm,Ct)] + {- not solved -} [Ct] + {- new work -} [Ct] \end{code} From git at git.haskell.org Fri Oct 10 00:34:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 10 Oct 2014 00:34:58 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Update comments. (66fa545) Message-ID: <20141010003458.35B823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/66fa5451f5baf86b7f6e6ff6ae01ec671b4f645c/ghc >--------------------------------------------------------------- commit 66fa5451f5baf86b7f6e6ff6ae01ec671b4f645c Author: Iavor S. Diatchki Date: Thu Oct 9 17:35:00 2014 -0700 Update comments. >--------------------------------------------------------------- 66fa5451f5baf86b7f6e6ff6ae01ec671b4f645c compiler/typecheck/TcRnTypes.lhs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index aa54941..6e6db1e 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -1939,8 +1939,8 @@ data TcPluginResult = TcPluginContradiction {- inconsistent -} [Ct] {- all others -} [Ct] - | TcPluginOk {- solved, non-empty -} [(EvTerm,Ct)] - {- not solved -} [Ct] + | TcPluginOk {- solved -} [(EvTerm,Ct)] + {- all others -} [Ct] {- new work -} [Ct] \end{code} From git at git.haskell.org Fri Oct 10 01:13:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 10 Oct 2014 01:13:50 +0000 (UTC) Subject: [commit: ghc] branch 'ghc-validate' created Message-ID: <20141010011350.4BF623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : ghc-validate Referencing: 267ad95b16bf5b7405e271dcf69c4d5ad6387abe From git at git.haskell.org Fri Oct 10 01:13:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 10 Oct 2014 01:13:52 +0000 (UTC) Subject: [commit: ghc] ghc-validate: Ignore exe files in base (from tests) (267ad95) Message-ID: <20141010011352.E7A223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-validate Link : http://ghc.haskell.org/trac/ghc/changeset/267ad95b16bf5b7405e271dcf69c4d5ad6387abe/ghc >--------------------------------------------------------------- commit 267ad95b16bf5b7405e271dcf69c4d5ad6387abe Author: Edward Z. Yang Date: Fri Oct 3 15:15:52 2014 -0700 Ignore exe files in base (from tests) Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 267ad95b16bf5b7405e271dcf69c4d5ad6387abe libraries/base/.gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/libraries/base/.gitignore b/libraries/base/.gitignore index 54bc34c..6a6d524 100644 --- a/libraries/base/.gitignore +++ b/libraries/base/.gitignore @@ -2,6 +2,7 @@ *.aux *.hi *.tix +*.exe # Backup files *~ From git at git.haskell.org Fri Oct 10 01:14:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 10 Oct 2014 01:14:20 +0000 (UTC) Subject: [commit: ghc] master's head updated: Ignore exe files in base (from tests) (267ad95) Message-ID: <20141010011420.7D6DF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: 267ad95 Ignore exe files in base (from tests) From git at git.haskell.org Fri Oct 10 04:40:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 10 Oct 2014 04:40:46 +0000 (UTC) Subject: [commit: ghc] master: Update haddock submodule with lazy IO fix. (39666ae) Message-ID: <20141010044046.9E5DF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/39666aeefaeb98474552a1fb5d5502b2d0b53278/ghc >--------------------------------------------------------------- commit 39666aeefaeb98474552a1fb5d5502b2d0b53278 Author: Edward Z. Yang Date: Thu Oct 9 21:40:41 2014 -0700 Update haddock submodule with lazy IO fix. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 39666aeefaeb98474552a1fb5d5502b2d0b53278 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index a65d213..2f639ff 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit a65d2131647e010608d2a1956116a0012946838f +Subproject commit 2f639ffe09dd24d8648363b567de2d7caa39db99 From git at git.haskell.org Fri Oct 10 07:03:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 10 Oct 2014 07:03:34 +0000 (UTC) Subject: [commit: ghc] master: Rewrite section 1 of the Backpack manual. [skip ci] (d3f56ec) Message-ID: <20141010070334.185413A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d3f56ec6a6ead847233fee5dfad7979c2d63fc3d/ghc >--------------------------------------------------------------- commit d3f56ec6a6ead847233fee5dfad7979c2d63fc3d Author: Edward Z. Yang Date: Fri Oct 10 00:01:57 2014 -0700 Rewrite section 1 of the Backpack manual. [skip ci] Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- d3f56ec6a6ead847233fee5dfad7979c2d63fc3d docs/backpack/backpack-manual.tex | 546 ++++++++++++++++++++++++-------------- 1 file changed, 344 insertions(+), 202 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 d3f56ec6a6ead847233fee5dfad7979c2d63fc3d From git at git.haskell.org Fri Oct 10 10:52:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 10 Oct 2014 10:52:02 +0000 (UTC) Subject: [commit: ghc] wip/T8584: WIP #STASH (9237fc9) Message-ID: <20141010105202.D3E8B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/9237fc911fba0f55ae84bdbe5aa53cef15ca7c6d/ghc >--------------------------------------------------------------- commit 9237fc911fba0f55ae84bdbe5aa53cef15ca7c6d Author: Dr. ERDI Gergo Date: Thu Oct 9 21:54:42 2014 +0800 WIP #STASH >--------------------------------------------------------------- 9237fc911fba0f55ae84bdbe5aa53cef15ca7c6d compiler/rename/RnBinds.lhs | 0 compiler/typecheck/TcBinds.lhs | 18 ++++--- compiler/typecheck/TcPatSyn.lhs | 109 ++++++++++++++++++++++++++++------------ 3 files changed, 88 insertions(+), 39 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 9237fc911fba0f55ae84bdbe5aa53cef15ca7c6d From git at git.haskell.org Fri Oct 10 13:32:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 10 Oct 2014 13:32:05 +0000 (UTC) Subject: [commit: ghc] master: Name worker threads using pthread_setname_np (674c631) Message-ID: <20141010133205.655C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/674c631ea111233daa929ef63500d75ba0db8858/ghc >--------------------------------------------------------------- commit 674c631ea111233daa929ef63500d75ba0db8858 Author: Simon Marlow Date: Fri Oct 10 14:26:19 2014 +0100 Name worker threads using pthread_setname_np This helps identify threads in gdb particularly in processes with a lot of threads. >--------------------------------------------------------------- 674c631ea111233daa929ef63500d75ba0db8858 includes/rts/OSThreads.h | 2 +- rts/Task.c | 2 +- rts/posix/OSThreads.c | 7 +++++-- rts/sm/GC.c | 17 +++++++++-------- rts/win32/OSThreads.c | 3 ++- testsuite/tests/rts/testwsdeque.c | 2 +- 6 files changed, 19 insertions(+), 14 deletions(-) diff --git a/includes/rts/OSThreads.h b/includes/rts/OSThreads.h index e99be8a..a3ed47c 100644 --- a/includes/rts/OSThreads.h +++ b/includes/rts/OSThreads.h @@ -171,7 +171,7 @@ extern void yieldThread ( void ); typedef void OSThreadProcAttr OSThreadProc(void *); -extern int createOSThread ( OSThreadId* tid, +extern int createOSThread ( OSThreadId* tid, char *name, OSThreadProc *startProc, void *param); extern rtsBool osThreadIsAlive ( OSThreadId id ); extern void interruptOSThread (OSThreadId id); diff --git a/rts/Task.c b/rts/Task.c index 0370711..42893fe 100644 --- a/rts/Task.c +++ b/rts/Task.c @@ -462,7 +462,7 @@ startWorkerTask (Capability *cap) ASSERT_LOCK_HELD(&cap->lock); cap->running_task = task; - r = createOSThread(&tid, (OSThreadProc*)workerStart, task); + r = createOSThread(&tid, "ghc_worker", (OSThreadProc*)workerStart, task); if (r != 0) { sysErrorBelch("failed to create OS thread"); stg_exit(EXIT_FAILURE); diff --git a/rts/posix/OSThreads.c b/rts/posix/OSThreads.c index e627bab..e880b89 100644 --- a/rts/posix/OSThreads.c +++ b/rts/posix/OSThreads.c @@ -129,11 +129,14 @@ shutdownThread(void) } int -createOSThread (OSThreadId* pId, OSThreadProc *startProc, void *param) +createOSThread (OSThreadId* pId, char *name, + OSThreadProc *startProc, void *param) { int result = pthread_create(pId, NULL, (void *(*)(void *))startProc, param); - if(!result) + if (!result) { pthread_detach(*pId); + pthread_setname_np(*pId, name); + } return result; } diff --git a/rts/sm/GC.c b/rts/sm/GC.c index dabcd72..19d9ab2 100644 --- a/rts/sm/GC.c +++ b/rts/sm/GC.c @@ -670,6 +670,15 @@ GarbageCollect (nat collect_gen, if (major_gc) { gcCAFs(); } #endif + // Update the stable pointer hash table. + updateStableTables(major_gc); + + // unlock the StablePtr table. Must be before scheduleFinalizers(), + // because a finalizer may call hs_free_fun_ptr() or + // hs_free_stable_ptr(), both of which access the StablePtr table. + stableUnlock(); + + // Must be after stableUnlock(), because it might free stable ptrs. if (major_gc) { checkUnload (gct->scavenged_static_objects); } @@ -696,14 +705,6 @@ GarbageCollect (nat collect_gen, } } - // Update the stable pointer hash table. - updateStableTables(major_gc); - - // unlock the StablePtr table. Must be before scheduleFinalizers(), - // because a finalizer may call hs_free_fun_ptr() or - // hs_free_stable_ptr(), both of which access the StablePtr table. - stableUnlock(); - // Start any pending finalizers. Must be after // updateStableTables() and stableUnlock() (see #4221). RELEASE_SM_LOCK; diff --git a/rts/win32/OSThreads.c b/rts/win32/OSThreads.c index e336bd2..c3d3af6 100644 --- a/rts/win32/OSThreads.c +++ b/rts/win32/OSThreads.c @@ -98,7 +98,8 @@ shutdownThread() } int -createOSThread (OSThreadId* pId, OSThreadProc *startProc, void *param) +createOSThread (OSThreadId* pId, char *name STG_UNUSED, + OSThreadProc *startProc, void *param) { HANDLE h; h = CreateThread ( NULL, /* default security attributes */ diff --git a/testsuite/tests/rts/testwsdeque.c b/testsuite/tests/rts/testwsdeque.c index 51aeec1..e6f644c 100644 --- a/testsuite/tests/rts/testwsdeque.c +++ b/testsuite/tests/rts/testwsdeque.c @@ -149,7 +149,7 @@ int main(int argc, char*argv[]) } for (n=0; n < THREADS; n++) { - createOSThread(&ids[n], thief, (void*)(StgWord)n); + createOSThread(&ids[n], "thief", thief, (void*)(StgWord)n); } for (n=0; n < SCRATCH_SIZE; n++) { From git at git.haskell.org Fri Oct 10 19:14:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 10 Oct 2014 19:14:12 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Modify TcPlugin interface, and move loading of plugins to `initTc` (2a6787c) Message-ID: <20141010191412.1CD523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/2a6787c9be36918d0deaa2747aed87dfae492f48/ghc >--------------------------------------------------------------- commit 2a6787c9be36918d0deaa2747aed87dfae492f48 Author: Iavor S. Diatchki Date: Fri Oct 10 12:14:13 2014 -0700 Modify TcPlugin interface, and move loading of plugins to `initTc` The typechecker plugins are now written in a restricted monad, which wraps TcM. See TcPluginM in TcRnTypes and the related funcitons in TcRnMonad. Also, plugin loading now happens when initializing the type-checker, conditional on a boolean flag. The flag is important, so that we can disable plugin loding while loading the plugins themselves, to avoid a loop. Also, uses of `initTcInteractive` that are related to dynamic loading were renamed to a separate function: `initTcDynamic`. >--------------------------------------------------------------- 2a6787c9be36918d0deaa2747aed87dfae492f48 compiler/ghc.cabal.in | 1 - compiler/ghc.mk | 14 +- compiler/ghci/RtClosureInspect.hs | 4 +- compiler/main/DynamicLoading.hs | 6 +- compiler/main/DynamicLoading.hs-boot | 12 ++ compiler/typecheck/TcInteract.lhs | 4 +- compiler/typecheck/TcRnDriver.lhs | 43 +--- compiler/typecheck/TcRnMonad.lhs | 128 ++++++++---- compiler/typecheck/TcRnTypes.lhs | 35 +++- compiler/typecheck/TcSMonad.lhs | 367 +++++++++++++++++++++++++++++++-- compiler/typecheck/TcSTypes.hs | 385 ----------------------------------- compiler/typecheck/TcSTypes.hs-boot | 7 - 12 files changed, 508 insertions(+), 498 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 2a6787c9be36918d0deaa2747aed87dfae492f48 From git at git.haskell.org Fri Oct 10 20:57:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 10 Oct 2014 20:57:35 +0000 (UTC) Subject: [commit: ghc] master: rts: don't crash on 'hs_init(NULL, NULL)' in debug rts (97b7593) Message-ID: <20141010205735.763EB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/97b75935ca2cc9d5c9c8dcdb65439dd32af1907b/ghc >--------------------------------------------------------------- commit 97b75935ca2cc9d5c9c8dcdb65439dd32af1907b Author: Sergei Trofimovich Date: Fri Oct 10 21:43:30 2014 +0100 rts: don't crash on 'hs_init(NULL, NULL)' in debug rts Caught by T6006 as a NULL dereference: Command: ./T6006 Invalid read of size 8 at 0x660ED9: hs_init_ghc (RtsStartup.c:168) by 0x660D90: hs_init (RtsStartup.c:112) by 0x40504D: main (in /home/slyfox/dev/git/ghc-validate/testsuite/tests/rts/T6006) Address 0x0 is not stack'd, malloc'd or (recently) free'd The regression was introduced by commit cb0a503a44bf016de3d9042906c6ac0c0821ffea Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 97b75935ca2cc9d5c9c8dcdb65439dd32af1907b rts/RtsStartup.c | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/rts/RtsStartup.c b/rts/RtsStartup.c index 5e6f9fa..32bed5a 100644 --- a/rts/RtsStartup.c +++ b/rts/RtsStartup.c @@ -161,12 +161,12 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config) setFullProgArgv(*argc,*argv); setupRtsFlags(argc, *argv, rts_config.rts_opts_enabled, rts_config.rts_opts, rts_config.rts_hs_main); - } #ifdef DEBUG - /* load debugging symbols for current binary */ - DEBUG_LoadSymbols((*argv)[0]); + /* load debugging symbols for current binary */ + DEBUG_LoadSymbols((*argv)[0]); #endif /* DEBUG */ + } /* Initialise the stats department, phase 1 */ initStats1(); From git at git.haskell.org Sat Oct 11 07:07:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 11 Oct 2014 07:07:50 +0000 (UTC) Subject: [commit: ghc] master: Remove a few redundant `.hs-boot` files (ad4a713) Message-ID: <20141011070750.A79C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ad4a713964225e8e2d4e4a9579305a07a6ec2721/ghc >--------------------------------------------------------------- commit ad4a713964225e8e2d4e4a9579305a07a6ec2721 Author: Herbert Valerio Riedel Date: Sat Oct 11 00:44:54 2014 +0200 Remove a few redundant `.hs-boot` files There don't seem to be any corresponding `{-# SOURCE #-}` for the removed `.hs-boot`-files anymore (if there ever was any in the first place). This also removes a commented out `{-# SOURCE #-}` import which turns up when grepping the source for `{-# SOURCE #-}` occurences. >--------------------------------------------------------------- ad4a713964225e8e2d4e4a9579305a07a6ec2721 libraries/base/Data/OldTypeable/Internal.hs-boot | 28 ---------------------- libraries/base/Data/Typeable/Internal.hs-boot | 30 ------------------------ libraries/base/GHC/Show.lhs-boot | 11 --------- libraries/base/GHC/Word.hs | 1 - 4 files changed, 70 deletions(-) diff --git a/libraries/base/Data/OldTypeable/Internal.hs-boot b/libraries/base/Data/OldTypeable/Internal.hs-boot deleted file mode 100644 index 4c1d636..0000000 --- a/libraries/base/Data/OldTypeable/Internal.hs-boot +++ /dev/null @@ -1,28 +0,0 @@ -{-# LANGUAGE Unsafe #-} -{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-} - -module Data.OldTypeable.Internal ( - Typeable(typeOf), - TypeRep, - TyCon, - mkTyCon, - mkTyConApp - ) where - -import GHC.Base - -data TypeRep -data TyCon - -#include "MachDeps.h" - -#if WORD_SIZE_IN_BITS < 64 -mkTyCon :: Word64# -> Word64# -> String -> String -> String -> TyCon -#else -mkTyCon :: Word# -> Word# -> String -> String -> String -> TyCon -#endif - -mkTyConApp :: TyCon -> [TypeRep] -> TypeRep - -class Typeable a where - typeOf :: a -> TypeRep diff --git a/libraries/base/Data/Typeable/Internal.hs-boot b/libraries/base/Data/Typeable/Internal.hs-boot deleted file mode 100644 index e2f65ee..0000000 --- a/libraries/base/Data/Typeable/Internal.hs-boot +++ /dev/null @@ -1,30 +0,0 @@ -{-# LANGUAGE Unsafe #-} -{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, PolyKinds #-} - -module Data.Typeable.Internal ( - Proxy(..), - Typeable(typeRep), - TypeRep, - TyCon, - mkTyCon, - mkTyConApp - ) where - -import GHC.Base -import {-# SOURCE #-} Data.Proxy - -data TypeRep -data TyCon - -#include "MachDeps.h" - -#if WORD_SIZE_IN_BITS < 64 -mkTyCon :: Word64# -> Word64# -> String -> String -> String -> TyCon -#else -mkTyCon :: Word# -> Word# -> String -> String -> String -> TyCon -#endif - -mkTyConApp :: TyCon -> [TypeRep] -> TypeRep - -class Typeable a where - typeRep :: proxy a -> TypeRep diff --git a/libraries/base/GHC/Show.lhs-boot b/libraries/base/GHC/Show.lhs-boot deleted file mode 100644 index a2363f6..0000000 --- a/libraries/base/GHC/Show.lhs-boot +++ /dev/null @@ -1,11 +0,0 @@ -\begin{code} -{-# LANGUAGE Trustworthy #-} -{-# LANGUAGE NoImplicitPrelude #-} - -module GHC.Show (showSignedInt) where - -import GHC.Types - -showSignedInt :: Int -> Int -> [Char] -> [Char] -\end{code} - diff --git a/libraries/base/GHC/Word.hs b/libraries/base/GHC/Word.hs index 6721d07..b2c70a2 100644 --- a/libraries/base/GHC/Word.hs +++ b/libraries/base/GHC/Word.hs @@ -35,7 +35,6 @@ import Data.Maybe import GHC.IntWord64 #endif --- import {-# SOURCE #-} GHC.Exception import GHC.Base import GHC.Enum import GHC.Num From git at git.haskell.org Sat Oct 11 09:47:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 11 Oct 2014 09:47:45 +0000 (UTC) Subject: [commit: ghc] master: Fallback to `ctypes.cdll` if `ctypes.windll` unavailable (1032554) Message-ID: <20141011094745.833BD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1032554a7084a12d38a08beaaeb7a07088883e29/ghc >--------------------------------------------------------------- commit 1032554a7084a12d38a08beaaeb7a07088883e29 Author: Gintautas Miliauskas Date: Wed Sep 17 20:57:04 2014 +0200 Fallback to `ctypes.cdll` if `ctypes.windll` unavailable On Windows, we may be using a native build of Python or a mingw/msys build. The former exports `ctypes.windll`, the latter exports `cdll`. Previously the code threw an exception when using the msys Python because it expected `windll` to always be available on Windows. Differential Revision: https://phabricator.haskell.org/D308 >--------------------------------------------------------------- 1032554a7084a12d38a08beaaeb7a07088883e29 testsuite/driver/runtests.py | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index 103c7ac..cc55dad 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -149,13 +149,11 @@ if windows: # Try to use UTF8 if windows: import ctypes - if config.cygwin: - # Is this actually right? Which calling convention does it use? - # As of the time of writing, ctypes.windll doesn't exist in the - # cygwin python, anyway. - mydll = ctypes.cdll - else: + # Windows Python provides windll, mingw python provides cdll. + if hasattr(ctypes, 'windll'): mydll = ctypes.windll + else: + mydll = ctypes.cdll # This actually leaves the terminal in codepage 65001 (UTF8) even # after python terminates. We ought really remember the old codepage From git at git.haskell.org Sat Oct 11 10:32:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 11 Oct 2014 10:32:10 +0000 (UTC) Subject: [commit: ghc] master: Extend windows detection in testsuite to recognize MSYS target (034b203) Message-ID: <20141011103210.738063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/034b2035d6099c8a253bb1fbd1864001a27b44d6/ghc >--------------------------------------------------------------- commit 034b2035d6099c8a253bb1fbd1864001a27b44d6 Author: Gintautas Miliauskas Date: Wed Sep 17 20:57:39 2014 +0200 Extend windows detection in testsuite to recognize MSYS target Currently, the detection recognizes the following `uname -s` strings: - `CYGWIN_NT-6.3` - `MINGW32_NT-6.3` - `MINGW64_NT_6.3` However, MSYS2 provides an additional target, in which case `uname -s` returns a string such as `MSYS_NT-6.3`. In all these cases, the system ought to be recognized as being a `windows` os by the testsuite runner. See also #9604 >--------------------------------------------------------------- 034b2035d6099c8a253bb1fbd1864001a27b44d6 testsuite/driver/runtests.py | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index cc55dad..571165a 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -139,9 +139,9 @@ if windows: h.close() if v.startswith("CYGWIN"): config.cygwin = True - elif v.startswith("MINGW"): + elif v.startswith("MINGW") or v.startswith("MSYS"): # msys gives "MINGW32" -# msys2 gives "MINGW_NT-6.2" +# msys2 gives "MINGW_NT-6.2" or "MSYS_NT-6.3" config.msys = True else: raise Exception("Can't detect Windows terminal type") From git at git.haskell.org Sat Oct 11 10:36:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 11 Oct 2014 10:36:14 +0000 (UTC) Subject: [commit: ghc] master: Refactor to avoid need for `Unicode.hs-boot` (1942fd6) Message-ID: <20141011103614.36E233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1942fd6a8414d5664f3c9f6d1e6e39ca5265ef21/ghc >--------------------------------------------------------------- commit 1942fd6a8414d5664f3c9f6d1e6e39ca5265ef21 Author: Herbert Valerio Riedel Date: Sat Oct 11 12:35:28 2014 +0200 Refactor to avoid need for `Unicode.hs-boot` This avoids the import-cycle caused by the import of `Foreign.C.Types` by using `Int` instead of `CInt` for the Unicode classification functions. This refactoring also allows to remove a couple of `fromIntegral`s. Reviewed By: rwbarton, ekmett Differential Revision: https://phabricator.haskell.org/D328 >--------------------------------------------------------------- 1942fd6a8414d5664f3c9f6d1e6e39ca5265ef21 libraries/base/GHC/Read.lhs | 2 +- libraries/base/GHC/Unicode.hs | 48 ++++++++++++-------------- libraries/base/GHC/Unicode.hs-boot | 20 ----------- libraries/base/Text/ParserCombinators/ReadP.hs | 2 +- libraries/base/Text/Read/Lex.hs | 2 +- libraries/base/cbits/WCsubst.c | 10 +++--- libraries/base/cbits/ubconfc | 10 +++--- libraries/base/include/WCsubst.h | 25 +++++++------- 8 files changed, 49 insertions(+), 70 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 1942fd6a8414d5664f3c9f6d1e6e39ca5265ef21 From git at git.haskell.org Sun Oct 12 19:55:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 12 Oct 2014 19:55:26 +0000 (UTC) Subject: [commit: ghc] master: Fix build on some platforms (a36991b) Message-ID: <20141012195526.9E9343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a36991b272e623e24f85437f05019d6e35ab8085/ghc >--------------------------------------------------------------- commit a36991b272e623e24f85437f05019d6e35ab8085 Author: Simon Marlow Date: Sun Oct 12 17:39:23 2014 +0100 Fix build on some platforms >--------------------------------------------------------------- a36991b272e623e24f85437f05019d6e35ab8085 rts/Linker.c | 2 ++ 1 file changed, 2 insertions(+) diff --git a/rts/Linker.c b/rts/Linker.c index 4ea7fd6..a34aeb7 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -2369,7 +2369,9 @@ mkOc( pathchar *path, char *image, int imageSize, oc->sections = NULL; oc->proddables = NULL; oc->stable_ptrs = NULL; +#if powerpc_HOST_ARCH || x86_64_HOST_ARCH || arm_HOST_ARCH oc->symbol_extras = NULL; +#endif #ifndef USE_MMAP #ifdef darwin_HOST_OS From git at git.haskell.org Mon Oct 13 08:22:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 13 Oct 2014 08:22:35 +0000 (UTC) Subject: [commit: ghc] master: Update `time` submodule to address linker issue (c375de0) Message-ID: <20141013082235.6F4C93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c375de0193f66df55fa765a7562f2c1a3d2dba93/ghc >--------------------------------------------------------------- commit c375de0193f66df55fa765a7562f2c1a3d2dba93 Author: Herbert Valerio Riedel Date: Mon Oct 13 09:56:28 2014 +0200 Update `time` submodule to address linker issue See also https://github.com/haskell/time/issues/2 However, while the `time-1.5` package now loads successful in GHCi, the linker warnings as reported in #9297 occur (which let the testsuite fail for a dozen of testcases due to this additional output) >--------------------------------------------------------------- c375de0193f66df55fa765a7562f2c1a3d2dba93 libraries/time | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/time b/libraries/time index 892717c..991e6be 160000 --- a/libraries/time +++ b/libraries/time @@ -1 +1 @@ -Subproject commit 892717c506ebbeadf8b9f1f8eecf5e145cfed47e +Subproject commit 991e6be84974b02d7f968601ab02d2e2b3e14190 From git at git.haskell.org Mon Oct 13 10:24:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 13 Oct 2014 10:24:51 +0000 (UTC) Subject: [commit: ghc] master: Compiler performance benchmark for #9675 (05f962d) Message-ID: <20141013102451.96AA33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/05f962df2ba028fd304fdada9e68e7199822cbf0/ghc >--------------------------------------------------------------- commit 05f962df2ba028fd304fdada9e68e7199822cbf0 Author: Joachim Breitner Date: Mon Oct 13 11:27:17 2014 +0200 Compiler performance benchmark for #9675 so that whoever improves the situation can feel good about it. >--------------------------------------------------------------- 05f962df2ba028fd304fdada9e68e7199822cbf0 testsuite/tests/perf/compiler/T9675.hs | 103 +++++++++++++++++++++++++++++++++ testsuite/tests/perf/compiler/all.T | 18 ++++++ 2 files changed, 121 insertions(+) diff --git a/testsuite/tests/perf/compiler/T9675.hs b/testsuite/tests/perf/compiler/T9675.hs new file mode 100644 index 0000000..6ea64de --- /dev/null +++ b/testsuite/tests/perf/compiler/T9675.hs @@ -0,0 +1,103 @@ +module T6975 where +data Foo = Foo + { field1 :: Int -> Int + , field2 :: Int -> Int + , field3 :: Int -> Int + , field4 :: Int -> Int + , field5 :: Int -> Int + , field6 :: Int -> Int + , field7 :: Int -> Int + , field8 :: Int -> Int + , field9 :: Int -> Int + , field10 :: Int -> Int + , field11 :: Int -> Int + , field12 :: Int -> Int + , field13 :: Int -> Int + , field14 :: Int -> Int + , field15 :: Int -> Int + , field16 :: Int -> Int + , field17 :: Int -> Int + , field18 :: Int -> Int + , field19 :: Int -> Int + , field20 :: Int -> Int + , field21 :: Int -> Int + , field22 :: Int -> Int + , field23 :: Int -> Int + , field24 :: Int -> Int + , field25 :: Int -> Int + , field26 :: Int -> Int + , field27 :: Int -> Int + , field28 :: Int -> Int + , field29 :: Int -> Int + , field30 :: Int -> Int + , field31 :: Int -> Int + , field32 :: Int -> Int + , field33 :: Int -> Int + , field34 :: Int -> Int + , field35 :: Int -> Int + , field36 :: Int -> Int + , field37 :: Int -> Int + , field38 :: Int -> Int + , field39 :: Int -> Int + , field40 :: Int -> Int + , field41 :: Int -> Int + , field42 :: Int -> Int + , field43 :: Int -> Int + , field44 :: Int -> Int + , field45 :: Int -> Int + , field46 :: Int -> Int + , field47 :: Int -> Int + , field48 :: Int -> Int + , field49 :: Int -> Int + , field50 :: Int -> Int + , field51 :: Int -> Int + , field52 :: Int -> Int + , field53 :: Int -> Int + , field54 :: Int -> Int + , field55 :: Int -> Int + , field56 :: Int -> Int + , field57 :: Int -> Int + , field58 :: Int -> Int + , field59 :: Int -> Int + , field60 :: Int -> Int + , field61 :: Int -> Int + , field62 :: Int -> Int + , field63 :: Int -> Int + , field64 :: Int -> Int + , field65 :: Int -> Int + , field66 :: Int -> Int + , field67 :: Int -> Int + , field68 :: Int -> Int + , field69 :: Int -> Int + , field70 :: Int -> Int + , field71 :: Int -> Int + , field72 :: Int -> Int + , field73 :: Int -> Int + , field74 :: Int -> Int + , field75 :: Int -> Int + , field76 :: Int -> Int + , field77 :: Int -> Int + , field78 :: Int -> Int + , field79 :: Int -> Int + , field80 :: Int -> Int + , field81 :: Int -> Int + , field82 :: Int -> Int + , field83 :: Int -> Int + , field84 :: Int -> Int + , field85 :: Int -> Int + , field86 :: Int -> Int + , field87 :: Int -> Int + , field88 :: Int -> Int + , field89 :: Int -> Int + , field90 :: Int -> Int + , field91 :: Int -> Int + , field92 :: Int -> Int + , field93 :: Int -> Int + , field94 :: Int -> Int + , field95 :: Int -> Int + , field96 :: Int -> Int + , field97 :: Int -> Int + , field98 :: Int -> Int + , field99 :: Int -> Int + , field100 :: Int -> Int + } diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 1afcf88..1de224e 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -492,3 +492,21 @@ test('T9020', # 2014-09-10: 785871680 post-AMP-cleanup ], compile,['']) + +test('T9675', + [ only_ways(['optasm']), + compiler_stats_num_field('max_bytes_used', + [(wordsize(64), 25822728, 15), + # 2014-10-13 25822728 + ]), + compiler_stats_num_field('peak_megabytes_allocated', + [(wordsize(64), 62, 1), + # 2014-10-13 62 + ]), + compiler_stats_num_field('bytes allocated', + [(wordsize(64), 601441240, 1) + # 2014-10-13 601441240 + ]), + ], + compile, + ['']) From git at git.haskell.org Mon Oct 13 12:50:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 13 Oct 2014 12:50:00 +0000 (UTC) Subject: [commit: ghc] master: Adjust T9675 baseline numbers based on ghc-speed (23da971) Message-ID: <20141013125000.100963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/23da971fd6694a1fcb323f797a65c8cd976b7cc1/ghc >--------------------------------------------------------------- commit 23da971fd6694a1fcb323f797a65c8cd976b7cc1 Author: Joachim Breitner Date: Mon Oct 13 13:49:55 2014 +0200 Adjust T9675 baseline numbers based on ghc-speed although I obtained them originally from a clean validate tree on my laptop, they did not match what I found on the build bot host. >--------------------------------------------------------------- 23da971fd6694a1fcb323f797a65c8cd976b7cc1 testsuite/tests/perf/compiler/all.T | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 1de224e..9ef98ac 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -496,16 +496,16 @@ test('T9020', test('T9675', [ only_ways(['optasm']), compiler_stats_num_field('max_bytes_used', - [(wordsize(64), 25822728, 15), - # 2014-10-13 25822728 + [(wordsize(64), 29596552, 15), + # 2014-10-13 29596552 ]), compiler_stats_num_field('peak_megabytes_allocated', - [(wordsize(64), 62, 1), - # 2014-10-13 62 + [(wordsize(64), 66, 4), + # 2014-10-13 66 ]), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 601441240, 1) - # 2014-10-13 601441240 + [(wordsize(64), 544489040, 10) + # 2014-10-13 544489040 ]), ], compile, From git at git.haskell.org Mon Oct 13 13:20:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 13 Oct 2014 13:20:26 +0000 (UTC) Subject: [commit: ghc] master: seqDmdType needs to seq the DmdEnv as well (d9db81f) Message-ID: <20141013132026.D552E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d9db81f4ed8ca6e7262f84347174d6b0e2e9a76a/ghc >--------------------------------------------------------------- commit d9db81f4ed8ca6e7262f84347174d6b0e2e9a76a Author: Joachim Breitner Date: Mon Oct 13 12:44:56 2014 +0200 seqDmdType needs to seq the DmdEnv as well otherwise this can retain large lazy calculations. This fixed one space leak pointed out in #9675. >--------------------------------------------------------------- d9db81f4ed8ca6e7262f84347174d6b0e2e9a76a compiler/basicTypes/Demand.lhs | 8 ++++++-- testsuite/tests/perf/compiler/all.T | 6 ++++-- 2 files changed, 10 insertions(+), 4 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index ed055b5..2aa25ce 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1155,8 +1155,12 @@ ensureArgs n d | n == depth = d -- See [Nature of result demand] seqDmdType :: DmdType -> () -seqDmdType (DmdType _env ds res) = - {- ??? env `seq` -} seqDemandList ds `seq` seqDmdResult res `seq` () +seqDmdType (DmdType env ds res) = + seqDmdEnv env `seq` seqDemandList ds `seq` seqDmdResult res `seq` () + +seqDmdEnv :: DmdEnv -> () +seqDmdEnv env = seqDemandList (varEnvElts env) + splitDmdTy :: DmdType -> (Demand, DmdType) -- Split off one function argument diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 9ef98ac..ad91b91 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -496,12 +496,14 @@ test('T9020', test('T9675', [ only_ways(['optasm']), compiler_stats_num_field('max_bytes_used', - [(wordsize(64), 29596552, 15), + [(wordsize(64), 26570896, 15), # 2014-10-13 29596552 + # 2014-10-13 26570896 seq the DmdEnv in seqDmdType as well ]), compiler_stats_num_field('peak_megabytes_allocated', - [(wordsize(64), 66, 4), + [(wordsize(64), 58, 4), # 2014-10-13 66 + # 2014-10-13 58 seq the DmdEnv in seqDmdType as well ]), compiler_stats_num_field('bytes allocated', [(wordsize(64), 544489040, 10) From git at git.haskell.org Mon Oct 13 14:38:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 13 Oct 2014 14:38:07 +0000 (UTC) Subject: [commit: ghc] master: Update more performance numbers due to stricter seqDmdType (3575109) Message-ID: <20141013143807.D4A453A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3575109bebf4269c1fd02550b6bf9580f92b0ef4/ghc >--------------------------------------------------------------- commit 3575109bebf4269c1fd02550b6bf9580f92b0ef4 Author: Joachim Breitner Date: Mon Oct 13 16:37:15 2014 +0200 Update more performance numbers due to stricter seqDmdType including T9675 itself. Maybe its memory behaviour is too spiky for max_bytes_used and peak_megabytes_allocated to be used sensibly at all. >--------------------------------------------------------------- 3575109bebf4269c1fd02550b6bf9580f92b0ef4 testsuite/tests/perf/compiler/all.T | 15 ++++++++++----- 1 file changed, 10 insertions(+), 5 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index ad91b91..171105f 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -171,7 +171,7 @@ test('T4801', # expected value: 58 (amd64/OS X) # 13/01/2014 - 70 (wordsize(32), 30, 20), - (wordsize(64), 62, 20)]), + (wordsize(64), 55, 20)]), # prev: 50 (amd64/Linux) # 19/10/2012: 64 (amd64/Linux) # (^ REASON UNKNOWN!) @@ -181,6 +181,7 @@ test('T4801', # (^ 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), @@ -234,7 +235,7 @@ test('T3064', # expected value: 14 (x86/Linux 28-06-2012): # 2013-11-13: 18 (x86/Windows, 64bit machine) # 2014-01-22: 23 (x86/Linux) - (wordsize(64), 42, 20)]), + (wordsize(64), 38, 20)]), # (amd64/Linux): 18 # (amd64/Linux) 2012-02-07: 26 # (amd64/Linux) 2013-02-12: 23; increased range to 10% @@ -244,6 +245,7 @@ test('T3064', # depending on whether the old .hi file exists # (amd64/Linux) 2013-09-11: 37; better arity analysis (weird) # (amd64/Linux) (09/09/2014): 42, AMP changes (larger interfaces, more loading) + # (amd64/Linux) 2014-10-13: 38: Stricter seqDmdType compiler_stats_num_field('bytes allocated', [(wordsize(32), 162457940, 10), @@ -271,7 +273,7 @@ test('T3064', #(some date): 5511604 # 2013-11-13: 7218200 (x86/Windows, 64bit machine) # 2014-04-04: 11202304 (x86/Windows, 64bit machine) - (wordsize(64), 18744992, 20)]), + (wordsize(64), 13251728, 20)]), # (amd64/Linux, intree) (28/06/2011): 4032024 # (amd64/Linux, intree) (07/02/2013): 9819288 # (amd64/Linux) (14/02/2013): 8687360 @@ -285,6 +287,7 @@ test('T3064', # (amd64/Linux) (09/09/2014): 24357392, AMP changes (larger interfaces, more loading) # (amd64/Linux) (14/09/2014): 16053888, BPP changes (more NoImplicitPrelude in base) # (amd64/Linux) (19/09/2014): 18744992, unknown + # (amd64/Linux) 2014-10-13: 13251728, Stricter seqDmdType only_ways(['normal']) ], @@ -496,14 +499,16 @@ test('T9020', test('T9675', [ only_ways(['optasm']), compiler_stats_num_field('max_bytes_used', - [(wordsize(64), 26570896, 15), + [(wordsize(64), 18582472, 15), # 2014-10-13 29596552 # 2014-10-13 26570896 seq the DmdEnv in seqDmdType as well + # 2014-10-13 18582472 different machines giving different results.. ]), compiler_stats_num_field('peak_megabytes_allocated', - [(wordsize(64), 58, 4), + [(wordsize(64), 49, 4), # 2014-10-13 66 # 2014-10-13 58 seq the DmdEnv in seqDmdType as well + # 2014-10-13 49 different machines giving different results... ]), compiler_stats_num_field('bytes allocated', [(wordsize(64), 544489040, 10) From git at git.haskell.org Mon Oct 13 17:23:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 13 Oct 2014 17:23:32 +0000 (UTC) Subject: [commit: ghc] master: T9675: Allow Much wider range of values (f3ae936) Message-ID: <20141013172332.D8DEF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f3ae936e04dda1b28b0fa8f4c65a99407164ee99/ghc >--------------------------------------------------------------- commit f3ae936e04dda1b28b0fa8f4c65a99407164ee99 Author: Joachim Breitner Date: Mon Oct 13 19:20:44 2014 +0200 T9675: Allow Much wider range of values to include at least what?s observed on ghc-speed and my laptop, and hopefully also Harbormaster. >--------------------------------------------------------------- f3ae936e04dda1b28b0fa8f4c65a99407164ee99 testsuite/tests/perf/compiler/all.T | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 171105f..b27777e 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -499,16 +499,18 @@ test('T9020', test('T9675', [ only_ways(['optasm']), compiler_stats_num_field('max_bytes_used', - [(wordsize(64), 18582472, 15), + [(wordsize(64), 22220552, 25), # 2014-10-13 29596552 # 2014-10-13 26570896 seq the DmdEnv in seqDmdType as well # 2014-10-13 18582472 different machines giving different results.. + # 2014-10-13 22220552 use the mean ]), compiler_stats_num_field('peak_megabytes_allocated', - [(wordsize(64), 49, 4), + [(wordsize(64), 53, 15), # 2014-10-13 66 # 2014-10-13 58 seq the DmdEnv in seqDmdType as well # 2014-10-13 49 different machines giving different results... + # 2014-10-13 53 use the mean ]), compiler_stats_num_field('bytes allocated', [(wordsize(64), 544489040, 10) From git at git.haskell.org Mon Oct 13 21:34:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 13 Oct 2014 21:34:23 +0000 (UTC) Subject: [commit: ghc] master: Actually put in new perf number for T4801 (f0af3d8) Message-ID: <20141013213423.1BFD03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f0af3d852207147202bebdb3a607fc5cef6d550e/ghc >--------------------------------------------------------------- commit f0af3d852207147202bebdb3a607fc5cef6d550e Author: Joachim Breitner Date: Mon Oct 13 23:33:45 2014 +0200 Actually put in new perf number for T4801 which I just put it in comments. Thanks Yuras for noticing, and sorry for the noise. >--------------------------------------------------------------- f0af3d852207147202bebdb3a607fc5cef6d550e testsuite/tests/perf/compiler/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index b27777e..3259857 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -171,7 +171,7 @@ test('T4801', # expected value: 58 (amd64/OS X) # 13/01/2014 - 70 (wordsize(32), 30, 20), - (wordsize(64), 55, 20)]), + (wordsize(64), 48, 20)]), # prev: 50 (amd64/Linux) # 19/10/2012: 64 (amd64/Linux) # (^ REASON UNKNOWN!) From git at git.haskell.org Tue Oct 14 12:39:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 14 Oct 2014 12:39:23 +0000 (UTC) Subject: [commit: ghc] master: Fix comment typos: lll -> ll, THe -> The (8376027) Message-ID: <20141014123923.131853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8376027dc2b7a9075a5a4306869735cc6691d89d/ghc >--------------------------------------------------------------- commit 8376027dc2b7a9075a5a4306869735cc6691d89d Author: Jan Stolarek Date: Tue Oct 14 14:38:16 2014 +0200 Fix comment typos: lll -> ll, THe -> The >--------------------------------------------------------------- 8376027dc2b7a9075a5a4306869735cc6691d89d compiler/deSugar/DsBinds.lhs | 2 +- compiler/rename/RnEnv.lhs | 2 +- compiler/simplCore/OccurAnal.lhs | 2 +- compiler/simplCore/Simplify.lhs | 2 +- compiler/typecheck/TcInstDcls.lhs | 2 +- compiler/typecheck/TcPat.lhs | 2 +- compiler/typecheck/TcRnTypes.lhs | 2 +- compiler/typecheck/TcSMonad.lhs | 2 +- 8 files changed, 8 insertions(+), 8 deletions(-) diff --git a/compiler/deSugar/DsBinds.lhs b/compiler/deSugar/DsBinds.lhs index a8d37a4..8c2541c 100644 --- a/compiler/deSugar/DsBinds.lhs +++ b/compiler/deSugar/DsBinds.lhs @@ -331,7 +331,7 @@ Notice (a) g has a different number of type variables to f, so we must variables of the particular RHS. Tiresome. Why got to this trouble? It's a common case, and it removes the -quadratic-sized tuple desugaring. Less clutter, hopefullly faster +quadratic-sized tuple desugaring. Less clutter, hopefully faster compilation, especially in a case where there are a *lot* of bindings. diff --git a/compiler/rename/RnEnv.lhs b/compiler/rename/RnEnv.lhs index b9bfcce..65da421 100644 --- a/compiler/rename/RnEnv.lhs +++ b/compiler/rename/RnEnv.lhs @@ -519,7 +519,7 @@ There is another wrinkle. With TH and -XDataKinds, consider After splicing, but before renaming we get this: data Nat_77{tc} = Zero_78{d} data T_79{tc} = MkT_80{d} (Proxy 'Zero_78{tc}) |] ) -THe occurrence of 'Zero in the data type for T has the right unique, +The occurrence of 'Zero in the data type for T has the right unique, but it has a TcClsName name-space in its OccName. (This is set by the ctxt_ns argument of Convert.thRdrName.) When we check that is in scope in the GlobalRdrEnv, we need to look up the DataName namespace diff --git a/compiler/simplCore/OccurAnal.lhs b/compiler/simplCore/OccurAnal.lhs index 3477073..0fbd2ca 100644 --- a/compiler/simplCore/OccurAnal.lhs +++ b/compiler/simplCore/OccurAnal.lhs @@ -1728,7 +1728,7 @@ binder-swap in OccAnal: Notice that because MkT is strict, x is marked "evaluated". But to eliminate the last case, we must either make sure that x (as well as - x1) has unfolding MkT y1. THe straightforward thing to do is to do + x1) has unfolding MkT y1. The straightforward thing to do is to do the binder-swap. So this whole note is a no-op. It's fixed by doing the binder-swap in OccAnal because we can do the diff --git a/compiler/simplCore/Simplify.lhs b/compiler/simplCore/Simplify.lhs index ae2c6ea..f044be5 100644 --- a/compiler/simplCore/Simplify.lhs +++ b/compiler/simplCore/Simplify.lhs @@ -316,7 +316,7 @@ Nota bene: 2. It assumes that the binder type is lifted. - 3. It does not check for pre-inline-unconditionallly; + 3. It does not check for pre-inline-unconditionally; that should have been done already. \begin{code} diff --git a/compiler/typecheck/TcInstDcls.lhs b/compiler/typecheck/TcInstDcls.lhs index 366f65f..985530a 100644 --- a/compiler/typecheck/TcInstDcls.lhs +++ b/compiler/typecheck/TcInstDcls.lhs @@ -1471,7 +1471,7 @@ So for the above example we generate: $cop2 = -Note carefullly: +Note carefully: * We *copy* any INLINE pragma from the default method $dmop1 to the instance $cop1. Otherwise we'll just inline the former in the diff --git a/compiler/typecheck/TcPat.lhs b/compiler/typecheck/TcPat.lhs index c4c3f88..2f86f37 100644 --- a/compiler/typecheck/TcPat.lhs +++ b/compiler/typecheck/TcPat.lhs @@ -184,7 +184,7 @@ be a subset of the *quantified type variables* of the signatures, for two reason * With kind polymorphism a signature like f :: forall f a. f a -> f a - may actuallly give rise to + may actually give rise to f :: forall k. forall (f::k -> *) (a:k). f a -> f a So the sig_tvs will be [k,f,a], but only f,a are scoped. NB: the scoped ones are not necessarily the *inital* ones! diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index 0900ed0..22765a7 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -1000,7 +1000,7 @@ We can't require *equal* kinds, because Note [Kind orientation for CFunEqCan] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ For (F xis ~ rhs) we require that kind(lhs) is a subkind of kind(rhs). -This reallly only maters when rhs is an Open type variable (since only type +This really only maters when rhs is an Open type variable (since only type variables have Open kinds): F ty ~ (a:Open) which can happen, say, from diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index 4cb679d..034c7a8 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -396,7 +396,7 @@ Type-family equations, of form (ev : F tys ~ ty), live in four places * The inert_solved_funeqs. These are all "solved" goals (see Note [Solved constraints]), the result of using a top-level type-family instance. - * THe inert_funeqs are un-solved but fully processed and in the InertCans. + * The inert_funeqs are un-solved but fully processed and in the InertCans. \begin{code} From git at git.haskell.org Tue Oct 14 12:40:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 14 Oct 2014 12:40:52 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: More progress (48e51ab) Message-ID: <20141014124052.B7AFB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/48e51abc6ad2aa5311f6e370278a6623a4cafb2c/ghc >--------------------------------------------------------------- commit 48e51abc6ad2aa5311f6e370278a6623a4cafb2c Author: Simon Peyton Jones Date: Tue Oct 14 13:40:44 2014 +0100 More progress >--------------------------------------------------------------- 48e51abc6ad2aa5311f6e370278a6623a4cafb2c compiler/typecheck/Flattening-notes | 124 ++++++++++++++++++ compiler/typecheck/TcCanonical.lhs | 25 ++-- compiler/typecheck/TcInteract.lhs | 2 +- compiler/typecheck/TcRnTypes.lhs | 2 +- compiler/typecheck/TcSMonad.lhs | 142 ++++++++++++--------- compiler/typecheck/TcType.lhs | 6 +- .../indexed-types/should_compile/T3017.stderr | 2 +- .../indexed-types/should_compile/T3208b.stderr | 7 +- .../tests/indexed-types/should_compile/T4494.hs | 20 +++ testsuite/tests/indexed-types/should_fail/T8227.hs | 23 ++-- testsuite/tests/typecheck/should_fail/T5684.stderr | 24 ++-- testsuite/tests/typecheck/should_fail/T8142.stderr | 19 ++- 12 files changed, 284 insertions(+), 112 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 48e51abc6ad2aa5311f6e370278a6623a4cafb2c From git at git.haskell.org Tue Oct 14 19:08:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 14 Oct 2014 19:08:23 +0000 (UTC) Subject: [commit: ghc] master: Add a configure test for pthread_setname_np (4b69d96) Message-ID: <20141014190823.DCF0E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4b69d96b3d2758bbc06c58ea44a975c6e08d7400/ghc >--------------------------------------------------------------- commit 4b69d96b3d2758bbc06c58ea44a975c6e08d7400 Author: Simon Marlow Date: Mon Oct 13 18:30:30 2014 +0100 Add a configure test for pthread_setname_np >--------------------------------------------------------------- 4b69d96b3d2758bbc06c58ea44a975c6e08d7400 configure.ac | 16 ++++++++++++++++ rts/posix/OSThreads.c | 2 ++ 2 files changed, 18 insertions(+) diff --git a/configure.ac b/configure.ac index f992c0d..7bd599f 100644 --- a/configure.ac +++ b/configure.ac @@ -896,6 +896,22 @@ AC_TRY_LINK_FUNC(printf\$LDBLStub, [Define to 1 if we have printf$LDBLStub (Apple Mac OS >= 10.4, PPC).]) ]) +dnl ** pthread_setname_np is a recent addition to glibc, and OS X has +dnl a different single-argument version. +AC_CHECK_LIB(pthread, pthread_setname_np) +AC_MSG_CHECKING(for pthread_setname_np) +AC_TRY_LINK( +[ +#define _GNU_SOURCE +#include +], +[pthread_setname_np(pthread_self(), "name");], + AC_MSG_RESULT(yes) + AC_DEFINE([HAVE_PTHREAD_SETNAME_NP], [1], + [Define to 1 if you have the glibc version of pthread_setname_np]), + AC_MSG_RESULT(no) +) + dnl ** check for eventfd which is needed by the I/O manager AC_CHECK_HEADERS([sys/eventfd.h]) AC_CHECK_FUNCS([eventfd]) diff --git a/rts/posix/OSThreads.c b/rts/posix/OSThreads.c index e880b89..fb6d9d4 100644 --- a/rts/posix/OSThreads.c +++ b/rts/posix/OSThreads.c @@ -135,7 +135,9 @@ createOSThread (OSThreadId* pId, char *name, int result = pthread_create(pId, NULL, (void *(*)(void *))startProc, param); if (!result) { pthread_detach(*pId); +#if HAVE_PTHREAD_SETNAME_NP pthread_setname_np(*pId, name); +#endif } return result; } From git at git.haskell.org Wed Oct 15 08:56:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 15 Oct 2014 08:56:07 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: More progress (9d55484) Message-ID: <20141015085607.7CF8B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/9d554841fe63e5f73ed9c0517eaef0135b944037/ghc >--------------------------------------------------------------- commit 9d554841fe63e5f73ed9c0517eaef0135b944037 Author: Simon Peyton Jones Date: Wed Oct 15 09:56:02 2014 +0100 More progress >--------------------------------------------------------------- 9d554841fe63e5f73ed9c0517eaef0135b944037 compiler/typecheck/TcCanonical.lhs | 8 +- compiler/typecheck/TcInteract.lhs | 73 +++++++------- compiler/typecheck/TcMType.lhs | 2 +- compiler/typecheck/TcSMonad.lhs | 192 ++++++++++++++++++------------------- compiler/typecheck/TcSimplify.lhs | 73 +++++++------- 5 files changed, 182 insertions(+), 166 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 9d554841fe63e5f73ed9c0517eaef0135b944037 From git at git.haskell.org Wed Oct 15 16:08:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 15 Oct 2014 16:08:49 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Checkpoint with each CFunEqCan having a distinct fmv (ae0ef57) Message-ID: <20141015160849.0880D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/ae0ef5784d331a7a2bda10c2342eff96eed0d2d8/ghc >--------------------------------------------------------------- commit ae0ef5784d331a7a2bda10c2342eff96eed0d2d8 Author: Simon Peyton Jones Date: Wed Oct 15 12:34:47 2014 +0100 Checkpoint with each CFunEqCan having a distinct fmv >--------------------------------------------------------------- ae0ef5784d331a7a2bda10c2342eff96eed0d2d8 compiler/typecheck/TcCanonical.lhs | 8 +- compiler/typecheck/TcInteract.lhs | 49 ++--- compiler/typecheck/TcRnMonad.lhs | 8 +- compiler/typecheck/TcRnTypes.lhs | 9 +- compiler/typecheck/TcSMonad.lhs | 202 +++++++++++++-------- compiler/typecheck/TcSimplify.lhs | 30 +-- .../indexed-types/should_compile/T3017.stderr | 2 +- .../indexed-types/should_compile/T3208b.stderr | 7 +- .../indexed-types/should_compile/T8889.stderr | 2 +- 9 files changed, 186 insertions(+), 131 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 ae0ef5784d331a7a2bda10c2342eff96eed0d2d8 From git at git.haskell.org Wed Oct 15 16:08:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 15 Oct 2014 16:08:51 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Finally getting there (22b3649) Message-ID: <20141015160851.A70A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/22b36492fba7b86a5fd2ab8277dd9cd33c7f6b2f/ghc >--------------------------------------------------------------- commit 22b36492fba7b86a5fd2ab8277dd9cd33c7f6b2f Author: Simon Peyton Jones Date: Wed Oct 15 17:07:12 2014 +0100 Finally getting there >--------------------------------------------------------------- 22b36492fba7b86a5fd2ab8277dd9cd33c7f6b2f compiler/typecheck/Flattening-notes | 31 ++++++++++ compiler/typecheck/TcBinds.lhs | 23 ++++--- compiler/typecheck/TcCanonical.lhs | 36 +++++------ compiler/typecheck/TcErrors.lhs | 6 +- compiler/typecheck/TcRnTypes.lhs | 2 +- compiler/typecheck/TcSMonad.lhs | 71 ++++++++++++---------- testsuite/tests/deriving/should_fail/T9071.stderr | 2 +- .../tests/deriving/should_fail/T9071_2.stderr | 2 +- .../tests/ghc-api/apirecomp001/apirecomp001.stderr | 12 ++-- .../indexed-types/should_compile/T3208b.stderr | 7 +-- .../indexed-types/should_compile/T8889.stderr | 2 +- .../indexed-types/should_fail/SimpleFail16.stderr | 3 +- .../tests/indexed-types/should_fail/T2544.stderr | 21 +++++-- .../tests/indexed-types/should_fail/T2627b.stderr | 4 +- .../tests/indexed-types/should_fail/T4093a.hs | 27 ++++++++ .../tests/indexed-types/should_fail/T4174.stderr | 27 +++++++- .../tests/indexed-types/should_fail/T4179.stderr | 6 +- .../tests/indexed-types/should_fail/T6123.stderr | 6 +- .../tests/indexed-types/should_fail/T7729a.stderr | 16 +++-- testsuite/tests/indexed-types/should_fail/T8227.hs | 0 .../tests/indexed-types/should_fail/T8227.stderr | 25 ++++++-- .../tests/indexed-types/should_fail/T9036.stderr | 4 +- testsuite/tests/parser/should_compile/T2245.stderr | 10 +-- testsuite/tests/rebindable/rebindable6.stderr | 12 ++-- testsuite/tests/typecheck/should_compile/T8474.hs | 2 + testsuite/tests/typecheck/should_fail/T5300.stderr | 4 +- testsuite/tests/typecheck/should_fail/T5853.stderr | 25 ++++---- testsuite/tests/typecheck/should_fail/T8142.stderr | 23 ++----- testsuite/tests/typecheck/should_fail/T8883.stderr | 2 +- testsuite/tests/typecheck/should_fail/T9305.stderr | 2 +- .../tests/typecheck/should_fail/tcfail019.stderr | 2 +- .../tests/typecheck/should_fail/tcfail067.stderr | 4 +- .../tests/typecheck/should_fail/tcfail072.stderr | 4 +- .../tests/typecheck/should_fail/tcfail171.stderr | 4 +- .../tests/typecheck/should_fail/tcfail204.stderr | 7 ++- 35 files changed, 271 insertions(+), 163 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 22b36492fba7b86a5fd2ab8277dd9cd33c7f6b2f From git at git.haskell.org Thu Oct 16 07:45:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 16 Oct 2014 07:45:39 +0000 (UTC) Subject: [commit: ghc] master: Make Data.List.Inits fast (cde3a77) Message-ID: <20141016074539.9F8FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cde3a77f9703966145cae481ee35f52dcca2cf7d/ghc >--------------------------------------------------------------- commit cde3a77f9703966145cae481ee35f52dcca2cf7d Author: David Feuer Date: Thu Oct 16 09:42:27 2014 +0200 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 >--------------------------------------------------------------- cde3a77f9703966145cae481ee35f52dcca2cf7d libraries/base/Data/OldList.hs | 60 +++++++++++++++++++++++++++++++++++++++--- libraries/base/tests/all.T | 1 + libraries/base/tests/inits.hs | 28 ++++++++++++++++++++ 3 files changed, 86 insertions(+), 3 deletions(-) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index 9b6a431..ad2c510 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -208,6 +208,7 @@ module Data.OldList ) where import Data.Maybe +import Data.Bits ( (.&.) ) import Data.Char ( isSpace ) import Data.Ord ( comparing ) import Data.Tuple ( fst, snd ) @@ -767,11 +768,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, @@ -1130,3 +1136,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 diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T index 6520b21..f80f542 100644 --- a/libraries/base/tests/all.T +++ b/libraries/base/tests/all.T @@ -23,6 +23,7 @@ test('readInteger001', normal, compile_and_run, ['']) test('readFixed001', normal, compile_and_run, ['']) test('lex001', normal, compile_and_run, ['']) test('take001', extra_run_opts('1'), compile_and_run, ['']) +test('inits', normal, compile_and_run, ['']) test('genericNegative001', extra_run_opts('-1'), compile_and_run, ['']) test('ix001', normal, compile_and_run, ['']) diff --git a/libraries/base/tests/inits.hs b/libraries/base/tests/inits.hs new file mode 100644 index 0000000..4474769 --- /dev/null +++ b/libraries/base/tests/inits.hs @@ -0,0 +1,28 @@ +{-# LANGUAGE RankNTypes #-} +module Main (main) where + +import Data.List + +-- A simple implementation of inits that should be obviously correct. +{-# NOINLINE initsR #-} +initsR :: [a] -> [[a]] +initsR = map reverse . scanl (flip (:)) [] + +-- The inits implementation added in 7.10 uses a queue rotated around +-- powers of 2, starting the rotation only at size 255, so we want to check +-- around powers of 2 and around the switch. +ranges :: [Int] +ranges = [0..20] ++ [252..259] ++ [508..515] + +simple :: (forall a . [a] -> [[a]]) -> [[[Int]]] +simple impl = [impl [1..n] | n <- ranges] + +-- We want inits (xs ++ undefined) = inits xs ++ undefined +laziness :: Bool +laziness = [take (n+1) (inits $ [1..n] ++ undefined) | n <- ranges] + == simple inits + +main :: IO () +main | simple initsR /= simple inits = error "inits failed simple test" + | not laziness = error "inits failed laziness test" + | otherwise = return () From git at git.haskell.org Thu Oct 16 07:45:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 16 Oct 2014 07:45:42 +0000 (UTC) Subject: [commit: ghc] master: Make tails a good producer (#9670) (7e73595) Message-ID: <20141016074542.348AA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7e735950a44f7f3c34319ea65631e11e52eb68a7/ghc >--------------------------------------------------------------- commit 7e735950a44f7f3c34319ea65631e11e52eb68a7 Author: David Feuer Date: Thu Oct 16 09:44:25 2014 +0200 Make tails a good producer (#9670) Reviewed By: nomeata, austin Differential Revision: https://phabricator.haskell.org/D325 >--------------------------------------------------------------- 7e735950a44f7f3c34319ea65631e11e52eb68a7 libraries/base/Data/OldList.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index ad2c510..ff85154 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -787,9 +787,12 @@ inits = map toListSB . scanl' snocSB emptySB -- Note that 'tails' has the following strictness property: -- @tails _|_ = _|_ : _|_@ tails :: [a] -> [[a]] -tails xs = xs : case xs of - [] -> [] - _ : xs' -> tails xs' +{-# INLINABLE tails #-} +tails lst = build (\c n -> + let tailsGo xs = xs `c` case xs of + [] -> n + _ : xs' -> tailsGo xs' + in tailsGo lst) -- | The 'subsequences' function returns the list of all subsequences of the argument. -- From git at git.haskell.org Thu Oct 16 07:49:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 16 Oct 2014 07:49:42 +0000 (UTC) Subject: [commit: ghc] master: Declare official GitHub home of libraries/deepseq (d786781) Message-ID: <20141016074942.7EAFE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d7867810d5ffd08c77c30e928bb3dca21beae0b9/ghc >--------------------------------------------------------------- commit d7867810d5ffd08c77c30e928bb3dca21beae0b9 Author: Herbert Valerio Riedel Date: Thu Oct 16 09:47:31 2014 +0200 Declare official GitHub home of libraries/deepseq Effective immediately, `deepseq` is maintained officially by the core-library-comittee. Moreover, pushing to libraries/deepseq requires pushing to ssh://git at github.com/haskell/deepseq.git from now on. [skip ci] >--------------------------------------------------------------- d7867810d5ffd08c77c30e928bb3dca21beae0b9 packages | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/packages b/packages index e6db883..80b0235 100644 --- a/packages +++ b/packages @@ -56,7 +56,7 @@ libraries/binary - - https:/ libraries/bytestring - - https://github.com/haskell/bytestring.git libraries/Cabal - - https://github.com/haskell/cabal.git libraries/containers - - https://github.com/haskell/containers.git -libraries/deepseq - - - +libraries/deepseq - - ssh://git at github.com/haskell/deepseq.git 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 From git at git.haskell.org Thu Oct 16 14:24:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 16 Oct 2014 14:24:13 +0000 (UTC) Subject: [commit: ghc] wip/T8584: universially-bound tyvars are in scope when renaming existentially-bound tyvars in a pattern synonym signature (09a6b89) Message-ID: <20141016142413.5C20D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/09a6b895b8ba9431566f4ef339d6cc4e7d44a12d/ghc >--------------------------------------------------------------- commit 09a6b895b8ba9431566f4ef339d6cc4e7d44a12d 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 >--------------------------------------------------------------- 09a6b895b8ba9431566f4ef339d6cc4e7d44a12d 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 f649e27..666a270 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -56,6 +56,7 @@ import Data.List ( partition, sort ) import Maybes ( orElse ) import Control.Monad import Data.Traversable ( traverse ) +import Util ( filterOut ) \end{code} -- ToDo: Put the annotations into the monad, so that they arrive in the proper @@ -855,10 +856,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 Thu Oct 16 14:24:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 16 Oct 2014 14:24:15 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add TcPatSynInfo as a separate type (same pattern as PatSynBind being a separate type) (4288b32) Message-ID: <20141016142415.F1F953A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/4288b327f66cb8d8764e26f81101645a331efe8a/ghc >--------------------------------------------------------------- commit 4288b327f66cb8d8764e26f81101645a331efe8a 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) >--------------------------------------------------------------- 4288b327f66cb8d8764e26f81101645a331efe8a 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 e92c1ec..5e5e17b 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 @@ -1319,10 +1317,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 c044e31..7ca4fdb 100644 --- a/compiler/typecheck/TcPat.lhs +++ b/compiler/typecheck/TcPat.lhs @@ -15,7 +15,8 @@ TcPat: Typechecking patterns -- for details module TcPat ( tcLetPat, TcSigFun, TcPragFun - , TcSigInfo(..), findScopedTyVars + , TcSigInfo(..), TcPatSynInfo(..) + , findScopedTyVars , LetBndrSpec(..), addInlinePrags, warnPrags , tcPat, tcPats, newNoSigLetBndr , addDataConStupidTheta, badFieldCon, polyPatSig ) where @@ -158,11 +159,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] @@ -185,13 +191,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 3ae6303..e60cfb6 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -92,14 +92,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 Thu Oct 16 14:24:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 16 Oct 2014 14:24:18 +0000 (UTC) Subject: [commit: ghc] wip/T8584: tcTySig for PatSynSigs: filter out universially-bound type variables from ex_tvs (01a9b22) Message-ID: <20141016142418.9C3D03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/01a9b2240c9164e172c7da11a085329e14c824c7/ghc >--------------------------------------------------------------- commit 01a9b2240c9164e172c7da11a085329e14c824c7 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 >--------------------------------------------------------------- 01a9b2240c9164e172c7da11a085329e14c824c7 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 8ee53db..e92c1ec 100644 --- a/compiler/typecheck/TcBinds.lhs +++ b/compiler/typecheck/TcBinds.lhs @@ -1313,7 +1313,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 Thu Oct 16 14:24:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 16 Oct 2014 14:24:21 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Show foralls (when requested) in pattern synonym types (597f3cc) Message-ID: <20141016142421.7591E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/597f3cc21ad5f29d76b74ef10c3625b748e67595/ghc >--------------------------------------------------------------- commit 597f3cc21ad5f29d76b74ef10c3625b748e67595 Author: Dr. ERDI Gergo Date: Sun Aug 3 15:26:13 2014 +0200 Show foralls (when requested) in pattern synonym types >--------------------------------------------------------------- 597f3cc21ad5f29d76b74ef10c3625b748e67595 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 673a269..74b5187 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -710,24 +710,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 -> @@ -735,9 +729,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 935b8ed..e595266 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -771,11 +771,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 @@ -786,8 +788,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 Thu Oct 16 14:24:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 16 Oct 2014 14:24:24 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Create SigTyVars for existentials under tcPat when typechecking a PatSyn with a type signature (40d1a5d) Message-ID: <20141016142424.2AD363A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/40d1a5de28bc2bb52e60b28f998f27ba3477eb6a/ghc >--------------------------------------------------------------- commit 40d1a5de28bc2bb52e60b28f998f27ba3477eb6a Author: Dr. ERDI Gergo Date: Thu Oct 16 22:20:45 2014 +0800 Create SigTyVars for existentials under tcPat when typechecking a PatSyn with a type signature >--------------------------------------------------------------- 40d1a5de28bc2bb52e60b28f998f27ba3477eb6a compiler/typecheck/TcPatSyn.lhs | 97 ++++++++++++++++++++++------------------- 1 file changed, 52 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 40d1a5de28bc2bb52e60b28f998f27ba3477eb6a From git at git.haskell.org Thu Oct 16 14:26:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 16 Oct 2014 14:26:11 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Create SigTyVars for existentials under tcPat when typechecking a PatSyn with a type signature (f74d2f1) Message-ID: <20141016142611.401A43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/f74d2f1f7d7a14e4fb21b90d81855a4b34e8b4f6/ghc >--------------------------------------------------------------- commit f74d2f1f7d7a14e4fb21b90d81855a4b34e8b4f6 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 >--------------------------------------------------------------- f74d2f1f7d7a14e4fb21b90d81855a4b34e8b4f6 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 f74d2f1f7d7a14e4fb21b90d81855a4b34e8b4f6 From git at git.haskell.org Thu Oct 16 16:51:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 16 Oct 2014 16:51:02 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 (dae919a) Message-ID: <20141016165102.E75B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/dae919a0f6b90d295fef3ebe4f2695db2eb6790b/ghc >--------------------------------------------------------------- commit dae919a0f6b90d295fef3ebe4f2695db2eb6790b Merge: 22b3649 d786781 Author: Simon Peyton Jones Date: Thu Oct 16 09:05:19 2014 +0100 Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 Conflicts: compiler/typecheck/TcRnTypes.lhs compiler/typecheck/TcSMonad.lhs testsuite/tests/typecheck/should_fail/ContextStack2.stderr testsuite/tests/typecheck/should_fail/FrozenErrorTests.stderr testsuite/tests/typecheck/should_run/T5751.hs >--------------------------------------------------------------- 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 dae919a0f6b90d295fef3ebe4f2695db2eb6790b From git at git.haskell.org Thu Oct 16 16:51:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 16 Oct 2014 16:51:05 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: More progress (4665087) Message-ID: <20141016165105.9557E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/46650873672a30d6f73266241495b508948882b1/ghc >--------------------------------------------------------------- commit 46650873672a30d6f73266241495b508948882b1 Author: Simon Peyton Jones Date: Thu Oct 16 17:50:36 2014 +0100 More progress >--------------------------------------------------------------- 46650873672a30d6f73266241495b508948882b1 compiler/typecheck/Flattening-notes | 31 ++- compiler/typecheck/FunDeps.lhs | 5 +- compiler/typecheck/TcBinds.lhs | 7 +- compiler/typecheck/TcCanonical.lhs | 4 +- compiler/typecheck/TcErrors.lhs | 4 +- compiler/typecheck/TcInteract.lhs | 79 +++--- compiler/typecheck/TcPatSyn.lhs | 9 +- compiler/typecheck/TcRnDriver.lhs | 7 +- compiler/typecheck/TcRnTypes.lhs | 9 +- compiler/typecheck/TcSMonad.lhs | 31 +-- compiler/typecheck/TcSimplify.lhs | 112 +++++--- compiler/types/FamInstEnv.lhs | 24 +- .../indexed-types/should_fail/ExtraTcsUntch.hs | 4 + .../tests/indexed-types/should_fail/T5439.stderr | 18 +- testsuite/tests/perf/compiler/T5837.stderr | 310 ++++++++++----------- .../typecheck/should_fail/ContextStack2.stderr | 8 +- .../typecheck/should_fail/FrozenErrorTests.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5684.stderr | 92 +++++- testsuite/tests/typecheck/should_fail/tcfail068.hs | 2 +- .../tests/typecheck/should_fail/tcfail068.stderr | 2 +- .../tests/typecheck/should_fail/tcfail186.stderr | 4 +- 21 files changed, 441 insertions(+), 323 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 46650873672a30d6f73266241495b508948882b1 From git at git.haskell.org Thu Oct 16 16:51:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 16 Oct 2014 16:51:08 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14's head updated: More progress (4665087) Message-ID: <20141016165108.0D46E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/new-flatten-skolems-Aug14' now includes: 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 dae919a Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 4665087 More progress From git at git.haskell.org Thu Oct 16 22:44:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 16 Oct 2014 22:44:41 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: More progress (5aee24f) Message-ID: <20141016224441.915F93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/5aee24f0bd0fa2997812dc7e0331bef4c4aff75f/ghc >--------------------------------------------------------------- commit 5aee24f0bd0fa2997812dc7e0331bef4c4aff75f Author: Simon Peyton Jones Date: Thu Oct 16 23:44:36 2014 +0100 More progress >--------------------------------------------------------------- 5aee24f0bd0fa2997812dc7e0331bef4c4aff75f compiler/typecheck/FunDeps.lhs | 43 +------- compiler/typecheck/TcBinds.lhs | 1 - compiler/typecheck/TcCanonical.lhs | 9 +- compiler/typecheck/TcErrors.lhs | 23 +++-- compiler/typecheck/TcInteract.lhs | 93 ++++++------------ compiler/typecheck/TcSMonad.lhs | 33 +++++-- compiler/typecheck/TcSimplify.lhs | 109 ++++++++++++--------- compiler/typecheck/TcTyClsDecls.lhs | 2 +- compiler/typecheck/TcType.lhs | 2 +- libraries/time | 2 +- rts/Linker.c | 4 +- testsuite/tests/gadt/gadt21.stderr | 7 +- .../tests/ghci.debugger/scripts/break026.stdout | 40 ++++---- .../tests/indexed-types/should_fail/T2693.stderr | 12 +-- .../tests/indexed-types/should_fail/T5439.stderr | 18 ++-- testsuite/tests/typecheck/should_fail/T5236.stderr | 4 +- .../tests/typecheck/should_fail/tcfail143.stderr | 4 +- .../tests/typecheck/should_fail/tcfail186.stderr | 4 +- 18 files changed, 187 insertions(+), 223 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 5aee24f0bd0fa2997812dc7e0331bef4c4aff75f From git at git.haskell.org Fri Oct 17 13:37:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 17 Oct 2014 13:37:27 +0000 (UTC) Subject: [commit: ghc] master: Avoid printing uniques in specialization rules (a477e81) Message-ID: <20141017133727.3FDF13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a477e8118137b7483d0a7680c1fd337a007a023b/ghc >--------------------------------------------------------------- commit a477e8118137b7483d0a7680c1fd337a007a023b Author: Joachim Breitner Date: Fri Oct 17 11:09:16 2014 +0200 Avoid printing uniques in specialization rules Akio found an avoidable cause of non-determinisim: The names of RULES generated by Specialise had uniques in them: "SPEC $cshowsPrec_a2QX @ [GHC.Types.Char]" [ALWAYS] forall ... By using showSDocForUser instead of showSDocDump when building the rule name, this is avoided: "SPEC $cshowsPrec @ [Char]" [ALWAYS] forall ... See #4012, comments 61ff. >--------------------------------------------------------------- a477e8118137b7483d0a7680c1fd337a007a023b compiler/specialise/Specialise.lhs | 6 +++++- .../tests/simplCore/should_compile/T6056.stderr | 24 ++++++++-------------- .../tests/simplCore/should_compile/T7785.stderr | 2 +- .../tests/simplCore/should_compile/T8848.stderr | 18 ++++++++-------- 4 files changed, 22 insertions(+), 28 deletions(-) diff --git a/compiler/specialise/Specialise.lhs b/compiler/specialise/Specialise.lhs index 09acd70..bc04e06 100644 --- a/compiler/specialise/Specialise.lhs +++ b/compiler/specialise/Specialise.lhs @@ -1196,8 +1196,12 @@ specCalls mb_mod env rules_for_me calls_for_me fn rhs Just this_mod -- Specialising imoprted fn -> ptext (sLit "SPEC/") <> ppr this_mod - rule_name = mkFastString $ showSDocDump dflags $ + rule_name = mkFastString $ showSDocForUser dflags neverQualify $ herald <+> ppr fn <+> hsep (map ppr_call_key_ty call_ts) + -- This name ends up in interface files, so use showSDocForUser, + -- otherwise uniques end up there, making builds + -- less deterministic (See #4012 comment:61 ff) + spec_env_rule = mkRule True {- Auto generated -} is_local rule_name inl_act -- Note [Auto-specialisation and RULES] diff --git a/testsuite/tests/simplCore/should_compile/T6056.stderr b/testsuite/tests/simplCore/should_compile/T6056.stderr index d1ae187..b38e34d 100644 --- a/testsuite/tests/simplCore/should_compile/T6056.stderr +++ b/testsuite/tests/simplCore/should_compile/T6056.stderr @@ -1,20 +1,12 @@ Rule fired: foldr/nil Rule fired: foldr/nil -Rule fired: - SPEC/main at main:T6056 T6056a.$wsmallerAndRest @ GHC.Integer.Type.Integer -Rule fired: - SPEC/main at main:T6056 T6056a.$wsmallerAndRest @ GHC.Types.Int +Rule fired: SPEC/T6056 $wsmallerAndRest @ Integer +Rule fired: SPEC/T6056 $wsmallerAndRest @ Int Rule fired: Class op < Rule fired: Class op < -Rule fired: - SPEC/main at main:T6056 T6056a.$wsmallerAndRest @ GHC.Integer.Type.Integer -Rule fired: - SPEC/main at main:T6056 T6056a.$wsmallerAndRest @ GHC.Integer.Type.Integer -Rule fired: - SPEC/main at main:T6056 T6056a.$wsmallerAndRest @ GHC.Types.Int -Rule fired: - SPEC/main at main:T6056 T6056a.$wsmallerAndRest @ GHC.Types.Int -Rule fired: - SPEC/main at main:T6056 T6056a.$wsmallerAndRest @ GHC.Integer.Type.Integer -Rule fired: - SPEC/main at main:T6056 T6056a.$wsmallerAndRest @ GHC.Types.Int +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 diff --git a/testsuite/tests/simplCore/should_compile/T7785.stderr b/testsuite/tests/simplCore/should_compile/T7785.stderr index c80738f..db80b99 100644 --- a/testsuite/tests/simplCore/should_compile/T7785.stderr +++ b/testsuite/tests/simplCore/should_compile/T7785.stderr @@ -1,6 +1,6 @@ ==================== Tidy Core rules ==================== -"SPEC Foo.shared @ []" [ALWAYS] +"SPEC shared @ []" [ALWAYS] forall ($dMyFunctor :: MyFunctor []) (irred :: Domain [] Int). shared @ [] $dMyFunctor irred = bar_$sshared diff --git a/testsuite/tests/simplCore/should_compile/T8848.stderr b/testsuite/tests/simplCore/should_compile/T8848.stderr index ba77c46..dad6b17 100644 --- a/testsuite/tests/simplCore/should_compile/T8848.stderr +++ b/testsuite/tests/simplCore/should_compile/T8848.stderr @@ -16,13 +16,11 @@ Rule fired: Class op <*> Rule fired: Class op $p1Applicative Rule fired: Class op fmap Rule fired: Class op <*> -Rule fired: - SPEC/main at main:T8848 GHC.Base.liftA2 _ _ _ @ (T8848.Shape 'T8848.Z) +Rule fired: SPEC/T8848 liftA2 _ _ _ @ (Shape 'Z) Rule fired: Class op $p1Applicative Rule fired: Class op fmap Rule fired: Class op <*> -Rule fired: - SPEC/main at main:T8848 GHC.Base.liftA2 _ _ _ @ (T8848.Shape 'T8848.Z) +Rule fired: SPEC/T8848 liftA2 _ _ _ @ (Shape 'Z) Rule fired: Class op $p1Applicative Rule fired: Class op fmap Rule fired: Class op <*> @@ -31,13 +29,13 @@ Rule fired: Class op fmap Rule fired: Class op <*> Rule fired: Class op fmap Rule fired: Class op fmap -Rule fired: SPEC $cfmap @ 'T8848.Z -Rule fired: SPEC $c<$ @ 'T8848.Z -Rule fired: SPEC T8848.$fFunctorShape @ 'T8848.Z +Rule fired: SPEC $cfmap @ 'Z +Rule fired: SPEC $c<$ @ 'Z +Rule fired: SPEC $fFunctorShape @ 'Z Rule fired: Class op fmap Rule fired: Class op fmap -Rule fired: SPEC $c<$ @ 'T8848.Z -Rule fired: SPEC T8848.$fFunctorShape @ 'T8848.Z -Rule fired: SPEC T8848.$fFunctorShape @ 'T8848.Z +Rule fired: SPEC $c<$ @ 'Z +Rule fired: SPEC $fFunctorShape @ 'Z +Rule fired: SPEC $fFunctorShape @ 'Z Rule fired: Class op fmap Rule fired: Class op fmap From git at git.haskell.org Fri Oct 17 14:54:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 17 Oct 2014 14:54:53 +0000 (UTC) Subject: [commit: ghc] master: Update T6056 output (0e2bd03) Message-ID: <20141017145453.A018C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0e2bd03b0dc21b16f3b53bbec47bbfd4aaad0756/ghc >--------------------------------------------------------------- commit 0e2bd03b0dc21b16f3b53bbec47bbfd4aaad0756 Author: Joachim Breitner Date: Fri Oct 17 16:54:22 2014 +0200 Update T6056 output according to travis (and proably Harbormaster), although I just cannot reproduce it here. >--------------------------------------------------------------- 0e2bd03b0dc21b16f3b53bbec47bbfd4aaad0756 testsuite/tests/simplCore/should_compile/T6056.stderr | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/simplCore/should_compile/T6056.stderr b/testsuite/tests/simplCore/should_compile/T6056.stderr index b38e34d..50c7e66 100644 --- a/testsuite/tests/simplCore/should_compile/T6056.stderr +++ b/testsuite/tests/simplCore/should_compile/T6056.stderr @@ -8,5 +8,5 @@ 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 +Rule fired: SPEC/T6056 $wsmallerAndRest @ Int From git at git.haskell.org Sat Oct 18 12:34:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 18 Oct 2014 12:34:39 +0000 (UTC) Subject: [commit: ghc] master: rts: fix unused parameter warning (1c35f9f) Message-ID: <20141018123439.869DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1c35f9f1cb7a293da85d649904ce731a65824cfe/ghc >--------------------------------------------------------------- commit 1c35f9f1cb7a293da85d649904ce731a65824cfe Author: Austin Seipp Date: Fri Oct 17 11:58:07 2014 -0500 rts: fix unused parameter warning Summary: If `pthread_setname_np` is not available, then a regular ./validate will fail due to warnings; the `name` parameter to `createOSThread` becomes unused. Signed-off-by: Austin Seipp Test Plan: iiam Reviewers: simonmar, nomeata, jstolarek, hvr Reviewed By: nomeata, jstolarek, hvr Subscribers: nomeata, thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D344 >--------------------------------------------------------------- 1c35f9f1cb7a293da85d649904ce731a65824cfe rts/posix/OSThreads.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/posix/OSThreads.c b/rts/posix/OSThreads.c index fb6d9d4..8c1beda 100644 --- a/rts/posix/OSThreads.c +++ b/rts/posix/OSThreads.c @@ -129,7 +129,7 @@ shutdownThread(void) } int -createOSThread (OSThreadId* pId, char *name, +createOSThread (OSThreadId* pId, char *name STG_UNUSED, OSThreadProc *startProc, void *param) { int result = pthread_create(pId, NULL, (void *(*)(void *))startProc, param); From git at git.haskell.org Sat Oct 18 12:34:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 18 Oct 2014 12:34:42 +0000 (UTC) Subject: [commit: ghc] master: Implement optimized NCG `MO_Ctz W64` op for i386 (#9340) (612f3d1) Message-ID: <20141018123442.194093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/612f3d120c65a461a4ad7f212d67bdae005f4975/ghc >--------------------------------------------------------------- commit 612f3d120c65a461a4ad7f212d67bdae005f4975 Author: Herbert Valerio Riedel Date: Sat Oct 18 14:32:33 2014 +0200 Implement optimized NCG `MO_Ctz W64` op for i386 (#9340) Summary: This is an optimization to the CTZ primops introduced for #9340 Previously we called out to `hs_ctz64`, but we can actually generate better hand-tuned code while avoiding the FFI ccall. With this patch, the code {-# LANGUAGE MagicHash #-} module TestClz0 where import GHC.Prim ctz64 :: Word64# -> Word# ctz64 x = ctz64# x results in the following assembler generated by NCG on i386: TestClz.ctz64_info: movl (%ebp),%eax movl 4(%ebp),%ecx movl %ecx,%edx orl %eax,%edx movl $64,%edx je _nAO bsf %ecx,%ecx addl $32,%ecx bsf %eax,%eax cmovne %eax,%ecx movl %ecx,%edx _nAO: movl %edx,%esi addl $8,%ebp jmp *(%ebp) For comparision, here's what LLVM 3.4 currently generates: 000000fc : fc: 0f bc 45 04 bsf 0x4(%ebp),%eax 100: b9 20 00 00 00 mov $0x20,%ecx 105: 0f 45 c8 cmovne %eax,%ecx 108: 83 c1 20 add $0x20,%ecx 10b: 8b 45 00 mov 0x0(%ebp),%eax 10e: 8b 55 08 mov 0x8(%ebp),%edx 111: 0f bc f0 bsf %eax,%esi 114: 85 c0 test %eax,%eax 116: 0f 44 f1 cmove %ecx,%esi 119: 83 c5 08 add $0x8,%ebp 11c: ff e2 jmp *%edx Reviewed By: austin Auditors: simonmar Differential Revision: https://phabricator.haskell.org/D163 >--------------------------------------------------------------- 612f3d120c65a461a4ad7f212d67bdae005f4975 compiler/nativeGen/X86/CodeGen.hs | 41 ++++++++++++++++++++++++++++++--------- 1 file changed, 32 insertions(+), 9 deletions(-) diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs index 9d7cb78..abd87ed 100644 --- a/compiler/nativeGen/X86/CodeGen.hs +++ b/compiler/nativeGen/X86/CodeGen.hs @@ -1799,14 +1799,38 @@ genCCall dflags is32Bit (PrimTarget (MO_Clz width)) dest_regs@[dst] args@[src] size = if width == W8 then II16 else intSize width lbl = mkCmmCodeLabel primPackageKey (fsLit (clzLabel width)) -genCCall dflags is32Bit (PrimTarget (MO_Ctz width)) dest_regs@[dst] args@[src] +genCCall dflags is32Bit (PrimTarget (MO_Ctz width)) [dst] [src] | is32Bit, width == W64 = do - -- Fallback to `hs_ctz64` on i386 - targetExpr <- cmmMakeDynamicReference dflags CallReference lbl - let target = ForeignTarget targetExpr (ForeignConvention CCallConv - [NoHint] [NoHint] - CmmMayReturn) - genCCall dflags is32Bit target dest_regs args + ChildCode64 vcode rlo <- iselExpr64 src + let rhi = getHiVRegFromLo rlo + dst_r = getRegisterReg platform False (CmmLocal dst) + lbl1 <- getBlockIdNat + lbl2 <- getBlockIdNat + tmp_r <- getNewRegNat size + + -- The following instruction sequence corresponds to the pseudo-code + -- + -- if (src) { + -- dst = src.lo32 ? BSF(src.lo32) : (BSF(src.hi32) + 32); + -- } else { + -- dst = 64; + -- } + return $ vcode `appOL` toOL + ([ MOV II32 (OpReg rhi) (OpReg tmp_r) + , OR II32 (OpReg rlo) (OpReg tmp_r) + , MOV II32 (OpImm (ImmInt 64)) (OpReg dst_r) + , JXX EQQ lbl2 + , JXX ALWAYS lbl1 + + , NEWBLOCK lbl1 + , BSF II32 (OpReg rhi) dst_r + , ADD II32 (OpImm (ImmInt 32)) (OpReg dst_r) + , BSF II32 (OpReg rlo) tmp_r + , CMOV NE II32 (OpReg tmp_r) dst_r + , JXX ALWAYS lbl2 + + , NEWBLOCK lbl2 + ]) | otherwise = do code_src <- getAnyReg src @@ -1828,7 +1852,6 @@ genCCall dflags is32Bit (PrimTarget (MO_Ctz width)) dest_regs@[dst] args@[src] bw = widthInBits width platform = targetPlatform dflags size = if width == W8 then II16 else intSize width - lbl = mkCmmCodeLabel primPackageKey (fsLit (ctzLabel width)) genCCall dflags is32Bit (PrimTarget (MO_UF_Conv width)) dest_regs args = do targetExpr <- cmmMakeDynamicReference dflags @@ -2485,7 +2508,7 @@ outOfLineCmmOp mop res args MO_PopCnt _ -> fsLit "popcnt" MO_BSwap _ -> fsLit "bswap" MO_Clz w -> fsLit $ clzLabel w - MO_Ctz w -> fsLit $ ctzLabel w + MO_Ctz _ -> unsupported MO_AtomicRMW _ _ -> fsLit "atomicrmw" MO_AtomicRead _ -> fsLit "atomicread" From git at git.haskell.org Sat Oct 18 14:23:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 18 Oct 2014 14:23:18 +0000 (UTC) Subject: [commit: ghc] master: Remove obsolete Data.OldTypeable (#9639) (7369d25) Message-ID: <20141018142318.1B9503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7369d2595a8cceebe457a44c8400828f4df87ea0/ghc >--------------------------------------------------------------- commit 7369d2595a8cceebe457a44c8400828f4df87ea0 Author: Michael Karg Date: Sat Oct 18 15:50:48 2014 +0200 Remove obsolete Data.OldTypeable (#9639) This finally removes the `Data.OldTypeable` module (which has been deprecated in 7.8), from `base`, compiler and testsuite. The deprecated `Typeable{1..7}` aliases in `Data.Typeable` are not removed yet in order to give existing code a bit more time to adapt. Reviewed By: hvr, dreixel Differential Revision: https://phabricator.haskell.org/D311 >--------------------------------------------------------------- 7369d2595a8cceebe457a44c8400828f4df87ea0 compiler/prelude/PrelNames.lhs | 42 +- compiler/typecheck/TcDeriv.lhs | 67 +-- compiler/typecheck/TcGenDeriv.lhs | 65 --- compiler/typecheck/TcInstDcls.lhs | 10 +- libraries/base/Data/OldTypeable.hs | 179 -------- libraries/base/Data/OldTypeable/Internal.hs | 474 --------------------- libraries/base/base.cabal | 3 - libraries/base/changelog.md | 2 + libraries/base/include/OldTypeable.h | 29 -- testsuite/tests/deriving/should_compile/all.T | 1 - testsuite/tests/deriving/should_compile/drv021.hs | 16 - .../tests/deriving/should_compile/drv021.stderr | 13 - testsuite/tests/deriving/should_fail/all.T | 1 - testsuite/tests/deriving/should_fail/drvfail014.hs | 13 - .../tests/deriving/should_fail/drvfail014.stderr | 9 - testsuite/tests/safeHaskell/ghci/all.T | 1 - testsuite/tests/safeHaskell/ghci/p15.script | 23 - testsuite/tests/safeHaskell/ghci/p15.stderr | 20 - testsuite/tests/safeHaskell/ghci/p15.stdout | 2 - .../safeHaskell/safeInfered/UnsafeInfered07.hs | 5 - .../safeHaskell/safeInfered/UnsafeInfered07.stderr | 24 -- .../safeHaskell/safeInfered/UnsafeInfered07_A.hs | 10 - testsuite/tests/safeHaskell/safeInfered/all.T | 3 - .../tests/safeHaskell/safeLanguage/SafeLang13.hs | 41 -- .../safeHaskell/safeLanguage/SafeLang13.stdout | 5 - .../tests/safeHaskell/safeLanguage/SafeLang13_A.hs | 19 - .../tests/safeHaskell/safeLanguage/SafeLang14.hs | 41 -- .../safeHaskell/safeLanguage/SafeLang14.stderr | 12 - .../tests/safeHaskell/safeLanguage/SafeLang14_A.hs | 19 - testsuite/tests/safeHaskell/safeLanguage/all.T | 8 - .../tests/safeHaskell/unsafeLibs/BadImport02.hs | 27 -- .../safeHaskell/unsafeLibs/BadImport02.stderr | 0 .../safeHaskell/unsafeLibs/BadImport02.stdout | 3 - .../tests/safeHaskell/unsafeLibs/BadImport02_A.hs | 16 - .../tests/safeHaskell/unsafeLibs/BadImport03.hs | 29 -- .../safeHaskell/unsafeLibs/BadImport03.stderr | 7 - .../tests/safeHaskell/unsafeLibs/BadImport03_A.hs | 16 - testsuite/tests/safeHaskell/unsafeLibs/all.T | 8 - 38 files changed, 8 insertions(+), 1255 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 7369d2595a8cceebe457a44c8400828f4df87ea0 From git at git.haskell.org Sat Oct 18 20:00:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 18 Oct 2014 20:00:15 +0000 (UTC) Subject: [commit: ghc] master: Generalise `Control.Monad.{foldM, foldM_}` to `Foldable` (#9586) (ce23745) Message-ID: <20141018200015.1B39B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ce23745147b9aab99187e266412efa27148a9b19/ghc >--------------------------------------------------------------- commit ce23745147b9aab99187e266412efa27148a9b19 Author: Herbert Valerio Riedel Date: Sat Oct 18 17:01:11 2014 +0200 Generalise `Control.Monad.{foldM,foldM_}` to `Foldable` (#9586) With this change `Control.Monad.foldM` becomes an alias for `Data.Foldable.foldlM`. Reviewed By: austin, ekmett Differential Revision: https://phabricator.haskell.org/D251 >--------------------------------------------------------------- ce23745147b9aab99187e266412efa27148a9b19 libraries/base/Control/Monad.hs | 13 +++++++------ libraries/base/changelog.md | 2 ++ testsuite/tests/indexed-types/should_fail/T1897b.stderr | 12 +++++++----- testsuite/tests/typecheck/should_compile/T4969.hs | 2 +- 4 files changed, 17 insertions(+), 12 deletions(-) diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs index db46dea..07b011a 100644 --- a/libraries/base/Control/Monad.hs +++ b/libraries/base/Control/Monad.hs @@ -75,7 +75,7 @@ module Control.Monad , (<$!>) ) where -import Data.Foldable ( sequence_, msum, mapM_, forM_ ) +import Data.Foldable ( Foldable, sequence_, msum, mapM_, foldlM, forM_ ) import Data.Functor ( void ) import Data.Traversable ( forM, mapM, sequence ) @@ -156,21 +156,22 @@ function' are not commutative. > f am xm If right-to-left evaluation is required, the input list should be reversed. + +Note: 'foldM' is the same as 'foldlM' -} -foldM :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a +foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b {-# INLINEABLE foldM #-} {-# SPECIALISE foldM :: (a -> b -> IO a) -> a -> [b] -> IO a #-} {-# SPECIALISE foldM :: (a -> b -> Maybe a) -> a -> [b] -> Maybe a #-} -foldM _ a [] = return a -foldM f a (x:xs) = f a x >>= \fax -> foldM f fax xs +foldM = foldlM -- | Like 'foldM', but discards the result. -foldM_ :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m () +foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m () {-# INLINEABLE foldM_ #-} {-# SPECIALISE foldM_ :: (a -> b -> IO a) -> a -> [b] -> IO () #-} {-# SPECIALISE foldM_ :: (a -> b -> Maybe a) -> a -> [b] -> Maybe () #-} -foldM_ f a xs = foldM f a xs >> return () +foldM_ f a xs = foldlM f a xs >> return () -- | @'replicateM' n act@ performs the action @n@ times, -- gathering the results. diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 52a076b..ed93b46 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -69,6 +69,8 @@ * Generalise `Control.Monad.{when,unless,guard}` from `Monad` to `Applicative` and from `MonadPlus` to `Alternative` respectively. + * 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`) diff --git a/testsuite/tests/indexed-types/should_fail/T1897b.stderr b/testsuite/tests/indexed-types/should_fail/T1897b.stderr index 6372bd9..785f21a 100644 --- a/testsuite/tests/indexed-types/should_fail/T1897b.stderr +++ b/testsuite/tests/indexed-types/should_fail/T1897b.stderr @@ -1,14 +1,16 @@ T1897b.hs:16:1: Could not deduce (Depend a0 ~ Depend a) - from the context (Bug a) + from the context (Bug a, Foldable t) bound by the inferred type for ?isValid?: - Bug a => [Depend a] -> Bool + (Bug a, Foldable t) => t (Depend a) -> Bool at T1897b.hs:16:1-41 NB: ?Depend? is a type function, and may not be injective The type variable ?a0? is ambiguous - Expected type: [Depend a] -> Bool - Actual type: [Depend a0] -> Bool + Expected type: t (Depend a) -> Bool + Actual type: t (Depend a0) -> Bool When checking that ?isValid? has the inferred type - isValid :: forall a. Bug a => [Depend a] -> Bool + isValid :: forall a (t :: * -> *). + (Bug a, Foldable t) => + t (Depend a) -> Bool Probable cause: the inferred type is ambiguous diff --git a/testsuite/tests/typecheck/should_compile/T4969.hs b/testsuite/tests/typecheck/should_compile/T4969.hs index 2bdd4a7..e35b37e 100644 --- a/testsuite/tests/typecheck/should_compile/T4969.hs +++ b/testsuite/tests/typecheck/should_compile/T4969.hs @@ -63,7 +63,7 @@ instance ToAbstract LetDef [ALetBinding] where undefined where letToAbstract = do localToAbstract lhsArgs $ \args -> - foldM lambda undefined undefined + foldM lambda undefined (undefined :: [a]) lambda _ _ = do x <- freshNoName undefined return undefined lambda _ _ = typeError $ NotAValidLetBinding d From git at git.haskell.org Sat Oct 18 21:51:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 18 Oct 2014 21:51:25 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Pass all potentially interesting constraints to plugin (changes API). (c55777e) Message-ID: <20141018215125.B63C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/c55777ed8725e33041cbbabdcebc5227f19ac771/ghc >--------------------------------------------------------------- commit c55777ed8725e33041cbbabdcebc5227f19ac771 Author: Iavor S. Diatchki Date: Sat Oct 18 14:35:16 2014 -0700 Pass all potentially interesting constraints to plugin (changes API). We now pass 3 lists of constraints to the plugin: givens, derived, and wanteds. Furthermore, the list of constraints will now contain dictionaries, so one could write plugins for the class system. In addition, we also change the return type for plugins: now plugins don't need to return "all other constraints". In the case of contradiction, plugins just return the conflicting constraints, and in the case when things were OK, plugins return the solved constraints + new work. This is not only simpler, but might makes things more efficient as we don't rebuild the entire inerts set all the time, instead we just delete the solved/contradicting constraints. >--------------------------------------------------------------- c55777ed8725e33041cbbabdcebc5227f19ac771 compiler/typecheck/TcInteract.lhs | 59 +++++++++++++++++++++++---------------- compiler/typecheck/TcRnTypes.lhs | 22 ++++++++++----- compiler/typecheck/TcSMonad.lhs | 12 ++++++++ 3 files changed, 62 insertions(+), 31 deletions(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 8974ac7..91a9fb0 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -40,7 +40,7 @@ import Bag import Control.Monad ( foldM ) import Data.Maybe ( catMaybes ) -import Data.List( partition ) +import Data.List( partition, foldl' ) import VarEnv @@ -143,38 +143,49 @@ runTcPlugin :: TcPluginSolver -> TcS () runTcPlugin solver = do iSet <- getTcSInerts let iCans = inert_cans iSet - iEqs = concat (varEnvElts (inert_eqs iCans)) - iFunEqs = funEqsToList (inert_funeqs iCans) - allCts = iEqs ++ iFunEqs + allCts = foldDicts (:) (inert_dicts iCans) + $ foldFunEqs (:) (inert_funeqs iCans) + $ concat (varEnvElts (inert_eqs iCans)) + (derived,other) = partition isDerivedCt allCts (wanted,given) = partition isWantedCt other - -- We use this to remove some constraints. - -- 'survived' should be the sub-set of constraints that - -- remains inert. - restoreICans survived = - do let iCans1 = iCans { inert_eqs = emptyVarEnv - , inert_funeqs = emptyFunEqs } - iCans2 = foldl addInertCan iCans1 derived - iCans3 = foldl addInertCan iCans2 survived - setInertCans iCans3 - - result <- runTcPluginTcS (solver given wanted) + result <- runTcPluginTcS (solver given derived wanted) case result of - TcPluginContradiction bad_cts ok_cts -> - do restoreICans ok_cts + TcPluginContradiction bad_cts -> + do setInertCans (removeInertCts iCans bad_cts) mapM_ emitInsoluble bad_cts - -- other_cts should include both givens and wanteds. - TcPluginOk solved_cts other_cts new_cts -> - do case solved_cts of - [] -> return () -- Fast common case - _ -> do restoreICans other_cts - let setEv (ev,ct) = setEvBind (ctev_evar (cc_ev ct)) ev - mapM_ setEv solved_cts + 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 + removeInertCts :: InertCans -> [Ct] -> InertCans + removeInertCts = foldl' removeInertCt + + -- 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" type WorkItem = Ct type SimplifierStage = WorkItem -> TcS StopOrContinue diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index ed54559..9054f99 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -1922,7 +1922,10 @@ Constraint Solver Plugins \begin{code} -type TcPluginSolver = [Ct] -> [Ct] -> TcPluginM TcPluginResult +type TcPluginSolver = [Ct] -- given + -> [Ct] -- derived + -> [Ct] -- wanted + -> TcPluginM TcPluginResult newtype TcPluginM a = TcPluginM (TcM a) @@ -1963,12 +1966,17 @@ data TcPlugin = forall s. TcPlugin } data TcPluginResult - = TcPluginContradiction {- inconsistent -} [Ct] - {- all others -} [Ct] - - | TcPluginOk {- solved -} [(EvTerm,Ct)] - {- all others -} [Ct] - {- new work -} [Ct] + = TcPluginContradiction [Ct] + -- ^ The plugin found a contradiction. + -- The returned constraints are removed from the inert set, + -- and recorded as insoluable. + + | TcPluginOk [(EvTerm,Ct)] [Ct] + -- ^ The first field is for constraints that were solved. + -- These are removed from the inert set, + -- and the evidence for them is recorded. + -- The second field contains new work, that should be processed by + -- the constraint solver. \end{code} diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index 3c339fb..5c3b32f 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -77,11 +77,15 @@ module TcSMonad ( lookupSolvedDict, extendFlatCache, findDict, findDictsByClass, addDict, addDictsByClass, delDict, partitionDicts, + foldDicts, emptyFunEqs, funEqsToList, findFunEq, findTyEqs, findFunEqsByTyCon, findFunEqs, partitionFunEqs, sizeFunEqMap, + foldFunEqs, + delFunEq, + delTyEq, instDFunType, -- Instantiation newFlexiTcSTy, instFlexiTcS, instFlexiTcSHelperTcS, @@ -888,6 +892,11 @@ type TyEqMap a = TyVarEnv a findTyEqs :: TyEqMap EqualCtList -> TyVar -> EqualCtList findTyEqs m tv = lookupVarEnv m tv `orElse` [] + +delTyEq :: TyEqMap EqualCtList -> TcTyVar -> TcType -> TyEqMap EqualCtList +delTyEq m tv t = modifyVarEnv (filter (not . isThisOne)) m tv + where isThisOne (CTyEqCan { cc_rhs = t1 }) = eqType t t1 + isThisOne _ = False \end{code} @@ -1041,6 +1050,9 @@ partitionFunEqs f m = foldTcAppMap k m (emptyBag, emptyFunEqs) k ct (yeses, noes) | f ct = (yeses `snocBag` ct, noes) | otherwise = (yeses, insertFunEqCt noes ct) + +delFunEq :: FunEqMap a -> TyCon -> [Type] -> FunEqMap a +delFunEq m tc tys = delTcApp m (getUnique tc) tys \end{code} From git at git.haskell.org Sun Oct 19 10:45:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 19 Oct 2014 10:45:52 +0000 (UTC) Subject: [commit: ghc] master: Remove redundant explicit `Prelude` imports (abfbb0d) Message-ID: <20141019104552.037CE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/abfbb0d6aa65bf6f664fd86eecc72bd3a28bb0b9/ghc >--------------------------------------------------------------- commit abfbb0d6aa65bf6f664fd86eecc72bd3a28bb0b9 Author: Herbert Valerio Riedel Date: Sun Oct 19 12:03:11 2014 +0200 Remove redundant explicit `Prelude` imports Since they're implied by the lack of `NoImplicitPrelude` >--------------------------------------------------------------- abfbb0d6aa65bf6f664fd86eecc72bd3a28bb0b9 libraries/base/Control/Concurrent.hs | 2 -- libraries/base/Control/Concurrent/Chan.hs | 2 -- libraries/base/Control/Monad/Instances.hs | 2 -- libraries/base/Control/Monad/ST/Lazy/Imp.hs | 2 -- libraries/base/Control/Monad/Zip.hs | 1 - libraries/base/Data/Complex.hs | 2 -- libraries/base/Data/Fixed.hs | 1 - libraries/base/Data/Ix.hs | 2 -- libraries/base/Data/Ratio.hs | 2 -- libraries/base/Data/STRef.hs | 2 -- libraries/base/Data/STRef/Lazy.hs | 1 - libraries/base/Data/Unique.hs | 2 -- libraries/base/GHC/Constants.hs | 2 -- libraries/base/GHC/Environment.hs | 1 - libraries/base/System/CPUTime.hsc | 2 -- libraries/base/System/Console/GetOpt.hs | 2 -- libraries/base/System/Environment.hs | 2 -- libraries/base/System/Exit.hs | 1 - libraries/base/System/Info.hs | 1 - libraries/base/System/Mem.hs | 1 - libraries/base/System/Mem/StableName.hs | 2 -- libraries/base/Text/Printf.hs | 1 - libraries/base/Text/Show/Functions.hs | 2 -- 23 files changed, 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 abfbb0d6aa65bf6f664fd86eecc72bd3a28bb0b9 From git at git.haskell.org Sun Oct 19 11:41:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 19 Oct 2014 11:41:19 +0000 (UTC) Subject: [commit: ghc] master: Python 3 support, second attempt (Trac #9184) (d576fc3) Message-ID: <20141019114119.29C813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d576fc38d9493c4979217fa36565f1f97fcc03d4/ghc >--------------------------------------------------------------- commit d576fc38d9493c4979217fa36565f1f97fcc03d4 Author: Krzysztof Gogolewski Date: Sun Oct 19 13:41:24 2014 +0200 Python 3 support, second attempt (Trac #9184) Summary: This is a fixup of https://phabricator.haskell.org/D233 The only difference is in findTFiles (first commit), which previously broke Windows runner; now I translated literally instead attempting to improve it, and checked it works. Test Plan: I used validate under 2,3 on Linux and under 2 on msys2. On Windows I've seen a large number of failures, but they don't seem to be connected with the patch. Reviewers: hvr, simonmar, thomie, austin Reviewed By: austin Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D310 GHC Trac Issues: #9184 >--------------------------------------------------------------- d576fc38d9493c4979217fa36565f1f97fcc03d4 testsuite/config/ghc | 22 ++-- testsuite/driver/runtests.py | 67 ++++++----- testsuite/driver/testlib.py | 177 +++++++++++++++-------------- testsuite/driver/testutil.py | 34 ------ testsuite/tests/ffi/should_run/all.T | 10 +- testsuite/tests/numeric/should_run/all.T | 8 +- testsuite/tests/perf/compiler/all.T | 2 +- testsuite/tests/th/all.T | 6 +- testsuite/tests/typecheck/should_run/all.T | 4 +- testsuite/timeout/calibrate | 2 +- testsuite/timeout/timeout.py | 2 +- utils/fingerprint/fingerprint.py | 8 +- 12 files changed, 162 insertions(+), 180 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 d576fc38d9493c4979217fa36565f1f97fcc03d4 From git at git.haskell.org Sun Oct 19 12:19:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 19 Oct 2014 12:19:39 +0000 (UTC) Subject: [commit: ghc] master: Refactor module imports in base (b5930f8) Message-ID: <20141019121939.2F5423A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b5930f8b8030350eff306bf56ba7607098ada61e/ghc >--------------------------------------------------------------- commit b5930f8b8030350eff306bf56ba7607098ada61e Author: Herbert Valerio Riedel Date: Sun Oct 19 14:15:14 2014 +0200 Refactor module imports in base This commit removes a couple of {-# OPTIONS_GHC -fno-warn-unused-imports #-} by cleaning up the imports, as well as ensuring that all modules in the GHC.* hierarchy avoid importing the `Prelude` module to clean-up the import graph a bit. >--------------------------------------------------------------- b5930f8b8030350eff306bf56ba7607098ada61e libraries/base/Control/Concurrent.hs | 7 +++---- libraries/base/Data/Tuple.hs | 17 ++--------------- libraries/base/GHC/ConsoleHandler.hs | 4 ++++ libraries/base/GHC/Constants.hs | 2 ++ libraries/base/GHC/Environment.hs | 6 ++++-- libraries/base/GHC/Event.hs | 1 + libraries/base/GHC/Int.hs | 1 - libraries/base/GHC/PArr.hs | 1 + libraries/base/GHC/Profiling.hs | 4 ++++ libraries/base/GHC/Stats.hsc | 6 +++++- libraries/base/GHC/TopHandler.lhs | 8 +++----- libraries/base/GHC/Word.hs | 1 - 12 files changed, 29 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 b5930f8b8030350eff306bf56ba7607098ada61e From git at git.haskell.org Sun Oct 19 19:06:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 19 Oct 2014 19:06:52 +0000 (UTC) Subject: [commit: ghc] master: Indentation and non-semantic changes only. (5b9fe33) Message-ID: <20141019190652.718763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5b9fe33d8a85c2e2105844b65da417c7358187ab/ghc >--------------------------------------------------------------- commit 5b9fe33d8a85c2e2105844b65da417c7358187ab Author: Edward Z. Yang Date: Wed Oct 15 22:51:59 2014 -0700 Indentation and non-semantic changes only. Summary: Get these lines fitting in 80 columns, and replace ptext (sLit ...) with text Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonmar, austin Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D342 >--------------------------------------------------------------- 5b9fe33d8a85c2e2105844b65da417c7358187ab compiler/cmm/PprCmmDecl.hs | 14 +++--- compiler/main/DriverPipeline.hs | 40 +++++++++--------- compiler/nativeGen/PPC/Ppr.hs | 42 +++++++++--------- compiler/nativeGen/SPARC/Ppr.hs | 20 ++++----- compiler/nativeGen/X86/Ppr.hs | 94 +++++++++++++++++++++-------------------- 5 files changed, 107 insertions(+), 103 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 5b9fe33d8a85c2e2105844b65da417c7358187ab From git at git.haskell.org Mon Oct 20 09:44:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 20 Oct 2014 09:44:39 +0000 (UTC) Subject: [commit: ghc] master: Sync up `containers` submodule to latest `master`-tip (4d90b53) Message-ID: <20141020094439.87B053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4d90b534ef989169bddf0f681237fedcf93b9ed2/ghc >--------------------------------------------------------------- commit 4d90b534ef989169bddf0f681237fedcf93b9ed2 Author: Herbert Valerio Riedel Date: Mon Oct 20 11:38:27 2014 +0200 Sync up `containers` submodule to latest `master`-tip This updates `containers` to provide more specialised `Foldable` instance methods, see also https://github.com/haskell/containers/issues/56 for more details. >--------------------------------------------------------------- 4d90b534ef989169bddf0f681237fedcf93b9ed2 libraries/containers | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/containers b/libraries/containers index 085e1b8..530fc76 160000 --- a/libraries/containers +++ b/libraries/containers @@ -1 +1 @@ -Subproject commit 085e1b8b2cfbd1159bbc9f8cbf6a4127cc32227b +Subproject commit 530fc76bdd17089fcaaa655d66156abbc2092c2c From git at git.haskell.org Mon Oct 20 23:28:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 20 Oct 2014 23:28:46 +0000 (UTC) Subject: [commit: ghc] master: Revert "Place static closures in their own section." (d5d6fb3) Message-ID: <20141020232846.20D303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d5d6fb340410727345a7b5a47bcf83e7847ea4a3/ghc >--------------------------------------------------------------- commit d5d6fb340410727345a7b5a47bcf83e7847ea4a3 Author: Edward Z. Yang Date: Mon Oct 20 16:03:50 2014 -0700 Revert "Place static closures in their own section." This reverts commit b23ba2a7d612c6b466521399b33fe9aacf5c4f75. Conflicts: compiler/cmm/PprCmmDecl.hs compiler/nativeGen/PPC/Ppr.hs compiler/nativeGen/SPARC/Ppr.hs compiler/nativeGen/X86/Ppr.hs >--------------------------------------------------------------- d5d6fb340410727345a7b5a47bcf83e7847ea4a3 compiler/cmm/Cmm.hs | 1 - compiler/cmm/CmmParse.y | 2 +- compiler/cmm/PprCmmDecl.hs | 1 - compiler/codeGen/StgCmmBind.hs | 4 ++-- compiler/codeGen/StgCmmCon.hs | 2 +- compiler/codeGen/StgCmmUtils.hs | 6 ------ compiler/llvmGen/LlvmCodeGen/Data.hs | 1 - compiler/nativeGen/PPC/Ppr.hs | 1 - compiler/nativeGen/SPARC/Ppr.hs | 1 - compiler/nativeGen/X86/Ppr.hs | 4 ---- 10 files changed, 4 insertions(+), 19 deletions(-) diff --git a/compiler/cmm/Cmm.hs b/compiler/cmm/Cmm.hs index 98c5b59..9e9bae9 100644 --- a/compiler/cmm/Cmm.hs +++ b/compiler/cmm/Cmm.hs @@ -170,7 +170,6 @@ data Section | RelocatableReadOnlyData | UninitialisedData | ReadOnlyData16 -- .rodata.cst16 on x86_64, 16-byte aligned - | StaticClosures | OtherSection String data CmmStatic diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index db6cc49..8033330 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -1105,7 +1105,7 @@ staticClosure :: PackageKey -> FastString -> FastString -> [CmmLit] -> CmmParse staticClosure pkg cl_label info payload = do dflags <- getDynFlags let lits = mkStaticClosure dflags (mkCmmInfoLabel pkg info) dontCareCCS payload [] [] [] - code $ emitStaticClosure (mkCmmDataLabel pkg cl_label) lits + code $ emitDataLits (mkCmmDataLabel pkg cl_label) lits foreignCall :: String diff --git a/compiler/cmm/PprCmmDecl.hs b/compiler/cmm/PprCmmDecl.hs index c9bbc8b..87cda6a 100644 --- a/compiler/cmm/PprCmmDecl.hs +++ b/compiler/cmm/PprCmmDecl.hs @@ -162,7 +162,6 @@ pprSection s = case s of RelocatableReadOnlyData -> section <+> doubleQuotes (text "relreadonly") UninitialisedData -> section <+> doubleQuotes (text "uninitialised") - StaticClosures -> section <+> doubleQuotes (text "staticclosures") OtherSection s' -> section <+> doubleQuotes (text s') where section = ptext (sLit "section") diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs index a253b11..444112f 100644 --- a/compiler/codeGen/StgCmmBind.hs +++ b/compiler/codeGen/StgCmmBind.hs @@ -98,7 +98,7 @@ cgTopRhsClosure dflags rec id ccs _ upd_flag args body = let closure_rep = mkStaticClosureFields dflags indStaticInfoTable ccs MayHaveCafRefs [unLit (idInfoToAmode cg_info)] - emitStaticClosure closure_label closure_rep + emitDataLits closure_label closure_rep return () gen_code dflags lf_info closure_label @@ -113,7 +113,7 @@ cgTopRhsClosure dflags rec id ccs _ upd_flag args body = closure_rep = mkStaticClosureFields dflags info_tbl ccs caffy [] -- BUILD THE OBJECT, AND GENERATE INFO TABLE (IF NECESSARY) - ; emitStaticClosure closure_label closure_rep + ; emitDataLits closure_label closure_rep ; let fv_details :: [(NonVoid Id, VirtualHpOffset)] (_, _, fv_details) = mkVirtHeapOffsets dflags (isLFThunk lf_info) (addIdReps []) diff --git a/compiler/codeGen/StgCmmCon.hs b/compiler/codeGen/StgCmmCon.hs index 93bfaf0..edd0648 100644 --- a/compiler/codeGen/StgCmmCon.hs +++ b/compiler/codeGen/StgCmmCon.hs @@ -101,7 +101,7 @@ cgTopRhsCon dflags id con args = payload -- BUILD THE OBJECT - ; emitStaticClosure closure_label closure_rep + ; emitDataLits closure_label closure_rep ; return () } diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index 8b3616f..d47a016 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -12,7 +12,6 @@ module StgCmmUtils ( cgLit, mkSimpleLit, emitDataLits, mkDataLits, emitRODataLits, mkRODataLits, - emitStaticClosure, emitRtsCall, emitRtsCallWithResult, emitRtsCallGen, assignTemp, newTemp, @@ -321,11 +320,6 @@ emitRODataLits :: CLabel -> [CmmLit] -> FCode () -- Emit a read-only data block emitRODataLits lbl lits = emitDecl (mkRODataLits lbl lits) -emitStaticClosure :: CLabel -> [CmmLit] -> FCode () --- Emit a static closure data block, which is only used at startup time. --- Eventually make this READ ONLY(?) -emitStaticClosure lbl lits = emitDecl (mkDataLits StaticClosures lbl lits) - newStringCLit :: String -> FCode CmmLit -- Make a global definition for the string, -- and return its label diff --git a/compiler/llvmGen/LlvmCodeGen/Data.hs b/compiler/llvmGen/LlvmCodeGen/Data.hs index 6115b88..1dbfb4b 100644 --- a/compiler/llvmGen/LlvmCodeGen/Data.hs +++ b/compiler/llvmGen/LlvmCodeGen/Data.hs @@ -56,7 +56,6 @@ isSecConstant ReadOnlyData = True isSecConstant RelocatableReadOnlyData = True isSecConstant ReadOnlyData16 = True isSecConstant Data = False -isSecConstant StaticClosures = False isSecConstant UninitialisedData = False isSecConstant (OtherSection _) = False diff --git a/compiler/nativeGen/PPC/Ppr.hs b/compiler/nativeGen/PPC/Ppr.hs index 36db75a..e62a1c4 100644 --- a/compiler/nativeGen/PPC/Ppr.hs +++ b/compiler/nativeGen/PPC/Ppr.hs @@ -291,7 +291,6 @@ pprSectionHeader seg = ReadOnlyData16 | osDarwin -> text ".const\n\t.align 4" | otherwise -> text ".section .rodata\n\t.align 4" - StaticClosures -> text ".section staticclosures,\"aw\"\n\t.align 2" OtherSection _ -> panic "PprMach.pprSectionHeader: unknown section" diff --git a/compiler/nativeGen/SPARC/Ppr.hs b/compiler/nativeGen/SPARC/Ppr.hs index c0ae9c1..c734687 100644 --- a/compiler/nativeGen/SPARC/Ppr.hs +++ b/compiler/nativeGen/SPARC/Ppr.hs @@ -334,7 +334,6 @@ pprSectionHeader seg = case seg of -> text ".text\n\t.align 8" UninitialisedData -> text ".bss\n\t.align 8" ReadOnlyData16 -> text ".data\n\t.align 16" - StaticClosures -> text ".section staticclosures,\"aw\"\n\t.align 8" OtherSection _ -> panic "PprMach.pprSectionHeader: unknown section" diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs index 6449d8e..cc39557 100644 --- a/compiler/nativeGen/X86/Ppr.hs +++ b/compiler/nativeGen/X86/Ppr.hs @@ -389,7 +389,6 @@ pprSectionHeader seg = -> text ".const_data\n\t.align 2" UninitialisedData -> text ".data\n\t.align 2" ReadOnlyData16 -> text ".const\n\t.align 4" - StaticClosures -> text ".section staticclosures,\"aw\"\n\t.align 2" OtherSection _ -> panic "X86.Ppr.pprSectionHeader: unknown section" | otherwise -> case seg of @@ -400,7 +399,6 @@ pprSectionHeader seg = -> text ".const_data\n\t.align 3" UninitialisedData -> text ".data\n\t.align 3" ReadOnlyData16 -> text ".const\n\t.align 4" - StaticClosures -> text ".section staticclosures,\"aw\"\n\t.align 3" OtherSection _ -> panic "PprMach.pprSectionHeader: unknown section" _ | target32Bit platform -> @@ -412,7 +410,6 @@ pprSectionHeader seg = -> text ".section .data\n\t.align 4" UninitialisedData -> text ".section .bss\n\t.align 4" ReadOnlyData16 -> text ".section .rodata\n\t.align 16" - StaticClosures -> text ".section staticclosures,\"aw\"\n\t.align 4" OtherSection _ -> panic "X86.Ppr.pprSectionHeader: unknown section" | otherwise -> case seg of @@ -423,7 +420,6 @@ pprSectionHeader seg = -> text ".section .data\n\t.align 8" UninitialisedData -> text ".section .bss\n\t.align 8" ReadOnlyData16 -> text ".section .rodata.cst16\n\t.align 16" - StaticClosures -> text ".section staticclosures,\"aw\"\n\t.align 8" OtherSection _ -> panic "PprMach.pprSectionHeader: unknown section" From git at git.haskell.org Mon Oct 20 23:28:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 20 Oct 2014 23:28:48 +0000 (UTC) Subject: [commit: ghc] master: Revert "Fix typo in section name: no leading period." (07da36b) Message-ID: <20141020232848.AF9853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/07da36b586b52a9a9b5993b1d9cb66c852486f2b/ghc >--------------------------------------------------------------- commit 07da36b586b52a9a9b5993b1d9cb66c852486f2b Author: Edward Z. Yang Date: Mon Oct 20 15:55:12 2014 -0700 Revert "Fix typo in section name: no leading period." This reverts commit e8dac6dc60beea863c3a5daded68f5157ab546fb. >--------------------------------------------------------------- 07da36b586b52a9a9b5993b1d9cb66c852486f2b rts/Linker.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/Linker.c b/rts/Linker.c index a34aeb7..5853795 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -4260,7 +4260,7 @@ ocGetNames_PEi386 ( ObjectCode* oc ) 0==strcmp(".rodata",(char*)secname)) kind = SECTIONKIND_CODE_OR_RODATA; if (0==strcmp(".data",(char*)secname) || - 0==strcmp("staticclosures",(char*)secname) || + 0==strcmp(".staticclosures",(char*)secname) || 0==strcmp(".bss",(char*)secname)) kind = SECTIONKIND_RWDATA; if (0==strcmp(".ctors", (char*)secname)) From git at git.haskell.org Mon Oct 20 23:28:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 20 Oct 2014 23:28:51 +0000 (UTC) Subject: [commit: ghc] master: Revert "Check for staticclosures section in Windows linker." (0202b7c) Message-ID: <20141020232851.46E2E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0202b7cefbaf76dc53d43562dbc84a52debe2eb2/ghc >--------------------------------------------------------------- commit 0202b7cefbaf76dc53d43562dbc84a52debe2eb2 Author: Edward Z. Yang Date: Mon Oct 20 15:55:29 2014 -0700 Revert "Check for staticclosures section in Windows linker." This reverts commit 2fc0c6cf594731f343b4f8a5b3ecf9e72db4c3c0. >--------------------------------------------------------------- 0202b7cefbaf76dc53d43562dbc84a52debe2eb2 rts/Linker.c | 1 - 1 file changed, 1 deletion(-) diff --git a/rts/Linker.c b/rts/Linker.c index 5853795..aa44330 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -4260,7 +4260,6 @@ ocGetNames_PEi386 ( ObjectCode* oc ) 0==strcmp(".rodata",(char*)secname)) kind = SECTIONKIND_CODE_OR_RODATA; if (0==strcmp(".data",(char*)secname) || - 0==strcmp(".staticclosures",(char*)secname) || 0==strcmp(".bss",(char*)secname)) kind = SECTIONKIND_RWDATA; if (0==strcmp(".ctors", (char*)secname)) From git at git.haskell.org Mon Oct 20 23:28:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 20 Oct 2014 23:28:53 +0000 (UTC) Subject: [commit: ghc] master: Revert "Properly generate info tables for static closures in C--." (126b0c4) Message-ID: <20141020232853.CF91F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/126b0c410f2596d1bf7ba6a1af872487c5bb2b52/ghc >--------------------------------------------------------------- commit 126b0c410f2596d1bf7ba6a1af872487c5bb2b52 Author: Edward Z. Yang Date: Mon Oct 20 16:01:39 2014 -0700 Revert "Properly generate info tables for static closures in C--." This reverts commit 178eb9060f369b216f3f401196e28eab4af5624d. >--------------------------------------------------------------- 126b0c410f2596d1bf7ba6a1af872487c5bb2b52 compiler/cmm/CmmParse.y | 3 +-- compiler/cmm/SMRep.lhs | 5 ++--- 2 files changed, 3 insertions(+), 5 deletions(-) diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 31b1198..3bd0053 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -496,8 +496,7 @@ info :: { CmmParse (CLabel, Maybe CmmInfoTable, [LocalReg]) } ty = Constr (fromIntegral $9) -- Tag (stringToWord8s $13) rep = mkRTSRep (fromIntegral $11) $ - mkHeapRep dflags (fromIntegral $11 == cONSTR_NOCAF_STATIC) - (fromIntegral $5) + mkHeapRep dflags False (fromIntegral $5) (fromIntegral $7) ty return (mkCmmEntryLabel pkg $3, Just $ CmmInfoTable { cit_lbl = mkCmmInfoLabel pkg $3 diff --git a/compiler/cmm/SMRep.lhs b/compiler/cmm/SMRep.lhs index 1d0b9b0..53c9d0a 100644 --- a/compiler/cmm/SMRep.lhs +++ b/compiler/cmm/SMRep.lhs @@ -41,7 +41,7 @@ module SMRep ( -- ** RTS closure types rtsClosureType, rET_SMALL, rET_BIG, - aRG_GEN, aRG_GEN_BIG, cONSTR_NOCAF_STATIC, + aRG_GEN, aRG_GEN_BIG, -- ** Arrays card, cardRoundUp, cardTableSizeB, cardTableSizeW, @@ -473,12 +473,11 @@ rtsClosureType rep _ -> panic "rtsClosureType" -- We export these ones -rET_SMALL, rET_BIG, aRG_GEN, aRG_GEN_BIG, cONSTR_NOCAF_STATIC :: Int +rET_SMALL, rET_BIG, aRG_GEN, aRG_GEN_BIG :: Int rET_SMALL = RET_SMALL rET_BIG = RET_BIG aRG_GEN = ARG_GEN aRG_GEN_BIG = ARG_GEN_BIG -cONSTR_NOCAF_STATIC = CONSTR_NOCAF_STATIC \end{code} Note [Static NoCaf constructors] From git at git.haskell.org Mon Oct 20 23:28:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 20 Oct 2014 23:28:56 +0000 (UTC) Subject: [commit: ghc] master: Revert "Rename _closure to _static_closure, apply naming consistently." (89a8d81) Message-ID: <20141020232856.771D43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/89a8d817f0c2951ec305c286a526205d06bf9221/ghc >--------------------------------------------------------------- commit 89a8d817f0c2951ec305c286a526205d06bf9221 Author: Edward Z. Yang Date: Mon Oct 20 15:57:13 2014 -0700 Revert "Rename _closure to _static_closure, apply naming consistently." This reverts commit 35672072b4091d6f0031417bc160c568f22d0469. Conflicts: compiler/main/DriverPipeline.hs >--------------------------------------------------------------- 89a8d817f0c2951ec305c286a526205d06bf9221 compiler/cmm/CLabel.hs | 4 +- compiler/deSugar/DsForeign.lhs | 6 +- compiler/ghci/ByteCodeLink.lhs | 4 +- compiler/main/DriverPipeline.hs | 4 +- driver/utils/dynwrapper.c | 2 +- ghc/GhciMonad.hs | 6 +- includes/Cmm.h | 1 - includes/Rts.h | 1 - includes/RtsAPI.h | 12 ++-- includes/rts/StaticClosures.h | 34 ----------- includes/rts/storage/ClosureMacros.h | 5 +- includes/rts/storage/TSO.h | 2 +- includes/stg/MiscClosures.h | 30 +++++----- libraries/integer-gmp/cbits/gmp-wrappers.cmm | 4 +- rts/Exception.cmm | 6 +- rts/Interpreter.c | 2 +- rts/Linker.c | 4 +- rts/Prelude.h | 86 +++++++++++++--------------- rts/PrimOps.cmm | 8 +-- rts/RaiseAsync.c | 4 +- rts/RetainerProfile.c | 2 +- rts/STM.c | 4 +- rts/STM.h | 8 +-- rts/StgMiscClosures.cmm | 4 +- rts/Weak.c | 6 +- rts/package.conf.in | 72 +++++++++++------------ rts/posix/Signals.c | 4 +- rts/sm/Storage.c | 4 +- rts/win32/libHSbase.def | 34 +++++------ testsuite/tests/rts/rdynamic.hs | 2 +- 30 files changed, 162 insertions(+), 203 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 89a8d817f0c2951ec305c286a526205d06bf9221 From git at git.haskell.org Mon Oct 20 23:28:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 20 Oct 2014 23:28:59 +0000 (UTC) Subject: [commit: ghc] master: Revert "BC-breaking changes to C-- CLOSURE syntax." (a3860fc) Message-ID: <20141020232859.0E9903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a3860fc4e253ecb4854e86aed78c56e72f318840/ghc >--------------------------------------------------------------- commit a3860fc4e253ecb4854e86aed78c56e72f318840 Author: Edward Z. Yang Date: Mon Oct 20 16:01:45 2014 -0700 Revert "BC-breaking changes to C-- CLOSURE syntax." This reverts commit 3b5a840bba375c4c4c11ccfeb283f84c3a1ef22c. >--------------------------------------------------------------- a3860fc4e253ecb4854e86aed78c56e72f318840 compiler/cmm/CLabel.hs | 4 ++-- compiler/cmm/CmmLex.x | 2 -- compiler/cmm/CmmParse.y | 17 ++++++++--------- rts/StgMiscClosures.cmm | 20 ++++++++++---------- 4 files changed, 20 insertions(+), 23 deletions(-) diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs index c5afa09..0f2c0ae 100644 --- a/compiler/cmm/CLabel.hs +++ b/compiler/cmm/CLabel.hs @@ -333,9 +333,9 @@ data CmmLabelInfo | CmmEntry -- ^ misc rts entry points, suffix _entry | CmmRetInfo -- ^ misc rts ret info tables, suffix _info | CmmRet -- ^ misc rts return points, suffix _ret - | CmmData -- ^ misc rts data bits + | CmmData -- ^ misc rts data bits, eg CHARLIKE_closure | CmmCode -- ^ misc rts code - | CmmClosure -- ^ misc rts closures, suffix _closure + | CmmClosure -- ^ closures eg CHARLIKE_closure | CmmPrimCall -- ^ a prim call to some hand written Cmm code deriving (Eq, Ord) diff --git a/compiler/cmm/CmmLex.x b/compiler/cmm/CmmLex.x index dfbb751..f56db7b 100644 --- a/compiler/cmm/CmmLex.x +++ b/compiler/cmm/CmmLex.x @@ -135,7 +135,6 @@ data CmmToken | CmmT_Ne | CmmT_BoolAnd | CmmT_BoolOr - | CmmT_ANONYMOUS_CLOSURE | CmmT_CLOSURE | CmmT_INFO_TABLE | CmmT_INFO_TABLE_RET @@ -219,7 +218,6 @@ name span buf len = reservedWordsFM = listToUFM $ map (\(x, y) -> (mkFastString x, y)) [ - ( "ANONYMOUS_CLOSURE", CmmT_ANONYMOUS_CLOSURE ), ( "CLOSURE", CmmT_CLOSURE ), ( "INFO_TABLE", CmmT_INFO_TABLE ), ( "INFO_TABLE_RET", CmmT_INFO_TABLE_RET ), diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 3bd0053..db6cc49 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -300,7 +300,6 @@ import Data.Maybe '||' { L _ (CmmT_BoolOr) } 'CLOSURE' { L _ (CmmT_CLOSURE) } - 'ANONYMOUS_CLOSURE'{ L _ (CmmT_ANONYMOUS_CLOSURE) } 'INFO_TABLE' { L _ (CmmT_INFO_TABLE) } 'INFO_TABLE_RET'{ L _ (CmmT_INFO_TABLE_RET) } 'INFO_TABLE_FUN'{ L _ (CmmT_INFO_TABLE_FUN) } @@ -370,10 +369,10 @@ cmmtop :: { CmmParse () } : cmmproc { $1 } | cmmdata { $1 } | decl { $1 } - | 'CLOSURE' '(' NAME lits ')' ';' + | 'CLOSURE' '(' NAME ',' NAME lits ')' ';' {% withThisPackage $ \pkg -> - do lits <- sequence $4; - staticClosure pkg $3 (map getLit lits) } + do lits <- sequence $6; + staticClosure pkg $3 $5 (map getLit lits) } -- The only static closures in the RTS are dummy closures like -- stg_END_TSO_QUEUE_closure and stg_dummy_ret. We don't need @@ -412,7 +411,7 @@ static :: { CmmParse [CmmStatic] } | typenot8 '[' INT ']' ';' { return [CmmUninitialised (widthInBytes (typeWidth $1) * fromIntegral $3)] } - | 'ANONYMOUS_CLOSURE' '(' NAME lits ')' + | 'CLOSURE' '(' NAME lits ')' { do { lits <- sequence $4 ; dflags <- getDynFlags ; return $ map CmmStaticLit $ @@ -1102,11 +1101,11 @@ profilingInfo dflags desc_str ty_str else ProfilingInfo (stringToWord8s desc_str) (stringToWord8s ty_str) -staticClosure :: PackageKey -> FastString -> [CmmLit] -> CmmParse () -staticClosure pkg label payload +staticClosure :: PackageKey -> FastString -> FastString -> [CmmLit] -> CmmParse () +staticClosure pkg cl_label info payload = do dflags <- getDynFlags - let lits = mkStaticClosure dflags (mkCmmInfoLabel pkg label) dontCareCCS payload [] [] [] - code $ emitStaticClosure (mkCmmClosureLabel pkg label) lits + let lits = mkStaticClosure dflags (mkCmmInfoLabel pkg info) dontCareCCS payload [] [] [] + code $ emitStaticClosure (mkCmmDataLabel pkg cl_label) lits foreignCall :: String diff --git a/rts/StgMiscClosures.cmm b/rts/StgMiscClosures.cmm index 85ecb5e..42ef39e 100644 --- a/rts/StgMiscClosures.cmm +++ b/rts/StgMiscClosures.cmm @@ -457,7 +457,7 @@ INFO_TABLE_CONSTR(stg_C_FINALIZER_LIST,1,4,0,CONSTR,"C_FINALIZER_LIST","C_FINALI INFO_TABLE_CONSTR(stg_NO_FINALIZER,0,0,0,CONSTR_NOCAF_STATIC,"NO_FINALIZER","NO_FINALIZER") { foreign "C" barf("NO_FINALIZER object entered!") never returns; } -CLOSURE(stg_NO_FINALIZER); +CLOSURE(stg_NO_FINALIZER_closure,stg_NO_FINALIZER); /* ---------------------------------------------------------------------------- Stable Names are unlifted too. @@ -516,13 +516,13 @@ INFO_TABLE_CONSTR(stg_END_STM_CHUNK_LIST,0,0,0,CONSTR_NOCAF_STATIC,"END_STM_CHUN INFO_TABLE_CONSTR(stg_NO_TREC,0,0,0,CONSTR_NOCAF_STATIC,"NO_TREC","NO_TREC") { foreign "C" barf("NO_TREC object entered!") never returns; } -CLOSURE(stg_END_STM_WATCH_QUEUE); +CLOSURE(stg_END_STM_WATCH_QUEUE_closure,stg_END_STM_WATCH_QUEUE); -CLOSURE(stg_END_INVARIANT_CHECK_QUEUE); +CLOSURE(stg_END_INVARIANT_CHECK_QUEUE_closure,stg_END_INVARIANT_CHECK_QUEUE); -CLOSURE(stg_END_STM_CHUNK_LIST); +CLOSURE(stg_END_STM_CHUNK_LIST_closure,stg_END_STM_CHUNK_LIST); -CLOSURE(stg_NO_TREC); +CLOSURE(stg_NO_TREC_closure,stg_NO_TREC); /* ---------------------------------------------------------------------------- Messages @@ -553,7 +553,7 @@ INFO_TABLE_CONSTR(stg_MSG_NULL,1,0,0,PRIM,"MSG_NULL","MSG_NULL") INFO_TABLE_CONSTR(stg_END_TSO_QUEUE,0,0,0,CONSTR_NOCAF_STATIC,"END_TSO_QUEUE","END_TSO_QUEUE") { foreign "C" barf("END_TSO_QUEUE object entered!") never returns; } -CLOSURE(stg_END_TSO_QUEUE); +CLOSURE(stg_END_TSO_QUEUE_closure,stg_END_TSO_QUEUE); /* ---------------------------------------------------------------------------- GCD_CAF @@ -572,7 +572,7 @@ INFO_TABLE_CONSTR(stg_GCD_CAF,0,0,0,CONSTR_NOCAF_STATIC,"GCD_CAF","GCD_CAF") INFO_TABLE_CONSTR(stg_STM_AWOKEN,0,0,0,CONSTR_NOCAF_STATIC,"STM_AWOKEN","STM_AWOKEN") { foreign "C" barf("STM_AWOKEN object entered!") never returns; } -CLOSURE(stg_STM_AWOKEN); +CLOSURE(stg_STM_AWOKEN_closure,stg_STM_AWOKEN); /* ---------------------------------------------------------------------------- Arrays @@ -638,7 +638,7 @@ INFO_TABLE( stg_dummy_ret, 0, 0, CONSTR_NOCAF_STATIC, "DUMMY_RET", "DUMMY_RET") { return (); } -CLOSURE(stg_dummy_ret); +CLOSURE(stg_dummy_ret_closure,stg_dummy_ret); /* ---------------------------------------------------------------------------- MVAR_TSO_QUEUE @@ -673,8 +673,8 @@ INFO_TABLE_CONSTR(stg_MVAR_TSO_QUEUE,2,0,0,PRIM,"MVAR_TSO_QUEUE","MVAR_TSO_QUEUE #endif -#define CHARLIKE_HDR(n) ANONYMOUS_CLOSURE(Char_hash_static_info, n) -#define INTLIKE_HDR(n) ANONYMOUS_CLOSURE(Int_hash_static_info, n) +#define CHARLIKE_HDR(n) CLOSURE(Char_hash_static_info, n) +#define INTLIKE_HDR(n) CLOSURE(Int_hash_static_info, n) /* put these in the *data* section, since the garbage collector relies * on the fact that static closures live in the data section. From git at git.haskell.org Tue Oct 21 01:09:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 01:09:34 +0000 (UTC) Subject: [commit: ghc] master: Update Haddock submodule (47c4c91) Message-ID: <20141021010934.C341E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/47c4c91d54cecd40dd1f384844b097bc807adc4b/ghc >--------------------------------------------------------------- commit 47c4c91d54cecd40dd1f384844b097bc807adc4b Author: Austin Seipp Date: Mon Oct 20 20:08:14 2014 -0500 Update Haddock submodule As requested by Yuras Shumovich, this updates Haddock to include .arcconfig and .arclint files, so diffs for GHC patches can go into Phabricator. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 47c4c91d54cecd40dd1f384844b097bc807adc4b utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 2f639ff..c3f27a9 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 2f639ffe09dd24d8648363b567de2d7caa39db99 +Subproject commit c3f27a96bd2a1ec14f441c72a2df95c16c2c5408 From git at git.haskell.org Tue Oct 21 09:05:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 09:05:43 +0000 (UTC) Subject: [commit: ghc] branch 'wip/orf-new' created Message-ID: <20141021090543.828143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/orf-new Referencing: c975175efcf733062c2e3fb1821dbf72f466b031 From git at git.haskell.org Tue Oct 21 09:05:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 09:05:46 +0000 (UTC) Subject: [commit: ghc] wip/orf-new: ghc: implement OverloadedRecordFields (c975175) Message-ID: <20141021090546.888363A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-new Link : http://ghc.haskell.org/trac/ghc/changeset/c975175efcf733062c2e3fb1821dbf72f466b031/ghc >--------------------------------------------------------------- commit c975175efcf733062c2e3fb1821dbf72f466b031 Author: Adam Gundry Date: Sat Oct 18 17:29:12 2014 +0100 ghc: implement OverloadedRecordFields This fully implements the new ORF extension, developed during the Google Summer of Code 2013, and as described on the wiki: https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields This also updates the Haddock submodule. >--------------------------------------------------------------- c975175efcf733062c2e3fb1821dbf72f466b031 compiler/basicTypes/Avail.hs | 149 ++++++- compiler/basicTypes/DataCon.lhs | 21 +- compiler/basicTypes/DataCon.lhs-boot | 2 + compiler/basicTypes/FieldLabel.lhs | 145 +++++++ compiler/basicTypes/Id.lhs | 12 +- compiler/basicTypes/MkId.lhs | 2 +- compiler/basicTypes/OccName.lhs | 32 +- compiler/basicTypes/RdrName.lhs | 152 +++++-- compiler/basicTypes/SrcLoc.lhs | 8 +- compiler/deSugar/Check.lhs | 4 +- compiler/deSugar/Coverage.lhs | 4 +- compiler/deSugar/Desugar.lhs | 2 + compiler/deSugar/DsExpr.lhs | 18 +- compiler/deSugar/DsMeta.hs | 4 +- compiler/deSugar/DsMonad.lhs | 1 + compiler/deSugar/MatchCon.lhs | 4 +- compiler/ghc.cabal.in | 3 + compiler/ghc.mk | 7 + compiler/hsSyn/Convert.lhs | 17 +- compiler/hsSyn/HsDecls.lhs | 15 +- compiler/hsSyn/HsExpr.lhs | 7 +- compiler/hsSyn/HsImpExp.lhs | 50 ++- compiler/hsSyn/HsPat.lhs | 73 +++- compiler/hsSyn/HsTypes.lhs | 72 +++- compiler/hsSyn/HsUtils.lhs | 85 ++-- compiler/iface/BuildTyCl.lhs | 2 +- compiler/iface/IfaceSyn.lhs | 47 +- compiler/iface/LoadIface.lhs | 14 +- compiler/iface/MkIface.lhs | 31 +- compiler/iface/TcIface.lhs | 30 +- compiler/main/DynFlags.hs | 10 + compiler/main/GHC.hs | 19 +- compiler/main/HscMain.hs | 16 +- compiler/main/HscTypes.lhs | 27 +- compiler/main/InteractiveEval.hs | 2 +- compiler/main/TidyPgm.lhs | 10 +- compiler/parser/Parser.y.pp | 6 +- compiler/parser/RdrHsSyn.lhs | 6 +- compiler/prelude/PrelInfo.lhs | 2 +- compiler/prelude/PrelNames.lhs | 43 +- compiler/prelude/TysWiredIn.lhs | 2 +- compiler/rename/RnEnv.lhs | 305 ++++++++++--- compiler/rename/RnExpr.lhs | 20 +- compiler/rename/RnNames.lhs | 449 ++++++++++++++----- compiler/rename/RnPat.lhs | 75 ++-- compiler/rename/RnSource.lhs | 125 ++++-- compiler/rename/RnTypes.lhs | 53 ++- compiler/typecheck/FamInst.lhs | 55 ++- compiler/typecheck/Inst.lhs | 3 +- compiler/typecheck/TcEnv.lhs | 57 +-- compiler/typecheck/TcErrors.lhs | 54 ++- compiler/typecheck/TcEvidence.lhs | 1 + compiler/typecheck/TcExpr.lhs | 320 +++++++++++--- compiler/typecheck/TcFldInsts.lhs | 473 +++++++++++++++++++++ compiler/typecheck/TcGenDeriv.lhs | 11 +- compiler/typecheck/TcGenGenerics.lhs | 16 +- compiler/typecheck/TcHsSyn.lhs | 4 +- compiler/typecheck/TcHsType.lhs | 17 +- compiler/typecheck/TcInstDcls.lhs | 2 +- compiler/typecheck/TcInteract.lhs | 65 ++- compiler/typecheck/TcPat.lhs | 24 +- compiler/typecheck/TcRnDriver.lhs | 22 +- compiler/typecheck/TcRnMonad.lhs | 5 +- compiler/typecheck/TcRnTypes.lhs | 31 +- compiler/typecheck/TcSMonad.lhs | 18 +- compiler/typecheck/TcSplice.lhs | 2 +- compiler/typecheck/TcTyClsDecls.lhs | 79 ++-- compiler/typecheck/TcType.lhs | 9 + compiler/typecheck/TcValidity.lhs | 19 +- compiler/types/TyCon.lhs | 52 ++- compiler/types/Type.lhs | 29 +- compiler/types/Type.lhs-boot | 2 + compiler/types/TypeRep.lhs | 44 +- compiler/utils/Binary.hs | 1 - compiler/utils/FastStringEnv.lhs | 75 ++++ docs/users_guide/glasgow_exts.xml | 307 +++++++++++++ libraries/base/GHC/Base.lhs | 1 + libraries/base/GHC/Records.hs | 249 +++++++++++ libraries/base/GHC/TypeLits.hs | 8 +- libraries/base/base.cabal | 1 + testsuite/tests/driver/T4437.hs | 1 + testsuite/tests/ghci/scripts/ghci042.stdout | 2 +- testsuite/tests/module/mod176.stderr | 2 +- .../{annotations => overloadedrecflds}/Makefile | 0 .../ghci}/Makefile | 0 testsuite/tests/overloadedrecflds/ghci/all.T | 3 + .../ghci/overloadedrecfldsghci01.script | 13 + .../ghci/overloadedrecfldsghci01.stdout | 11 + .../should_fail}/Makefile | 0 .../should_fail/OverloadedRecFldsFail04_A.hs | 9 + .../should_fail/OverloadedRecFldsFail06_A.hs | 16 + .../should_fail/OverloadedRecFldsFail08_A.hs | 14 + .../tests/overloadedrecflds/should_fail/all.T | 16 + .../should_fail/overloadedrecfldsfail01.hs | 17 + .../should_fail/overloadedrecfldsfail01.stderr | 16 + .../should_fail/overloadedrecfldsfail02.hs | 19 + .../should_fail/overloadedrecfldsfail02.stderr | 50 +++ .../should_fail/overloadedrecfldsfail03.hs | 7 + .../should_fail/overloadedrecfldsfail03.stderr | 5 + .../should_fail/overloadedrecfldsfail04.hs | 9 + .../should_fail/overloadedrecfldsfail04.stderr | 5 + .../should_fail/overloadedrecfldsfail05.hs | 10 + .../should_fail/overloadedrecfldsfail05.stderr | 10 + .../should_fail/overloadedrecfldsfail06.hs | 10 + .../should_fail/overloadedrecfldsfail06.stderr | 15 + .../should_fail/overloadedrecfldsfail07.hs | 11 + .../should_fail/overloadedrecfldsfail07.stderr | 6 + .../should_fail/overloadedrecfldsfail08.hs | 13 + .../should_fail/overloadedrecfldsfail08.stderr | 47 ++ .../should_fail/overloadedrecfldsfail09.hs | 9 + .../should_fail/overloadedrecfldsfail09.stderr | 20 + .../should_fail/overloadedrecfldsfail10.hs | 11 + .../should_fail/overloadedrecfldsfail10.stderr | 9 + .../should_run}/Makefile | 0 .../should_run/OverloadedRecFldsRun01_A.hs | 9 + .../should_run/OverloadedRecFldsRun02_A.hs | 9 + .../should_run/OverloadedRecFldsRun07_A.hs | 11 + .../should_run/OverloadedRecFldsRun07_B.hs | 7 + .../should_run/OverloadedRecFldsRun08_A.hs | 11 + .../should_run/OverloadedRecFldsRun08_B.hs | 7 + .../should_run/OverloadedRecFldsRun08_C.hs | 7 + .../should_run/OverloadedRecFldsRun11_A.hs | 9 + .../should_run/OverloadedRecFldsRun11_A.hs-boot | 5 + .../should_run/OverloadedRecFldsRun11_B.hs | 7 + .../should_run/OverloadedRecFldsRun12_A.hs | 11 + .../should_run/OverloadedRecFldsRun12_B.hs | 7 + testsuite/tests/overloadedrecflds/should_run/all.T | 26 ++ .../should_run/overloadedrecfldsrun01.hs | 70 +++ .../should_run/overloadedrecfldsrun01.stdout | 13 + .../should_run/overloadedrecfldsrun02.hs | 6 + .../should_run/overloadedrecfldsrun02.stdout | 0 .../should_run/overloadedrecfldsrun03.hs | 18 + .../should_run/overloadedrecfldsrun03.stdout | 4 + .../should_run/overloadedrecfldsrun04.hs | 18 + .../should_run/overloadedrecfldsrun04.stdout | 3 + .../should_run/overloadedrecfldsrun05.hs | 34 ++ .../should_run/overloadedrecfldsrun05.stdout | 2 + .../should_run/overloadedrecfldsrun06.hs | 28 ++ .../should_run/overloadedrecfldsrun06.stdout | 1 + .../should_run/overloadedrecfldsrun07.hs | 7 + .../should_run/overloadedrecfldsrun07.stdout} | 0 .../should_run/overloadedrecfldsrun08.hs | 7 + .../should_run/overloadedrecfldsrun08.stdout | 2 + .../should_run/overloadedrecfldsrun09.hs | 8 + .../should_run/overloadedrecfldsrun09.stdout | 2 + .../should_run/overloadedrecfldsrun10.hs | 12 + .../should_run/overloadedrecfldsrun10.stderr | 2 + .../should_run/overloadedrecfldsrun11.hs | 5 + .../should_run/overloadedrecfldsrun11.stdout} | 0 .../should_run/overloadedrecfldsrun12.hs | 6 + .../should_run/overloadedrecfldsrun12.stdout | 2 + .../should_run/overloadedrecfldsrun13.hs | 9 + .../should_run/overloadedrecfldsrun13.stdout} | 0 testsuite/tests/rename/should_fail/T5892a.stderr | 2 +- .../tests/typecheck/should_fail/tcfail102.stderr | 3 +- utils/ghctags/Main.hs | 2 +- utils/haddock | 2 +- 157 files changed, 4277 insertions(+), 742 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 c975175efcf733062c2e3fb1821dbf72f466b031 From git at git.haskell.org Tue Oct 21 09:15:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 09:15:16 +0000 (UTC) Subject: [commit: ghc] master: Revert "rts/PrimOps.cmm: follow '_static_closure' update" (07a99c1) Message-ID: <20141021091516.034B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/07a99c163af2ea5346e94e416d00d50f09f4b7f7/ghc >--------------------------------------------------------------- commit 07a99c163af2ea5346e94e416d00d50f09f4b7f7 Author: Sergei Trofimovich Date: Tue Oct 21 09:40:07 2014 +0100 Revert "rts/PrimOps.cmm: follow '_static_closure' update" This reverts commit eb191ab6c85f4b668a6e9151dcecaf1f1e7ec7c2. Follows revert of STATIC_CLOSURE and restores UNREG build. >--------------------------------------------------------------- 07a99c163af2ea5346e94e416d00d50f09f4b7f7 rts/PrimOps.cmm | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm index 16c91e9..3e8612c 100644 --- a/rts/PrimOps.cmm +++ b/rts/PrimOps.cmm @@ -28,7 +28,7 @@ import pthread_mutex_lock; import pthread_mutex_unlock; #endif -import base_ControlziExceptionziBase_nestedAtomically_static_closure; +import base_ControlziExceptionziBase_nestedAtomically_closure; import EnterCriticalSection; import LeaveCriticalSection; import ghczmprim_GHCziTypes_False_closure; From git at git.haskell.org Tue Oct 21 12:54:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 12:54:19 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T9705' created Message-ID: <20141021125419.5C3D93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T9705 Referencing: 85aacc60244af978b8fa086369e832c9e0f7d3ee From git at git.haskell.org Tue Oct 21 12:54:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 12:54:21 +0000 (UTC) Subject: [commit: ghc] wip/T9705: rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) (6a50d98) Message-ID: <20141021125421.F019B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9705 Link : http://ghc.haskell.org/trac/ghc/changeset/6a50d983c079a921679bb7834ea361b70648fc2e/ghc >--------------------------------------------------------------- commit 6a50d983c079a921679bb7834ea361b70648fc2e Author: Dr. ERDI Gergo Date: Tue Oct 21 20:51:35 2014 +0800 rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) >--------------------------------------------------------------- 6a50d983c079a921679bb7834ea361b70648fc2e compiler/rename/RnBinds.lhs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index c572e32..553df0b 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 Tue Oct 21 12:54:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 12:54:24 +0000 (UTC) Subject: [commit: ghc] wip/T9705: Add test case for T9705 (85aacc6) Message-ID: <20141021125424.EAAEC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9705 Link : http://ghc.haskell.org/trac/ghc/changeset/85aacc60244af978b8fa086369e832c9e0f7d3ee/ghc >--------------------------------------------------------------- commit 85aacc60244af978b8fa086369e832c9e0f7d3ee Author: Dr. ERDI Gergo Date: Tue Oct 21 20:51:55 2014 +0800 Add test case for T9705 >--------------------------------------------------------------- 85aacc60244af978b8fa086369e832c9e0f7d3ee 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 Tue Oct 21 13:10:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:10:55 +0000 (UTC) Subject: [commit: ghc] wip/T9705: rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) (775a9c1) Message-ID: <20141021131055.0AD823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9705 Link : http://ghc.haskell.org/trac/ghc/changeset/775a9c139a7a85bfa471fc4482cd26329dc64809/ghc >--------------------------------------------------------------- commit 775a9c139a7a85bfa471fc4482cd26329dc64809 Author: Dr. ERDI Gergo Date: Tue Oct 21 20:51:35 2014 +0800 rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705) >--------------------------------------------------------------- 775a9c139a7a85bfa471fc4482cd26329dc64809 compiler/rename/RnBinds.lhs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index c572e32..553df0b 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 Tue Oct 21 13:10:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:10:58 +0000 (UTC) Subject: [commit: ghc] wip/T9705: Add test case for T9705 (18d52f3) Message-ID: <20141021131058.08E9F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9705 Link : http://ghc.haskell.org/trac/ghc/changeset/18d52f30251f04f7f822371865839c947e75ddcb/ghc >--------------------------------------------------------------- commit 18d52f30251f04f7f822371865839c947e75ddcb Author: Dr. ERDI Gergo Date: Tue Oct 21 20:51:55 2014 +0800 Add test case for T9705 >--------------------------------------------------------------- 18d52f30251f04f7f822371865839c947e75ddcb 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 Tue Oct 21 13:21:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:21:24 +0000 (UTC) Subject: [commit: ghc] master: Clarify location of Note. Comment change only. (2cd80ba) Message-ID: <20141021132124.8BA403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2cd80baab42e2352d0216517a14b898abae7f697/ghc >--------------------------------------------------------------- commit 2cd80baab42e2352d0216517a14b898abae7f697 Author: Richard Eisenberg Date: Mon Oct 20 15:36:37 2014 -0400 Clarify location of Note. Comment change only. >--------------------------------------------------------------- 2cd80baab42e2352d0216517a14b898abae7f697 compiler/types/FamInstEnv.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/types/FamInstEnv.lhs b/compiler/types/FamInstEnv.lhs index 3ff9e3b..7fe35ff 100644 --- a/compiler/types/FamInstEnv.lhs +++ b/compiler/types/FamInstEnv.lhs @@ -757,7 +757,7 @@ We handle data families and type families separately here: * For data family instances, though, we need to re-split for each instance, because the breakdown might be different for each instance. Why? Because of eta reduction; see Note [Eta reduction - for data family axioms] + for data family axioms] in TcInstDcls. \begin{code} From git at git.haskell.org Tue Oct 21 13:21:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:21:27 +0000 (UTC) Subject: [commit: ghc] master: Test #9692 in th/T9692 (f681c32) Message-ID: <20141021132127.BC3733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f681c3274c4481ab549508fa346892023bf9d9bb/ghc >--------------------------------------------------------------- commit f681c3274c4481ab549508fa346892023bf9d9bb Author: Richard Eisenberg Date: Mon Oct 20 15:11:59 2014 -0400 Test #9692 in th/T9692 >--------------------------------------------------------------- f681c3274c4481ab549508fa346892023bf9d9bb testsuite/tests/th/T9692.hs | 17 +++++++++++++++++ testsuite/tests/th/T9692.stderr | 2 ++ testsuite/tests/th/all.T | 2 +- 3 files changed, 20 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/th/T9692.hs b/testsuite/tests/th/T9692.hs new file mode 100644 index 0000000..82e5951 --- /dev/null +++ b/testsuite/tests/th/T9692.hs @@ -0,0 +1,17 @@ +{-# LANGUAGE TemplateHaskell, TypeFamilies, PolyKinds #-} + +module T9692 where + +import Language.Haskell.TH +import Language.Haskell.TH.Syntax +import Language.Haskell.TH.Ppr + +class C a where + data F a (b :: k) :: * + +instance C Int where + data F Int x = FInt x + +$( do info <- qReify (mkName "F") + runIO $ putStrLn $ pprint info + return []) diff --git a/testsuite/tests/th/T9692.stderr b/testsuite/tests/th/T9692.stderr new file mode 100644 index 0000000..e62c8c5 --- /dev/null +++ b/testsuite/tests/th/T9692.stderr @@ -0,0 +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 diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 7c030d0..2981202 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -330,4 +330,4 @@ test('T8932', normal, compile_fail, ['-v0']) test('T8987', normal, compile_fail, ['-v0']) test('T7241', normal, compile_fail, ['-v0']) test('T9199', normal, compile, ['-v0']) - +test('T9692', normal, compile, ['-v0']) From git at git.haskell.org Tue Oct 21 13:21:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:21:30 +0000 (UTC) Subject: [commit: ghc] master: Reify data family instances correctly. (e319d6d) Message-ID: <20141021132130.5945A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e319d6d2704edc2696f47409f85f4d4ce58a6cc4/ghc >--------------------------------------------------------------- commit e319d6d2704edc2696f47409f85f4d4ce58a6cc4 Author: Richard Eisenberg Date: Mon Oct 20 15:36:57 2014 -0400 Reify data family instances correctly. Summary: Fix #9692. The reifier didn't account for the possibility that data/newtype instances are sometimes eta-reduced. It now eta-expands as necessary. Test Plan: th/T9692 Reviewers: simonpj, austin Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D355 >--------------------------------------------------------------- e319d6d2704edc2696f47409f85f4d4ce58a6cc4 compiler/typecheck/TcSplice.lhs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcSplice.lhs b/compiler/typecheck/TcSplice.lhs index bb6af8c..e952a27 100644 --- a/compiler/typecheck/TcSplice.lhs +++ b/compiler/typecheck/TcSplice.lhs @@ -1338,8 +1338,16 @@ reifyFamilyInstance (FamInst { fi_flavor = flavor DataFamilyInst rep_tc -> do { let tvs = tyConTyVars rep_tc fam' = reifyName fam + + -- eta-expand lhs types, because sometimes data/newtype + -- instances are eta-reduced; See Trac #9692 + -- See Note [Eta reduction for data family axioms] + -- in TcInstDcls + (_rep_tc, rep_tc_args) = splitTyConApp rhs + etad_tyvars = dropList rep_tc_args tvs + eta_expanded_lhs = lhs `chkAppend` mkTyVarTys etad_tyvars ; cons <- mapM (reifyDataCon (mkTyVarTys tvs)) (tyConDataCons rep_tc) - ; th_tys <- reifyTypes lhs + ; th_tys <- reifyTypes (filter (not . isKind) eta_expanded_lhs) ; return (if isNewTyCon rep_tc then TH.NewtypeInstD [] fam' th_tys (head cons) [] else TH.DataInstD [] fam' th_tys cons []) } From git at git.haskell.org Tue Oct 21 13:30:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:30:04 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Update baseline shift/reduce conflict number (e80e0d9) Message-ID: <20141021133004.B19233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/e80e0d9e9900a56ab4e46202c014200f9185587b/ghc >--------------------------------------------------------------- commit e80e0d9e9900a56ab4e46202c014200f9185587b Author: Dr. ERDI Gergo Date: Wed Jul 2 19:18:43 2014 +0800 Update baseline shift/reduce conflict number >--------------------------------------------------------------- e80e0d9e9900a56ab4e46202c014200f9185587b 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 Tue Oct 21 13:30:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:30:07 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add parser for pattern synonym type signatures. Syntax is of the form (7774b50) Message-ID: <20141021133007.527D73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/7774b507abae777593ee575307bd4284788e1ba7/ghc >--------------------------------------------------------------- commit 7774b507abae777593ee575307bd4284788e1ba7 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. >--------------------------------------------------------------- 7774b507abae777593ee575307bd4284788e1ba7 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 Tue Oct 21 13:30:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:30:09 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Renamer for PatSynSigs: handle type variable bindings (cf66d7f) Message-ID: <20141021133009.EC6343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/cf66d7f3c8f395874e290076ac9dd57beec49ff3/ghc >--------------------------------------------------------------- commit cf66d7f3c8f395874e290076ac9dd57beec49ff3 Author: Dr. ERDI Gergo Date: Tue Oct 21 21:19:21 2014 +0800 Renamer for PatSynSigs: handle type variable bindings >--------------------------------------------------------------- cf66d7f3c8f395874e290076ac9dd57beec49ff3 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 c572e32..582c0e7 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 @@ -837,22 +837,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 Tue Oct 21 13:30:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:30:12 +0000 (UTC) Subject: [commit: ghc] wip/T8584: PatSynSig: Add type variable binders (1bd74d9) Message-ID: <20141021133012.8D5DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/1bd74d9195778bca51e0a12b3fb61de6d28d8865/ghc >--------------------------------------------------------------- commit 1bd74d9195778bca51e0a12b3fb61de6d28d8865 Author: Dr. ERDI Gergo Date: Mon Jul 21 19:40:34 2014 +0800 PatSynSig: Add type variable binders >--------------------------------------------------------------- 1bd74d9195778bca51e0a12b3fb61de6d28d8865 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 582c0e7..96a2066 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -836,15 +836,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 @@ -860,15 +860,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 Tue Oct 21 13:30:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:30:15 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Split tcPatSynDecl into inferring function and general workhorse function (d9bee88) Message-ID: <20141021133015.300303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/d9bee880790b08fabb9ee5743ecea15a4cf56804/ghc >--------------------------------------------------------------- commit d9bee880790b08fabb9ee5743ecea15a4cf56804 Author: Dr. ERDI Gergo Date: Sun Jul 27 14:10:34 2014 +0200 Split tcPatSynDecl into inferring function and general workhorse function >--------------------------------------------------------------- d9bee880790b08fabb9ee5743ecea15a4cf56804 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 c286d3b..6662b8a 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 Tue Oct 21 13:30:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:30:17 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add TcPatSynInfo to store the typechecked representation of a pattern synonym type signature (fefa5bf) Message-ID: <20141021133017.BF1383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/fefa5bfb5a18f6c59d89d3beffeed4045856ad20/ghc >--------------------------------------------------------------- commit fefa5bfb5a18f6c59d89d3beffeed4045856ad20 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 >--------------------------------------------------------------- fefa5bfb5a18f6c59d89d3beffeed4045856ad20 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 fefa5bfb5a18f6c59d89d3beffeed4045856ad20 From git at git.haskell.org Tue Oct 21 13:30:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:30:20 +0000 (UTC) Subject: [commit: ghc] wip/T8584: universially-bound tyvars are in scope when renaming existentially-bound tyvars in a pattern synonym signature (5c196b2) Message-ID: <20141021133020.5B6E23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/5c196b27fa4b6889e6803135743299172c97fe70/ghc >--------------------------------------------------------------- commit 5c196b27fa4b6889e6803135743299172c97fe70 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 >--------------------------------------------------------------- 5c196b27fa4b6889e6803135743299172c97fe70 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 96a2066..be98815 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 @@ -860,10 +861,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 Tue Oct 21 13:30:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:30:22 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Show foralls (when requested) in pattern synonym types (a8b245a) Message-ID: <20141021133022.F3B853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/a8b245ada1788ed8e4f79cbff9b92f01d5c8265e/ghc >--------------------------------------------------------------- commit a8b245ada1788ed8e4f79cbff9b92f01d5c8265e Author: Dr. ERDI Gergo Date: Sun Aug 3 15:26:13 2014 +0200 Show foralls (when requested) in pattern synonym types >--------------------------------------------------------------- a8b245ada1788ed8e4f79cbff9b92f01d5c8265e 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 e45fac2..5f42446 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -765,11 +765,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 @@ -780,8 +782,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 Tue Oct 21 13:30:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:30:25 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Add TcPatSynInfo as a separate type (same pattern as PatSynBind being a separate type) (03e36b4) Message-ID: <20141021133025.910223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/03e36b46c3e6bad730db25cd988c909595c97d01/ghc >--------------------------------------------------------------- commit 03e36b46c3e6bad730db25cd988c909595c97d01 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) >--------------------------------------------------------------- 03e36b46c3e6bad730db25cd988c909595c97d01 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 d5eb19b..1a80369 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 Tue Oct 21 13:30:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:30:28 +0000 (UTC) Subject: [commit: ghc] wip/T8584: tcTySig for PatSynSigs: filter out universially-bound type variables from ex_tvs (44474bd) Message-ID: <20141021133028.362833A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/44474bd1f7f8659972ad736387b4c889ebc81855/ghc >--------------------------------------------------------------- commit 44474bd1f7f8659972ad736387b4c889ebc81855 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 >--------------------------------------------------------------- 44474bd1f7f8659972ad736387b4c889ebc81855 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 bfa703e..d5eb19b 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 Tue Oct 21 13:30:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:30:30 +0000 (UTC) Subject: [commit: ghc] wip/T8584: Create SigTyVars for existentials under tcPat when typechecking a PatSyn with a type signature (afc9af3) Message-ID: <20141021133030.CBA6F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8584 Link : http://ghc.haskell.org/trac/ghc/changeset/afc9af3df8e93def19d00b20ea3bab108acf8535/ghc >--------------------------------------------------------------- commit afc9af3df8e93def19d00b20ea3bab108acf8535 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 >--------------------------------------------------------------- afc9af3df8e93def19d00b20ea3bab108acf8535 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 afc9af3df8e93def19d00b20ea3bab108acf8535 From git at git.haskell.org Tue Oct 21 13:30:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:30:34 +0000 (UTC) Subject: [commit: ghc] wip/T8584's head updated: Create SigTyVars for existentials under tcPat when typechecking a PatSyn with a type signature (afc9af3) Message-ID: <20141021133034.5C7263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T8584' now includes: 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 e80e0d9 Update baseline shift/reduce conflict number 7774b50 Add parser for pattern synonym type signatures. Syntax is of the form cf66d7f Renamer for PatSynSigs: handle type variable bindings 1bd74d9 PatSynSig: Add type variable binders d9bee88 Split tcPatSynDecl into inferring function and general workhorse function fefa5bf Add TcPatSynInfo to store the typechecked representation of a pattern synonym type signature 5c196b2 universially-bound tyvars are in scope when renaming existentially-bound tyvars in a pattern synonym signature 44474bd tcTySig for PatSynSigs: filter out universially-bound type variables from ex_tvs a8b245a Show foralls (when requested) in pattern synonym types 03e36b4 Add TcPatSynInfo as a separate type (same pattern as PatSynBind being a separate type) afc9af3 Create SigTyVars for existentials under tcPat when typechecking a PatSyn with a type signature From git at git.haskell.org Tue Oct 21 13:59:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 13:59:57 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: More progress (ffd19d0) Message-ID: <20141021135957.A05EE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/ffd19d0e26ff2840909ea2dd2848e8c2c930d3b2/ghc >--------------------------------------------------------------- commit ffd19d0e26ff2840909ea2dd2848e8c2c930d3b2 Author: Simon Peyton Jones Date: Mon Oct 20 22:28:53 2014 +0100 More progress >--------------------------------------------------------------- ffd19d0e26ff2840909ea2dd2848e8c2c930d3b2 compiler/main/PprTyThing.hs | 2 +- compiler/typecheck/Flattening-notes | 8 ++-- compiler/typecheck/TcCanonical.lhs | 54 +++++++++++++------------- compiler/typecheck/TcPatSyn.lhs | 16 +++++--- compiler/typecheck/TcSMonad.lhs | 75 +++++++++++-------------------------- compiler/typecheck/TcSimplify.lhs | 9 +---- 6 files changed, 66 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 ffd19d0e26ff2840909ea2dd2848e8c2c930d3b2 From git at git.haskell.org Tue Oct 21 14:00:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 14:00:01 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: More progress (e7988ed) Message-ID: <20141021140001.3F2973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/e7988ed7eead16d065d93c7c894e6ca5d0e906cf/ghc >--------------------------------------------------------------- commit e7988ed7eead16d065d93c7c894e6ca5d0e906cf Author: Simon Peyton Jones Date: Tue Oct 21 14:59:32 2014 +0100 More progress Including adding ib_tyvars to InstBindings >--------------------------------------------------------------- e7988ed7eead16d065d93c7c894e6ca5d0e906cf compiler/typecheck/Inst.lhs | 9 ++++++--- compiler/typecheck/TcDeriv.lhs | 21 ++++++++++----------- compiler/typecheck/TcEnv.lhs | 13 +++++++++---- compiler/typecheck/TcGenGenerics.lhs | 3 +++ compiler/typecheck/TcInstDcls.lhs | 13 ++++++------- compiler/typecheck/TcMType.lhs | 5 ++--- compiler/types/InstEnv.lhs | 4 ++-- testsuite/tests/typecheck/should_compile/T9708.hs | 10 ++++++++++ .../tests/typecheck/should_compile/T9708.stderr | 17 +++++++++++++++++ .../typecheck/should_compile/TcTypeNatSimple.hs | 8 -------- testsuite/tests/typecheck/should_compile/all.T | 1 + 11 files changed, 66 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 e7988ed7eead16d065d93c7c894e6ca5d0e906cf From git at git.haskell.org Tue Oct 21 14:12:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 14:12:16 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Merge commit with origin/master (c4eb017) Message-ID: <20141021141216.D95EE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/c4eb0176b606d2712ccce200fc12168013a144fc/ghc >--------------------------------------------------------------- commit c4eb0176b606d2712ccce200fc12168013a144fc Merge: e7988ed e319d6d Author: Simon Peyton Jones Date: Tue Oct 21 15:11:29 2014 +0100 Merge commit with origin/master >--------------------------------------------------------------- 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 c4eb0176b606d2712ccce200fc12168013a144fc From git at git.haskell.org Tue Oct 21 14:12:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 14:12:19 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14's head updated: Merge commit with origin/master (c4eb017) Message-ID: <20141021141219.21E083A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/new-flatten-skolems-Aug14' now includes: 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. c4eb017 Merge commit with origin/master From git at git.haskell.org Tue Oct 21 18:44:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 18:44:09 +0000 (UTC) Subject: [commit: ghc] master: Update primitive, vector, and dph submodules. (710bc8d) Message-ID: <20141021184409.52F193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/710bc8d77be454243ae8de2a1fb9070b72b525c4/ghc >--------------------------------------------------------------- commit 710bc8d77be454243ae8de2a1fb9070b72b525c4 Author: Geoffrey Mainland Date: Wed Aug 27 22:33:44 2014 -0400 Update primitive, vector, and dph submodules. >--------------------------------------------------------------- 710bc8d77be454243ae8de2a1fb9070b72b525c4 libraries/dph | 2 +- libraries/primitive | 2 +- libraries/vector | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/dph b/libraries/dph index 3ebad52..33eb2fb 160000 --- a/libraries/dph +++ b/libraries/dph @@ -1 +1 @@ -Subproject commit 3ebad521cd1e3b5573d97b483305ca465a9cba69 +Subproject commit 33eb2fb7e178c18f2afd0d537d791d021ff75231 diff --git a/libraries/primitive b/libraries/primitive index be63ee1..29cb0db 160000 --- a/libraries/primitive +++ b/libraries/primitive @@ -1 +1 @@ -Subproject commit be63ee15d961dc1b08bc8853b9ff97708551ef36 +Subproject commit 29cb0db59803c9d9181f7c4ce35ef1c6cbc6ccfb diff --git a/libraries/vector b/libraries/vector index a6049ab..c0308f1 160000 --- a/libraries/vector +++ b/libraries/vector @@ -1 +1 @@ -Subproject commit a6049abce040713e9a5f175887cf70d12b9057c6 +Subproject commit c0308f1c4f57859d9a8b10d504afe56eebbb27c5 From git at git.haskell.org Tue Oct 21 18:44:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 18:44:11 +0000 (UTC) Subject: [commit: ghc] master: Make Applicative-Monad fixes for tests. (27f7552) Message-ID: <20141021184411.E3D643A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/27f7552745fa320e72096b30b08558b7a275bbcc/ghc >--------------------------------------------------------------- commit 27f7552745fa320e72096b30b08558b7a275bbcc Author: Geoffrey Mainland Date: Thu Oct 2 17:39:34 2014 -0400 Make Applicative-Monad fixes for tests. >--------------------------------------------------------------- 27f7552745fa320e72096b30b08558b7a275bbcc testsuite/tests/array/should_run/arr016.hs | 8 ++++++-- testsuite/tests/codeGen/should_run/CopySmallArrayStressTest.hs | 2 +- testsuite/tests/codeGen/should_run/cgrun068.hs | 2 +- 3 files changed, 8 insertions(+), 4 deletions(-) diff --git a/testsuite/tests/array/should_run/arr016.hs b/testsuite/tests/array/should_run/arr016.hs index 055e660..0e8e2bf 100644 --- a/testsuite/tests/array/should_run/arr016.hs +++ b/testsuite/tests/array/should_run/arr016.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE ScopedTypeVariables, DatatypeContexts #-} +{-# LANGUAGE ScopedTypeVariables #-} module Main where @@ -151,7 +151,7 @@ instance Show (a -> b) where { show _ = "" } ------------------------------------------------------------------------------ -data (Ix a) => Array a b = MkArray (a,a) (a -> b) deriving () +data Array a b = MkArray (a,a) (a -> b) deriving () array :: (Ix a) => (a,a) -> [(a,b)] -> Array a b array b ivs = @@ -259,6 +259,10 @@ generate n rnd (Gen m) = m size rnd' instance Functor Gen where fmap f m = m >>= return . f +instance Applicative Gen where + pure = return + (<*>) = liftM2 id + instance Monad Gen where return a = Gen (\n r -> a) Gen m >>= k = diff --git a/testsuite/tests/codeGen/should_run/CopySmallArrayStressTest.hs b/testsuite/tests/codeGen/should_run/CopySmallArrayStressTest.hs index 7243fad..05a84df 100644 --- a/testsuite/tests/codeGen/should_run/CopySmallArrayStressTest.hs +++ b/testsuite/tests/codeGen/should_run/CopySmallArrayStressTest.hs @@ -361,7 +361,7 @@ cloneMArraySlow !marr !off n = -- Utilities for simplifying RNG passing newtype Rng s a = Rng { unRng :: StateT StdGen (ST s) a } - deriving Monad + deriving (Functor, Applicative, Monad) -- Same as 'randomR', but using the RNG state kept in the 'Rng' monad. rnd :: Random a => (a, a) -> Rng s a diff --git a/testsuite/tests/codeGen/should_run/cgrun068.hs b/testsuite/tests/codeGen/should_run/cgrun068.hs index 69a8b27..00d1249 100644 --- a/testsuite/tests/codeGen/should_run/cgrun068.hs +++ b/testsuite/tests/codeGen/should_run/cgrun068.hs @@ -361,7 +361,7 @@ cloneMArraySlow !marr !off n = -- Utilities for simplifying RNG passing newtype Rng s a = Rng { unRng :: StateT StdGen (ST s) a } - deriving Monad + deriving (Functor, Applicative, Monad) -- Same as 'randomR', but using the RNG state kept in the 'Rng' monad. rnd :: Random a => (a, a) -> Rng s a From git at git.haskell.org Tue Oct 21 21:50:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:50:28 +0000 (UTC) Subject: [commit: ghc] master: Updated testsuite/.gitignore to cover artifacts on Windows. (3687089) Message-ID: <20141021215028.55CFF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3687089fd55e3c8d2710da5c9fb4b53c6c84e0cf/ghc >--------------------------------------------------------------- commit 3687089fd55e3c8d2710da5c9fb4b53c6c84e0cf Author: Gintautas Miliauskas Date: Tue Oct 21 14:57:57 2014 -0500 Updated testsuite/.gitignore to cover artifacts on Windows. Test Plan: git status after a test run Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D333 GHC Trac Issues: #9679 >--------------------------------------------------------------- 3687089fd55e3c8d2710da5c9fb4b53c6c84e0cf testsuite/.gitignore | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/testsuite/.gitignore b/testsuite/.gitignore index e8b83e8..4552204 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -30,6 +30,7 @@ Thumbs.db *.genscript *.stderr.normalised +*.stderr-mingw32.normalised *.stderr-ghc.normalised *.stdout.normalised *.interp.stdout @@ -53,9 +54,9 @@ tmp.d *.so *bindisttest_install___dir_bin_ghc.mk *bindisttest_install___dir_bin_ghc.exe.mk -mk/ghcconfig_*_inplace_bin_ghc-stage1.mk -mk/ghcconfig_*_inplace_bin_ghc-stage2.mk -mk/ghcconfig_*_inplace_bin_ghc-stage2.exe.mk +mk/ghcconfig*_inplace_bin_ghc-stage1.mk +mk/ghcconfig*_inplace_bin_ghc-stage2.mk +mk/ghcconfig*_inplace_bin_ghc-stage2.exe.mk *.imports # ----------------------------------------------------------------------------- From git at git.haskell.org Tue Oct 21 21:50:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:50:30 +0000 (UTC) Subject: [commit: ghc] master: Use objdump instead of nm to derive constants on OpenBSD (2cc2065) Message-ID: <20141021215030.DE0AC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2cc206505d248ac8c706aa85342a895857c9f091/ghc >--------------------------------------------------------------- commit 2cc206505d248ac8c706aa85342a895857c9f091 Author: Austin Seipp Date: Tue Oct 21 14:58:21 2014 -0500 Use objdump instead of nm to derive constants on OpenBSD Summary: OpenBSD's nm doesn't support the -P option and there appears to be no other way to get the desired information from it. Reviewers: kgardas, #ghc, austin Reviewed By: kgardas, #ghc, austin Subscribers: austin, ggreif Projects: #ghc Differential Revision: https://phabricator.haskell.org/D332 GHC Trac Issues: #9549 >--------------------------------------------------------------- 2cc206505d248ac8c706aa85342a895857c9f091 utils/deriveConstants/DeriveConstants.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/utils/deriveConstants/DeriveConstants.hs b/utils/deriveConstants/DeriveConstants.hs index 9bf2160..72605d7 100644 --- a/utils/deriveConstants/DeriveConstants.hs +++ b/utils/deriveConstants/DeriveConstants.hs @@ -643,7 +643,10 @@ getWanted verbose tmpdir gccProgram gccFlags nmProgram oFile = tmpdir "tmp.o" writeFile cFile cStuff execute verbose gccProgram (gccFlags ++ ["-c", cFile, "-o", oFile]) - xs <- readProcess nmProgram ["-P", oFile] "" + xs <- case os of + "openbsd" -> readProcess "/usr/bin/objdump" ["--syms", oFile] "" + _ -> readProcess nmProgram ["-P", oFile] "" + let ls = lines xs ms = map parseNmLine ls m = Map.fromList $ catMaybes ms @@ -723,6 +726,7 @@ getWanted verbose tmpdir gccProgram gccFlags nmProgram ('_' : n) : "C" : s : _ -> mkP n s n : "C" : s : _ -> mkP n s [n, "D", _, s] -> mkP n s + [s, "O", "*COM*", _, n] -> mkP n s _ -> Nothing where mkP r s = case (stripPrefix prefix r, readHex s) of (Just name, [(size, "")]) -> Just (name, size) From git at git.haskell.org Tue Oct 21 21:50:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:50:33 +0000 (UTC) Subject: [commit: ghc] master: ghc-prim: Use population count appropriate for platform (9f29e03) Message-ID: <20141021215033.6E5213A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9f29e032a0a0fa3f7685d8e3553cc64e33cc317d/ghc >--------------------------------------------------------------- commit 9f29e032a0a0fa3f7685d8e3553cc64e33cc317d Author: Ben Gamari Date: Tue Oct 21 15:00:02 2014 -0500 ghc-prim: Use population count appropriate for platform Summary: This #ifdef was previously x86-centric and consequently the 64-bit implementation was chosen for ARM. Reviewers: rwbarton, hvr, austin, tibbe Reviewed By: hvr, austin, tibbe Subscribers: hvr, thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D312 >--------------------------------------------------------------- 9f29e032a0a0fa3f7685d8e3553cc64e33cc317d libraries/ghc-prim/cbits/popcnt.c | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/libraries/ghc-prim/cbits/popcnt.c b/libraries/ghc-prim/cbits/popcnt.c index fc44ee7..70662e8 100644 --- a/libraries/ghc-prim/cbits/popcnt.c +++ b/libraries/ghc-prim/cbits/popcnt.c @@ -1,4 +1,5 @@ #include "Rts.h" +#include "MachDeps.h" static const unsigned char popcount_tab[] = { @@ -51,7 +52,7 @@ hs_popcnt64(StgWord64 x) popcount_tab[(unsigned char)(x >> 56)]; } -#ifdef i386_HOST_ARCH +#if WORD_SIZE_IN_BITS == 32 extern StgWord hs_popcnt(StgWord x); StgWord @@ -63,7 +64,7 @@ hs_popcnt(StgWord x) popcount_tab[(unsigned char)(x >> 24)]; } -#else +#elif WORD_SIZE_IN_BITS == 64 extern StgWord hs_popcnt(StgWord x); StgWord @@ -79,4 +80,8 @@ hs_popcnt(StgWord x) popcount_tab[(unsigned char)(x >> 56)]; } +#else + +#error Unknown machine word size + #endif From git at git.haskell.org Tue Oct 21 21:50:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:50:36 +0000 (UTC) Subject: [commit: ghc] master: Update to Unicode version 7.0 (d4fd168) Message-ID: <20141021215036.10A503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d4fd16801bc59034abdc6214e60fcce2b21af9c8/ghc >--------------------------------------------------------------- commit d4fd16801bc59034abdc6214e60fcce2b21af9c8 Author: David Feuer Date: Tue Oct 21 15:00:33 2014 -0500 Update to Unicode version 7.0 Summary: Update Unicode data to version 7.0 Reviewers: rwbarton, austin Reviewed By: austin Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D316 >--------------------------------------------------------------- d4fd16801bc59034abdc6214e60fcce2b21af9c8 libraries/base/cbits/WCsubst.c | 7285 +++++++++++++++++--------------- libraries/base/tests/unicode002.stdout | 196 +- 2 files changed, 3915 insertions(+), 3566 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 d4fd16801bc59034abdc6214e60fcce2b21af9c8 From git at git.haskell.org Tue Oct 21 21:50:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:50:38 +0000 (UTC) Subject: [commit: ghc] master: Remove extra period (a5f4fb6) Message-ID: <20141021215038.99E123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a5f4fb67ee6adb645e4bf0cd73f5bd995c40e6c7/ghc >--------------------------------------------------------------- commit a5f4fb67ee6adb645e4bf0cd73f5bd995c40e6c7 Author: Matt Kraai Date: Tue Oct 21 15:00:51 2014 -0500 Remove extra period Summary: The documentation has an extra period, which is rendered as > However, GHCi also has support for interactively loading compiled > code, as well as supporting all[2] the language extensions that GHC > provides. . Removing the extra period should fix this problem. Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D326 >--------------------------------------------------------------- a5f4fb67ee6adb645e4bf0cd73f5bd995c40e6c7 docs/users_guide/ghci.xml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/ghci.xml b/docs/users_guide/ghci.xml index cbf5b76..4ea1f92 100644 --- a/docs/users_guide/ghci.xml +++ b/docs/users_guide/ghci.xml @@ -17,7 +17,7 @@ the language extensions that GHC provides. FFIGHCi support Foreign Function - InterfaceGHCi support. + InterfaceGHCi support GHCi also includes an interactive debugger (see ). From git at git.haskell.org Tue Oct 21 21:50:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:50:41 +0000 (UTC) Subject: [commit: ghc] master: Improve isDigit, isSpace, etc. (3157127) Message-ID: <20141021215041.3B08B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/31571270625a690410b794b7cfe48d866c084e74/ghc >--------------------------------------------------------------- commit 31571270625a690410b794b7cfe48d866c084e74 Author: David Feuer Date: Tue Oct 21 15:01:14 2014 -0500 Improve isDigit, isSpace, etc. Summary: Make things less branchy; use unsigned comparisons for range checking. Eliminate non-spaces more quickly in common cases in isSpace. Reviewers: ekmett, carter, austin Reviewed By: austin Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D340 GHC Trac Issues: #1473 >--------------------------------------------------------------- 31571270625a690410b794b7cfe48d866c084e74 libraries/base/Data/Char.hs | 12 ++++++++---- libraries/base/GHC/Unicode.hs | 37 ++++++++++++++++++++++--------------- 2 files changed, 30 insertions(+), 19 deletions(-) diff --git a/libraries/base/Data/Char.hs b/libraries/base/Data/Char.hs index aa4a594..ac708ac 100644 --- a/libraries/base/Data/Char.hs +++ b/libraries/base/Data/Char.hs @@ -68,10 +68,14 @@ import GHC.Enum -- (i.e. @\'0\'@..@\'9\'@, @\'a\'@..@\'f\'@, @\'A\'@..@\'F\'@). digitToInt :: Char -> Int digitToInt c - | isDigit c = ord c - ord '0' - | c >= 'a' && c <= 'f' = ord c - ord 'a' + 10 - | c >= 'A' && c <= 'F' = ord c - ord 'A' + 10 - | otherwise = error ("Char.digitToInt: not a digit " ++ show c) -- sigh + | (fromIntegral dec::Word) <= 9 = dec + | (fromIntegral hexl::Word) <= 5 = hexl + 10 + | (fromIntegral hexu::Word) <= 5 = hexu + 10 + | otherwise = error ("Char.digitToInt: not a digit " ++ show c) -- sigh + where + dec = ord c - ord '0' + hexl = ord c - ord 'a' + hexu = ord c - ord 'A' -- | Unicode General Categories (column 2 of the UnicodeData table) -- in the order they are listed in the Unicode standard. diff --git a/libraries/base/GHC/Unicode.hs b/libraries/base/GHC/Unicode.hs index dea2fb9..6277805 100644 --- a/libraries/base/GHC/Unicode.hs +++ b/libraries/base/GHC/Unicode.hs @@ -30,6 +30,8 @@ module GHC.Unicode ( import GHC.Base import GHC.Char (chr) +import GHC.Real +import GHC.Num #include "HsBaseConfig.h" @@ -65,16 +67,16 @@ isPrint :: Char -> Bool -- characters @\\t@, @\\n@, @\\r@, @\\f@, @\\v at . isSpace :: Char -> Bool -- isSpace includes non-breaking space --- Done with explicit equalities both for efficiency, and to avoid a tiresome --- recursion with GHC.List elem -isSpace c = c == ' ' || - c == '\t' || - c == '\n' || - c == '\r' || - c == '\f' || - c == '\v' || - c == '\xa0' || - iswspace (ord c) /= 0 +-- The magic 0x377 isn't really that magical. As of 2014, all the codepoints +-- at or below 0x377 have been assigned, so we shouldn't have to worry about +-- any new spaces appearing below there. It would probably be best to +-- use branchless ||, but currently the eqLit transformation will undo that, +-- so we'll do it like this until there's a way around that. +isSpace c + | uc <= 0x377 = uc == 32 || uc - 0x9 <= 4 || uc == 0xa0 + | otherwise = iswspace (ord c) /= 0 + where + uc = fromIntegral (ord c) :: Word -- | Selects upper-case or title-case alphabetic Unicode characters (letters). -- Title case is used by a small number of letter ligatures like the @@ -98,17 +100,23 @@ isAlphaNum :: Char -> Bool -- | Selects ASCII digits, i.e. @\'0\'@..@\'9\'@. isDigit :: Char -> Bool -isDigit c = c >= '0' && c <= '9' +isDigit c = (fromIntegral (ord c - ord '0') :: Word) <= 9 + +-- We use an addition and an unsigned comparison instead of two signed +-- comparisons because it's usually faster and puts less strain on branch +-- prediction. It likely also enables some CSE when combined with functions +-- that follow up with an actual conversion. -- | Selects ASCII octal digits, i.e. @\'0\'@..@\'7\'@. isOctDigit :: Char -> Bool -isOctDigit c = c >= '0' && c <= '7' +isOctDigit c = (fromIntegral (ord c - ord '0') :: Word) <= 7 -- | Selects ASCII hexadecimal digits, -- i.e. @\'0\'@..@\'9\'@, @\'a\'@..@\'f\'@, @\'A\'@..@\'F\'@. isHexDigit :: Char -> Bool -isHexDigit c = isDigit c || c >= 'A' && c <= 'F' || - c >= 'a' && c <= 'f' +isHexDigit c = isDigit c || + (fromIntegral (ord c - ord 'A')::Word) <= 5 || + (fromIntegral (ord c - ord 'a')::Word) <= 5 -- | Convert a letter to the corresponding upper-case letter, if any. -- Any other character is returned unchanged. @@ -132,7 +140,6 @@ toTitle :: Char -> Char isAlpha c = iswalpha (ord c) /= 0 isAlphaNum c = iswalnum (ord c) /= 0 ---isSpace c = iswspace (ord c) /= 0 isControl c = iswcntrl (ord c) /= 0 isPrint c = iswprint (ord c) /= 0 isUpper c = iswupper (ord c) /= 0 From git at git.haskell.org Tue Oct 21 21:50:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:50:43 +0000 (UTC) Subject: [commit: ghc] master: Make findIndices fuse (ef2d027) Message-ID: <20141021215043.C70C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ef2d027917ca7e5415ba5e9f3ff439beda89b3ea/ghc >--------------------------------------------------------------- commit ef2d027917ca7e5415ba5e9f3ff439beda89b3ea Author: David Feuer Date: Tue Oct 21 15:01:26 2014 -0500 Make findIndices fuse Summary: Steal the findIndices implementation from Data.Sequence, that can participate in fold/build fusion Reviewers: nomeata, austin Reviewed By: nomeata, austin Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D345 >--------------------------------------------------------------- ef2d027917ca7e5415ba5e9f3ff439beda89b3ea libraries/base/Data/OldList.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index ff85154..0e6709e 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -277,12 +277,12 @@ findIndices :: (a -> Bool) -> [a] -> [Int] #ifdef USE_REPORT_PRELUDE findIndices p xs = [ i | (x,i) <- zip xs [0..], p x] #else --- Efficient definition -findIndices p ls = loop 0# ls - where - loop _ [] = [] - loop n (x:xs) | p x = I# n : loop (n +# 1#) xs - | otherwise = loop (n +# 1#) xs +-- Efficient definition, adapted from Data.Sequence +{-# INLINE findIndices #-} +findIndices p ls = build $ \c n -> + let go x r k | p x = I# k `c` r (k +# 1#) + | otherwise = r (k +# 1#) + in foldr go (\_ -> n) ls 0# #endif /* USE_REPORT_PRELUDE */ -- | The 'isPrefixOf' function takes two lists and returns 'True' From git at git.haskell.org Tue Oct 21 21:50:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:50:46 +0000 (UTC) Subject: [commit: ghc] master: Make Data.List.concatMap fuse better (1e269bf) Message-ID: <20141021215046.5DB5F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1e269bf404fb2719bbe8d72154156ef275c9a6f9/ghc >--------------------------------------------------------------- commit 1e269bf404fb2719bbe8d72154156ef275c9a6f9 Author: David Feuer Date: Tue Oct 21 15:02:03 2014 -0500 Make Data.List.concatMap fuse better Summary: Fix #9537 precisely as Joachim Breitner proposed in http://www.haskell.org/pipermail/haskell-cafe/2011-December/097228.html Reviewers: austin, nomeata Reviewed By: austin, nomeata Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D348 GHC Trac Issues: #9537 >--------------------------------------------------------------- 1e269bf404fb2719bbe8d72154156ef275c9a6f9 libraries/base/GHC/List.lhs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/libraries/base/GHC/List.lhs b/libraries/base/GHC/List.lhs index 7792eed..2d01678 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -717,6 +717,14 @@ lookup key ((x,y):xys) concatMap :: (a -> [b]) -> [a] -> [b] concatMap f = foldr ((++) . f) [] +{-# NOINLINE [1] concatMap #-} + +{-# RULES +"concatMap" forall f xs . concatMap f xs = + build (\c n -> foldr (\x b -> foldr c b (f x)) n xs) + #-} + + -- | Concatenate a list of lists. concat :: [[a]] -> [a] concat = foldr (++) [] From git at git.haskell.org Tue Oct 21 21:50:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:50:48 +0000 (UTC) Subject: [commit: ghc] master: Add doctest examples for Data.Functor. (6825558) Message-ID: <20141021215048.E622D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/68255588f89462e542c502f6f92548712808032f/ghc >--------------------------------------------------------------- commit 68255588f89462e542c502f6f92548712808032f Author: Michael Orlitzky Date: Tue Oct 21 15:02:11 2014 -0500 Add doctest examples for Data.Functor. Summary: Add doctest examples for the three standalone functions defined in Data.Functor: * Data.Functor.$> * Data.Functor.<$> * Data.Functor.void This is part of a larger plan to add examples for the functions in base, and to eventually enable automatic testing of them. Reviewers: austin, hvr, ekmett Reviewed By: austin Subscribers: hvr, ekmett, thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D352 >--------------------------------------------------------------- 68255588f89462e542c502f6f92548712808032f libraries/base/Data/Functor.hs | 105 +++++++++++++++++++++++++++++++++++++++-- 1 file changed, 102 insertions(+), 3 deletions(-) diff --git a/libraries/base/Data/Functor.hs b/libraries/base/Data/Functor.hs index 878445f..010ab50 100644 --- a/libraries/base/Data/Functor.hs +++ b/libraries/base/Data/Functor.hs @@ -25,9 +25,42 @@ module Data.Functor import GHC.Base ( Functor(..), const, flip ) +-- $setup +-- Allow the use of Prelude in doctests. +-- >>> import Prelude + infixl 4 <$> -- | An infix synonym for 'fmap'. +-- +-- __Examples__: +-- +-- Convert from a 'Maybe' 'Int' to a 'Maybe' 'String' using 'show': +-- +-- >>> show <$> Nothing +-- Nothing +-- >>> show <$> Just 3 +-- Just "3" +-- +-- Convert from an 'Either' 'Int' 'Int' to an 'Either' 'Int' +-- 'String' using 'show': +-- +-- >>> show <$> Left 17 +-- Left 17 +-- >>> show <$> Right 17 +-- Right "17" +-- +-- Double each element of a list: +-- +-- >>> (*2) <$> [1,2,3] +-- [2,4,6] +-- +-- Apply 'even' to the second element of a pair: +-- +-- >>> even <$> (2,2) +-- (2,True) +-- +-- (<$>) :: Functor f => (a -> b) -> f a -> f b (<$>) = fmap @@ -35,11 +68,77 @@ infixl 4 $> -- | Flipped version of '<$'. -- --- /Since: 4.7.0.0/ +-- /Since: 4.7.0.0/ +-- +-- __Examples__: +-- +-- Replace the contents of a 'Maybe' 'Int' with a constant 'String': +-- +-- >>> 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': +-- +-- >>> Left 8675309 $> "foo" +-- Left 8675309 +-- >>> Right 8675309 $> "foo" +-- Right "foo" +-- +-- Replace each element of a list with a constant 'String': +-- +-- >>> [1,2,3] $> "foo" +-- ["foo","foo","foo"] +-- +-- Replace the second element of a pair with a constant 'String': +-- +-- >>> (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. +-- | @'void' value@ discards or ignores the result of evaluation, such +-- as the return value of an 'IO' action. +-- +-- __Examples__: +-- +-- Replace the contents of a 'Maybe' 'Int' with unit: +-- +-- >>> void Nothing +-- Nothing +-- >>> void (Just 3) +-- Just () +-- +-- Replace the contents of an 'Either' 'Int' 'Int' with unit, +-- resulting in an 'Either' 'Int' '()': +-- +-- >>> void (Left 8675309) +-- Left 8675309 +-- >>> void (Right 8675309) +-- Right () +-- +-- Replace every element of a list with unit: +-- +-- >>> void [1,2,3] +-- [(),(),()] +-- +-- Replace the second element of a pair with unit: +-- +-- >>> void (1,2) +-- (1,()) +-- +-- Discard the result of an 'IO' action: +-- +-- >>> 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 Tue Oct 21 21:50:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:50:51 +0000 (UTC) Subject: [commit: ghc] master: Fix typo in -XConstraintKinds docs (5211673) Message-ID: <20141021215051.8803D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5211673155038dbae3837682c6f737c2446f5c20/ghc >--------------------------------------------------------------- commit 5211673155038dbae3837682c6f737c2446f5c20 Author: Ricky Elrod Date: Tue Oct 21 15:02:21 2014 -0500 Fix typo in -XConstraintKinds docs Summary: Fix a minor typo that seems to have existed for a long time. Signed-off-by: Ricky Elrod Test Plan: My eyes. Reviewers: austin, #ghc Reviewed By: austin, #ghc Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D356 >--------------------------------------------------------------- 5211673155038dbae3837682c6f737c2446f5c20 docs/users_guide/glasgow_exts.xml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index dd98f5a..7aff1a7 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -7121,7 +7121,7 @@ class (F a ~ b) => C a b where type (Show a, Ord a) is of kind Constraint. - Anything whose form is not yet know, but the user has declared to have kind Constraint + Anything whose form is not yet known, but the user has declared to have kind Constraint (for which they need to import it from GHC.Exts). So for example type Foo (f :: * -> Constraint) = forall b. f b => b -> b is allowed, as well as examples involving type families: From git at git.haskell.org Tue Oct 21 21:50:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:50:54 +0000 (UTC) Subject: [commit: ghc] master: Add doctest examples for Data.Bool. (9c464f8) Message-ID: <20141021215054.1BF053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9c464f89b90a6b3fb353341e48b3eecb2381d00e/ghc >--------------------------------------------------------------- commit 9c464f89b90a6b3fb353341e48b3eecb2381d00e Author: Michael Orlitzky Date: Tue Oct 21 15:02:29 2014 -0500 Add doctest examples for Data.Bool. Summary: Add examples for `Data.Bool`, and rework the existing documentation of the `bool` function slightly: the `a`,`b` in its explanation were changed to `x`,`y` to avoid ambiguity with the type variable 'a'. The examples have been tested, and two trailing spaces were removed. Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D360 >--------------------------------------------------------------- 9c464f89b90a6b3fb353341e48b3eecb2381d00e libraries/base/Data/Bool.hs | 31 +++++++++++++++++++++++++++---- 1 file changed, 27 insertions(+), 4 deletions(-) diff --git a/libraries/base/Data/Bool.hs b/libraries/base/Data/Bool.hs index deeac80..ace5acf 100644 --- a/libraries/base/Data/Bool.hs +++ b/libraries/base/Data/Bool.hs @@ -28,11 +28,34 @@ module Data.Bool ( import GHC.Base --- | Case analysis for the 'Bool' type. --- @bool a b p@ evaluates to @a@ when @p@ is @False@, and evaluates to @b@ --- when @p@ is @True at . +-- | Case analysis for the 'Bool' type. @bool x y p@ evaluates to @x@ +-- when @p@ is @False@, and evaluates to @y@ when @p@ is @True at . +-- +-- This is equivalent to @if p then y else x@; that is, one can +-- think of it as an if-then-else construct with its arguments +-- reordered. +-- +-- /Since: 4.7.0.0/ +-- +-- __Examples__: +-- +-- Basic usage: +-- +-- >>> bool "foo" "bar" True +-- "bar" +-- >>> bool "foo" "bar" False +-- "foo" +-- +-- Confirm that @bool x y p@ and @if p then y else x@ are +-- equivalent: +-- +-- >>> let p = True; x = "bar"; y = "foo" +-- >>> bool x y p == if p then y else x +-- True +-- >>> let p = False +-- >>> bool x y p == if p then y else x +-- True -- --- /Since: 4.7.0.0/ bool :: a -> a -> Bool -> a bool f _ False = f bool _ t True = t From git at git.haskell.org Tue Oct 21 21:50:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:50:56 +0000 (UTC) Subject: [commit: ghc] master: Add release note about Unicode 7.0 (c819958) Message-ID: <20141021215056.A62F53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c8199582ffe98fbfaef8e4aa036c748f8ec6b7ca/ghc >--------------------------------------------------------------- commit c8199582ffe98fbfaef8e4aa036c748f8ec6b7ca Author: Austin Seipp Date: Tue Oct 21 15:31:57 2014 -0500 Add release note about Unicode 7.0 Signed-off-by: Austin Seipp >--------------------------------------------------------------- c8199582ffe98fbfaef8e4aa036c748f8ec6b7ca docs/users_guide/7.10.1-notes.xml | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index a02c4b0..7b40002 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -66,6 +66,12 @@ + GHC has had its internal Unicode database for + parsing updated to the Unicode 7.0 standard. + + + + GHC now checks that all the language extensions required for the inferred type signatures are explicitly enabled. This means that if any of the type signatures inferred in your From git at git.haskell.org Tue Oct 21 21:50:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:50:59 +0000 (UTC) Subject: [commit: ghc] master: Fixes the ARM build (69f6361) Message-ID: <20141021215059.41F1A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/69f63612fc17cd6b3baaa8898c8595bde304ebfb/ghc >--------------------------------------------------------------- commit 69f63612fc17cd6b3baaa8898c8595bde304ebfb Author: Moritz Angermann Date: Tue Oct 21 15:33:18 2014 -0500 Fixes the ARM build Summary: CodeGen.Platform.hs was changed with the following diff: -#endif globalRegMaybe _ = Nothing +#elif MACHREGS_NO_REGS +globalRegMaybe _ = Nothing +#else +globalRegMaybe = panic "globalRegMaybe not defined for this platform" +#endif which causes globalRegMaybe ot panic for arch ARM. This patch ensures globalRegMaybe is not called on ARM. Signed-off-by: Moritz Angermann Test Plan: Building arm cross-compiler (e.g. --target=arm-apple-darwin10) Reviewers: hvr, ezyang, simonmar, rwbarton, austin Reviewed By: austin Subscribers: dterei, bgamari, simonmar, ezyang, carter Differential Revision: https://phabricator.haskell.org/D208 GHC Trac Issues: #9593 >--------------------------------------------------------------- 69f63612fc17cd6b3baaa8898c8595bde304ebfb compiler/cmm/CmmSink.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/cmm/CmmSink.hs b/compiler/cmm/CmmSink.hs index 4dced9a..22f4d2e 100644 --- a/compiler/cmm/CmmSink.hs +++ b/compiler/cmm/CmmSink.hs @@ -10,6 +10,7 @@ import CmmLive import CmmUtils import Hoopl import CodeGen.Platform +import Platform (isARM, platformArch) import DynFlags import UniqFM @@ -235,8 +236,10 @@ isSmall _ = False isTrivial :: DynFlags -> CmmExpr -> Bool isTrivial _ (CmmReg (CmmLocal _)) = True isTrivial dflags (CmmReg (CmmGlobal r)) = -- see Note [Inline GlobalRegs?] - isJust (globalRegMaybe (targetPlatform dflags) r) - -- GlobalRegs that are loads from BaseReg are not trivial + if isARM (platformArch (targetPlatform dflags)) + then True -- CodeGen.Platform.ARM does not have globalRegMaybe + else isJust (globalRegMaybe (targetPlatform dflags) r) + -- GlobalRegs that are loads from BaseReg are not trivial isTrivial _ (CmmLit _) = True isTrivial _ _ = False From git at git.haskell.org Tue Oct 21 21:51:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:02 +0000 (UTC) Subject: [commit: ghc] master: Enabled warn on tabs by default (fixes #9230) (972ba12) Message-ID: <20141021215102.40B133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/972ba1210d1bb535c41526ce396c0f086d30b59a/ghc >--------------------------------------------------------------- commit 972ba1210d1bb535c41526ce396c0f086d30b59a Author: Mateusz Lenik Date: Tue Oct 21 15:34:00 2014 -0500 Enabled warn on tabs by default (fixes #9230) Summary: This revision enables -fwarn-tabs by default and add a suppression flag, so that GHC compilation won't fail when some files contain tab characters. Test Plan: Additional test case, T9230, was added to cover that change. Reviewers: austin Reviewed By: austin Subscribers: simonmar, ezyang, carter, thomie, mlen Differential Revision: https://phabricator.haskell.org/D255 GHC Trac Issues: #9230 Conflicts: testsuite/driver/testlib.py >--------------------------------------------------------------- 972ba1210d1bb535c41526ce396c0f086d30b59a compiler/main/DynFlags.hs | 3 +- docs/users_guide/7.10.1-notes.xml | 6 +++ mk/validate-settings.mk | 9 ++++ testsuite/driver/testlib.py | 62 +++++++++++++++++++--- testsuite/mk/test.mk | 8 +++ testsuite/tests/deSugar/should_compile/all.T | 4 +- testsuite/tests/ghci/scripts/all.T | 2 +- testsuite/tests/module/all.T | 2 +- testsuite/tests/warnings/should_compile/T9230.hs | 5 ++ .../tests/warnings/should_compile/T9230.stderr | 2 + testsuite/tests/warnings/should_compile/all.T | 1 + 11 files changed, 92 insertions(+), 12 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 972ba1210d1bb535c41526ce396c0f086d30b59a From git at git.haskell.org Tue Oct 21 21:51:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:04 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify RtsMessages.c (4faeecb) Message-ID: <20141021215104.D70083A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4faeecb67aabba34d07793d9f39134c9d4fb6639/ghc >--------------------------------------------------------------- commit 4faeecb67aabba34d07793d9f39134c9d4fb6639 Author: Austin Seipp Date: Tue Oct 21 16:31:22 2014 -0500 [skip ci] rts: Detabify RtsMessages.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- 4faeecb67aabba34d07793d9f39134c9d4fb6639 rts/RtsMessages.c | 84 +++++++++++++++++++++++++++---------------------------- 1 file changed, 42 insertions(+), 42 deletions(-) diff --git a/rts/RtsMessages.c b/rts/RtsMessages.c index 6e75abc..b3d8f94 100644 --- a/rts/RtsMessages.c +++ b/rts/RtsMessages.c @@ -142,10 +142,10 @@ rtsFatalInternalErrorFn(const char *s, va_list ap) vsnprintf(message, BUFSIZE, s, ap); MessageBox(NULL /* hWnd */, - message, - title, - MB_OK | MB_ICONERROR | MB_TASKMODAL - ); + message, + title, + MB_OK | MB_ICONERROR | MB_TASKMODAL + ); } else #endif @@ -180,9 +180,9 @@ rtsErrorMsgFn(const char *s, va_list ap) char buf[BUFSIZE]; int r; - r = vsnprintf(buf, BUFSIZE, s, ap); - if (r > 0 && r < BUFSIZE) { - MessageBox(NULL /* hWnd */, + r = vsnprintf(buf, BUFSIZE, s, ap); + if (r > 0 && r < BUFSIZE) { + MessageBox(NULL /* hWnd */, buf, prog_name, MB_OK | MB_ICONERROR | MB_TASKMODAL @@ -208,30 +208,30 @@ rtsSysErrorMsgFn(const char *s, va_list ap) #if defined(cygwin32_HOST_OS) || defined (mingw32_HOST_OS) FormatMessage( - FORMAT_MESSAGE_ALLOCATE_BUFFER | - FORMAT_MESSAGE_FROM_SYSTEM | - FORMAT_MESSAGE_IGNORE_INSERTS, - NULL, - GetLastError(), - MAKELANGID(LANG_NEUTRAL, SUBLANG_DEFAULT), // Default language - (LPTSTR) &syserr, - 0, - NULL ); + FORMAT_MESSAGE_ALLOCATE_BUFFER | + FORMAT_MESSAGE_FROM_SYSTEM | + FORMAT_MESSAGE_IGNORE_INSERTS, + NULL, + GetLastError(), + MAKELANGID(LANG_NEUTRAL, SUBLANG_DEFAULT), // Default language + (LPTSTR) &syserr, + 0, + NULL ); if (isGUIApp()) { - char buf[BUFSIZE]; - int r; - - r = vsnprintf(buf, BUFSIZE, s, ap); - if (r > 0 && r < BUFSIZE) { - r = vsnprintf(buf+r, BUFSIZE-r, ": %s", syserr); - MessageBox(NULL /* hWnd */, - buf, - prog_name, - MB_OK | MB_ICONERROR | MB_TASKMODAL - ); - } + char buf[BUFSIZE]; + int r; + + r = vsnprintf(buf, BUFSIZE, s, ap); + if (r > 0 && r < BUFSIZE) { + r = vsnprintf(buf+r, BUFSIZE-r, ": %s", syserr); + MessageBox(NULL /* hWnd */, + buf, + prog_name, + MB_OK | MB_ICONERROR | MB_TASKMODAL + ); + } } else #else @@ -239,21 +239,21 @@ rtsSysErrorMsgFn(const char *s, va_list ap) // ToDo: use strerror_r() if available #endif { - /* don't fflush(stdout); WORKAROUND bug in Linux glibc */ - if (prog_argv != NULL && prog_name != NULL) { - fprintf(stderr, "%s: ", prog_name); - } - vfprintf(stderr, s, ap); - if (syserr) { + /* don't fflush(stdout); WORKAROUND bug in Linux glibc */ + if (prog_argv != NULL && prog_name != NULL) { + fprintf(stderr, "%s: ", prog_name); + } + vfprintf(stderr, s, ap); + if (syserr) { #if defined(cygwin32_HOST_OS) || defined (mingw32_HOST_OS) // Win32 error messages have a terminating \n - fprintf(stderr, ": %s", syserr); + fprintf(stderr, ": %s", syserr); #else - fprintf(stderr, ": %s\n", syserr); + fprintf(stderr, ": %s\n", syserr); #endif - } else { - fprintf(stderr, "\n"); - } + } else { + fprintf(stderr, "\n"); + } } #if defined(cygwin32_HOST_OS) || defined (mingw32_HOST_OS) @@ -268,10 +268,10 @@ rtsDebugMsgFn(const char *s, va_list ap) if (isGUIApp()) { char buf[BUFSIZE]; - int r; + int r; - r = vsnprintf(buf, BUFSIZE, s, ap); - if (r > 0 && r < BUFSIZE) { + r = vsnprintf(buf, BUFSIZE, s, ap); + if (r > 0 && r < BUFSIZE) { OutputDebugString(buf); } } From git at git.haskell.org Tue Oct 21 21:51:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:07 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify RaiseAsync.h (aa8d23d) Message-ID: <20141021215107.6B5203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aa8d23d24d6777c2881b89928776cce2e51a631f/ghc >--------------------------------------------------------------- commit aa8d23d24d6777c2881b89928776cce2e51a631f Author: Austin Seipp Date: Tue Oct 21 16:32:20 2014 -0500 [skip ci] rts: Detabify RaiseAsync.h Signed-off-by: Austin Seipp >--------------------------------------------------------------- aa8d23d24d6777c2881b89928776cce2e51a631f rts/RaiseAsync.h | 15 +++++++-------- 1 file changed, 7 insertions(+), 8 deletions(-) diff --git a/rts/RaiseAsync.h b/rts/RaiseAsync.h index 3da9e7b..e2763d0 100644 --- a/rts/RaiseAsync.h +++ b/rts/RaiseAsync.h @@ -20,17 +20,17 @@ void blockedThrowTo (Capability *cap, StgTSO *target, MessageThrowTo *msg); void throwToSingleThreaded (Capability *cap, - StgTSO *tso, - StgClosure *exception); + StgTSO *tso, + StgClosure *exception); void throwToSingleThreaded_ (Capability *cap, - StgTSO *tso, - StgClosure *exception, - rtsBool stop_at_atomically); + StgTSO *tso, + StgClosure *exception, + rtsBool stop_at_atomically); void suspendComputation (Capability *cap, - StgTSO *tso, - StgUpdateFrame *stop_here); + StgTSO *tso, + StgUpdateFrame *stop_here); MessageThrowTo *throwTo (Capability *cap, // the Capability we hold StgTSO *source, @@ -74,4 +74,3 @@ interruptible(StgTSO *t) #endif /* CMINUSMINUS */ #endif /* RAISEASYNC_H */ - From git at git.haskell.org Tue Oct 21 21:51:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:10 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify Capability.h (bb04867) Message-ID: <20141021215110.044E93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bb04867af92ff970e169f26c2260b899c461e279/ghc >--------------------------------------------------------------- commit bb04867af92ff970e169f26c2260b899c461e279 Author: Austin Seipp Date: Tue Oct 21 16:32:58 2014 -0500 [skip ci] rts: Detabify Capability.h Signed-off-by: Austin Seipp >--------------------------------------------------------------- bb04867af92ff970e169f26c2260b899c461e279 rts/Capability.h | 24 ++++++++++++------------ 1 file changed, 12 insertions(+), 12 deletions(-) diff --git a/rts/Capability.h b/rts/Capability.h index 9ef7b24..910c92c 100644 --- a/rts/Capability.h +++ b/rts/Capability.h @@ -156,9 +156,9 @@ struct Capability_ { #endif // These properties should be true when a Task is holding a Capability -#define ASSERT_FULL_CAPABILITY_INVARIANTS(cap,task) \ - ASSERT(cap->running_task != NULL && cap->running_task == task); \ - ASSERT(task->cap == cap); \ +#define ASSERT_FULL_CAPABILITY_INVARIANTS(cap,task) \ + ASSERT(cap->running_task != NULL && cap->running_task == task); \ + ASSERT(task->cap == cap); \ ASSERT_PARTIAL_CAPABILITY_INVARIANTS(cap,task) // Sometimes a Task holds a Capability, but the Task is not associated @@ -166,10 +166,10 @@ struct Capability_ { // (a) a Task holds multiple Capabilities, and (b) when the current // Task is bound, its thread has just blocked, and it may have been // moved to another Capability. -#define ASSERT_PARTIAL_CAPABILITY_INVARIANTS(cap,task) \ - ASSERT(cap->run_queue_hd == END_TSO_QUEUE ? \ - cap->run_queue_tl == END_TSO_QUEUE : 1); \ - ASSERT(myTask() == task); \ +#define ASSERT_PARTIAL_CAPABILITY_INVARIANTS(cap,task) \ + ASSERT(cap->run_queue_hd == END_TSO_QUEUE ? \ + cap->run_queue_tl == END_TSO_QUEUE : 1); \ + ASSERT(myTask() == task); \ ASSERT_TASK_ID(task); #if defined(THREADED_RTS) @@ -361,11 +361,11 @@ recordMutableCap (StgClosure *p, Capability *cap, nat gen) // NO: assertion is violated by performPendingThrowTos() bd = cap->mut_lists[gen]; if (bd->free >= bd->start + BLOCK_SIZE_W) { - bdescr *new_bd; - new_bd = allocBlock_lock(); - new_bd->link = bd; - bd = new_bd; - cap->mut_lists[gen] = bd; + bdescr *new_bd; + new_bd = allocBlock_lock(); + new_bd->link = bd; + bd = new_bd; + cap->mut_lists[gen] = bd; } *bd->free++ = (StgWord)p; } From git at git.haskell.org Tue Oct 21 21:51:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:12 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify CheckUnload.c (99edc35) Message-ID: <20141021215112.9B4023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/99edc35be84f50734f3e0cace33d595777203c5e/ghc >--------------------------------------------------------------- commit 99edc35be84f50734f3e0cace33d595777203c5e Author: Austin Seipp Date: Tue Oct 21 16:33:29 2014 -0500 [skip ci] rts: Detabify CheckUnload.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- 99edc35be84f50734f3e0cace33d595777203c5e rts/CheckUnload.c | 188 +++++++++++++++++++++++++++--------------------------- 1 file changed, 94 insertions(+), 94 deletions(-) diff --git a/rts/CheckUnload.c b/rts/CheckUnload.c index 98f184b..c63a35a 100644 --- a/rts/CheckUnload.c +++ b/rts/CheckUnload.c @@ -92,91 +92,91 @@ static void searchHeapBlocks (HashTable *addrs, bdescr *bd) continue; } - p = bd->start; - while (p < bd->free) { - info = get_itbl((StgClosure *)p); + p = bd->start; + while (p < bd->free) { + info = get_itbl((StgClosure *)p); prim = rtsFalse; - switch (info->type) { + switch (info->type) { - case THUNK: + case THUNK: size = thunk_sizeW_fromITBL(info); - break; - - case THUNK_1_1: - case THUNK_0_2: - case THUNK_2_0: - size = sizeofW(StgThunkHeader) + 2; - break; - - case THUNK_1_0: - case THUNK_0_1: - case THUNK_SELECTOR: - size = sizeofW(StgThunkHeader) + 1; - break; - - case CONSTR: - case FUN: + break; + + case THUNK_1_1: + case THUNK_0_2: + case THUNK_2_0: + size = sizeofW(StgThunkHeader) + 2; + break; + + case THUNK_1_0: + case THUNK_0_1: + case THUNK_SELECTOR: + size = sizeofW(StgThunkHeader) + 1; + break; + + case CONSTR: + case FUN: case FUN_1_0: - case FUN_0_1: - case FUN_1_1: - case FUN_0_2: - case FUN_2_0: - case CONSTR_1_0: - case CONSTR_0_1: - case CONSTR_1_1: - case CONSTR_0_2: - case CONSTR_2_0: - size = sizeW_fromITBL(info); - break; - - case IND_PERM: - case BLACKHOLE: - case BLOCKING_QUEUE: + case FUN_0_1: + case FUN_1_1: + case FUN_0_2: + case FUN_2_0: + case CONSTR_1_0: + case CONSTR_0_1: + case CONSTR_1_1: + case CONSTR_0_2: + case CONSTR_2_0: + size = sizeW_fromITBL(info); + break; + + case IND_PERM: + case BLACKHOLE: + case BLOCKING_QUEUE: prim = rtsTrue; size = sizeW_fromITBL(info); - break; + break; case IND: - // Special case/Delicate Hack: INDs don't normally - // appear, since we're doing this heap census right - // after GC. However, GarbageCollect() also does - // resurrectThreads(), which can update some - // blackholes when it calls raiseAsync() on the - // resurrected threads. So we know that any IND will - // be the size of a BLACKHOLE. + // Special case/Delicate Hack: INDs don't normally + // appear, since we're doing this heap census right + // after GC. However, GarbageCollect() also does + // resurrectThreads(), which can update some + // blackholes when it calls raiseAsync() on the + // resurrected threads. So we know that any IND will + // be the size of a BLACKHOLE. prim = rtsTrue; size = BLACKHOLE_sizeW(); - break; + break; - case BCO: + case BCO: prim = rtsTrue; - size = bco_sizeW((StgBCO *)p); - break; + size = bco_sizeW((StgBCO *)p); + break; case MVAR_CLEAN: case MVAR_DIRTY: case TVAR: case WEAK: - case PRIM: - case MUT_PRIM: - case MUT_VAR_CLEAN: - case MUT_VAR_DIRTY: - prim = rtsTrue; - size = sizeW_fromITBL(info); - break; - - case AP: + case PRIM: + case MUT_PRIM: + case MUT_VAR_CLEAN: + case MUT_VAR_DIRTY: + prim = rtsTrue; + size = sizeW_fromITBL(info); + break; + + case AP: prim = rtsTrue; size = ap_sizeW((StgAP *)p); - break; + break; - case PAP: + case PAP: prim = rtsTrue; size = pap_sizeW((StgPAP *)p); - break; + break; - case AP_STACK: + case AP_STACK: { StgAP_STACK *ap = (StgAP_STACK *)p; prim = rtsTrue; @@ -186,31 +186,31 @@ static void searchHeapBlocks (HashTable *addrs, bdescr *bd) break; } - case ARR_WORDS: - prim = rtsTrue; - size = arr_words_sizeW((StgArrWords*)p); - break; - - case MUT_ARR_PTRS_CLEAN: - case MUT_ARR_PTRS_DIRTY: - case MUT_ARR_PTRS_FROZEN: - case MUT_ARR_PTRS_FROZEN0: - prim = rtsTrue; - size = mut_arr_ptrs_sizeW((StgMutArrPtrs *)p); - break; - - case SMALL_MUT_ARR_PTRS_CLEAN: - case SMALL_MUT_ARR_PTRS_DIRTY: - case SMALL_MUT_ARR_PTRS_FROZEN: - case SMALL_MUT_ARR_PTRS_FROZEN0: - prim = rtsTrue; - size = small_mut_arr_ptrs_sizeW((StgSmallMutArrPtrs *)p); - break; - - case TSO: - prim = rtsTrue; + case ARR_WORDS: + prim = rtsTrue; + size = arr_words_sizeW((StgArrWords*)p); + break; + + case MUT_ARR_PTRS_CLEAN: + case MUT_ARR_PTRS_DIRTY: + case MUT_ARR_PTRS_FROZEN: + case MUT_ARR_PTRS_FROZEN0: + prim = rtsTrue; + size = mut_arr_ptrs_sizeW((StgMutArrPtrs *)p); + break; + + case SMALL_MUT_ARR_PTRS_CLEAN: + case SMALL_MUT_ARR_PTRS_DIRTY: + case SMALL_MUT_ARR_PTRS_FROZEN: + case SMALL_MUT_ARR_PTRS_FROZEN0: + prim = rtsTrue; + size = small_mut_arr_ptrs_sizeW((StgSmallMutArrPtrs *)p); + break; + + case TSO: + prim = rtsTrue; size = sizeofW(StgTSO); - break; + break; case STACK: { StgStack *stack = (StgStack*)p; @@ -218,24 +218,24 @@ static void searchHeapBlocks (HashTable *addrs, bdescr *bd) searchStackChunk(addrs, stack->sp, stack->stack + stack->stack_size); size = stack_sizeW(stack); - break; + break; } case TREC_CHUNK: - prim = rtsTrue; - size = sizeofW(StgTRecChunk); - break; + prim = rtsTrue; + size = sizeofW(StgTRecChunk); + break; - default: - barf("heapCensus, unknown object: %d", info->type); - } + default: + barf("heapCensus, unknown object: %d", info->type); + } if (!prim) { checkAddress(addrs,info); } - p += size; - } + p += size; + } } } From git at git.haskell.org Tue Oct 21 21:51:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:15 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify Profiling.c (6aa6ca8) Message-ID: <20141021215115.30D3D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6aa6ca89cf73a705ddd0cfccf8e89648e1edc6d5/ghc >--------------------------------------------------------------- commit 6aa6ca89cf73a705ddd0cfccf8e89648e1edc6d5 Author: Austin Seipp Date: Tue Oct 21 16:33:46 2014 -0500 [skip ci] rts: Detabify Profiling.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- 6aa6ca89cf73a705ddd0cfccf8e89648e1edc6d5 rts/Profiling.c | 72 ++++++++++++++++++++++++++++----------------------------- 1 file changed, 36 insertions(+), 36 deletions(-) diff --git a/rts/Profiling.c b/rts/Profiling.c index 53f64a7..a299189 100644 --- a/rts/Profiling.c +++ b/rts/Profiling.c @@ -49,7 +49,7 @@ static W_ total_prof_ticks; static char *prof_filename; /* prof report file name = .prof */ FILE *prof_file; -static char *hp_filename; /* heap profile (hp2ps style) log file */ +static char *hp_filename; /* heap profile (hp2ps style) log file */ FILE *hp_file; /* Linked lists to keep track of CCs and CCSs that haven't @@ -95,8 +95,8 @@ CC_DECLARE(CC_DONT_CARE, "DONT_CARE", "MAIN", "", CC_NOT_CAF, ) CC_DECLARE(CC_PINNED, "PINNED", "SYSTEM", "", CC_NOT_CAF, ); CC_DECLARE(CC_IDLE, "IDLE", "IDLE", "", CC_NOT_CAF, ); -CCS_DECLARE(CCS_MAIN, CC_MAIN, ); -CCS_DECLARE(CCS_SYSTEM, CC_SYSTEM, ); +CCS_DECLARE(CCS_MAIN, CC_MAIN, ); +CCS_DECLARE(CCS_SYSTEM, CC_SYSTEM, ); CCS_DECLARE(CCS_GC, CC_GC, ); CCS_DECLARE(CCS_OVERHEAD, CC_OVERHEAD, ); CCS_DECLARE(CCS_DONT_CARE, CC_DONT_CARE, ); @@ -129,7 +129,7 @@ static CostCentreStack * pruneCCSTree ( CostCentreStack *ccs ); static CostCentreStack * actualPush ( CostCentreStack *, CostCentre * ); static CostCentreStack * isInIndexTable ( IndexTable *, CostCentre * ); static IndexTable * addToIndexTable ( IndexTable *, CostCentreStack *, - CostCentre *, unsigned int ); + CostCentre *, unsigned int ); static void ccsSetSelected ( CostCentreStack *ccs ); static void initTimeProfiling ( void ); @@ -266,17 +266,17 @@ initProfilingLogFile(void) } if (RtsFlags.ProfFlags.doHeapProfile) { - /* Initialise the log file name */ - hp_filename = arenaAlloc(prof_arena, strlen(prog) + 6); - sprintf(hp_filename, "%s.hp", prog); - - /* open the log file */ - if ((hp_file = fopen(hp_filename, "w")) == NULL) { - debugBelch("Can't open profiling report file %s\n", - hp_filename); - RtsFlags.ProfFlags.doHeapProfile = 0; - return; - } + /* Initialise the log file name */ + hp_filename = arenaAlloc(prof_arena, strlen(prog) + 6); + sprintf(hp_filename, "%s.hp", prog); + + /* open the log file */ + if ((hp_file = fopen(hp_filename, "w")) == NULL) { + debugBelch("Can't open profiling report file %s\n", + hp_filename); + RtsFlags.ProfFlags.doHeapProfile = 0; + return; + } } } @@ -413,26 +413,26 @@ ccsSetSelected (CostCentreStack *ccs) if (RtsFlags.ProfFlags.modSelector) { if (! strMatchesSelector (ccs->cc->module, RtsFlags.ProfFlags.modSelector) ) { - ccs->selected = 0; + ccs->selected = 0; return; } } if (RtsFlags.ProfFlags.ccSelector) { if (! strMatchesSelector (ccs->cc->label, RtsFlags.ProfFlags.ccSelector) ) { - ccs->selected = 0; + ccs->selected = 0; return; } } if (RtsFlags.ProfFlags.ccsSelector) { - CostCentreStack *c; + CostCentreStack *c; for (c = ccs; c != NULL; c = c->prevStack) { if ( strMatchesSelector (c->cc->label, RtsFlags.ProfFlags.ccsSelector) ) { - break; - } - } + break; + } + } if (c == NULL) { ccs->selected = 0; return; @@ -454,9 +454,9 @@ pushCostCentre ( CostCentreStack *ccs, CostCentre *cc ) #define pushCostCentre _pushCostCentre { IF_DEBUG(prof, - traceBegin("pushing %s on ", cc->label); - debugCCS(ccs); - traceEnd();); + traceBegin("pushing %s on ", cc->label); + debugCCS(ccs); + traceEnd();); return pushCostCentre(ccs,cc); } @@ -670,13 +670,13 @@ ignoreCC (CostCentre *cc) { if (RtsFlags.CcFlags.doCostCentres < COST_CENTRES_ALL && ( cc == CC_OVERHEAD - || cc == CC_DONT_CARE - || cc == CC_GC + || cc == CC_DONT_CARE + || cc == CC_GC || cc == CC_SYSTEM || cc == CC_IDLE)) { - return rtsTrue; + return rtsTrue; } else { - return rtsFalse; + return rtsFalse; } } @@ -691,7 +691,7 @@ ignoreCCS (CostCentreStack *ccs) || ccs == CCS_IDLE)) { return rtsTrue; } else { - return rtsFalse; + return rtsFalse; } } @@ -839,28 +839,28 @@ reportCCSProfiling( void ) if (RtsFlags.CcFlags.doCostCentres == 0) return; fprintf(prof_file, "\t%s Time and Allocation Profiling Report (%s)\n", - time_str(), "Final"); + time_str(), "Final"); fprintf(prof_file, "\n\t "); fprintf(prof_file, " %s", prog_name); fprintf(prof_file, " +RTS"); for (count = 0; rts_argv[count]; count++) - fprintf(prof_file, " %s", rts_argv[count]); + fprintf(prof_file, " %s", rts_argv[count]); fprintf(prof_file, " -RTS"); for (count = 1; prog_argv[count]; count++) - fprintf(prof_file, " %s", prog_argv[count]); + fprintf(prof_file, " %s", prog_argv[count]); fprintf(prof_file, "\n\n"); fprintf(prof_file, "\ttotal time = %11.2f secs (%lu ticks @ %d us, %d processor%s)\n", ((double) total_prof_ticks * (double) RtsFlags.MiscFlags.tickInterval) / (TIME_RESOLUTION * n_capabilities), - (unsigned long) total_prof_ticks, + (unsigned long) total_prof_ticks, (int) TimeToUS(RtsFlags.MiscFlags.tickInterval), n_capabilities, n_capabilities > 1 ? "s" : ""); fprintf(prof_file, "\ttotal alloc = %11s bytes", - showStgWord64(total_alloc * sizeof(W_), - temp, rtsTrue/*commas*/)); + showStgWord64(total_alloc * sizeof(W_), + temp, rtsTrue/*commas*/)); fprintf(prof_file, " (excludes profiling overheads)\n\n"); @@ -915,7 +915,7 @@ logCCS(CostCentreStack *ccs, nat indent, nat max_label_len, nat max_module_len) total_alloc == 0 ? 0.0 : ((double)ccs->mem_alloc / (double)total_alloc * 100.0), total_prof_ticks == 0 ? 0.0 : ((double)ccs->inherited_ticks / (double)total_prof_ticks * 100.0), total_alloc == 0 ? 0.0 : ((double)ccs->inherited_alloc / (double)total_alloc * 100.0) - ); + ); if (RtsFlags.CcFlags.doCostCentres >= COST_CENTRES_VERBOSE) { fprintf(prof_file, " %5" FMT_Word64 " %9" FMT_Word64, From git at git.haskell.org Tue Oct 21 21:51:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:17 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify Threads.c (570b339) Message-ID: <20141021215117.BD55B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/570b3393f926e8fc107be6f4234381b3b636d0de/ghc >--------------------------------------------------------------- commit 570b3393f926e8fc107be6f4234381b3b636d0de Author: Austin Seipp Date: Tue Oct 21 16:34:07 2014 -0500 [skip ci] rts: Detabify Threads.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- 570b3393f926e8fc107be6f4234381b3b636d0de rts/Threads.c | 74 +++++++++++++++++++++++++++++------------------------------ 1 file changed, 37 insertions(+), 37 deletions(-) diff --git a/rts/Threads.c b/rts/Threads.c index 0d0a3fc..76e844a 100644 --- a/rts/Threads.c +++ b/rts/Threads.c @@ -35,8 +35,8 @@ static StgThreadID next_thread_id = 1; * RESERVED_STACK_WORDS (so we can get back from the stack overflow) * + sizeofW(StgStopFrame) (the stg_stop_thread_info frame) * + 1 (the closure to enter) - * + 1 (stg_ap_v_ret) - * + 1 (spare slot req'd by stg_ap_v_ret) + * + 1 (stg_ap_v_ret) + * + 1 (spare slot req'd by stg_ap_v_ret) * * A thread with this stack will bomb immediately with a stack * overflow, which will increase its stack size. @@ -176,17 +176,17 @@ removeThreadFromQueue (Capability *cap, StgTSO **queue, StgTSO *tso) prev = NULL; for (t = *queue; t != END_TSO_QUEUE; prev = t, t = t->_link) { - if (t == tso) { - if (prev) { - setTSOLink(cap,prev,t->_link); + if (t == tso) { + if (prev) { + setTSOLink(cap,prev,t->_link); t->_link = END_TSO_QUEUE; return rtsFalse; - } else { - *queue = t->_link; + } else { + *queue = t->_link; t->_link = END_TSO_QUEUE; return rtsTrue; - } - } + } + } } barf("removeThreadFromQueue: not found"); } @@ -200,26 +200,26 @@ removeThreadFromDeQueue (Capability *cap, prev = NULL; for (t = *head; t != END_TSO_QUEUE; prev = t, t = t->_link) { - if (t == tso) { - if (prev) { - setTSOLink(cap,prev,t->_link); + if (t == tso) { + if (prev) { + setTSOLink(cap,prev,t->_link); flag = rtsFalse; - } else { - *head = t->_link; + } else { + *head = t->_link; flag = rtsTrue; - } + } t->_link = END_TSO_QUEUE; if (*tail == tso) { - if (prev) { - *tail = prev; - } else { - *tail = END_TSO_QUEUE; - } + if (prev) { + *tail = prev; + } else { + *tail = END_TSO_QUEUE; + } return rtsTrue; - } else { + } else { return flag; } - } + } } barf("removeThreadFromDeQueue: not found"); } @@ -810,7 +810,7 @@ printThreadBlockage(StgTSO *tso) break; default: barf("printThreadBlockage: strange tso->why_blocked: %d for TSO %d (%d)", - tso->why_blocked, tso->id, tso); + tso->why_blocked, tso->id, tso); } } @@ -824,19 +824,19 @@ printThreadStatus(StgTSO *t) if (label) debugBelch("[\"%s\"] ",(char *)label); } switch (t->what_next) { - case ThreadKilled: - debugBelch("has been killed"); - break; - case ThreadComplete: - debugBelch("has completed"); - break; - default: - printThreadBlockage(t); - } + case ThreadKilled: + debugBelch("has been killed"); + break; + case ThreadComplete: + debugBelch("has completed"); + break; + default: + printThreadBlockage(t); + } if (t->dirty) { debugBelch(" (TSO_DIRTY)"); } - debugBelch("\n"); + debugBelch("\n"); } void @@ -852,7 +852,7 @@ printAllThreads(void) cap = capabilities[i]; debugBelch("threads on capability %d:\n", cap->no); for (t = cap->run_queue_hd; t != END_TSO_QUEUE; t = t->_link) { - printThreadStatus(t); + printThreadStatus(t); } } @@ -860,7 +860,7 @@ printAllThreads(void) for (g = 0; g < RtsFlags.GcFlags.generations; g++) { for (t = generations[g].threads; t != END_TSO_QUEUE; t = next) { if (t->why_blocked != NotBlocked) { - printThreadStatus(t); + printThreadStatus(t); } next = t->global_link; } @@ -873,8 +873,8 @@ printThreadQueue(StgTSO *t) { nat i = 0; for (; t != END_TSO_QUEUE; t = t->_link) { - printThreadStatus(t); - i++; + printThreadStatus(t); + i++; } debugBelch("%d threads on queue\n", i); } From git at git.haskell.org Tue Oct 21 21:51:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:20 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify sm/Evac.c (21eaaa1) Message-ID: <20141021215120.5A7213A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/21eaaa138393a647fb5c90417f8aeb458a240ba5/ghc >--------------------------------------------------------------- commit 21eaaa138393a647fb5c90417f8aeb458a240ba5 Author: Austin Seipp Date: Tue Oct 21 16:35:59 2014 -0500 [skip ci] rts: Detabify sm/Evac.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- 21eaaa138393a647fb5c90417f8aeb458a240ba5 rts/sm/Evac.c | 158 +++++++++++++++++++++++++++++----------------------------- 1 file changed, 79 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 21eaaa138393a647fb5c90417f8aeb458a240ba5 From git at git.haskell.org Tue Oct 21 21:51:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:22 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify sm/Scav.c (9167d0e) Message-ID: <20141021215122.E74B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9167d0ea44f1f806408abfc9e358099e41c9675e/ghc >--------------------------------------------------------------- commit 9167d0ea44f1f806408abfc9e358099e41c9675e Author: Austin Seipp Date: Tue Oct 21 16:36:30 2014 -0500 [skip ci] rts: Detabify sm/Scav.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- 9167d0ea44f1f806408abfc9e358099e41c9675e rts/sm/Scav.c | 1367 ++++++++++++++++++++++++++++----------------------------- 1 file changed, 683 insertions(+), 684 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 9167d0ea44f1f806408abfc9e358099e41c9675e From git at git.haskell.org Tue Oct 21 21:51:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:25 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify Stats.c (5bb8f14) Message-ID: <20141021215125.7F8B83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5bb8f14ccd05f2c32e49680e44a3b3ac9595504a/ghc >--------------------------------------------------------------- commit 5bb8f14ccd05f2c32e49680e44a3b3ac9595504a Author: Austin Seipp Date: Tue Oct 21 16:37:09 2014 -0500 [skip ci] rts: Detabify Stats.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- 5bb8f14ccd05f2c32e49680e44a3b3ac9595504a rts/Stats.c | 242 ++++++++++++++++++++++++++++++------------------------------ 1 file changed, 121 insertions(+), 121 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 5bb8f14ccd05f2c32e49680e44a3b3ac9595504a From git at git.haskell.org Tue Oct 21 21:51:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:28 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify Schedule.h (2dc21b9) Message-ID: <20141021215128.14C803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2dc21b97ffd8e78a177e8b3562ab8f08a566defd/ghc >--------------------------------------------------------------- commit 2dc21b97ffd8e78a177e8b3562ab8f08a566defd Author: Austin Seipp Date: Tue Oct 21 16:37:53 2014 -0500 [skip ci] rts: Detabify Schedule.h Signed-off-by: Austin Seipp >--------------------------------------------------------------- 2dc21b97ffd8e78a177e8b3562ab8f08a566defd rts/Schedule.h | 15 +++++++-------- 1 file changed, 7 insertions(+), 8 deletions(-) diff --git a/rts/Schedule.h b/rts/Schedule.h index 015cc1c..d61be04 100644 --- a/rts/Schedule.h +++ b/rts/Schedule.h @@ -136,10 +136,10 @@ appendToRunQueue (Capability *cap, StgTSO *tso) { ASSERT(tso->_link == END_TSO_QUEUE); if (cap->run_queue_hd == END_TSO_QUEUE) { - cap->run_queue_hd = tso; + cap->run_queue_hd = tso; tso->block_info.prev = END_TSO_QUEUE; } else { - setTSOLink(cap, cap->run_queue_tl, tso); + setTSOLink(cap, cap->run_queue_tl, tso); setTSOPrev(cap, tso, cap->run_queue_tl); } cap->run_queue_tl = tso; @@ -161,7 +161,7 @@ pushOnRunQueue (Capability *cap, StgTSO *tso) } cap->run_queue_hd = tso; if (cap->run_queue_tl == END_TSO_QUEUE) { - cap->run_queue_tl = tso; + cap->run_queue_tl = tso; } } @@ -178,7 +178,7 @@ popRunQueue (Capability *cap) } t->_link = END_TSO_QUEUE; // no write barrier req'd if (cap->run_queue_hd == END_TSO_QUEUE) { - cap->run_queue_tl = END_TSO_QUEUE; + cap->run_queue_tl = END_TSO_QUEUE; } return t; } @@ -200,9 +200,9 @@ appendToBlockedQueue(StgTSO *tso) { ASSERT(tso->_link == END_TSO_QUEUE); if (blocked_queue_hd == END_TSO_QUEUE) { - blocked_queue_hd = tso; + blocked_queue_hd = tso; } else { - setTSOLink(&MainCapability, blocked_queue_tl, tso); + setTSOLink(&MainCapability, blocked_queue_tl, tso); } blocked_queue_tl = tso; } @@ -248,7 +248,7 @@ emptyThreadQueues(Capability *cap) { return emptyRunQueue(cap) #if !defined(THREADED_RTS) - && EMPTY_BLOCKED_QUEUE() && EMPTY_SLEEPING_QUEUE() + && EMPTY_BLOCKED_QUEUE() && EMPTY_SLEEPING_QUEUE() #endif ; } @@ -258,4 +258,3 @@ emptyThreadQueues(Capability *cap) #include "EndPrivate.h" #endif /* SCHEDULE_H */ - From git at git.haskell.org Tue Oct 21 21:51:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:30 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify LdvProfile.h (1d12df3) Message-ID: <20141021215130.9A8EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1d12df3794b4f230d9f1dcca9973a2d9f45fbeed/ghc >--------------------------------------------------------------- commit 1d12df3794b4f230d9f1dcca9973a2d9f45fbeed Author: Austin Seipp Date: Tue Oct 21 16:38:06 2014 -0500 [skip ci] rts: Detabify LdvProfile.h Signed-off-by: Austin Seipp >--------------------------------------------------------------- 1d12df3794b4f230d9f1dcca9973a2d9f45fbeed rts/LdvProfile.h | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/rts/LdvProfile.h b/rts/LdvProfile.h index b441804..d58c5fb 100644 --- a/rts/LdvProfile.h +++ b/rts/LdvProfile.h @@ -23,11 +23,11 @@ RTS_PRIVATE void LdvCensusKillAll ( void ); // Invoked when: // 1) Hp is incremented and exceeds HpLim (in Updates.hc). // 2) copypart() is called (in GC.c). -#define LDV_FILL_SLOP(from, howMany) \ - if (era > 0) { \ - int i; \ - for (i = 0;i < (howMany); i++) \ - ((StgWord *)(from))[i] = 0; \ +#define LDV_FILL_SLOP(from, howMany) \ + if (era > 0) { \ + int i; \ + for (i = 0;i < (howMany); i++) \ + ((StgWord *)(from))[i] = 0; \ } // Informs the LDV profiler that closure c has just been evacuated. From git at git.haskell.org Tue Oct 21 21:51:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:33 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify Proftimer.c (3d0e695) Message-ID: <20141021215133.2D2603A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3d0e695e8ccd505066c806193f4c17487200fce3/ghc >--------------------------------------------------------------- commit 3d0e695e8ccd505066c806193f4c17487200fce3 Author: Austin Seipp Date: Tue Oct 21 16:38:27 2014 -0500 [skip ci] rts: Detabify Proftimer.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- 3d0e695e8ccd505066c806193f4c17487200fce3 rts/Proftimer.c | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/rts/Proftimer.c b/rts/Proftimer.c index 6458f6e..d1736f7 100644 --- a/rts/Proftimer.c +++ b/rts/Proftimer.c @@ -52,7 +52,7 @@ startHeapProfTimer( void ) { if (RtsFlags.ProfFlags.doHeapProfile && RtsFlags.ProfFlags.heapProfileIntervalTicks > 0) { - do_heap_prof_ticks = rtsTrue; + do_heap_prof_ticks = rtsTrue; } } @@ -82,10 +82,10 @@ handleProfTick(void) #endif if (do_heap_prof_ticks) { - ticks_to_heap_profile--; - if (ticks_to_heap_profile <= 0) { + ticks_to_heap_profile--; + if (ticks_to_heap_profile <= 0) { ticks_to_heap_profile = RtsFlags.ProfFlags.heapProfileIntervalTicks; - performHeapProfile = rtsTrue; - } + performHeapProfile = rtsTrue; + } } } From git at git.haskell.org Tue Oct 21 21:51:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:35 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify Exception.cmm (68c45b6) Message-ID: <20141021215135.B75553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/68c45b6563c375cf50d9da187747c57353cfcd0d/ghc >--------------------------------------------------------------- commit 68c45b6563c375cf50d9da187747c57353cfcd0d Author: Austin Seipp Date: Tue Oct 21 16:39:15 2014 -0500 [skip ci] rts: Detabify Exception.cmm Signed-off-by: Austin Seipp >--------------------------------------------------------------- 68c45b6563c375cf50d9da187747c57353cfcd0d rts/Exception.cmm | 54 +++++++++++++++++++++++++++--------------------------- 1 file changed, 27 insertions(+), 27 deletions(-) diff --git a/rts/Exception.cmm b/rts/Exception.cmm index bc55911..e03d53e 100644 --- a/rts/Exception.cmm +++ b/rts/Exception.cmm @@ -21,7 +21,7 @@ import ghczmprim_GHCziTypes_True_closure; A thread can request that asynchronous exceptions not be delivered ("masked") for the duration of an I/O computation. The primitives - maskAsyncExceptions# :: IO a -> IO a + maskAsyncExceptions# :: IO a -> IO a and @@ -30,7 +30,7 @@ import ghczmprim_GHCziTypes_True_closure; are used for this purpose. During a masked section, asynchronous exceptions may be unmasked again temporarily: - unmaskAsyncExceptions# :: IO a -> IO a + unmaskAsyncExceptions# :: IO a -> IO a Furthermore, asynchronous exceptions are masked automatically during the execution of an exception handler. All three of these primitives @@ -111,7 +111,7 @@ INFO_TABLE_RET(stg_maskAsyncExceptionszh_ret, RET_SMALL, W_ info_ptr) { StgTSO_flags(CurrentTSO) = %lobits32( - TO_W_(StgTSO_flags(CurrentTSO)) + TO_W_(StgTSO_flags(CurrentTSO)) | TSO_BLOCKEX | TSO_INTERRUPTIBLE ); @@ -123,7 +123,7 @@ INFO_TABLE_RET(stg_maskUninterruptiblezh_ret, RET_SMALL, W_ info_ptr) { StgTSO_flags(CurrentTSO) = %lobits32( - (TO_W_(StgTSO_flags(CurrentTSO)) + (TO_W_(StgTSO_flags(CurrentTSO)) | TSO_BLOCKEX) & ~TSO_INTERRUPTIBLE ); @@ -204,19 +204,19 @@ stg_unmaskAsyncExceptionszh /* explicit stack */ /* If exceptions are already unmasked, there's nothing to do */ if ((TO_W_(StgTSO_flags(CurrentTSO)) & TSO_BLOCKEX) != 0) { - /* avoid growing the stack unnecessarily */ - if (Sp(0) == stg_unmaskAsyncExceptionszh_ret_info) { - Sp_adj(1); - } else { - Sp_adj(-1); + /* avoid growing the stack unnecessarily */ + if (Sp(0) == stg_unmaskAsyncExceptionszh_ret_info) { + Sp_adj(1); + } else { + Sp_adj(-1); if ((TO_W_(StgTSO_flags(CurrentTSO)) & TSO_INTERRUPTIBLE) != 0) { Sp(0) = stg_maskAsyncExceptionszh_ret_info; } else { Sp(0) = stg_maskUninterruptiblezh_ret_info; } - } + } - StgTSO_flags(CurrentTSO) = %lobits32( + StgTSO_flags(CurrentTSO) = %lobits32( TO_W_(StgTSO_flags(CurrentTSO)) & ~(TSO_BLOCKEX|TSO_INTERRUPTIBLE)); /* Eagerly raise a masked exception, if there is one */ @@ -244,12 +244,12 @@ stg_unmaskAsyncExceptionszh /* explicit stack */ if (r != 0::CInt) { if (StgTSO_what_next(CurrentTSO) == ThreadKilled::I16) { jump stg_threadFinished []; - } else { - LOAD_THREAD_STATE(); - ASSERT(StgTSO_what_next(CurrentTSO) == ThreadRunGHC::I16); + } else { + LOAD_THREAD_STATE(); + ASSERT(StgTSO_what_next(CurrentTSO) == ThreadRunGHC::I16); R1 = io; jump %ENTRY_CODE(Sp(0)) [R1]; - } + } } else { /* we'll just call R1 directly, below */ Sp_adj(3); @@ -306,7 +306,7 @@ stg_killThreadzh (P_ target, P_ exception) } else { W_ msg; - (msg) = ccall throwTo(MyCapability() "ptr", + (msg) = ccall throwTo(MyCapability() "ptr", CurrentTSO "ptr", target "ptr", exception "ptr"); @@ -316,9 +316,9 @@ stg_killThreadzh (P_ target, P_ exception) } else { StgTSO_why_blocked(CurrentTSO) = BlockedOnMsgThrowTo; StgTSO_block_info(CurrentTSO) = msg; - // we must block, and unlock the message before returning + // we must block, and unlock the message before returning jump stg_block_throwto (target, exception); - } + } } } @@ -535,19 +535,19 @@ retry_pop_stack: } if (frame_type == STOP_FRAME) { - /* - * We've stripped the entire stack, the thread is now dead. - * We will leave the stack in a GC'able state, see the stg_stop_thread - * entry code in StgStartup.cmm. - */ + /* + * We've stripped the entire stack, the thread is now dead. + * We will leave the stack in a GC'able state, see the stg_stop_thread + * entry code in StgStartup.cmm. + */ W_ stack; stack = StgTSO_stackobj(CurrentTSO); Sp = stack + OFFSET_StgStack_stack + WDS(TO_W_(StgStack_stack_size(stack))) - WDS(2); - Sp(1) = exception; /* save the exception */ - Sp(0) = stg_enter_info; /* so that GC can traverse this stack */ - StgTSO_what_next(CurrentTSO) = ThreadKilled::I16; - SAVE_THREAD_STATE(); /* inline! */ + Sp(1) = exception; /* save the exception */ + Sp(0) = stg_enter_info; /* so that GC can traverse this stack */ + StgTSO_what_next(CurrentTSO) = ThreadKilled::I16; + SAVE_THREAD_STATE(); /* inline! */ jump stg_threadFinished []; } From git at git.haskell.org Tue Oct 21 21:51:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:38 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify HeapStackCheck.cmm (a7ab7d3) Message-ID: <20141021215138.4BA293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a7ab7d385e6097e0ea1fd4729a9ef1041f9710a8/ghc >--------------------------------------------------------------- commit a7ab7d385e6097e0ea1fd4729a9ef1041f9710a8 Author: Austin Seipp Date: Tue Oct 21 16:39:44 2014 -0500 [skip ci] rts: Detabify HeapStackCheck.cmm Signed-off-by: Austin Seipp >--------------------------------------------------------------- a7ab7d385e6097e0ea1fd4729a9ef1041f9710a8 rts/HeapStackCheck.cmm | 52 +++++++++++++++++++++++++------------------------- 1 file changed, 26 insertions(+), 26 deletions(-) diff --git a/rts/HeapStackCheck.cmm b/rts/HeapStackCheck.cmm index f090bff..0659fed 100644 --- a/rts/HeapStackCheck.cmm +++ b/rts/HeapStackCheck.cmm @@ -73,9 +73,9 @@ import LeaveCriticalSection; * the stack is already too big. */ -#define PRE_RETURN(why,what_next) \ - StgTSO_what_next(CurrentTSO) = what_next::I16; \ - StgRegTable_rRet(BaseReg) = why; \ +#define PRE_RETURN(why,what_next) \ + StgTSO_what_next(CurrentTSO) = what_next::I16; \ + StgRegTable_rRet(BaseReg) = why; \ R1 = BaseReg; /* Remember that the return address is *removed* when returning to a @@ -122,24 +122,24 @@ stg_gc_noregs jump stg_returnToSched [R1]; } -#define HP_GENERIC \ +#define HP_GENERIC \ PRE_RETURN(HeapOverflow, ThreadRunGHC) \ jump stg_returnToSched [R1]; -#define BLOCK_GENERIC \ +#define BLOCK_GENERIC \ PRE_RETURN(ThreadBlocked, ThreadRunGHC) \ jump stg_returnToSched [R1]; -#define YIELD_GENERIC \ +#define YIELD_GENERIC \ PRE_RETURN(ThreadYielding, ThreadRunGHC) \ jump stg_returnToSched [R1]; -#define BLOCK_BUT_FIRST(c) \ +#define BLOCK_BUT_FIRST(c) \ PRE_RETURN(ThreadBlocked, ThreadRunGHC) \ R2 = c; \ jump stg_returnToSchedButFirst [R1,R2,R3]; -#define YIELD_TO_INTERPRETER \ +#define YIELD_TO_INTERPRETER \ PRE_RETURN(ThreadYielding, ThreadInterpret) \ jump stg_returnToSchedNotPaused [R1]; @@ -368,13 +368,13 @@ stg_gc_pppp return (P_ arg1, P_ arg2, P_ arg3, P_ arg4) | .... | | args | - +---------------------+ + +---------------------+ | f_closure | - +---------------------+ + +---------------------+ | size | - +---------------------+ + +---------------------+ | stg_gc_fun_info | - +---------------------+ + +---------------------+ The size is the number of words of arguments on the stack, and is cached in the frame in order to simplify stack walking: otherwise the size of @@ -393,19 +393,19 @@ __stg_gc_fun /* explicit stack */ // cache the size type = TO_W_(StgFunInfoExtra_fun_type(info)); if (type == ARG_GEN) { - size = BITMAP_SIZE(StgFunInfoExtra_bitmap(info)); + size = BITMAP_SIZE(StgFunInfoExtra_bitmap(info)); } else { - if (type == ARG_GEN_BIG) { + if (type == ARG_GEN_BIG) { #ifdef TABLES_NEXT_TO_CODE // bitmap field holds an offset size = StgLargeBitmap_size( StgFunInfoExtra_bitmap(info) + %GET_ENTRY(UNTAG(R1)) /* ### */ ); #else - size = StgLargeBitmap_size( StgFunInfoExtra_bitmap(info) ); + size = StgLargeBitmap_size( StgFunInfoExtra_bitmap(info) ); #endif - } else { - size = BITMAP_SIZE(W_[stg_arg_bitmaps + WDS(type)]); - } + } else { + size = BITMAP_SIZE(W_[stg_arg_bitmaps + WDS(type)]); + } } #ifdef NO_ARG_REGS @@ -429,7 +429,7 @@ __stg_gc_fun /* explicit stack */ jump stg_gc_noregs []; } else { jump W_[stg_stack_save_entries + WDS(type)] [*]; // all regs live - // jumps to stg_gc_noregs after saving stuff + // jumps to stg_gc_noregs after saving stuff } #endif /* !NO_ARG_REGS */ } @@ -461,15 +461,15 @@ INFO_TABLE_RET ( stg_gc_fun, RET_FUN ) if (type == ARG_GEN || type == ARG_GEN_BIG) { jump StgFunInfoExtra_slow_apply(info) [R1]; } else { - if (type == ARG_BCO) { - // cover this case just to be on the safe side - Sp_adj(-2); - Sp(1) = R1; - Sp(0) = stg_apply_interp_info; + if (type == ARG_BCO) { + // cover this case just to be on the safe side + Sp_adj(-2); + Sp(1) = R1; + Sp(0) = stg_apply_interp_info; jump stg_yield_to_interpreter []; - } else { + } else { jump W_[stg_ap_stack_entries + WDS(type)] [R1]; - } + } } #endif } From git at git.haskell.org Tue Oct 21 21:51:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:40 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify Capability.c (6811e53) Message-ID: <20141021215140.DF6CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6811e53ae174dcb042be976f9c65e3ed6a6d1782/ghc >--------------------------------------------------------------- commit 6811e53ae174dcb042be976f9c65e3ed6a6d1782 Author: Austin Seipp Date: Tue Oct 21 16:40:40 2014 -0500 [skip ci] rts: Detabify Capability.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- 6811e53ae174dcb042be976f9c65e3ed6a6d1782 rts/Capability.c | 278 +++++++++++++++++++++++++++---------------------------- 1 file changed, 139 insertions(+), 139 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 6811e53ae174dcb042be976f9c65e3ed6a6d1782 From git at git.haskell.org Tue Oct 21 21:51:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:43 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify RaiseAsync.c (beb5c2e) Message-ID: <20141021215143.749E83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/beb5c2ec91091c9028f8ba962ddd39b3fde20a9b/ghc >--------------------------------------------------------------- commit beb5c2ec91091c9028f8ba962ddd39b3fde20a9b Author: Austin Seipp Date: Tue Oct 21 16:41:02 2014 -0500 [skip ci] rts: Detabify RaiseAsync.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- beb5c2ec91091c9028f8ba962ddd39b3fde20a9b rts/RaiseAsync.c | 392 +++++++++++++++++++++++++++---------------------------- 1 file changed, 195 insertions(+), 197 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 beb5c2ec91091c9028f8ba962ddd39b3fde20a9b From git at git.haskell.org Tue Oct 21 21:51:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:46 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify sm/GC.c (e13478f) Message-ID: <20141021215146.0C7E23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e13478f2f4e350f57c9f73b5a8e41b68f98964e2/ghc >--------------------------------------------------------------- commit e13478f2f4e350f57c9f73b5a8e41b68f98964e2 Author: Austin Seipp Date: Tue Oct 21 16:42:10 2014 -0500 [skip ci] rts: Detabify sm/GC.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- e13478f2f4e350f57c9f73b5a8e41b68f98964e2 rts/sm/GC.c | 328 ++++++++++++++++++++++++++++++------------------------------ 1 file changed, 164 insertions(+), 164 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 e13478f2f4e350f57c9f73b5a8e41b68f98964e2 From git at git.haskell.org Tue Oct 21 21:51:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:48 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify sm/Sanity.c (faa3339) Message-ID: <20141021215148.AC26F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/faa3339682baa898a97bf50b0327675b985fb981/ghc >--------------------------------------------------------------- commit faa3339682baa898a97bf50b0327675b985fb981 Author: Austin Seipp Date: Tue Oct 21 16:42:24 2014 -0500 [skip ci] rts: Detabify sm/Sanity.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- faa3339682baa898a97bf50b0327675b985fb981 rts/sm/Sanity.c | 282 ++++++++++++++++++++++++++++---------------------------- 1 file changed, 141 insertions(+), 141 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 faa3339682baa898a97bf50b0327675b985fb981 From git at git.haskell.org Tue Oct 21 21:51:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:51 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify sm/Compact.c (bc1609a) Message-ID: <20141021215151.4973D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bc1609a722dbddd169734b4a4ba11ef88fd42c01/ghc >--------------------------------------------------------------- commit bc1609a722dbddd169734b4a4ba11ef88fd42c01 Author: Austin Seipp Date: Tue Oct 21 16:42:49 2014 -0500 [skip ci] rts: Detabify sm/Compact.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- bc1609a722dbddd169734b4a4ba11ef88fd42c01 rts/sm/Compact.c | 608 +++++++++++++++++++++++++++---------------------------- 1 file changed, 304 insertions(+), 304 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 bc1609a722dbddd169734b4a4ba11ef88fd42c01 From git at git.haskell.org Tue Oct 21 21:51:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:53 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify sm/Compact.h (c8173d5) Message-ID: <20141021215153.D62AF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c8173d5105a8463890e536d621c35805d6f67e4b/ghc >--------------------------------------------------------------- commit c8173d5105a8463890e536d621c35805d6f67e4b Author: Austin Seipp Date: Tue Oct 21 16:43:04 2014 -0500 [skip ci] rts: Detabify sm/Compact.h Signed-off-by: Austin Seipp >--------------------------------------------------------------- c8173d5105a8463890e536d621c35805d6f67e4b rts/sm/Compact.h | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/rts/sm/Compact.h b/rts/sm/Compact.h index 1ec915f..db7a969 100644 --- a/rts/sm/Compact.h +++ b/rts/sm/Compact.h @@ -21,7 +21,7 @@ mark(StgPtr p, bdescr *bd) { nat offset_within_block = p - bd->start; // in words StgPtr bitmap_word = (StgPtr)bd->u.bitmap + - (offset_within_block / (sizeof(W_)*BITS_PER_BYTE)); + (offset_within_block / (sizeof(W_)*BITS_PER_BYTE)); StgWord bit_mask = (StgWord)1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); *bitmap_word |= bit_mask; } @@ -31,7 +31,7 @@ unmark(StgPtr p, bdescr *bd) { nat offset_within_block = p - bd->start; // in words StgPtr bitmap_word = (StgPtr)bd->u.bitmap + - (offset_within_block / (sizeof(W_)*BITS_PER_BYTE)); + (offset_within_block / (sizeof(W_)*BITS_PER_BYTE)); StgWord bit_mask = (StgWord)1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); *bitmap_word &= ~bit_mask; } @@ -41,7 +41,7 @@ is_marked(StgPtr p, bdescr *bd) { nat offset_within_block = p - bd->start; // in words StgPtr bitmap_word = (StgPtr)bd->u.bitmap + - (offset_within_block / (sizeof(W_)*BITS_PER_BYTE)); + (offset_within_block / (sizeof(W_)*BITS_PER_BYTE)); StgWord bit_mask = (StgWord)1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); return (*bitmap_word & bit_mask); } From git at git.haskell.org Tue Oct 21 21:51:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:56 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify RetainerProfile.c (5106e20) Message-ID: <20141021215156.74E5E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5106e201241aa8f07ba97decab301a01e363bdc2/ghc >--------------------------------------------------------------- commit 5106e201241aa8f07ba97decab301a01e363bdc2 Author: Austin Seipp Date: Tue Oct 21 16:44:19 2014 -0500 [skip ci] rts: Detabify RetainerProfile.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- 5106e201241aa8f07ba97decab301a01e363bdc2 rts/RetainerProfile.c | 1610 ++++++++++++++++++++++++------------------------- 1 file changed, 805 insertions(+), 805 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 5106e201241aa8f07ba97decab301a01e363bdc2 From git at git.haskell.org Tue Oct 21 21:51:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:51:59 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify ProfHeap.c (03c3e9a) Message-ID: <20141021215159.0E01F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/03c3e9ae76a2294a4014aa64b608bd86597dcada/ghc >--------------------------------------------------------------- commit 03c3e9ae76a2294a4014aa64b608bd86597dcada Author: Austin Seipp Date: Tue Oct 21 16:44:41 2014 -0500 [skip ci] rts: Detabify ProfHeap.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- 03c3e9ae76a2294a4014aa64b608bd86597dcada rts/ProfHeap.c | 873 ++++++++++++++++++++++++++++----------------------------- 1 file changed, 436 insertions(+), 437 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 03c3e9ae76a2294a4014aa64b608bd86597dcada From git at git.haskell.org Tue Oct 21 21:52:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:52:01 +0000 (UTC) Subject: [commit: ghc] master: [skip ci] rts: Detabify Schedule.c (6abb34c) Message-ID: <20141021215201.9A8BA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6abb34c6c2f4cff938b435cda71b97cee9fb830f/ghc >--------------------------------------------------------------- commit 6abb34c6c2f4cff938b435cda71b97cee9fb830f Author: Austin Seipp Date: Tue Oct 21 16:45:19 2014 -0500 [skip ci] rts: Detabify Schedule.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- 6abb34c6c2f4cff938b435cda71b97cee9fb830f rts/Schedule.c | 720 ++++++++++++++++++++++++++++----------------------------- 1 file changed, 360 insertions(+), 360 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 6abb34c6c2f4cff938b435cda71b97cee9fb830f From git at git.haskell.org Tue Oct 21 21:52:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:52:04 +0000 (UTC) Subject: [commit: ghc] master: rts: Detabify Interpreter.c (9bfe602) Message-ID: <20141021215204.366543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9bfe6026ca0f611ff8b2d0e03041662e3666c94f/ghc >--------------------------------------------------------------- commit 9bfe6026ca0f611ff8b2d0e03041662e3666c94f Author: Austin Seipp Date: Tue Oct 21 16:45:57 2014 -0500 rts: Detabify Interpreter.c Signed-off-by: Austin Seipp >--------------------------------------------------------------- 9bfe6026ca0f611ff8b2d0e03041662e3666c94f rts/Interpreter.c | 1670 ++++++++++++++++++++++++++--------------------------- 1 file changed, 835 insertions(+), 835 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 9bfe6026ca0f611ff8b2d0e03041662e3666c94f From git at git.haskell.org Tue Oct 21 21:52:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 21 Oct 2014 21:52:06 +0000 (UTC) Subject: [commit: ghc] master: base: Mark WCsubst.c as generated for Phabricator (df5c11a) Message-ID: <20141021215206.C45B03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/df5c11a54dab2f84765be129e8a51a95ec14378a/ghc >--------------------------------------------------------------- commit df5c11a54dab2f84765be129e8a51a95ec14378a Author: Austin Seipp Date: Tue Oct 21 16:50:23 2014 -0500 base: Mark WCsubst.c as generated for Phabricator Signed-off-by: Austin Seipp >--------------------------------------------------------------- df5c11a54dab2f84765be129e8a51a95ec14378a libraries/base/cbits/WCsubst.c | 1 + libraries/base/cbits/ubconfc | 1 + 2 files changed, 2 insertions(+) diff --git a/libraries/base/cbits/WCsubst.c b/libraries/base/cbits/WCsubst.c index a1abadd..c4b0645 100644 --- a/libraries/base/cbits/WCsubst.c +++ b/libraries/base/cbits/WCsubst.c @@ -1,6 +1,7 @@ /*------------------------------------------------------------------------- This is an automatically generated file: do not edit Generated by ubconfc at Wed Oct 15 14:24:39 EDT 2014 + at generated -------------------------------------------------------------------------*/ #include "WCsubst.h" diff --git a/libraries/base/cbits/ubconfc b/libraries/base/cbits/ubconfc index fc768cc..509049d 100644 --- a/libraries/base/cbits/ubconfc +++ b/libraries/base/cbits/ubconfc @@ -20,6 +20,7 @@ echo "/*-------------------------------------------------------------------------" echo "This is an automatically generated file: do not edit" echo "Generated by `basename $0` at `date`" +echo "@generated" echo "-------------------------------------------------------------------------*/" echo echo "#include \"WCsubst.h\"" From git at git.haskell.org Wed Oct 22 08:49:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 22 Oct 2014 08:49:42 +0000 (UTC) Subject: [commit: ghc] master: Flush stdout in T9692 (45cbe85) Message-ID: <20141022084942.361883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/45cbe8533faee2416f354018826db48263377765/ghc >--------------------------------------------------------------- commit 45cbe8533faee2416f354018826db48263377765 Author: Joachim Breitner Date: Wed Oct 22 10:49:35 2014 +0200 Flush stdout in T9692 >--------------------------------------------------------------- 45cbe8533faee2416f354018826db48263377765 testsuite/tests/th/T9692.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/testsuite/tests/th/T9692.hs b/testsuite/tests/th/T9692.hs index 82e5951..2ae835c 100644 --- a/testsuite/tests/th/T9692.hs +++ b/testsuite/tests/th/T9692.hs @@ -14,4 +14,5 @@ instance C Int where $( do info <- qReify (mkName "F") runIO $ putStrLn $ pprint info + runIO $ hFlush stdout return []) From git at git.haskell.org Wed Oct 22 13:02:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 22 Oct 2014 13:02:46 +0000 (UTC) Subject: [commit: ghc] master: Add forgotten import to T9692 (aa641e5) Message-ID: <20141022130246.B2DF83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aa641e514821514e76a07d03f3783b94f819f085/ghc >--------------------------------------------------------------- commit aa641e514821514e76a07d03f3783b94f819f085 Author: Joachim Breitner Date: Wed Oct 22 15:02:42 2014 +0200 Add forgotten import to T9692 (sorry) >--------------------------------------------------------------- aa641e514821514e76a07d03f3783b94f819f085 testsuite/tests/th/T9692.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/testsuite/tests/th/T9692.hs b/testsuite/tests/th/T9692.hs index 2ae835c..770290d 100644 --- a/testsuite/tests/th/T9692.hs +++ b/testsuite/tests/th/T9692.hs @@ -5,6 +5,7 @@ module T9692 where import Language.Haskell.TH import Language.Haskell.TH.Syntax import Language.Haskell.TH.Ppr +import System.IO class C a where data F a (b :: k) :: * From git at git.haskell.org Thu Oct 23 13:57:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 23 Oct 2014 13:57:16 +0000 (UTC) Subject: [commit: ghc] master: Fix a rare parallel GC bug (a11f71e) Message-ID: <20141023135716.7175A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a11f71eff15ba2706cbb2ee29aaf7350909e0d2f/ghc >--------------------------------------------------------------- commit a11f71eff15ba2706cbb2ee29aaf7350909e0d2f Author: Simon Marlow Date: Thu Oct 23 11:12:16 2014 +0100 Fix a rare parallel GC bug When there's a conflict between two threads evacuating the same TSO, in some cases we would update the incall->tso pointer to point to the wrong copy of the TSO. This would get fixed during the next GC, but if the thread completed in the meantime, it would likely crash. We're seeing this about once per day on a heavily loaded machine (it varies a lot though). >--------------------------------------------------------------- a11f71eff15ba2706cbb2ee29aaf7350909e0d2f rts/sm/Scav.c | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/rts/sm/Scav.c b/rts/sm/Scav.c index 1abaefb..97c6589 100644 --- a/rts/sm/Scav.c +++ b/rts/sm/Scav.c @@ -55,7 +55,12 @@ scavengeTSO (StgTSO *tso) // update the pointer from the InCall. if (tso->bound != NULL) { - tso->bound->tso = tso; + // NB. We can't just set tso->bound->tso = tso, because this + // might be an invalid copy the TSO resulting from multiple + // threads evacuating the TSO simultaneously (see + // Evac.c:copy_tag()). Calling evacuate() on this pointer + // will ensure that we update it to point to the correct copy. + evacuate((StgClosure **)&tso->bound->tso); } saved_eager = gct->eager_promotion; From git at git.haskell.org Fri Oct 24 01:20:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 24 Oct 2014 01:20:16 +0000 (UTC) Subject: [commit: ghc] master: More updates to Backpack manual [skip ci] (427925d) Message-ID: <20141024012016.2FC843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/427925d0806fca7facf76ba42429a3b0ebc4eb8a/ghc >--------------------------------------------------------------- commit 427925d0806fca7facf76ba42429a3b0ebc4eb8a Author: Edward Z. Yang Date: Thu Oct 23 18:19:46 2014 -0700 More updates to Backpack manual [skip ci] Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 427925d0806fca7facf76ba42429a3b0ebc4eb8a docs/backpack/backpack-manual.tex | 259 +++++++++++++++++--------------------- 1 file changed, 112 insertions(+), 147 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 427925d0806fca7facf76ba42429a3b0ebc4eb8a From git at git.haskell.org Fri Oct 24 01:20:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 24 Oct 2014 01:20:19 +0000 (UTC) Subject: [commit: ghc] master: Check in up-to-date PDF copies of Backpack docs. [skip ci] (5bb73d7) Message-ID: <20141024012019.2204B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5bb73d79a83bca57dc431421ca1e022f34b8dec9/ghc >--------------------------------------------------------------- commit 5bb73d79a83bca57dc431421ca1e022f34b8dec9 Author: Edward Z. Yang Date: Thu Oct 23 18:20:25 2014 -0700 Check in up-to-date PDF copies of Backpack docs. [skip ci] Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 5bb73d79a83bca57dc431421ca1e022f34b8dec9 docs/backpack/backpack-impl.pdf | Bin 0 -> 436890 bytes docs/backpack/backpack-manual.pdf | Bin 0 -> 181875 bytes 2 files changed, 0 insertions(+), 0 deletions(-) diff --git a/docs/backpack/backpack-impl.pdf b/docs/backpack/backpack-impl.pdf new file mode 100644 index 0000000..80dafbc Binary files /dev/null and b/docs/backpack/backpack-impl.pdf differ diff --git a/docs/backpack/backpack-manual.pdf b/docs/backpack/backpack-manual.pdf new file mode 100644 index 0000000..0ec544a Binary files /dev/null and b/docs/backpack/backpack-manual.pdf differ From git at git.haskell.org Fri Oct 24 23:47:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 24 Oct 2014 23:47:53 +0000 (UTC) Subject: [commit: ghc] master: Implementation of hsig (module signatures), per #9252 (aa47995) Message-ID: <20141024234754.001D93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aa4799534225e3fc6bbde0d5e5eeab8868cc3111/ghc >--------------------------------------------------------------- commit aa4799534225e3fc6bbde0d5e5eeab8868cc3111 Author: Edward Z. Yang Date: Thu Aug 7 18:32:12 2014 +0100 Implementation of hsig (module signatures), per #9252 Summary: Module signatures, like hs-boot files, are Haskell modules which omit value definitions and contain only signatures. This patchset implements one particular aspect of module signature, namely compiling them against a concrete implementation. It works like this: when we compile an hsig file, we must be told (via the -sig-of flag) what module this signature is implementing. The signature is compiled into an interface file which reexports precisely the entities mentioned in the signature file. We also verify that the interface is compatible with the implementation. This feature is useful in a few situations: 1. Like explicit import lists, signatures can be used to reduce sensitivity to upstream changes. However, a signature can be defined once and then reused by many modules. 2. Signatures can be used to quickly check if a new upstream version is compatible, by typechecking just the signatures and not the actual modules. 3. A signature can be used to mediate separate modular development, where the signature is used as a placeholder for functionality which is loaded in later. (This is only half useful at the moment, since typechecking against signatures without implementations is not implemented in this patchset.) Unlike hs-boot files, hsig files impose no performance overhead. This patchset punts on the type class instances (and type families) problem: instances simply leak from the implementation to the signature. You can explicitly specify what instances you expect to have, and those will be checked, but you may get more instances than you asked for. Our eventual plan is to allow hiding instances, but to consider all transitively reachable instances when considering overlap and soundness. ToDo: signature merging: when a module is provided by multiple signatures for the same base implementation, we should not consider this ambiguous. ToDo: at the moment, signatures do not constitute use-sites, so if you write a signature for a deprecated function, you won't get a warning when you compile the signature. Future work: The ability to feed in shaping information so that we can take advantage of more type equalities than might be immediately evident. Signed-off-by: Edward Z. Yang Test Plan: validate and new tests Reviewers: simonpj, simonmar, hvr, austin Subscribers: simonmar, relrod, ezyang, carter, goldfire Differential Revision: https://phabricator.haskell.org/D130 GHC Trac Issues: #9252 >--------------------------------------------------------------- aa4799534225e3fc6bbde0d5e5eeab8868cc3111 compiler/basicTypes/Name.lhs | 6 + compiler/deSugar/Desugar.lhs | 4 +- compiler/iface/LoadIface.lhs | 1 + compiler/iface/MkIface.lhs | 10 +- compiler/iface/TcIface.lhs | 2 +- compiler/main/DriverPhases.hs | 64 +++++- compiler/main/DriverPipeline.hs | 17 +- compiler/main/DynFlags.hs | 47 ++++- compiler/main/Finder.lhs | 2 + compiler/main/GhcMake.hs | 103 +++++++--- compiler/main/HscMain.hs | 2 +- compiler/main/HscTypes.lhs | 33 +++- compiler/main/TidyPgm.lhs | 3 + compiler/rename/RnBinds.lhs | 2 +- compiler/rename/RnEnv.lhs | 90 ++++++++- compiler/rename/RnNames.lhs | 187 ++++++++++-------- compiler/typecheck/Inst.lhs | 59 +++++- compiler/typecheck/TcBinds.lhs | 4 +- compiler/typecheck/TcDeriv.lhs | 2 +- compiler/typecheck/TcEnv.lhs | 2 +- compiler/typecheck/TcInstDcls.lhs | 11 +- compiler/typecheck/TcRnDriver.lhs | 217 ++++++++++++++++++--- compiler/typecheck/TcRnMonad.lhs | 11 +- compiler/typecheck/TcRnTypes.lhs | 52 +++++ compiler/typecheck/TcTyClsDecls.lhs | 8 +- compiler/types/InstEnv.lhs | 8 + docs/users_guide/separate_compilation.xml | 96 +++++++++ testsuite/.gitignore | 10 + testsuite/tests/driver/recomp014/Makefile | 27 +++ testsuite/tests/driver/recomp014/all.T | 4 + testsuite/tests/driver/recomp014/recomp014.stdout | 3 + testsuite/tests/driver/sigof01/A.hs | 10 + testsuite/tests/driver/sigof01/B.hsig | 6 + testsuite/tests/driver/sigof01/Main.hs | 6 + testsuite/tests/driver/sigof01/Makefile | 23 +++ testsuite/tests/driver/sigof01/all.T | 9 + testsuite/tests/driver/sigof01/sigof01.stdout | 3 + testsuite/tests/driver/sigof01/sigof01m.stdout | 7 + testsuite/tests/driver/sigof02/Double.hs | 13 ++ testsuite/tests/driver/sigof02/Main.hs | 11 ++ testsuite/tests/driver/sigof02/Makefile | 75 +++++++ testsuite/tests/driver/sigof02/Map.hsig | 133 +++++++++++++ testsuite/tests/driver/sigof02/MapAsSet.hsig | 11 ++ testsuite/tests/driver/sigof02/all.T | 41 ++++ testsuite/tests/driver/sigof02/sigof02.stderr | 1 + testsuite/tests/driver/sigof02/sigof02.stdout | 3 + testsuite/tests/driver/sigof02/sigof02d.stdout | 4 + testsuite/tests/driver/sigof02/sigof02dm.stdout | 8 + testsuite/tests/driver/sigof02/sigof02dmt.stderr | 8 + testsuite/tests/driver/sigof02/sigof02dmt.stdout | 3 + testsuite/tests/driver/sigof02/sigof02dt.stderr | 8 + testsuite/tests/driver/sigof02/sigof02m.stderr | 1 + testsuite/tests/driver/sigof02/sigof02m.stdout | 9 + testsuite/tests/driver/sigof02/sigof02mt.stdout | 2 + testsuite/tests/driver/sigof03/A.hs | 3 + testsuite/tests/driver/sigof03/ASig1.hsig | 3 + testsuite/tests/driver/sigof03/ASig2.hsig | 3 + testsuite/tests/driver/sigof03/Main.hs | 3 + testsuite/tests/driver/sigof03/Makefile | 30 +++ testsuite/tests/driver/sigof03/all.T | 11 ++ testsuite/tests/driver/sigof04/Makefile | 14 ++ testsuite/tests/driver/sigof04/Sig.hsig | 2 + testsuite/tests/driver/sigof04/all.T | 4 + testsuite/tests/driver/sigof04/sigof04.stderr | 3 + testsuite/tests/ghci/scripts/T5979.stderr | 6 +- .../tests/safeHaskell/check/pkg01/safePkg01.stdout | 6 +- testsuite/tests/typecheck/should_compile/all.T | 1 + .../tests/typecheck/should_compile/tc264.hsig | 2 + .../tests/typecheck/should_compile/tc264.stderr | 1 + testsuite/tests/typecheck/should_fail/all.T | 5 + .../tests/typecheck/should_fail/tcfail219.hsig | 2 + .../tests/typecheck/should_fail/tcfail219.stderr | 3 + .../tests/typecheck/should_fail/tcfail220.hsig | 5 + .../tests/typecheck/should_fail/tcfail220.stderr | 13 ++ .../tests/typecheck/should_fail/tcfail221.hsig | 3 + .../tests/typecheck/should_fail/tcfail221.stderr | 6 + .../tests/typecheck/should_fail/tcfail222.hsig | 2 + .../tests/typecheck/should_fail/tcfail222.stderr | 4 + 78 files changed, 1409 insertions(+), 208 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 aa4799534225e3fc6bbde0d5e5eeab8868cc3111 From git at git.haskell.org Sat Oct 25 00:09:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 00:09:06 +0000 (UTC) Subject: [commit: ghc] master: Fix windows build failure. (1addef8) Message-ID: <20141025000906.C4B863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1addef805ceacb13d346eb14190e1c9b88d02d2d/ghc >--------------------------------------------------------------- commit 1addef805ceacb13d346eb14190e1c9b88d02d2d Author: Austin Seipp Date: Fri Oct 24 17:57:50 2014 -0500 Fix windows build failure. Authored-by: Simon Marlow Signed-off-by: Austin Seipp >--------------------------------------------------------------- 1addef805ceacb13d346eb14190e1c9b88d02d2d rts/Linker.c | 14 ++++++++------ 1 file changed, 8 insertions(+), 6 deletions(-) diff --git a/rts/Linker.c b/rts/Linker.c index 4ab7cc5..c40086d 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -217,8 +217,9 @@ static int ocRunInit_PEi386 ( ObjectCode* oc ); static void *lookupSymbolInDLLs ( unsigned char *lbl ); static void zapTrailingAtSign ( unsigned char *sym ); static char *allocateImageAndTrampolines ( + pathchar* arch_name, char* member_name, #if defined(x86_64_HOST_ARCH) - FILE* f, pathchar* arch_name, char* member_name, + FILE* f, #endif int size ); #if defined(x86_64_HOST_ARCH) @@ -2725,9 +2726,9 @@ loadArchive( pathchar *path ) #elif defined(mingw32_HOST_OS) // TODO: We would like to use allocateExec here, but allocateExec // cannot currently allocate blocks large enough. - image = allocateImageAndTrampolines( + image = allocateImageAndTrampolines(path, fileName, #if defined(x86_64_HOST_ARCH) - f, path, fileName, + f, #endif memberSize); #elif defined(darwin_HOST_OS) @@ -2946,9 +2947,9 @@ loadObj( pathchar *path ) # if defined(mingw32_HOST_OS) // TODO: We would like to use allocateExec here, but allocateExec // cannot currently allocate blocks large enough. - image = allocateImageAndTrampolines( + image = allocateImageAndTrampolines(path, "itself", #if defined(x86_64_HOST_ARCH) - f, path, "itself", + f, #endif fileSize); if (image == NULL) { @@ -3663,8 +3664,9 @@ static int verifyCOFFHeader ( COFF_header *hdr, pathchar *filename); */ static char * allocateImageAndTrampolines ( + pathchar* arch_name, char* member_name, #if defined(x86_64_HOST_ARCH) - FILE* f, pathchar* arch_name, char* member_name, + FILE* f, #endif int size ) { From git at git.haskell.org Sat Oct 25 00:27:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 00:27:07 +0000 (UTC) Subject: [commit: ghc] master: fix a typo in comments: normaliseFfiType (73c7ea7) Message-ID: <20141025002707.432B53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/73c7ea7e00f31993990ad2d57b86b6b7a5424a4a/ghc >--------------------------------------------------------------- commit 73c7ea7e00f31993990ad2d57b86b6b7a5424a4a Author: Yuras Shumovich Date: Fri Oct 24 19:26:55 2014 -0500 fix a typo in comments: normaliseFfiType Summary: The function is defined in TcForeign module, but misspelled comment makes it hard to find Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D368 >--------------------------------------------------------------- 73c7ea7e00f31993990ad2d57b86b6b7a5424a4a compiler/typecheck/TcType.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcType.lhs b/compiler/typecheck/TcType.lhs index 6c14b4b..ffd3e07 100644 --- a/compiler/typecheck/TcType.lhs +++ b/compiler/typecheck/TcType.lhs @@ -1442,7 +1442,7 @@ isFFIExportResultTy ty = checkRepTyCon legalFEResultTyCon ty empty isFFIDynTy :: Type -> Type -> Validity -- The type in a foreign import dynamic must be Ptr, FunPtr, or a newtype of -- either, and the wrapped function type must be equal to the given type. --- We assume that all types have been run through normalizeFfiType, so we don't +-- We assume that all types have been run through normaliseFfiType, so we don't -- need to worry about expanding newtypes here. isFFIDynTy expected ty -- Note [Foreign import dynamic] From git at git.haskell.org Sat Oct 25 00:27:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 00:27:09 +0000 (UTC) Subject: [commit: ghc] master: Pass in CXX to libffi's configure script. (0855b24) Message-ID: <20141025002709.E288E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0855b249aba370e285c866d04ce7e4c1183311b9/ghc >--------------------------------------------------------------- commit 0855b249aba370e285c866d04ce7e4c1183311b9 Author: Gintautas Miliauskas Date: Fri Oct 24 19:27:05 2014 -0500 Pass in CXX to libffi's configure script. Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D370 GHC Trac Issues: #9720 >--------------------------------------------------------------- 0855b249aba370e285c866d04ce7e4c1183311b9 libffi/ghc.mk | 1 + 1 file changed, 1 insertion(+) diff --git a/libffi/ghc.mk b/libffi/ghc.mk index 4e177d2..ec37f0c 100644 --- a/libffi/ghc.mk +++ b/libffi/ghc.mk @@ -90,6 +90,7 @@ $(libffi_STAMP_CONFIGURE): $(TOUCH_DEP) $(LIBFFI_PATH_MANGLE) \ cd build && \ CC=$(CC_STAGE1) \ + CXX=$(CC_STAGE1) \ LD=$(LD) \ AR=$(AR_STAGE1) \ NM=$(NM) \ From git at git.haskell.org Sat Oct 25 10:27:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 10:27:09 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Make travis happy (d059438) Message-ID: <20141025102709.EB6293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/d059438d498bee57acb47205c08f22fc45e96f13/ghc >--------------------------------------------------------------- commit d059438d498bee57acb47205c08f22fc45e96f13 Author: Joachim Breitner Date: Tue Oct 7 13:37:23 2014 +0200 Make travis happy >--------------------------------------------------------------- d059438d498bee57acb47205c08f22fc45e96f13 libraries/base/GHC/Event/Manager.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/Event/Manager.hs b/libraries/base/GHC/Event/Manager.hs index 2041379..29edd97 100644 --- a/libraries/base/GHC/Event/Manager.hs +++ b/libraries/base/GHC/Event/Manager.hs @@ -167,10 +167,10 @@ newDefaultBackend = error "no back end for this platform" -- | Create a new event manager. new :: Bool -> IO EventManager -new oneShot = newWith oneShot =<< newDefaultBackend +new isOneShot = newWith isOneShot =<< newDefaultBackend newWith :: Bool -> Backend -> IO EventManager -newWith oneShot be = do +newWith isOneShot be = do iofds <- fmap (listArray (0, callbackArraySize-1)) $ replicateM callbackArraySize (newMVar =<< IT.new 8) ctrl <- newControl False @@ -187,7 +187,7 @@ newWith oneShot be = do , emState = state , emUniqueSource = us , emControl = ctrl - , emOneShot = oneShot + , emOneShot = isOneShot , emLock = lockVar } registerControlFd mgr (controlReadFd ctrl) evtRead From git at git.haskell.org Sat Oct 25 10:27:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 10:27:12 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Add oneShot demo file (5b531c6) Message-ID: <20141025102712.DA30A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/5b531c6b250b76ba779c5aee193c824c0ac1857c/ghc >--------------------------------------------------------------- commit 5b531c6b250b76ba779c5aee193c824c0ac1857c Author: Joachim Breitner Date: Mon Oct 6 23:04:02 2014 +0200 Add oneShot demo file (if you remove {-# GHC_OPTIONS -fno-call-arity #-} then both functions have the same Core). Obviously, this patch is not meant to be merged. >--------------------------------------------------------------- 5b531c6b250b76ba779c5aee193c824c0ac1857c OneShotTest.hs | 19 +++++++++++++++++++ 1 file changed, 19 insertions(+) diff --git a/OneShotTest.hs b/OneShotTest.hs new file mode 100644 index 0000000..852450e --- /dev/null +++ b/OneShotTest.hs @@ -0,0 +1,19 @@ +{-# GHC_OPTIONS -fno-call-arity #-} + +module OneShotTest (fooA, fooB) where + +import GHC.Prim (oneShot) + +foldlA, foldlB :: (x -> a -> a) -> a -> [x] -> a + +foldlA k a xs = foldr (\v f a -> f (v `k` a)) id xs a + +foldlB k a xs = foldr (\v f -> oneShot (\ a -> f (v `k` a))) id xs a + +f :: Int -> Bool +f 0 = True +f 1 = False +{-# NOINLINE f #-} + +fooA = foldlA (+) 0 . filter f +fooB = foldlB (+) 0 . filter f From git at git.haskell.org Sat Oct 25 10:27:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 10:27:15 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Add GHC.Prim.oneShot (955d9f5) Message-ID: <20141025102715.6E1A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/955d9f53b6c934585a90423dfc95d86d8a129908/ghc >--------------------------------------------------------------- commit 955d9f53b6c934585a90423dfc95d86d8a129908 Author: Joachim Breitner Date: Sun Jan 26 11:36:23 2014 +0000 Add GHC.Prim.oneShot Conflicts: compiler/basicTypes/MkId.lhs >--------------------------------------------------------------- 955d9f53b6c934585a90423dfc95d86d8a129908 compiler/basicTypes/MkId.lhs | 17 +++++++++++++++-- compiler/prelude/PrelNames.lhs | 3 ++- 2 files changed, 17 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index bf1c199..05dcdd5 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -135,7 +135,8 @@ ghcPrimIds seqId, magicDictId, coerceId, - proxyHashId + proxyHashId, + oneShotId ] \end{code} @@ -1016,7 +1017,7 @@ another gun with which to shoot yourself in the foot. \begin{code} lazyIdName, unsafeCoerceName, nullAddrName, seqName, realWorldName, voidPrimIdName, coercionTokenName, - magicDictName, coerceName, proxyName, dollarName :: Name + 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 @@ -1028,6 +1029,7 @@ magicDictName = mkWiredInIdName gHC_PRIM (fsLit "magicDict") magicDict coerceName = mkWiredInIdName gHC_PRIM (fsLit "coerce") coerceKey coerceId proxyName = mkWiredInIdName gHC_PRIM (fsLit "proxy#") proxyHashKey proxyHashId dollarName = mkWiredInIdName gHC_BASE (fsLit "$") dollarIdKey dollarId +oneShotName = mkWiredInIdName gHC_PRIM (fsLit "oneShot") oneShotKey oneShotId \end{code} \begin{code} @@ -1119,6 +1121,17 @@ lazyId = pcMiscPrelId lazyIdName ty info info = noCafIdInfo ty = mkForAllTys [alphaTyVar] (mkFunTy alphaTy alphaTy) +oneShotId :: Id +oneShotId = pcMiscPrelId oneShotName ty info + where + info = noCafIdInfo `setInlinePragInfo` alwaysInlinePragma + `setUnfoldingInfo` mkCompulsoryUnfolding rhs + ty = mkForAllTys [alphaTyVar, betaTyVar] (mkFunTy fun_ty fun_ty) + fun_ty = mkFunTy alphaTy betaTy + [body, x] = mkTemplateLocals [fun_ty, alphaTy] + x' = setOneShotLambda x + rhs = mkLams [alphaTyVar, betaTyVar, body, x'] $ Var body `App` Var x + -------------------------------------------------------------------------------- magicDictId :: Id -- See Note [magicDictId magic] diff --git a/compiler/prelude/PrelNames.lhs b/compiler/prelude/PrelNames.lhs index e053b11..e2ade33 100644 --- a/compiler/prelude/PrelNames.lhs +++ b/compiler/prelude/PrelNames.lhs @@ -1682,10 +1682,11 @@ rootMainKey, runMainKey :: Unique rootMainKey = mkPreludeMiscIdUnique 101 runMainKey = mkPreludeMiscIdUnique 102 -thenIOIdKey, lazyIdKey, assertErrorIdKey :: Unique +thenIOIdKey, lazyIdKey, assertErrorIdKey, oneShotKey :: Unique thenIOIdKey = mkPreludeMiscIdUnique 103 lazyIdKey = mkPreludeMiscIdUnique 104 assertErrorIdKey = mkPreludeMiscIdUnique 105 +oneShotKey = mkPreludeMiscIdUnique 106 breakpointIdKey, breakpointCondIdKey, breakpointAutoIdKey, breakpointJumpIdKey, breakpointCondJumpIdKey, From git at git.haskell.org Sat Oct 25 10:27:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 10:27:18 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Use oneShot in the definition of foldl etc. (6f101d2) Message-ID: <20141025102718.0481C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/6f101d20805fb52de0423bc8beab373b94bd4a7d/ghc >--------------------------------------------------------------- commit 6f101d20805fb52de0423bc8beab373b94bd4a7d Author: Joachim Breitner Date: Sat Oct 25 12:27:06 2014 +0200 Use oneShot in the definition of foldl etc. >--------------------------------------------------------------- 6f101d20805fb52de0423bc8beab373b94bd4a7d libraries/base/Data/OldList.hs | 5 +++-- libraries/base/GHC/List.lhs | 6 +++--- 2 files changed, 6 insertions(+), 5 deletions(-) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index 0e6709e..75fba35 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -499,7 +499,8 @@ 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) @@ -1058,7 +1059,7 @@ unfoldr f b0 = build (\c n -> -- | A strict version of 'foldl'. foldl' :: forall a b . (b -> a -> b) -> b -> [a] -> b -foldl' k z0 xs = foldr (\(v::a) (fn::b->b) (z::b) -> z `seq` fn (k z v)) (id :: b -> b) xs z0 +foldl' k z0 xs = foldr (\(v::a) (fn::b->b) -> oneShot (\(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 diff --git a/libraries/base/GHC/List.lhs b/libraries/base/GHC/List.lhs index 2d01678..c7a0cb3 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -186,7 +186,7 @@ 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 +foldl k z0 xs = foldr (\(v::a) (fn::b->b) -> oneShot (\(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 @@ -221,7 +221,7 @@ 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') {-# INLINE [0] constScanl #-} constScanl :: a -> b -> a @@ -258,7 +258,7 @@ 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' `seq` b' `c` g b' +scanlFB' f c = \b g -> oneShot (\x -> let b' = f x b in b' `seq` b' `c` g b') {-# INLINE [0] flipSeqScanl' #-} flipSeqScanl' :: a -> b -> a From git at git.haskell.org Sat Oct 25 10:27:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 10:27:20 +0000 (UTC) Subject: [commit: ghc] wip/oneShot's head updated: Use oneShot in the definition of foldl etc. (6f101d2) Message-ID: <20141025102720.AD53C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/oneShot' now includes: 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. 955d9f5 Add GHC.Prim.oneShot 5b531c6 Add oneShot demo file d059438 Make travis happy 6f101d2 Use oneShot in the definition of foldl etc. From git at git.haskell.org Sat Oct 25 12:58:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 12:58:30 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Avoid inlining oneShot in unfoldings (16066a1) Message-ID: <20141025125830.DBD2F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/16066a165dd7245be58d0fbee265e13fb21e2aed/ghc >--------------------------------------------------------------- commit 16066a165dd7245be58d0fbee265e13fb21e2aed Author: Joachim Breitner Date: Sat Oct 25 14:46:27 2014 +0200 Avoid inlining oneShot in unfoldings >--------------------------------------------------------------- 16066a165dd7245be58d0fbee265e13fb21e2aed 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 05dcdd5..31cd426 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -1124,8 +1124,8 @@ lazyId = pcMiscPrelId lazyIdName ty info oneShotId :: Id oneShotId = pcMiscPrelId oneShotName ty info where - info = noCafIdInfo `setInlinePragInfo` alwaysInlinePragma - `setUnfoldingInfo` mkCompulsoryUnfolding rhs + info = noCafIdInfo -- `setInlinePragInfo` alwaysInlinePragma + `setUnfoldingInfo` mkWwInlineRule rhs 1 ty = mkForAllTys [alphaTyVar, betaTyVar] (mkFunTy fun_ty fun_ty) fun_ty = mkFunTy alphaTy betaTy [body, x] = mkTemplateLocals [fun_ty, alphaTy] From git at git.haskell.org Sat Oct 25 14:07:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 14:07:41 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Inline foldl' (6949f86) Message-ID: <20141025140741.2EBF13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/6949f86a9401156999230c7d016fbcd4ce1c69b4/ghc >--------------------------------------------------------------- commit 6949f86a9401156999230c7d016fbcd4ce1c69b4 Author: Joachim Breitner Date: Sat Oct 25 16:07:35 2014 +0200 Inline foldl' (otherwise the oneShot gets lost in the unfolding in the interface) >--------------------------------------------------------------- 6949f86a9401156999230c7d016fbcd4ce1c69b4 libraries/base/Data/OldList.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index 75fba35..b207b5e 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -1059,6 +1059,7 @@ unfoldr f b0 = build (\c n -> -- | A strict version of 'foldl'. foldl' :: forall a b . (b -> a -> b) -> b -> [a] -> b +{-# INLINE foldl' #-} foldl' k z0 xs = foldr (\(v::a) (fn::b->b) -> oneShot (\(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! From git at git.haskell.org Sat Oct 25 14:12:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 14:12:43 +0000 (UTC) Subject: [commit: ghc] master: `M-x delete-trailing-whitespace` & `M-x untabify` (7b59db2) Message-ID: <20141025141243.3E0A93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7b59db21fd85515f47d0cbc8712538559b25633e/ghc >--------------------------------------------------------------- commit 7b59db21fd85515f47d0cbc8712538559b25633e Author: Herbert Valerio Riedel Date: Sat Oct 25 16:11:21 2014 +0200 `M-x delete-trailing-whitespace` & `M-x untabify` This removes all remaining tabs from `base`'s source code >--------------------------------------------------------------- 7b59db21fd85515f47d0cbc8712538559b25633e libraries/base/GHC/Arr.lhs | 14 +++++++------- libraries/base/GHC/Exception.lhs | 4 ++-- libraries/base/GHC/Float.lhs | 6 +++--- libraries/base/GHC/IO/Buffer.hs | 16 ++++++++-------- libraries/base/GHC/IO/Encoding/Iconv.hs | 22 +++++++++++----------- libraries/base/GHC/Num.lhs | 2 +- libraries/base/GHC/Real.lhs | 4 ++-- libraries/base/GHC/TopHandler.lhs | 8 ++++---- libraries/base/System/Mem/StableName.hs | 12 ++++++------ libraries/base/System/Mem/Weak.hs | 26 +++++++++++++------------- libraries/base/Text/Show/Functions.hs | 4 ++-- 11 files changed, 59 insertions(+), 59 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 7b59db21fd85515f47d0cbc8712538559b25633e From git at git.haskell.org Sat Oct 25 14:53:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 14:53:42 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Use oneShot in the definition of foldl etc. (6d5852a) Message-ID: <20141025145342.D343A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/6d5852a62c4c3e4343ad5316bc0ea00a2a7a7559/ghc >--------------------------------------------------------------- commit 6d5852a62c4c3e4343ad5316bc0ea00a2a7a7559 Author: Joachim Breitner Date: Sat Oct 25 12:27:06 2014 +0200 Use oneShot in the definition of foldl etc. >--------------------------------------------------------------- 6d5852a62c4c3e4343ad5316bc0ea00a2a7a7559 libraries/base/Data/OldList.hs | 5 +++-- libraries/base/GHC/List.lhs | 6 +++--- 2 files changed, 6 insertions(+), 5 deletions(-) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index 0e6709e..75fba35 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -499,7 +499,8 @@ 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) @@ -1058,7 +1059,7 @@ unfoldr f b0 = build (\c n -> -- | A strict version of 'foldl'. foldl' :: forall a b . (b -> a -> b) -> b -> [a] -> b -foldl' k z0 xs = foldr (\(v::a) (fn::b->b) (z::b) -> z `seq` fn (k z v)) (id :: b -> b) xs z0 +foldl' k z0 xs = foldr (\(v::a) (fn::b->b) -> oneShot (\(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 diff --git a/libraries/base/GHC/List.lhs b/libraries/base/GHC/List.lhs index 2d01678..c7a0cb3 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -186,7 +186,7 @@ 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 +foldl k z0 xs = foldr (\(v::a) (fn::b->b) -> oneShot (\(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 @@ -221,7 +221,7 @@ 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') {-# INLINE [0] constScanl #-} constScanl :: a -> b -> a @@ -258,7 +258,7 @@ 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' `seq` b' `c` g b' +scanlFB' f c = \b g -> oneShot (\x -> let b' = f x b in b' `seq` b' `c` g b') {-# INLINE [0] flipSeqScanl' #-} flipSeqScanl' :: a -> b -> a From git at git.haskell.org Sat Oct 25 14:53:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 14:53:45 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Add oneShot demo file (3f6aa43) Message-ID: <20141025145345.B80E83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/3f6aa436bd21711ba315b715b64389b543cb8044/ghc >--------------------------------------------------------------- commit 3f6aa436bd21711ba315b715b64389b543cb8044 Author: Joachim Breitner Date: Mon Oct 6 23:04:02 2014 +0200 Add oneShot demo file (if you remove {-# GHC_OPTIONS -fno-call-arity #-} then both functions have the same Core). Obviously, this patch is not meant to be merged. >--------------------------------------------------------------- 3f6aa436bd21711ba315b715b64389b543cb8044 OneShotTest.hs | 22 ++++++++++++++++++++++ 1 file changed, 22 insertions(+) diff --git a/OneShotTest.hs b/OneShotTest.hs new file mode 100644 index 0000000..b595285 --- /dev/null +++ b/OneShotTest.hs @@ -0,0 +1,22 @@ +{-# OPTIONS_GHC -fno-call-arity #-} + +module OneShotTest (foldlB, foldlA, fooA, fooB, fooC) where + +import GHC.Prim (oneShot) + +foldlA, foldlB :: (x -> a -> a) -> a -> [x] -> a + +foldlA k a xs = foldr (\v f a -> f (v `k` a)) id xs a +{-# INLINEABLE foldlA #-} + +foldlB k a xs = foldr (\v f -> oneShot (\ a -> f (v `k` a))) id xs a +{-# INLINEABLE foldlB #-} + +f :: Int -> Bool +f 0 = True +f 1 = False +{-# NOINLINE f #-} + +fooA = foldlA (+) 0 . filter f +fooB = foldlB (+) 0 . filter f +fooC = foldl (+) 0 . filter f From git at git.haskell.org Sat Oct 25 14:53:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 14:53:48 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Hack to prevent oneShot from being inlined when simplifying unfoldings (8dfc9b0) Message-ID: <20141025145348.559073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/8dfc9b0809359011c4d25761ad5278eab1372388/ghc >--------------------------------------------------------------- commit 8dfc9b0809359011c4d25761ad5278eab1372388 Author: Joachim Breitner Date: Sat Oct 25 16:45:27 2014 +0200 Hack to prevent oneShot from being inlined when simplifying unfoldings >--------------------------------------------------------------- 8dfc9b0809359011c4d25761ad5278eab1372388 compiler/basicTypes/MkId.lhs | 2 +- compiler/simplCore/CoreMonad.lhs | 7 +++++-- compiler/simplCore/SimplCore.lhs | 3 ++- compiler/simplCore/SimplUtils.lhs | 17 ++++++++++++++--- 4 files changed, 22 insertions(+), 7 deletions(-) diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index 05dcdd5..360c06d 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -30,7 +30,7 @@ module MkId ( wiredInIds, ghcPrimIds, unsafeCoerceName, unsafeCoerceId, realWorldPrimId, voidPrimId, voidArgId, - nullAddrId, seqId, lazyId, lazyIdKey, + nullAddrId, seqId, lazyId, lazyIdKey, oneShotId, coercionTokenId, magicDictId, coerceId, -- Re-export error Ids diff --git a/compiler/simplCore/CoreMonad.lhs b/compiler/simplCore/CoreMonad.lhs index 8d2d3bf..8c1e322 100644 --- a/compiler/simplCore/CoreMonad.lhs +++ b/compiler/simplCore/CoreMonad.lhs @@ -382,19 +382,22 @@ data SimplifierMode -- See comments in SimplMonad , sm_inline :: Bool -- Whether inlining is enabled , sm_case_case :: Bool -- Whether case-of-case is enabled , sm_eta_expand :: Bool -- Whether eta-expansion is enabled + , sm_in_rule :: Bool -- Whether we are simplified the RHS of a rule (do not inline stuff that would not survive the interface) } instance Outputable SimplifierMode where ppr (SimplMode { sm_phase = p, sm_names = ss , sm_rules = r, sm_inline = i - , sm_eta_expand = eta, sm_case_case = cc }) + , sm_eta_expand = eta, sm_case_case = cc + , sm_in_rule = ir }) = ptext (sLit "SimplMode") <+> braces ( sep [ ptext (sLit "Phase =") <+> ppr p <+> brackets (text (concat $ intersperse "," ss)) <> comma , pp_flag i (sLit "inline") <> comma , pp_flag r (sLit "rules") <> comma , pp_flag eta (sLit "eta-expand") <> comma - , pp_flag cc (sLit "case-of-case") ]) + , pp_flag cc (sLit "case-of-case") <> comma + , pp_flag ir (sLit "in-rule") ]) where pp_flag f s = ppUnless f (ptext (sLit "no")) <+> ptext s \end{code} diff --git a/compiler/simplCore/SimplCore.lhs b/compiler/simplCore/SimplCore.lhs index 2a70dcf..c2fba8b 100644 --- a/compiler/simplCore/SimplCore.lhs +++ b/compiler/simplCore/SimplCore.lhs @@ -140,7 +140,8 @@ getCoreToDo dflags , sm_rules = rules_on , sm_eta_expand = eta_expand_on , sm_inline = True - , sm_case_case = True } + , sm_case_case = True + , sm_in_rule = False} simpl_phase phase names iter = CoreDoPasses diff --git a/compiler/simplCore/SimplUtils.lhs b/compiler/simplCore/SimplUtils.lhs index 1cfba43..c450ad9 100644 --- a/compiler/simplCore/SimplUtils.lhs +++ b/compiler/simplCore/SimplUtils.lhs @@ -47,6 +47,7 @@ import CoreArity import CoreUnfold import Name import Id +import MkId (oneShotId) import Var import Demand import SimplMonad @@ -535,7 +536,8 @@ simplEnvForGHCi dflags , sm_rules = rules_on , sm_inline = False , sm_eta_expand = eta_expand_on - , sm_case_case = True } + , sm_case_case = True + , sm_in_rule = False } where rules_on = gopt Opt_EnableRewriteRules dflags eta_expand_on = gopt Opt_DoLambdaEtaExpansion dflags @@ -547,7 +549,8 @@ updModeForStableUnfoldings :: Activation -> SimplifierMode -> SimplifierMode updModeForStableUnfoldings inline_rule_act current_mode = current_mode { sm_phase = phaseFromActivation inline_rule_act , sm_inline = True - , sm_eta_expand = False } + , sm_eta_expand = False + , sm_in_rule = True} -- For sm_rules, just inherit; sm_rules might be "off" -- because of -fno-enable-rewrite-rules where @@ -672,8 +675,16 @@ mark it 'demanded', so when the RHS is simplified, it'll get an ArgOf continuation. \begin{code} +-- Debugging HACK activeUnfolding :: SimplEnv -> Id -> Bool -activeUnfolding env +activeUnfolding env id + | sm_in_rule (getMode env) + , id == oneShotId + = False + | otherwise = activeUnfolding' env id + +activeUnfolding' :: SimplEnv -> Id -> Bool +activeUnfolding' env | not (sm_inline mode) = active_unfolding_minimal | otherwise = case sm_phase mode of InitialPhase -> active_unfolding_gentle From git at git.haskell.org Sat Oct 25 14:53:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 14:53:50 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Make travis happy (4a84e61) Message-ID: <20141025145350.E57933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/4a84e61357540062e72f5c844e8ecb4e4c3986ac/ghc >--------------------------------------------------------------- commit 4a84e61357540062e72f5c844e8ecb4e4c3986ac Author: Joachim Breitner Date: Tue Oct 7 13:37:23 2014 +0200 Make travis happy >--------------------------------------------------------------- 4a84e61357540062e72f5c844e8ecb4e4c3986ac libraries/base/GHC/Event/Manager.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/Event/Manager.hs b/libraries/base/GHC/Event/Manager.hs index 2041379..29edd97 100644 --- a/libraries/base/GHC/Event/Manager.hs +++ b/libraries/base/GHC/Event/Manager.hs @@ -167,10 +167,10 @@ newDefaultBackend = error "no back end for this platform" -- | Create a new event manager. new :: Bool -> IO EventManager -new oneShot = newWith oneShot =<< newDefaultBackend +new isOneShot = newWith isOneShot =<< newDefaultBackend newWith :: Bool -> Backend -> IO EventManager -newWith oneShot be = do +newWith isOneShot be = do iofds <- fmap (listArray (0, callbackArraySize-1)) $ replicateM callbackArraySize (newMVar =<< IT.new 8) ctrl <- newControl False @@ -187,7 +187,7 @@ newWith oneShot be = do , emState = state , emUniqueSource = us , emControl = ctrl - , emOneShot = oneShot + , emOneShot = isOneShot , emLock = lockVar } registerControlFd mgr (controlReadFd ctrl) evtRead From git at git.haskell.org Sat Oct 25 14:53:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 14:53:53 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Avoid inlining oneShot in unfoldings (63a5d69) Message-ID: <20141025145353.7A9AD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/63a5d69d7893749664c4beb955af64efc5bba982/ghc >--------------------------------------------------------------- commit 63a5d69d7893749664c4beb955af64efc5bba982 Author: Joachim Breitner Date: Sat Oct 25 14:46:27 2014 +0200 Avoid inlining oneShot in unfoldings >--------------------------------------------------------------- 63a5d69d7893749664c4beb955af64efc5bba982 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 360c06d..b074c93 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -1124,8 +1124,8 @@ lazyId = pcMiscPrelId lazyIdName ty info oneShotId :: Id oneShotId = pcMiscPrelId oneShotName ty info where - info = noCafIdInfo `setInlinePragInfo` alwaysInlinePragma - `setUnfoldingInfo` mkCompulsoryUnfolding rhs + info = noCafIdInfo -- `setInlinePragInfo` alwaysInlinePragma + `setUnfoldingInfo` mkWwInlineRule rhs 1 ty = mkForAllTys [alphaTyVar, betaTyVar] (mkFunTy fun_ty fun_ty) fun_ty = mkFunTy alphaTy betaTy [body, x] = mkTemplateLocals [fun_ty, alphaTy] From git at git.haskell.org Sat Oct 25 14:53:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 25 Oct 2014 14:53:56 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Inline foldl' (e0c0c89) Message-ID: <20141025145356.1A7993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/e0c0c89ba5054e9304ca1342b73f589c43a90d61/ghc >--------------------------------------------------------------- commit e0c0c89ba5054e9304ca1342b73f589c43a90d61 Author: Joachim Breitner Date: Sat Oct 25 16:07:35 2014 +0200 Inline foldl' (otherwise the oneShot gets lost in the unfolding in the interface) >--------------------------------------------------------------- e0c0c89ba5054e9304ca1342b73f589c43a90d61 libraries/base/Data/OldList.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index 75fba35..b207b5e 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -1059,6 +1059,7 @@ unfoldr f b0 = build (\c n -> -- | A strict version of 'foldl'. foldl' :: forall a b . (b -> a -> b) -> b -> [a] -> b +{-# INLINE foldl' #-} foldl' k z0 xs = foldr (\(v::a) (fn::b->b) -> oneShot (\(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! From git at git.haskell.org Sun Oct 26 05:47:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 26 Oct 2014 05:47:07 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Fix outdated output for T5979/safePkg01 (a3312c3) Message-ID: <20141026054707.15F0A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a3312c3a8d96c52a7d21aa2341de8deab564d910/ghc >--------------------------------------------------------------- commit a3312c3a8d96c52a7d21aa2341de8deab564d910 Author: Austin Seipp Date: Sun Oct 26 00:45:56 2014 -0500 testsuite: Fix outdated output for T5979/safePkg01 Looks like it was broken in aa4799534225. Signed-off-by: Austin Seipp >--------------------------------------------------------------- a3312c3a8d96c52a7d21aa2341de8deab564d910 testsuite/tests/ghci/scripts/T5979.stderr | 6 +++--- testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout | 6 +++--- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/testsuite/tests/ghci/scripts/T5979.stderr b/testsuite/tests/ghci/scripts/T5979.stderr index c59c2e2..c2869b0 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_GjLVjHaAO8fEGf8lChbngr) - Control.Monad.Trans.Class (from transformers-0.4.1.0 at trans_GjLVjHaAO8fEGf8lChbngr) - Control.Monad.Trans.Cont (from transformers-0.4.1.0 at trans_GjLVjHaAO8fEGf8lChbngr) + Control.Monad.Trans.State (from transformers-0.4.1.0 at trans_5jw4w9yTgmZ89ByuixDAKP) + Control.Monad.Trans.Class (from transformers-0.4.1.0 at trans_5jw4w9yTgmZ89ByuixDAKP) + Control.Monad.Trans.Cont (from transformers-0.4.1.0 at trans_5jw4w9yTgmZ89ByuixDAKP) diff --git a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout index 7ff5e24..7ce7704 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 at array_5q713e1nmXtAgNRa542ahu +package dependencies: array-0.5.0.1 at array_GX4NwjS8xZkC2ZPtjgwhnz trusted: trustworthy require own pkg trusted: False M_SafePkg7 -package dependencies: array-0.5.0.1 at array_5q713e1nmXtAgNRa542ahu +package dependencies: array-0.5.0.1 at array_GX4NwjS8xZkC2ZPtjgwhnz trusted: safe require own pkg trusted: False M_SafePkg8 -package dependencies: array-0.5.0.1 at array_5q713e1nmXtAgNRa542ahu +package dependencies: array-0.5.0.1 at array_GX4NwjS8xZkC2ZPtjgwhnz trusted: trustworthy require own pkg trusted: False From git at git.haskell.org Sun Oct 26 08:45:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 26 Oct 2014 08:45:49 +0000 (UTC) Subject: [commit: ghc] master: Add new `Data.Bifunctor` module (re #9682) (0a290ca) Message-ID: <20141026084549.DAD763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0a290ca0ad599e40ca15a60cc988640f1cfcb4c2/ghc >--------------------------------------------------------------- commit 0a290ca0ad599e40ca15a60cc988640f1cfcb4c2 Author: Herbert Valerio Riedel Date: Sun Oct 26 08:49:38 2014 +0100 Add new `Data.Bifunctor` module (re #9682) This adds the module `Data.Bifunctor` providing the `Bifunctor(bimap,first,second)` class and a couple of instances This module and the class were previously exported by the `bifunctors` package. In contrast to the original module all `INLINE` pragmas have been removed. Reviewed By: ekmett, austin, dolio Differential Revision: https://phabricator.haskell.org/D336 >--------------------------------------------------------------- 0a290ca0ad599e40ca15a60cc988640f1cfcb4c2 libraries/base/Data/Bifunctor.hs | 103 +++++++++++++++++++++++++++++++++++++++ libraries/base/base.cabal | 1 + libraries/base/changelog.md | 3 ++ 3 files changed, 107 insertions(+) diff --git a/libraries/base/Data/Bifunctor.hs b/libraries/base/Data/Bifunctor.hs new file mode 100644 index 0000000..4c84f1c --- /dev/null +++ b/libraries/base/Data/Bifunctor.hs @@ -0,0 +1,103 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE NoImplicitPrelude #-} + +----------------------------------------------------------------------------- +-- | +-- Module : Data.Bifunctor +-- Copyright : (C) 2008-2014 Edward Kmett, +-- License : BSD-style (see the file LICENSE) +-- +-- Maintainer : libraries at haskell.org +-- Stability : provisional +-- Portability : portable +-- +-- /Since: 4.8.0.0/ +---------------------------------------------------------------------------- +module Data.Bifunctor + ( Bifunctor(..) + ) where + +import Control.Applicative ( Const(..) ) +import Data.Either ( Either(..) ) +import GHC.Base ( (.), id ) + +-- | Formally, the class 'Bifunctor' represents a bifunctor +-- from @Hask@ -> @Hask at . +-- +-- Intuitively it is a bifunctor where both the first and second +-- arguments are covariant. +-- +-- You can define a 'Bifunctor' by either defining 'bimap' or by +-- defining both 'first' and 'second'. +-- +-- If you supply 'bimap', you should ensure that: +-- +-- @'bimap' 'id' 'id' ? 'id'@ +-- +-- If you supply 'first' and 'second', ensure: +-- +-- @ +-- 'first' 'id' ? 'id' +-- 'second' 'id' ? 'id' +-- @ +-- +-- If you supply both, you should also ensure: +-- +-- @'bimap' f g ? 'first' f '.' 'second' g@ +-- +-- These ensure by parametricity: +-- +-- @ +-- 'bimap' (f '.' g) (h '.' i) ? 'bimap' f h '.' 'bimap' g i +-- 'first' (f '.' g) ? 'first' f '.' 'first' g +-- 'second' (f '.' g) ? 'second' f '.' 'second' g +-- @ +-- +-- /Since: 4.8.0.0/ +class Bifunctor p where + {-# MINIMAL bimap | first, second #-} + + -- | Map over both arguments at the same time. + -- + -- @'bimap' f g ? 'first' f '.' 'second' g@ + bimap :: (a -> b) -> (c -> d) -> p a c -> p b d + bimap f g = first f . second g + + -- | Map covariantly over the first argument. + -- + -- @'first' f ? 'bimap' f 'id'@ + first :: (a -> b) -> p a c -> p b c + first f = bimap f id + + -- | Map covariantly over the second argument. + -- + -- @'second' ? 'bimap' 'id'@ + second :: (b -> c) -> p a b -> p a c + second = bimap id + + +instance Bifunctor (,) where + bimap f g ~(a, b) = (f a, g b) + +instance Bifunctor ((,,) x1) where + bimap f g ~(x1, a, b) = (x1, f a, g b) + +instance Bifunctor ((,,,) x1 x2) where + bimap f g ~(x1, x2, a, b) = (x1, x2, f a, g b) + +instance Bifunctor ((,,,,) x1 x2 x3) where + bimap f g ~(x1, x2, x3, a, b) = (x1, x2, x3, f a, g b) + +instance Bifunctor ((,,,,,) x1 x2 x3 x4) where + bimap f g ~(x1, x2, x3, x4, a, b) = (x1, x2, x3, x4, f a, g b) + +instance Bifunctor ((,,,,,,) x1 x2 x3 x4 x5) where + bimap f g ~(x1, x2, x3, x4, x5, a, b) = (x1, x2, x3, x4, x5, f a, g b) + + +instance Bifunctor Either where + bimap f _ (Left a) = Left (f a) + bimap _ g (Right b) = Right (g b) + +instance Bifunctor Const where + bimap f _ (Const a) = Const (f a) diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal index 45e674f..957053d 100644 --- a/libraries/base/base.cabal +++ b/libraries/base/base.cabal @@ -117,6 +117,7 @@ Library Control.Monad.ST.Strict Control.Monad.ST.Unsafe Control.Monad.Zip + Data.Bifunctor Data.Bits Data.Bool Data.Char diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index ed93b46..76fe87a 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -84,6 +84,9 @@ * Remove deprecated `Data.OldTypeable` (#9639) + * New module `Data.Bifunctor` providing the `Bifunctor(bimap,first,second)` + class (previously defined in `bifunctors` package) (#9682) + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 From git at git.haskell.org Mon Oct 27 04:13:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 04:13:31 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins: Merge remote-tracking branch 'origin/wip/new-flatten-skolems-Aug14' into wip/tc-plugins (1313ef8) Message-ID: <20141027041331.CA32A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc-plugins Link : http://ghc.haskell.org/trac/ghc/changeset/1313ef893d8813ba9a814258365aaa28faa43e64/ghc >--------------------------------------------------------------- commit 1313ef893d8813ba9a814258365aaa28faa43e64 Merge: c55777e c4eb017 Author: Iavor S. Diatchki Date: Sun Oct 26 21:13:46 2014 -0700 Merge remote-tracking branch 'origin/wip/new-flatten-skolems-Aug14' into wip/tc-plugins Conflicts: compiler/typecheck/TcInteract.lhs testsuite/tests/typecheck/should_fail/ContextStack2.stderr testsuite/tests/typecheck/should_fail/FrozenErrorTests.stderr testsuite/tests/typecheck/should_run/T5751.hs >--------------------------------------------------------------- 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 1313ef893d8813ba9a814258365aaa28faa43e64 From git at git.haskell.org Mon Oct 27 04:13:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 04:13:34 +0000 (UTC) Subject: [commit: ghc] wip/tc-plugins's head updated: Merge remote-tracking branch 'origin/wip/new-flatten-skolems-Aug14' into wip/tc-plugins (1313ef8) Message-ID: <20141027041334.658573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/tc-plugins' now includes: 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 077b553 arclint: Don't complain about tabs unless it's inside the diff. 97e8f38 Comments only (instances for Proxy are lazy) 542b9c3 Revert "Basic Python 3 support for testsuite driver (Trac #9184)" 474d320 Restore spaces instead of tabs, caused by revert of Python 3 9b5d230 Check for staticclosures section in Windows linker. 39a3adf6 Fix typo in section name: no leading period. db8ebc1 ghc.mk: fix list for dll-split on GHCi-less builds 3bac93c Implement `MIN_VERSION_GLASGOW_HASKELL()` macro 2085656 rts: unrust 'libbfd' debug symbols parser 3b2757f More progress (refactoring StopAndContinue) 22a8a36 More progress 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 48e51ab More progress 4b69d96 Add a configure test for pthread_setname_np 9d55484 More progress ae0ef57 Checkpoint with each CFunEqCan having a distinct fmv 22b3649 Finally getting there cde3a77 Make Data.List.Inits fast 7e73595 Make tails a good producer (#9670) d786781 Declare official GitHub home of libraries/deepseq dae919a Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 4665087 More progress 5aee24f More progress 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 ffd19d0 More progress 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. e7988ed More progress c4eb017 Merge commit with origin/master 1313ef8 Merge remote-tracking branch 'origin/wip/new-flatten-skolems-Aug14' into wip/tc-plugins From git at git.haskell.org Mon Oct 27 09:27:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 09:27:09 +0000 (UTC) Subject: [commit: ghc] master: Optimise atomicModifyIORef' implementation (#8345) (9e2cb00) Message-ID: <20141027092709.6A5B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9e2cb00e5af9d86546f82a74c3d0382e65704d56/ghc >--------------------------------------------------------------- commit 9e2cb00e5af9d86546f82a74c3d0382e65704d56 Author: David Feuer Date: Mon Oct 27 10:21:20 2014 +0100 Optimise atomicModifyIORef' implementation (#8345) This forces the new value before installing it in the IORef. This optimisation was originally suggested by Patrick Palka and "exhibits a speedup of 1.7x (vanilla RTS) / 1.4x (threaded RTS)" according to #8345 Reviewed By: austin, simonmar Differential Revision: https://phabricator.haskell.org/D315 >--------------------------------------------------------------- 9e2cb00e5af9d86546f82a74c3d0382e65704d56 libraries/base/Data/IORef.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/base/Data/IORef.hs b/libraries/base/Data/IORef.hs index 0e5717c..2981805 100644 --- a/libraries/base/Data/IORef.hs +++ b/libraries/base/Data/IORef.hs @@ -106,9 +106,9 @@ atomicModifyIORef = GHC.IORef.atomicModifyIORef -- /Since: 4.6.0.0/ atomicModifyIORef' :: IORef a -> (a -> (a,b)) -> IO b atomicModifyIORef' ref f = do - b <- atomicModifyIORef ref - (\x -> let (a, b) = f x - in (a, a `seq` b)) + b <- atomicModifyIORef ref $ \a -> + case f a of + v@(a',_) -> a' `seq` v b `seq` return b -- | Variant of 'writeIORef' with the \"barrier to reordering\" property that From git at git.haskell.org Mon Oct 27 15:51:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 15:51:41 +0000 (UTC) Subject: [commit: ghc] master: Un-wire `Integer` type (re #9714) (0e1f0f7) Message-ID: <20141027155141.E93123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0e1f0f7d1682d77c5dbb1d2b36f57037113cf7b4/ghc >--------------------------------------------------------------- commit 0e1f0f7d1682d77c5dbb1d2b36f57037113cf7b4 Author: Herbert Valerio Riedel Date: Mon Oct 27 16:44:36 2014 +0100 Un-wire `Integer` type (re #9714) Integer is currently a wired-in type for integer-gmp. This requires replicating its inner structure in `TysWiredIn`, which makes it much harder to change Integer to a more complex representation (as e.g. needed for implementing #9281) This commit stops `Integer` being a wired-in type, and makes it known-key type instead, thereby simplifying code notably. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D351 >--------------------------------------------------------------- 0e1f0f7d1682d77c5dbb1d2b36f57037113cf7b4 compiler/coreSyn/CorePrep.lhs | 47 +++++++++++++++++++++++++++-------------- compiler/main/TidyPgm.lhs | 43 ++++++++++++++++++++++--------------- compiler/prelude/PrelNames.lhs | 22 +++++++++++-------- compiler/prelude/TysWiredIn.lhs | 38 --------------------------------- 4 files changed, 70 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 0e1f0f7d1682d77c5dbb1d2b36f57037113cf7b4 From git at git.haskell.org Mon Oct 27 15:59:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 15:59:09 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Bug #9439: Ensure that stage 0 compiler isn't affected (1f7dc1b) Message-ID: <20141027155909.39AEF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/1f7dc1bbd0f4f55cf0c7b15d7e4d2480cf2db9d1/ghc >--------------------------------------------------------------- commit 1f7dc1bbd0f4f55cf0c7b15d7e4d2480cf2db9d1 Author: Ben Gamari Date: Mon Aug 18 21:44:25 2014 -0500 Bug #9439: Ensure that stage 0 compiler isn't affected Summary: Bug #9439 will cause miscompilation of GHC's LLVM backend. Here we ensure that an affected compiler isn't used to bootstrap. Test Plan: Attempt to bootstrap GHC with an affected stage 0 compiler. Reviewers: rwbarton, austin Reviewed By: austin Subscribers: simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D159 (cherry picked from commit bbd031134a571c1020945b2548e3fc4795b5047a) >--------------------------------------------------------------- 1f7dc1bbd0f4f55cf0c7b15d7e4d2480cf2db9d1 Makefile | 7 +++++++ configure.ac | 50 ++++++++++++++++++++++++++++++++++++++++++++++++++ mk/project.mk.in | 3 +++ 3 files changed, 60 insertions(+) diff --git a/Makefile b/Makefile index 6872cb3..4145d97 100644 --- a/Makefile +++ b/Makefile @@ -44,6 +44,13 @@ endif include mk/custom-settings.mk +# Verify that stage 0 LLVM backend isn't affected by Bug #9439 if needed +ifeq "$(GHC_LLVM_AFFECTED_BY_9439)" "1" +ifneq "$(findstring -fllvm,$(GhcHcOpts) $(GhcStage1HcOpts))" "" +$(error Stage 0 compiler is affected by Bug #9439. Refusing to bootstrap with -fllvm) +endif +endif + # No need to update makefiles for these targets: REALGOALS=$(filter-out binary-dist binary-dist-prep bootstrapping-files framework-pkg clean clean_% distclean maintainer-clean show echo help test fulltest,$(MAKECMDGOALS)) diff --git a/configure.ac b/configure.ac index 8f53bdf..f455e3d 100644 --- a/configure.ac +++ b/configure.ac @@ -184,6 +184,56 @@ 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-------------------------------------------------------------------- diff --git a/mk/project.mk.in b/mk/project.mk.in index 28692d4..69ed885 100644 --- a/mk/project.mk.in +++ b/mk/project.mk.in @@ -157,3 +157,6 @@ SOLARIS_BROKEN_SHLD=@SOLARIS_BROKEN_SHLD@ # Do we have a C compiler using an LLVM back end? CC_LLVM_BACKEND = @CC_LLVM_BACKEND@ CC_CLANG_BACKEND = @CC_CLANG_BACKEND@ + +# Is the stage0 compiler affected by Bug #9439? +GHC_LLVM_AFFECTED_BY_9439 = @GHC_LLVM_AFFECTED_BY_9439@ From git at git.haskell.org Mon Oct 27 15:59:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 15:59:11 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: rts/Linker.c: declare 'deRefStablePtr' as an exported 'rts' symbol (b2f306e) Message-ID: <20141027155911.EAE733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/b2f306e24541ff750b9113a23c6dd6146e2f12c1/ghc >--------------------------------------------------------------- commit b2f306e24541ff750b9113a23c6dd6146e2f12c1 Author: Sergei Trofimovich Date: Sat Aug 23 13:11:23 2014 +0300 rts/Linker.c: declare 'deRefStablePtr' as an exported 'rts' symbol $ inplace/bin/ghc-stage2 -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output -no-user-package-db -rtsopts -optc-fno-builtin -fno-ghci-history \ testsuite/tests/ffi/should_run/T4038.hs --interactive -v0 -ignore-dot-ghci +RTS -I0.1 -RTS *Main> main : /tmp/ghc16668_0/ghc16668_5.o: unknown symbol `deRefStablePtr' The reference to 'deRefStablePtr' is generated by 'compiler/deSugar/DsForeign.lhs': the_cfun = case maybe_target of Nothing -> text "(StgClosure*)deRefStablePtr(the_stableptr)" Just hs_fn -> char '&' <> ppr hs_fn <> text "_closure" Patch fixes all broken tests using 'import wrapper': TEST="ffi013 ffi010 ffi011 ffi005 ffi020 ffi006 ffi019 fed001 T1679 T4038" Tests manifested as broken only in DYNAMIC_GHC_PROGRAMS=NO builds, where GHCi's custom linker is used instead of system's linker. Signed-off-by: Sergei Trofimovich (cherry picked from commit 104a66a461f4f89b8e5ad9c829923bb7ca8ceddb) >--------------------------------------------------------------- b2f306e24541ff750b9113a23c6dd6146e2f12c1 rts/Linker.c | 1 + 1 file changed, 1 insertion(+) diff --git a/rts/Linker.c b/rts/Linker.c index 47b4008..ceb6a4f 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1090,6 +1090,7 @@ typedef struct _RtsSymbolVal { SymI_HasProto(__word_encodeFloat) \ SymI_HasProto(stg_atomicallyzh) \ SymI_HasProto(barf) \ + SymI_HasProto(deRefStablePtr) \ SymI_HasProto(debugBelch) \ SymI_HasProto(errorBelch) \ SymI_HasProto(sysErrorBelch) \ From git at git.haskell.org Mon Oct 27 15:59:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 15:59:14 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: UNREG: fix emission of large Integer literals in C codegen (53c6dcf) Message-ID: <20141027155914.9187C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/53c6dcf7de6a57c68df52bb0efac3a4205086f73/ghc >--------------------------------------------------------------- commit 53c6dcf7de6a57c68df52bb0efac3a4205086f73 Author: Sergei Trofimovich Date: Tue Aug 26 13:07:14 2014 +0300 UNREG: fix emission of large Integer literals in C codegen Summary: On amd64/UNREG build there is many failing tests trying to deal with 'Integer' types. Looking at 'integerConversions' test I've observed invalid C code generated by GHC. Cmm code CInt a = -1; (a == -1) yields 'False' with optimisations enabled via the following C code: StgWord64 a = (StgWord32)0xFFFFffffFFFFffffu; (a == 0xFFFFffffFFFFffffu) The patch fixes it by shrinking emitted literals to required sizes: StgWord64 a = (StgWord32)0xFFFFffffu; (a == 0xFFFFffffu) Thanks to Reid Barton for tracking down and fixing the issue. Signed-off-by: Sergei Trofimovich Test Plan: validate on UNREG build (amd64, x86) Reviewers: simonmar, rwbarton, austin Subscribers: hvr, simonmar, ezyang, carter Differential Revision: https://phabricator.haskell.org/D173 (cherry picked from commit 43f1b2ecd1960fa7377cf55a2b97c66059a701ef) >--------------------------------------------------------------- 53c6dcf7de6a57c68df52bb0efac3a4205086f73 compiler/cmm/PprC.hs | 30 +++++++++++++++++++++++++++--- 1 file changed, 27 insertions(+), 3 deletions(-) diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs index 2398981..e957f3e 100644 --- a/compiler/cmm/PprC.hs +++ b/compiler/cmm/PprC.hs @@ -1214,8 +1214,9 @@ commafy xs = hsep $ punctuate comma xs pprHexVal :: Integer -> Width -> SDoc pprHexVal 0 _ = ptext (sLit "0x0") pprHexVal w rep - | w < 0 = parens (char '-' <> ptext (sLit "0x") <> go (-w) <> repsuffix rep) - | otherwise = ptext (sLit "0x") <> go w <> repsuffix rep + | w < 0 = parens (char '-' <> + ptext (sLit "0x") <> intToDoc (-w) <> repsuffix rep) + | otherwise = ptext (sLit "0x") <> intToDoc w <> repsuffix rep where -- type suffix for literals: -- Integer literals are unsigned in Cmm/C. We explicitly cast to @@ -1230,10 +1231,33 @@ pprHexVal w rep else panic "pprHexVal: Can't find a 64-bit type" repsuffix _ = char 'U' + intToDoc :: Integer -> SDoc + intToDoc i = go (truncInt i) + + -- We need to truncate value as Cmm backend does not drop + -- redundant bits to ease handling of negative values. + -- Thus the following Cmm code on 64-bit arch, like amd64: + -- CInt v; + -- v = {something}; + -- if (v == %lobits32(-1)) { ... + -- leads to the following C code: + -- StgWord64 v = (StgWord32)({something}); + -- if (v == 0xFFFFffffFFFFffffU) { ... + -- Such code is incorrect as it promotes both operands to StgWord64 + -- and the whole condition is always false. + truncInt :: Integer -> Integer + truncInt i = + case rep of + W8 -> i `rem` (2^(8 :: Int)) + W16 -> i `rem` (2^(16 :: Int)) + W32 -> i `rem` (2^(32 :: Int)) + W64 -> i `rem` (2^(64 :: Int)) + _ -> panic ("pprHexVal/truncInt: C backend can't encode " + ++ show rep ++ " literals") + go 0 = empty go w' = go q <> dig where (q,r) = w' `quotRem` 16 dig | r < 10 = char (chr (fromInteger r + ord '0')) | otherwise = char (chr (fromInteger r - 10 + ord 'a')) - From git at git.haskell.org Mon Oct 27 15:59:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 15:59:17 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: driver: pass '-fPIC' option to assembler as well (39d0cad) Message-ID: <20141027155917.444153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/39d0cad37a91591ae5be22200753206b57d0f169/ghc >--------------------------------------------------------------- commit 39d0cad37a91591ae5be22200753206b57d0f169 Author: Sergei Trofimovich Date: Wed Aug 27 22:19:52 2014 +0300 driver: pass '-fPIC' option to assembler as well Summary: Before the patch '-fPIC' was passed only to C compiler, but not to assembler itself. It led to runtime crash in GHC_DYNAMIC_PROGRAMS=YES mode on sparc32. Technical details are in 'Note [-fPIC for assembler]'. Signed-off-by: Sergei Trofimovich Test Plan: validate on sparc Reviewers: simonmar, austin, kgardas Reviewed By: austin Subscribers: simonmar, ezyang, carter Differential Revision: https://phabricator.haskell.org/D177 (cherry picked from commit a93ab43ab5f40cadbedea2f6342b93c245e91434) >--------------------------------------------------------------- 39d0cad37a91591ae5be22200753206b57d0f169 compiler/main/DriverPipeline.hs | 44 +++++++++++++++++++++++++++++++++++++++++ 1 file changed, 44 insertions(+) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index d2d2bc0..745199e 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1208,6 +1208,7 @@ runPhase (RealPhase (As with_cpp)) input_fn dflags as_prog <- whichAsProg let cmdline_include_paths = includePaths dflags + let pic_c_flags = picCCOpts dflags next_phase <- maybeMergeStub output_fn <- phaseOutputFilename next_phase @@ -1221,6 +1222,9 @@ runPhase (RealPhase (As with_cpp)) input_fn dflags = liftIO $ as_prog dflags ([ SysTools.Option ("-I" ++ p) | p <- cmdline_include_paths ] + -- See Note [-fPIC for assembler] + ++ map SysTools.Option pic_c_flags + -- We only support SparcV9 and better because V8 lacks an atomic CAS -- instruction so we have to make sure that the assembler accepts the -- instruction set. Note that the user can still override this @@ -1262,6 +1266,8 @@ runPhase (RealPhase SplitAs) _input_fn dflags osuf = objectSuf dflags split_odir = base_o ++ "_" ++ osuf ++ "_split" + let pic_c_flags = picCCOpts dflags + -- this also creates the hierarchy liftIO $ createDirectoryIfMissing True split_odir @@ -1295,6 +1301,9 @@ runPhase (RealPhase SplitAs) _input_fn dflags then [SysTools.Option "-mcpu=v9"] else []) ++ + -- See Note [-fPIC for assembler] + map SysTools.Option pic_c_flags ++ + [ SysTools.Option "-c" , SysTools.Option "-o" , SysTools.FileOption "" (split_obj n) @@ -2210,3 +2219,38 @@ haveRtsOptsFlags dflags = isJust (rtsOpts dflags) || case rtsOptsEnabled dflags of RtsOptsSafeOnly -> False _ -> True + +-- Note [-fPIC for assembler] +-- When compiling .c source file GHC's driver pipeline basically +-- does the following two things: +-- 1. ${CC} -S 'PIC_CFLAGS' source.c +-- 2. ${CC} -x assembler -c 'PIC_CFLAGS' source.S +-- +-- Why do we need to pass 'PIC_CFLAGS' both to C compiler and assembler? +-- Because on some architectures (at least sparc32) assembler also choses +-- relocation type! +-- Consider the following C module: +-- +-- /* pic-sample.c */ +-- int v; +-- void set_v (int n) { v = n; } +-- int get_v (void) { return v; } +-- +-- $ gcc -S -fPIC pic-sample.c +-- $ gcc -c pic-sample.s -o pic-sample.no-pic.o # incorrect binary +-- $ gcc -c -fPIC pic-sample.s -o pic-sample.pic.o # correct binary +-- +-- $ objdump -r -d pic-sample.pic.o > pic-sample.pic.o.od +-- $ objdump -r -d pic-sample.no-pic.o > pic-sample.no-pic.o.od +-- $ diff -u pic-sample.pic.o.od pic-sample.no-pic.o.od +-- +-- Most of architectures won't show any difference in this test, but on sparc32 +-- the following assembly snippet: +-- +-- sethi %hi(_GLOBAL_OFFSET_TABLE_-8), %l7 +-- +-- generates two kinds or relocations, only 'R_SPARC_PC22' is correct: +-- +-- 3c: 2f 00 00 00 sethi %hi(0), %l7 +-- - 3c: R_SPARC_PC22 _GLOBAL_OFFSET_TABLE_-0x8 +-- + 3c: R_SPARC_HI22 _GLOBAL_OFFSET_TABLE_-0x8 From git at git.haskell.org Mon Oct 27 15:59:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 15:59:19 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: pprC: declare extern cmm primitives as functions, not data (04e21ae) Message-ID: <20141027155919.E13C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/04e21ae3c47fba6d2f6ca0ecdbea394fbe1d881c/ghc >--------------------------------------------------------------- commit 04e21ae3c47fba6d2f6ca0ecdbea394fbe1d881c Author: Sergei Trofimovich Date: Thu Sep 4 17:50:45 2014 +0300 pprC: declare extern cmm primitives as functions, not data Summary: The commit fixes incorrect code generation of integer-gmp package on ia64 due to C prototypes mismatch. Before the patch prototypes for "foreign import prim" were: StgWord poizh[]; After the patch they became: StgFunPtr poizh(); Long story: Consider the following simple example: {-# LANGUAGE MagicHash, GHCForeignImportPrim, UnliftedFFITypes #-} module M where import GHC.Prim -- Int# foreign import prim "poizh" poi# :: Int# -> Int# Before the patch unregisterised build generated the following 'poizh' reference: EI_(poizh); /* StgWord poizh[]; */ FN_(M_poizh_entry) { // ... JMP_((W_)&poizh); } After the patch it looks this way: EF_(poizh); /* StgFunPtr poizh(); */ FN_(M_poizh_entry) { // ... JMP_((W_)&poizh); } On ia64 it leads to different relocation types being generated: incorrect one: addl r14 = @ltoffx(poizh#) ld8.mov r14 = [r14], poizh# ; r14 = address-of 'poizh#' correct one: addl r14 = @ltoff(@fptr(poizh#)), gp ; r14 = address-of-thunk 'poizh#' ld8 r14 = [r14] '@fptr(poizh#)' basically instructs assembler to creates another obect consisting of real address to 'poizh' instructions and module address. That '@fptr' object is used as a function "address" This object is different for every module referencing 'poizh' symbol. All indirect function calls expect '@fptr' object. That way call site reads real destination address and set destination module address in 'gp' register from '@fptr'. Signed-off-by: Sergei Trofimovich (cherry picked from commit e18525fae273f4c1ad8d6cbe1dea4fc074cac721) >--------------------------------------------------------------- 04e21ae3c47fba6d2f6ca0ecdbea394fbe1d881c compiler/cmm/CLabel.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs index 65c597c..991fc57 100644 --- a/compiler/cmm/CLabel.hs +++ b/compiler/cmm/CLabel.hs @@ -801,6 +801,7 @@ labelType (CmmLabel _ _ CmmClosure) = GcPtrLabel labelType (CmmLabel _ _ CmmCode) = CodeLabel labelType (CmmLabel _ _ CmmInfo) = DataLabel labelType (CmmLabel _ _ CmmEntry) = CodeLabel +labelType (CmmLabel _ _ CmmPrimCall) = CodeLabel labelType (CmmLabel _ _ CmmRetInfo) = DataLabel labelType (CmmLabel _ _ CmmRet) = CodeLabel labelType (RtsLabel (RtsSelectorInfoTable _ _)) = DataLabel From git at git.haskell.org Mon Oct 27 15:59:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 15:59:22 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix a rare parallel GC bug (29d8d32) Message-ID: <20141027155922.87B7C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/29d8d320bb772e08246cf00e88d1970f7d6b26f3/ghc >--------------------------------------------------------------- commit 29d8d320bb772e08246cf00e88d1970f7d6b26f3 Author: Simon Marlow Date: Thu Oct 23 11:12:16 2014 +0100 Fix a rare parallel GC bug When there's a conflict between two threads evacuating the same TSO, in some cases we would update the incall->tso pointer to point to the wrong copy of the TSO. This would get fixed during the next GC, but if the thread completed in the meantime, it would likely crash. We're seeing this about once per day on a heavily loaded machine (it varies a lot though). (cherry picked from commit a11f71eff15ba2706cbb2ee29aaf7350909e0d2f) >--------------------------------------------------------------- 29d8d320bb772e08246cf00e88d1970f7d6b26f3 rts/sm/Scav.c | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/rts/sm/Scav.c b/rts/sm/Scav.c index 5b1e5d0..1cc1482 100644 --- a/rts/sm/Scav.c +++ b/rts/sm/Scav.c @@ -55,7 +55,12 @@ scavengeTSO (StgTSO *tso) // update the pointer from the InCall. if (tso->bound != NULL) { - tso->bound->tso = tso; + // NB. We can't just set tso->bound->tso = tso, because this + // might be an invalid copy the TSO resulting from multiple + // threads evacuating the TSO simultaneously (see + // Evac.c:copy_tag()). Calling evacuate() on this pointer + // will ensure that we update it to point to the correct copy. + evacuate((StgClosure **)&tso->bound->tso); } saved_eager = gct->eager_promotion; From git at git.haskell.org Mon Oct 27 16:04:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 16:04:51 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: systools: fix gcc version detecton on non-english locale (7548ec8) Message-ID: <20141027160451.840A03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/7548ec859071c67d92632e4228aba74796d5d5ad/ghc >--------------------------------------------------------------- commit 7548ec859071c67d92632e4228aba74796d5d5ad Author: Sergei Trofimovich Date: Tue Sep 2 00:06:56 2014 +0300 systools: fix gcc version detecton on non-english locale Summary: ghc runs 'gcc -v' to check if we run under vanilla gcc or disaguised clang by checking for string "gcc version " But this check does not always work as gcc has that string localized via gettext mechanism: (some gcc's locale strings) be.po-msgstr "?????? gcc %s\n" da.po-msgstr "GCC version %s\n" de.po-msgstr "gcc-Version %s %s\n" el.po-msgstr "?????? gcc %s\n" ... To ping gcc to English locale we now override environment variable with 'LANGUAGE=en' value. Fixes Issue #8825 Signed-off-by: Sergei Trofimovich Test Plan: validate Reviewers: austin Reviewed By: austin Subscribers: simonmar, ezyang, carter Differential Revision: https://phabricator.haskell.org/D185 GHC Trac Issues: #8825 (cherry picked from commit 4d4d07704ee78221607a18b8118294b0aea1bac4) >--------------------------------------------------------------- 7548ec859071c67d92632e4228aba74796d5d5ad compiler/main/SysTools.lhs | 56 ++++++++++++++++++++++++++++++++++++++++++---- 1 file changed, 52 insertions(+), 4 deletions(-) diff --git a/compiler/main/SysTools.lhs b/compiler/main/SysTools.lhs index 2945911..cd9b9f5 100644 --- a/compiler/main/SysTools.lhs +++ b/compiler/main/SysTools.lhs @@ -490,6 +490,51 @@ readCreateProcess proc = do return (ex, output) +readProcessEnvWithExitCode + :: String -- ^ program path + -> [String] -- ^ program args + -> [(String, String)] -- ^ environment to override + -> IO (ExitCode, String, String) -- ^ (exit_code, stdout, stderr) +readProcessEnvWithExitCode prog args env_update = do + current_env <- getEnvironment + let new_env = env_update ++ [ (k, v) + | let overriden_keys = map fst env_update + , (k, v) <- current_env + , k `notElem` overriden_keys + ] + p = proc prog args + + (_stdin, Just stdoh, Just stdeh, pid) <- + createProcess p{ std_out = CreatePipe + , std_err = CreatePipe + , env = Just new_env + } + + outMVar <- newEmptyMVar + errMVar <- newEmptyMVar + + _ <- forkIO $ do + stdo <- hGetContents stdoh + _ <- evaluate (length stdo) + putMVar outMVar stdo + + _ <- forkIO $ do + stde <- hGetContents stdeh + _ <- evaluate (length stde) + putMVar errMVar stde + + out <- takeMVar outMVar + hClose stdoh + err <- takeMVar errMVar + hClose stdeh + + ex <- waitForProcess pid + + return (ex, out, err) + +-- Don't let gcc localize version info string, #8825 +en_locale_env :: [(String, String)] +en_locale_env = [("LANGUAGE", "en")] -- If the -B option is set, add to PATH. This works around -- a bug in gcc on Windows Vista where it can't find its auxiliary @@ -744,8 +789,9 @@ getLinkerInfo' dflags = do _ -> do -- In practice, we use the compiler as the linker here. Pass -- -Wl,--version to get linker version info. - (exitc, stdo, stde) <- readProcessWithExitCode pgm - ["-Wl,--version"] "" + (exitc, stdo, stde) <- readProcessEnvWithExitCode pgm + ["-Wl,--version"] + en_locale_env -- Split the output by lines to make certain kinds -- of processing easier. In particular, 'clang' and 'gcc' -- have slightly different outputs for '-Wl,--version', but @@ -800,7 +846,8 @@ getCompilerInfo' dflags = do -- Process the executable call info <- catchIO (do - (exitc, stdo, stde) <- readProcessWithExitCode pgm ["-v"] "" + (exitc, stdo, stde) <- + readProcessEnvWithExitCode pgm ["-v"] en_locale_env -- Split the output by lines to make certain kinds -- of processing easier. parseCompilerInfo (lines stdo) (lines stde) exitc @@ -900,7 +947,8 @@ readElfSection _dflags section exe = do prog = "readelf" args = [Option "-p", Option section, FileOption "" exe] -- - r <- readProcessWithExitCode prog (filter notNull (map showOpt args)) "" + r <- readProcessEnvWithExitCode prog (filter notNull (map showOpt args)) + en_locale_env case r of (ExitSuccess, out, _err) -> return (doFilter (lines out)) _ -> return Nothing From git at git.haskell.org Mon Oct 27 16:04:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 16:04:54 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Take account of the AvailTC invariant when importing (86d240b) Message-ID: <20141027160454.A587C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/86d240b356b9d7b595da98ec286754c8f86e45e1/ghc >--------------------------------------------------------------- commit 86d240b356b9d7b595da98ec286754c8f86e45e1 Author: Simon Peyton Jones Date: Fri Apr 18 23:30:18 2014 +0100 Take account of the AvailTC invariant when importing In the rather gnarly filterImports code, someone had forgotten the AvailTC invariant: in AvailTC n [n,s1,s2], the 'n' is itself included in the list of names. (cherry picked from commit f964cd9c5c411f8a2383cf2b080581a5c3349661) >--------------------------------------------------------------- 86d240b356b9d7b595da98ec286754c8f86e45e1 compiler/rename/RnNames.lhs | 80 +++++++++++++++---------- testsuite/tests/rename/should_fail/T9006.hs | 3 + testsuite/tests/rename/should_fail/T9006.stderr | 2 + testsuite/tests/rename/should_fail/T9006a.hs | 3 + testsuite/tests/rename/should_fail/all.T | 3 + 5 files changed, 59 insertions(+), 32 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 86d240b356b9d7b595da98ec286754c8f86e45e1 From git at git.haskell.org Mon Oct 27 16:04:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 16:04:57 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Include pattern synonyms as AConLikes in the type environment, even for simplified/boot ModDetails (fixes #9417) (fd15d5c) Message-ID: <20141027160457.55FAA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/fd15d5c637a09fef913a74fc1424e3c28b1db91f/ghc >--------------------------------------------------------------- commit fd15d5c637a09fef913a74fc1424e3c28b1db91f Author: Dr. ERDI Gergo Date: Fri Aug 29 21:15:22 2014 +0800 Include pattern synonyms as AConLikes in the type environment, even for simplified/boot ModDetails (fixes #9417) (cherry picked from commit f0db1857b053597e9ac43d9ce578e5f5fa0545cb) >--------------------------------------------------------------- fd15d5c637a09fef913a74fc1424e3c28b1db91f compiler/basicTypes/PatSyn.lhs | 8 +------- compiler/main/TidyPgm.lhs | 15 +++++++++------ 2 files changed, 10 insertions(+), 13 deletions(-) diff --git a/compiler/basicTypes/PatSyn.lhs b/compiler/basicTypes/PatSyn.lhs index 32908f6..aa5a86a 100644 --- a/compiler/basicTypes/PatSyn.lhs +++ b/compiler/basicTypes/PatSyn.lhs @@ -16,7 +16,7 @@ module PatSyn ( patSynWrapper, patSynMatcher, patSynExTyVars, patSynSig, patSynInstArgTys, patSynInstResTy, - tidyPatSynIds, patSynIds + tidyPatSynIds ) where #include "HsVersions.h" @@ -266,12 +266,6 @@ patSynWrapper = psWrapper patSynMatcher :: PatSyn -> Id patSynMatcher = psMatcher -patSynIds :: PatSyn -> [Id] -patSynIds (MkPatSyn { psMatcher = match_id, psWrapper = mb_wrap_id }) - = case mb_wrap_id of - Nothing -> [match_id] - Just wrap_id -> [match_id, wrap_id] - tidyPatSynIds :: (Id -> Id) -> PatSyn -> PatSyn tidyPatSynIds tidy_fn ps@(MkPatSyn { psMatcher = match_id, psWrapper = mb_wrap_id }) = ps { psMatcher = tidy_fn match_id, psWrapper = fmap tidy_fn mb_wrap_id } diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs index ef7661a..5d2b6fa 100644 --- a/compiler/main/TidyPgm.lhs +++ b/compiler/main/TidyPgm.lhs @@ -139,12 +139,12 @@ mkBootModDetailsTc hsc_env ; showPass dflags CoreTidy ; let { insts' = map (tidyClsInstDFun globaliseAndTidyId) insts - ; pat_syns' = map (tidyPatSynIds globaliseAndTidyId) pat_syns - ; dfun_ids = map instanceDFunId insts' - ; pat_syn_ids = concatMap patSynIds pat_syns' ; type_env1 = mkBootTypeEnv (availsToNameSet exports) (typeEnvIds type_env) tcs fam_insts - ; type_env' = extendTypeEnvWithIds type_env1 (pat_syn_ids ++ dfun_ids) + ; pat_syns' = map (tidyPatSynIds globaliseAndTidyId) pat_syns + ; type_env2 = extendTypeEnvWithPatSyns pat_syns' type_env1 + ; dfun_ids = map instanceDFunId insts' + ; type_env' = extendTypeEnvWithIds type_env2 dfun_ids } ; return (ModDetails { md_types = type_env' , md_insts = insts' @@ -357,8 +357,7 @@ tidyProgram hsc_env (ModGuts { mg_module = mod -- This is really the only reason we keep mg_patsyns at all; otherwise -- they could just stay in type_env ; tidy_patsyns = map (tidyPatSynIds (lookup_aux_id tidy_type_env)) patsyns - ; type_env2 = extendTypeEnvList type_env1 - [AConLike (PatSynCon ps) | ps <- tidy_patsyns ] + ; type_env2 = extendTypeEnvWithPatSyns tidy_patsyns type_env1 ; tidy_type_env = tidyTypeEnv omit_prags type_env2 @@ -454,6 +453,10 @@ trimThing (AnId id) trimThing other_thing = other_thing + +extendTypeEnvWithPatSyns :: [PatSyn] -> TypeEnv -> TypeEnv +extendTypeEnvWithPatSyns tidy_patsyns type_env + = extendTypeEnvList type_env [AConLike (PatSynCon ps) | ps <- tidy_patsyns ] \end{code} \begin{code} From git at git.haskell.org Mon Oct 27 16:05:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 16:05:00 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: x86: zero extend the result of 16-bit popcnt instructions (#9435) (7766e5e) Message-ID: <20141027160500.15A293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/7766e5e9fd4889eecc8a1f7fe1982981c8694b58/ghc >--------------------------------------------------------------- commit 7766e5e9fd4889eecc8a1f7fe1982981c8694b58 Author: Reid Barton Date: Tue Aug 12 11:11:46 2014 -0400 x86: zero extend the result of 16-bit popcnt instructions (#9435) Summary: The 'popcnt r16, r/m16' instruction only writes the low 16 bits of the destination register, so we have to zero-extend the result to a full word as popCnt16# is supposed to return a Word#. For popCnt8# we could instead zero-extend the input to 32 bits and then do a 32-bit popcnt, and not have to zero-extend the result. LLVM produces the 16-bit popcnt sequence with two zero extensions, though, and who am I to argue? Test Plan: - ran "make TEST=cgrun071 EXTRA_HC_OPTS=-msse42" - then ran again adding "WAY=optasm", and verified that the popcnt sequences we generate match the ones produced by LLVM for its @llvm.ctpop.* intrinsics Reviewers: austin, hvr, tibbe Reviewed By: austin, hvr, tibbe Subscribers: phaskell, hvr, simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D147 GHC Trac Issues: #9435 (cherry picked from commit 64151913f1ed32ecfe17fcc40f7adc6cbfbb0bc1) >--------------------------------------------------------------- 7766e5e9fd4889eecc8a1f7fe1982981c8694b58 compiler/nativeGen/X86/CodeGen.hs | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs index 2456688..8b7d0df 100644 --- a/compiler/nativeGen/X86/CodeGen.hs +++ b/compiler/nativeGen/X86/CodeGen.hs @@ -1710,15 +1710,19 @@ genCCall is32Bit (PrimTarget (MO_PopCnt width)) dest_regs@[dst] if sse4_2 then do code_src <- getAnyReg src src_r <- getNewRegNat size + let dst_r = getRegisterReg platform False (CmmLocal dst) return $ code_src src_r `appOL` (if width == W8 then -- The POPCNT instruction doesn't take a r/m8 unitOL (MOVZxL II8 (OpReg src_r) (OpReg src_r)) `appOL` - unitOL (POPCNT II16 (OpReg src_r) - (getRegisterReg platform False (CmmLocal dst))) + unitOL (POPCNT II16 (OpReg src_r) dst_r) else - unitOL (POPCNT size (OpReg src_r) - (getRegisterReg platform False (CmmLocal dst)))) + unitOL (POPCNT size (OpReg src_r) dst_r)) `appOL` + (if width == W8 || width == W16 then + -- We used a 16-bit destination register above, + -- so zero-extend + unitOL (MOVZxL II16 (OpReg dst_r) (OpReg dst_r)) + else nilOL) else do targetExpr <- cmmMakeDynamicReference dflags CallReference lbl From git at git.haskell.org Mon Oct 27 20:53:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 20:53:43 +0000 (UTC) Subject: [commit: ghc] master: Deactivate T3064 `max_bytes_used`-check (0013613) Message-ID: <20141027205343.0E4CE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0013613dbb4bf969bd70a69ce521239f06624f0f/ghc >--------------------------------------------------------------- commit 0013613dbb4bf969bd70a69ce521239f06624f0f Author: Herbert Valerio Riedel Date: Mon Oct 27 19:37:16 2014 +0100 Deactivate T3064 `max_bytes_used`-check Summary: T3064 is deactivated for now because it's currently too volatile and causes too much noise in Phabricator's CI C.f. 4805abf413c02a2ed1af4fbeca2476590e984e37 Reviewers: austin Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D381 >--------------------------------------------------------------- 0013613dbb4bf969bd70a69ce521239f06624f0f testsuite/tests/perf/compiler/all.T | 45 ++++++++++++++++++++----------------- 1 file changed, 24 insertions(+), 21 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 489289b..1a9dfcb 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -267,27 +267,30 @@ test('T3064', # (amd64/Linux) (09/09/2014): 407416464, AMP changes (larger interfaces, more loading) # (amd64/Linux) (14/09/2014): 385145080, BPP changes (more NoImplicitPrelude in base) - compiler_stats_num_field('max_bytes_used', - [(wordsize(32), 11202304, 20), - # 2011-06-28: 2247016 (x86/Linux) (28/6/2011): - #(some date): 5511604 - # 2013-11-13: 7218200 (x86/Windows, 64bit machine) - # 2014-04-04: 11202304 (x86/Windows, 64bit machine) - (wordsize(64), 13251728, 20)]), - # (amd64/Linux, intree) (28/06/2011): 4032024 - # (amd64/Linux, intree) (07/02/2013): 9819288 - # (amd64/Linux) (14/02/2013): 8687360 - # (amd64/Linux) (18/02/2013): 9397488 - # (amd64/Linux) (02/08/2013): 10742536, increase from roles - # (amd64/Linux) (19/08/2013): 9211816, decrease apparently from better eta reduction - # (amd64/Linux) (11/09/2013): 12000480, increase from AMP warnings - # 933cdf15a2d85229d3df04b437da31fdfbf4961f - # (amd64/Linux) (22/11/2013): 16266992, GND via Coercible and counters for constraints solving - # (amd64/Linux) (12/12/2013): 19821544, better One shot analysis - # (amd64/Linux) (09/09/2014): 24357392, AMP changes (larger interfaces, more loading) - # (amd64/Linux) (14/09/2014): 16053888, BPP changes (more NoImplicitPrelude in base) - # (amd64/Linux) (19/09/2014): 18744992, unknown - # (amd64/Linux) 2014-10-13: 13251728, Stricter seqDmdType +################################### +# deactivated for now, as this metric became too volatile recently +# +# compiler_stats_num_field('max_bytes_used', +# [(wordsize(32), 11202304, 20), +# # 2011-06-28: 2247016 (x86/Linux) (28/6/2011): +# #(some date): 5511604 +# # 2013-11-13: 7218200 (x86/Windows, 64bit machine) +# # 2014-04-04: 11202304 (x86/Windows, 64bit machine) +# (wordsize(64), 13251728, 20)]), +# # (amd64/Linux, intree) (28/06/2011): 4032024 +# # (amd64/Linux, intree) (07/02/2013): 9819288 +# # (amd64/Linux) (14/02/2013): 8687360 +# # (amd64/Linux) (18/02/2013): 9397488 +# # (amd64/Linux) (02/08/2013): 10742536, increase from roles +# # (amd64/Linux) (19/08/2013): 9211816, decrease apparently from better eta reduction +# # (amd64/Linux) (11/09/2013): 12000480, increase from AMP warnings +# # 933cdf15a2d85229d3df04b437da31fdfbf4961f +# # (amd64/Linux) (22/11/2013): 16266992, GND via Coercible and counters for constraints solving +# # (amd64/Linux) (12/12/2013): 19821544, better One shot analysis +# # (amd64/Linux) (09/09/2014): 24357392, AMP changes (larger interfaces, more loading) +# # (amd64/Linux) (14/09/2014): 16053888, BPP changes (more NoImplicitPrelude in base) +# # (amd64/Linux) (19/09/2014): 18744992, unknown +# # (amd64/Linux) 2014-10-13: 13251728, Stricter seqDmdType only_ways(['normal']) ], From git at git.haskell.org Mon Oct 27 21:15:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 21:15:10 +0000 (UTC) Subject: [commit: ghc] master: Improve performance of isSuffixOf (#9676) (49b05d6) Message-ID: <20141027211510.7465E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/49b05d6935b6677443a970a45138def66c6f8cee/ghc >--------------------------------------------------------------- commit 49b05d6935b6677443a970a45138def66c6f8cee Author: David Feuer Date: Mon Oct 27 22:12:07 2014 +0100 Improve performance of isSuffixOf (#9676) The new implementation avoids reversing the "haystack" list, which can be very expensive. Reviewed By: ekmett Differential Revision: https://phabricator.haskell.org/D330 >--------------------------------------------------------------- 49b05d6935b6677443a970a45138def66c6f8cee libraries/base/Data/OldList.hs | 31 +++++++++++-- libraries/base/tests/all.T | 1 + libraries/base/tests/isSuffixOf.hs | 10 ++++ libraries/base/tests/isSuffixOf.stdout | 84 ++++++++++++++++++++++++++++++++++ 4 files changed, 122 insertions(+), 4 deletions(-) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index 0e6709e..53685d8 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -292,11 +292,34 @@ isPrefixOf [] _ = True isPrefixOf _ [] = False isPrefixOf (x:xs) (y:ys)= x == y && isPrefixOf xs ys --- | The 'isSuffixOf' function takes two lists and returns 'True' --- iff the first list is a suffix of the second. --- Both lists must be finite. +-- | The 'isSuffixOf' function takes two lists and returns 'True' iff +-- the first list is a suffix of the second. The second list must be +-- finite. isSuffixOf :: (Eq a) => [a] -> [a] -> Bool -isSuffixOf x y = reverse x `isPrefixOf` reverse y +ns `isSuffixOf` hs = maybe False id $ do + delta <- dropLengthMaybe ns hs + return $ ns == dropLength delta hs + -- Since dropLengthMaybe ns hs succeeded, we know that (if hs is finite) + -- length ns + length delta = length hs + -- so dropping the length of delta from hs will yield a suffix exactly + -- the length of ns. + +-- A version of drop that drops the length of the first argument from the +-- second argument. If xs is longer than ys, xs will not be traversed in its +-- entirety. dropLength is also generally faster than (drop . length) +-- Both this and dropLengthMaybe could be written as folds over their first +-- arguments, but this reduces clarity with no benefit to isSuffixOf. +dropLength :: [a] -> [b] -> [b] +dropLength [] y = y +dropLength _ [] = [] +dropLength (_:x') (_:y') = dropLength x' y' + +-- A version of dropLength that returns Nothing if the second list runs out of +-- elements before the first. +dropLengthMaybe :: [a] -> [b] -> Maybe [b] +dropLengthMaybe [] y = Just y +dropLengthMaybe _ [] = Nothing +dropLengthMaybe (_:x') (_:y') = dropLengthMaybe x' y' -- | The 'isInfixOf' function takes two lists and returns 'True' -- iff the first list is contained, wholly and intact, diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T index f80f542..edb5fc3 100644 --- a/libraries/base/tests/all.T +++ b/libraries/base/tests/all.T @@ -86,6 +86,7 @@ test('exceptionsrun002', normal, compile_and_run, ['']) test('list001' , when(fast(), skip), compile_and_run, ['']) test('list002', when(fast(), skip), compile_and_run, ['']) test('list003', when(fast(), skip), compile_and_run, ['']) +test('isSuffixOf', normal, compile_and_run, ['']) test('memo001', [extra_run_opts('+RTS -A10k -RTS'), diff --git a/libraries/base/tests/isSuffixOf.hs b/libraries/base/tests/isSuffixOf.hs new file mode 100644 index 0000000..bcbb77f --- /dev/null +++ b/libraries/base/tests/isSuffixOf.hs @@ -0,0 +1,10 @@ +module Main (main) where +import Data.List + +needles = ["","1","2","12","123","1234"] +haystacks = ["","a","ab","abc","1","2","3","a1","1a", + "23","123","a123","ab123","abc123"] + +main :: IO() +main = mapM_ print $ [needle `isSuffixOf` haystack + | needle <- needles, haystack <- haystacks] diff --git a/libraries/base/tests/isSuffixOf.stdout b/libraries/base/tests/isSuffixOf.stdout new file mode 100644 index 0000000..adba395 --- /dev/null +++ b/libraries/base/tests/isSuffixOf.stdout @@ -0,0 +1,84 @@ +True +True +True +True +True +True +True +True +True +True +True +True +True +True +False +False +False +False +True +False +False +True +False +False +False +False +False +False +False +False +False +False +False +True +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +False +True +True +True +True +False +False +False +False +False +False +False +False +False +False +False +False +False +False From git at git.haskell.org Mon Oct 27 23:20:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 27 Oct 2014 23:20:14 +0000 (UTC) Subject: [commit: ghc] master: Typo in comment (1874501) Message-ID: <20141027232014.EDB0C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/187450131877aef159fbfcdda0a5117f779f1688/ghc >--------------------------------------------------------------- commit 187450131877aef159fbfcdda0a5117f779f1688 Author: Gabor Greif Date: Tue Oct 28 00:17:13 2014 +0100 Typo in comment >--------------------------------------------------------------- 187450131877aef159fbfcdda0a5117f779f1688 compiler/main/DriverPipeline.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 870d994..6bc67e7 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -2241,8 +2241,8 @@ getGhcVersionPathName dflags = do -- 2. ${CC} -x assembler -c 'PIC_CFLAGS' source.S -- -- Why do we need to pass 'PIC_CFLAGS' both to C compiler and assembler? --- Because on some architectures (at least sparc32) assembler also choses --- relocation type! +-- Because on some architectures (at least sparc32) assembler also chooses +-- the relocation type! -- Consider the following C module: -- -- /* pic-sample.c */ From git at git.haskell.org Tue Oct 28 01:16:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 01:16:51 +0000 (UTC) Subject: [commit: ghc] master: Normalise package key hash to make tests less fragile. (aa2ceba) Message-ID: <20141028011651.7D3B33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aa2ceba33a8b98a2e8020464684f2eef7c98acf1/ghc >--------------------------------------------------------------- commit aa2ceba33a8b98a2e8020464684f2eef7c98acf1 Author: Edward Z. Yang Date: Mon Oct 27 17:52:39 2014 -0700 Normalise package key hash to make tests less fragile. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- aa2ceba33a8b98a2e8020464684f2eef7c98acf1 testsuite/tests/ghci/scripts/T5979.stderr | 6 +++--- testsuite/tests/ghci/scripts/all.T | 9 ++++++++- testsuite/tests/safeHaskell/check/pkg01/all.T | 6 +++++- testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout | 6 +++--- 4 files changed, 19 insertions(+), 8 deletions(-) diff --git a/testsuite/tests/ghci/scripts/T5979.stderr b/testsuite/tests/ghci/scripts/T5979.stderr index c2869b0..c8fc7c2 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_5jw4w9yTgmZ89ByuixDAKP) - Control.Monad.Trans.Class (from transformers-0.4.1.0 at trans_5jw4w9yTgmZ89ByuixDAKP) - Control.Monad.Trans.Cont (from transformers-0.4.1.0 at trans_5jw4w9yTgmZ89ByuixDAKP) + 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_) diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 1c8adeb..ede9807 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -1,5 +1,8 @@ # coding=utf8 +def normaliseTransformersPackageKey(str): + return re.sub('trans_[A-Za-z0-9]+', 'trans_', str) + setTestOpts(when(compiler_profiled(), skip)) test('ghci001', combined_output, ghci_script, ['ghci001.script']) @@ -114,7 +117,11 @@ test('T5564', normal, ghci_script, ['T5564.script']) test('Defer02', normal, ghci_script, ['Defer02.script']) test('T5820', normal, ghci_script, ['T5820.script']) test('T5836', normal, ghci_script, ['T5836.script']) -test('T5979', [reqlib('transformers'), normalise_slashes], ghci_script, ['T5979.script']) +test('T5979', + [reqlib('transformers'), + normalise_slashes, + normalise_errmsg_fun(normaliseTransformersPackageKey)], + ghci_script, ['T5979.script']) test('T5975a', [pre_cmd('touch f??b?r1.hs'), clean_cmd('rm f??b?r1.hs')], diff --git a/testsuite/tests/safeHaskell/check/pkg01/all.T b/testsuite/tests/safeHaskell/check/pkg01/all.T index 08f0b61..8b33f27 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/all.T +++ b/testsuite/tests/safeHaskell/check/pkg01/all.T @@ -8,6 +8,9 @@ def normaliseArrayPackage(str): def normaliseBytestringPackage(str): return re.sub('bytestring-[0-9]+(\.[0-9]+)*', 'bytestring-', 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) @@ -35,7 +38,8 @@ make_args = 'VANILLA=' + vanilla + ' PROF=' + prof + ' DYN=' + dyn test('safePkg01', [clean_cmd('$MAKE -s --no-print-directory cleanPackageDatabase.safePkg01'), normalise_errmsg_fun(ignoreLdOutput), - normalise_fun(two_normalisers(normaliseArrayPackage, + normalise_fun(two_normalisers(two_normalisers(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 7ce7704..62074de 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 at array_GX4NwjS8xZkC2ZPtjgwhnz +package dependencies: array-0.5.0.1 at array_ trusted: trustworthy require own pkg trusted: False M_SafePkg7 -package dependencies: array-0.5.0.1 at array_GX4NwjS8xZkC2ZPtjgwhnz +package dependencies: array-0.5.0.1 at array_ trusted: safe require own pkg trusted: False M_SafePkg8 -package dependencies: array-0.5.0.1 at array_GX4NwjS8xZkC2ZPtjgwhnz +package dependencies: array-0.5.0.1 at array_ trusted: trustworthy require own pkg trusted: False From git at git.haskell.org Tue Oct 28 09:44:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 09:44:33 +0000 (UTC) Subject: [commit: ghc] master: Add n-ary version of `two_normalisers` to testsuite lib (63918e6) Message-ID: <20141028094433.B3ED43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/63918e6d7f048597ae8f61c6297a7b700630a819/ghc >--------------------------------------------------------------- commit 63918e6d7f048597ae8f61c6297a7b700630a819 Author: Herbert Valerio Riedel Date: Tue Oct 28 10:42:34 2014 +0100 Add n-ary version of `two_normalisers` to testsuite lib This is more readable than nesting `two_normalisers()`-invocations >--------------------------------------------------------------- 63918e6d7f048597ae8f61c6297a7b700630a819 testsuite/driver/testlib.py | 27 +++++++++++++++++++++++++-- testsuite/tests/safeHaskell/check/pkg01/all.T | 10 +++++++--- 2 files changed, 32 insertions(+), 5 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 19fd0f8..17dbc6b 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -506,8 +506,29 @@ def _normalise_errmsg_fun( name, opts, f ): opts.extra_errmsg_normaliser = f def two_normalisers(f, g): + """ + See also `join_normalisers` for a n-ary version of `two_normalisers` + """ return lambda x, f=f, g=g: f(g(x)) +def join_normalisers(*a): + """ + Compose functions, e.g. + + join_normalisers(f1,f2,f3) + + is the same as + + lambda x: f1(f2(f3(x))) + """ + + assert all(callable(f) for f in a) + + fn = lambda x:x # identity function + for f in a: + fn = lambda x,f=f,fn=fn: fn(f(x)) + return fn + # ---- # Function for composing two opt-fns together @@ -1004,8 +1025,10 @@ def do_compile( name, way, should_fail, top_mod, extra_mods, extra_hc_opts, over (platform_specific, expected_stderr_file) = platform_wordsize_qualify(namebase, 'stderr') actual_stderr_file = qualify(name, 'comp.stderr') - if not compare_outputs('stderr', \ - two_normalisers(two_normalisers(getTestOpts().extra_errmsg_normaliser, normalise_errmsg), normalise_whitespace), \ + if not compare_outputs('stderr', + join_normalisers(getTestOpts().extra_errmsg_normaliser, + normalise_errmsg, + normalise_whitespace), expected_stderr_file, actual_stderr_file): return failBecause('stderr mismatch') diff --git a/testsuite/tests/safeHaskell/check/pkg01/all.T b/testsuite/tests/safeHaskell/check/pkg01/all.T index 8b33f27..5b2839d 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/all.T +++ b/testsuite/tests/safeHaskell/check/pkg01/all.T @@ -8,6 +8,9 @@ def normaliseArrayPackage(str): def normaliseBytestringPackage(str): return re.sub('bytestring-[0-9]+(\.[0-9]+)*', 'bytestring-', 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) @@ -38,9 +41,10 @@ make_args = 'VANILLA=' + vanilla + ' PROF=' + prof + ' DYN=' + dyn test('safePkg01', [clean_cmd('$MAKE -s --no-print-directory cleanPackageDatabase.safePkg01'), normalise_errmsg_fun(ignoreLdOutput), - normalise_fun(two_normalisers(two_normalisers(normaliseArrayPackage, - normaliseArrayPackageKey), - normaliseBytestringPackage))], + normalise_fun(join_normalisers( + normaliseArrayPackage, + normaliseArrayPackageKey, + normaliseBytestringPackage))], run_command, ['$MAKE -s --no-print-directory safePkg01 ' + make_args]) From git at git.haskell.org Tue Oct 28 10:22:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 10:22:31 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate-no-two_normalisers' created Message-ID: <20141028102231.6DD9D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/validate-no-two_normalisers Referencing: 236488a7e91ad327e698740594345396947d7612 From git at git.haskell.org Tue Oct 28 10:22:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 10:22:34 +0000 (UTC) Subject: [commit: ghc] wip/validate-no-two_normalisers: testlib: Get rid of two_normalisers (236488a) Message-ID: <20141028102234.128D33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/validate-no-two_normalisers Link : http://ghc.haskell.org/trac/ghc/changeset/236488a7e91ad327e698740594345396947d7612/ghc >--------------------------------------------------------------- commit 236488a7e91ad327e698740594345396947d7612 Author: Joachim Breitner Date: Tue Oct 28 11:21:49 2014 +0100 testlib: Get rid of two_normalisers And make normalise_fun polyvariadic. After all, this is untyped code, so lets make use of it :-) >--------------------------------------------------------------- 236488a7e91ad327e698740594345396947d7612 testsuite/driver/testlib.py | 51 +++++++++++++++------------ testsuite/tests/cabal/all.T | 3 +- testsuite/tests/safeHaskell/check/pkg01/all.T | 4 +-- 3 files changed, 31 insertions(+), 27 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 17dbc6b..a69fda3 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -16,6 +16,7 @@ import datetime import copy import glob from math import ceil, trunc +import collections have_subprocess = False try: @@ -493,35 +494,39 @@ def normalise_slashes( name, opts ): def normalise_exe( name, opts ): opts.extra_normaliser = normalise_exe_ -def normalise_fun( fun ): - return lambda name, opts, f=fun: _normalise_fun(name, opts, f) +def normalise_fun( *fs ): + return lambda name, opts: _normalise_fun(name, opts, fs) -def _normalise_fun( name, opts, f ): - opts.extra_normaliser = f +def _normalise_fun( name, opts, *fs ): + opts.extra_normaliser = join_normalisers(fs) -def normalise_errmsg_fun( fun ): - return lambda name, opts, f=fun: _normalise_errmsg_fun(name, opts, f) +def normalise_errmsg_fun( *fs ): + return lambda name, opts: _normalise_errmsg_fun(name, opts, fs) -def _normalise_errmsg_fun( name, opts, f ): - opts.extra_errmsg_normaliser = f - -def two_normalisers(f, g): - """ - See also `join_normalisers` for a n-ary version of `two_normalisers` - """ - return lambda x, f=f, g=g: f(g(x)) +def _normalise_errmsg_fun( name, opts, *fs ): + opts.extra_errmsg_normaliser = join_normalisers(fs) def join_normalisers(*a): """ - Compose functions, e.g. + Compose functions, flattening sequences. - join_normalisers(f1,f2,f3) + join_normalisers(f1,[f2,f3],f4) is the same as - lambda x: f1(f2(f3(x))) + lambda x: f1(f2(f3(f4(x)))) """ + def flatten(l): + for el in l: + if isinstance(el, collections.Iterable) and not isinstance(el, basestring): + for sub in flatten(el): + yield sub + else: + yield el + + a = flatten(a) + assert all(callable(f) for f in a) fn = lambda x:x # identity function @@ -1055,7 +1060,7 @@ def compile_cmp_asm( name, way, extra_hc_opts ): (platform_specific, expected_asm_file) = platform_wordsize_qualify(namebase, 'asm') actual_asm_file = qualify(name, 's') - if not compare_outputs('asm', two_normalisers(normalise_errmsg, normalise_asm), \ + if not compare_outputs('asm', join_normalisers(normalise_errmsg, normalise_asm), \ expected_asm_file, actual_asm_file): return failBecause('asm mismatch') @@ -1492,14 +1497,14 @@ def check_stdout_ok( name ): else: return normalise_output(str) - two_norm = two_normalisers(norm, getTestOpts().extra_normaliser) + extra_norm = join_normalisers(norm, getTestOpts().extra_normaliser) check_stdout = getTestOpts().check_stdout if check_stdout: - return check_stdout(actual_stdout_file, two_norm) + return check_stdout(actual_stdout_file, extra_norm) return compare_outputs('stdout', \ - two_norm, \ + extra_norm, \ expected_stdout_file, actual_stdout_file) def dump_stdout( name ): @@ -1522,7 +1527,7 @@ def check_stderr_ok( name ): return normalise_errmsg(str) return compare_outputs('stderr', \ - two_normalisers(norm, getTestOpts().extra_errmsg_normaliser), \ + join_normalisers(norm, getTestOpts().extra_errmsg_normaliser), \ expected_stderr_file, actual_stderr_file) def dump_stderr( name ): @@ -1596,7 +1601,7 @@ def check_prof_ok(name): return True else: return compare_outputs('prof', \ - two_normalisers(normalise_whitespace,normalise_prof), \ + join_normalisers(normalise_whitespace,normalise_prof), \ expected_prof_file, prof_file) # Compare expected output to actual output, and optionally accept the diff --git a/testsuite/tests/cabal/all.T b/testsuite/tests/cabal/all.T index 60f8d6d..08df23d 100644 --- a/testsuite/tests/cabal/all.T +++ b/testsuite/tests/cabal/all.T @@ -36,8 +36,7 @@ test('ghcpkg05', 'local05a.package.conf.old', 'local05b.package.conf', 'local05b.package.conf.old']), - normalise_errmsg_fun(two_normalisers(normalise_haddock_junk, - normaliseDynlibNames)) + normalise_errmsg_fun(normalise_haddock_junk, normaliseDynlibNames) ], run_command, ['$MAKE -s --no-print-directory ghcpkg05']) diff --git a/testsuite/tests/safeHaskell/check/pkg01/all.T b/testsuite/tests/safeHaskell/check/pkg01/all.T index 5b2839d..732f6fb 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/all.T +++ b/testsuite/tests/safeHaskell/check/pkg01/all.T @@ -41,10 +41,10 @@ make_args = 'VANILLA=' + vanilla + ' PROF=' + prof + ' DYN=' + dyn test('safePkg01', [clean_cmd('$MAKE -s --no-print-directory cleanPackageDatabase.safePkg01'), normalise_errmsg_fun(ignoreLdOutput), - normalise_fun(join_normalisers( + normalise_fun( normaliseArrayPackage, normaliseArrayPackageKey, - normaliseBytestringPackage))], + normaliseBytestringPackage)], run_command, ['$MAKE -s --no-print-directory safePkg01 ' + make_args]) From git at git.haskell.org Tue Oct 28 11:43:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 11:43:11 +0000 (UTC) Subject: [commit: ghc] wip/validate-no-two_normalisers: testlib: Get rid of two_normalisers (c491779) Message-ID: <20141028114311.EA8003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/validate-no-two_normalisers Link : http://ghc.haskell.org/trac/ghc/changeset/c491779d03a2f7bfa05af09012c376860b228f69/ghc >--------------------------------------------------------------- commit c491779d03a2f7bfa05af09012c376860b228f69 Author: Joachim Breitner Date: Tue Oct 28 11:21:49 2014 +0100 testlib: Get rid of two_normalisers And make normalise_fun polyvariadic. After all, this is untyped code, so lets make use of it :-) >--------------------------------------------------------------- c491779d03a2f7bfa05af09012c376860b228f69 testsuite/driver/testlib.py | 57 +++++++++++++++------------ testsuite/tests/cabal/all.T | 3 +- testsuite/tests/safeHaskell/check/pkg01/all.T | 4 +- 3 files changed, 35 insertions(+), 29 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 17dbc6b..0aa203e 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -16,6 +16,7 @@ import datetime import copy import glob from math import ceil, trunc +import collections have_subprocess = False try: @@ -493,40 +494,46 @@ def normalise_slashes( name, opts ): def normalise_exe( name, opts ): opts.extra_normaliser = normalise_exe_ -def normalise_fun( fun ): - return lambda name, opts, f=fun: _normalise_fun(name, opts, f) +def normalise_fun( *fs ): + return lambda name, opts: _normalise_fun(name, opts, fs) -def _normalise_fun( name, opts, f ): - opts.extra_normaliser = f +def _normalise_fun( name, opts, *fs ): + opts.extra_normaliser = join_normalisers(fs) -def normalise_errmsg_fun( fun ): - return lambda name, opts, f=fun: _normalise_errmsg_fun(name, opts, f) +def normalise_errmsg_fun( *fs ): + return lambda name, opts: _normalise_errmsg_fun(name, opts, fs) -def _normalise_errmsg_fun( name, opts, f ): - opts.extra_errmsg_normaliser = f - -def two_normalisers(f, g): - """ - See also `join_normalisers` for a n-ary version of `two_normalisers` - """ - return lambda x, f=f, g=g: f(g(x)) +def _normalise_errmsg_fun( name, opts, *fs ): + opts.extra_errmsg_normaliser = join_normalisers(fs) def join_normalisers(*a): """ - Compose functions, e.g. + Compose functions, flattening sequences. - join_normalisers(f1,f2,f3) + join_normalisers(f1,[f2,f3],f4) is the same as - lambda x: f1(f2(f3(x))) + lambda x: f1(f2(f3(f4(x)))) """ - assert all(callable(f) for f in a) + def flatten(l): + """ + Taken from http://stackoverflow.com/a/2158532/946226 + """ + for el in l: + if isinstance(el, collections.Iterable) and not isinstance(el, basestring): + for sub in flatten(el): + yield sub + else: + yield el + + a = flatten(a) fn = lambda x:x # identity function for f in a: - fn = lambda x,f=f,fn=fn: fn(f(x)) + assert callable(f) + fn = lambda x: fn(f(x)) return fn # ---- @@ -1055,7 +1062,7 @@ def compile_cmp_asm( name, way, extra_hc_opts ): (platform_specific, expected_asm_file) = platform_wordsize_qualify(namebase, 'asm') actual_asm_file = qualify(name, 's') - if not compare_outputs('asm', two_normalisers(normalise_errmsg, normalise_asm), \ + if not compare_outputs('asm', join_normalisers(normalise_errmsg, normalise_asm), \ expected_asm_file, actual_asm_file): return failBecause('asm mismatch') @@ -1492,14 +1499,14 @@ def check_stdout_ok( name ): else: return normalise_output(str) - two_norm = two_normalisers(norm, getTestOpts().extra_normaliser) + extra_norm = join_normalisers(norm, getTestOpts().extra_normaliser) check_stdout = getTestOpts().check_stdout if check_stdout: - return check_stdout(actual_stdout_file, two_norm) + return check_stdout(actual_stdout_file, extra_norm) return compare_outputs('stdout', \ - two_norm, \ + extra_norm, \ expected_stdout_file, actual_stdout_file) def dump_stdout( name ): @@ -1522,7 +1529,7 @@ def check_stderr_ok( name ): return normalise_errmsg(str) return compare_outputs('stderr', \ - two_normalisers(norm, getTestOpts().extra_errmsg_normaliser), \ + join_normalisers(norm, getTestOpts().extra_errmsg_normaliser), \ expected_stderr_file, actual_stderr_file) def dump_stderr( name ): @@ -1596,7 +1603,7 @@ def check_prof_ok(name): return True else: return compare_outputs('prof', \ - two_normalisers(normalise_whitespace,normalise_prof), \ + join_normalisers(normalise_whitespace,normalise_prof), \ expected_prof_file, prof_file) # Compare expected output to actual output, and optionally accept the diff --git a/testsuite/tests/cabal/all.T b/testsuite/tests/cabal/all.T index 60f8d6d..08df23d 100644 --- a/testsuite/tests/cabal/all.T +++ b/testsuite/tests/cabal/all.T @@ -36,8 +36,7 @@ test('ghcpkg05', 'local05a.package.conf.old', 'local05b.package.conf', 'local05b.package.conf.old']), - normalise_errmsg_fun(two_normalisers(normalise_haddock_junk, - normaliseDynlibNames)) + normalise_errmsg_fun(normalise_haddock_junk, normaliseDynlibNames) ], run_command, ['$MAKE -s --no-print-directory ghcpkg05']) diff --git a/testsuite/tests/safeHaskell/check/pkg01/all.T b/testsuite/tests/safeHaskell/check/pkg01/all.T index 5b2839d..732f6fb 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/all.T +++ b/testsuite/tests/safeHaskell/check/pkg01/all.T @@ -41,10 +41,10 @@ make_args = 'VANILLA=' + vanilla + ' PROF=' + prof + ' DYN=' + dyn test('safePkg01', [clean_cmd('$MAKE -s --no-print-directory cleanPackageDatabase.safePkg01'), normalise_errmsg_fun(ignoreLdOutput), - normalise_fun(join_normalisers( + normalise_fun( normaliseArrayPackage, normaliseArrayPackageKey, - normaliseBytestringPackage))], + normaliseBytestringPackage)], run_command, ['$MAKE -s --no-print-directory safePkg01 ' + make_args]) From git at git.haskell.org Tue Oct 28 12:06:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 12:06:18 +0000 (UTC) Subject: [commit: ghc] wip/validate-no-two_normalisers: testlib: Get rid of two_normalisers (3d6422b) Message-ID: <20141028120618.AA6F53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/validate-no-two_normalisers Link : http://ghc.haskell.org/trac/ghc/changeset/3d6422b20db918d1911dd52470a2dad04fd5e1bc/ghc >--------------------------------------------------------------- commit 3d6422b20db918d1911dd52470a2dad04fd5e1bc Author: Joachim Breitner Date: Tue Oct 28 11:21:49 2014 +0100 testlib: Get rid of two_normalisers And make normalise_fun polyvariadic. After all, this is untyped code, so lets make use of it :-) >--------------------------------------------------------------- 3d6422b20db918d1911dd52470a2dad04fd5e1bc testsuite/driver/testlib.py | 55 +++++++++++++++------------ testsuite/tests/cabal/all.T | 3 +- testsuite/tests/safeHaskell/check/pkg01/all.T | 4 +- 3 files changed, 34 insertions(+), 28 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 17dbc6b..3093982 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -16,6 +16,7 @@ import datetime import copy import glob from math import ceil, trunc +import collections have_subprocess = False try: @@ -493,39 +494,45 @@ def normalise_slashes( name, opts ): def normalise_exe( name, opts ): opts.extra_normaliser = normalise_exe_ -def normalise_fun( fun ): - return lambda name, opts, f=fun: _normalise_fun(name, opts, f) +def normalise_fun( *fs ): + return lambda name, opts: _normalise_fun(name, opts, fs) -def _normalise_fun( name, opts, f ): - opts.extra_normaliser = f +def _normalise_fun( name, opts, *fs ): + opts.extra_normaliser = join_normalisers(fs) -def normalise_errmsg_fun( fun ): - return lambda name, opts, f=fun: _normalise_errmsg_fun(name, opts, f) +def normalise_errmsg_fun( *fs ): + return lambda name, opts: _normalise_errmsg_fun(name, opts, fs) -def _normalise_errmsg_fun( name, opts, f ): - opts.extra_errmsg_normaliser = f - -def two_normalisers(f, g): - """ - See also `join_normalisers` for a n-ary version of `two_normalisers` - """ - return lambda x, f=f, g=g: f(g(x)) +def _normalise_errmsg_fun( name, opts, *fs ): + opts.extra_errmsg_normaliser = join_normalisers(fs) def join_normalisers(*a): """ - Compose functions, e.g. + Compose functions, flattening sequences. - join_normalisers(f1,f2,f3) + join_normalisers(f1,[f2,f3],f4) is the same as - lambda x: f1(f2(f3(x))) + lambda x: f1(f2(f3(f4(x)))) """ - assert all(callable(f) for f in a) + def flatten(l): + """ + Taken from http://stackoverflow.com/a/2158532/946226 + """ + for el in l: + if isinstance(el, collections.Iterable) and not isinstance(el, basestring): + for sub in flatten(el): + yield sub + else: + yield el + + a = flatten(a) fn = lambda x:x # identity function for f in a: + assert callable(f) fn = lambda x,f=f,fn=fn: fn(f(x)) return fn @@ -1055,7 +1062,7 @@ def compile_cmp_asm( name, way, extra_hc_opts ): (platform_specific, expected_asm_file) = platform_wordsize_qualify(namebase, 'asm') actual_asm_file = qualify(name, 's') - if not compare_outputs('asm', two_normalisers(normalise_errmsg, normalise_asm), \ + if not compare_outputs('asm', join_normalisers(normalise_errmsg, normalise_asm), \ expected_asm_file, actual_asm_file): return failBecause('asm mismatch') @@ -1492,14 +1499,14 @@ def check_stdout_ok( name ): else: return normalise_output(str) - two_norm = two_normalisers(norm, getTestOpts().extra_normaliser) + extra_norm = join_normalisers(norm, getTestOpts().extra_normaliser) check_stdout = getTestOpts().check_stdout if check_stdout: - return check_stdout(actual_stdout_file, two_norm) + return check_stdout(actual_stdout_file, extra_norm) return compare_outputs('stdout', \ - two_norm, \ + extra_norm, \ expected_stdout_file, actual_stdout_file) def dump_stdout( name ): @@ -1522,7 +1529,7 @@ def check_stderr_ok( name ): return normalise_errmsg(str) return compare_outputs('stderr', \ - two_normalisers(norm, getTestOpts().extra_errmsg_normaliser), \ + join_normalisers(norm, getTestOpts().extra_errmsg_normaliser), \ expected_stderr_file, actual_stderr_file) def dump_stderr( name ): @@ -1596,7 +1603,7 @@ def check_prof_ok(name): return True else: return compare_outputs('prof', \ - two_normalisers(normalise_whitespace,normalise_prof), \ + join_normalisers(normalise_whitespace,normalise_prof), \ expected_prof_file, prof_file) # Compare expected output to actual output, and optionally accept the diff --git a/testsuite/tests/cabal/all.T b/testsuite/tests/cabal/all.T index 60f8d6d..08df23d 100644 --- a/testsuite/tests/cabal/all.T +++ b/testsuite/tests/cabal/all.T @@ -36,8 +36,7 @@ test('ghcpkg05', 'local05a.package.conf.old', 'local05b.package.conf', 'local05b.package.conf.old']), - normalise_errmsg_fun(two_normalisers(normalise_haddock_junk, - normaliseDynlibNames)) + normalise_errmsg_fun(normalise_haddock_junk, normaliseDynlibNames) ], run_command, ['$MAKE -s --no-print-directory ghcpkg05']) diff --git a/testsuite/tests/safeHaskell/check/pkg01/all.T b/testsuite/tests/safeHaskell/check/pkg01/all.T index 5b2839d..732f6fb 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/all.T +++ b/testsuite/tests/safeHaskell/check/pkg01/all.T @@ -41,10 +41,10 @@ make_args = 'VANILLA=' + vanilla + ' PROF=' + prof + ' DYN=' + dyn test('safePkg01', [clean_cmd('$MAKE -s --no-print-directory cleanPackageDatabase.safePkg01'), normalise_errmsg_fun(ignoreLdOutput), - normalise_fun(join_normalisers( + normalise_fun( normaliseArrayPackage, normaliseArrayPackageKey, - normaliseBytestringPackage))], + normaliseBytestringPackage)], run_command, ['$MAKE -s --no-print-directory safePkg01 ' + make_args]) From git at git.haskell.org Tue Oct 28 13:09:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 13:09:59 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate-no-two_normalisers' deleted Message-ID: <20141028130959.64C053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/validate-no-two_normalisers From git at git.haskell.org Tue Oct 28 13:10:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 13:10:01 +0000 (UTC) Subject: [commit: ghc] master's head updated: testlib: Get rid of two_normalisers (3d6422b) Message-ID: <20141028131001.8C8153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: 3d6422b testlib: Get rid of two_normalisers From git at git.haskell.org Tue Oct 28 14:30:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 14:30:36 +0000 (UTC) Subject: [commit: ghc] master: Make iterateFB inlineable (98ed815) Message-ID: <20141028143036.C22B03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/98ed815f658bdf9cc0299a4818244c3a56c20487/ghc >--------------------------------------------------------------- commit 98ed815f658bdf9cc0299a4818244c3a56c20487 Author: Joachim Breitner Date: Tue Oct 28 15:28:59 2014 +0100 Make iterateFB inlineable When investigating a case of unexpected Call Arity failure I noticed that iterateFB would not inline as far as desired, as it is recursive. This patch makes it non-recursive (with a local go), which seem so do great good. >--------------------------------------------------------------- 98ed815f658bdf9cc0299a4818244c3a56c20487 libraries/base/GHC/List.lhs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/libraries/base/GHC/List.lhs b/libraries/base/GHC/List.lhs index 2d01678..f993ee7 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -352,7 +352,8 @@ iterate f x = x : iterate f (f x) {-# NOINLINE [0] iterateFB #-} iterateFB :: (a -> b -> b) -> (a -> a) -> a -> b -iterateFB c f x = x `c` iterateFB c f (f x) +iterateFB c f x0 = go x0 + where go x = x `c` go (f x) {-# RULES "iterate" [~1] forall f x. iterate f x = build (\c _n -> iterateFB c f x) From git at git.haskell.org Tue Oct 28 14:33:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 14:33:31 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Make travis happy (5b0aefa) Message-ID: <20141028143331.AFBB83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/5b0aefa2689ac71d4b45815de6b1a76d35af2ed2/ghc >--------------------------------------------------------------- commit 5b0aefa2689ac71d4b45815de6b1a76d35af2ed2 Author: Joachim Breitner Date: Tue Oct 7 13:37:23 2014 +0200 Make travis happy >--------------------------------------------------------------- 5b0aefa2689ac71d4b45815de6b1a76d35af2ed2 libraries/base/GHC/Event/Manager.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/Event/Manager.hs b/libraries/base/GHC/Event/Manager.hs index 2041379..29edd97 100644 --- a/libraries/base/GHC/Event/Manager.hs +++ b/libraries/base/GHC/Event/Manager.hs @@ -167,10 +167,10 @@ newDefaultBackend = error "no back end for this platform" -- | Create a new event manager. new :: Bool -> IO EventManager -new oneShot = newWith oneShot =<< newDefaultBackend +new isOneShot = newWith isOneShot =<< newDefaultBackend newWith :: Bool -> Backend -> IO EventManager -newWith oneShot be = do +newWith isOneShot be = do iofds <- fmap (listArray (0, callbackArraySize-1)) $ replicateM callbackArraySize (newMVar =<< IT.new 8) ctrl <- newControl False @@ -187,7 +187,7 @@ newWith oneShot be = do , emState = state , emUniqueSource = us , emControl = ctrl - , emOneShot = oneShot + , emOneShot = isOneShot , emLock = lockVar } registerControlFd mgr (controlReadFd ctrl) evtRead From git at git.haskell.org Tue Oct 28 14:33:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 14:33:34 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Use oneShot in the definition of foldl etc. (67abb9c) Message-ID: <20141028143334.4910D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/67abb9c5019052baeb334f66c9a4427371b2958c/ghc >--------------------------------------------------------------- commit 67abb9c5019052baeb334f66c9a4427371b2958c Author: Joachim Breitner Date: Sat Oct 25 12:27:06 2014 +0200 Use oneShot in the definition of foldl etc. >--------------------------------------------------------------- 67abb9c5019052baeb334f66c9a4427371b2958c libraries/base/Data/OldList.hs | 5 +++-- libraries/base/GHC/List.lhs | 6 +++--- 2 files changed, 6 insertions(+), 5 deletions(-) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index 53685d8..bce1102 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -522,7 +522,8 @@ 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) @@ -1081,7 +1082,7 @@ unfoldr f b0 = build (\c n -> -- | A strict version of 'foldl'. foldl' :: forall a b . (b -> a -> b) -> b -> [a] -> b -foldl' k z0 xs = foldr (\(v::a) (fn::b->b) (z::b) -> z `seq` fn (k z v)) (id :: b -> b) xs z0 +foldl' k z0 xs = foldr (\(v::a) (fn::b->b) -> oneShot (\(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 diff --git a/libraries/base/GHC/List.lhs b/libraries/base/GHC/List.lhs index f993ee7..4c67c89 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -186,7 +186,7 @@ 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 +foldl k z0 xs = foldr (\(v::a) (fn::b->b) -> oneShot (\(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 @@ -221,7 +221,7 @@ 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') {-# INLINE [0] constScanl #-} constScanl :: a -> b -> a @@ -258,7 +258,7 @@ 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' `seq` b' `c` g b' +scanlFB' f c = \b g -> oneShot (\x -> let b' = f x b in b' `seq` b' `c` g b') {-# INLINE [0] flipSeqScanl' #-} flipSeqScanl' :: a -> b -> a From git at git.haskell.org Tue Oct 28 14:33:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 14:33:36 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Add GHC.Prim.oneShot (f653aab) Message-ID: <20141028143336.ED1BD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/f653aab99d56a9f0931075b0c684bb07c1b25f08/ghc >--------------------------------------------------------------- commit f653aab99d56a9f0931075b0c684bb07c1b25f08 Author: Joachim Breitner Date: Sun Jan 26 11:36:23 2014 +0000 Add GHC.Prim.oneShot Conflicts: compiler/basicTypes/MkId.lhs >--------------------------------------------------------------- f653aab99d56a9f0931075b0c684bb07c1b25f08 compiler/basicTypes/MkId.lhs | 17 +++++++++++++++-- compiler/prelude/PrelNames.lhs | 3 ++- 2 files changed, 17 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index bf1c199..05dcdd5 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -135,7 +135,8 @@ ghcPrimIds seqId, magicDictId, coerceId, - proxyHashId + proxyHashId, + oneShotId ] \end{code} @@ -1016,7 +1017,7 @@ another gun with which to shoot yourself in the foot. \begin{code} lazyIdName, unsafeCoerceName, nullAddrName, seqName, realWorldName, voidPrimIdName, coercionTokenName, - magicDictName, coerceName, proxyName, dollarName :: Name + 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 @@ -1028,6 +1029,7 @@ magicDictName = mkWiredInIdName gHC_PRIM (fsLit "magicDict") magicDict coerceName = mkWiredInIdName gHC_PRIM (fsLit "coerce") coerceKey coerceId proxyName = mkWiredInIdName gHC_PRIM (fsLit "proxy#") proxyHashKey proxyHashId dollarName = mkWiredInIdName gHC_BASE (fsLit "$") dollarIdKey dollarId +oneShotName = mkWiredInIdName gHC_PRIM (fsLit "oneShot") oneShotKey oneShotId \end{code} \begin{code} @@ -1119,6 +1121,17 @@ lazyId = pcMiscPrelId lazyIdName ty info info = noCafIdInfo ty = mkForAllTys [alphaTyVar] (mkFunTy alphaTy alphaTy) +oneShotId :: Id +oneShotId = pcMiscPrelId oneShotName ty info + where + info = noCafIdInfo `setInlinePragInfo` alwaysInlinePragma + `setUnfoldingInfo` mkCompulsoryUnfolding rhs + ty = mkForAllTys [alphaTyVar, betaTyVar] (mkFunTy fun_ty fun_ty) + fun_ty = mkFunTy alphaTy betaTy + [body, x] = mkTemplateLocals [fun_ty, alphaTy] + x' = setOneShotLambda x + rhs = mkLams [alphaTyVar, betaTyVar, body, x'] $ Var body `App` Var x + -------------------------------------------------------------------------------- magicDictId :: Id -- See Note [magicDictId magic] diff --git a/compiler/prelude/PrelNames.lhs b/compiler/prelude/PrelNames.lhs index 4e98739..73d1cf3 100644 --- a/compiler/prelude/PrelNames.lhs +++ b/compiler/prelude/PrelNames.lhs @@ -1686,10 +1686,11 @@ rootMainKey, runMainKey :: Unique rootMainKey = mkPreludeMiscIdUnique 101 runMainKey = mkPreludeMiscIdUnique 102 -thenIOIdKey, lazyIdKey, assertErrorIdKey :: Unique +thenIOIdKey, lazyIdKey, assertErrorIdKey, oneShotKey :: Unique thenIOIdKey = mkPreludeMiscIdUnique 103 lazyIdKey = mkPreludeMiscIdUnique 104 assertErrorIdKey = mkPreludeMiscIdUnique 105 +oneShotKey = mkPreludeMiscIdUnique 106 breakpointIdKey, breakpointCondIdKey, breakpointAutoIdKey, breakpointJumpIdKey, breakpointCondJumpIdKey, From git at git.haskell.org Tue Oct 28 14:33:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 14:33:39 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Add oneShot demo file (04ad665) Message-ID: <20141028143339.D57B03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/04ad66536daf9e2eaa0f3c2133112d3b21904b2c/ghc >--------------------------------------------------------------- commit 04ad66536daf9e2eaa0f3c2133112d3b21904b2c Author: Joachim Breitner Date: Mon Oct 6 23:04:02 2014 +0200 Add oneShot demo file (if you remove {-# GHC_OPTIONS -fno-call-arity #-} then both functions have the same Core). Obviously, this patch is not meant to be merged. >--------------------------------------------------------------- 04ad66536daf9e2eaa0f3c2133112d3b21904b2c OneShotTest.hs | 22 ++++++++++++++++++++++ 1 file changed, 22 insertions(+) diff --git a/OneShotTest.hs b/OneShotTest.hs new file mode 100644 index 0000000..b595285 --- /dev/null +++ b/OneShotTest.hs @@ -0,0 +1,22 @@ +{-# OPTIONS_GHC -fno-call-arity #-} + +module OneShotTest (foldlB, foldlA, fooA, fooB, fooC) where + +import GHC.Prim (oneShot) + +foldlA, foldlB :: (x -> a -> a) -> a -> [x] -> a + +foldlA k a xs = foldr (\v f a -> f (v `k` a)) id xs a +{-# INLINEABLE foldlA #-} + +foldlB k a xs = foldr (\v f -> oneShot (\ a -> f (v `k` a))) id xs a +{-# INLINEABLE foldlB #-} + +f :: Int -> Bool +f 0 = True +f 1 = False +{-# NOINLINE f #-} + +fooA = foldlA (+) 0 . filter f +fooB = foldlB (+) 0 . filter f +fooC = foldl (+) 0 . filter f From git at git.haskell.org Tue Oct 28 14:33:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 14:33:42 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Put one-Shot info in the interface (7df4ba4) Message-ID: <20141028143342.794393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/7df4ba4d4b9f3a9efab199c699d79f8c883fffb5/ghc >--------------------------------------------------------------- commit 7df4ba4d4b9f3a9efab199c699d79f8c883fffb5 Author: Joachim Breitner Date: Tue Oct 28 13:02:40 2014 +0100 Put one-Shot info in the interface >--------------------------------------------------------------- 7df4ba4d4b9f3a9efab199c699d79f8c883fffb5 compiler/iface/IfaceSyn.lhs | 30 ++++++++++++++++-------------- compiler/iface/IfaceType.lhs | 29 +++++++++++++++++++++++++++-- compiler/iface/MkIface.lhs | 9 ++++++++- compiler/iface/TcIface.lhs | 7 +++++-- 4 files changed, 56 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 7df4ba4d4b9f3a9efab199c699d79f8c883fffb5 From git at git.haskell.org Tue Oct 28 14:33:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 14:33:45 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Preserve oneShotInfo in CoreTidy (81af069) Message-ID: <20141028143345.185523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/81af0699037a7fa51a3dbf937084722210d8311d/ghc >--------------------------------------------------------------- commit 81af0699037a7fa51a3dbf937084722210d8311d Author: Joachim Breitner Date: Tue Oct 28 15:25:20 2014 +0100 Preserve oneShotInfo in CoreTidy >--------------------------------------------------------------- 81af0699037a7fa51a3dbf937084722210d8311d compiler/coreSyn/CoreTidy.lhs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/coreSyn/CoreTidy.lhs b/compiler/coreSyn/CoreTidy.lhs index 56da494..563e965 100644 --- a/compiler/coreSyn/CoreTidy.lhs +++ b/compiler/coreSyn/CoreTidy.lhs @@ -153,6 +153,7 @@ tidyIdBndr env@(tidy_env, var_env) id -- Note [Tidy IdInfo] new_info = vanillaIdInfo `setOccInfo` occInfo old_info `setUnfoldingInfo` new_unf + `setOneShotInfo` oneShotInfo old_info old_info = idInfo id old_unf = unfoldingInfo old_info new_unf | isEvaldUnfolding old_unf = evaldUnfolding From git at git.haskell.org Tue Oct 28 14:33:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 14:33:47 +0000 (UTC) Subject: [commit: ghc] wip/oneShot's head updated: Preserve oneShotInfo in CoreTidy (81af069) Message-ID: <20141028143347.496B53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/oneShot' now includes: 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 f653aab Add GHC.Prim.oneShot 04ad665 Add oneShot demo file 5b0aefa Make travis happy 67abb9c Use oneShot in the definition of foldl etc. 7df4ba4 Put one-Shot info in the interface 81af069 Preserve oneShotInfo in CoreTidy From git at git.haskell.org Tue Oct 28 14:36:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 14:36:46 +0000 (UTC) Subject: [commit: ghc] master: base: Refactor/clean-up *List modules (75979f3) Message-ID: <20141028143646.568513A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/75979f3661ff16ec44528a23005ac1be2b9683fe/ghc >--------------------------------------------------------------- commit 75979f3661ff16ec44528a23005ac1be2b9683fe Author: David Feuer Date: Tue Oct 28 15:26:39 2014 +0100 base: Refactor/clean-up *List modules This gets rid of all hand-unboxing in `GHC.List` and moves `Foldable` requirements from `Data.OldList` into `GHC.List` (preparatory work for addressing #9716). Specifically, this moves the definition of `maximum`, `minimum`, `foldl'`, `foldl1`, `foldl1'`, `sum`, and `product` into `GHC.List` (which now needs to import `GHC.Num`) Make `take`, `drop`, `length`, and `!!` generally saner (see also #9510) Performance overall seems minimally affected. Some things go up; some things go down; nothing moves horribly much. The code is much easier to read. Differential Revision: https://phabricator.haskell.org/D380 >--------------------------------------------------------------- 75979f3661ff16ec44528a23005ac1be2b9683fe libraries/base/Data/Foldable.hs | 2 +- libraries/base/Data/OldList.hs | 72 ----- libraries/base/GHC/List.lhs | 348 +++++++++++++-------- testsuite/tests/perf/compiler/T4007.stdout | 2 +- .../tests/simplCore/should_compile/T3772.stdout | 25 +- .../tests/simplCore/should_compile/T7360.stderr | 8 +- 6 files changed, 238 insertions(+), 219 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 75979f3661ff16ec44528a23005ac1be2b9683fe From git at git.haskell.org Tue Oct 28 22:44:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 22:44:47 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Put one-Shot info in the interface (28a000e) Message-ID: <20141028224447.CF5593A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/28a000e17577a837a3dfdd92196f9f6c2c4b4dbe/ghc >--------------------------------------------------------------- commit 28a000e17577a837a3dfdd92196f9f6c2c4b4dbe Author: Joachim Breitner Date: Tue Oct 28 13:02:40 2014 +0100 Put one-Shot info in the interface >--------------------------------------------------------------- 28a000e17577a837a3dfdd92196f9f6c2c4b4dbe compiler/coreSyn/CoreTidy.lhs | 12 ++++++++++++ compiler/iface/IfaceSyn.lhs | 30 ++++++++++++++++-------------- compiler/iface/IfaceType.lhs | 29 +++++++++++++++++++++++++++-- compiler/iface/MkIface.lhs | 9 ++++++++- compiler/iface/TcIface.lhs | 7 +++++-- 5 files changed, 68 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 28a000e17577a837a3dfdd92196f9f6c2c4b4dbe From git at git.haskell.org Tue Oct 28 22:44:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 22:44:50 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Add GHC.Prim.oneShot (d27eb19) Message-ID: <20141028224450.671623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/d27eb195223dbdd9de3248be903b6b2dc44422b1/ghc >--------------------------------------------------------------- commit d27eb195223dbdd9de3248be903b6b2dc44422b1 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 >--------------------------------------------------------------- d27eb195223dbdd9de3248be903b6b2dc44422b1 compiler/basicTypes/MkId.lhs | 31 +++++++++++++++++++++++++++++-- compiler/prelude/PrelNames.lhs | 3 ++- libraries/base/GHC/Event/Manager.hs | 6 +++--- 3 files changed, 34 insertions(+), 6 deletions(-) diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index bf1c199..34045db 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -135,7 +135,8 @@ ghcPrimIds seqId, magicDictId, coerceId, - proxyHashId + proxyHashId, + oneShotId ] \end{code} @@ -1016,7 +1017,7 @@ another gun with which to shoot yourself in the foot. \begin{code} lazyIdName, unsafeCoerceName, nullAddrName, seqName, realWorldName, voidPrimIdName, coercionTokenName, - magicDictName, coerceName, proxyName, dollarName :: Name + 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 @@ -1028,6 +1029,7 @@ magicDictName = mkWiredInIdName gHC_PRIM (fsLit "magicDict") magicDict coerceName = mkWiredInIdName gHC_PRIM (fsLit "coerce") coerceKey coerceId proxyName = mkWiredInIdName gHC_PRIM (fsLit "proxy#") proxyHashKey proxyHashId dollarName = mkWiredInIdName gHC_BASE (fsLit "$") dollarIdKey dollarId +oneShotName = mkWiredInIdName gHC_PRIM (fsLit "oneShot") oneShotKey oneShotId \end{code} \begin{code} @@ -1119,6 +1121,17 @@ lazyId = pcMiscPrelId lazyIdName ty info info = noCafIdInfo ty = mkForAllTys [alphaTyVar] (mkFunTy alphaTy alphaTy) +oneShotId :: Id -- See Note [The oneShot function] +oneShotId = pcMiscPrelId oneShotName ty info + where + info = noCafIdInfo `setInlinePragInfo` alwaysInlinePragma + `setUnfoldingInfo` mkCompulsoryUnfolding rhs + ty = mkForAllTys [alphaTyVar, betaTyVar] (mkFunTy fun_ty fun_ty) + fun_ty = mkFunTy alphaTy betaTy + [body, x] = mkTemplateLocals [fun_ty, alphaTy] + x' = setOneShotLambda x + rhs = mkLams [alphaTyVar, betaTyVar, body, x'] $ Var body `App` Var x + -------------------------------------------------------------------------------- magicDictId :: Id -- See Note [magicDictId magic] @@ -1253,6 +1266,20 @@ See Trac #3259 for a real world example. lazyId is defined in GHC.Base, so we don't *have* to inline it. If it appears un-applied, we'll end up just calling it. +Note [The oneShot function] +~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +In the context of making left-folds fuse somewhat okish (see ticket #7994 +and Note [Left folds via right fold]) it was determined that it would be useful +if library authors could explicitly tell the compiler that a certain lambda is +called at most once. The oneShot function allows that. + +Like most magic functions it has a compulsary unfolding, so there is no need +for a real definition somewhere. It uses `setOneShotLambda` on the lambdas +binder, that is the whole magic. It is only effective if this bits survives as +long as possible and makes it into the interface in unfoldings (See Note +[Preserve OneShotInfo]). Also see https://ghc.haskell.org/trac/ghc/wiki/OneShot. + Note [magicDictId magic] ~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/prelude/PrelNames.lhs b/compiler/prelude/PrelNames.lhs index 4e98739..73d1cf3 100644 --- a/compiler/prelude/PrelNames.lhs +++ b/compiler/prelude/PrelNames.lhs @@ -1686,10 +1686,11 @@ rootMainKey, runMainKey :: Unique rootMainKey = mkPreludeMiscIdUnique 101 runMainKey = mkPreludeMiscIdUnique 102 -thenIOIdKey, lazyIdKey, assertErrorIdKey :: Unique +thenIOIdKey, lazyIdKey, assertErrorIdKey, oneShotKey :: Unique thenIOIdKey = mkPreludeMiscIdUnique 103 lazyIdKey = mkPreludeMiscIdUnique 104 assertErrorIdKey = mkPreludeMiscIdUnique 105 +oneShotKey = mkPreludeMiscIdUnique 106 breakpointIdKey, breakpointCondIdKey, breakpointAutoIdKey, breakpointJumpIdKey, breakpointCondJumpIdKey, diff --git a/libraries/base/GHC/Event/Manager.hs b/libraries/base/GHC/Event/Manager.hs index 2041379..29edd97 100644 --- a/libraries/base/GHC/Event/Manager.hs +++ b/libraries/base/GHC/Event/Manager.hs @@ -167,10 +167,10 @@ newDefaultBackend = error "no back end for this platform" -- | Create a new event manager. new :: Bool -> IO EventManager -new oneShot = newWith oneShot =<< newDefaultBackend +new isOneShot = newWith isOneShot =<< newDefaultBackend newWith :: Bool -> Backend -> IO EventManager -newWith oneShot be = do +newWith isOneShot be = do iofds <- fmap (listArray (0, callbackArraySize-1)) $ replicateM callbackArraySize (newMVar =<< IT.new 8) ctrl <- newControl False @@ -187,7 +187,7 @@ newWith oneShot be = do , emState = state , emUniqueSource = us , emControl = ctrl - , emOneShot = oneShot + , emOneShot = isOneShot , emLock = lockVar } registerControlFd mgr (controlReadFd ctrl) evtRead From git at git.haskell.org Tue Oct 28 22:44:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 22:44:53 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Use oneShot in the definition of foldl etc. (12530cb) Message-ID: <20141028224453.15A7A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/12530cb05dc75bbdf79b9ac51442eb41f9d8b0fa/ghc >--------------------------------------------------------------- commit 12530cb05dc75bbdf79b9ac51442eb41f9d8b0fa 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] >--------------------------------------------------------------- 12530cb05dc75bbdf79b9ac51442eb41f9d8b0fa libraries/base/Data/OldList.hs | 4 +++- libraries/base/GHC/List.lhs | 33 ++++++++++++++++++++++----------- 2 files changed, 25 insertions(+), 12 deletions(-) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index 00bc660..78b5fe1 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) + -- 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 52fab6f..5632d5c 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -186,10 +186,22 @@ 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 (-call-ary, 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] and especially [Eta expanding thunks] +-} -- ---------------------------------------------------------------------------- @@ -197,11 +209,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. @@ -257,7 +266,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 @@ -294,7 +304,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' `seq` b' `c` g b' +scanlFB' f c = \b g -> oneShot (\x -> let b' = f x b in b' `seq` b' `c` g b') + -- See Note [Left folds via right fold] {-# INLINE [0] flipSeqScanl' #-} flipSeqScanl' :: a -> b -> a From git at git.haskell.org Tue Oct 28 22:44:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 22:44:56 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Add oneShot demo file (d49da7d) Message-ID: <20141028224456.081D43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/d49da7d491a90e020727a7b61f4bb0c2dfc41148/ghc >--------------------------------------------------------------- commit d49da7d491a90e020727a7b61f4bb0c2dfc41148 Author: Joachim Breitner Date: Mon Oct 6 23:04:02 2014 +0200 Add oneShot demo file (if you remove {-# GHC_OPTIONS -fno-call-arity #-} then both functions have the same Core). Obviously, this patch is not meant to be merged. >--------------------------------------------------------------- d49da7d491a90e020727a7b61f4bb0c2dfc41148 OneShotTest.hs | 22 ++++++++++++++++++++++ 1 file changed, 22 insertions(+) diff --git a/OneShotTest.hs b/OneShotTest.hs new file mode 100644 index 0000000..b595285 --- /dev/null +++ b/OneShotTest.hs @@ -0,0 +1,22 @@ +{-# OPTIONS_GHC -fno-call-arity #-} + +module OneShotTest (foldlB, foldlA, fooA, fooB, fooC) where + +import GHC.Prim (oneShot) + +foldlA, foldlB :: (x -> a -> a) -> a -> [x] -> a + +foldlA k a xs = foldr (\v f a -> f (v `k` a)) id xs a +{-# INLINEABLE foldlA #-} + +foldlB k a xs = foldr (\v f -> oneShot (\ a -> f (v `k` a))) id xs a +{-# INLINEABLE foldlB #-} + +f :: Int -> Bool +f 0 = True +f 1 = False +{-# NOINLINE f #-} + +fooA = foldlA (+) 0 . filter f +fooB = foldlB (+) 0 . filter f +fooC = foldl (+) 0 . filter f From git at git.haskell.org Tue Oct 28 22:44:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 28 Oct 2014 22:44:58 +0000 (UTC) Subject: [commit: ghc] wip/oneShot's head updated: Add oneShot demo file (d49da7d) Message-ID: <20141028224458.2E6D83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/oneShot' now includes: 75979f3 base: Refactor/clean-up *List modules 28a000e Put one-Shot info in the interface d27eb19 Add GHC.Prim.oneShot 12530cb Use oneShot in the definition of foldl etc. d49da7d Add oneShot demo file From git at git.haskell.org Wed Oct 29 07:20:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 29 Oct 2014 07:20:55 +0000 (UTC) Subject: [commit: ghc] master: Reorder GHC.List; fix performance regressions (5f69c8e) Message-ID: <20141029072055.993B63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5f69c8efd94862261bc6730f8dd80c2b67b430ad/ghc >--------------------------------------------------------------- commit 5f69c8efd94862261bc6730f8dd80c2b67b430ad Author: David Feuer Date: Wed Oct 29 08:15:08 2014 +0100 Reorder GHC.List; fix performance regressions Rearrange some oddly placed code. Modify `take` to make the fold unconditionally strict in the passed `Int`. This clears up the `fft2` regression. This fixes #9740. Differential Revision: https://phabricator.haskell.org/D390 >--------------------------------------------------------------- 5f69c8efd94862261bc6730f8dd80c2b67b430ad libraries/base/GHC/List.lhs | 110 ++++++++++++++++++++++---------------------- 1 file changed, 56 insertions(+), 54 deletions(-) diff --git a/libraries/base/GHC/List.lhs b/libraries/base/GHC/List.lhs index 52fab6f..89c33d6 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -1,6 +1,7 @@ \begin{code} {-# LANGUAGE Trustworthy #-} {-# LANGUAGE CPP, NoImplicitPrelude, ScopedTypeVariables, MagicHash #-} +{-# LANGUAGE BangPatterns #-} {-# OPTIONS_HADDOCK hide #-} ----------------------------------------------------------------------------- @@ -132,7 +133,7 @@ lenAcc (_:ys) n = lenAcc ys (n+1) -- when we need it to and give good performance. {-# INLINE [0] lengthFB #-} lengthFB :: x -> (Int -> Int) -> Int -> Int -lengthFB _ r = \ a -> a `seq` r (a + 1) +lengthFB _ r = \ !a -> r (a + 1) {-# INLINE [0] idLength #-} idLength :: Int -> Int @@ -280,9 +281,9 @@ scanl' :: (b -> a -> b) -> b -> [a] -> [b] scanl' = scanlGo' where scanlGo' :: (b -> a -> b) -> b -> [a] -> [b] - scanlGo' f q ls = q `seq` q : (case ls of - [] -> [] - x:xs -> scanlGo' f (f q x) xs) + scanlGo' f !q ls = q : (case ls of + [] -> [] + x:xs -> scanlGo' f (f q x) xs) -- Note [scanl rewrite rules] {-# RULES @@ -294,11 +295,11 @@ 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' `seq` b' `c` g b' +scanlFB' f c = \b g x -> let !b' = f x b in b' `c` g b' {-# INLINE [0] flipSeqScanl' #-} flipSeqScanl' :: a -> b -> a -flipSeqScanl' = flip seq +flipSeqScanl' a !_b = a {- Note [scanl rewrite rules] @@ -527,38 +528,6 @@ dropWhile p xs@(x:xs') -- It is an instance of the more general 'Data.List.genericTake', -- in which @n@ may be of any integral type. take :: Int -> [a] -> [a] - --- | 'drop' @n xs@ returns the suffix of @xs@ --- after the first @n@ elements, or @[]@ if @n > 'length' xs@: --- --- > drop 6 "Hello World!" == "World!" --- > drop 3 [1,2,3,4,5] == [4,5] --- > drop 3 [1,2] == [] --- > drop 3 [] == [] --- > drop (-1) [1,2] == [1,2] --- > drop 0 [1,2] == [1,2] --- --- It is an instance of the more general 'Data.List.genericDrop', --- in which @n@ may be of any integral type. -drop :: Int -> [a] -> [a] - --- | 'splitAt' @n xs@ returns a tuple where first element is @xs@ prefix of --- length @n@ and second element is the remainder of the list: --- --- > splitAt 6 "Hello World!" == ("Hello ","World!") --- > splitAt 3 [1,2,3,4,5] == ([1,2,3],[4,5]) --- > splitAt 1 [1,2,3] == ([1],[2,3]) --- > splitAt 3 [1,2,3] == ([1,2,3],[]) --- > splitAt 4 [1,2,3] == ([1,2,3],[]) --- > splitAt 0 [1,2,3] == ([],[1,2,3]) --- > splitAt (-1) [1,2,3] == ([],[1,2,3]) --- --- It is equivalent to @('take' n xs, 'drop' n xs)@ when @n@ is not @_|_@ --- (@splitAt _|_ xs = _|_@). --- 'splitAt' is an instance of the more general 'Data.List.genericSplitAt', --- in which @n@ may be of any integral type. -splitAt :: Int -> [a] -> ([a],[a]) - #ifdef USE_REPORT_PRELUDE take n _ | n <= 0 = [] take _ [] = [] @@ -580,16 +549,19 @@ unsafeTake m (x:xs) = x : unsafeTake (m - 1) xs {-# RULES "unsafeTake" [~1] forall n xs . unsafeTake n xs = - build (\c nil -> foldr (takeFB c nil) (takeConst nil) xs n) -"unsafeTakeList" [1] forall n xs . foldr (takeFB (:) []) (takeConst []) xs n = - unsafeTake n xs + build (\c nil -> foldr (takeFB c nil) (flipSeqTake nil) xs n) +"unsafeTakeList" [1] forall n xs . foldr (takeFB (:) []) (flipSeqTake []) xs n + = unsafeTake n xs #-} -{-# NOINLINE [0] takeConst #-} --- just a version of const that doesn't get inlined too early, so we --- can spot it in rules. -takeConst :: a -> Int -> a -takeConst x _ = x +{-# INLINE [0] flipSeqTake #-} +-- Just flip seq, specialized to Int, but not inlined too early. +-- It's important to force the numeric argument here, even though +-- it's not used. Otherwise, take n [] doesn't force n. This is +-- bad for strictness analysis and unboxing, and leads to test suite +-- performance regressions. +flipSeqTake :: a -> Int -> a +flipSeqTake x !_n = x {-# INLINE [0] takeFB #-} takeFB :: (a -> b -> b) -> b -> a -> (Int -> b) -> Int -> b @@ -602,15 +574,25 @@ takeFB c n x xs = \ m -> case m of 1 -> x `c` n _ -> x `c` xs (m - 1) - #endif + +-- | 'drop' @n xs@ returns the suffix of @xs@ +-- after the first @n@ elements, or @[]@ if @n > 'length' xs@: +-- +-- > drop 6 "Hello World!" == "World!" +-- > drop 3 [1,2,3,4,5] == [4,5] +-- > drop 3 [1,2] == [] +-- > drop 3 [] == [] +-- > drop (-1) [1,2] == [1,2] +-- > drop 0 [1,2] == [1,2] +-- +-- It is an instance of the more general 'Data.List.genericDrop', +-- in which @n@ may be of any integral type. +drop :: Int -> [a] -> [a] #ifdef USE_REPORT_PRELUDE drop n xs | n <= 0 = xs drop _ [] = [] drop n (_:xs) = drop (n-1) xs - -splitAt n xs = (take n xs, drop n xs) - #else /* hack away */ {-# INLINE drop #-} drop n ls @@ -623,7 +605,28 @@ drop n ls unsafeDrop _ [] = [] unsafeDrop 1 (_:xs) = xs unsafeDrop m (_:xs) = unsafeDrop (m - 1) xs +#endif + +-- | 'splitAt' @n xs@ returns a tuple where first element is @xs@ prefix of +-- length @n@ and second element is the remainder of the list: +-- +-- > splitAt 6 "Hello World!" == ("Hello ","World!") +-- > splitAt 3 [1,2,3,4,5] == ([1,2,3],[4,5]) +-- > splitAt 1 [1,2,3] == ([1],[2,3]) +-- > splitAt 3 [1,2,3] == ([1,2,3],[]) +-- > splitAt 4 [1,2,3] == ([1,2,3],[]) +-- > splitAt 0 [1,2,3] == ([],[1,2,3]) +-- > splitAt (-1) [1,2,3] == ([],[1,2,3]) +-- +-- It is equivalent to @('take' n xs, 'drop' n xs)@ when @n@ is not @_|_@ +-- (@splitAt _|_ xs = _|_@). +-- 'splitAt' is an instance of the more general 'Data.List.genericSplitAt', +-- in which @n@ may be of any integral type. +splitAt :: Int -> [a] -> ([a],[a]) +#ifdef USE_REPORT_PRELUDE +splitAt n xs = (take n xs, drop n xs) +#else splitAt n ls | n <= 0 = ([], ls) | otherwise = splitAt' n ls @@ -634,7 +637,6 @@ splitAt n ls splitAt' m (x:xs) = (x:xs', xs'') where (xs', xs'') = splitAt' (m - 1) xs - #endif /* USE_REPORT_PRELUDE */ -- | 'span', applied to a predicate @p@ and a list @xs@, returns a tuple where @@ -866,7 +868,7 @@ xs !! n foldr2 :: (a -> b -> c -> c) -> c -> [a] -> [b] -> c foldr2 k z = go where - go [] ys = ys `seq` z -- see #9495 for the seq + go [] !_ys = z -- see #9495 for the ! go _xs [] = z go (x:xs) (y:ys) = k x y (go xs ys) {-# INLINE [0] foldr2 #-} @@ -910,7 +912,7 @@ Zips for larger tuples are in the List module. -- list preserve semantics. {-# NOINLINE [1] zip #-} zip :: [a] -> [b] -> [(a,b)] -zip [] bs = bs `seq` [] -- see #9495 for the seq +zip [] !_bs = [] -- see #9495 for the ! zip _as [] = [] zip (a:as) (b:bs) = (a,b) : zip as bs @@ -959,7 +961,7 @@ zip3 _ _ _ = [] {-# NOINLINE [1] zipWith #-} zipWith :: (a->b->c) -> [a]->[b]->[c] -zipWith _f [] bs = bs `seq` [] -- see #9495 for the seq +zipWith _f [] !_bs = [] -- see #9495 for the ! zipWith _f _as [] = [] zipWith f (a:as) (b:bs) = f a b : zipWith f as bs From git at git.haskell.org Wed Oct 29 09:38:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 29 Oct 2014 09:38:37 +0000 (UTC) Subject: [commit: ghc] master: Update Haddock submodule for collapsible section support (f109085) Message-ID: <20141029093837.DFD1F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f1090855d9b8d33b3194364dcca0683d89049f03/ghc >--------------------------------------------------------------- commit f1090855d9b8d33b3194364dcca0683d89049f03 Author: Herbert Valerio Riedel Date: Wed Oct 29 10:08:26 2014 +0100 Update Haddock submodule for collapsible section support This also updates a few occurences of recently added "Example" headings to make use of this new feature for testing >--------------------------------------------------------------- f1090855d9b8d33b3194364dcca0683d89049f03 libraries/base/Data/Bool.hs | 2 +- libraries/base/Data/Functor.hs | 6 +++--- libraries/base/Text/Printf.hs | 2 +- utils/haddock | 2 +- 4 files changed, 6 insertions(+), 6 deletions(-) diff --git a/libraries/base/Data/Bool.hs b/libraries/base/Data/Bool.hs index ace5acf..1537198 100644 --- a/libraries/base/Data/Bool.hs +++ b/libraries/base/Data/Bool.hs @@ -37,7 +37,7 @@ import GHC.Base -- -- /Since: 4.7.0.0/ -- --- __Examples__: +-- ==== __Examples__ -- -- Basic usage: -- diff --git a/libraries/base/Data/Functor.hs b/libraries/base/Data/Functor.hs index 010ab50..0896947 100644 --- a/libraries/base/Data/Functor.hs +++ b/libraries/base/Data/Functor.hs @@ -33,7 +33,7 @@ infixl 4 <$> -- | An infix synonym for 'fmap'. -- --- __Examples__: +-- ==== __Examples__ -- -- Convert from a 'Maybe' 'Int' to a 'Maybe' 'String' using 'show': -- @@ -70,7 +70,7 @@ infixl 4 $> -- -- /Since: 4.7.0.0/ -- --- __Examples__: +-- ==== __Examples__ -- -- Replace the contents of a 'Maybe' 'Int' with a constant 'String': -- @@ -103,7 +103,7 @@ infixl 4 $> -- | @'void' value@ discards or ignores the result of evaluation, such -- as the return value of an 'IO' action. -- --- __Examples__: +-- ==== __Examples__ -- -- Replace the contents of a 'Maybe' 'Int' with unit: -- diff --git a/libraries/base/Text/Printf.hs b/libraries/base/Text/Printf.hs index d20e077..7cf4204 100644 --- a/libraries/base/Text/Printf.hs +++ b/libraries/base/Text/Printf.hs @@ -246,7 +246,7 @@ import System.IO -- * Haskell 'printf' will place a zero after a decimal point when -- possible. -- --- Examples: +-- ==== __Examples__ -- -- > > printf "%d\n" (23::Int) -- > 23 diff --git a/utils/haddock b/utils/haddock index c3f27a9..3fb325a 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit c3f27a96bd2a1ec14f441c72a2df95c16c2c5408 +Subproject commit 3fb325a2ca6b6397905116024922d079447a2e08 From git at git.haskell.org Wed Oct 29 14:48:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 29 Oct 2014 14:48:10 +0000 (UTC) Subject: [commit: ghc] master: Really fix fft2 regression. #9740 (64d0a19) Message-ID: <20141029144810.A87883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/64d0a198be05c7baff36e43ab96928a402f00a19/ghc >--------------------------------------------------------------- commit 64d0a198be05c7baff36e43ab96928a402f00a19 Author: David Feuer Date: Wed Oct 29 15:47:57 2014 +0100 Really fix fft2 regression. #9740 Rewrite `take` more aggressively for fusion. Add some more explicit strictness to `unsafeTake` and `unsafeDrop` that seems to help code size and allocation just a drop in some nofib tests. They were not previously strict in their numerical arguments, but always called in contexts where those had been forced; it didn't make a difference in simple test cases, but made a small difference for nofib. See #9740. Differential Revision: https://phabricator.haskell.org/D394 >--------------------------------------------------------------- 64d0a198be05c7baff36e43ab96928a402f00a19 libraries/base/GHC/List.lhs | 34 ++++++++++++++++++++-------------- 1 file changed, 20 insertions(+), 14 deletions(-) diff --git a/libraries/base/GHC/List.lhs b/libraries/base/GHC/List.lhs index 89c33d6..6a93033 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -533,23 +533,29 @@ take n _ | n <= 0 = [] take _ [] = [] take n (x:xs) = x : take (n-1) xs #else --- We always want to inline this to take advantage of a known --- length argument sign. -{-# INLINE take #-} + +{- We always want to inline this to take advantage of a known length argument +sign. Note, however, that it's important for the RULES to grab take, rather +than trying to INLINE take immediately and then letting the RULES grab +unsafeTake. Presumably the latter approach doesn't grab it early enough; it led +to an allocation regression in nofib/fft2. -} +{-# INLINE [1] take #-} take n xs | 0 < n = unsafeTake n xs | otherwise = [] -- A version of take that takes the whole list if it's given an argument less --- than 1. This does the same thing as the fold version. +-- than 1. {-# NOINLINE [1] unsafeTake #-} unsafeTake :: Int -> [a] -> [a] -unsafeTake _ [] = [] -unsafeTake 1 (x: _) = [x] -unsafeTake m (x:xs) = x : unsafeTake (m - 1) xs +unsafeTake !_ [] = [] +unsafeTake 1 (x: _) = [x] +unsafeTake m (x:xs) = x : unsafeTake (m - 1) xs {-# RULES -"unsafeTake" [~1] forall n xs . unsafeTake n xs = - build (\c nil -> foldr (takeFB c nil) (flipSeqTake nil) xs n) +"take" [~1] forall n xs . take n xs = + build (\c nil -> if 0 < n + then foldr (takeFB c nil) (flipSeqTake nil) xs n + else nil) "unsafeTakeList" [1] forall n xs . foldr (takeFB (:) []) (flipSeqTake []) xs n = unsafeTake n xs #-} @@ -558,8 +564,8 @@ unsafeTake m (x:xs) = x : unsafeTake (m - 1) xs -- Just flip seq, specialized to Int, but not inlined too early. -- It's important to force the numeric argument here, even though -- it's not used. Otherwise, take n [] doesn't force n. This is --- bad for strictness analysis and unboxing, and leads to test suite --- performance regressions. +-- bad for strictness analysis and unboxing, and leads to increased +-- allocation in T7257. flipSeqTake :: a -> Int -> a flipSeqTake x !_n = x @@ -602,9 +608,9 @@ drop n ls -- A version of drop that drops the whole list if given an argument -- less than 1 unsafeDrop :: Int -> [a] -> [a] - unsafeDrop _ [] = [] - unsafeDrop 1 (_:xs) = xs - unsafeDrop m (_:xs) = unsafeDrop (m - 1) xs + unsafeDrop !_ [] = [] + unsafeDrop 1 (_:xs) = xs + unsafeDrop m (_:xs) = unsafeDrop (m - 1) xs #endif -- | 'splitAt' @n xs@ returns a tuple where first element is @xs@ prefix of From git at git.haskell.org Wed Oct 29 23:16:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 29 Oct 2014 23:16:39 +0000 (UTC) Subject: [commit: ghc] master: Fixed unused variable warning on mingw32/i686 in rts/Linker.c (208a0c2) Message-ID: <20141029231639.AF25A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/208a0c207c1001da0fe63e9640e2a7e0e11c4aff/ghc >--------------------------------------------------------------- commit 208a0c207c1001da0fe63e9640e2a7e0e11c4aff Author: Gintautas Miliauskas Date: Wed Oct 29 18:16:12 2014 -0500 Fixed unused variable warning on mingw32/i686 in rts/Linker.c The warning was breaking validate.sh runs due to -Wall. Reviewers: austin Reviewed By: austin Subscribers: #ghc_windows_task_force, thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D400 >--------------------------------------------------------------- 208a0c207c1001da0fe63e9640e2a7e0e11c4aff rts/Linker.c | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/rts/Linker.c b/rts/Linker.c index c40086d..35cee2c 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -3706,8 +3706,8 @@ allocateImageAndTrampolines ( PAGE_EXECUTE_READWRITE); if (image == NULL) { - errorBelch("%" PATH_FMT ": failed to allocate memory for image", - arch_name); + errorBelch("%" PATH_FMT ": failed to allocate memory for image for %s", + arch_name, member_name); return NULL; } From git at git.haskell.org Thu Oct 30 04:03:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 04:03:40 +0000 (UTC) Subject: [commit: hsc2hs] master: Make --cross-compile handle negative enum values. (10696fe) Message-ID: <20141030040340.0BA5B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hsc2hs On branch : master Link : http://git.haskell.org/hsc2hs.git/commitdiff/10696fe17c9d2b4e3498684c6ffbd9f44eda53c4 >--------------------------------------------------------------- commit 10696fe17c9d2b4e3498684c6ffbd9f44eda53c4 Author: Stephen Paul Weber Date: Wed Oct 29 23:02:50 2014 -0500 Make --cross-compile handle negative enum values. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 10696fe17c9d2b4e3498684c6ffbd9f44eda53c4 CrossCodegen.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/CrossCodegen.hs b/CrossCodegen.hs index 687f5be..bb275ff 100644 --- a/CrossCodegen.hs +++ b/CrossCodegen.hs @@ -452,7 +452,7 @@ computeEnum z@(ZCursor (Special _ _ enumText) _ _) = let hsName = fromMaybe (haskellize cName) maybeHsName return $ hsName ++ " :: " ++ stringify enumType ++ "\n" ++ - hsName ++ " = " ++ stringify constructor ++ " " ++ show constValue ++ "\n" + hsName ++ " = " ++ stringify constructor ++ " " ++ showsPrec 11 constValue "\n" where concatM l = liftM concat . forM l computeEnum _ = error "computeEnum argument isn't a Special" From git at git.haskell.org Thu Oct 30 04:05:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 04:05:18 +0000 (UTC) Subject: [commit: ghc] master: hsc2hs: Update submodule (f9ca529) Message-ID: <20141030040518.283BD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f9ca529d3b35f24e7d4193489f48609584bd5a37/ghc >--------------------------------------------------------------- commit f9ca529d3b35f24e7d4193489f48609584bd5a37 Author: Austin Seipp Date: Wed Oct 29 23:04:59 2014 -0500 hsc2hs: Update submodule This makes sure the --cross-compile mode can handle negative enum values. Differential Revision: https://phabricator.haskell.org/D301 Signed-off-by: Austin Seipp >--------------------------------------------------------------- f9ca529d3b35f24e7d4193489f48609584bd5a37 utils/hsc2hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/hsc2hs b/utils/hsc2hs index 286dd5d..10696fe 160000 --- a/utils/hsc2hs +++ b/utils/hsc2hs @@ -1 +1 @@ -Subproject commit 286dd5d6bf83115404ec6e9e194711554390e976 +Subproject commit 10696fe17c9d2b4e3498684c6ffbd9f44eda53c4 From git at git.haskell.org Thu Oct 30 04:15:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 04:15:35 +0000 (UTC) Subject: [commit: ghc] master: Convert GHCi sources from .lhs to .hs (322810e) Message-ID: <20141030041535.13FF53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/322810e32cb18d7749e255937437ff2ef99dca3f/ghc >--------------------------------------------------------------- commit 322810e32cb18d7749e255937437ff2ef99dca3f Author: Rodlogic Date: Wed Oct 29 23:12:54 2014 -0500 Convert GHCi sources from .lhs to .hs Summary: Signed-off-by: Rodlogic Test Plan: Does it compile? Reviewers: hvr, austin Reviewed By: austin Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D319 >--------------------------------------------------------------- 322810e32cb18d7749e255937437ff2ef99dca3f compiler/ghci/{ByteCodeAsm.lhs => ByteCodeAsm.hs} | 12 +- compiler/ghci/{ByteCodeGen.lhs => ByteCodeGen.hs} | 13 +- .../ghci/{ByteCodeInstr.lhs => ByteCodeInstr.hs} | 12 +- .../ghci/{ByteCodeItbls.lhs => ByteCodeItbls.hs} | 21 +-- .../ghci/{ByteCodeLink.lhs => ByteCodeLink.hs} | 33 ++--- compiler/ghci/{Linker.lhs => Linker.hs} | 141 +++++++++------------ compiler/ghci/{ObjLink.lhs => ObjLink.hs} | 12 +- 7 files changed, 93 insertions(+), 151 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 322810e32cb18d7749e255937437ff2ef99dca3f From git at git.haskell.org Thu Oct 30 04:15:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 04:15:37 +0000 (UTC) Subject: [commit: ghc] master: Fix #9236 Error on read from closed handle (257cbec) Message-ID: <20141030041537.ABECC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/257cbec2f605c31d335a6709b43754a88f184d9d/ghc >--------------------------------------------------------------- commit 257cbec2f605c31d335a6709b43754a88f184d9d Author: David Feuer Date: Wed Oct 29 23:13:07 2014 -0500 Fix #9236 Error on read from closed handle Summary: Fixes #9236. My testing indicates that this does *not* lead to problems with broken pipes and such, but further testing is required. It found a bug in haddock; I've submitted a pull request upstream. Reviewers: ekmett, austin Reviewed By: ekmett, austin Subscribers: rwbarton, thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D327 GHC Trac Issues: #9236 >--------------------------------------------------------------- 257cbec2f605c31d335a6709b43754a88f184d9d libraries/base/GHC/IO/Handle/Text.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/libraries/base/GHC/IO/Handle/Text.hs b/libraries/base/GHC/IO/Handle/Text.hs index de48bf4..88ec3c4 100644 --- a/libraries/base/GHC/IO/Handle/Text.hs +++ b/libraries/base/GHC/IO/Handle/Text.hs @@ -389,8 +389,11 @@ lazyRead handle = unsafeInterleaveIO $ withHandle "hGetContents" handle $ \ handle_ -> do case haType handle_ of - ClosedHandle -> return (handle_, "") SemiClosedHandle -> lazyReadBuffered handle handle_ + ClosedHandle + -> ioException + (IOError (Just handle) IllegalOperation "hGetContents" + "delayed read on closed handle" Nothing Nothing) _ -> ioException (IOError (Just handle) IllegalOperation "hGetContents" "illegal handle type" Nothing Nothing) From git at git.haskell.org Thu Oct 30 04:15:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 04:15:40 +0000 (UTC) Subject: [commit: ghc] master: Use snwprintf instead of swprintf in rts/Linker.c. (5ce1266) Message-ID: <20141030041540.41F293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5ce1266a7d323fd4fe4262f07be908d65e5b5b43/ghc >--------------------------------------------------------------- commit 5ce1266a7d323fd4fe4262f07be908d65e5b5b43 Author: Gintautas Miliauskas Date: Wed Oct 29 23:13:31 2014 -0500 Use snwprintf instead of swprintf in rts/Linker.c. Summary: swprintf has different signatures in mingw32, where it does not include the buffer size, and in mingw-w64, where it does. That of course breaks the code as mingw-w64 treats the pointer to the format string as a size_t. snwprintf is available in both environments and is consistent, so use that instead. Reviewers: simonmar, austin Reviewed By: austin Subscribers: #ghc_windows_task_force, thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D372 GHC Trac Issues: #9726 >--------------------------------------------------------------- 5ce1266a7d323fd4fe4262f07be908d65e5b5b43 rts/Linker.c | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/rts/Linker.c b/rts/Linker.c index 35cee2c..7d029c6 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1968,18 +1968,19 @@ addDLL( pathchar *dll_name ) point character (.) to indicate that the module name has no extension. */ - buf = stgMallocBytes((pathlen(dll_name) + 10) * sizeof(wchar_t), "addDLL"); - swprintf(buf, L"%s.DLL", dll_name); + size_t bufsize = pathlen(dll_name) + 10; + buf = stgMallocBytes(bufsize * sizeof(wchar_t), "addDLL"); + snwprintf(buf, bufsize, L"%s.DLL", dll_name); instance = LoadLibraryW(buf); if (instance == NULL) { if (GetLastError() != ERROR_MOD_NOT_FOUND) goto error; // KAA: allow loading of drivers (like winspool.drv) - swprintf(buf, L"%s.DRV", dll_name); + snwprintf(buf, bufsize, L"%s.DRV", dll_name); instance = LoadLibraryW(buf); if (instance == NULL) { if (GetLastError() != ERROR_MOD_NOT_FOUND) goto error; // #1883: allow loading of unix-style libfoo.dll DLLs - swprintf(buf, L"lib%s.DLL", dll_name); + snwprintf(buf, bufsize, L"lib%s.DLL", dll_name); instance = LoadLibraryW(buf); if (instance == NULL) { goto error; From git at git.haskell.org Thu Oct 30 04:15:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 04:15:42 +0000 (UTC) Subject: [commit: ghc] master: Avoid setting -Werror=unused-but-set-variable on Windows. (acb3295) Message-ID: <20141030041542.D39793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/acb3295c69179159ba8230baff4104414c1db2c2/ghc >--------------------------------------------------------------- commit acb3295c69179159ba8230baff4104414c1db2c2 Author: Gintautas Miliauskas Date: Wed Oct 29 23:13:51 2014 -0500 Avoid setting -Werror=unused-but-set-variable on Windows. Summary: The option is not needed (it was only intended to override Debian's default) and causes an error if the host ghc's mingw is too old (which the script does not detect). Fixes T9727 Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D373 GHC Trac Issues: #9727 >--------------------------------------------------------------- acb3295c69179159ba8230baff4104414c1db2c2 mk/validate-settings.mk | 3 +++ 1 file changed, 3 insertions(+) diff --git a/mk/validate-settings.mk b/mk/validate-settings.mk index b05b289..52aa648 100644 --- a/mk/validate-settings.mk +++ b/mk/validate-settings.mk @@ -15,7 +15,10 @@ ifneq "$(GccIsClang)" "YES" # Debian doesn't turn -Werror=unused-but-set-variable on by default, so # we turn it on explicitly for consistency with other users ifeq "$(GccLT46)" "NO" +# Never set the flag on Windows as the host gcc may be too old. +ifneq "$(HostOS_CPP)" "mingw32" SRC_CC_WARNING_OPTS += -Werror=unused-but-set-variable +endif # gcc 4.6 gives 3 warning for giveCapabilityToTask not being inlined SRC_CC_WARNING_OPTS += -Wno-error=inline endif From git at git.haskell.org Thu Oct 30 04:15:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 04:15:45 +0000 (UTC) Subject: [commit: ghc] master: Extra CRs are now filtered out from the source file for :list. (45175e1) Message-ID: <20141030041545.D5BF93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/45175e13edad452843207491d01cdbce0bedbbd4/ghc >--------------------------------------------------------------- commit 45175e13edad452843207491d01cdbce0bedbbd4 Author: Gintautas Miliauskas Date: Wed Oct 29 23:14:17 2014 -0500 Extra CRs are now filtered out from the source file for :list. Fixes #9367. Reviewers: austin Reviewed By: austin Subscribers: #ghc_windows_task_force, thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D382 GHC Trac Issues: #9367 >--------------------------------------------------------------- 45175e13edad452843207491d01cdbce0bedbbd4 ghc/InteractiveUI.hs | 3 ++- testsuite/tests/ghci/scripts/Makefile | 5 +++++ testsuite/tests/ghci/scripts/T9367-raw.stdout | 6 ++++++ testsuite/tests/ghci/scripts/T9367.hs | 2 ++ testsuite/tests/ghci/scripts/T9367.script | 4 ++++ testsuite/tests/ghci/scripts/all.T | 4 ++++ 6 files changed, 23 insertions(+), 1 deletion(-) diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 3192d20..ed4ea7b 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -2934,7 +2934,8 @@ listModuleLine modl line = do listAround :: MonadIO m => RealSrcSpan -> Bool -> InputT m () listAround pan do_highlight = do contents <- liftIO $ BS.readFile (unpackFS file) - let ls = BS.split '\n' contents + -- Drop carriage returns to avoid duplicates, see #9367. + let ls = BS.split '\n' $ BS.filter (/= '\r') contents ls' = take (line2 - line1 + 1 + pad_before + pad_after) $ drop (line1 - 1 - pad_before) $ ls fst_line = max 1 (line1 - pad_before) diff --git a/testsuite/tests/ghci/scripts/Makefile b/testsuite/tests/ghci/scripts/Makefile index 73f6203..873de43 100644 --- a/testsuite/tests/ghci/scripts/Makefile +++ b/testsuite/tests/ghci/scripts/Makefile @@ -39,3 +39,8 @@ ghci056_setup: T6106_prep: '$(TEST_HC)' $(TEST_HC_OPTS) -v0 --make T6106_preproc +.PHONY: T9367 +T9367: + '$(TEST_HC)' $(TEST_HC_OPTS) --interactive -v0 -ignore-dot-ghci < T9367.script > T9367-raw.run.stdout + cmp T9367-raw.run.stdout T9367-raw.stdout + diff --git a/testsuite/tests/ghci/scripts/T9367-raw.stdout b/testsuite/tests/ghci/scripts/T9367-raw.stdout new file mode 100644 index 0000000..69da032 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T9367-raw.stdout @@ -0,0 +1,6 @@ +Breakpoint 0 activated at T9367.hs:1:5-9 +"Stopped at T9367.hs:1:5-9 +_result :: [Char] = _ +1 x = "abc" + ^^^^^ +2 main = print x diff --git a/testsuite/tests/ghci/scripts/T9367.hs b/testsuite/tests/ghci/scripts/T9367.hs new file mode 100644 index 0000000..0f24fa4 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T9367.hs @@ -0,0 +1,2 @@ +x = "abc" +main = print x diff --git a/testsuite/tests/ghci/scripts/T9367.script b/testsuite/tests/ghci/scripts/T9367.script new file mode 100644 index 0000000..afc89a8 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T9367.script @@ -0,0 +1,4 @@ +:l T9367 +:b 1 +:main +:list diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index ede9807..624f431 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -43,6 +43,10 @@ test('ghci024', when(fast(), skip), run_command, ['$MAKE -s --no-print-directory ghci024']) +test('T9367', + when(fast() or config.os != 'mingw32', skip), + run_command, + ['$MAKE -s --no-print-directory T9367']) test('ghci025', normal, ghci_script, ['ghci025.script']) test('ghci026', normal, ghci_script, ['ghci026.script']) From git at git.haskell.org Thu Oct 30 04:15:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 04:15:48 +0000 (UTC) Subject: [commit: ghc] master: Updated stale ghcpkg05.stderr-mingw32. (f10b67a) Message-ID: <20141030041548.7598B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f10b67a0d3ca588629f1cddd2f5a2bf1e1a4bc8e/ghc >--------------------------------------------------------------- commit f10b67a0d3ca588629f1cddd2f5a2bf1e1a4bc8e Author: Gintautas Miliauskas Date: Wed Oct 29 23:14:28 2014 -0500 Updated stale ghcpkg05.stderr-mingw32. Looks like the mingw32-specific test was accidentally forgotten after changing the code and the expected outputs for non OS-specific tests. Reviewers: austin Reviewed By: austin Subscribers: #ghc_windows_task_force, thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D383 >--------------------------------------------------------------- f10b67a0d3ca588629f1cddd2f5a2bf1e1a4bc8e testsuite/tests/cabal/ghcpkg05.stderr-mingw32 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/cabal/ghcpkg05.stderr-mingw32 b/testsuite/tests/cabal/ghcpkg05.stderr-mingw32 index ac51816..55a82814 100644 --- a/testsuite/tests/cabal/ghcpkg05.stderr-mingw32 +++ b/testsuite/tests/cabal/ghcpkg05.stderr-mingw32 @@ -15,4 +15,4 @@ The following packages are broken, either because they have a problem listed above, or because they depend on a broken package. testpkg-2.0 testpkg-3.0 -ghc-pkg.exe: unregistering testpkg-2.0 would break the following packages: testpkg-3.0 (use --force to override) +ghc-pkg.exe: unregistering would break the following packages: testpkg-3.0 (use --force to override) From git at git.haskell.org Thu Oct 30 04:15:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 04:15:51 +0000 (UTC) Subject: [commit: ghc] master: Do not use a relative path for echo in tests/ghci/prog013. (3d27f69) Message-ID: <20141030041551.2795E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3d27f6975467ea05bc7e8aaf9e5a3c26d1cd20a6/ghc >--------------------------------------------------------------- commit 3d27f6975467ea05bc7e8aaf9e5a3c26d1cd20a6 Author: Gintautas Miliauskas Date: Wed Oct 29 23:14:38 2014 -0500 Do not use a relative path for echo in tests/ghci/prog013. Trying to run /usr/bin/echo fails when running tests on Windows, but using plain "echo" works fine. I think it's fine to assume the environment is not doing anything particularly funny... Summary: ...with echo... Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, simonmar, #ghc_windows_task_force Differential Revision: https://phabricator.haskell.org/D384 >--------------------------------------------------------------- 3d27f6975467ea05bc7e8aaf9e5a3c26d1cd20a6 testsuite/tests/ghci/prog013/prog013.script | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/ghci/prog013/prog013.script b/testsuite/tests/ghci/prog013/prog013.script index b9df968..d4b91de 100644 --- a/testsuite/tests/ghci/prog013/prog013.script +++ b/testsuite/tests/ghci/prog013/prog013.script @@ -1,4 +1,4 @@ -:set editor /bin/echo +:set editor echo :l Good.hs :e :l Bad.hs From git at git.haskell.org Thu Oct 30 04:15:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 04:15:53 +0000 (UTC) Subject: [commit: ghc] master: Add __GLASGOW_HASKELL_TH__=YES/NO to CPP definitions (c211f8e) Message-ID: <20141030041553.C4C2D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c211f8e55b8dd1d43854ce3c4554ffbafb0009f9/ghc >--------------------------------------------------------------- commit c211f8e55b8dd1d43854ce3c4554ffbafb0009f9 Author: Joachim Breitner Date: Wed Oct 29 23:15:07 2014 -0500 Add __GLASGOW_HASKELL_TH__=YES/NO to CPP definitions Test Plan: None really. Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D386 GHC Trac Issues: #9734 >--------------------------------------------------------------- c211f8e55b8dd1d43854ce3c4554ffbafb0009f9 compiler/main/DriverPipeline.hs | 6 ++++++ docs/users_guide/phases.xml | 15 +++++++++++++++ 2 files changed, 21 insertions(+) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 6bc67e7..66c6e97 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -2100,6 +2100,11 @@ doCpp dflags raw input_fn output_fn = do backend_defs <- getBackendDefs dflags +#ifdef GHCI + let th_defs = [ "-D__GLASGOW_HASKELL_TH__=YES" ] +#else + let th_defs = [ "-D__GLASGOW_HASKELL_TH__=NO" ] +#endif -- Default CPP defines in Haskell source ghcVersionH <- getGhcVersionPathName dflags let hsSourceCppOpts = @@ -2112,6 +2117,7 @@ doCpp dflags raw input_fn output_fn = do ++ map SysTools.Option hsSourceCppOpts ++ map SysTools.Option target_defs ++ map SysTools.Option backend_defs + ++ map SysTools.Option th_defs ++ map SysTools.Option hscpp_opts ++ map SysTools.Option sse_defs ++ map SysTools.Option avx_defs diff --git a/docs/users_guide/phases.xml b/docs/users_guide/phases.xml index 085ebbf..b05de99 100644 --- a/docs/users_guide/phases.xml +++ b/docs/users_guide/phases.xml @@ -468,6 +468,21 @@ $ cat foo.hspp + __GLASGOW_HASKELL_TH__ + __GLASGOW_HASKELL_TH__ + + + + This is set to YES when the compiler supports Template Haskell, and to + NO when not. The latter is the case for a stage-1 compiler during bootstrapping, or + on architectures where the interpreter is not available. + + + + + + + __GLASGOW_HASKELL_LLVM__ __GLASGOW_HASKELL_LLVM__ From git at git.haskell.org Thu Oct 30 04:15:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 04:15:56 +0000 (UTC) Subject: [commit: ghc] master: Added mingw32-specific expected stdout files for tests/driver/sigof{01, 02, 03} (93c776a) Message-ID: <20141030041556.ED73D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/93c776a445a7692fb87d7f480671187ecb8c730e/ghc >--------------------------------------------------------------- commit 93c776a445a7692fb87d7f480671187ecb8c730e Author: Gintautas Miliauskas Date: Wed Oct 29 23:15:25 2014 -0500 Added mingw32-specific expected stdout files for tests/driver/sigof{01,02,03} Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D398 >--------------------------------------------------------------- 93c776a445a7692fb87d7f480671187ecb8c730e testsuite/tests/driver/sigof01/sigof01m.stdout-mingw32 | 7 +++++++ .../driver/sigof02/{sigof02dm.stdout => sigof02dm.stdout-mingw32} | 4 ++-- .../driver/sigof02/{sigof02m.stdout => sigof02m.stdout-mingw32} | 8 ++++---- 3 files changed, 13 insertions(+), 6 deletions(-) diff --git a/testsuite/tests/driver/sigof01/sigof01m.stdout-mingw32 b/testsuite/tests/driver/sigof01/sigof01m.stdout-mingw32 new file mode 100644 index 0000000..9fe3257 --- /dev/null +++ b/testsuite/tests/driver/sigof01/sigof01m.stdout-mingw32 @@ -0,0 +1,7 @@ +[1 of 3] Compiling A ( A.hs, tmp_sigof01m\A.o ) +[2 of 3] Compiling B[sig of A] ( B.hsig, nothing ) +[3 of 3] Compiling Main ( Main.hs, tmp_sigof01m\Main.o ) +Linking tmp_sigof01m/Main.exe ... +False +T +True diff --git a/testsuite/tests/driver/sigof02/sigof02dm.stdout b/testsuite/tests/driver/sigof02/sigof02dm.stdout-mingw32 similarity index 69% copy from testsuite/tests/driver/sigof02/sigof02dm.stdout copy to testsuite/tests/driver/sigof02/sigof02dm.stdout-mingw32 index 14ee837..3c8a1fa 100644 --- a/testsuite/tests/driver/sigof02/sigof02dm.stdout +++ b/testsuite/tests/driver/sigof02/sigof02dm.stdout-mingw32 @@ -1,7 +1,7 @@ [1 of 3] Compiling MapAsSet[sig of Data.Map.Lazy] ( MapAsSet.hsig, nothing ) [2 of 3] Compiling Map[sig of Data.Map.Lazy] ( Map.hsig, nothing ) -[3 of 3] Compiling Main ( Double.hs, tmp_sigof02dm/Main.o ) -Linking tmp_sigof02dm/Double ... +[3 of 3] Compiling Main ( Double.hs, tmp_sigof02dm\Main.o ) +Linking tmp_sigof02dm/Double.exe ... False fromList [0,6] [(0,"foo"),(6,"foo")] diff --git a/testsuite/tests/driver/sigof02/sigof02m.stdout b/testsuite/tests/driver/sigof02/sigof02m.stdout-mingw32 similarity index 53% copy from testsuite/tests/driver/sigof02/sigof02m.stdout copy to testsuite/tests/driver/sigof02/sigof02m.stdout-mingw32 index 41cc4a7..65b1857 100644 --- a/testsuite/tests/driver/sigof02/sigof02m.stdout +++ b/testsuite/tests/driver/sigof02/sigof02m.stdout-mingw32 @@ -1,9 +1,9 @@ [1 of 2] Compiling Map[sig of Data.Map.Strict] ( Map.hsig, nothing ) -[2 of 2] Compiling Main ( Main.hs, tmp_sigof02m/Main.o ) -Linking tmp_sigof02m/StrictMain ... +[2 of 2] Compiling Main ( Main.hs, tmp_sigof02m\Main.o ) +Linking tmp_sigof02m/StrictMain.exe ... [1 of 2] Compiling Map[sig of Data.Map.Lazy] ( Map.hsig, nothing ) [sig-of changed] -[2 of 2] Compiling Main ( Main.hs, tmp_sigof02m/Main.o ) [Map changed] -Linking tmp_sigof02m/LazyMain ... +[2 of 2] Compiling Main ( Main.hs, tmp_sigof02m\Main.o ) [Map changed] +Linking tmp_sigof02m/LazyMain.exe ... False [(0,"foo"),(6,"foo")] fromList [(0,"foo"),(6,"foo")] From git at git.haskell.org Thu Oct 30 09:20:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 09:20:03 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Put one-Shot info in the interface (5273cae) Message-ID: <20141030092003.54F703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/5273cae62623358c4918482abeac91e41f6f1abc/ghc >--------------------------------------------------------------- commit 5273cae62623358c4918482abeac91e41f6f1abc Author: Joachim Breitner Date: Tue Oct 28 13:02:40 2014 +0100 Put one-Shot info in the interface >--------------------------------------------------------------- 5273cae62623358c4918482abeac91e41f6f1abc compiler/coreSyn/CoreTidy.lhs | 12 ++++++++++++ compiler/iface/IfaceSyn.lhs | 30 ++++++++++++++++-------------- compiler/iface/IfaceType.lhs | 29 +++++++++++++++++++++++++++-- compiler/iface/MkIface.lhs | 9 ++++++++- compiler/iface/TcIface.lhs | 7 +++++-- 5 files changed, 68 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 5273cae62623358c4918482abeac91e41f6f1abc From git at git.haskell.org Thu Oct 30 09:20:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 09:20:07 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Add GHC.Prim.oneShot (13a1ebe) Message-ID: <20141030092007.0B96C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/13a1ebef026784df9f7662f5aaaff004fbc2ec6c/ghc >--------------------------------------------------------------- commit 13a1ebef026784df9f7662f5aaaff004fbc2ec6c 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 >--------------------------------------------------------------- 13a1ebef026784df9f7662f5aaaff004fbc2ec6c compiler/basicTypes/MkId.lhs | 33 ++++++++++++++++++++-- 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, 121 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 13a1ebef026784df9f7662f5aaaff004fbc2ec6c From git at git.haskell.org Thu Oct 30 09:20:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 09:20:09 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Add oneShot demo file (f9b4c5e) Message-ID: <20141030092009.EF5C13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/f9b4c5e8664bf94b4328ea11ac64e6266474fcdf/ghc >--------------------------------------------------------------- commit f9b4c5e8664bf94b4328ea11ac64e6266474fcdf Author: Joachim Breitner Date: Mon Oct 6 23:04:02 2014 +0200 Add oneShot demo file (if you remove {-# GHC_OPTIONS -fno-call-arity #-} then both functions have the same Core). Obviously, this patch is not meant to be merged. >--------------------------------------------------------------- f9b4c5e8664bf94b4328ea11ac64e6266474fcdf OneShotTest.hs | 22 ++++++++++++++++++++++ 1 file changed, 22 insertions(+) diff --git a/OneShotTest.hs b/OneShotTest.hs new file mode 100644 index 0000000..b595285 --- /dev/null +++ b/OneShotTest.hs @@ -0,0 +1,22 @@ +{-# OPTIONS_GHC -fno-call-arity #-} + +module OneShotTest (foldlB, foldlA, fooA, fooB, fooC) where + +import GHC.Prim (oneShot) + +foldlA, foldlB :: (x -> a -> a) -> a -> [x] -> a + +foldlA k a xs = foldr (\v f a -> f (v `k` a)) id xs a +{-# INLINEABLE foldlA #-} + +foldlB k a xs = foldr (\v f -> oneShot (\ a -> f (v `k` a))) id xs a +{-# INLINEABLE foldlB #-} + +f :: Int -> Bool +f 0 = True +f 1 = False +{-# NOINLINE f #-} + +fooA = foldlA (+) 0 . filter f +fooB = foldlB (+) 0 . filter f +fooC = foldl (+) 0 . filter f From git at git.haskell.org Thu Oct 30 09:20:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 09:20:12 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Use oneShot in the definition of foldl etc. (21d0630) Message-ID: <20141030092012.891873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/21d063040b8b4e0745c2e7a427791a1871cfdd4b/ghc >--------------------------------------------------------------- commit 21d063040b8b4e0745c2e7a427791a1871cfdd4b 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] >--------------------------------------------------------------- 21d063040b8b4e0745c2e7a427791a1871cfdd4b libraries/base/Data/OldList.hs | 6 ++++-- libraries/base/GHC/List.lhs | 33 ++++++++++++++++++++++----------- 2 files changed, 26 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..4826be6 100644 --- a/libraries/base/GHC/List.lhs +++ b/libraries/base/GHC/List.lhs @@ -187,10 +187,22 @@ 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] and especially [Eta expanding thunks] +-} -- ---------------------------------------------------------------------------- @@ -198,11 +210,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 +267,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 +305,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 Thu Oct 30 09:20:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 09:20:14 +0000 (UTC) Subject: [commit: ghc] wip/oneShot's head updated: Add oneShot demo file (f9b4c5e) Message-ID: <20141030092014.B7C0C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/oneShot' now includes: 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} 5273cae Put one-Shot info in the interface 13a1ebe Add GHC.Prim.oneShot 21d0630 Use oneShot in the definition of foldl etc. f9b4c5e Add oneShot demo file From git at git.haskell.org Thu Oct 30 10:51:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 10:51:38 +0000 (UTC) Subject: [commit: ghc] master: Comments only (9de5240) Message-ID: <20141030105138.393793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9de52406522dc43722f5ee06ba89a63da133099e/ghc >--------------------------------------------------------------- commit 9de52406522dc43722f5ee06ba89a63da133099e Author: Jan Stolarek Date: Thu Oct 30 11:51:10 2014 +0100 Comments only >--------------------------------------------------------------- 9de52406522dc43722f5ee06ba89a63da133099e compiler/simplCore/FloatIn.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/simplCore/FloatIn.lhs b/compiler/simplCore/FloatIn.lhs index 3527702..13d03ef 100644 --- a/compiler/simplCore/FloatIn.lhs +++ b/compiler/simplCore/FloatIn.lhs @@ -188,7 +188,7 @@ unlifted function arguments to be ok-for-speculation. Note [Floating in past a lambda group] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -* We must be careful about floating inside inside a value lambda. +* We must be careful about floating inside a value lambda. That risks losing laziness. The float-out pass might rescue us, but then again it might not. From git at git.haskell.org Thu Oct 30 11:59:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 11:59:14 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Test commit (40bb559) Message-ID: <20141030115914.D33523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/40bb55941163553f883f5694af3b71535de0de17/ghc >--------------------------------------------------------------- commit 40bb55941163553f883f5694af3b71535de0de17 Author: Simon Peyton Jones Date: Thu Oct 30 11:59:27 2014 +0000 Test commit >--------------------------------------------------------------- 40bb55941163553f883f5694af3b71535de0de17 compiler/typecheck/Flattening-notes | 1 - 1 file changed, 1 deletion(-) diff --git a/compiler/typecheck/Flattening-notes b/compiler/typecheck/Flattening-notes index bc56d28..8d7e376 100644 --- a/compiler/typecheck/Flattening-notes +++ b/compiler/typecheck/Flattening-notes @@ -52,7 +52,6 @@ Order of finding iprovements typecheck/should_compile TcTypeNatSimple [exit code non-0] (normal) - ----------------- Unflattening ~~~~~~~~~~~~ From git at git.haskell.org Thu Oct 30 12:52:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:52:20 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Wibbles (a02cd3f) Message-ID: <20141030125220.74F9B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/a02cd3f7c518b9fa15a15e71572a9d389560b7b4/ghc >--------------------------------------------------------------- commit a02cd3f7c518b9fa15a15e71572a9d389560b7b4 Author: Simon Peyton Jones Date: Wed Oct 29 08:34:34 2014 +0000 Wibbles >--------------------------------------------------------------- a02cd3f7c518b9fa15a15e71572a9d389560b7b4 compiler/typecheck/TcMType.lhs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcMType.lhs b/compiler/typecheck/TcMType.lhs index 91abcd3..b48e307 100644 --- a/compiler/typecheck/TcMType.lhs +++ b/compiler/typecheck/TcMType.lhs @@ -37,7 +37,7 @@ module TcMType ( -- Instantiation tcInstTyVars, newSigTyVar, tcInstType, - tcInstSkolTyVars, tcInstSuperSkolTyVars,tcInstSuperSkolTyVarsX, + tcInstSkolTyVars, tcInstSuperSkolTyVarsX, tcInstSigTyVarsLoc, tcInstSigTyVars, tcInstSkolType, tcSkolDFunType, tcSuperSkolTyVars, @@ -197,7 +197,7 @@ tcInstType inst_tyvars ty tcSkolDFunType :: Type -> TcM ([TcTyVar], TcThetaType, TcType) -- Instantiate a type signature with skolem constants. -- We could give them fresh names, but no need to do so -tcSkolDFunType ty = tcInstType (\tvs -> return (tcSuperSkolTyVars tvs)) ty +tcSkolDFunType ty = tcInstType tcInstSuperSkolTyVars ty tcSuperSkolTyVars :: [TyVar] -> (TvSubst, [TcTyVar]) -- Make skolem constants, but do *not* give them new names, as above @@ -216,8 +216,8 @@ tcSuperSkolTyVar subst tv tcInstSkolTyVars :: [TyVar] -> TcM (TvSubst, [TcTyVar]) tcInstSkolTyVars = tcInstSkolTyVars' False emptyTvSubst -tcInstSuperSkolTyVars :: [TyVar] -> TcM [TcTyVar] -tcInstSuperSkolTyVars = fmap snd . tcInstSuperSkolTyVarsX emptyTvSubst +tcInstSuperSkolTyVars :: [TyVar] -> TcM (TvSubst, [TcTyVar]) +tcInstSuperSkolTyVars = tcInstSuperSkolTyVarsX emptyTvSubst tcInstSuperSkolTyVarsX :: TvSubst -> [TyVar] -> TcM (TvSubst, [TcTyVar]) tcInstSuperSkolTyVarsX subst = tcInstSkolTyVars' True subst From git at git.haskell.org Thu Oct 30 12:52:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:52:23 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: White space and comments (8fe2231) Message-ID: <20141030125223.0889D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/8fe2231a50522d1253dfa7eeed1023de4327d7a7/ghc >--------------------------------------------------------------- commit 8fe2231a50522d1253dfa7eeed1023de4327d7a7 Author: Simon Peyton Jones Date: Wed Oct 29 08:35:03 2014 +0000 White space and comments >--------------------------------------------------------------- 8fe2231a50522d1253dfa7eeed1023de4327d7a7 testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.hs b/testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.hs index 42d1be9..cce5aa3 100644 --- a/testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.hs +++ b/testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.hs @@ -43,16 +43,19 @@ f x = {- Assume x:beta - From g1 we get (forall b. F Int ~ [beta]) + From g1 we get [W] (forall b. F Int ~ [beta]) - From g2 we get (forall c. 0 => F Int ~ [[alpha]] /\ C beta [c]) + From g2 we get [W] (forall c. 0 => F Int ~ [[alpha]] /\ C beta [c]) (g2 is not generalised; the forall comes from the TEx pattern) Floating we get F Int ~ [beta], F Int ~ [[alpha]], alpha ~ alpha', forall c. C beta [c] + = { alpha := alpha' } -= beta ~ [alpha'], F Int ~ [[alpha']], forall c. C beta [c] + beta ~ [alpha'], F Int ~ [[alpha']], forall c. C beta [c] + = { beta := [alpha'] F Int ~ [[alpha']], forall c. C [alpha'] [c] + = F Int ~ [[alpha']], forall c. (C [alpha'] [c], alpha' ~ c) -} \ No newline at end of file From git at git.haskell.org Thu Oct 30 12:52:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:52:26 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 (dbb36b5) Message-ID: <20141030125226.DD5933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/dbb36b5210c20f81351d941e9cc2641732c45e9a/ghc >--------------------------------------------------------------- commit dbb36b5210c20f81351d941e9cc2641732c45e9a Merge: 8fe2231 5f69c8e Author: Simon Peyton Jones Date: Wed Oct 29 08:38:48 2014 +0000 Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 Conflicts: compiler/typecheck/Inst.lhs 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 dbb36b5210c20f81351d941e9cc2641732c45e9a From git at git.haskell.org Thu Oct 30 12:52:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:52:29 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Final wibbles (3c17388) Message-ID: <20141030125229.767623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/3c17388f3a23dbed0a69c6e385d57bac1a91f83e/ghc >--------------------------------------------------------------- commit 3c17388f3a23dbed0a69c6e385d57bac1a91f83e Author: Simon Peyton Jones Date: Wed Oct 29 15:07:24 2014 +0000 Final wibbles >--------------------------------------------------------------- 3c17388f3a23dbed0a69c6e385d57bac1a91f83e compiler/stranal/DmdAnal.lhs | 3 +- compiler/typecheck/TcSimplify.lhs | 21 +++++++++++-- compiler/types/Coercion.lhs | 36 +++++++++++----------- compiler/types/FamInstEnv.lhs | 30 +++++++++++++----- .../should_compile/PushedInAsGivens.hs | 9 +++++- testsuite/tests/indexed-types/should_compile/all.T | 2 +- .../indexed-types/should_fail/ExtraTcsUntch.hs | 14 ++++----- .../indexed-types/should_fail/ExtraTcsUntch.stderr | 22 ++++++++----- .../tests/indexed-types/should_fail/T1897b.stderr | 8 +++-- .../tests/indexed-types/should_fail/T4093a.hs | 4 +++ .../tests/indexed-types/should_fail/T4093a.stderr | 17 +++++----- .../tests/simplCore/should_compile/T3772.stdout | 24 +++++++-------- 12 files changed, 118 insertions(+), 72 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 3c17388f3a23dbed0a69c6e385d57bac1a91f83e From git at git.haskell.org Thu Oct 30 12:52:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:52:32 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 (7d57cec) Message-ID: <20141030125232.EDA803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/7d57cec81800f53e6ebb42e84bd1625327902658/ghc >--------------------------------------------------------------- commit 7d57cec81800f53e6ebb42e84bd1625327902658 Merge: 3c17388 64d0a19 Author: Simon Peyton Jones Date: Wed Oct 29 15:07:55 2014 +0000 Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 >--------------------------------------------------------------- 7d57cec81800f53e6ebb42e84bd1625327902658 libraries/base/Data/Bool.hs | 2 +- libraries/base/Data/Functor.hs | 6 +++--- libraries/base/GHC/List.lhs | 34 ++++++++++++++++++++-------------- libraries/base/Text/Printf.hs | 2 +- utils/haddock | 2 +- 5 files changed, 26 insertions(+), 20 deletions(-) From git at git.haskell.org Thu Oct 30 12:52:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:52:35 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14: Merge branch 'wip/new-flatten-skolems-Aug14' of https://git.haskell.org/ghc into wip/new-flatten-skolems-Aug14 (d900c1b) Message-ID: <20141030125235.C27CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/new-flatten-skolems-Aug14 Link : http://ghc.haskell.org/trac/ghc/changeset/d900c1b4bf16620925e444fd29cc5115f302870d/ghc >--------------------------------------------------------------- commit d900c1b4bf16620925e444fd29cc5115f302870d Merge: 7d57cec 40bb559 Author: Simon Peyton Jones Date: Thu Oct 30 12:31:56 2014 +0000 Merge branch 'wip/new-flatten-skolems-Aug14' of https://git.haskell.org/ghc into wip/new-flatten-skolems-Aug14 >--------------------------------------------------------------- d900c1b4bf16620925e444fd29cc5115f302870d compiler/typecheck/Flattening-notes | 1 - 1 file changed, 1 deletion(-) From git at git.haskell.org Thu Oct 30 12:52:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:52:38 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Aug14's head updated: Merge branch 'wip/new-flatten-skolems-Aug14' of https://git.haskell.org/ghc into wip/new-flatten-skolems-Aug14 (d900c1b) Message-ID: <20141030125238.3C3EE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/new-flatten-skolems-Aug14' 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 a02cd3f Wibbles 8fe2231 White space and comments dbb36b5 Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 f109085 Update Haddock submodule for collapsible section support 64d0a19 Really fix fft2 regression. #9740 3c17388 Final wibbles 7d57cec Merge remote-tracking branch 'origin/master' into wip/new-flatten-skolems-Aug14 d900c1b Merge branch 'wip/new-flatten-skolems-Aug14' of https://git.haskell.org/ghc into wip/new-flatten-skolems-Aug14 From git at git.haskell.org Thu Oct 30 12:53:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:53:54 +0000 (UTC) Subject: [commit: ghc] branch 'wip/new-flatten-skolems-Oct14' created Message-ID: <20141030125354.B28883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/new-flatten-skolems-Oct14 Referencing: 9be5cc671099b28aa56d89139f443ecea677de7e From git at git.haskell.org Thu Oct 30 12:53:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:53:57 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Tidy up pretty-printing of SrcLoc and SrcSpan (61940b5) Message-ID: <20141030125357.4AAEB3A300@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/61940b5fbbadb590885904bd072753d57235d708/ghc >--------------------------------------------------------------- commit 61940b5fbbadb590885904bd072753d57235d708 Author: Simon Peyton Jones Date: Wed Oct 29 15:13:41 2014 +0000 Tidy up pretty-printing of SrcLoc and SrcSpan >--------------------------------------------------------------- 61940b5fbbadb590885904bd072753d57235d708 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 Thu Oct 30 12:53:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:53:59 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Improve pretty-printing of type variables (c8d8f92) Message-ID: <20141030125359.D87333A300@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/c8d8f92a74387e2e11223bad5d1a9cd0abd05fb9/ghc >--------------------------------------------------------------- commit c8d8f92a74387e2e11223bad5d1a9cd0abd05fb9 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 >--------------------------------------------------------------- c8d8f92a74387e2e11223bad5d1a9cd0abd05fb9 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 Thu Oct 30 12:54:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:02 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Some refactoring around endPass and debug dumping (80accce) Message-ID: <20141030125402.7E7713A300@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/80accce2c7e596a687253c84af927453d9590c43/ghc >--------------------------------------------------------------- commit 80accce2c7e596a687253c84af927453d9590c43 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 >--------------------------------------------------------------- 80accce2c7e596a687253c84af927453d9590c43 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 80accce2c7e596a687253c84af927453d9590c43 From git at git.haskell.org Thu Oct 30 12:54:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:05 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Simplify the generation of superclass constraints in tcInstDecl2 (b310a0d) Message-ID: <20141030125405.181B03A300@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/b310a0d0b0e3ce3cfb15c234bc5524157b9b54db/ghc >--------------------------------------------------------------- commit b310a0d0b0e3ce3cfb15c234bc5524157b9b54db 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 >--------------------------------------------------------------- b310a0d0b0e3ce3cfb15c234bc5524157b9b54db 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 Thu Oct 30 12:54:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:07 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Add the unfolding and inline-pragma for DFuns in DsBinds, not TcInstDcls (7dfc454) Message-ID: <20141030125407.A46923A300@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/7dfc4543eb387835de5be9634424d42d1b490bad/ghc >--------------------------------------------------------------- commit 7dfc4543eb387835de5be9634424d42d1b490bad 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 >--------------------------------------------------------------- 7dfc4543eb387835de5be9634424d42d1b490bad 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 Thu Oct 30 12:54:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:10 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: White space only (d91da6a) Message-ID: <20141030125410.3CC313A300@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/d91da6a7006c098bdbb6b676ae85d63d63bd1fd6/ghc >--------------------------------------------------------------- commit d91da6a7006c098bdbb6b676ae85d63d63bd1fd6 Author: Simon Peyton Jones Date: Wed Oct 29 16:27:50 2014 +0000 White space only >--------------------------------------------------------------- d91da6a7006c098bdbb6b676ae85d63d63bd1fd6 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 Thu Oct 30 12:54:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:12 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Simplify the API for tcInstTyVars, and make it more consistent with other similar functions (4413b3d) Message-ID: <20141030125412.D59B63A300@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/4413b3d605702e74f94e86321df5323636ba27c5/ghc >--------------------------------------------------------------- commit 4413b3d605702e74f94e86321df5323636ba27c5 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 >--------------------------------------------------------------- 4413b3d605702e74f94e86321df5323636ba27c5 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 4413b3d605702e74f94e86321df5323636ba27c5 From git at git.haskell.org Thu Oct 30 12:54:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:15 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Fix reduceTyFamApp_maybe (ad9c4c9) Message-ID: <20141030125415.820DE3A300@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/ad9c4c9f98edc4d24098c4441c1d9f8feede13ae/ghc >--------------------------------------------------------------- commit ad9c4c9f98edc4d24098c4441c1d9f8feede13ae 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. >--------------------------------------------------------------- ad9c4c9f98edc4d24098c4441c1d9f8feede13ae 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 Thu Oct 30 12:54:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:18 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Refactor skolemising, and newClsInst (f9fcb34) Message-ID: <20141030125418.35D8C3A300@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/f9fcb34b7eaeae5cc08e078cc764f679142b0b63/ghc >--------------------------------------------------------------- commit f9fcb34b7eaeae5cc08e078cc764f679142b0b63 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. >--------------------------------------------------------------- f9fcb34b7eaeae5cc08e078cc764f679142b0b63 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 f9fcb34b7eaeae5cc08e078cc764f679142b0b63 From git at git.haskell.org Thu Oct 30 12:54:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:20 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Rename setRole_maybe to downgradeRole_maybe (c000b69) Message-ID: <20141030125420.C4F8A3A300@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/c000b6999a2fcce09fea885b4fa2bb1e358f717b/ghc >--------------------------------------------------------------- commit c000b6999a2fcce09fea885b4fa2bb1e358f717b 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 >--------------------------------------------------------------- c000b6999a2fcce09fea885b4fa2bb1e358f717b 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 Thu Oct 30 12:54:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:23 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Refactor the treatment of lexically-scoped type variables for instance declarations (19eb2cc) Message-ID: <20141030125423.767D03A300@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/19eb2ccc4cded8d327ec6c3c1a8c1a538c05e35a/ghc >--------------------------------------------------------------- commit 19eb2ccc4cded8d327ec6c3c1a8c1a538c05e35a 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.) >--------------------------------------------------------------- 19eb2ccc4cded8d327ec6c3c1a8c1a538c05e35a 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 19eb2ccc4cded8d327ec6c3c1a8c1a538c05e35a From git at git.haskell.org Thu Oct 30 12:54:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:26 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Get the Untouchables level right in simplifyInfer (b24590f) Message-ID: <20141030125426.1C4853A300@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/b24590fe696e7732964b55372994da5e882e4a8b/ghc >--------------------------------------------------------------- commit b24590fe696e7732964b55372994da5e882e4a8b 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 >--------------------------------------------------------------- b24590fe696e7732964b55372994da5e882e4a8b 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 b24590fe696e7732964b55372994da5e882e4a8b From git at git.haskell.org Thu Oct 30 12:54:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:28 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Normalise the type of an inferred let-binding (6e057f6) Message-ID: <20141030125428.B5BAF3A300@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/6e057f63e3c2674055d2445a6d15f15ce74a7917/ghc >--------------------------------------------------------------- commit 6e057f63e3c2674055d2445a6d15f15ce74a7917 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 >--------------------------------------------------------------- 6e057f63e3c2674055d2445a6d15f15ce74a7917 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 8ec8118..e9a6f82 100644 --- a/compiler/typecheck/TcRnDriver.lhs +++ b/compiler/typecheck/TcRnDriver.lhs @@ -1645,11 +1645,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 Thu Oct 30 12:54:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:31 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: When reporting the context of given constraints, stop when you find one that binds a variable mentioned in the wanted (5d40a36) Message-ID: <20141030125431.5BD9F3A300@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/5d40a36eaad349d8d50f8a0c54d02f434ac328e6/ghc >--------------------------------------------------------------- commit 5d40a36eaad349d8d50f8a0c54d02f434ac328e6 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 >--------------------------------------------------------------- 5d40a36eaad349d8d50f8a0c54d02f434ac328e6 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 Thu Oct 30 12:54:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:34 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Typechecker debug tracing only (61e0c3b) Message-ID: <20141030125434.07C5F3A300@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/61e0c3bbf10652e32c7112fac58b169cf2b2880c/ghc >--------------------------------------------------------------- commit 61e0c3bbf10652e32c7112fac58b169cf2b2880c Author: Simon Peyton Jones Date: Wed Oct 29 17:22:57 2014 +0000 Typechecker debug tracing only >--------------------------------------------------------------- 61e0c3bbf10652e32c7112fac58b169cf2b2880c 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 e9a6f82..3440b4f 100644 --- a/compiler/typecheck/TcRnDriver.lhs +++ b/compiler/typecheck/TcRnDriver.lhs @@ -1920,7 +1920,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 Thu Oct 30 12:54:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:36 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Minor refactoring (no change in functionality) (f132ea5) Message-ID: <20141030125436.9F97A3A300@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/f132ea5db80e89ec8108594751c09242820be276/ghc >--------------------------------------------------------------- commit f132ea5db80e89ec8108594751c09242820be276 Author: Simon Peyton Jones Date: Wed Oct 29 17:51:41 2014 +0000 Minor refactoring (no change in functionality) >--------------------------------------------------------------- f132ea5db80e89ec8108594751c09242820be276 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 Thu Oct 30 12:54:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:39 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Only report "could not deduce s~t from ..." for givens that include equalities (92f4d96) Message-ID: <20141030125439.366A83A300@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/92f4d9637e4e61e38b408b4d90950498bd6abe4c/ghc >--------------------------------------------------------------- commit 92f4d9637e4e61e38b408b4d90950498bd6abe4c 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 >--------------------------------------------------------------- 92f4d9637e4e61e38b408b4d90950498bd6abe4c 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 Thu Oct 30 12:54:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:41 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Don't filter out allegedly-irrelevant bindings with -dppr-debug (91b3ba1) Message-ID: <20141030125441.C715D3A300@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/91b3ba104ff21289813482e64104c953525b4f9a/ghc >--------------------------------------------------------------- commit 91b3ba104ff21289813482e64104c953525b4f9a Author: Simon Peyton Jones Date: Wed Oct 29 17:50:44 2014 +0000 Don't filter out allegedly-irrelevant bindings with -dppr-debug >--------------------------------------------------------------- 91b3ba104ff21289813482e64104c953525b4f9a 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 Thu Oct 30 12:54:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:44 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Define ctEvLoc and ctEvCoercion, and use them (12111e4) Message-ID: <20141030125444.620F43A300@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/12111e4bf4d8892d49e9768a90d48ae306e61371/ghc >--------------------------------------------------------------- commit 12111e4bf4d8892d49e9768a90d48ae306e61371 Author: Simon Peyton Jones Date: Thu Oct 30 09:08:23 2014 +0000 Define ctEvLoc and ctEvCoercion, and use them >--------------------------------------------------------------- 12111e4bf4d8892d49e9768a90d48ae306e61371 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 Thu Oct 30 12:54:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:47 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Test Trac #9211 (e49ce87) Message-ID: <20141030125447.750563A300@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/e49ce87ac6b73c0832b3ed19b68f602698f613e5/ghc >--------------------------------------------------------------- commit e49ce87ac6b73c0832b3ed19b68f602698f613e5 Author: Simon Peyton Jones Date: Thu Oct 30 11:37:39 2014 +0000 Test Trac #9211 >--------------------------------------------------------------- e49ce87ac6b73c0832b3ed19b68f602698f613e5 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 Thu Oct 30 12:54:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:53 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Testsuite error message changes (346815e) Message-ID: <20141030125453.4F80B3A301@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/346815e8adab0442cf06f00cf7b94173395e6e6d/ghc >--------------------------------------------------------------- commit 346815e8adab0442cf06f00cf7b94173395e6e6d Author: Simon Peyton Jones Date: Thu Oct 30 11:41:17 2014 +0000 Testsuite error message changes >--------------------------------------------------------------- 346815e8adab0442cf06f00cf7b94173395e6e6d .../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 +- .../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/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 +- testsuite/tests/typecheck/should_fail/T7453.stderr | 23 +- .../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 +- 120 files changed, 1033 insertions(+), 770 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 346815e8adab0442cf06f00cf7b94173395e6e6d From git at git.haskell.org Thu Oct 30 12:54:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:50 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Test Trac #9708 (9675c2a) Message-ID: <20141030125450.A5C863A300@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/9675c2a0265a1836aed1be80ace82db8b349bc15/ghc >--------------------------------------------------------------- commit 9675c2a0265a1836aed1be80ace82db8b349bc15 Author: Simon Peyton Jones Date: Thu Oct 30 11:39:39 2014 +0000 Test Trac #9708 >--------------------------------------------------------------- 9675c2a0265a1836aed1be80ace82db8b349bc15 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 Thu Oct 30 12:54:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:56 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Source code work in progress (471c877) Message-ID: <20141030125456.A24083A301@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/471c877407255c6633d6783a1737624e8e9ae4bf/ghc >--------------------------------------------------------------- commit 471c877407255c6633d6783a1737624e8e9ae4bf Author: Simon Peyton Jones Date: Thu Oct 30 11:40:48 2014 +0000 Source code work in progress >--------------------------------------------------------------- 471c877407255c6633d6783a1737624e8e9ae4bf compiler/ghc.cabal.in | 1 + compiler/typecheck/Inst.lhs | 19 +- compiler/typecheck/TcCanonical.lhs | 790 ++++++++------------------ compiler/typecheck/TcFlatten.lhs | 1044 ++++++++++++++++++++++++++++++++++ compiler/typecheck/TcInteract.lhs | 840 ++++++++++++++-------------- compiler/typecheck/TcMType.lhs | 139 +---- compiler/typecheck/TcRnTypes.lhs | 155 +++--- compiler/typecheck/TcRules.lhs | 2 - compiler/typecheck/TcSMonad.lhs | 1082 +++++++++++++++++++----------------- compiler/typecheck/TcSimplify.lhs | 401 ++++++------- compiler/typecheck/TcType.lhs | 107 ++-- compiler/typecheck/TcUnify.lhs | 1 - 12 files changed, 2611 insertions(+), 1970 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 471c877407255c6633d6783a1737624e8e9ae4bf From git at git.haskell.org Thu Oct 30 12:54:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:54:59 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Wibble to TcSimplify (d10e03d) Message-ID: <20141030125459.43F983A300@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/d10e03dd81542a44f41841715353c71787ee0b24/ghc >--------------------------------------------------------------- commit d10e03dd81542a44f41841715353c71787ee0b24 Author: Simon Peyton Jones Date: Thu Oct 30 12:10:40 2014 +0000 Wibble to TcSimplify >--------------------------------------------------------------- d10e03dd81542a44f41841715353c71787ee0b24 compiler/typecheck/TcSimplify.lhs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcSimplify.lhs b/compiler/typecheck/TcSimplify.lhs index 52cdf6d..e68129f 100644 --- a/compiler/typecheck/TcSimplify.lhs +++ b/compiler/typecheck/TcSimplify.lhs @@ -1252,7 +1252,8 @@ floatEqualities skols no_given_eqs wanteds@(WC { wc_flat = flats }) (float_eqs, remaining_flats) = partitionBag float_me flats float_me :: Ct -> Bool float_me ct - | EqPred ty1 ty2 <- classifyPredType (ctPred ct) + | let pred = ctPred ct + , EqPred ty1 ty2 <- classifyPredType pred , tyVarsOfType pred `disjointVarSet` skol_set , useful_to_float ty1 ty2 = True From git at git.haskell.org Thu Oct 30 12:55:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 12:55:02 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Add flattening-notes (9be5cc6) Message-ID: <20141030125502.1DD353A300@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/9be5cc671099b28aa56d89139f443ecea677de7e/ghc >--------------------------------------------------------------- commit 9be5cc671099b28aa56d89139f443ecea677de7e Author: Simon Peyton Jones Date: Thu Oct 30 12:11:27 2014 +0000 Add flattening-notes >--------------------------------------------------------------- 9be5cc671099b28aa56d89139f443ecea677de7e 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 Thu Oct 30 15:40:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 15:40:04 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T9732' created Message-ID: <20141030154004.C6F363A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T9732 Referencing: 9f8b67ea4e57b958a95de876d1ee713c99e8d687 From git at git.haskell.org Thu Oct 30 15:40:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 15:40:08 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Binding things matched by an unboxed pattern synonym should require a bang (73e69d0) Message-ID: <20141030154008.098983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/73e69d0616979d9b6969f06b908ec0ff700901b8/ghc >--------------------------------------------------------------- commit 73e69d0616979d9b6969f06b908ec0ff700901b8 Author: Dr. ERDI Gergo Date: Wed Oct 29 11:58:29 2014 +0800 Binding things matched by an unboxed pattern synonym should require a bang >--------------------------------------------------------------- 73e69d0616979d9b6969f06b908ec0ff700901b8 testsuite/tests/patsyn/should_fail/all.T | 1 + testsuite/tests/patsyn/should_fail/unboxed-bind.hs | 8 ++++++++ testsuite/tests/patsyn/should_fail/unboxed-bind.stderr | 9 +++++++++ 3 files changed, 18 insertions(+) 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..037dc0e --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE PatternSynonyms, MagicHash #-} +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..429ed07 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/unboxed-bind.stderr @@ -0,0 +1,9 @@ + +unboxed-bind.hs:1:1: + The IO action ?main? is not defined in module ?Main? + +unboxed-bind.hs:8: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 Oct 30 15:40:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 15:40:10 +0000 (UTC) Subject: [commit: ghc] wip/T9732: Generate two versions of pattern synonym matcher: * one where the continuation is lifted, * one where the continuation is unlifted. (423e9b2) Message-ID: <20141030154010.B2F503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/423e9b28930fb9e6dfcd4a20dd604ec488a2bb1d/ghc >--------------------------------------------------------------- commit 423e9b28930fb9e6dfcd4a20dd604ec488a2bb1d Author: Dr. ERDI Gergo Date: Thu Oct 30 23:07:50 2014 +0800 Generate two versions of pattern synonym matcher: * one where the continuation is lifted, * one where the continuation is unlifted. >--------------------------------------------------------------- 423e9b28930fb9e6dfcd4a20dd604ec488a2bb1d compiler/basicTypes/OccName.lhs | 5 +++-- compiler/basicTypes/PatSyn.lhs | 21 ++++++++++++--------- compiler/deSugar/DsUtils.lhs | 2 +- compiler/iface/BuildTyCl.lhs | 7 ++++--- compiler/iface/IfaceSyn.lhs | 8 ++++++-- compiler/iface/MkIface.lhs | 4 +++- compiler/iface/TcIface.lhs | 4 +++- compiler/typecheck/TcBinds.lhs | 3 ++- compiler/typecheck/TcPatSyn.lhs | 28 +++++++++++++++++----------- 9 files changed, 51 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 423e9b28930fb9e6dfcd4a20dd604ec488a2bb1d From git at git.haskell.org Thu Oct 30 15:40:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 15:40:13 +0000 (UTC) Subject: [commit: ghc] wip/T9732: In PatSyn matchers for unlifted result types, add an extra Void# argument to both cont and fail continuations, so that they are not needlessly strict. (9f8b67e) Message-ID: <20141030154013.4F3A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9732 Link : http://ghc.haskell.org/trac/ghc/changeset/9f8b67ea4e57b958a95de876d1ee713c99e8d687/ghc >--------------------------------------------------------------- commit 9f8b67ea4e57b958a95de876d1ee713c99e8d687 Author: Dr. ERDI Gergo Date: Thu Oct 30 23:38:24 2014 +0800 In PatSyn matchers for unlifted result types, add an extra Void# argument to both cont and fail continuations, so that they are not needlessly strict. >--------------------------------------------------------------- 9f8b67ea4e57b958a95de876d1ee713c99e8d687 compiler/deSugar/DsUtils.lhs | 7 +++++-- compiler/typecheck/TcPatSyn.lhs | 13 ++++++++----- 2 files changed, 13 insertions(+), 7 deletions(-) diff --git a/compiler/deSugar/DsUtils.lhs b/compiler/deSugar/DsUtils.lhs index 503e88c..61fdbca 100644 --- a/compiler/deSugar/DsUtils.lhs +++ b/compiler/deSugar/DsUtils.lhs @@ -348,13 +348,16 @@ 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, make_unstrict cont, make_unstrict fail] where MkCaseAlt{ alt_pat = psyn, alt_bndrs = bndrs, alt_wrapper = wrapper, alt_result = match_result} = alt - matcher = patSynMatcher (isUnLiftedType ty) psyn + is_unlifted = isUnLiftedType ty + matcher = patSynMatcher is_unlifted psyn + make_unstrict | is_unlifted = Lam voidArgId + | otherwise = id mkDataConCase :: Id -> Type -> [CaseAlt DataCon] -> MatchResult mkDataConCase _ _ [] = panic "mkDataConCase: no alternatives" diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index a7ac763..68667d7 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -27,6 +27,7 @@ import Id import IdInfo( IdDetails( VanillaId ) ) import TcBinds import BasicTypes +import MkId import TcSimplify import TcType import VarSet @@ -130,13 +131,15 @@ tcPatSynMatcher :: Located Name tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_dicts prov_theta req_theta pat_ty unlifted = do { let res_kind = if unlifted then unliftedTypeKind else liftedTypeKind + dummy_args = if unlifted then [voidPrimId] else [] ; res_tv <- zonkQuantifiedTyVar =<< newFlexiTyVar res_kind ; matcher_name <- newImplicitBinder name (if unlifted then mkMatcherUnlOcc else mkMatcherOcc) ; let res_ty = TyVarTy res_tv cont_ty = mkSigmaTy ex_tvs prov_theta $ - mkFunTys (map varType args) res_ty + mkFunTys (map varType (dummy_args ++ args)) res_ty + fail_ty = mkFunTys (map varType dummy_args) 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 @@ -145,9 +148,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 ++ dummy_args ++ args) + ; fail <- mkId "fail" fail_ty + ; let fail' = nlHsApps fail $ map nlHsVar dummy_args ; let args = map nlVarPat [scrutinee, cont, fail] From git at git.haskell.org Thu Oct 30 16:54:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 16:54:19 +0000 (UTC) Subject: [commit: ghc] master: Fix test driver python3 compatibility issues (c6d4ae6) Message-ID: <20141030165419.930A23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c6d4ae6f437fb041ea70f3d2b4f7f0d03ff797bf/ghc >--------------------------------------------------------------- commit c6d4ae6f437fb041ea70f3d2b4f7f0d03ff797bf Author: Mateusz Lenik Date: Thu Oct 30 11:50:41 2014 -0500 Fix test driver python3 compatibility issues Summary: Fixes python3 compatibility issues by replacing filter with a list comperhension and a potential issue with python2 when override_flags would be an empty list. Reviewers: austin, thomie Reviewed By: austin, thomie Subscribers: thomie, carter, simonmar, mlen Differential Revision: https://phabricator.haskell.org/D399 GHC Trac Issues: #9230 >--------------------------------------------------------------- c6d4ae6f437fb041ea70f3d2b4f7f0d03ff797bf testsuite/driver/testlib.py | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 3093982..87e37d5 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -920,7 +920,7 @@ def run_command( name, way, cmd ): def ghci_script_without_flag(flag): def apply(name, way, script): - overrides = filter(lambda f: f != flag, getTestOpts().compiler_always_flags) + overrides = [f for f in getTestOpts().compiler_always_flags if f != flag] return ghci_script_override_default_flags(overrides)(name, way, script) return apply @@ -933,7 +933,7 @@ def ghci_script_override_default_flags(overrides): def ghci_script( name, way, script, override_flags = None ): # Use overriden default flags when given - if override_flags: + if override_flags is not None: default_flags = override_flags else: default_flags = getTestOpts().compiler_always_flags @@ -973,14 +973,14 @@ def compile_fail_override_default_flags(overrides): def compile_without_flag(flag): def apply(name, way, extra_opts): - overrides = filter(lambda f: f != flag, getTestOpts().compiler_always_flags) + overrides = [f for f in getTestOpts().compiler_always_flags if f != flag] return compile_override_default_flags(overrides)(name, way, extra_opts) return apply def compile_fail_without_flag(flag): def apply(name, way, extra_opts): - overrides = filter(lambda f: f != flag, getTestOpts().compiler_always_flags) + overrides = [f for f in getTestOpts.compiler_always_flags if f != flag] return compile_fail_override_default_flags(overrides)(name, way, extra_opts) return apply @@ -1225,7 +1225,7 @@ def simple_build( name, way, extra_hc_opts, should_fail, top_mod, link, addsuf, else: cmd_prefix = getTestOpts().compile_cmd_prefix + ' ' - if override_flags: + if override_flags is not None: comp_flags = copy.copy(override_flags) else: comp_flags = copy.copy(getTestOpts().compiler_always_flags) From git at git.haskell.org Thu Oct 30 16:54:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 16:54:22 +0000 (UTC) Subject: [commit: ghc] master: Add notes on change to hGetContents semantics (578bc00) Message-ID: <20141030165422.3444F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/578bc0035a58d254e97e94eefcab88f3d74c7537/ghc >--------------------------------------------------------------- commit 578bc0035a58d254e97e94eefcab88f3d74c7537 Author: David Feuer Date: Thu Oct 30 11:50:58 2014 -0500 Add notes on change to hGetContents semantics Summary: Additionally, move Unicode 7.0 update notice from the compiler section to the base libraries section. Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, simonmar Projects: #ghc Differential Revision: https://phabricator.haskell.org/D401 >--------------------------------------------------------------- 578bc0035a58d254e97e94eefcab88f3d74c7537 docs/users_guide/7.10.1-notes.xml | 22 ++++++++++++++++------ 1 file changed, 16 insertions(+), 6 deletions(-) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 3ca5112..fa7ad1a 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -66,12 +66,6 @@ - GHC has had its internal Unicode database for - parsing updated to the Unicode 7.0 standard. - - - - GHC now checks that all the language extensions required for the inferred type signatures are explicitly enabled. This means that if any of the type signatures inferred in your @@ -212,6 +206,22 @@ echo "[]" > package.conf Version number XXXXX (was 4.7.0.0) + + + GHC has had its internal Unicode database for + parsing updated to the Unicode 7.0 standard. + + + + + Attempting to access a portion of the result of + System.IO.hGetContents that was not yet + read when the handle was closed now throws an exception. + Previously, a lazy read from a closed handle would simply + end the result string, leading to silent or delayed + failures. + + From git at git.haskell.org Thu Oct 30 16:54:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 16:54:25 +0000 (UTC) Subject: [commit: ghc] master: Fixed missing trailing newline bug in pretty printer (995ea1c) Message-ID: <20141030165425.49E413A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/995ea1c8335631d6e4db1ff4da38251b2f396edb/ghc >--------------------------------------------------------------- commit 995ea1c8335631d6e4db1ff4da38251b2f396edb Author: Mateusz Lenik Date: Thu Oct 30 11:53:40 2014 -0500 Fixed missing trailing newline bug in pretty printer Summary: Pretty printer didn't produce trailing newline in strings in error messages. Reviewers: simonpj, austin Reviewed By: austin Subscribers: thomie, carter, simonmar, mlen Differential Revision: https://phabricator.haskell.org/D405 GHC Trac Issues: #9681 >--------------------------------------------------------------- 995ea1c8335631d6e4db1ff4da38251b2f396edb libraries/base/GHC/Show.lhs | 1 + libraries/base/tests/T9681.hs | 3 +++ libraries/base/tests/T9681.stderr | 5 +++++ libraries/base/tests/all.T | 1 + 4 files changed, 10 insertions(+) diff --git a/libraries/base/GHC/Show.lhs b/libraries/base/GHC/Show.lhs index 2834817..d5ed094 100644 --- a/libraries/base/GHC/Show.lhs +++ b/libraries/base/GHC/Show.lhs @@ -386,6 +386,7 @@ showMultiLineString str where go ch s = case break (== '\n') s of (l, _:s'@(_:_)) -> (ch : showLitString l "\\n\\") : go '\\' s' + (l, "\n") -> [ch : showLitString l "\\n\""] (l, _) -> [ch : showLitString l "\""] isDec :: Char -> Bool diff --git a/libraries/base/tests/T9681.hs b/libraries/base/tests/T9681.hs new file mode 100644 index 0000000..b0fd499 --- /dev/null +++ b/libraries/base/tests/T9681.hs @@ -0,0 +1,3 @@ +module T9681 where + +foo = 1 + "\n" diff --git a/libraries/base/tests/T9681.stderr b/libraries/base/tests/T9681.stderr new file mode 100644 index 0000000..7945ff7 --- /dev/null +++ b/libraries/base/tests/T9681.stderr @@ -0,0 +1,5 @@ + +T9681.hs:3:9: + No instance for (Num [Char]) arising from a use of ?+? + In the expression: 1 + "\n" + In an equation for ?foo?: foo = 1 + "\n" diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T index edb5fc3..ee0fb6b 100644 --- a/libraries/base/tests/all.T +++ b/libraries/base/tests/all.T @@ -173,3 +173,4 @@ test('T9111', normal, compile, ['']) test('T9395', normal, compile_and_run, ['']) test('T9532', normal, compile_and_run, ['']) test('T9586', normal, compile, ['']) +test('T9681', normal, compile_fail, ['']) From git at git.haskell.org Thu Oct 30 16:57:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 16:57:06 +0000 (UTC) Subject: [commit: ghc] master: Updated testsuite/.gitignore to exclude some test artifacts on Windows. (1907e81) Message-ID: <20141030165706.2E3753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1907e8196a50100a646b0d70f22468dad7023442/ghc >--------------------------------------------------------------- commit 1907e8196a50100a646b0d70f22468dad7023442 Author: Gintautas Miliauskas Date: Thu Oct 30 11:57:18 2014 -0500 Updated testsuite/.gitignore to exclude some test artifacts on Windows. Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D404 >--------------------------------------------------------------- 1907e8196a50100a646b0d70f22468dad7023442 testsuite/.gitignore | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/testsuite/.gitignore b/testsuite/.gitignore index d3dc9cb..ce5c2c2 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -29,10 +29,12 @@ Thumbs.db .hpc.*/ *.genscript +*.stdout.normalised +*.stdout-mingw32.normalised +*.stdout-ghc.normalised *.stderr.normalised *.stderr-mingw32.normalised *.stderr-ghc.normalised -*.stdout.normalised *.interp.stdout *.interp.stderr *.run.stdout From git at git.haskell.org Thu Oct 30 17:49:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 17:49:16 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Improve error message for a handwritten Typeable instance (b4f7b49) Message-ID: <20141030174916.6743D3A300@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/b4f7b491923a40533f0e47d567e6804bff6f7ddb/ghc >--------------------------------------------------------------- commit b4f7b491923a40533f0e47d567e6804bff6f7ddb Author: Simon Peyton Jones Date: Thu Oct 30 16:33:34 2014 +0000 Improve error message for a handwritten Typeable instance >--------------------------------------------------------------- b4f7b491923a40533f0e47d567e6804bff6f7ddb compiler/typecheck/TcInstDcls.lhs | 37 ++++++++++++---------- 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, 30 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcInstDcls.lhs b/compiler/typecheck/TcInstDcls.lhs index 10bc466..77f1ebd 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 $ @@ -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,15 @@ 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)) + instMsg i = 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 + pp_tc | [_kind, ty] <- is_tys (iSpec i) + , 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..7ea7bdb --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T9687.stderr @@ -0,0 +1,5 @@ + +T9687.hs:1:1: + 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 Thu Oct 30 17:49:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 30 Oct 2014 17:49:19 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Work in progress (859ef91) Message-ID: <20141030174919.16EC33A300@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/859ef913e030cb95cafbbedf0d6288ed8ce6d7bc/ghc >--------------------------------------------------------------- commit 859ef913e030cb95cafbbedf0d6288ed8ce6d7bc Author: Simon Peyton Jones Date: Thu Oct 30 17:49:15 2014 +0000 Work in progress >--------------------------------------------------------------- 859ef913e030cb95cafbbedf0d6288ed8ce6d7bc compiler/typecheck/TcCanonical.lhs | 1 + compiler/typecheck/TcFlatten.lhs | 293 ++++++++++----------- compiler/typecheck/TcInteract.lhs | 36 ++- compiler/typecheck/TcSMonad.lhs | 15 +- testsuite/tests/indexed-types/should_fail/T7786.hs | 4 +- .../tests/indexed-types/should_fail/T7786.stderr | 13 - testsuite/tests/indexed-types/should_fail/all.T | 2 +- 7 files changed, 183 insertions(+), 181 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 859ef913e030cb95cafbbedf0d6288ed8ce6d7bc From git at git.haskell.org Fri Oct 31 08:36:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 08:36:17 +0000 (UTC) Subject: [commit: ghc] master: Drop deprecated `OverlappingInstances` from base (cbb20ab) Message-ID: <20141031083617.A3C923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cbb20ab2c3222da75625bcf41f8ff67a7e9ba5f7/ghc >--------------------------------------------------------------- commit cbb20ab2c3222da75625bcf41f8ff67a7e9ba5f7 Author: Herbert Valerio Riedel Date: Fri Oct 31 08:52:47 2014 +0100 Drop deprecated `OverlappingInstances` from base With #9242 the `OverlappingInstances` extension got deprecated, this commit adapts the only two remaining places in `base` where it was still used. Starting with this commit, the `Typeable (s t)` instance (which seemingly was the motivation for using `OverlappingInstances` in the first place when `Typeable` was neither polykinded nor auto-derived-only, see also commit ce3fd0e02826367e6134a3362d8d37aa114236f5 which introduced overlapping instances) does no longer allow overlapping instances, and there doesn't seem to be any good reason to keep allowing overlapping instance now. This also removes redundant `LANGUAGE`/`OPTIONS_GHC` pragmas from `Data.Typeable` and refactors the language pragmas into more uniform single-line pragmas. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D377 >--------------------------------------------------------------- cbb20ab2c3222da75625bcf41f8ff67a7e9ba5f7 libraries/base/Data/Typeable.hs | 21 +++++---------------- libraries/base/Data/Typeable/Internal.hs | 27 ++++++++++++--------------- libraries/base/base.cabal | 1 - 3 files changed, 17 insertions(+), 32 deletions(-) diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs index f658a9e..ddb9582 100644 --- a/libraries/base/Data/Typeable.hs +++ b/libraries/base/Data/Typeable.hs @@ -1,20 +1,9 @@ +{-# LANGUAGE GADTs #-} +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE Trustworthy #-} -{-# LANGUAGE NoImplicitPrelude - , OverlappingInstances - , ScopedTypeVariables - , FlexibleInstances - , TypeOperators - , PolyKinds - , GADTs - , MagicHash - #-} -{-# OPTIONS_GHC -funbox-strict-fields #-} - --- The -XOverlappingInstances flag allows the user to over-ride --- the instances for Typeable given here. In particular, we provide an instance --- instance ... => Typeable (s a) --- But a user might want to say --- instance ... => Typeable (MyType a b) +{-# LANGUAGE TypeOperators #-} ----------------------------------------------------------------------------- -- | diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 140b895..475f083 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -1,5 +1,16 @@ -{-# LANGUAGE Unsafe #-} {-# LANGUAGE BangPatterns #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE ConstraintKinds #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE Unsafe #-} ----------------------------------------------------------------------------- -- | @@ -13,20 +24,6 @@ -- ----------------------------------------------------------------------------- -{-# LANGUAGE CPP - , NoImplicitPrelude - , OverlappingInstances - , ScopedTypeVariables - , FlexibleInstances - , MagicHash - , KindSignatures - , PolyKinds - , ConstraintKinds - , DeriveDataTypeable - , DataKinds - , UndecidableInstances - , StandaloneDeriving #-} - module Data.Typeable.Internal ( Proxy (..), TypeRep(..), diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal index 957053d..6277d89 100644 --- a/libraries/base/base.cabal +++ b/libraries/base/base.cabal @@ -69,7 +69,6 @@ Library NegativeLiterals NoImplicitPrelude NondecreasingIndentation - OverlappingInstances OverloadedStrings ParallelArrays PolyKinds From git at git.haskell.org Fri Oct 31 09:32:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 09:32:25 +0000 (UTC) Subject: [commit: ghc] master: Fix comment typos (919e930) Message-ID: <20141031093225.6B4F93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/919e9303c1ce0fffc5d09b6875f17cf9b1f5167d/ghc >--------------------------------------------------------------- commit 919e9303c1ce0fffc5d09b6875f17cf9b1f5167d Author: Jan Stolarek Date: Fri Oct 31 10:31:40 2014 +0100 Fix comment typos >--------------------------------------------------------------- 919e9303c1ce0fffc5d09b6875f17cf9b1f5167d compiler/simplCore/CallArity.hs | 4 ++-- compiler/simplCore/SetLevels.lhs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs index bead230..5ee5fe2 100644 --- a/compiler/simplCore/CallArity.hs +++ b/compiler/simplCore/CallArity.hs @@ -33,7 +33,7 @@ Note [Call Arity: The goal] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ The goal of this analysis is to find out if we can eta-expand a local function, -based on how it is being called. The motivating example is code this this, +based on how it is being called. The motivating example is this code, which comes up when we implement foldl using foldr, and do list fusion: let go = \x -> let d = case ... of @@ -46,7 +46,7 @@ If we do not eta-expand `go` to have arity 2, we are going to allocate a lot of partial function applications, which would be bad. The function `go` has a type of arity two, but only one lambda is manifest. -Further more, an analysis that only looks at the RHS of go cannot be sufficient +Furthermore, an analysis that only looks at the RHS of go cannot be sufficient to eta-expand go: If `go` is ever called with one argument (and the result used multiple times), we would be doing the work in `...` multiple times. diff --git a/compiler/simplCore/SetLevels.lhs b/compiler/simplCore/SetLevels.lhs index 5f63096..e5cd42e 100644 --- a/compiler/simplCore/SetLevels.lhs +++ b/compiler/simplCore/SetLevels.lhs @@ -331,7 +331,7 @@ lvlExpr env expr@(_, AnnApp _ _) = do -- We don't split adjacent lambdas. That is, given -- \x y -> (x+1,y) -- we don't float to give --- \x -> let v = x+y in \y -> (v,y) +-- \x -> let v = x+1 in \y -> (v,y) -- Why not? Because partial applications are fairly rare, and splitting -- lambdas makes them more expensive. From git at git.haskell.org Fri Oct 31 09:46:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 09:46:50 +0000 (UTC) Subject: [commit: ghc] master: Add doctest examples for Data.Char (8ef4cf1) Message-ID: <20141031094650.14A273A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8ef4cf161dc76963a0094bdfe6bdc623a4863787/ghc >--------------------------------------------------------------- commit 8ef4cf161dc76963a0094bdfe6bdc623a4863787 Author: Michael Orlitzky Date: Fri Oct 31 09:50:00 2014 +0100 Add doctest examples for Data.Char This adds doctest examples for every function and data type in `Data.Char`. Reviewed By: austin, hvr Differential Revision: https://phabricator.haskell.org/D371 >--------------------------------------------------------------- 8ef4cf161dc76963a0094bdfe6bdc623a4863787 libraries/base/Data/Char.hs | 341 ++++++++++++++++++++++++++++++++++++++++++-- 1 file changed, 328 insertions(+), 13 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 8ef4cf161dc76963a0094bdfe6bdc623a4863787 From git at git.haskell.org Fri Oct 31 13:19:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:19:24 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Put one-Shot info in the interface (dfed8ac) Message-ID: <20141031131924.99C033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/dfed8acfdf5cd153541b243a893c128dd253e88c/ghc >--------------------------------------------------------------- commit dfed8acfdf5cd153541b243a893c128dd253e88c Author: Joachim Breitner Date: Tue Oct 28 13:02:40 2014 +0100 Put one-Shot info in the interface >--------------------------------------------------------------- dfed8acfdf5cd153541b243a893c128dd253e88c 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 dfed8acfdf5cd153541b243a893c128dd253e88c From git at git.haskell.org Fri Oct 31 13:19:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:19:28 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Add GHC.Prim.oneShot (b4dcb04) Message-ID: <20141031131928.08CD83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/b4dcb04253bb7277567b2823c17245b823acc029/ghc >--------------------------------------------------------------- commit b4dcb04253bb7277567b2823c17245b823acc029 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. >--------------------------------------------------------------- b4dcb04253bb7277567b2823c17245b823acc029 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 b4dcb04253bb7277567b2823c17245b823acc029 From git at git.haskell.org Fri Oct 31 13:19:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:19:30 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Use oneShot in the definition of foldl etc. (8b1de47) Message-ID: <20141031131930.A30533A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/8b1de47667bb8b30986ef9fc72d37c15b61640ae/ghc >--------------------------------------------------------------- commit 8b1de47667bb8b30986ef9fc72d37c15b61640ae 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] >--------------------------------------------------------------- 8b1de47667bb8b30986ef9fc72d37c15b61640ae 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 Fri Oct 31 13:19:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:19:33 +0000 (UTC) Subject: [commit: ghc] wip/oneShot: Add oneShot demo file (294b749) Message-ID: <20141031131933.CCC873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/oneShot Link : http://ghc.haskell.org/trac/ghc/changeset/294b7490e028d619c6e27636fe0d9affd32be6c1/ghc >--------------------------------------------------------------- commit 294b7490e028d619c6e27636fe0d9affd32be6c1 Author: Joachim Breitner Date: Mon Oct 6 23:04:02 2014 +0200 Add oneShot demo file (if you remove {-# GHC_OPTIONS -fno-call-arity #-} then both functions have the same Core). Obviously, this patch is not meant to be merged. >--------------------------------------------------------------- 294b7490e028d619c6e27636fe0d9affd32be6c1 OneShotTest.hs | 22 ++++++++++++++++++++++ 1 file changed, 22 insertions(+) diff --git a/OneShotTest.hs b/OneShotTest.hs new file mode 100644 index 0000000..b595285 --- /dev/null +++ b/OneShotTest.hs @@ -0,0 +1,22 @@ +{-# OPTIONS_GHC -fno-call-arity #-} + +module OneShotTest (foldlB, foldlA, fooA, fooB, fooC) where + +import GHC.Prim (oneShot) + +foldlA, foldlB :: (x -> a -> a) -> a -> [x] -> a + +foldlA k a xs = foldr (\v f a -> f (v `k` a)) id xs a +{-# INLINEABLE foldlA #-} + +foldlB k a xs = foldr (\v f -> oneShot (\ a -> f (v `k` a))) id xs a +{-# INLINEABLE foldlB #-} + +f :: Int -> Bool +f 0 = True +f 1 = False +{-# NOINLINE f #-} + +fooA = foldlA (+) 0 . filter f +fooB = foldlB (+) 0 . filter f +fooC = foldl (+) 0 . filter f From git at git.haskell.org Fri Oct 31 13:33:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:33:10 +0000 (UTC) Subject: [commit: ghc] master: Update Haddock submodule (bd6c6f6) Message-ID: <20141031133310.240F03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bd6c6f60d296bf76d13397c2c383644e2fcca614/ghc >--------------------------------------------------------------- commit bd6c6f60d296bf76d13397c2c383644e2fcca614 Author: Herbert Valerio Riedel Date: Fri Oct 31 14:04:57 2014 +0100 Update Haddock submodule This pulls in a change to have the new "Examples" sections being in `base` collapsed by default. >--------------------------------------------------------------- bd6c6f60d296bf76d13397c2c383644e2fcca614 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 3fb325a..3937a98 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 3fb325a2ca6b6397905116024922d079447a2e08 +Subproject commit 3937a98afe1bf1a215fd9115051af388e45b7299 From git at git.haskell.org Fri Oct 31 13:33:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:33:12 +0000 (UTC) Subject: [commit: ghc] master: Clean-up `Data.Fixed` (54addb1) Message-ID: <20141031133312.AFDE13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/54addb12bfae03ac6567315c471981e4ee042693/ghc >--------------------------------------------------------------- commit 54addb12bfae03ac6567315c471981e4ee042693 Author: Herbert Valerio Riedel Date: Fri Oct 31 14:25:45 2014 +0100 Clean-up `Data.Fixed` This gets rid of `-fno-warn-unused-binds` by turning the E* types into constructor-less data types (as they're used as phantom-types only) Moreover, this modules uses `AutoDeriveTypeable` so we can drop all those redundant `deriving (Typeable)` lines as well Reviewed By: austin, ekmett Differential Revision: https://phabricator.haskell.org/D385 >--------------------------------------------------------------- 54addb12bfae03ac6567315c471981e4ee042693 libraries/base/Data/Fixed.hs | 25 ++++++++----------------- 1 file changed, 8 insertions(+), 17 deletions(-) diff --git a/libraries/base/Data/Fixed.hs b/libraries/base/Data/Fixed.hs index b499617..068eec5 100644 --- a/libraries/base/Data/Fixed.hs +++ b/libraries/base/Data/Fixed.hs @@ -1,7 +1,6 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE AutoDeriveTypeable #-} -{-# OPTIONS -Wall -fno-warn-unused-binds #-} ----------------------------------------------------------------------------- -- | @@ -37,7 +36,6 @@ module Data.Fixed E12,Pico ) where -import Data.Typeable import Data.Data import GHC.Read import Text.ParserCombinators.ReadPrec @@ -61,7 +59,7 @@ mod' n d = n - (fromInteger f) * d where -- | The type parameter should be an instance of 'HasResolution'. newtype Fixed a = MkFixed Integer -- ^ /Since: 4.7.0.0/ - deriving (Eq,Ord,Typeable) + deriving (Eq,Ord) -- We do this because the automatically derived Data instance requires (Data a) context. -- Our manual instance has the more general (Typeable a) context. @@ -166,50 +164,43 @@ convertFixed (Number n) e = ceiling (logBase 10 (fromInteger r) :: Double) convertFixed _ = pfail -data E0 = E0 - deriving (Typeable) +data E0 instance HasResolution E0 where resolution _ = 1 -- | resolution of 1, this works the same as Integer type Uni = Fixed E0 -data E1 = E1 - deriving (Typeable) +data E1 instance HasResolution E1 where resolution _ = 10 -- | resolution of 10^-1 = .1 type Deci = Fixed E1 -data E2 = E2 - deriving (Typeable) +data E2 instance HasResolution E2 where resolution _ = 100 -- | resolution of 10^-2 = .01, useful for many monetary currencies type Centi = Fixed E2 -data E3 = E3 - deriving (Typeable) +data E3 instance HasResolution E3 where resolution _ = 1000 -- | resolution of 10^-3 = .001 type Milli = Fixed E3 -data E6 = E6 - deriving (Typeable) +data E6 instance HasResolution E6 where resolution _ = 1000000 -- | resolution of 10^-6 = .000001 type Micro = Fixed E6 -data E9 = E9 - deriving (Typeable) +data E9 instance HasResolution E9 where resolution _ = 1000000000 -- | resolution of 10^-9 = .000000001 type Nano = Fixed E9 -data E12 = E12 - deriving (Typeable) +data E12 instance HasResolution E12 where resolution _ = 1000000000000 -- | resolution of 10^-12 = .000000000001 From git at git.haskell.org Fri Oct 31 13:33:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:33:15 +0000 (UTC) Subject: [commit: ghc] master: Add changelog entry for recent Unicode 7.0 update (f12be5b) Message-ID: <20141031133315.6FE0C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f12be5b99a993989165c19a0c3c958e6a6034a4c/ghc >--------------------------------------------------------------- commit f12be5b99a993989165c19a0c3c958e6a6034a4c Author: Herbert Valerio Riedel Date: Fri Oct 31 14:30:32 2014 +0100 Add changelog entry for recent Unicode 7.0 update The internal Unicode definitions were updated via d4fd16801bc59034abdc6214e60fcce2b21af9c8 [skip ci] >--------------------------------------------------------------- f12be5b99a993989165c19a0c3c958e6a6034a4c libraries/base/changelog.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 76fe87a..0f89249 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -87,6 +87,8 @@ * New module `Data.Bifunctor` providing the `Bifunctor(bimap,first,second)` class (previously defined in `bifunctors` package) (#9682) + * Update Unicode class definitions to Unicode version 7.0 + ## 4.7.0.1 *Jul 2014* * Bundled with GHC 7.8.3 From git at git.haskell.org Fri Oct 31 13:38:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:38:24 +0000 (UTC) Subject: [commit: ghc] master: Update doctest example style in `Data.Bool` (d3a7126) Message-ID: <20141031133824.2B94E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d3a7126ff749d1eff31128ace31bcea26c4eadaa/ghc >--------------------------------------------------------------- commit d3a7126ff749d1eff31128ace31bcea26c4eadaa Author: Michael Orlitzky Date: Fri Oct 31 14:34:56 2014 +0100 Update doctest example style in `Data.Bool` hvr made some suggestions in D352 and D371, this fixes them in the already-applied patch for Data/Bool.hs as well for consistency. Reviewed By: austin, hvr Differential Revision: https://phabricator.haskell.org/D379 >--------------------------------------------------------------- d3a7126ff749d1eff31128ace31bcea26c4eadaa libraries/base/Data/Bool.hs | 40 ++++++++++++++++++++-------------------- 1 file changed, 20 insertions(+), 20 deletions(-) diff --git a/libraries/base/Data/Bool.hs b/libraries/base/Data/Bool.hs index 1537198..9f1bef6 100644 --- a/libraries/base/Data/Bool.hs +++ b/libraries/base/Data/Bool.hs @@ -28,33 +28,33 @@ module Data.Bool ( import GHC.Base --- | Case analysis for the 'Bool' type. @bool x y p@ evaluates to @x@ --- when @p@ is @False@, and evaluates to @y@ when @p@ is @True at . +-- | Case analysis for the 'Bool' type. @'bool' x y p@ evaluates to @x@ +-- when @p@ is 'False', and evaluates to @y@ when @p@ is 'True'. -- --- This is equivalent to @if p then y else x@; that is, one can --- think of it as an if-then-else construct with its arguments --- reordered. +-- This is equivalent to @if p then y else x@; that is, one can +-- think of it as an if-then-else construct with its arguments +-- reordered. -- --- /Since: 4.7.0.0/ +-- /Since: 4.7.0.0/ -- --- ==== __Examples__ +-- ==== __Examples__ -- --- Basic usage: +-- Basic usage: -- --- >>> bool "foo" "bar" True --- "bar" --- >>> bool "foo" "bar" False --- "foo" +-- >>> bool "foo" "bar" True +-- "bar" +-- >>> bool "foo" "bar" False +-- "foo" -- --- Confirm that @bool x y p@ and @if p then y else x@ are --- equivalent: +-- Confirm that @'bool' x y p@ and @if p then y else x@ are +-- equivalent: -- --- >>> let p = True; x = "bar"; y = "foo" --- >>> bool x y p == if p then y else x --- True --- >>> let p = False --- >>> bool x y p == if p then y else x --- True +-- >>> let p = True; x = "bar"; y = "foo" +-- >>> bool x y p == if p then y else x +-- True +-- >>> let p = False +-- >>> bool x y p == if p then y else x +-- True -- bool :: a -> a -> Bool -> a bool f _ False = f From git at git.haskell.org Fri Oct 31 13:42:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:42:48 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Tidy up pretty-printing of SrcLoc and SrcSpan (b52c345) Message-ID: <20141031134248.5EFC13A300@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/b52c34557571a00bfddaee45f755dc2df74ef18d/ghc >--------------------------------------------------------------- commit b52c34557571a00bfddaee45f755dc2df74ef18d Author: Simon Peyton Jones Date: Wed Oct 29 15:13:41 2014 +0000 Tidy up pretty-printing of SrcLoc and SrcSpan >--------------------------------------------------------------- b52c34557571a00bfddaee45f755dc2df74ef18d 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 Fri Oct 31 13:42:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:42:50 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Improve pretty-printing of type variables (fe60b78) Message-ID: <20141031134250.E928F3A300@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/fe60b78eb538ea9703c52185b15e61c8f797f1e7/ghc >--------------------------------------------------------------- commit fe60b78eb538ea9703c52185b15e61c8f797f1e7 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 >--------------------------------------------------------------- fe60b78eb538ea9703c52185b15e61c8f797f1e7 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 Fri Oct 31 13:42:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:42:53 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Some refactoring around endPass and debug dumping (e4a0a3e) Message-ID: <20141031134253.90D3D3A300@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/e4a0a3ed8a2ac8462794a1c3b5bad4da08c3680d/ghc >--------------------------------------------------------------- commit e4a0a3ed8a2ac8462794a1c3b5bad4da08c3680d 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 >--------------------------------------------------------------- e4a0a3ed8a2ac8462794a1c3b5bad4da08c3680d 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 e4a0a3ed8a2ac8462794a1c3b5bad4da08c3680d From git at git.haskell.org Fri Oct 31 13:42:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:42:56 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Simplify the generation of superclass constraints in tcInstDecl2 (68d3377) Message-ID: <20141031134256.332993A300@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/68d3377644a25b0428d09a1135e5b30bb0a32fbd/ghc >--------------------------------------------------------------- commit 68d3377644a25b0428d09a1135e5b30bb0a32fbd 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 >--------------------------------------------------------------- 68d3377644a25b0428d09a1135e5b30bb0a32fbd 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 Fri Oct 31 13:42:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:42:58 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: White space only (3c7eec4) Message-ID: <20141031134258.C3E7A3A300@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/3c7eec43328b4a3e83c6c1ecdf47a1784cde0803/ghc >--------------------------------------------------------------- commit 3c7eec43328b4a3e83c6c1ecdf47a1784cde0803 Author: Simon Peyton Jones Date: Wed Oct 29 16:27:50 2014 +0000 White space only >--------------------------------------------------------------- 3c7eec43328b4a3e83c6c1ecdf47a1784cde0803 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 Fri Oct 31 13:43:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:01 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Add the unfolding and inline-pragma for DFuns in DsBinds, not TcInstDcls (e741075) Message-ID: <20141031134301.66DF53A300@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/e741075ee27bceee696dde9647b1c102850af5b6/ghc >--------------------------------------------------------------- commit e741075ee27bceee696dde9647b1c102850af5b6 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 >--------------------------------------------------------------- e741075ee27bceee696dde9647b1c102850af5b6 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 Fri Oct 31 13:43:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:04 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Simplify the API for tcInstTyVars, and make it more consistent with other similar functions (9b888dd) Message-ID: <20141031134304.0D7623A300@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/9b888dd890b7ed1a202121f95ecff860b27ce9ba/ghc >--------------------------------------------------------------- commit 9b888dd890b7ed1a202121f95ecff860b27ce9ba 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 >--------------------------------------------------------------- 9b888dd890b7ed1a202121f95ecff860b27ce9ba 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 9b888dd890b7ed1a202121f95ecff860b27ce9ba From git at git.haskell.org Fri Oct 31 13:43:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:06 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Fix reduceTyFamApp_maybe (54e5a43) Message-ID: <20141031134306.9CA263A300@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/54e5a43bc27020a77e6d109542a5fafe1e3bc503/ghc >--------------------------------------------------------------- commit 54e5a43bc27020a77e6d109542a5fafe1e3bc503 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. >--------------------------------------------------------------- 54e5a43bc27020a77e6d109542a5fafe1e3bc503 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 Fri Oct 31 13:43:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:09 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Rename setRole_maybe to downgradeRole_maybe (7b3c742) Message-ID: <20141031134309.367BB3A300@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/7b3c7422ae04117b1cd4dc61e08b8c89b55b8633/ghc >--------------------------------------------------------------- commit 7b3c7422ae04117b1cd4dc61e08b8c89b55b8633 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 >--------------------------------------------------------------- 7b3c7422ae04117b1cd4dc61e08b8c89b55b8633 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 Fri Oct 31 13:43:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:11 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Refactor the treatment of lexically-scoped type variables for instance declarations (0ce46e7) Message-ID: <20141031134311.CCF3C3A300@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/0ce46e7025f31df5c0b96bd5319361505101e59b/ghc >--------------------------------------------------------------- commit 0ce46e7025f31df5c0b96bd5319361505101e59b 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.) >--------------------------------------------------------------- 0ce46e7025f31df5c0b96bd5319361505101e59b 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 0ce46e7025f31df5c0b96bd5319361505101e59b From git at git.haskell.org Fri Oct 31 13:43:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:14 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Refactor skolemising, and newClsInst (4290bda) Message-ID: <20141031134314.6F1C13A300@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/4290bdaef7d7290efebeb537194dee5accf14b6a/ghc >--------------------------------------------------------------- commit 4290bdaef7d7290efebeb537194dee5accf14b6a 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. >--------------------------------------------------------------- 4290bdaef7d7290efebeb537194dee5accf14b6a 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 4290bdaef7d7290efebeb537194dee5accf14b6a From git at git.haskell.org Fri Oct 31 13:43:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:17 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Get the Untouchables level right in simplifyInfer (446ced2) Message-ID: <20141031134317.1277A3A300@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/446ced2fab5e221c724be4b4fbc6946e7959508f/ghc >--------------------------------------------------------------- commit 446ced2fab5e221c724be4b4fbc6946e7959508f 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 >--------------------------------------------------------------- 446ced2fab5e221c724be4b4fbc6946e7959508f 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 446ced2fab5e221c724be4b4fbc6946e7959508f From git at git.haskell.org Fri Oct 31 13:43:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:19 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Normalise the type of an inferred let-binding (23600fb) Message-ID: <20141031134319.BAA063A300@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/23600fb2016bd460e1e9d208441d4056f1359ee9/ghc >--------------------------------------------------------------- commit 23600fb2016bd460e1e9d208441d4056f1359ee9 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 >--------------------------------------------------------------- 23600fb2016bd460e1e9d208441d4056f1359ee9 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 8ec8118..e9a6f82 100644 --- a/compiler/typecheck/TcRnDriver.lhs +++ b/compiler/typecheck/TcRnDriver.lhs @@ -1645,11 +1645,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 Fri Oct 31 13:43:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:22 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Typechecker debug tracing only (ac31ee3) Message-ID: <20141031134322.59FCE3A300@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/ac31ee34be3d93f4220625195aa67d25bac19b7a/ghc >--------------------------------------------------------------- commit ac31ee34be3d93f4220625195aa67d25bac19b7a Author: Simon Peyton Jones Date: Wed Oct 29 17:22:57 2014 +0000 Typechecker debug tracing only >--------------------------------------------------------------- ac31ee34be3d93f4220625195aa67d25bac19b7a 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 e9a6f82..3440b4f 100644 --- a/compiler/typecheck/TcRnDriver.lhs +++ b/compiler/typecheck/TcRnDriver.lhs @@ -1920,7 +1920,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 Fri Oct 31 13:43:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:25 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: When reporting the context of given constraints, stop when you find one that binds a variable mentioned in the wanted (69cdebf) Message-ID: <20141031134325.05D183A300@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/69cdebf66ea6f062d7b0906f3d60d6dc54b9b48a/ghc >--------------------------------------------------------------- commit 69cdebf66ea6f062d7b0906f3d60d6dc54b9b48a 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 >--------------------------------------------------------------- 69cdebf66ea6f062d7b0906f3d60d6dc54b9b48a 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 Fri Oct 31 13:43:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:27 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Only report "could not deduce s~t from ..." for givens that include equalities (394ca3b) Message-ID: <20141031134327.8E1643A300@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/394ca3be64d101e30fb4f47de88afd3d55615309/ghc >--------------------------------------------------------------- commit 394ca3be64d101e30fb4f47de88afd3d55615309 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 >--------------------------------------------------------------- 394ca3be64d101e30fb4f47de88afd3d55615309 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 Fri Oct 31 13:43:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:30 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Don't filter out allegedly-irrelevant bindings with -dppr-debug (ec5be5fb) Message-ID: <20141031134330.2FD203A300@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/ec5be5fb8991801f8683d23df7722e2152026436/ghc >--------------------------------------------------------------- commit ec5be5fb8991801f8683d23df7722e2152026436 Author: Simon Peyton Jones Date: Wed Oct 29 17:50:44 2014 +0000 Don't filter out allegedly-irrelevant bindings with -dppr-debug >--------------------------------------------------------------- ec5be5fb8991801f8683d23df7722e2152026436 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 Fri Oct 31 13:43:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:32 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Define ctEvLoc and ctEvCoercion, and use them (697444d) Message-ID: <20141031134332.C9BC33A300@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/697444dd9d7b240f14abeff364a610153f5039ed/ghc >--------------------------------------------------------------- commit 697444dd9d7b240f14abeff364a610153f5039ed Author: Simon Peyton Jones Date: Thu Oct 30 09:08:23 2014 +0000 Define ctEvLoc and ctEvCoercion, and use them >--------------------------------------------------------------- 697444dd9d7b240f14abeff364a610153f5039ed 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 Fri Oct 31 13:43:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:35 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Minor refactoring (no change in functionality) (f61b89f) Message-ID: <20141031134335.652BC3A300@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/f61b89fce22bdfd64f48d2fe26844e118e7e384d/ghc >--------------------------------------------------------------- commit f61b89fce22bdfd64f48d2fe26844e118e7e384d Author: Simon Peyton Jones Date: Wed Oct 29 17:51:41 2014 +0000 Minor refactoring (no change in functionality) >--------------------------------------------------------------- f61b89fce22bdfd64f48d2fe26844e118e7e384d 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 Fri Oct 31 13:43:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:38 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Test Trac #9211 (d60edce) Message-ID: <20141031134338.62ADD3A300@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/d60edce187223594acc4139fefdef0ed886bdf35/ghc >--------------------------------------------------------------- commit d60edce187223594acc4139fefdef0ed886bdf35 Author: Simon Peyton Jones Date: Thu Oct 30 11:37:39 2014 +0000 Test Trac #9211 >--------------------------------------------------------------- d60edce187223594acc4139fefdef0ed886bdf35 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 Fri Oct 31 13:43:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:41 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Test Trac #9708 (8075e43) Message-ID: <20141031134341.A71ED3A300@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/8075e4327df83b6a68100c07937f5e01a4801ecd/ghc >--------------------------------------------------------------- commit 8075e4327df83b6a68100c07937f5e01a4801ecd Author: Simon Peyton Jones Date: Thu Oct 30 11:39:39 2014 +0000 Test Trac #9708 >--------------------------------------------------------------- 8075e4327df83b6a68100c07937f5e01a4801ecd 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 Fri Oct 31 13:43:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:44 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Testsuite error message changes (8e62b70) Message-ID: <20141031134344.845783A300@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/8e62b70e5ce78770483322fe43cb23cc9acc52ed/ghc >--------------------------------------------------------------- commit 8e62b70e5ce78770483322fe43cb23cc9acc52ed Author: Simon Peyton Jones Date: Thu Oct 30 11:41:17 2014 +0000 Testsuite error message changes >--------------------------------------------------------------- 8e62b70e5ce78770483322fe43cb23cc9acc52ed .../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 +- .../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 +- 120 files changed, 1027 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 8e62b70e5ce78770483322fe43cb23cc9acc52ed From git at git.haskell.org Fri Oct 31 13:43:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:47 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Add flattening-notes (891f03d) Message-ID: <20141031134347.5AD1C3A300@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/891f03dad6a85a60073ba6250f4d96911221bd35/ghc >--------------------------------------------------------------- commit 891f03dad6a85a60073ba6250f4d96911221bd35 Author: Simon Peyton Jones Date: Thu Oct 30 12:11:27 2014 +0000 Add flattening-notes >--------------------------------------------------------------- 891f03dad6a85a60073ba6250f4d96911221bd35 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 Fri Oct 31 13:43:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:50 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Improve error message for a handwritten Typeable instance (d81c97f) Message-ID: <20141031134350.686DC3A300@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/d81c97fb64fee5d1b8d7406b41e2af513031c3b9/ghc >--------------------------------------------------------------- commit d81c97fb64fee5d1b8d7406b41e2af513031c3b9 Author: Simon Peyton Jones Date: Thu Oct 30 16:33:34 2014 +0000 Improve error message for a handwritten Typeable instance >--------------------------------------------------------------- d81c97fb64fee5d1b8d7406b41e2af513031c3b9 compiler/typecheck/TcInstDcls.lhs | 42 ++++++++++++---------- testsuite/tests/deriving/should_fail/T9687.hs | 4 +++ .../should_fail/T9687.stderr} | 4 +-- .../should_fail/T9730.stderr} | 0 testsuite/tests/deriving/should_fail/all.T | 1 + 5 files changed, 31 insertions(+), 20 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/polykinds/T8132.stderr b/testsuite/tests/deriving/should_fail/T9687.stderr similarity index 54% copy from testsuite/tests/polykinds/T8132.stderr copy to testsuite/tests/deriving/should_fail/T9687.stderr index 6c567de..10619a6 100644 --- a/testsuite/tests/polykinds/T8132.stderr +++ b/testsuite/tests/deriving/should_fail/T9687.stderr @@ -1,5 +1,5 @@ -T8132.hs:6:10: +T9687.hs:4:10: Typeable instances can only be derived - Try ?deriving instance Typeable K? + 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 Fri Oct 31 13:43:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:53 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Test Trac #9747 (c9f8742) Message-ID: <20141031134353.400E73A300@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/c9f8742dd22328c0fe8199d5b78eb42c7ca90590/ghc >--------------------------------------------------------------- commit c9f8742dd22328c0fe8199d5b78eb42c7ca90590 Author: Simon Peyton Jones Date: Fri Oct 31 08:53:52 2014 +0000 Test Trac #9747 >--------------------------------------------------------------- c9f8742dd22328c0fe8199d5b78eb42c7ca90590 .../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 64683b2..fbd0b0e 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 Fri Oct 31 13:43:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:56 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Source code work in progress (9b911e3) Message-ID: <20141031134356.A11E33A300@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/9b911e3e9c0c5585b79bd3cf94b0a3cc08d7aa9a/ghc >--------------------------------------------------------------- commit 9b911e3e9c0c5585b79bd3cf94b0a3cc08d7aa9a Author: Simon Peyton Jones Date: Thu Oct 30 11:40:48 2014 +0000 Source code work in progress >--------------------------------------------------------------- 9b911e3e9c0c5585b79bd3cf94b0a3cc08d7aa9a compiler/ghc.cabal.in | 1 + compiler/typecheck/Inst.lhs | 19 +- compiler/typecheck/TcCanonical.lhs | 791 +++++--------- compiler/typecheck/TcFlatten.lhs | 1017 ++++++++++++++++++ compiler/typecheck/TcInteract.lhs | 874 ++++++++-------- compiler/typecheck/TcMType.lhs | 139 +-- compiler/typecheck/TcRnTypes.lhs | 155 +-- compiler/typecheck/TcRules.lhs | 2 - compiler/typecheck/TcSMonad.lhs | 1089 ++++++++++---------- compiler/typecheck/TcSimplify.lhs | 402 +++----- compiler/typecheck/TcType.lhs | 107 +- compiler/typecheck/TcUnify.lhs | 1 - testsuite/tests/indexed-types/should_fail/T7786.hs | 4 +- .../tests/indexed-types/should_fail/T7786.stderr | 13 - testsuite/tests/indexed-types/should_fail/all.T | 2 +- 15 files changed, 2630 insertions(+), 1986 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 9b911e3e9c0c5585b79bd3cf94b0a3cc08d7aa9a From git at git.haskell.org Fri Oct 31 13:43:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:43:59 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Make this test a bit simpler (d3ac485) Message-ID: <20141031134359.3DE483A300@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/d3ac485023f3a1a22a8a5c9b2f52e760dd476d81/ghc >--------------------------------------------------------------- commit d3ac485023f3a1a22a8a5c9b2f52e760dd476d81 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. >--------------------------------------------------------------- d3ac485023f3a1a22a8a5c9b2f52e760dd476d81 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 Fri Oct 31 13:44:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:44:01 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Add comments explaining ProbOneShot (0dc512a) Message-ID: <20141031134401.D9D993A300@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/0dc512afed53cc7c1bc76b271bc2ae7b3b85651e/ghc >--------------------------------------------------------------- commit 0dc512afed53cc7c1bc76b271bc2ae7b3b85651e Author: Simon Peyton Jones Date: Fri Oct 31 11:13:37 2014 +0000 Add comments explaining ProbOneShot >--------------------------------------------------------------- 0dc512afed53cc7c1bc76b271bc2ae7b3b85651e 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 5f63096..645cf9f 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 Fri Oct 31 13:44:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:44:05 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Test Trac #9739 (054d7ef) Message-ID: <20141031134405.0E0C93A300@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/054d7efd316228cd53c608a5828a93df67766074/ghc >--------------------------------------------------------------- commit 054d7efd316228cd53c608a5828a93df67766074 Author: Simon Peyton Jones Date: Fri Oct 31 11:11:50 2014 +0000 Test Trac #9739 >--------------------------------------------------------------- 054d7efd316228cd53c608a5828a93df67766074 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 Fri Oct 31 13:44:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:44:07 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Fix the superclass-cycle detection code (Trac #9739) (f2cec02) Message-ID: <20141031134407.A78A13A300@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/f2cec027b76a51364f9724de049a52adf6205c07/ghc >--------------------------------------------------------------- commit f2cec027b76a51364f9724de049a52adf6205c07 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. >--------------------------------------------------------------- f2cec027b76a51364f9724de049a52adf6205c07 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 50113db..5d610b4 100644 --- a/compiler/typecheck/TcTyClsDecls.lhs +++ b/compiler/typecheck/TcTyClsDecls.lhs @@ -1369,25 +1369,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 @@ -1640,8 +1624,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 } @@ -1707,6 +1694,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 Fri Oct 31 13:44:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:44:10 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Comments only (9e6c0e8) Message-ID: <20141031134410.3EC7B3A300@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/9e6c0e81a48a739d1397c06033b6505d9e96d22c/ghc >--------------------------------------------------------------- commit 9e6c0e81a48a739d1397c06033b6505d9e96d22c Author: Simon Peyton Jones Date: Fri Oct 31 12:32:36 2014 +0000 Comments only >--------------------------------------------------------------- 9e6c0e81a48a739d1397c06033b6505d9e96d22c 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 Fri Oct 31 13:44:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 13:44:12 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14's head updated: Comments only (9e6c0e8) Message-ID: <20141031134412.852083A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/new-flatten-skolems-Oct14' now includes: 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 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 8e62b70 Testsuite error message changes 891f03d Add flattening-notes d81c97f Improve error message for a handwritten Typeable instance c9f8742 Test Trac #9747 9b911e3 Source code work in progress 0dc512a Add comments explaining ProbOneShot d3ac485 Make this test a bit simpler 054d7ef Test Trac #9739 f2cec02 Fix the superclass-cycle detection code (Trac #9739) 9e6c0e8 Comments only From git at git.haskell.org Fri Oct 31 17:36:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:36:19 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9262 in th/T9262, and update other tests. (68bfc13) Message-ID: <20141031173619.D74373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/68bfc13e17723933a0eef2d433ff28a44a649794/ghc >--------------------------------------------------------------- commit 68bfc13e17723933a0eef2d433ff28a44a649794 Author: Richard Eisenberg Date: Tue Oct 21 09:12:34 2014 -0400 Test #9262 in th/T9262, and update other tests. >--------------------------------------------------------------- 68bfc13e17723933a0eef2d433ff28a44a649794 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 Fri Oct 31 17:36:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:36:22 +0000 (UTC) Subject: [commit: ghc] wip/rae: Bring unbound tyvars into scope during reifyInstances. (89eb979) Message-ID: <20141031173622.75CA93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/89eb97936346f356a2db50ead41745a6f432bb15/ghc >--------------------------------------------------------------- commit 89eb97936346f356a2db50ead41745a6f432bb15 Author: Richard Eisenberg Date: Tue Oct 21 09:13:08 2014 -0400 Bring unbound tyvars into scope during reifyInstances. Fix #9262. >--------------------------------------------------------------- 89eb97936346f356a2db50ead41745a6f432bb15 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 Fri Oct 31 17:36:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:36:25 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #8953 in th/T8953 (7918899) Message-ID: <20141031173625.5B93A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/79188998702a2758409b002729b40600f92ac9fd/ghc >--------------------------------------------------------------- commit 79188998702a2758409b002729b40600f92ac9fd Author: Richard Eisenberg Date: Tue Oct 21 10:46:27 2014 -0400 Test #8953 in th/T8953 >--------------------------------------------------------------- 79188998702a2758409b002729b40600f92ac9fd 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 Fri Oct 31 17:36:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:36:27 +0000 (UTC) Subject: [commit: ghc] wip/rae: Always use KindedTV when reifying. (#8953) (a8acb09) Message-ID: <20141031173627.F0EE63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/a8acb095a1d050d909f7b4ce2d5b7bdf7cdd5f0d/ghc >--------------------------------------------------------------- commit a8acb095a1d050d909f7b4ce2d5b7bdf7cdd5f0d Author: Richard Eisenberg Date: Tue Oct 21 10:48:49 2014 -0400 Always use KindedTV when reifying. (#8953) >--------------------------------------------------------------- a8acb095a1d050d909f7b4ce2d5b7bdf7cdd5f0d 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 Fri Oct 31 17:36:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:36:30 +0000 (UTC) Subject: [commit: ghc] wip/rae: Annotate reified poly-kinded tycons when necessary. (#8953) (20acbc9) Message-ID: <20141031173630.8C6A83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/20acbc967eff5842d474d90e38304d14d7087577/ghc >--------------------------------------------------------------- commit 20acbc967eff5842d474d90e38304d14d7087577 Author: Richard Eisenberg Date: Tue Oct 21 10:58:05 2014 -0400 Annotate reified poly-kinded tycons when necessary. (#8953) >--------------------------------------------------------------- 20acbc967eff5842d474d90e38304d14d7087577 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 Fri Oct 31 17:36:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:36:33 +0000 (UTC) Subject: [commit: ghc] wip/rae: Annotate poly-kinded type patterns in instance reification. (94d640b) Message-ID: <20141031173633.283E43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/94d640bfcc49918a869592352176e0511971acb1/ghc >--------------------------------------------------------------- commit 94d640bfcc49918a869592352176e0511971acb1 Author: Richard Eisenberg Date: Tue Oct 21 11:27:16 2014 -0400 Annotate poly-kinded type patterns in instance reification. This should fix #8953. >--------------------------------------------------------------- 94d640bfcc49918a869592352176e0511971acb1 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 94d640bfcc49918a869592352176e0511971acb1 From git at git.haskell.org Fri Oct 31 17:36:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:36:35 +0000 (UTC) Subject: [commit: ghc] wip/rae: Testsuite wibbles from fixing #8953 (7bd431d) Message-ID: <20141031173635.AF4543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/7bd431d5855a342ae4c5cf5d772172f4f584272f/ghc >--------------------------------------------------------------- commit 7bd431d5855a342ae4c5cf5d772172f4f584272f Author: Richard Eisenberg Date: Tue Oct 28 10:42:32 2014 -0400 Testsuite wibbles from fixing #8953 >--------------------------------------------------------------- 7bd431d5855a342ae4c5cf5d772172f4f584272f 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 Fri Oct 31 17:36:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:36:38 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9084 by calling notHandled when unknown bits are enountered. (701bb90) Message-ID: <20141031173638.44FDF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/701bb90da61cee34f115cd5e7720d42ac5c3c3c9/ghc >--------------------------------------------------------------- commit 701bb90da61cee34f115cd5e7720d42ac5c3c3c9 Author: Richard Eisenberg Date: Tue Oct 28 13:21:34 2014 -0400 Fix #9084 by calling notHandled when unknown bits are enountered. >--------------------------------------------------------------- 701bb90da61cee34f115cd5e7720d42ac5c3c3c9 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 Fri Oct 31 17:36:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:36:41 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9084 in th/T9084. (8155cc4) Message-ID: <20141031173641.5AA313A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/8155cc4581ac313f7b73f887a87dbe6bf02956e5/ghc >--------------------------------------------------------------- commit 8155cc4581ac313f7b73f887a87dbe6bf02956e5 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. >--------------------------------------------------------------- 8155cc4581ac313f7b73f887a87dbe6bf02956e5 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 Fri Oct 31 17:36:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:36:44 +0000 (UTC) Subject: [commit: ghc] wip/rae: Test #9738 in th/T9738 (56de19b) Message-ID: <20141031173644.9BFE33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/56de19b2930d067d338dcf4e8cb254be73d3b640/ghc >--------------------------------------------------------------- commit 56de19b2930d067d338dcf4e8cb254be73d3b640 Author: Richard Eisenberg Date: Tue Oct 28 14:53:59 2014 -0400 Test #9738 in th/T9738 >--------------------------------------------------------------- 56de19b2930d067d338dcf4e8cb254be73d3b640 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 Fri Oct 31 17:36:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:36:47 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix testsuite output from #9084. (42c4e67) Message-ID: <20141031173647.391E93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/42c4e678c234229b7fc9f5d366f8dcb1d587f960/ghc >--------------------------------------------------------------- commit 42c4e678c234229b7fc9f5d366f8dcb1d587f960 Author: Richard Eisenberg Date: Tue Oct 28 15:15:02 2014 -0400 Fix testsuite output from #9084. >--------------------------------------------------------------- 42c4e678c234229b7fc9f5d366f8dcb1d587f960 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 Fri Oct 31 17:36:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:36:49 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix #9738, by handling {-# ANN ... #-} in DsMeta. (5038ed9) Message-ID: <20141031173649.E22E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/5038ed999997922446cb0165b3080d6cbb7467fa/ghc >--------------------------------------------------------------- commit 5038ed999997922446cb0165b3080d6cbb7467fa Author: Richard Eisenberg Date: Tue Oct 28 14:54:20 2014 -0400 Fix #9738, by handling {-# ANN ... #-} in DsMeta. >--------------------------------------------------------------- 5038ed999997922446cb0165b3080d6cbb7467fa 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 5038ed999997922446cb0165b3080d6cbb7467fa From git at git.haskell.org Fri Oct 31 17:36:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:36:55 +0000 (UTC) Subject: [commit: ghc] wip/rae's head updated: Fix #9738, by handling {-# ANN ... #-} in DsMeta. (5038ed9) Message-ID: <20141031173655.314B53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/rae' now includes: 16776e9 configure.ac: drop unused HAVE_BIN_SH a2ac57b Tweak Haddock markup in GHC.Magic 4e020b3 Tweak Haddock in GHC.Types 44c1e3f testsuite: add list of llvm_ways caa9c8aa Add test case for #9013 8e01ca6 Remove obsolete "-- #hide" Haddock pragmas b7b7633 Add a test for plusWord2#, addIntC#, subIntC# e83e873 Clarify documentation of addIntC#, subIntC# 3260467 systools info: fix warning about C compiler (message said about linker) ba9277c Tweak linting rules. 02be4ff fix T4201 to avoid GNU grep specific -B option by usage of pure POSIX tools 2396940 fix T4981-V3 and T9208 tests for no newline at end of file warning ba3650c fix T4981-V3 to avoid DOS line endings bb00308 Don't build or test dph by default 238fd05 change topHandler02/topHandler03 tests to use signal_exit_code function 7a754a9 rts/Printer.c: drop zcode mangling/demangling support in C code b02fa3b rts: Remove trailing whitespace and tabs from Printer.c 8d90ffa fix darwin threaded static linking by removing -lpthread option #9189 cbfa107 Improve seq documentation; part of trac issue #9390 c80d238 Eliminate some code duplication in x86 backend (genCCall32/64) 5f5d662 Make IntAddCOp, IntSubCOp into GenericOps 71bd4e3 x86: Always generate add instruction in MO_Add2 (#9013) 8e64151 stg/Prim.h: drop redundant #ifdef 6e3c44e Unbreak travis by not passing --no-dph 0a3944c testsuite/base: update .gitignore 3694d87 Re-add `--no-dph` option to ./validate 3669b60 Add bit scan {forward,reverse} insns to x86 NCG 9f285fa Add CMOVcc insns to x86 NCG 6415191 x86: zero extend the result of 16-bit popcnt instructions (#9435) a09508b Test #9371 (indexed-types/should_fail/T9371) f29bdfb Fix Trac #9371. 1b13886 Fix #9415. 1a3e19d Test #9415 (typecheck/should_fail/T9415) 8d27c76 Test #9200. (polykinds/T9200) 6485930 Change definition of CUSK for data and class definitions (#9200). 3dfd3c3 Added more testing for #9200. (polykinds/T9200b) b2c6167 Change treatment of CUSKs for synonyms and families (#9200). 578377c Remove NonParametricKinds (#9200) 1c66b3d Update manual (#9200). 91a48c5 Testsuite wibbles around #9200 6f862df shouldInlinePrimOp: Fix Int overflow a6fd7b5 Add some Haddocks to SMRep 4342049 StgCmmPrim: add note to stop using fixed size signed types for sizes 5e46e1f Have ghc-pkg use an old-style package key when it's not provided. 2272c50 Explicitly version test for package key support. 6b5ea61 Remove out of date TODO e0c1767 Implement new CLZ and CTZ primops (re #9340) 03a8003 Declare `ghc-head` to be haddock's upstream branch 5895f2b LlvmMangler: Be more selective when mangling object types d39c434 Make configure's sed(1) expression for GHC_LDFLAGS more BSD-friendly. 246436f Implement {resize,shrink}MutableByteArray# primops 425d517 Fix typos 'resizze' 53cc943 Revert "Fix typos 'resizze'" this is z-encoding (as hvr tells me) 6375934 Workaround GCC `__ctzdi2` intrinsic linker errors 96d0418 Remove obsolete `digitsTyConKey :: Unique` 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) 68bfc13 Test #9262 in th/T9262, and update other tests. 89eb979 Bring unbound tyvars into scope during reifyInstances. 7918899 Test #8953 in th/T8953 a8acb09 Always use KindedTV when reifying. (#8953) 20acbc9 Annotate reified poly-kinded tycons when necessary. (#8953) 94d640b Annotate poly-kinded type patterns in instance reification. 7bd431d Testsuite wibbles from fixing #8953 8155cc4 Test #9084 in th/T9084. 701bb90 Fix #9084 by calling notHandled when unknown bits are enountered. 42c4e67 Fix testsuite output from #9084. 56de19b Test #9738 in th/T9738 5038ed9 Fix #9738, by handling {-# ANN ... #-} in DsMeta. From git at git.haskell.org Fri Oct 31 17:46:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:46:00 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Test Trac #9747 (bfadcaf) Message-ID: <20141031174600.A6EF03A300@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/bfadcaf24600b8e79438ad234888a9afdcaeb774/ghc >--------------------------------------------------------------- commit bfadcaf24600b8e79438ad234888a9afdcaeb774 Author: Simon Peyton Jones Date: Fri Oct 31 08:53:52 2014 +0000 Test Trac #9747 >--------------------------------------------------------------- bfadcaf24600b8e79438ad234888a9afdcaeb774 .../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 Fri Oct 31 17:46:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:46:04 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Improve error message for a handwritten Typeable instance (8aa08f2) Message-ID: <20141031174604.061A03A300@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/8aa08f2ed7ab121222e3c19d8a4e872b2bedd9e3/ghc >--------------------------------------------------------------- commit 8aa08f2ed7ab121222e3c19d8a4e872b2bedd9e3 Author: Simon Peyton Jones Date: Thu Oct 30 16:33:34 2014 +0000 Improve error message for a handwritten Typeable instance >--------------------------------------------------------------- 8aa08f2ed7ab121222e3c19d8a4e872b2bedd9e3 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 Fri Oct 31 17:46:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:46:07 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Test Trac #9739 (c140398) Message-ID: <20141031174607.5F27D3A300@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/c1403989b10a1fd7aae5297c2d9eac75ed101952/ghc >--------------------------------------------------------------- commit c1403989b10a1fd7aae5297c2d9eac75ed101952 Author: Simon Peyton Jones Date: Fri Oct 31 11:11:50 2014 +0000 Test Trac #9739 >--------------------------------------------------------------- c1403989b10a1fd7aae5297c2d9eac75ed101952 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 Fri Oct 31 17:46:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:46:10 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Add comments explaining ProbOneShot (1ca7670) Message-ID: <20141031174610.324D13A300@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/1ca76706be6ec65a858145926c95a981ca08402b/ghc >--------------------------------------------------------------- commit 1ca76706be6ec65a858145926c95a981ca08402b Author: Simon Peyton Jones Date: Fri Oct 31 11:13:37 2014 +0000 Add comments explaining ProbOneShot >--------------------------------------------------------------- 1ca76706be6ec65a858145926c95a981ca08402b 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 5f63096..645cf9f 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 Fri Oct 31 17:46:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:46:12 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Fix the superclass-cycle detection code (Trac #9739) (87d89ea) Message-ID: <20141031174612.DD95B3A300@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/87d89ea120504fe7a93812ec1fc05935a8461f17/ghc >--------------------------------------------------------------- commit 87d89ea120504fe7a93812ec1fc05935a8461f17 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. >--------------------------------------------------------------- 87d89ea120504fe7a93812ec1fc05935a8461f17 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 50113db..5d610b4 100644 --- a/compiler/typecheck/TcTyClsDecls.lhs +++ b/compiler/typecheck/TcTyClsDecls.lhs @@ -1369,25 +1369,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 @@ -1640,8 +1624,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 } @@ -1707,6 +1694,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 Fri Oct 31 17:46:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:46:15 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Comments only (9b82cfb) Message-ID: <20141031174615.82A8E3A300@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/9b82cfb8aac55e29ee7aa3789e967f647521bc16/ghc >--------------------------------------------------------------- commit 9b82cfb8aac55e29ee7aa3789e967f647521bc16 Author: Simon Peyton Jones Date: Fri Oct 31 12:32:36 2014 +0000 Comments only >--------------------------------------------------------------- 9b82cfb8aac55e29ee7aa3789e967f647521bc16 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 Fri Oct 31 17:46:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:46:18 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Testsuite error message changes (b75d3e5) Message-ID: <20141031174618.36EDF3A300@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/b75d3e5d33d7a8eef4e3f82e0d28be5b6d4f9062/ghc >--------------------------------------------------------------- commit b75d3e5d33d7a8eef4e3f82e0d28be5b6d4f9062 Author: Simon Peyton Jones Date: Thu Oct 30 11:41:17 2014 +0000 Testsuite error message changes >--------------------------------------------------------------- b75d3e5d33d7a8eef4e3f82e0d28be5b6d4f9062 .../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 +- .../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 +- 120 files changed, 1027 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 b75d3e5d33d7a8eef4e3f82e0d28be5b6d4f9062 From git at git.haskell.org Fri Oct 31 17:46:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:46:21 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Add flattening-notes (4fe6e76) Message-ID: <20141031174621.04FA63A300@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/4fe6e7691d3f8caca2a2e583fa4ca3291d2c8789/ghc >--------------------------------------------------------------- commit 4fe6e7691d3f8caca2a2e583fa4ca3291d2c8789 Author: Simon Peyton Jones Date: Thu Oct 30 12:11:27 2014 +0000 Add flattening-notes >--------------------------------------------------------------- 4fe6e7691d3f8caca2a2e583fa4ca3291d2c8789 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 Fri Oct 31 17:46:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:46:23 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Make this test a bit simpler (a59bfa9) Message-ID: <20141031174623.8E9913A300@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/a59bfa9f55af50abfad1f5349f9b69cfc39bd226/ghc >--------------------------------------------------------------- commit a59bfa9f55af50abfad1f5349f9b69cfc39bd226 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. >--------------------------------------------------------------- a59bfa9f55af50abfad1f5349f9b69cfc39bd226 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 Fri Oct 31 17:46:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 17:46:26 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Work in progress (5fd7b47) Message-ID: <20141031174626.61F9E3A300@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/5fd7b47f0d340c6a94bc0ce36b4245d137ac1638/ghc >--------------------------------------------------------------- commit 5fd7b47f0d340c6a94bc0ce36b4245d137ac1638 Author: Simon Peyton Jones Date: Fri Oct 31 17:45:56 2014 +0000 Work in progress >--------------------------------------------------------------- 5fd7b47f0d340c6a94bc0ce36b4245d137ac1638 compiler/ghc.cabal.in | 1 + compiler/typecheck/Flattening-notes | 19 + compiler/typecheck/Inst.lhs | 19 +- compiler/typecheck/TcCanonical.lhs | 928 +++++------------ compiler/typecheck/TcInteract.lhs | 886 ++++++++-------- compiler/typecheck/TcMType.lhs | 139 +-- compiler/typecheck/TcRnTypes.lhs | 184 ++-- compiler/typecheck/TcRules.lhs | 2 - compiler/typecheck/TcSMonad.lhs | 1091 ++++++++++---------- compiler/typecheck/TcSimplify.lhs | 402 +++----- compiler/typecheck/TcType.lhs | 107 +- compiler/typecheck/TcUnify.lhs | 1 - testsuite/tests/indexed-types/should_fail/T7786.hs | 4 +- .../tests/indexed-types/should_fail/T7786.stderr | 13 - testsuite/tests/indexed-types/should_fail/all.T | 2 +- 15 files changed, 1666 insertions(+), 2132 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 5fd7b47f0d340c6a94bc0ce36b4245d137ac1638 From git at git.haskell.org Fri Oct 31 20:51:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 20:51:36 +0000 (UTC) Subject: [commit: ghc] master: Split off stat (benchmark) test failures into a separate section in the test runner summary. (4667fb5) Message-ID: <20141031205136.6AE7A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4667fb5201833e079256b7e4b420e5c87ca19b1a/ghc >--------------------------------------------------------------- commit 4667fb5201833e079256b7e4b420e5c87ca19b1a Author: Gintautas Miliauskas Date: Fri Oct 31 15:51:16 2014 -0500 Split off stat (benchmark) test failures into a separate section in the test runner summary. Stat tests are generally less reliable than other types of tests, so it's nice to have them in a separate section rather than interspersed with potential... Summary: ...correctness issues. Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D406 >--------------------------------------------------------------- 4667fb5201833e079256b7e4b420e5c87ca19b1a testsuite/driver/testglobals.py | 2 ++ testsuite/driver/testlib.py | 28 ++++++++++++++++++++-------- 2 files changed, 22 insertions(+), 8 deletions(-) diff --git a/testsuite/driver/testglobals.py b/testsuite/driver/testglobals.py index 7b9bd9a..643dad6 100644 --- a/testsuite/driver/testglobals.py +++ b/testsuite/driver/testglobals.py @@ -143,6 +143,8 @@ class TestRun: self.unexpected_passes = {} self.n_unexpected_failures = 0 self.unexpected_failures = {} + self.n_unexpected_stat_failures = 0 + self.unexpected_stat_failures = {} global t t = TestRun() diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 87e37d5..1549381 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -820,10 +820,16 @@ def do_test(name, way, func, args): elif passFail == 'fail': if getTestOpts().expect == 'pass' \ and way not in getTestOpts().expect_fail_for: - if_verbose(1, '*** unexpected failure for %s' % full_name) - t.n_unexpected_failures = t.n_unexpected_failures + 1 reason = result['reason'] - addFailingTestInfo(t.unexpected_failures, getTestOpts().testdir, name, reason, way) + tag = result.get('tag') + if tag == 'stat': + if_verbose(1, '*** unexpected stat test failure for %s' % full_name) + t.n_unexpected_stat_failures = t.n_unexpected_stat_failures + 1 + addFailingTestInfo(t.unexpected_stat_failures, getTestOpts().testdir, name, reason, way) + else: + if_verbose(1, '*** unexpected failure for %s' % full_name) + t.n_unexpected_failures = t.n_unexpected_failures + 1 + addFailingTestInfo(t.unexpected_failures, getTestOpts().testdir, name, reason, way) else: if getTestOpts().expect == 'missing-lib': t.n_missing_libs = t.n_missing_libs + 1 @@ -898,8 +904,8 @@ def badResult(result): def passed(): return {'passFail': 'pass'} -def failBecause(reason): - return {'passFail': 'fail', 'reason': reason} +def failBecause(reason, tag=None): + return {'passFail': 'fail', 'reason': reason, 'tag': tag} # ----------------------------------------------------------------------------- # Generic command tests @@ -1138,10 +1144,10 @@ def checkStats(name, way, stats_file, range_fields): print(field, 'value is too low:') print('(If this is because you have improved GHC, please') print('update the test so that GHC doesn\'t regress again)') - result = failBecause('stat too good') + result = failBecause('stat too good', tag='stat') if val > upperBound: print(field, 'value is too high:') - result = failBecause('stat not good enough') + result = failBecause('stat not good enough', tag='stat') if val < lowerBound or val > upperBound or config.verbose >= 4: valStr = str(val) @@ -2146,7 +2152,7 @@ def findTFiles_(path): def summary(t, file): file.write('\n') - printUnexpectedTests(file, [t.unexpected_passes, t.unexpected_failures]) + printUnexpectedTests(file, [t.unexpected_passes, t.unexpected_failures, t.unexpected_stat_failures]) file.write('OVERALL SUMMARY for test run started at ' + time.strftime("%c %Z", t.start_time) + '\n' + str(datetime.timedelta(seconds= @@ -2172,6 +2178,8 @@ def summary(t, file): + ' unexpected passes\n' + repr(t.n_unexpected_failures).rjust(8) + ' unexpected failures\n' + + repr(t.n_unexpected_stat_failures).rjust(8) + + ' unexpected stat failures\n' + '\n') if t.n_unexpected_passes > 0: @@ -2182,6 +2190,10 @@ def summary(t, file): file.write('Unexpected failures:\n') printFailingTestInfosSummary(file, t.unexpected_failures) + if t.n_unexpected_stat_failures > 0: + file.write('Unexpected stat failures:\n') + printFailingTestInfosSummary(file, t.unexpected_stat_failures) + if config.check_files_written: checkForFilesWrittenProblems(file) From git at git.haskell.org Fri Oct 31 20:54:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 20:54:05 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Add TcFlatten (5d5546d) Message-ID: <20141031205405.269FA3A300@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/5d5546d7a4936a4acc6d94a5ff7892aafd390e2a/ghc >--------------------------------------------------------------- commit 5d5546d7a4936a4acc6d94a5ff7892aafd390e2a Author: Simon Peyton Jones Date: Fri Oct 31 20:54:25 2014 +0000 Add TcFlatten >--------------------------------------------------------------- 5d5546d7a4936a4acc6d94a5ff7892aafd390e2a compiler/typecheck/TcFlatten.lhs | 1084 ++++++++++++++++++++++++++++++++++++++ 1 file changed, 1084 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 5d5546d7a4936a4acc6d94a5ff7892aafd390e2a From git at git.haskell.org Fri Oct 31 21:13:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 21:13:21 +0000 (UTC) Subject: [commit: ghc] master: remove old .NET related code (322c139) Message-ID: <20141031211321.209093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/322c1391dc2aae2e3c5d01a565850859e2faa90e/ghc >--------------------------------------------------------------- commit 322c1391dc2aae2e3c5d01a565850859e2faa90e Author: Yuras Shumovich Date: Fri Oct 31 16:12:19 2014 -0500 remove old .NET related code Summary: It seems to be dead anyway. Also update Haddock submodule. Test Plan: validate Reviewers: austin Reviewed By: austin Subscribers: thomie, goldfire, carter, simonmar Differential Revision: https://phabricator.haskell.org/D357 >--------------------------------------------------------------- 322c1391dc2aae2e3c5d01a565850859e2faa90e compiler/hsSyn/HsDecls.lhs | 13 +----------- compiler/hsSyn/HsUtils.lhs | 1 - compiler/iface/IfaceSyn.lhs | 12 ----------- compiler/iface/MkIface.lhs | 4 ---- compiler/iface/TcIface.lhs | 5 ----- compiler/prelude/PrelNames.lhs | 22 +------------------- compiler/rename/RnSource.lhs | 4 ---- compiler/typecheck/TcRnDriver.lhs | 4 ---- compiler/typecheck/TcTyClsDecls.lhs | 12 ----------- compiler/types/TyCon.lhs | 41 ++++--------------------------------- compiler/types/Type.lhs | 2 -- utils/haddock | 2 +- 12 files changed, 7 insertions(+), 115 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 322c1391dc2aae2e3c5d01a565850859e2faa90e From git at git.haskell.org Fri Oct 31 21:14:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 21:14:58 +0000 (UTC) Subject: [commit: ghc] master: Remove legacy support for -optdef flags (e466ea7) Message-ID: <20141031211458.4DE303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e466ea7a153a1b8d5bcfebf3dddaa33125c14c5d/ghc >--------------------------------------------------------------- commit e466ea7a153a1b8d5bcfebf3dddaa33125c14c5d Author: Thomas Miedema Date: Fri Oct 31 16:15:06 2014 -0500 Remove legacy support for -optdef flags Summary: -optdef flags were deprecated in or before 2008 Reviewers: austin Reviewed By: austin Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D409 GHC Trac Issues: #2773 >--------------------------------------------------------------- e466ea7a153a1b8d5bcfebf3dddaa33125c14c5d compiler/main/DynFlags.hs | 28 ++++------------------------ 1 file changed, 4 insertions(+), 24 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 166ceba..6db0f2c 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -1896,25 +1896,17 @@ addOptP f = alterSettings (\s -> s { sOpt_P = f : sOpt_P s}) setDepMakefile :: FilePath -> DynFlags -> DynFlags -setDepMakefile f d = d { depMakefile = deOptDep f } +setDepMakefile f d = d { depMakefile = f } setDepIncludePkgDeps :: Bool -> DynFlags -> DynFlags setDepIncludePkgDeps b d = d { depIncludePkgDeps = b } addDepExcludeMod :: String -> DynFlags -> DynFlags addDepExcludeMod m d - = d { depExcludeMods = mkModuleName (deOptDep m) : depExcludeMods d } + = d { depExcludeMods = mkModuleName m : depExcludeMods d } addDepSuffix :: FilePath -> DynFlags -> DynFlags -addDepSuffix s d = d { depSuffixes = deOptDep s : depSuffixes d } - --- XXX Legacy code: --- We used to use "-optdep-flag -optdeparg", so for legacy applications --- we need to strip the "-optdep" off of the arg -deOptDep :: String -> String -deOptDep x = case stripPrefix "-optdep" x of - Just rest -> rest - Nothing -> x +addDepSuffix s d = d { depSuffixes = s : depSuffixes d } addCmdlineFramework f d = d{ cmdlineFrameworks = f : cmdlineFrameworks d} @@ -2024,20 +2016,8 @@ parseDynamicFlagsFull :: MonadIO m -> [Located String] -- ^ arguments to parse -> m (DynFlags, [Located String], [Located String]) parseDynamicFlagsFull activeFlags cmdline dflags0 args = do - -- XXX Legacy support code - -- We used to accept things like - -- optdep-f -optdepdepend - -- optdep-f -optdep depend - -- optdep -f -optdepdepend - -- optdep -f -optdep depend - -- but the spaces trip up proper argument handling. So get rid of them. - let f (L p "-optdep" : L _ x : xs) = (L p ("-optdep" ++ x)) : f xs - f (x : xs) = x : f xs - f xs = xs - args' = f args - let ((leftover, errs, warns), dflags1) - = runCmdLine (processArgs activeFlags args') dflags0 + = runCmdLine (processArgs activeFlags args) dflags0 when (not (null errs)) $ liftIO $ throwGhcExceptionIO $ errorsToGhcException errs From git at git.haskell.org Fri Oct 31 22:44:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 31 Oct 2014 22:44:37 +0000 (UTC) Subject: [commit: ghc] wip/new-flatten-skolems-Oct14: Test Trac #9662 (f7a008e) Message-ID: <20141031224437.E30F33A300@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/f7a008e35c3bda82ac8fbeec3670a675e4021b83/ghc >--------------------------------------------------------------- commit f7a008e35c3bda82ac8fbeec3670a675e4021b83 Author: Simon Peyton Jones Date: Fri Oct 31 22:44:39 2014 +0000 Test Trac #9662 >--------------------------------------------------------------- f7a008e35c3bda82ac8fbeec3670a675e4021b83 testsuite/tests/indexed-types/should_fail/T9662.hs | 52 ++++++++++++++ .../tests/indexed-types/should_fail/T9662.stderr | 84 ++++++++++++++++++++++ testsuite/tests/indexed-types/should_fail/all.T | 1 + 3 files changed, 137 insertions(+) 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..22b34a1 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T9662.hs @@ -0,0 +1,52 @@ +{-# 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 +{- + (modify (atom:.atom:.atom:.atom) + (\(ix:.m:.n:.k) -> (ix:.k:.m:.n))) +-} 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..ad804ab --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T9662.stderr @@ -0,0 +1,84 @@ + +T9662.hs:46: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:43: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:44: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:46: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:43: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:44: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:46: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:43: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:44: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 diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index 1e2c43d..71c89d9 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, [''])