From git at git.haskell.org Mon Dec 1 07:40:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Dec 2014 07:40:34 +0000 (UTC) Subject: [commit: ghc] master: Revert "Remove RAWCPP_FLAGS" (0511c0a) Message-ID: <20141201074034.2F3003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0511c0ab09f705c3012b405781c9398a143b0e38/ghc >--------------------------------------------------------------- commit 0511c0ab09f705c3012b405781c9398a143b0e38 Author: Herbert Valerio Riedel Date: Mon Dec 1 08:37:09 2014 +0100 Revert "Remove RAWCPP_FLAGS" This reverts commit 460eebec65811c6a7bbe11645df322dda868e80d. Thomas requested to revert the commit with the words: > Please revert this commit, it is horribly wrong. I'll have a proper look > later, but not supplying `-traditional` to the C preprocessor is the cause > of #9828. the reverted commit was related to #9094 >--------------------------------------------------------------- 0511c0ab09f705c3012b405781c9398a143b0e38 compiler/ghc.mk | 4 ++-- mk/config.mk.in | 9 +++++++++ rules/manual-package-config.mk | 4 ++-- 3 files changed, 13 insertions(+), 4 deletions(-) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index 640bf75..c1b168e 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -269,10 +269,10 @@ compiler_CPP_OPTS += ${GhcCppOpts} define preprocessCompilerFiles # $0 = stage compiler/stage$1/build/Parser.y: compiler/parser/Parser.y.pp - $$(CPP) -P $$(compiler_CPP_OPTS) -x c $$< | grep -v '^#pragma GCC' > $$@ + $$(CPP) $$(RAWCPP_FLAGS) -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) -P $$(compiler_CPP_OPTS) -Icompiler/stage$1 -x c $$< | grep -v '^#pragma GCC' > $$@ + $$(CPP) $$(RAWCPP_FLAGS) -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 4f22c56..0f5820f 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -626,6 +626,15 @@ 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 56eea70..10629aa 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) -P \ + $$(CPP) $$(RAWCPP_FLAGS) -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) -P \ + $$(CPP) $$(RAWCPP_FLAGS) -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 Mon Dec 1 07:45:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Dec 2014 07:45:47 +0000 (UTC) Subject: [commit: ghc] master: unlit compiler/stranal/ modules (4b16ff6) Message-ID: <20141201074547.057933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4b16ff6d5d89ba7054daad312acf32de4140488e/ghc >--------------------------------------------------------------- commit 4b16ff6d5d89ba7054daad312acf32de4140488e Author: Herbert Valerio Riedel Date: Mon Dec 1 08:45:16 2014 +0100 unlit compiler/stranal/ modules Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D541 >--------------------------------------------------------------- 4b16ff6d5d89ba7054daad312acf32de4140488e compiler/stranal/{DmdAnal.lhs => DmdAnal.hs} | 93 +++++++++++---------- compiler/stranal/{WorkWrap.lhs => WorkWrap.hs} | 45 +++++----- compiler/stranal/{WwLib.lhs => WwLib.hs} | 110 ++++++++++++------------- 3 files changed, 120 insertions(+), 128 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4b16ff6d5d89ba7054daad312acf32de4140488e From git at git.haskell.org Mon Dec 1 09:54:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Dec 2014 09:54:18 +0000 (UTC) Subject: [commit: ghc] master: unlit compiler/types/ modules (e992317) Message-ID: <20141201095418.EACA13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e992317be141bb93363a13543d810da1ecfeccdd/ghc >--------------------------------------------------------------- commit e992317be141bb93363a13543d810da1ecfeccdd Author: Herbert Valerio Riedel Date: Mon Dec 1 10:52:09 2014 +0100 unlit compiler/types/ modules Differential Revision: https://phabricator.haskell.org/D544 >--------------------------------------------------------------- e992317be141bb93363a13543d810da1ecfeccdd compiler/types/{Class.lhs => Class.hs} | 55 +++--- compiler/types/{CoAxiom.lhs => CoAxiom.hs} | 66 +++---- compiler/types/{Coercion.lhs => Coercion.hs} | 172 ++++++++-------- compiler/types/{FamInstEnv.lhs => FamInstEnv.hs} | 141 ++++++------- compiler/types/{InstEnv.lhs => InstEnv.hs} | 76 ++++---- compiler/types/{Kind.lhs => Kind.hs} | 18 +- compiler/types/{OptCoercion.lhs => OptCoercion.hs} | 26 ++- compiler/types/{TyCon.lhs => TyCon.hs} | 99 ++++------ compiler/types/{TyCon.lhs-boot => TyCon.hs-boot} | 2 - compiler/types/{Type.lhs => Type.hs} | 217 +++++++++------------ compiler/types/{Type.lhs-boot => Type.hs-boot} | 2 - compiler/types/{TypeRep.lhs => TypeRep.hs} | 112 +++++------ .../types/{TypeRep.lhs-boot => TypeRep.hs-boot} | 3 - compiler/types/{Unify.lhs => Unify.hs} | 100 +++++----- 14 files changed, 478 insertions(+), 611 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e992317be141bb93363a13543d810da1ecfeccdd From git at git.haskell.org Mon Dec 1 14:19:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Dec 2014 14:19:23 +0000 (UTC) Subject: [commit: ghc] master: Fix the handling of instance signatures (Trac #9582, #9833) (e6a2050) Message-ID: <20141201141923.58FC03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e6a2050ebb6da316aecec66a6795715fbab355ca/ghc >--------------------------------------------------------------- commit e6a2050ebb6da316aecec66a6795715fbab355ca Author: Simon Peyton Jones Date: Mon Dec 1 11:43:20 2014 +0000 Fix the handling of instance signatures (Trac #9582, #9833) This finally solves the issue of instance-method signatures that are more polymorphic than the instanted class method. See Note [Instance method signatures] in TcInstDcls. A very nice fix for the two Trac tickets above. >--------------------------------------------------------------- e6a2050ebb6da316aecec66a6795715fbab355ca compiler/typecheck/TcBinds.lhs | 18 ++- compiler/typecheck/TcClassDcl.lhs | 16 +-- compiler/typecheck/TcInstDcls.lhs | 121 ++++++++++++--------- docs/users_guide/glasgow_exts.xml | 29 ++++- .../tests/indexed-types/should_compile/T9582.hs | 14 +++ testsuite/tests/indexed-types/should_compile/all.T | 1 + testsuite/tests/polykinds/T9833.hs | 18 +++ testsuite/tests/polykinds/all.T | 2 + testsuite/tests/typecheck/should_fail/T6001.stderr | 9 +- testsuite/tests/typecheck/should_fail/T7545.hs | 1 + testsuite/tests/typecheck/should_fail/T7545.stderr | 5 - testsuite/tests/typecheck/should_fail/all.T | 2 +- 12 files changed, 157 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 e6a2050ebb6da316aecec66a6795715fbab355ca From git at git.haskell.org Mon Dec 1 14:29:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Dec 2014 14:29:00 +0000 (UTC) Subject: [commit: ghc] master: Wibble to the "instance signatures" patch (e77faac) Message-ID: <20141201142900.B46443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e77faaced8da576e65108d961ce9869502b62f2a/ghc >--------------------------------------------------------------- commit e77faaced8da576e65108d961ce9869502b62f2a Author: Simon Peyton Jones Date: Mon Dec 1 14:29:30 2014 +0000 Wibble to the "instance signatures" patch Sorry about this. I somehow failed to include this one line in my patch. >--------------------------------------------------------------- e77faaced8da576e65108d961ce9869502b62f2a compiler/typecheck/TcBinds.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcBinds.lhs b/compiler/typecheck/TcBinds.lhs index f2f4b1a..f1a6463 100644 --- a/compiler/typecheck/TcBinds.lhs +++ b/compiler/typecheck/TcBinds.lhs @@ -1371,7 +1371,7 @@ tcTySigs hs_sigs tcTySig :: LSig Name -> TcM ([TcSigInfo], [TcTyVar]) tcTySig (L _ (IdSig id)) - = do { sig <- instTcTySigFromId _ id + = do { sig <- instTcTySigFromId id ; return ([sig], []) } tcTySig (L loc (TypeSig names@(L _ name1 : _) hs_ty wcs)) = setSrcSpan loc $ From git at git.haskell.org Mon Dec 1 15:26:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Dec 2014 15:26:28 +0000 (UTC) Subject: [commit: ghc] master: Remove references to Parser.y.pp (370b0f5) Message-ID: <20141201152628.CAED73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/370b0f5bac51b99525d09226a988ebddde9e09bd/ghc >--------------------------------------------------------------- commit 370b0f5bac51b99525d09226a988ebddde9e09bd Author: Thomas Miedema Date: Mon Dec 1 09:26:51 2014 -0600 Remove references to Parser.y.pp Summary: Commit 37d64a51348a803a1cf974d9e97ec9231215064a removed the preprocessing step for Parser.y. Reviewers: rodlogic, austin Reviewed By: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D543 >--------------------------------------------------------------- 370b0f5bac51b99525d09226a988ebddde9e09bd compiler/ghc.mk | 3 --- compiler/hsSyn/HsTypes.lhs | 2 +- compiler/rename/RnExpr.lhs | 4 ++-- 3 files changed, 3 insertions(+), 6 deletions(-) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index c1b168e..a33fde8 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -268,9 +268,6 @@ 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' > $$@ - 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' > $$@ diff --git a/compiler/hsSyn/HsTypes.lhs b/compiler/hsSyn/HsTypes.lhs index af888cd..37aaa56 100644 --- a/compiler/hsSyn/HsTypes.lhs +++ b/compiler/hsSyn/HsTypes.lhs @@ -475,7 +475,7 @@ mk_forall_ty exp tvs ty = HsForAllTy exp Nothing (mkHsQTvs tvs -- Even if tvs is empty, we still make a HsForAll! -- In the Implicit case, this signals the place to do implicit quantification -- In the Explicit case, it prevents implicit quantification - -- (see the sigtype production in Parser.y.pp) + -- (see the sigtype production in Parser.y) -- so that (forall. ty) isn't implicitly quantified plus :: HsExplicitFlag -> HsExplicitFlag -> HsExplicitFlag diff --git a/compiler/rename/RnExpr.lhs b/compiler/rename/RnExpr.lhs index edf16b8..533cdcd 100644 --- a/compiler/rename/RnExpr.lhs +++ b/compiler/rename/RnExpr.lhs @@ -166,7 +166,7 @@ rnExpr (HsQuasiQuoteE qq) --------------------------------------------- -- Sections --- See Note [Parsing sections] in Parser.y.pp +-- See Note [Parsing sections] in Parser.y rnExpr (HsPar (L loc (section@(SectionL {})))) = do { (section', fvs) <- rnSection section ; return (HsPar (L loc section'), fvs) } @@ -339,7 +339,7 @@ arrowFail e ; return (hsHoleExpr, emptyFVs) } ---------------------- --- See Note [Parsing sections] in Parser.y.pp +-- See Note [Parsing sections] in Parser.y rnSection :: HsExpr RdrName -> RnM (HsExpr Name, FreeVars) rnSection section@(SectionR op expr) = do { (op', fvs_op) <- rnLExpr op From git at git.haskell.org Mon Dec 1 17:07:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Dec 2014 17:07:18 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #7908 (c34ef46) Message-ID: <20141201170718.389313A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c34ef467429771edf0b2b18c05994c461c82df38/ghc >--------------------------------------------------------------- commit c34ef467429771edf0b2b18c05994c461c82df38 Author: Simon Peyton Jones Date: Mon Dec 1 17:04:47 2014 +0000 Test Trac #7908 Fixed by e6a2050ebb6da316aecec66a6795715fbab355ca along with #9582, #9833 >--------------------------------------------------------------- c34ef467429771edf0b2b18c05994c461c82df38 testsuite/tests/polykinds/T7908.hs | 49 ++++++++++++++++++++++++++++++++++++++ testsuite/tests/polykinds/all.T | 2 +- 2 files changed, 50 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/polykinds/T7908.hs b/testsuite/tests/polykinds/T7908.hs new file mode 100644 index 0000000..1bb4cc5 --- /dev/null +++ b/testsuite/tests/polykinds/T7908.hs @@ -0,0 +1,49 @@ +{-# LANGUAGE GADTs, InstanceSigs, DataKinds, PolyKinds, RankNTypes, LambdaCase #-} + +module T7908 where + +class Monad' (m :: (k -> *) -> *) where + return' :: c a -> m c + (>>>=) :: m c -> (forall a . c a -> m d) -> m d + (>>-) :: m c -> (forall a . c a -> d) -> d + + +data Nat = Z' | S' Nat + +data Nat' (n :: Nat) where + Z :: Nat' Z' + S :: Nat' n -> Nat' (S' n) + +data Hidden :: (k -> *) -> * where + Hide :: m a -> Hidden m + +instance Monad' Hidden where + --return' :: forall (c :: k -> *) (a :: k) . c a -> Hidden c + return' = Hide + --(>>>=) :: forall (c :: k -> *) (d :: k -> *) . Hidden c -> (forall (a :: k) . c a -> Hidden d) -> Hidden d + Hide a >>>= f = f a + --(>>-) :: forall (c :: k -> *) d . Hidden c -> (forall (a :: k) . c a -> d) -> d + Hide a >>- f = f a + + +int2nat' 0 = return' Z +int2nat' i = (int2nat' $ i - 1) >>>= (\n -> return' $ S n) + + +data Fin (m :: Nat) (n :: Nat) where + Fz :: Fin (S' m) Z' + Fs :: Fin m n -> Fin (S' m) (S' n) + +-- N.B. not total! +nat2fin :: Nat' f -> Hidden Nat' -> Hidden (Fin f) +nat2fin (S _) (Hide Z) = return' Fz +nat2fin (S f) n = n >>>= (\case S n -> (nat2fin f (return' n) >>>= (\fn -> return' $ Fs fn))) + +fin2int :: Hidden (Fin f) -> Int +fin2int f = f >>- go + where go :: Fin f n -> Int + go Fz = 0 + go (Fs f) = 1 + go f + + +test = fin2int (nat2fin (S $ S Z) $ return' (S Z)) diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index 387e2bf..c86e317 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -113,4 +113,4 @@ test('T9569', normal, compile, ['']) test('T9838', normal, multimod_compile, ['T9838.hs','-v0']) test('T9574', normal, compile_fail, ['']) test('T9833', normal, compile, ['']) - +test('T7908', normal, compile, ['']) From git at git.haskell.org Mon Dec 1 17:07:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Dec 2014 17:07:20 +0000 (UTC) Subject: [commit: ghc] master: Fix parser for UNPACK pragmas (1d32a85) Message-ID: <20141201170720.D1EBD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1d32a8503c2ebfab2bbdb696fe65dd0823d1ed27/ghc >--------------------------------------------------------------- commit 1d32a8503c2ebfab2bbdb696fe65dd0823d1ed27 Author: Simon Peyton Jones Date: Mon Dec 1 17:07:48 2014 +0000 Fix parser for UNPACK pragmas {-# NOUNPACK #-} {-# NOUNPACK #-} ! were being parsed the same way. The former was wrong. Thanks to Alan Zimmerman for pointing this out >--------------------------------------------------------------- 1d32a8503c2ebfab2bbdb696fe65dd0823d1ed27 compiler/parser/Parser.y | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index e3f82ce..c7143ae 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -1350,11 +1350,11 @@ sigtypes1 :: { (OrdList (LHsType RdrName)) } -- Always HsForAllTys -- Types strict_mark :: { Located ([AddAnn],HsBang) } - : '!' { sL1 $1 ([],HsUserBang Nothing True) } - | '{-# UNPACK' '#-}' { sLL $1 $> ([mo $1,mc $2],HsUserBang (Just True) False) } - | '{-# NOUNPACK' '#-}' { sLL $1 $> ([mo $1,mc $2],HsUserBang (Just False) True) } - | '{-# UNPACK' '#-}' '!' { sLL $1 $> ([mo $1,mc $2],HsUserBang (Just True) True) } - | '{-# NOUNPACK' '#-}' '!' { sLL $1 $> ([mo $1,mc $2],HsUserBang (Just False) True) } + : '!' { sL1 $1 ([], HsUserBang Nothing True) } + | '{-# UNPACK' '#-}' { sLL $1 $> ([mo $1,mc $2], HsUserBang (Just True) False) } + | '{-# NOUNPACK' '#-}' { sLL $1 $> ([mo $1,mc $2], HsUserBang (Just False) False) } + | '{-# UNPACK' '#-}' '!' { sLL $1 $> ([mo $1,mc $2], HsUserBang (Just True) True) } + | '{-# NOUNPACK' '#-}' '!' { sLL $1 $> ([mo $1,mc $2], HsUserBang (Just False) True) } -- Although UNPACK with no '!' is illegal, we get a -- better error message if we parse it here From git at git.haskell.org Mon Dec 1 20:30:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Dec 2014 20:30:37 +0000 (UTC) Subject: [commit: ghc] master: Fix malformed `configure` script (2d324dd) Message-ID: <20141201203037.2F43D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2d324dd41d1c5ee5f9fd667d6cae48539e6279ba/ghc >--------------------------------------------------------------- commit 2d324dd41d1c5ee5f9fd667d6cae48539e6279ba Author: Herbert Valerio Riedel Date: Mon Dec 1 21:30:10 2014 +0100 Fix malformed `configure` script Don't pass empty string `[]` as "action-if-not-given" to `AC_ARG_ENABLE()` macro, as this would otherwise lead to an empty else-block in the resulting bash `configure` script. This bug was introduced via cb0a503a. This issue was pointed out by @christiaanb Reviewed By: christiaanb Differential Revision: https://phabricator.haskell.org/D545 >--------------------------------------------------------------- 2d324dd41d1c5ee5f9fd667d6cae48539e6279ba aclocal.m4 | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 2aa55d7..6caa10a 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2277,8 +2277,7 @@ AC_DEFUN([FP_BFD_SUPPORT], [ [],dnl bfd seems to work [AC_MSG_ERROR([can't use 'bfd' library])]) LIBS="$save_LIBS" - ], - [] + ] ) ]) From git at git.haskell.org Tue Dec 2 07:40:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 07:40:26 +0000 (UTC) Subject: [commit: ghc] master: Mention existence of 'Natural' in "Data.Word" (a29e295) Message-ID: <20141202074026.E794D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a29e295c6fddfb0bbd390cff8cf2e5dbe9b1aa5b/ghc >--------------------------------------------------------------- commit a29e295c6fddfb0bbd390cff8cf2e5dbe9b1aa5b Author: Herbert Valerio Riedel Date: Tue Dec 2 08:38:38 2014 +0100 Mention existence of 'Natural' in "Data.Word" This replaces the note mentioning the lack of a `Natural`-type by a note pointing to the new "Numeric.Natural" (#9818) module. >--------------------------------------------------------------- a29e295c6fddfb0bbd390cff8cf2e5dbe9b1aa5b libraries/base/Data/Word.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/libraries/base/Data/Word.hs b/libraries/base/Data/Word.hs index 8af39b6..f20844f 100644 --- a/libraries/base/Data/Word.hs +++ b/libraries/base/Data/Word.hs @@ -43,10 +43,8 @@ import GHC.Word common cases so should be fast enough. Coercing word types to and from integer types preserves representation, not sign. -* It would be very natural to add a type @Natural@ providing an unbounded - size unsigned integer, just as 'Prelude.Integer' provides unbounded - size signed integers. We do not do that yet since there is no demand - for it. +* An unbounded size unsigned integer type is available with + 'Numeric.Natural.Natural'. * The rules that hold for 'Prelude.Enum' instances over a bounded type such as 'Prelude.Int' (see the section of the Haskell report dealing From git at git.haskell.org Tue Dec 2 10:22:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 10:22:08 +0000 (UTC) Subject: [commit: ghc] master: Uncomment the instance signatures, to activate the test (9437a24) Message-ID: <20141202102208.83DC43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9437a24d36f248fcd0b2709ae417b999d6a17444/ghc >--------------------------------------------------------------- commit 9437a24d36f248fcd0b2709ae417b999d6a17444 Author: Simon Peyton Jones Date: Mon Dec 1 22:29:18 2014 +0000 Uncomment the instance signatures, to activate the test >--------------------------------------------------------------- 9437a24d36f248fcd0b2709ae417b999d6a17444 testsuite/tests/polykinds/T7908.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/polykinds/T7908.hs b/testsuite/tests/polykinds/T7908.hs index 1bb4cc5..5895bbe 100644 --- a/testsuite/tests/polykinds/T7908.hs +++ b/testsuite/tests/polykinds/T7908.hs @@ -18,11 +18,11 @@ data Hidden :: (k -> *) -> * where Hide :: m a -> Hidden m instance Monad' Hidden where - --return' :: forall (c :: k -> *) (a :: k) . c a -> Hidden c + return' :: forall (c :: k -> *) (a :: k) . c a -> Hidden c return' = Hide - --(>>>=) :: forall (c :: k -> *) (d :: k -> *) . Hidden c -> (forall (a :: k) . c a -> Hidden d) -> Hidden d + (>>>=) :: forall (c :: k -> *) (d :: k -> *) . Hidden c -> (forall (a :: k) . c a -> Hidden d) -> Hidden d Hide a >>>= f = f a - --(>>-) :: forall (c :: k -> *) d . Hidden c -> (forall (a :: k) . c a -> d) -> d + (>>-) :: forall (c :: k -> *) d . Hidden c -> (forall (a :: k) . c a -> d) -> d Hide a >>- f = f a From git at git.haskell.org Tue Dec 2 10:22:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 10:22:11 +0000 (UTC) Subject: [commit: ghc] master: Revert "Add purgeObj() to remove the symbol table entries for an object" (7932b2a) Message-ID: <20141202102211.340733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7932b2adaecac6c86038176d909c20ad1b1f9604/ghc >--------------------------------------------------------------- commit 7932b2adaecac6c86038176d909c20ad1b1f9604 Author: Simon Peyton Jones Date: Mon Dec 1 22:39:12 2014 +0000 Revert "Add purgeObj() to remove the symbol table entries for an object" This reverts commit 9e6e4796437a7fc23e83605a45db9b2663570123. I reverted it because one of these two patches 9e6e4796437a7fc23e83605a45db9b2663570123 Add purgeObj() b5e8b3b162b3ff15ae6caf1afc659565365f54a8 Make the linker API thread-safe causes a seg-fault on Windows. The seg-fault happens immediately the linker is invoked, in ghci or in Template Haskell. I believe that it is the "linker API thread-safe" commit that causes the seg-fault; it happens even if the "purgeObj" commit alone is reverted. But since the two patches mess with the same code, to revert the "linker API" patch I had revert both. >--------------------------------------------------------------- 7932b2adaecac6c86038176d909c20ad1b1f9604 includes/rts/Linker.h | 3 -- rts/Linker.c | 74 ++++++++++---------------------- testsuite/tests/rts/linker_unload.c | 37 ---------------- testsuite/tests/rts/linker_unload.stdout | 2 +- 4 files changed, 24 insertions(+), 92 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7932b2adaecac6c86038176d909c20ad1b1f9604 From git at git.haskell.org Tue Dec 2 10:22:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 10:22:13 +0000 (UTC) Subject: [commit: ghc] master: Revert "Make the linker API thread-safe" (4b51194) Message-ID: <20141202102213.CB2F13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4b51194df4090d984f02c12128e868077660fb8b/ghc >--------------------------------------------------------------- commit 4b51194df4090d984f02c12128e868077660fb8b Author: Simon Peyton Jones Date: Tue Dec 2 10:05:49 2014 +0000 Revert "Make the linker API thread-safe" This reverts commit b5e8b3b162b3ff15ae6caf1afc659565365f54a8. I reverted it because one of these two patches 9e6e4796437a7fc23e83605a45db9b2663570123 Add purgeObj() b5e8b3b162b3ff15ae6caf1afc659565365f54a8 Make the linker API thread-safe causes a seg-fault on Windows. The seg-fault happens immediately the linker is invoked, in ghci or in Template Haskell. I believe that it is the "linker API thread-safe" commit that causes the seg-fault; it happens even if the "purgeObj" commit alone is reverted. But since the two patches mess with the same code, to revert the "linker API" patch I had revert both. >--------------------------------------------------------------- 4b51194df4090d984f02c12128e868077660fb8b docs/users_guide/7.10.1-notes.xml | 6 +-- rts/CheckUnload.c | 4 -- rts/Linker.c | 105 +++++++++++++------------------------- rts/LinkerInternals.h | 4 -- testsuite/tests/rts/Makefile | 8 +-- testsuite/tests/rts/T2615.hs | 1 - testsuite/tests/rts/rdynamic.hs | 2 - 7 files changed, 41 insertions(+), 89 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4b51194df4090d984f02c12128e868077660fb8b From git at git.haskell.org Tue Dec 2 11:11:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 11:11:23 +0000 (UTC) Subject: [commit: ghc] branch 'ghc-validate' created Message-ID: <20141202111123.49CFC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : ghc-validate Referencing: b8e1da1b277224162039cdbce757812aa5440905 From git at git.haskell.org Tue Dec 2 11:11:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 11:11:25 +0000 (UTC) Subject: [commit: ghc] ghc-validate: Fix test suite race on T5462 (solves intermittent T5462Yes1/T5462Yes2/T5462No1 failure) (b8e1da1) Message-ID: <20141202111125.D7AB23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-validate Link : http://ghc.haskell.org/trac/ghc/changeset/b8e1da1b277224162039cdbce757812aa5440905/ghc >--------------------------------------------------------------- commit b8e1da1b277224162039cdbce757812aa5440905 Author: Edward Z. Yang Date: Tue Dec 2 03:12:14 2014 -0800 Fix test suite race on T5462 (solves intermittent T5462Yes1/T5462Yes2/T5462No1 failure) Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- b8e1da1b277224162039cdbce757812aa5440905 testsuite/tests/generics/T5462No1.stderr | 4 ++-- testsuite/tests/generics/all.T | 6 +++--- 2 files changed, 5 insertions(+), 5 deletions(-) diff --git a/testsuite/tests/generics/T5462No1.stderr b/testsuite/tests/generics/T5462No1.stderr index 9deb08a..9a4418a 100644 --- a/testsuite/tests/generics/T5462No1.stderr +++ b/testsuite/tests/generics/T5462No1.stderr @@ -1,5 +1,5 @@ -[1 of 2] Compiling GFunctor ( GFunctor/GFunctor.hs, GFunctor/GFunctor.o ) -[2 of 2] Compiling T5462No1 ( T5462No1.hs, T5462No1.o ) +[1 of 2] Compiling GFunctor ( GFunctor/GFunctor.hs, T5462No1/GFunctor.o ) +[2 of 2] Compiling T5462No1 ( T5462No1.hs, T5462No1/T5462No1.o ) T5462No1.hs:24:42: Can't make a derived instance of ?GFunctor F?: diff --git a/testsuite/tests/generics/all.T b/testsuite/tests/generics/all.T index 694f214..d959d0c 100644 --- a/testsuite/tests/generics/all.T +++ b/testsuite/tests/generics/all.T @@ -19,9 +19,9 @@ test('GenCannotDoRep1_6', normal, compile_fail, ['']) test('GenCannotDoRep1_7', normal, compile_fail, ['']) test('GenCannotDoRep1_8', normal, compile_fail, ['']) -test('T5462Yes1', normal, multimod_compile_and_run, ['T5462Yes1', '-iGEq -iGEnum -iGFunctor']) -test('T5462Yes2', normal, multimod_compile_and_run, ['T5462Yes2', '-iGFunctor']) -test('T5462No1', normal, multimod_compile_fail, ['T5462No1', '-iGFunctor']) +test('T5462Yes1', normal, multimod_compile_and_run, ['T5462Yes1', '-iGEq -iGEnum -iGFunctor -outputdir=out_T5462Yes1']) +test('T5462Yes2', normal, multimod_compile_and_run, ['T5462Yes2', '-iGFunctor -outputdir=out_T5462Yes2']) +test('T5462No1', normal, multimod_compile_fail, ['T5462No1', '-iGFunctor -outputdir=T5462No1']) test('T5884', normal, compile, ['']) test('GenNewtype', normal, compile_and_run, ['']) From git at git.haskell.org Tue Dec 2 11:11:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 11:11:55 +0000 (UTC) Subject: [commit: ghc] master: Fix test suite race on T5462 (solves intermittent T5462Yes1/T5462Yes2/T5462No1 failure) (06eaa64) Message-ID: <20141202111155.3052A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/06eaa64d49a7c5a38018c89d8a8c9ab2be8b569a/ghc >--------------------------------------------------------------- commit 06eaa64d49a7c5a38018c89d8a8c9ab2be8b569a Author: Edward Z. Yang Date: Tue Dec 2 03:12:14 2014 -0800 Fix test suite race on T5462 (solves intermittent T5462Yes1/T5462Yes2/T5462No1 failure) Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 06eaa64d49a7c5a38018c89d8a8c9ab2be8b569a testsuite/tests/generics/T5462No1.stderr | 4 ++-- testsuite/tests/generics/all.T | 6 +++--- 2 files changed, 5 insertions(+), 5 deletions(-) diff --git a/testsuite/tests/generics/T5462No1.stderr b/testsuite/tests/generics/T5462No1.stderr index 9deb08a..9a4418a 100644 --- a/testsuite/tests/generics/T5462No1.stderr +++ b/testsuite/tests/generics/T5462No1.stderr @@ -1,5 +1,5 @@ -[1 of 2] Compiling GFunctor ( GFunctor/GFunctor.hs, GFunctor/GFunctor.o ) -[2 of 2] Compiling T5462No1 ( T5462No1.hs, T5462No1.o ) +[1 of 2] Compiling GFunctor ( GFunctor/GFunctor.hs, T5462No1/GFunctor.o ) +[2 of 2] Compiling T5462No1 ( T5462No1.hs, T5462No1/T5462No1.o ) T5462No1.hs:24:42: Can't make a derived instance of ?GFunctor F?: diff --git a/testsuite/tests/generics/all.T b/testsuite/tests/generics/all.T index 694f214..d959d0c 100644 --- a/testsuite/tests/generics/all.T +++ b/testsuite/tests/generics/all.T @@ -19,9 +19,9 @@ test('GenCannotDoRep1_6', normal, compile_fail, ['']) test('GenCannotDoRep1_7', normal, compile_fail, ['']) test('GenCannotDoRep1_8', normal, compile_fail, ['']) -test('T5462Yes1', normal, multimod_compile_and_run, ['T5462Yes1', '-iGEq -iGEnum -iGFunctor']) -test('T5462Yes2', normal, multimod_compile_and_run, ['T5462Yes2', '-iGFunctor']) -test('T5462No1', normal, multimod_compile_fail, ['T5462No1', '-iGFunctor']) +test('T5462Yes1', normal, multimod_compile_and_run, ['T5462Yes1', '-iGEq -iGEnum -iGFunctor -outputdir=out_T5462Yes1']) +test('T5462Yes2', normal, multimod_compile_and_run, ['T5462Yes2', '-iGFunctor -outputdir=out_T5462Yes2']) +test('T5462No1', normal, multimod_compile_fail, ['T5462No1', '-iGFunctor -outputdir=T5462No1']) test('T5884', normal, compile, ['']) test('GenNewtype', normal, compile_and_run, ['']) From git at git.haskell.org Tue Dec 2 13:10:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 13:10:49 +0000 (UTC) Subject: [commit: ghc] master: Comments and formatting in TyCon (5d9bb56) Message-ID: <20141202131049.B105E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5d9bb563b5d2cea4635ded27a35dfc421c5558db/ghc >--------------------------------------------------------------- commit 5d9bb563b5d2cea4635ded27a35dfc421c5558db Author: Jan Stolarek Date: Tue Dec 2 10:42:49 2014 +0100 Comments and formatting in TyCon >--------------------------------------------------------------- 5d9bb563b5d2cea4635ded27a35dfc421c5558db compiler/types/TyCon.hs | 199 ++++++++++++++++++++++++++++-------------------- 1 file changed, 118 insertions(+), 81 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5d9bb563b5d2cea4635ded27a35dfc421c5558db From git at git.haskell.org Tue Dec 2 13:10:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 13:10:52 +0000 (UTC) Subject: [commit: ghc] master: Remove references to SynTyCon. Fixes #9812 (668a137) Message-ID: <20141202131052.47D5C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/668a1379778189495679840e0151dfceed4b8ef7/ghc >--------------------------------------------------------------- commit 668a1379778189495679840e0151dfceed4b8ef7 Author: Jan Stolarek Date: Tue Dec 2 13:57:46 2014 +0100 Remove references to SynTyCon. Fixes #9812 >--------------------------------------------------------------- 668a1379778189495679840e0151dfceed4b8ef7 compiler/typecheck/TcTyDecls.lhs | 9 +++++---- compiler/types/TyCon.hs | 4 ++-- compiler/vectorise/Vectorise/Utils/Base.hs | 6 +++--- compiler/vectorise/Vectorise/Utils/PADict.hs | 3 ++- 4 files changed, 12 insertions(+), 10 deletions(-) diff --git a/compiler/typecheck/TcTyDecls.lhs b/compiler/typecheck/TcTyDecls.lhs index c998853..3f8b234 100644 --- a/compiler/typecheck/TcTyDecls.lhs +++ b/compiler/typecheck/TcTyDecls.lhs @@ -97,10 +97,10 @@ If we reverse this decision, this comment came from tcTyDecl1, and should We'd also need to add back in this definition -synTyConsOfType :: Type -> [TyCon] +synonymTyConsOfType :: Type -> [TyCon] -- Does not look through type synonyms at all -- Return a list of synonym tycons -synTyConsOfType ty +synonymTyConsOfType ty = nameEnvElts (go ty) where go :: Type -> NameEnv TyCon -- The NameEnv does duplicate elim @@ -110,8 +110,9 @@ synTyConsOfType ty go (FunTy a b) = go a `plusNameEnv` go b go (ForAllTy _ ty) = go ty - go_tc tc tys | isSynTyCon tc = extendNameEnv (go_s tys) (tyConName tc) tc - | otherwise = go_s tys + go_tc tc tys | isTypeSynonymTyCon tc = extendNameEnv (go_s tys) + (tyConName tc) tc + | otherwise = go_s tys go_s tys = foldr (plusNameEnv . go) emptyNameEnv tys ---------------------------------------- END NOTE ] diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index 5a2b33e..4283545 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -140,14 +140,14 @@ Note [Type synonym families] * Translation of type family decl: type family F a :: * translates to - a SynTyCon 'F', whose SynTyConRhs is OpenSynFamilyTyCon + a FamilyTyCon 'F', whose FamTyConFlav is OpenSynFamilyTyCon type family G a :: * where G Int = Bool G Bool = Char G a = () translates to - a SynTyCon 'G', whose SynTyConRhs is ClosedSynFamilyTyCon, with the + a FamilyTyCon 'G', whose FamTyConFlav is ClosedSynFamilyTyCon, with the appropriate CoAxiom representing the equations * In the future we might want to support diff --git a/compiler/vectorise/Vectorise/Utils/Base.hs b/compiler/vectorise/Vectorise/Utils/Base.hs index 7d4bae3..dc1f210 100644 --- a/compiler/vectorise/Vectorise/Utils/Base.hs +++ b/compiler/vectorise/Vectorise/Utils/Base.hs @@ -24,7 +24,7 @@ module Vectorise.Utils.Base , pdatasReprTyConExact , pdataUnwrapScrut - , preprSynTyCon + , preprFamInst ) where import Vectorise.Monad @@ -258,5 +258,5 @@ pdataUnwrapScrut (ve, le) -- |Get the representation tycon of the 'PRepr' type family for a given type. -- -preprSynTyCon :: Type -> VM FamInstMatch -preprSynTyCon ty = builtin preprTyCon >>= (`lookupFamInst` [ty]) +preprFamInst :: Type -> VM FamInstMatch +preprFamInst ty = builtin preprTyCon >>= (`lookupFamInst` [ty]) diff --git a/compiler/vectorise/Vectorise/Utils/PADict.hs b/compiler/vectorise/Vectorise/Utils/PADict.hs index 01fbede..c2ca20a 100644 --- a/compiler/vectorise/Vectorise/Utils/PADict.hs +++ b/compiler/vectorise/Vectorise/Utils/PADict.hs @@ -118,7 +118,8 @@ paMethod method _ ty prDictOfPReprInst :: Type -> VM CoreExpr prDictOfPReprInst ty = do - { (FamInstMatch { fim_instance = prepr_fam, fim_tys = prepr_args }) <- preprSynTyCon ty + { (FamInstMatch { fim_instance = prepr_fam, fim_tys = prepr_args }) + <- preprFamInst ty ; prDictOfPReprInstTyCon ty (famInstAxiom prepr_fam) prepr_args } From git at git.haskell.org Tue Dec 2 13:20:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 13:20:48 +0000 (UTC) Subject: [commit: ghc] branch 'ghc-validate' deleted Message-ID: <20141202132048.1D4833A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: ghc-validate From git at git.haskell.org Tue Dec 2 13:27:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 13:27:40 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #4921 (30d2605) Message-ID: <20141202132740.EAACD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/30d260586d46466419b109057ec87d4f097331a1/ghc >--------------------------------------------------------------- commit 30d260586d46466419b109057ec87d4f097331a1 Author: Simon Peyton Jones Date: Tue Dec 2 12:08:57 2014 +0000 Test Trac #4921 >--------------------------------------------------------------- 30d260586d46466419b109057ec87d4f097331a1 testsuite/tests/typecheck/should_fail/T4921.hs | 12 ++++++++++++ testsuite/tests/typecheck/should_fail/T4921.stderr | 19 +++++++++++++++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 32 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T4921.hs b/testsuite/tests/typecheck/should_fail/T4921.hs new file mode 100644 index 0000000..b024967 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T4921.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE MultiParamTypeClasses #-} +module T4921 where + +class C a b where + f :: (a,b) + +instance C Int Char where + f = undefined + +x = fst f + +y = fst f :: Int diff --git a/testsuite/tests/typecheck/should_fail/T4921.stderr b/testsuite/tests/typecheck/should_fail/T4921.stderr new file mode 100644 index 0000000..c304b05 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T4921.stderr @@ -0,0 +1,19 @@ + +T4921.hs:10:9: + No instance for (C a0 b1) arising from a use of ?f? + The type variables ?a0?, ?b1? are ambiguous + Relevant bindings include x :: a0 (bound at T4921.hs:10:1) + Note: there is a potential instance available: + instance C Int Char -- Defined at T4921.hs:7:10 + In the first argument of ?fst?, namely ?f? + In the expression: fst f + In an equation for ?x?: x = fst f + +T4921.hs:12:9: + No instance for (C Int b0) arising from a use of ?f? + The type variable ?b0? is ambiguous + Note: there is a potential instance available: + instance C Int Char -- Defined at T4921.hs:7:10 + In the first argument of ?fst?, namely ?f? + In the expression: fst f :: Int + In an equation for ?y?: y = fst f :: Int diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 7d1e558..d3c8941 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -345,3 +345,4 @@ test('T9201', normal, compile_fail, ['']) test('T9109', normal, compile_fail, ['']) test('T9497d', normal, compile_fail, ['-fdefer-type-errors -fno-defer-typed-holes']) test('T8044', normal, compile_fail, ['']) +test('T4921', normal, compile_fail, ['']) From git at git.haskell.org Tue Dec 2 13:27:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 13:27:43 +0000 (UTC) Subject: [commit: ghc] master: Rename Untouchables to TcLevel (26a3d0f) Message-ID: <20141202132743.A629A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/26a3d0fe019c52b37ff51d5abcf0d7fdabfa160a/ghc >--------------------------------------------------------------- commit 26a3d0fe019c52b37ff51d5abcf0d7fdabfa160a Author: Simon Peyton Jones Date: Tue Dec 2 11:13:56 2014 +0000 Rename Untouchables to TcLevel This is a long-overdue renaming Untouchables --> TcLevel It is renaming only; no change in functionality. We really wanted to get this done before the 7.10 fork. >--------------------------------------------------------------- 26a3d0fe019c52b37ff51d5abcf0d7fdabfa160a compiler/typecheck/TcBinds.lhs | 8 +-- compiler/typecheck/TcCanonical.lhs | 4 +- compiler/typecheck/TcErrors.lhs | 4 +- compiler/typecheck/TcFlatten.lhs | 14 ++--- compiler/typecheck/TcInteract.lhs | 30 +++++----- compiler/typecheck/TcMType.lhs | 4 +- compiler/typecheck/TcPatSyn.lhs | 8 +-- compiler/typecheck/TcRnDriver.lhs | 6 +- compiler/typecheck/TcRnMonad.lhs | 34 +++++------ compiler/typecheck/TcRnTypes.lhs | 16 ++--- compiler/typecheck/TcRules.lhs | 4 +- compiler/typecheck/TcSMonad.lhs | 38 ++++++------ compiler/typecheck/TcSimplify.lhs | 62 +++++++++---------- compiler/typecheck/TcType.lhs | 118 +++++++++++++++++++------------------ compiler/typecheck/TcUnify.lhs | 10 ++-- 15 files changed, 181 insertions(+), 179 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 26a3d0fe019c52b37ff51d5abcf0d7fdabfa160a From git at git.haskell.org Tue Dec 2 13:27:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 13:27:46 +0000 (UTC) Subject: [commit: ghc] master: Fix another bug in deriving( Data ) for data families; Trac #4896 (863854a) Message-ID: <20141202132746.A9B243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/863854a3a490afd9e3ecf0da6294a3b078f4a6a1/ghc >--------------------------------------------------------------- commit 863854a3a490afd9e3ecf0da6294a3b078f4a6a1 Author: Simon Peyton Jones Date: Tue Dec 2 13:20:33 2014 +0000 Fix another bug in deriving( Data ) for data families; Trac #4896 If we have data family D a data instance D (a,b,c) = ... deriving( Data ) then we want to generate instance ... => Data (D (a,b,c)) where ... dataCast1 x = gcast1 x The "1" here comes from the kind of D. But the kind of the *representation* TyCon is data Drep a b c = .... ie Drep :: * -> * -> * -> * So we must look for the *family* TyCon in this (rather horrible) dataCast1 / dataCast2 binding. >--------------------------------------------------------------- 863854a3a490afd9e3ecf0da6294a3b078f4a6a1 compiler/typecheck/TcGenDeriv.lhs | 34 +++++++++++++++++------- testsuite/tests/deriving/should_compile/T4896.hs | 19 +++++++++++++ testsuite/tests/deriving/should_compile/all.T | 2 ++ 3 files changed, 46 insertions(+), 9 deletions(-) diff --git a/compiler/typecheck/TcGenDeriv.lhs b/compiler/typecheck/TcGenDeriv.lhs index 9b5ef8b..0d4374b 100644 --- a/compiler/typecheck/TcGenDeriv.lhs +++ b/compiler/typecheck/TcGenDeriv.lhs @@ -1323,18 +1323,19 @@ we generate \begin{code} gen_Data_binds :: DynFlags - -> SrcSpan - -> TyCon + -> SrcSpan + -> TyCon -- For data families, this is the + -- *representation* TyCon -> (LHsBinds RdrName, -- The method bindings BagDerivStuff) -- Auxiliary bindings -gen_Data_binds dflags loc tycon +gen_Data_binds dflags loc rep_tc = (listToBag [gfoldl_bind, gunfold_bind, toCon_bind, dataTypeOf_bind] `unionBags` gcast_binds, -- Auxiliary definitions: the data type and constructors listToBag ( DerivHsBind (genDataTyCon) : map (DerivHsBind . genDataDataCon) data_cons)) where - data_cons = tyConDataCons tycon + data_cons = tyConDataCons rep_tc n_cons = length data_cons one_constr = n_cons == 1 @@ -1343,11 +1344,11 @@ gen_Data_binds dflags loc tycon = (mkHsVarBind loc rdr_name rhs, L loc (TypeSig [L loc rdr_name] sig_ty PlaceHolder)) where - rdr_name = mk_data_type_name tycon + rdr_name = mk_data_type_name rep_tc sig_ty = nlHsTyVar dataType_RDR - constrs = [nlHsVar (mk_constr_name con) | con <- tyConDataCons tycon] + constrs = [nlHsVar (mk_constr_name con) | con <- tyConDataCons rep_tc] rhs = nlHsVar mkDataType_RDR - `nlHsApp` nlHsLit (mkHsString (showSDocOneLine dflags (ppr tycon))) + `nlHsApp` nlHsLit (mkHsString (showSDocOneLine dflags (ppr rep_tc))) `nlHsApp` nlList constrs genDataDataCon :: DataCon -> (LHsBind RdrName, LSig RdrName) @@ -1418,10 +1419,25 @@ gen_Data_binds dflags loc tycon loc dataTypeOf_RDR [nlWildPat] - (nlHsVar (mk_data_type_name tycon)) + (nlHsVar (mk_data_type_name rep_tc)) ------------ gcast1/2 - tycon_kind = tyConKind tycon + -- Make the binding dataCast1 x = gcast1 x -- if T :: * -> * + -- or dataCast2 x = gcast2 s -- if T :: * -> * -> * + -- (or nothing if T has neither of these two types) + + -- But care is needed for data families: + -- If we have data family D a + -- data instance D (a,b,c) = A | B deriving( Data ) + -- and we want instance ... => Data (D [(a,b,c)]) where ... + -- then we need dataCast1 x = gcast1 x + -- because D :: * -> * + -- even though rep_tc has kind * -> * -> * -> * + -- Hence looking for the kind of fam_tc not rep_tc + -- See Trac #4896 + tycon_kind = case tyConFamInst_maybe rep_tc of + Just (fam_tc, _) -> tyConKind fam_tc + Nothing -> tyConKind rep_tc gcast_binds | tycon_kind `tcEqKind` kind1 = mk_gcast dataCast1_RDR gcast1_RDR | tycon_kind `tcEqKind` kind2 = mk_gcast dataCast2_RDR gcast2_RDR | otherwise = emptyBag diff --git a/testsuite/tests/deriving/should_compile/T4896.hs b/testsuite/tests/deriving/should_compile/T4896.hs new file mode 100644 index 0000000..18fcc7c --- /dev/null +++ b/testsuite/tests/deriving/should_compile/T4896.hs @@ -0,0 +1,19 @@ +{-# LANGUAGE FlexibleInstances, FlexibleContexts, UndecidableInstances, TypeFamilies, DeriveDataTypeable, StandaloneDeriving #-} + +module T4896 where + +import Data.Data +import Data.Typeable + +--instance Typeable1 Bar where +-- typeOf1 _ = mkTyConApp (mkTyCon "Main.Bar") [] +deriving instance Typeable Bar + +class Foo a where + data Bar a + +data D a b = D Int a deriving (Typeable, Data) + +instance Foo (D a b) where + data Bar (D a b) = B { l :: a } deriving (Eq, Ord, Read, Show, Data) + diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index 3bf871d..2234dd5 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -51,3 +51,5 @@ test('T8963', normal, compile, ['']) test('T7269', normal, compile, ['']) test('T9069', normal, compile, ['']) test('T9359', normal, compile, ['']) +test('T4896', normal, compile, ['']) + From git at git.haskell.org Tue Dec 2 13:27:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 13:27:49 +0000 (UTC) Subject: [commit: ghc] master: Minor refactoring of Edward's recent orphans patch (Trac #2182) (2a67fb3) Message-ID: <20141202132749.545BF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2a67fb3990f23391fecaec335f0d010434d2738e/ghc >--------------------------------------------------------------- commit 2a67fb3990f23391fecaec335f0d010434d2738e Author: Simon Peyton Jones Date: Tue Dec 2 12:11:52 2014 +0000 Minor refactoring of Edward's recent orphans patch (Trac #2182) This patch is all small stuff - Move VisibleOrphanModules from Module to InstEnv (with the other orphan stuff) - Move Notes about orphans from IfaceSyn to InstEnv (ditto) - Make use of the record field names in InstEnvs >--------------------------------------------------------------- 2a67fb3990f23391fecaec335f0d010434d2738e compiler/basicTypes/Module.lhs | 7 +- compiler/iface/IfaceSyn.lhs | 75 +------ compiler/iface/MkIface.lhs | 6 +- compiler/typecheck/Inst.lhs | 15 +- compiler/typecheck/TcEnv.lhs | 21 +- compiler/typecheck/TcRnDriver.lhs | 3 +- compiler/typecheck/TcRnTypes.lhs | 1 + compiler/types/InstEnv.hs | 413 ++++++++++++++++++++++++-------------- 8 files changed, 289 insertions(+), 252 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2a67fb3990f23391fecaec335f0d010434d2738e From git at git.haskell.org Tue Dec 2 15:05:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 15:05:09 +0000 (UTC) Subject: [commit: ghc] branch 'wip/static-pointers' created Message-ID: <20141202150509.D83733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/static-pointers Referencing: 79c87c039c47be0baf7a6dd33ecf5434daa1501c From git at git.haskell.org Tue Dec 2 15:05:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 15:05:12 +0000 (UTC) Subject: [commit: ghc] wip/static-pointers: Implement -XStaticValues. (79c87c0) Message-ID: <20141202150512.C937C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/static-pointers Link : http://ghc.haskell.org/trac/ghc/changeset/79c87c039c47be0baf7a6dd33ecf5434daa1501c/ghc >--------------------------------------------------------------- commit 79c87c039c47be0baf7a6dd33ecf5434daa1501c Author: Facundo Dom?nguez Date: Wed Jan 29 12:43:03 2014 -0200 Implement -XStaticValues. Contains contributions from Alexander Vershilov and Mathieu Boespflug. As proposed in [1], this extension introduces a new syntactic form `static e`, where `e :: a` can be any closed expression. The static form produces a value of type `StaticPtr a`, which works as a reference that programs can "dereference" to get the value of `e` back. References are like `Ptr`s, except that they are stable across invocations of a program. In essence the extension collects the arguments of the static form into a global static pointer table. The expressions can be looked up by a fingerprint computed from the package, the module and a fresh name given to the expression. For more details we refer to the users guide section contained in the patch. The extension is a contribution to the Cloud Haskell ecosystem (distributed-process and related), and thus has the potential to foster Haskell as a programming language for distributed systems. The immediate improvement brought by the extension is the elimination of remote tables from Cloud Haskell applications. Such applications contain table fragments spread throughout multiple modules and packages. Eliminating these fragments saves the programmer the burden required to construct and assemble the global remote table, a verbose and error-prone process, even with the help of Template Haskell, that moreover pollutes the export lists of all modules. [1] Jeff Epstein, Andrew P. Black, and Simon Peyton-Jones. Towards Haskell in the cloud. SIGPLAN Not., 46(12):118?129, September 2011. ISSN 0362-1340. >--------------------------------------------------------------- 79c87c039c47be0baf7a6dd33ecf5434daa1501c compiler/deSugar/Coverage.lhs | 3 + compiler/deSugar/Desugar.lhs | 31 ++++-- compiler/deSugar/DsExpr.lhs | 78 +++++++++++++ compiler/deSugar/DsMeta.hs | 9 +- compiler/deSugar/DsMonad.lhs | 22 +++- compiler/deSugar/SPT.lhs | 88 +++++++++++++++ compiler/ghc.cabal.in | 1 + compiler/hsSyn/Convert.lhs | 1 + compiler/hsSyn/HsExpr.lhs | 7 ++ compiler/main/DynFlags.hs | 4 +- compiler/parser/Lexer.x | 7 ++ compiler/parser/Parser.y | 2 + compiler/prelude/PrelNames.lhs | 25 +++++ compiler/prelude/TysWiredIn.lhs | 86 +++++++++++++- compiler/rename/RnExpr.lhs | 33 ++++++ compiler/typecheck/TcBinds.lhs | 2 +- compiler/typecheck/TcExpr.lhs | 30 +++++ compiler/typecheck/TcHsSyn.lhs | 4 + compiler/typecheck/TcHsType.lhs | 2 +- compiler/typecheck/TcRnDriver.lhs | 65 ++++++++++- compiler/typecheck/TcRnMonad.lhs | 6 +- compiler/typecheck/TcRnTypes.lhs | 24 +++- compiler/typecheck/TcType.lhs | 2 + compiler/typecheck/TcValidity.lhs | 1 + docs/users_guide/glasgow_exts.xml | 124 +++++++++++++++++++++ includes/HsFFI.h | 2 + includes/Rts.h | 1 + includes/rts/SPT.h | 32 ++++++ libraries/base/GHC/StaticPtr.hs | 107 ++++++++++++++++++ libraries/base/base.cabal | 1 + libraries/template-haskell/Language/Haskell/TH.hs | 2 +- .../template-haskell/Language/Haskell/TH/Lib.hs | 3 + .../template-haskell/Language/Haskell/TH/Ppr.hs | 2 + .../template-haskell/Language/Haskell/TH/Syntax.hs | 1 + rts/Hash.c | 41 +++++++ rts/Hash.h | 10 ++ rts/Linker.c | 2 + rts/SPT.c | 20 ++++ .../tests/codeGen/should_run/CgStaticPointers.hs | 31 ++++++ .../codeGen/should_run/CgStaticPointers.stdout | 2 + testsuite/tests/codeGen/should_run/all.T | 3 + .../tests/deSugar/should_run/DsStaticPointers.hs | 20 ++++ .../deSugar/should_run/DsStaticPointers.stdout | 2 + testsuite/tests/deSugar/should_run/all.T | 2 + testsuite/tests/driver/T4437.hs | 3 +- .../parser/should_compile/RdrNoStaticPointers01.hs | 7 ++ testsuite/tests/parser/should_compile/all.T | 1 + .../rename/should_fail/RnStaticPointersFail01.hs | 5 + .../should_fail/RnStaticPointersFail01.stderr | 6 + .../rename/should_fail/RnStaticPointersFail02.hs | 7 ++ .../should_fail/RnStaticPointersFail02.stderr | 8 ++ .../rename/should_fail/RnStaticPointersFail03.hs | 5 + .../should_fail/RnStaticPointersFail03.stderr | 6 + testsuite/tests/rename/should_fail/all.T | 6 + testsuite/tests/rts/GcStaticPointers.hs | 33 ++++++ testsuite/tests/rts/GcStaticPointers.stdout | 3 + testsuite/tests/rts/all.T | 4 + testsuite/tests/th/TH_StaticPointers.hs | 19 ++++ testsuite/tests/th/TH_StaticPointers.stdout | 1 + testsuite/tests/th/all.T | 3 + .../typecheck/should_compile/TcStaticPointers01.hs | 14 +++ .../typecheck/should_compile/TcStaticPointers02.hs | 19 ++++ testsuite/tests/typecheck/should_compile/all.T | 2 + .../should_fail/TcStaticPointersFail01.hs | 11 ++ .../should_fail/TcStaticPointersFail01.stderr | 6 + .../should_fail/TcStaticPointersFail02.hs | 12 ++ .../should_fail/TcStaticPointersFail02.stderr | 13 +++ .../should_fail/TcStaticPointersFail03.hs | 9 ++ .../should_fail/TcStaticPointersFail03.stderr | 6 + testsuite/tests/typecheck/should_fail/all.T | 6 + 70 files changed, 1127 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 79c87c039c47be0baf7a6dd33ecf5434daa1501c From git at git.haskell.org Tue Dec 2 15:13:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 15:13:05 +0000 (UTC) Subject: [commit: ghc] master: Unique-ify the names of top-level auxiliary bindings in derived instances (Trac #7947) (c41d214) Message-ID: <20141202151305.0EBA73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c41d214a8dd8e2fe7ae9a3446aeda1a07328b831/ghc >--------------------------------------------------------------- commit c41d214a8dd8e2fe7ae9a3446aeda1a07328b831 Author: Simon Peyton Jones Date: Tue Dec 2 15:13:32 2014 +0000 Unique-ify the names of top-level auxiliary bindings in derived instances (Trac #7947) The problem and its solution are explained in Note [Auxiliary binders] in TcGenDeriv >--------------------------------------------------------------- c41d214a8dd8e2fe7ae9a3446aeda1a07328b831 compiler/typecheck/TcGenDeriv.lhs | 49 +++++++++++++++++++---- testsuite/tests/deriving/should_compile/T7947.hs | 16 ++++++++ testsuite/tests/deriving/should_compile/T7947a.hs | 3 ++ testsuite/tests/deriving/should_compile/T7947b.hs | 3 ++ testsuite/tests/deriving/should_compile/all.T | 1 + 5 files changed, 64 insertions(+), 8 deletions(-) diff --git a/compiler/typecheck/TcGenDeriv.lhs b/compiler/typecheck/TcGenDeriv.lhs index 0d4374b..13d8e83 100644 --- a/compiler/typecheck/TcGenDeriv.lhs +++ b/compiler/typecheck/TcGenDeriv.lhs @@ -65,6 +65,7 @@ import Pair import Bag import Fingerprint import TcEnv (InstInfo) +import StaticFlags( opt_PprStyle_Debug ) import ListSetOps ( assocMaybe ) import Data.List ( partition, intersperse ) @@ -2294,6 +2295,11 @@ f_Pat = nlVarPat f_RDR k_Pat = nlVarPat k_RDR z_Pat = nlVarPat z_RDR +minusInt_RDR, tagToEnum_RDR, error_RDR :: RdrName +minusInt_RDR = getRdrName (primOpId IntSubOp ) +tagToEnum_RDR = getRdrName (primOpId TagToEnumOp) +error_RDR = getRdrName eRROR_ID + con2tag_RDR, tag2con_RDR, maxtag_RDR :: TyCon -> RdrName -- Generates Orig s RdrName, for the binding positions con2tag_RDR tycon = mk_tc_deriv_name tycon mkCon2TagOcc @@ -2304,13 +2310,40 @@ mk_tc_deriv_name :: TyCon -> (OccName -> OccName) -> RdrName mk_tc_deriv_name tycon occ_fun = mkAuxBinderName (tyConName tycon) occ_fun mkAuxBinderName :: Name -> (OccName -> OccName) -> RdrName -mkAuxBinderName parent occ_fun = mkRdrUnqual (occ_fun (nameOccName parent)) --- Was: mkDerivedRdrName name occ_fun, which made an original name --- But: (a) that does not work well for standalone-deriving --- (b) an unqualified name is just fine, provided it can't clash with user code +-- ^ Make a top-level binder name for an auxiliary binding for a parent name +-- See Note [Auxiliary binders] +mkAuxBinderName parent occ_fun + = mkRdrUnqual (occ_fun uniq_parent_occ) + where + uniq_parent_occ = mkOccName (occNameSpace parent_occ) uniq_string -minusInt_RDR, tagToEnum_RDR, error_RDR :: RdrName -minusInt_RDR = getRdrName (primOpId IntSubOp ) -tagToEnum_RDR = getRdrName (primOpId TagToEnumOp) -error_RDR = getRdrName eRROR_ID + uniq_string + | opt_PprStyle_Debug = showSDocSimple (ppr parent_occ <> underscore <> ppr parent_uniq) + | otherwise = show parent_uniq + -- The debug thing is just to generate longer, but perhaps more perspicuous, names + + parent_uniq = nameUnique parent + parent_occ = nameOccName parent \end{code} + +Note [Auxiliary binders] +~~~~~~~~~~~~~~~~~~~~~~~~ +We often want to make a top-level auxiliary binding. E.g. for comparison we haev + + instance Ord T where + compare a b = $con2tag a `compare` $con2tag b + + $con2tag :: T -> Int + $con2tag = ...code.... + +Of course these top-level bindings should all have distinct name, and we are +generating RdrNames here. We can't just use the TyCon or DataCon to distinguish +becuase with standalone deriving two imported TyCons might both be called T! +(See Trac #7947.) + +So we use the *unique* from the parent name (T in this example) as part of the +OccName we generate for the new binding. + +In the past we used mkDerivedRdrName name occ_fun, which made an original name +But: (a) that does not work well for standalone-deriving either + (b) an unqualified name is just fine, provided it can't clash with user code diff --git a/testsuite/tests/deriving/should_compile/T7947.hs b/testsuite/tests/deriving/should_compile/T7947.hs new file mode 100644 index 0000000..d4df435 --- /dev/null +++ b/testsuite/tests/deriving/should_compile/T7947.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE StandaloneDeriving #-} + +module T7947 where + +import Data.Data +import Data.Typeable + +import T7947a +import qualified T7947b as B + +deriving instance Typeable A +deriving instance Typeable B.B + +deriving instance Data A +deriving instance Data B.B diff --git a/testsuite/tests/deriving/should_compile/T7947a.hs b/testsuite/tests/deriving/should_compile/T7947a.hs new file mode 100644 index 0000000..eb5c747 --- /dev/null +++ b/testsuite/tests/deriving/should_compile/T7947a.hs @@ -0,0 +1,3 @@ +module T7947a where + +data A = C1 | C2 | C diff --git a/testsuite/tests/deriving/should_compile/T7947b.hs b/testsuite/tests/deriving/should_compile/T7947b.hs new file mode 100644 index 0000000..f17f1cd --- /dev/null +++ b/testsuite/tests/deriving/should_compile/T7947b.hs @@ -0,0 +1,3 @@ +module T7947b where + +data B = D1 | D2 | C diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index 2234dd5..8d90236 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -52,4 +52,5 @@ test('T7269', normal, compile, ['']) test('T9069', normal, compile, ['']) test('T9359', normal, compile, ['']) test('T4896', normal, compile, ['']) +test('T7947', extra_clean(['T7947a.o', 'T7947a.hi', 'T7947b.o', 'T7947b.hi']), multimod_compile, ['T7947', '-v0']) From git at git.haskell.org Tue Dec 2 16:51:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 16:51:44 +0000 (UTC) Subject: [commit: ghc] master: Make Natural's (.|.) really an OR operation (#9818) (6b063ef) Message-ID: <20141202165144.0E4033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6b063ef2a1f68290b51778a38e9b89b6fec5e170/ghc >--------------------------------------------------------------- commit 6b063ef2a1f68290b51778a38e9b89b6fec5e170 Author: Herbert Valerio Riedel Date: Tue Dec 2 17:51:36 2014 +0100 Make Natural's (.|.) really an OR operation (#9818) Currently it's an AND when at least one of the operands is big. Reviewed By: hvr Differential Revision: https://phabricator.haskell.org/D549 >--------------------------------------------------------------- 6b063ef2a1f68290b51778a38e9b89b6fec5e170 libraries/base/GHC/Natural.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/Natural.hs b/libraries/base/GHC/Natural.hs index 3519bcf..0211061 100644 --- a/libraries/base/GHC/Natural.hs +++ b/libraries/base/GHC/Natural.hs @@ -296,9 +296,9 @@ instance Bits Natural where NatJ# n .&. NatJ# m = bigNatToNatural (andBigNat n m) NatS# n .|. NatS# m = wordToNatural (W# n .|. W# m) - NatS# n .|. NatJ# m = NatJ# (andBigNat (wordToBigNat n) m) - NatJ# n .|. NatS# m = NatJ# (andBigNat n (wordToBigNat m)) - NatJ# n .|. NatJ# m = NatJ# (andBigNat n m) + NatS# n .|. NatJ# m = NatJ# (orBigNat (wordToBigNat n) m) + NatJ# n .|. NatS# m = NatJ# (orBigNat n (wordToBigNat m)) + NatJ# n .|. NatJ# m = NatJ# (orBigNat n m) NatS# n `xor` NatS# m = wordToNatural (W# n `xor` W# m) NatS# n `xor` NatJ# m = NatJ# (xorBigNat (wordToBigNat n) m) From git at git.haskell.org Tue Dec 2 16:54:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 16:54:13 +0000 (UTC) Subject: [commit: ghc] master: Make `read . show = id` for Data.Fixed (fix #9240) (7c38e98) Message-ID: <20141202165413.D4EBB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7c38e985aa211ca44039c6d1db9fa13690749c59/ghc >--------------------------------------------------------------- commit 7c38e985aa211ca44039c6d1db9fa13690749c59 Author: Brian McKenna Date: Tue Dec 2 17:53:38 2014 +0100 Make `read . show = id` for Data.Fixed (fix #9240) The QuickCheck property now succeeds: prop :: Fixed B7 -> Bool prop a = read (show a) == a This changes the Show instance for Fixed to round up, rather than down when calculating a digit. This needs to happen because Read also rounds down: data B7 instance HasResolution B7 where resolution _ = 128 1 / 128 = 0.0078125 read "0.007" = (0.000 :: Fixed B7) Here is an example of the change to Show: showFixed False (0.009 :: Fixed B7) -- Broken: "0.007" -- Fixed: "0.008" And now Read can continue to round down: read "0.008" = (0.0078125 :: Fixed B7) Reviewed By: hvr, ekmett Differential Revision: https://phabricator.haskell.org/D547 >--------------------------------------------------------------- 7c38e985aa211ca44039c6d1db9fa13690749c59 libraries/base/Data/Fixed.hs | 4 +++- libraries/base/changelog.md | 2 ++ libraries/base/tests/data-fixed-show-read.hs | 7 +++++++ libraries/base/tests/data-fixed-show-read.stdout | 2 ++ 4 files changed, 14 insertions(+), 1 deletion(-) diff --git a/libraries/base/Data/Fixed.hs b/libraries/base/Data/Fixed.hs index 068eec5..f12a0e4 100644 --- a/libraries/base/Data/Fixed.hs +++ b/libraries/base/Data/Fixed.hs @@ -143,7 +143,9 @@ showFixed chopTrailingZeros fa@(MkFixed a) = (show i) ++ (withDot (showIntegerZe -- enough digits to be unambiguous digits = ceiling (logBase 10 (fromInteger res) :: Double) maxnum = 10 ^ digits - fracNum = div (d * maxnum) res + -- read floors, so show must ceil for `read . show = id` to hold. See #9240 + fracNum = divCeil (d * maxnum) res + divCeil x y = (x + y - 1) `div` y instance (HasResolution a) => Show (Fixed a) where show = showFixed False diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 07c91a3..ef3e9ae 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -128,6 +128,8 @@ together with a new exception `AllocationLimitExceeded`. + * Make `read . show = id` for `Data.Fixed` (#9240) + ## 4.7.0.2 *Dec 2014* * Bundled with GHC 7.8.4 diff --git a/libraries/base/tests/data-fixed-show-read.hs b/libraries/base/tests/data-fixed-show-read.hs index 349f639..7e947f4 100644 --- a/libraries/base/tests/data-fixed-show-read.hs +++ b/libraries/base/tests/data-fixed-show-read.hs @@ -3,6 +3,11 @@ module Main (main) where import Data.Fixed +data B7 + +instance HasResolution B7 where + resolution _ = 128 + main :: IO () main = do doit 38.001 doit 38.009 @@ -14,6 +19,8 @@ main = do doit 38.001 doit (-38.01) doit (-38.09) print (read "-38" :: Centi) + print (read "0.008" :: Fixed B7) + print (read "-0.008" :: Fixed B7) doit :: Centi -> IO () doit c = do let s = show c diff --git a/libraries/base/tests/data-fixed-show-read.stdout b/libraries/base/tests/data-fixed-show-read.stdout index 0e5d7ca..4abb2d9 100644 --- a/libraries/base/tests/data-fixed-show-read.stdout +++ b/libraries/base/tests/data-fixed-show-read.stdout @@ -16,3 +16,5 @@ -38.09 -38.09 -38.00 +0.008 +-0.008 From git at git.haskell.org Tue Dec 2 20:43:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:14 +0000 (UTC) Subject: [commit: ghc] branch 'wip/rae-new-coercible' created Message-ID: <20141202204314.0C4163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/rae-new-coercible Referencing: fc853b9efaab02a61087b7b97caca8f1ada5bed7 From git at git.haskell.org Tue Dec 2 20:43:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:17 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Checkpoint. Starting in flattener. (675794f) Message-ID: <20141202204317.32CFC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/675794fdc8b537caf715d7e49e257d781668e9a2/ghc >--------------------------------------------------------------- commit 675794fdc8b537caf715d7e49e257d781668e9a2 Author: Richard Eisenberg Date: Fri Nov 14 15:06:24 2014 -0500 Checkpoint. Starting in flattener. >--------------------------------------------------------------- 675794fdc8b537caf715d7e49e257d781668e9a2 compiler/typecheck/TcCanonical.lhs | 64 +++++++++++++++++++++----------------- compiler/typecheck/TcHsSyn.lhs | 1 + compiler/typecheck/TcRnTypes.lhs | 9 ++++-- compiler/typecheck/TcSMonad.lhs | 6 ++-- compiler/types/Type.hs | 37 ++++++++++++++++++---- rae.txt | 3 ++ 6 files changed, 81 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 675794fdc8b537caf715d7e49e257d781668e9a2 From git at git.haskell.org Tue Dec 2 20:43:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:19 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Checkpoint in adding IsCoercion (fe5ccb1) Message-ID: <20141202204319.D17E53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/fe5ccb11c493664c046b032f5a9b3f066bdb80cf/ghc >--------------------------------------------------------------- commit fe5ccb11c493664c046b032f5a9b3f066bdb80cf Author: Richard Eisenberg Date: Tue Nov 18 15:33:49 2014 -0500 Checkpoint in adding IsCoercion >--------------------------------------------------------------- fe5ccb11c493664c046b032f5a9b3f066bdb80cf compiler/types/Coercion.hs | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/compiler/types/Coercion.hs b/compiler/types/Coercion.hs index a16a146..b427255 100644 --- a/compiler/types/Coercion.hs +++ b/compiler/types/Coercion.hs @@ -1922,4 +1922,19 @@ Note [Kind coercions] Kind coercions are only of the form: Refl kind. They are only used to instantiate kind polymorphic type constructors in TyConAppCo. Remember that kind instantiation only happens with TyConApp, not AppTy. + +%************************************************************************ +%* * + Generalised coercions +%* * +%************************************************************************ -} + +-- | Classifies a coercion type. The two canonical inhabitants are +-- 'Coercion' and 'TcCoercion'. This is useful in order to parameterise +-- several functions. +class IsCoercion co where + gMkReflCo :: Type -> co + gMkSymCo :: co -> co + gMkTransCo :: co -> co -> co + From git at git.haskell.org Tue Dec 2 20:43:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:22 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Finish rewriting canonicalizer w.r.t. representational equality. (ebc123f) Message-ID: <20141202204322.8C4C63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/ebc123f20ff10272e15f9b2e7f3d1d47ccc6fcf1/ghc >--------------------------------------------------------------- commit ebc123f20ff10272e15f9b2e7f3d1d47ccc6fcf1 Author: Richard Eisenberg Date: Wed Nov 19 13:16:53 2014 -0500 Finish rewriting canonicalizer w.r.t. representational equality. >--------------------------------------------------------------- ebc123f20ff10272e15f9b2e7f3d1d47ccc6fcf1 compiler/coreSyn/CoreArity.lhs | 2 +- compiler/deSugar/DsCCall.lhs | 4 +- compiler/stranal/WwLib.hs | 2 +- compiler/typecheck/FamInst.lhs | 19 +--- compiler/typecheck/TcCanonical.lhs | 224 +++++++++++++++++++++++++++++-------- compiler/typecheck/TcEvidence.lhs | 26 ++++- compiler/typecheck/TcInteract.lhs | 18 --- compiler/typecheck/TcRnTypes.lhs | 7 ++ compiler/typecheck/TcSMonad.lhs | 18 +-- compiler/typecheck/TcType.lhs | 15 ++- compiler/types/Coercion.hs | 63 ++++++++--- compiler/utils/Util.lhs | 12 +- rae.txt | 3 - 13 files changed, 300 insertions(+), 113 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ebc123f20ff10272e15f9b2e7f3d1d47ccc6fcf1 From git at git.haskell.org Tue Dec 2 20:43:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:25 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Remove old Coercible solver (2631fd8) Message-ID: <20141202204325.33CA93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/2631fd8c7f0e8b27648da274174244571e215c96/ghc >--------------------------------------------------------------- commit 2631fd8c7f0e8b27648da274174244571e215c96 Author: Richard Eisenberg Date: Wed Nov 19 13:34:14 2014 -0500 Remove old Coercible solver >--------------------------------------------------------------- 2631fd8c7f0e8b27648da274174244571e215c96 compiler/typecheck/TcInteract.lhs | 172 -------------------------------------- 1 file changed, 172 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2631fd8c7f0e8b27648da274174244571e215c96 From git at git.haskell.org Tue Dec 2 20:43:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:27 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Checkpoint (1aa5d57) Message-ID: <20141202204327.C8A933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/1aa5d575b3ec7831c7d61c9128bdd63b927c87cf/ghc >--------------------------------------------------------------- commit 1aa5d575b3ec7831c7d61c9128bdd63b927c87cf Author: Richard Eisenberg Date: Thu Nov 20 08:46:34 2014 -0500 Checkpoint >--------------------------------------------------------------- 1aa5d575b3ec7831c7d61c9128bdd63b927c87cf compiler/basicTypes/DataCon.lhs | 6 +++--- compiler/typecheck/TcCanonical.lhs | 4 ++-- compiler/typecheck/TcFlatten.lhs | 16 +++++++++------- 3 files changed, 14 insertions(+), 12 deletions(-) diff --git a/compiler/basicTypes/DataCon.lhs b/compiler/basicTypes/DataCon.lhs index e57439d..3305a90 100644 --- a/compiler/basicTypes/DataCon.lhs +++ b/compiler/basicTypes/DataCon.lhs @@ -983,9 +983,9 @@ dataConCannotMatch tys con -- TODO: could gather equalities from superclasses too predEqs pred = case classifyPredType pred of - EqPred ty1 ty2 -> [(ty1, ty2)] - TuplePred ts -> concatMap predEqs ts - _ -> [] + EqPred NomEq ty1 ty2 -> [(ty1, ty2)] + TuplePred ts -> concatMap predEqs ts + _ -> [] \end{code} %************************************************************************ diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index df89caf..cb4e5c9 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -824,12 +824,12 @@ canCFunEqCan ev fn tys fsk , cc_tyargs = tys', cc_fsk = fsk }) } } } --------------------- -canEqTyVar :: CtEvidence -> SwapFlag +canEqTyVar :: CtEvidence -> EqRel -> SwapFlag -> TcTyVar -> TcType -> TcType -> TcS (StopOrContinue Ct) -- A TyVar on LHS, but so far un-zonked -canEqTyVar ev swapped tv1 ty2 ps_ty2 -- ev :: tv ~ s2 +canEqTyVar ev eq_rel swapped tv1 ty2 ps_ty2 -- ev :: tv ~ s2 = do { traceTcS "canEqTyVar" (ppr tv1 $$ ppr ty2 $$ ppr swapped) ; mb_yes <- flattenTyVarOuter ev tv1 ; case mb_yes of diff --git a/compiler/typecheck/TcFlatten.lhs b/compiler/typecheck/TcFlatten.lhs index ac68ec9..ec6050f 100644 --- a/compiler/typecheck/TcFlatten.lhs +++ b/compiler/typecheck/TcFlatten.lhs @@ -838,9 +838,8 @@ flattenTyVar fmode tv ; return (ty2, co2 `mkTcTransCo` co1) } } -flattenTyVarOuter, flattenTyVarFinal - :: CtEvidence -> TcTyVar - -> TcS (Either TyVar (TcType, TcCoercion, Bool)) +flattenTyVarOuter :: CtEvidence -> EqRel -> TcTyVar + -> TcS (Either TyVar (TcType, TcCoercion, Bool)) -- Look up the tyvar in -- a) the internal MetaTyVar box -- b) the tyvar binds @@ -849,14 +848,16 @@ flattenTyVarOuter, flattenTyVarFinal -- (Right (ty, co, is_flat)) if found, with co :: ty ~ tv; -- is_flat says if the result is guaranteed flattened -flattenTyVarOuter ctxt_ev tv +flattenTyVarOuter ctxt_ev eq_rel tv | not (isTcTyVar tv) -- Happens when flatten under a (forall a. ty) - = flattenTyVarFinal ctxt_ev tv -- So ty contains refernces to the non-TcTyVar a + = Left <$> flattenTyVarFinal ctxt_ev tv + -- So ty contains refernces to the non-TcTyVar a + | otherwise = do { mb_ty <- isFilledMetaTyVar_maybe tv ; case mb_ty of { Just ty -> do { traceTcS "Following filled tyvar" (ppr tv <+> equals <+> ppr ty) - ; return (Right (ty, mkTcNomReflCo ty, False)) } ; + ; return (Right (ty, mkTcReflCo (eqRelRole eq_rel) ty, False)) } ; Nothing -> -- Try in the inert equalities @@ -876,12 +877,13 @@ flattenTyVarOuter ctxt_ev tv _other -> flattenTyVarFinal ctxt_ev tv } } } +flattenTyVarFinal :: CtEvidence -> TcTyVar -> TcS TyVar flattenTyVarFinal ctxt_ev tv = -- Done, but make sure the kind is zonked do { let kind = tyVarKind tv kind_fmode = FE { fe_ev = ctxt_ev, fe_mode = FM_SubstOnly } ; (new_knd, _kind_co) <- flatten kind_fmode kind - ; return (Left (setVarType tv new_knd)) } + ; return (setVarType tv new_knd) } \end{code} Note [Applying the inert substitution] From git at git.haskell.org Tue Dec 2 20:43:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:30 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Eager reflexivity check (729006e) Message-ID: <20141202204330.701933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/729006e8711b8de66c1103be30554a4d0d832275/ghc >--------------------------------------------------------------- commit 729006e8711b8de66c1103be30554a4d0d832275 Author: Richard Eisenberg Date: Wed Nov 19 13:29:44 2014 -0500 Eager reflexivity check >--------------------------------------------------------------- 729006e8711b8de66c1103be30554a4d0d832275 compiler/typecheck/TcCanonical.lhs | 28 ++++++++++++++++++++++++++-- 1 file changed, 26 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index de404b5..df89caf 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -559,6 +559,24 @@ can_eq_flat_app ev eq_rel swapped s1 t1 ps_ty1 ty2 ps_ty2 ; xCtEvidence ev (XEvTerm [mkTcEqPred s1 s2, mkTcEqPred t1 t2] xevcomp xevdecomp) ; stopWith ev "Decomposed AppTy" } +\end{code} + +Note [Eager reflexivity check] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Suppose we have + +newtype X = MkX (Int -> X) + +and + +[W] X ~R X + +Naively, we would start unwrapping X and end up in a loop. Instead, +we do this eager reflexivity check. This is necessary only for representational +equality because the flattener technology deals with the similar case +(recursive type families) for nominal equality. + +\begin{code} ------------------------ -- | We're able to unwrap a newtype. Update the bits accordingly. @@ -571,7 +589,7 @@ can_eq_newtype_nc :: GlobalRdrEnv -> TcType -- ^ ty2 -> TcType -- ^ ty2, with type synonyms -> TcS (StopOrContinue Ct) -can_eq_newtype_nc rdr_env ev swapped tc co ty1' ty2 ps_ty2 +can_eq_newtype_nc rdr_env ev swapped tc co ty1 ty1' ty2 ps_ty2 = do { traceTcS "can_eq_newtype_nc" $ vcat [ ppr ev, ppr swapped, ppr co, ppr ty1', ppr ty2 ] @@ -582,13 +600,19 @@ can_eq_newtype_nc rdr_env ev swapped tc co ty1' ty2 ps_ty2 then do { emitInsoluble (mkNonCanonical ev) ; stopWith ev "unwrapping newtypes blew stack" } else do + { if ty1 `eqType` ty2 -- See Note [Eager reflexivity check] + then do { when (isWanted ev) $ + setEvBind (ctev_evar ev) (EvCoercion $ + mkTcReflCo Representational ty1) + ; stopWith ev "Eager reflexivity check before newtype reduction" } + else do { markDataConsAsUsed rdr_env tc ; mb_ct <- rewriteEqEvidence ev swapped ty1' ps_ty2 (mkTcSymCo co) (mkTcReflCo Representational ps_ty2) ; case mb_ct of Stop ev s -> return (Stop ev s) - ContinueWith new_ev -> can_eq_nc new_ev ReprEq ty1' ty1' ty2 ps_ty2 }} + ContinueWith new_ev -> can_eq_nc new_ev ReprEq ty1' ty1' ty2 ps_ty2 }}} dataConsInScope :: GlobalRdrEnv -> TyCon -> Bool dataConsInScope rdr_env tc From git at git.haskell.org Tue Dec 2 20:43:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:33 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Abortive attempt at parameterising the flattener over EqRel. (0d55799) Message-ID: <20141202204333.0D9A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/0d55799a5c0d9783cd7e8e460aa246fb233459fd/ghc >--------------------------------------------------------------- commit 0d55799a5c0d9783cd7e8e460aa246fb233459fd Author: Richard Eisenberg Date: Mon Nov 17 16:28:37 2014 -0500 Abortive attempt at parameterising the flattener over EqRel. Aborted because flattening is not necessary for newtypes. The key bit about flattening for type families is that type families can have non-trivial patterns, where flattening a deeply-nested type can get the outer type family to reduce. This is *not true* with newtypes, where the patterns are always trivial. So, don't bother flattening to squeeze out newtypes. Just use topNormalizeNewType_maybe. >--------------------------------------------------------------- 0d55799a5c0d9783cd7e8e460aa246fb233459fd compiler/typecheck/TcFlatten.lhs | 56 ++++++++++++++++++++++++++++++++++++---- compiler/typecheck/TcRnTypes.lhs | 29 ++++++++++++++++++++- 2 files changed, 79 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcFlatten.lhs b/compiler/typecheck/TcFlatten.lhs index ec6050f..14fa051 100644 --- a/compiler/typecheck/TcFlatten.lhs +++ b/compiler/typecheck/TcFlatten.lhs @@ -564,10 +564,19 @@ transitive expansion contains any type function applications. If so, it expands the synonym and proceeds; if not, it simply returns the unexpanded synonym. +Note [Flattener EqRels] +~~~~~~~~~~~~~~~~~~~~~~~ +When flattening, we need to know which equality relation -- nominal +or representation -- we should be respecting. If respecting nominal +equality, we squeeze out only type families. If respecting representational +equality, we squeeze out newtypes whose constructors are in scope, too. + \begin{code} data FlattenEnv - = FE { fe_mode :: FlattenMode - , fe_ev :: CtEvidence } + = FE { fe_mode :: FlattenMode + , fe_loc :: CtLoc + , fe_nature :: CtNature + , fe_eq_rel :: EqRel } -- See Note [Flattener EqRels] data FlattenMode -- Postcondition for all three: inert wrt the type substitution = FM_FlattenAll -- Postcondition: function-free @@ -580,6 +589,15 @@ data FlattenMode -- Postcondition for all three: inert wrt the type substitutio -- (but under type constructors is ok e.g. [F a]) | FM_SubstOnly -- See Note [Flattening under a forall] + +mkFlattenEnv :: CtEvidence -> FlattenMode -> FlattenEnv +mkFlattenEnv ctev fm = FE { fe_mode = fm + , fe_loc = ctEvLoc ctev + , fe_nature = ctEvNature ctev + , fe_eq_rel = ctEvEqRel ctev } + +feRole :: FlattenEnv -> Role +feRole = eqRelRole . fe_eq_rel \end{code} Note [Lazy flattening] @@ -608,8 +626,19 @@ Bottom line: FM_Avoid is unused for now (Nov 14). Note: T5321Fun got faster when I disabled FM_Avoid T5837 did too, but it's pathalogical anyway +Note [Phantoms in the flattener] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Suppose we're flattening (w.r.t. representational equality; see Note +[Flattener EqRels]) `N Int (F Bool)`, where + + newtype N a b = MkN a + +The second parameter to `N` has a phantom role. As we flatten the type +above to + \begin{code} --- Flatten a bunch of types all at once. +-- Flatten a bunch of types all at once. Roles on the coercions returned +-- always match the EqRel in the FlattenEnv. flattenMany :: FlattenEnv -> [Type] -> TcS ([Xi], [TcCoercion]) -- Coercions :: Xi ~ Type -- Returns True iff (no flattening happened) @@ -630,14 +659,31 @@ flatten :: FlattenEnv -> TcType -> TcS (Xi, TcCoercion) -- constraints. See Note [Flattening] for more detail. -- -- Postcondition: Coercion :: Xi ~ TcType +-- The role on the result coercion matches the EqRel in the FlattenEnv -flatten _ xi@(LitTy {}) = return (xi, mkTcNomReflCo xi) +flatten fmode xi@(LitTy {}) = return (xi, mkTcReflCo (feRole fmode) xi) flatten fmode (TyVarTy tv) = flattenTyVar fmode tv -flatten fmode (AppTy ty1 ty2) +flatten fmode@(FE { fe_eq_rel = eq_rel }) (AppTy ty1 ty2) = do { (xi1,co1) <- flatten fmode ty1 + ; case splitTyConApp_maybe xi1 of + Just _ | ReprEq <- eq_rel + -> do { -- we may have just exposed a newtype that could reduce + -- with another argument. Recur. + (xi, co) <- flatten fmode (mkAppTy xi1 ty2) + -- co :: xi ~ xi1 ty2 + -- co1 :: xi1 ~ ty1 + -- co1 :: xi1 ty2 ~ ty1 ty2 + -- co ; co1 :: xi ~ ty1 ty2 + ; return (xi, co `mkTcTransCo` + mkTcAppCo co1 (mkTcNomReflCo ty2)) } + + ; let eq_rel2 = case nextRole co1 of + Nominal -> NomEq + Representational -> ReprEq + Phantom -> NomEq -- See Note [Phantoms in the flattener] ; (xi2,co2) <- flatten fmode ty2 ; traceTcS "flatten/appty" (ppr ty1 $$ ppr ty2 $$ ppr xi1 $$ ppr co1 $$ ppr xi2 $$ ppr co2) ; return (mkAppTy xi1 xi2, mkTcAppCo co1 co2) } diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index fdeb8a1..1c81481 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -52,7 +52,8 @@ module TcRnTypes( isGivenCt, isHoleCt, isTypedHoleCt, isPartialTypeSigCt, ctEvidence, ctLoc, ctPred, mkNonCanonical, mkNonCanonicalCt, - ctEvPred, ctEvLoc, ctEvTerm, ctEvCoercion, ctEvId, ctEvCheckDepth, + ctEvPred, ctEvLoc, ctEvEqRel, + ctEvTerm, ctEvCoercion, ctEvId, ctEvCheckDepth, WantedConstraints(..), insolubleWC, emptyWC, isEmptyWC, andWC, unionsWC, addFlats, addImplics, mkFlatWC, addInsols, @@ -78,6 +79,8 @@ module TcRnTypes( TcPlugin(..), TcPluginResult(..), TcPluginSolver, TcPluginM, runTcPluginM, unsafeTcPluginTcM, + CtNature(..), ctEvNature, + -- Pretty printing pprEvVarTheta, pprEvVars, pprEvVarWithType, @@ -1590,6 +1593,30 @@ isDerived (CtDerived {}) = True isDerived _ = False \end{code} +%************************************************************************ +%* * + CtNature +%* * +%************************************************************************ + +Just an enum type that tracks whether a constraint is wanted, derived, +or given, when we need to separate that info from the constraint itself. + +\begin{code} + +data CtNature = Given | Wanted | Derived + +instance Outputable CtNature where + ppr Given = text "[G]" + ppr Wanted = text "[W]" + ppr Derived = text "[D]" + +ctEvNature :: CtEvidence -> CtNature +ctEvNature (CtWanted {}) = Wanted +ctEvNature (CtGiven {}) = Given +ctEvNature (CtDerived {}) = Derived + +\end{code} %************************************************************************ %* * From git at git.haskell.org Tue Dec 2 20:43:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:35 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Checkpoint. Still need to write canEqTyVar & friends. (2c70778) Message-ID: <20141202204335.ADD9B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/2c7077836e2424375ca17673bdba6ce6bf893d19/ghc >--------------------------------------------------------------- commit 2c7077836e2424375ca17673bdba6ce6bf893d19 Author: Richard Eisenberg Date: Mon Nov 24 15:40:32 2014 -0500 Checkpoint. Still need to write canEqTyVar & friends. >--------------------------------------------------------------- 2c7077836e2424375ca17673bdba6ce6bf893d19 compiler/typecheck/TcCanonical.lhs | 22 +++--- compiler/typecheck/TcEvidence.lhs | 59 ++++++++++----- compiler/typecheck/TcFlatten.lhs | 147 +++++++++++++++++++++---------------- compiler/typecheck/TcRnTypes.lhs | 4 + compiler/typecheck/TcSMonad.lhs | 22 +++--- compiler/types/Coercion.hs | 29 ++++++-- 6 files changed, 176 insertions(+), 107 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2c7077836e2424375ca17673bdba6ce6bf893d19 From git at git.haskell.org Tue Dec 2 20:43:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:38 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Checkpoint in TcInteract (0c01f54) Message-ID: <20141202204338.5A3693A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/0c01f54fa21943d735072cd44c61012f5f8d7e38/ghc >--------------------------------------------------------------- commit 0c01f54fa21943d735072cd44c61012f5f8d7e38 Author: Richard Eisenberg Date: Tue Nov 25 08:44:14 2014 -0500 Checkpoint in TcInteract >--------------------------------------------------------------- 0c01f54fa21943d735072cd44c61012f5f8d7e38 compiler/typecheck/TcCanonical.lhs | 79 +++++++++-------- compiler/typecheck/TcFlatten.lhs | 66 +++++++++++++- compiler/typecheck/TcInteract.lhs | 11 ++- compiler/typecheck/TcSMonad.lhs | 177 +++++++++++++++++++++++++++---------- 4 files changed, 246 insertions(+), 87 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0c01f54fa21943d735072cd44c61012f5f8d7e38 From git at git.haskell.org Tue Dec 2 20:43:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:41 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Stage 1 compiles (3652635) Message-ID: <20141202204341.2803E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/3652635119ff52ad2c4511df8b456978d5cafea2/ghc >--------------------------------------------------------------- commit 3652635119ff52ad2c4511df8b456978d5cafea2 Author: Richard Eisenberg Date: Tue Nov 25 21:44:42 2014 -0500 Stage 1 compiles >--------------------------------------------------------------- 3652635119ff52ad2c4511df8b456978d5cafea2 compiler/typecheck/FamInst.lhs | 7 +-- compiler/typecheck/FunDeps.lhs | 6 +- compiler/typecheck/TcCanonical.lhs | 35 +++++++----- compiler/typecheck/TcErrors.lhs | 113 +++++++++++++++---------------------- compiler/typecheck/TcEvidence.lhs | 12 ++-- compiler/typecheck/TcFlatten.lhs | 65 ++++++++++----------- compiler/typecheck/TcInteract.lhs | 63 ++++++++++++--------- compiler/typecheck/TcMType.lhs | 2 +- compiler/typecheck/TcRnTypes.lhs | 26 ++++----- compiler/typecheck/TcSMonad.lhs | 24 +++++--- compiler/typecheck/TcSimplify.lhs | 19 ++++--- compiler/typecheck/TcValidity.lhs | 9 +-- compiler/types/Coercion.hs | 16 ++++-- compiler/types/Type.hs | 2 + compiler/utils/MonadUtils.hs | 9 ++- 15 files changed, 209 insertions(+), 199 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3652635119ff52ad2c4511df8b456978d5cafea2 From git at git.haskell.org Tue Dec 2 20:43:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:43 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Check for Coercible *before* checking for classes (eb02007) Message-ID: <20141202204343.C68C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/eb020078b9bb4e4593d6bc75bd7731242e96517c/ghc >--------------------------------------------------------------- commit eb020078b9bb4e4593d6bc75bd7731242e96517c Author: Richard Eisenberg Date: Fri Nov 28 15:34:02 2014 -0500 Check for Coercible *before* checking for classes >--------------------------------------------------------------- eb020078b9bb4e4593d6bc75bd7731242e96517c compiler/typecheck/TcCanonical.lhs | 3 ++- compiler/types/Type.hs | 6 ++++-- 2 files changed, 6 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index 688f878..09e876a 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -212,7 +212,8 @@ canClassNC ev cls tys `andWhenContinue` emitSuperclasses canClass ev cls tys - = ASSERT( ctEvRole ev == Nominal ) -- all classes do *nominal* matching + = -- all classes do *nominal* matching + ASSERT2( ctEvRole ev == Nominal, ppr ev $$ ppr cls $$ ppr tys ) do { let fmode = mkFlattenEnv ev FM_FlattenAll ; (xis, cos) <- flattenMany fmode (repeat Nominal) tys ; let co = mkTcTyConAppCo Nominal (classTyCon cls) cos diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index 49f7a53..737d05e 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -992,14 +992,16 @@ data PredTree = ClassPred Class [Type] classifyPredType :: PredType -> PredTree classifyPredType ev_ty = case splitTyConApp_maybe ev_ty of - Just (tc, tys) | Just clas <- tyConClass_maybe tc - -> ClassPred clas tys Just (tc, tys) | tc `hasKey` coercibleTyConKey , let [_, ty1, ty2] = tys -> EqPred ReprEq ty1 ty2 Just (tc, tys) | tc `hasKey` eqTyConKey , let [_, ty1, ty2] = tys -> EqPred NomEq ty1 ty2 + -- NB: Coercible is also a class, so this check must come *after* + -- the Coercible check + Just (tc, tys) | Just clas <- tyConClass_maybe tc + -> ClassPred clas tys Just (tc, tys) | isTupleTyCon tc -> TuplePred tys _ -> IrredPred ev_ty From git at git.haskell.org Tue Dec 2 20:43:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:46 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: kicking out really only cares about the flavour (fdfb8d3) Message-ID: <20141202204346.6FF2C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/fdfb8d39a6de081a453da746b7a6c359d041993d/ghc >--------------------------------------------------------------- commit fdfb8d39a6de081a453da746b7a6c359d041993d Author: Richard Eisenberg Date: Fri Nov 28 17:07:13 2014 -0500 kicking out really only cares about the flavour >--------------------------------------------------------------- fdfb8d39a6de081a453da746b7a6c359d041993d compiler/typecheck/TcFlatten.lhs | 2 +- compiler/typecheck/TcInteract.lhs | 46 ++++++++++++++++++--------------------- compiler/typecheck/TcRnTypes.lhs | 5 ++++- 3 files changed, 26 insertions(+), 27 deletions(-) diff --git a/compiler/typecheck/TcFlatten.lhs b/compiler/typecheck/TcFlatten.lhs index 7e4825d..1aa53ed 100644 --- a/compiler/typecheck/TcFlatten.lhs +++ b/compiler/typecheck/TcFlatten.lhs @@ -5,7 +5,7 @@ module TcFlatten( FlattenEnv(..), FlattenMode(..), mkFlattenEnv, flatten, flattenMany, flattenFamApp, flattenTyVarOuter, unflatten, - eqCanRewrite, canRewriteOrSame + eqCanRewrite, eqCanRewriteFlavour, canRewriteOrSame ) where #include "HsVersions.h" diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index f6c979e..e9c47f5 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -831,8 +831,10 @@ interactTyVarEq inerts workItem@(CTyEqCan { cc_tyvar = tv = do { untch <- getUntouchables ; if canSolveByUnification untch ev eq_rel tv rhs then do { solveByUnification ev tv rhs - ; n_kicked <- kickOutRewritable givenFlavour tv - -- givenFlavour because the tv := xi is given + ; n_kicked <- kickOutRewritable Given NomEq tv + -- Given because the tv := xi is given + -- NomEq because only nominal equalities are solved + -- by unification ; return (Stop ev (ptext (sLit "Spontaneously solved") <+> ppr_kicked n_kicked)) } else do { traceTcS "Can't solve tyvar equality" @@ -842,7 +844,7 @@ interactTyVarEq inerts workItem@(CTyEqCan { cc_tyvar = tv <+> text "is" <+> ppr (metaTyVarUntouchables tv)) , text "RHS:" <+> ppr rhs <+> dcolon <+> ppr (typeKind rhs) , text "Untouchables =" <+> ppr untch ]) - ; n_kicked <- kickOutRewritable ev tv + ; n_kicked <- kickOutRewritable (ctEvFlavour ev) (ctEvEqRel ev) tv ; updInertCans (\ ics -> addInertCan ics workItem) ; return (Stop ev (ptext (sLit "Kept as inert") <+> ppr_kicked n_kicked)) } } @@ -915,32 +917,26 @@ solveByUnification wd tv xi setEvBind (ctEvId wd) (EvCoercion (mkTcNomReflCo xi')) } -givenFlavour :: CtEvidence --- Used just to pass to kickOutRewritable --- and to guide 'flatten' for givens -givenFlavour = CtGiven { ctev_pred = panic "givenFlavour:ev" - , ctev_evtm = panic "givenFlavour:tm" - , ctev_loc = panic "givenFlavour:loc" } - ppr_kicked :: Int -> SDoc ppr_kicked 0 = empty ppr_kicked n = parens (int n <+> ptext (sLit "kicked out")) \end{code} \begin{code} -kickOutRewritable :: CtEvidence -- Flavour of the equality that is +kickOutRewritable :: CtFlavour -- Flavour of the equality that is -- being added to the inert set + -> EqRel -- of the new equality -> TcTyVar -- The new equality is tv ~ ty -> TcS Int -kickOutRewritable new_ev new_tv - | not (new_ev `eqCanRewrite` new_ev) - = return 0 -- If new_ev can't rewrite itself, it can't rewrite +kickOutRewritable new_flavour new_eq_rel new_tv + | not (new_flavour `eqCanRewriteFlavour` new_flavour) + = return 0 -- If new_flavour can't rewrite itself, it can't rewrite -- anything else, so no need to kick out anything -- This is a common case: wanteds can't rewrite wanteds | otherwise = do { ics <- getInertCans - ; let (kicked_out, ics') = kick_out new_ev (ctEvEqRel new_ev) new_tv ics + ; let (kicked_out, ics') = kick_out new_flavour new_eq_rel new_tv ics ; setInertCans ics' ; updWorkListTcS (appendWorkList kicked_out) @@ -950,13 +946,13 @@ kickOutRewritable new_ev new_tv 2 (ppr kicked_out) ; return (workListSize kicked_out) } -kick_out :: CtEvidence -> EqRel -> TcTyVar -> InertCans -> (WorkList, InertCans) -kick_out new_ev new_eq_rel new_tv (IC { inert_eqs = tv_eqs - , inert_repr_eqs = tv_repr_eqs - , inert_dicts = dictmap - , inert_funeqs = funeqmap - , inert_irreds = irreds - , inert_insols = insols }) +kick_out :: CtFlavour -> EqRel -> TcTyVar -> InertCans -> (WorkList, InertCans) +kick_out new_flavour new_eq_rel new_tv (IC { inert_eqs = tv_eqs + , inert_repr_eqs = tv_repr_eqs + , inert_dicts = dictmap + , inert_funeqs = funeqmap + , inert_irreds = irreds + , inert_insols = insols }) = (kicked_out, inert_cans_in) where -- NB: Notice that don't rewrite @@ -988,12 +984,12 @@ kick_out new_ev new_eq_rel new_tv (IC { inert_eqs = tv_eqs -- Kick out even insolubles; see Note [Kick out insolubles] kick_out_ct :: Ct -> Bool - kick_out_ct ct = eqCanRewrite new_ev (ctEvidence ct) + kick_out_ct ct = eqCanRewriteFlavour new_flavour (ctFlavour ct) && new_tv `elemVarSet` tyVarsOfCt ct -- See Note [Kicking out inert constraints] kick_out_irred :: Ct -> Bool - kick_out_irred ct = eqCanRewrite new_ev (ctEvidence ct) + kick_out_irred ct = eqCanRewriteFlavour new_flavour (ctFlavour ct) && new_tv `elemVarSet` closeOverKinds (tyVarsOfCt ct) -- See Note [Kicking out Irreds] @@ -1701,7 +1697,7 @@ dischargeFmv evar fmv co xi = ASSERT2( not (fmv `elemVarSet` tyVarsOfType xi), ppr evar $$ ppr fmv $$ ppr xi ) do { setWantedTyBind fmv xi ; setEvBind evar (EvCoercion co) - ; n_kicked <- kickOutRewritable givenFlavour fmv + ; n_kicked <- kickOutRewritable Given NomEq fmv ; traceTcS "dischargeFuv" (ppr fmv <+> equals <+> ppr xi $$ ppr_kicked n_kicked) } \end{code} diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index a0bfeec..0f74227 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -50,7 +50,7 @@ module TcRnTypes( isCDictCan_Maybe, isCFunEqCan_maybe, isCIrredEvCan, isCNonCanonical, isWantedCt, isDerivedCt, isGivenCt, isHoleCt, isTypedHoleCt, isPartialTypeSigCt, - ctEvidence, ctLoc, ctPred, + ctEvidence, ctLoc, ctPred, ctFlavour, mkNonCanonical, mkNonCanonicalCt, ctEvPred, ctEvLoc, ctEvEqRel, ctEvTerm, ctEvCoercion, ctEvId, ctEvCheckDepth, @@ -1178,6 +1178,9 @@ ctPred :: Ct -> PredType -- See Note [Ct/evidence invariant] ctPred ct = ctEvPred (cc_ev ct) +ctFlavour :: Ct -> CtFlavour +ctFlavour = ctEvFlavour . ctEvidence + dropDerivedWC :: WantedConstraints -> WantedConstraints -- See Note [Dropping derived constraints] dropDerivedWC wc@(WC { wc_flat = flats }) From git at git.haskell.org Tue Dec 2 20:43:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:49 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Check validity of EqPred ReprEq correctly (ada2776) Message-ID: <20141202204349.2BA523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/ada2776b77d042866035d5800d1727cc872fccd6/ghc >--------------------------------------------------------------- commit ada2776b77d042866035d5800d1727cc872fccd6 Author: Richard Eisenberg Date: Fri Nov 28 17:09:49 2014 -0500 Check validity of EqPred ReprEq correctly >--------------------------------------------------------------- ada2776b77d042866035d5800d1727cc872fccd6 compiler/typecheck/TcValidity.lhs | 42 +++++++++++++++++++++++---------------- 1 file changed, 25 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcValidity.lhs b/compiler/typecheck/TcValidity.lhs index d8e2721..d62fe38 100644 --- a/compiler/typecheck/TcValidity.lhs +++ b/compiler/typecheck/TcValidity.lhs @@ -502,7 +502,7 @@ check_pred_help under_syn dflags ctxt pred = case classifyPredType pred of ClassPred cls tys -> check_class_pred dflags ctxt pred cls tys EqPred NomEq _ _ -> check_eq_pred dflags pred - EqPred ReprEq ty1 ty2 -> check_class_pred dflags ctxt pred coercibleClass [ty1, ty2] + EqPred ReprEq ty1 ty2 -> check_repr_eq_pred dflags ctxt pred ty1 ty2 TuplePred tys -> check_tuple_pred under_syn dflags ctxt pred tys IrredPred _ -> check_irred_pred under_syn dflags ctxt pred @@ -515,27 +515,31 @@ check_class_pred dflags ctxt pred cls tys (badIPPred pred) -- Check the form of the argument types - ; checkTc (check_class_pred_tys dflags ctxt tys) - (predTyVarErr (mkClassPred cls tys) $$ how_to_allow) + ; check_class_pred_tys dflags ctxt pred tys } where class_name = className cls arity = classArity cls n_tys = length tys arity_err = arityErr "Class" class_name arity n_tys - how_to_allow = parens (ptext (sLit "Use FlexibleContexts to permit this")) check_eq_pred :: DynFlags -> PredType -> TcM () check_eq_pred dflags pred - = -- Equational constraints are valid in all contexts if type - -- families are permitted + = -- Equational constraints are valid in all contexts if type + -- families are permitted checkTc (xopt Opt_TypeFamilies dflags || xopt Opt_GADTs dflags) (eqPredTyErr pred) -check_tuple_pred :: Bool -> DynFlags -> UserTypeCtxt -> PredType -> [PredType] -> TcM () -check_tuple_pred under_syn dflags ctxt pred ts - = do { -- See Note [ConstraintKinds in predicates] - checkTc (under_syn || xopt Opt_ConstraintKinds dflags) +check_repr_eq_pred :: DynFlags -> UserTypeCtxt -> PredType -> TcType -> TcType -> TcM () +check_repr_eq_pred dflags ctxt pred ty1 ty2 + = do { mapM_ checkValidMonoType tys + ; check_class_pred_tys dflags ctxt pred tys } + where + tys = [ty1, ty2] + +check_tuple_pred :: DynFlags -> UserTypeCtxt -> PredType -> [PredType] -> TcM () +check_tuple_pred dflags ctxt pred ts + = do { checkTc (xopt Opt_ConstraintKinds dflags) (predTupleErr pred) ; mapM_ (check_pred_help under_syn dflags ctxt) ts } -- This case will not normally be executed because without @@ -587,18 +591,22 @@ It is equally dangerous to allow them in instance heads because in that case the Paterson conditions may not detect duplication of a type variable or size change. -} ------------------------- -check_class_pred_tys :: DynFlags -> UserTypeCtxt -> [KindOrType] -> Bool -check_class_pred_tys dflags ctxt kts - = case ctxt of +check_class_pred_tys :: DynFlags -> UserTypeCtxt -> PredType -> [KindOrType] -> TcM () +check_class_pred_tys dflags ctxt pred kts + = checkTc pred_ok (predTyVarErr pred $$ how_to_allow) + where + (_, tys) = span isKind kts -- see Note [Kind polymorphic type classes] + flexible_contexts = xopt Opt_FlexibleContexts dflags + undecidable_ok = xopt Opt_UndecidableInstances dflags + + pred_ok = case ctxt of SpecInstCtxt -> True -- {-# SPECIALISE instance Eq (T Int) #-} is fine InstDeclCtxt -> flexible_contexts || undecidable_ok || all tcIsTyVarTy tys -- Further checks on head and theta in -- checkInstTermination _ -> flexible_contexts || all tyvar_head tys - where - (_, tys) = span isKind kts -- see Note [Kind polymorphic type classes] - flexible_contexts = xopt Opt_FlexibleContexts dflags - undecidable_ok = xopt Opt_UndecidableInstances dflags + how_to_allow = parens (ptext (sLit "Use FlexibleContexts to permit this")) + ------------------------- tyvar_head :: Type -> Bool From git at git.haskell.org Tue Dec 2 20:43:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:51 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Rewrite `Coercible` solver (1d29739) Message-ID: <20141202204351.C015A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/1d29739aa690a43befd98b30223dabd93168ba5c/ghc >--------------------------------------------------------------- commit 1d29739aa690a43befd98b30223dabd93168ba5c Author: Richard Eisenberg Date: Mon Dec 1 10:28:34 2014 -0500 Rewrite `Coercible` solver Summary: This is a rewrite of the algorithm to solve for Coercible "instances". A preliminary form of these ideas is at https://ghc.haskell.org/trac/ghc/wiki/Design/NewCoercibleSolver The basic idea here is that the `EqPred` constructor of `PredTree` now is parameterised by a new type `EqRel` (where `data EqRel = NomEq | ReprEq`). Thus, every equality constraint can now talk about nominal equality (the usual case) or representational equality (the `Coercible` case). This is a change from the previous behavior where `Coercible` was just considered a regular class with a special case in `matchClassInst`. Because of this change, representational equalities are now canonicalized just like nominal ones, allowing more equalities to be solved -- in particular, the case at the top of #9117. A knock-on effect is that the flattener must be aware of the choice of equality relation, because the inert set now stores both representational inert equalities alongside the nominal inert equalities. Of course, we can use representational equalities to rewrite only within another representational equality -- thus the parameterization of the flattener. A nice side effect of this change is that I've introduced a new type `CtFlavour`, which tracks G vs. W vs. D, removing some ugliness in the flattener. Test Plan: testsuite, a new T9117, and others TBD Reviewers: simonpj, austin, nomeata Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D546 GHC Trac Issues: #9117 >--------------------------------------------------------------- 1d29739aa690a43befd98b30223dabd93168ba5c compiler/typecheck/TcCanonical.lhs | 0 compiler/typecheck/TcErrors.lhs | 0 compiler/typecheck/TcFlatten.lhs | 0 compiler/typecheck/TcSMonad.lhs | 11 ++++++++--- compiler/typecheck/TcValidity.lhs | 0 compiler/types/Coercion.hs | 2 -- 6 files changed, 8 insertions(+), 5 deletions(-) diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index 80ff73b..c9b979d 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -818,7 +818,8 @@ splitInertCans iCans = (given,derived,wanted) where allCts = foldDicts (:) (inert_dicts iCans) $ foldFunEqs (:) (inert_funeqs iCans) - $ concat (varEnvElts (inert_eqs iCans)) + $ concat (varEnvElts (inert_eqs iCans) ++ + varEnvElts (inert_repr_eqs iCans)) (derived,other) = partition isDerivedCt allCts (wanted,given) = partition isWantedCt other @@ -838,8 +839,12 @@ removeInertCt is ct = 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 } + CTyEqCan { cc_tyvar = x, cc_rhs = ty, cc_eq_rel = NomEq } -> + is { inert_eqs = delTyEq (inert_eqs is) x ty + , inert_repr_eqs = delTyEq (inert_repr_eqs is) x ty } + + CTyEqCan { cc_tyvar = x, cc_rhs = ty, cc_eq_rel = ReprEq } -> + is { inert_repr_eqs = delTyEq (inert_repr_eqs is) x ty } CIrredEvCan {} -> panic "removeInertCt: CIrredEvCan" CNonCanonical {} -> panic "removeInertCt: CNonCanonical" diff --git a/compiler/types/Coercion.hs b/compiler/types/Coercion.hs index bb39207..2b5081a 100644 --- a/compiler/types/Coercion.hs +++ b/compiler/types/Coercion.hs @@ -1994,5 +1994,3 @@ instance IsCoercion Coercion where gMkUnbranchedAxInstCo :: IsCoercion co => Role -> CoAxiom Unbranched -> [Type] -> co gMkUnbranchedAxInstCo r ax = gMkAxInstCo r ax 0 - -\end{code} From git at git.haskell.org Tue Dec 2 20:43:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:54 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Fix compiler errors (a2288fc) Message-ID: <20141202204354.6E02A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/a2288fc7693476fea62f10a6d3508d1938283ad1/ghc >--------------------------------------------------------------- commit a2288fc7693476fea62f10a6d3508d1938283ad1 Author: Richard Eisenberg Date: Mon Dec 1 11:32:26 2014 -0500 Fix compiler errors >--------------------------------------------------------------- a2288fc7693476fea62f10a6d3508d1938283ad1 compiler/typecheck/TcSMonad.lhs | 12 ++++++++++++ compiler/typecheck/TcValidity.lhs | 10 +++++----- 2 files changed, 17 insertions(+), 5 deletions(-) diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index c9b979d..214afa7 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -913,6 +913,18 @@ lookupSolvedDict (IS { inert_solved_dicts = solved }) loc cls tys Just ev | ctEvCheckDepth cls loc ev -> Just ev _ -> Nothing +\end{code} + +%************************************************************************ +%* * + TyEqMap +%* * +%************************************************************************ + +\begin{code} + +type TyEqMap a = TyVarEnv a + findTyEqs :: EqRel -> InertCans -> TyVar -> EqualCtList findTyEqs NomEq icans tv = lookupVarEnv (inert_eqs icans) tv `orElse` [] findTyEqs ReprEq icans tv = lookupVarEnv (inert_repr_eqs icans) tv `orElse` [] diff --git a/compiler/typecheck/TcValidity.lhs b/compiler/typecheck/TcValidity.lhs index 42336a3..de93387 100644 --- a/compiler/typecheck/TcValidity.lhs +++ b/compiler/typecheck/TcValidity.lhs @@ -530,15 +530,15 @@ check_eq_pred dflags pred checkTc (xopt Opt_TypeFamilies dflags || xopt Opt_GADTs dflags) (eqPredTyErr pred) -check_repr_eq_pred :: DynFlags -> UserTypeCtxt -> PredType -> TcType -> TcType -> TcM () +check_repr_eq_pred :: DynFlags -> UserTypeCtxt -> PredType + -> TcType -> TcType -> TcM () check_repr_eq_pred dflags ctxt pred ty1 ty2 - = do { mapM_ checkValidMonoType tys - ; check_class_pred_tys dflags ctxt pred tys } + = check_class_pred_tys dflags ctxt pred tys where tys = [ty1, ty2] -check_tuple_pred :: DynFlags -> UserTypeCtxt -> PredType -> [PredType] -> TcM () -check_tuple_pred dflags ctxt pred ts +check_tuple_pred :: Bool -> DynFlags -> UserTypeCtxt -> PredType -> [PredType] -> TcM () +check_tuple_pred under_syn dflags ctxt pred ts = do { checkTc (xopt Opt_ConstraintKinds dflags) (predTupleErr pred) ; mapM_ (check_pred_help under_syn dflags ctxt) ts } From git at git.haskell.org Tue Dec 2 20:43:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:57 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Clarify "representation" from "type" in error messages (40e997c) Message-ID: <20141202204357.2C63A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/40e997c709a17139e4e8a8d84a69f6669f413fd0/ghc >--------------------------------------------------------------- commit 40e997c709a17139e4e8a8d84a69f6669f413fd0 Author: Richard Eisenberg Date: Mon Dec 1 14:40:49 2014 -0500 Clarify "representation" from "type" in error messages >--------------------------------------------------------------- 40e997c709a17139e4e8a8d84a69f6669f413fd0 compiler/typecheck/TcErrors.lhs | 36 ++++++++++++++++++++++-------------- compiler/typecheck/TcRnTypes.lhs | 7 ++++++- 2 files changed, 28 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs index 4c829b1..072a736 100644 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@ -798,7 +798,7 @@ mkTyVarEqErr dflags ctxt extra ct oriented tv1 ty2 | (implic:_) <- cec_encl ctxt , Implic { ic_skols = skols } <- implic , tv1 `elem` skols - = mkErrorMsg ctxt ct (vcat [ misMatchMsg oriented ty1 ty2 + = mkErrorMsg ctxt ct (vcat [ misMatchMsg oriented eq_rel ty1 ty2 , extraTyVarInfo ctxt tv1 ty2 , extra ]) @@ -807,7 +807,7 @@ mkTyVarEqErr dflags ctxt extra ct oriented tv1 ty2 , Implic { ic_env = env, ic_skols = skols, ic_info = skol_info } <- implic , let esc_skols = filter (`elemVarSet` (tyVarsOfType ty2)) skols , not (null esc_skols) - = do { let msg = misMatchMsg oriented ty1 ty2 + = do { let msg = misMatchMsg oriented eq_rel ty1 ty2 esc_doc = sep [ ptext (sLit "because type variable") <> plural esc_skols <+> pprQuotedList esc_skols , ptext (sLit "would escape") <+> @@ -825,7 +825,7 @@ mkTyVarEqErr dflags ctxt extra ct oriented tv1 ty2 -- Nastiest case: attempt to unify an untouchable variable | (implic:_) <- cec_encl ctxt -- Get the innermost context , Implic { ic_env = env, ic_given = given, ic_info = skol_info } <- implic - = do { let msg = misMatchMsg oriented ty1 ty2 + = do { let msg = misMatchMsg oriented eq_rel ty1 ty2 untch_extra = nest 2 $ sep [ quotes (ppr tv1) <+> ptext (sLit "is untouchable") @@ -843,9 +843,10 @@ mkTyVarEqErr dflags ctxt extra ct oriented tv1 ty2 -- Not an occurs check, because F is a type function. where occ_check_expand = occurCheckExpand dflags tv1 ty2 - k1 = tyVarKind tv1 - k2 = typeKind ty2 - ty1 = mkTyVarTy tv1 + k1 = tyVarKind tv1 + k2 = typeKind ty2 + ty1 = mkTyVarTy tv1 + eq_rel = ctEqRel ct mkEqInfoMsg :: Ct -> TcType -> TcType -> SDoc -- Report (a) ambiguity if either side is a type function application @@ -889,7 +890,7 @@ misMatchOrCND ctxt ct oriented ty1 ty2 isGivenCt ct -- If the equality is unconditionally insoluble -- or there is no context, don't report the context - = misMatchMsg oriented ty1 ty2 + = misMatchMsg oriented (ctEqRel ct) ty1 ty2 | otherwise = couldNotDeduce givens ([mkTcEqPred ty1 ty2], orig) where @@ -964,23 +965,30 @@ kindErrorMsg ty1 ty2 k2 = typeKind ty2 -------------------- -misMatchMsg :: Maybe SwapFlag -> TcType -> TcType -> SDoc -- Types are already tidy +misMatchMsg :: Maybe SwapFlag -> EqRel -> TcType -> TcType -> SDoc +-- Types are already tidy -- If oriented then ty1 is actual, ty2 is expected -misMatchMsg oriented ty1 ty2 +misMatchMsg oriented eq_rel ty1 ty2 | Just IsSwapped <- oriented - = misMatchMsg (Just NotSwapped) ty2 ty1 + = misMatchMsg (Just NotSwapped) eq_rel ty2 ty1 | Just NotSwapped <- oriented - = sep [ ptext (sLit "Couldn't match expected") <+> what <+> quotes (ppr ty2) - , nest 12 $ ptext (sLit "with actual") <+> what <+> quotes (ppr ty1) + = sep [ text "Couldn't match" <+> repr1 <+> text "expected" <+> + what <+> quotes (ppr ty2) + , nest 12 $ text "with" <+> repr2 <+> text "actual" <+> + what <+> quotes (ppr ty1) , sameOccExtra ty2 ty1 ] | otherwise - = sep [ ptext (sLit "Couldn't match") <+> what <+> quotes (ppr ty1) - , nest 14 $ ptext (sLit "with") <+> quotes (ppr ty2) + = sep [ ptext (sLit "Couldn't match") <+> repr1 <+> what <+> quotes (ppr ty1) + , nest 14 $ ptext (sLit "with") <+> repr2 <+> quotes (ppr ty2) , sameOccExtra ty1 ty2 ] where what | isKind ty1 = ptext (sLit "kind") | otherwise = ptext (sLit "type") + (repr1, repr2) = case eq_rel of + NomEq -> (empty, empty) + ReprEq -> (text "representation of", text "that of") + mkExpectedActualMsg :: Type -> Type -> CtOrigin -> (Maybe SwapFlag, SDoc) -- NotSwapped means (actual, expected), IsSwapped is the reverse mkExpectedActualMsg ty1 ty2 (TypeEqOrigin { uo_actual = act, uo_expected = exp }) diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index 0f74227..713829a 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -50,7 +50,7 @@ module TcRnTypes( isCDictCan_Maybe, isCFunEqCan_maybe, isCIrredEvCan, isCNonCanonical, isWantedCt, isDerivedCt, isGivenCt, isHoleCt, isTypedHoleCt, isPartialTypeSigCt, - ctEvidence, ctLoc, ctPred, ctFlavour, + ctEvidence, ctLoc, ctPred, ctFlavour, ctEqRel, mkNonCanonical, mkNonCanonicalCt, ctEvPred, ctEvLoc, ctEvEqRel, ctEvTerm, ctEvCoercion, ctEvId, ctEvCheckDepth, @@ -1178,9 +1178,14 @@ ctPred :: Ct -> PredType -- See Note [Ct/evidence invariant] ctPred ct = ctEvPred (cc_ev ct) +-- | Get the flavour of the given 'Ct' ctFlavour :: Ct -> CtFlavour ctFlavour = ctEvFlavour . ctEvidence +-- | Get the equality relation for the given 'Ct' +ctEqRel :: Ct -> EqRel +ctEqRel = ctEvEqRel . ctEvidence + dropDerivedWC :: WantedConstraints -> WantedConstraints -- See Note [Dropping derived constraints] dropDerivedWC wc@(WC { wc_flat = flats }) From git at git.haskell.org Tue Dec 2 20:43:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:43:59 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Print DerivOriginCoerce errors with context (4be1115) Message-ID: <20141202204359.D066D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/4be1115933460d7c97e98bf83e49341ffabeda65/ghc >--------------------------------------------------------------- commit 4be1115933460d7c97e98bf83e49341ffabeda65 Author: Richard Eisenberg Date: Mon Dec 1 14:58:48 2014 -0500 Print DerivOriginCoerce errors with context >--------------------------------------------------------------- 4be1115933460d7c97e98bf83e49341ffabeda65 compiler/typecheck/TcErrors.lhs | 7 ++++--- compiler/typecheck/TcRnTypes.lhs | 4 ++-- 2 files changed, 6 insertions(+), 5 deletions(-) diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs index 072a736..1d8fedc 100644 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@ -708,9 +708,10 @@ mkEqErr1 ctxt ct TypeEqOrigin {} -> snd (mkExpectedActualMsg cty1 cty2 sub_o) _ -> empty - mk_wanted_extra orig@(FunDepOrigin1 {}) = (Nothing, pprArising orig) - mk_wanted_extra orig@(FunDepOrigin2 {}) = (Nothing, pprArising orig) - mk_wanted_extra _ = (Nothing, empty) + mk_wanted_extra orig@(FunDepOrigin1 {}) = (Nothing, pprArising orig) + mk_wanted_extra orig@(FunDepOrigin2 {}) = (Nothing, pprArising orig) + mk_wanted_extra orig@(DerivOriginCoerce {}) = (Nothing, pprArising orig) + mk_wanted_extra _ = (Nothing, empty) -- | This function tries to reconstruct why a "Coercible ty1 ty2" constraint -- is left over. diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index 713829a..136489a 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -2002,8 +2002,8 @@ pprCtOrigin (DerivOriginDC dc n) pprCtOrigin (DerivOriginCoerce meth ty1 ty2) = hang (ctoHerald <+> ptext (sLit "the coercion of the method") <+> quotes (ppr meth)) - 2 (sep [ ptext (sLit "from type") <+> quotes (ppr ty1) - , ptext (sLit " to type") <+> quotes (ppr ty2) ]) + 2 (sep [ text "from type" <+> quotes (ppr ty1) + , nest 2 $ text "to type" <+> quotes (ppr ty2) ]) pprCtOrigin simple_origin = ctoHerald <+> pprCtO simple_origin From git at git.haskell.org Tue Dec 2 20:44:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:44:02 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Solve reflexive repr eqs by reflexivity, even if they're AppTy's. (59d415f) Message-ID: <20141202204402.80D113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/59d415fc0c53328635729bd521c310e96b3e2bc0/ghc >--------------------------------------------------------------- commit 59d415fc0c53328635729bd521c310e96b3e2bc0 Author: Richard Eisenberg Date: Mon Dec 1 15:08:29 2014 -0500 Solve reflexive repr eqs by reflexivity, even if they're AppTy's. >--------------------------------------------------------------- 59d415fc0c53328635729bd521c310e96b3e2bc0 compiler/typecheck/TcCanonical.lhs | 21 +++++++++++++++++---- 1 file changed, 17 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index 2ee122f..19b9975 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -555,6 +555,11 @@ can_eq_flat_app ev eq_rel swapped s1 t1 ps_ty1 ty2 ps_ty2 | NomEq <- eq_rel , Just (s2,t2) <- tcSplitAppTy_maybe ty2 = unSwap swapped decompose_it (s1,t1) (s2,t2) + | mkAppTy s1 t1 `eqType` ty2 -- this check is necessary for representational + -- equalities, where we might be unable to + -- decompose a reflexive constraint, like + -- Coercible (f a) (f a) + = canEqReflexive ev eq_rel ty2 | otherwise = unSwap swapped (canEqFailure ev eq_rel) ps_ty1 ps_ty2 where @@ -609,10 +614,7 @@ can_eq_newtype_nc rdr_env ev swapped co ty1 ty1' ty2 ps_ty2 ; stopWith ev "unwrapping newtypes blew stack" } else do { if ty1 `eqType` ty2 -- See Note [Eager reflexivity check] - then do { when (isWanted ev) $ - setEvBind (ctev_evar ev) (EvCoercion $ - mkTcReflCo Representational ty1) - ; stopWith ev "Eager reflexivity check before newtype reduction" } + then canEqReflexive ev ReprEq ty1 else do { markDataConsAsUsed rdr_env (tyConAppTyCon ty1) ; mb_ct <- rewriteEqEvidence ev ReprEq swapped ty1' ps_ty2 @@ -1009,6 +1011,17 @@ canEqTyVarTyVar ev eq_rel swapped tv1 tv2 co2 = (isSigTyVar tv1 && not (isSigTyVar tv2)) || (isSystemName (Var.varName tv2) && not (isSystemName (Var.varName tv1))) +-- | Solve a reflexive equality constraint +canEqReflexive :: CtEvidence -- ty ~ ty + -> EqRel + -> TcType -- ty + -> TcS (StopOrContinue Ct) -- always Stop +canEqReflexive ev eq_rel ty + = do { when (isWanted ev) $ + setEvBind (ctev_evar ev) (EvCoercion $ + mkTcReflCo (eqRelRole eq_rel) ty) + ; stopWith ev "Solved by reflexivity" } + incompatibleKind :: CtEvidence -- t1~t2 -> TcType -> TcKind -> TcType -> TcKind -- s1~s2, flattened and zonked From git at git.haskell.org Tue Dec 2 20:44:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:44:05 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Don't allow newtypes at top-level on RHS of R equalities. (1376c00) Message-ID: <20141202204405.5FFBC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/1376c00a6f719d596849349c6f6cff4455efe868/ghc >--------------------------------------------------------------- commit 1376c00a6f719d596849349c6f6cff4455efe868 Author: Richard Eisenberg Date: Mon Dec 1 16:41:45 2014 -0500 Don't allow newtypes at top-level on RHS of R equalities. >--------------------------------------------------------------- 1376c00a6f719d596849349c6f6cff4455efe868 compiler/typecheck/TcCanonical.lhs | 76 +++++++++++++++++++++++++++++--------- 1 file changed, 58 insertions(+), 18 deletions(-) diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index 19b9975..e1e74cc 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -806,6 +806,26 @@ As this point we have an insoluble constraint, like Int~Bool. generating two (or more) insoluble fundep constraints from the same class constraint. +Note [No top-level newtypes on RHS] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Suppose we're in this situation: + + work item: [W] c1 : a ~R b + [G] c2 : b ~R Id a + +where + newtype Id a = Id a + +Further, suppose flattening `a` doesn't do anything. Then, we'll flatten the +RHS of c1 and have a new [W] c3 : a ~R Id a. If we just blindly proceed, we'll +fail in canEqTyVar2 with an occurs-check. What we really need to do is to +unwrap the `Id a` in the RHS. This is exactly analogous to the requirement for +no top-level type families on the RHS of a nominal equality. The only +annoyance is that the flattener doesn't do this work for us when flattening +the RHS, so we have to catch this case here and then go back to the beginning +of can_eq_nc. We know that this can't loop forever because we require that +flattening the RHS actually made progress. (If it didn't, then we really +*should* fail with an occurs-check!) \begin{code} canCFunEqCan :: CtEvidence @@ -845,24 +865,44 @@ canEqTyVar ev eq_rel swapped tv1 ty2 ps_ty2 -- ev :: tv ~ s2 ; let fmode = mkFlattenEnv ev FM_FlattenAll -- the FM_ param is ignored ; mb_yes <- flattenTyVarOuter fmode tv1 ; case mb_yes of - Right (ty1, co1, _) -- co1 :: ty1 ~ tv1 - -> do { mb <- rewriteEqEvidence ev eq_rel swapped ty1 ps_ty2 - co1 (mkTcReflCo (eqRelRole eq_rel) ps_ty2) - ; traceTcS "canEqTyVar2" (vcat [ppr tv1, ppr ty2, ppr swapped, ppr ty1, - ppUnless (isDerived ev) (ppr co1)]) - ; case mb of - Stop ev s -> return (Stop ev s) - ContinueWith new_ev -> can_eq_nc new_ev eq_rel ty1 ty1 ty2 ps_ty2 } - - Left tv1' -> do { -- FM_Avoid commented out: see Note [Lazy flattening] in TcFlatten - -- let fmode = FE { fe_ev = ev, fe_mode = FM_Avoid tv1' True } - -- Flatten the RHS less vigorously, to avoid gratuitous flattening - -- True <=> xi2 should not itself be a type-function application - let fmode = mkFlattenEnv ev FM_FlattenAll - ; (xi2, co2) <- flatten fmode ps_ty2 -- co2 :: xi2 ~ ps_ty2 - -- Use ps_ty2 to preserve type synonyms if poss - ; dflags <- getDynFlags - ; canEqTyVar2 dflags ev eq_rel swapped tv1' xi2 co2 } } + Right (ty1, co1, _) -> -- co1 :: ty1 ~ tv1 + do { mb <- rewriteEqEvidence ev eq_rel swapped ty1 ps_ty2 + co1 (mkTcReflCo (eqRelRole eq_rel) ps_ty2) + ; traceTcS "canEqTyVar2" (vcat [ppr tv1, ppr ty2, ppr swapped, ppr ty1, + ppUnless (isDerived ev) (ppr co1)]) + ; case mb of + Stop ev s -> return (Stop ev s) + ContinueWith new_ev -> can_eq_nc new_ev eq_rel ty1 ty1 ty2 ps_ty2 } + + Left tv1' -> + do { -- FM_Avoid commented out: see Note [Lazy flattening] in TcFlatten + -- let fmode = FE { fe_ev = ev, fe_mode = FM_Avoid tv1' True } + -- Flatten the RHS less vigorously, to avoid gratuitous flattening -- True <=> xi2 should not itself be a type-function application + let fmode = mkFlattenEnv ev FM_FlattenAll + ; (xi2, co2) <- flatten fmode ps_ty2 -- co2 :: xi2 ~ ps_ty2 + -- Use ps_ty2 to preserve type synonyms if poss + ; traceTcS "canEqTyVar flat LHS" + (vcat [ ppr tv1, ppr tv1', ppr ty2, ppr swapped, + ppr xi2 ]) + ; dflags <- getDynFlags + ; case eq_rel of + ReprEq -- See Note [No top-level newtypes on RHS] + | Just (tc2, _) <- tcSplitTyConApp_maybe xi2 + , isNewTyCon tc2 + , not (ps_ty2 `eqType` xi2) + -> do { let xi1 = mkTyVarTy tv1' + role = eqRelRole eq_rel + ; mb <- rewriteEqEvidence ev eq_rel swapped + xi1 xi2 + (mkTcReflCo role xi1) co2 + ; traceTcS "canEqTyVar exposed newtype" + (vcat [ ppr tv1', ppr ps_ty2 + , ppr xi2, ppr tc2 ]) + ; case mb of + Stop ev s -> return (Stop ev s) + ContinueWith new_ev -> + can_eq_nc new_ev eq_rel xi1 xi1 xi2 xi2 } + _ -> canEqTyVar2 dflags ev eq_rel swapped tv1' xi2 co2 } } canEqTyVar2 :: DynFlags -> CtEvidence -- olhs ~ orhs (or, if swapped, orhs ~ olhs) From git at git.haskell.org Tue Dec 2 20:44:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:44:08 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Refactor canonicalizer in terms of `andWhenContinue` (7b7cc9f) Message-ID: <20141202204408.1EA133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/7b7cc9ff7d23740ade82a41075a8c29d8d559e2d/ghc >--------------------------------------------------------------- commit 7b7cc9ff7d23740ade82a41075a8c29d8d559e2d Author: Richard Eisenberg Date: Mon Dec 1 19:17:29 2014 -0500 Refactor canonicalizer in terms of `andWhenContinue` >--------------------------------------------------------------- 7b7cc9ff7d23740ade82a41075a8c29d8d559e2d compiler/typecheck/TcCanonical.lhs | 134 +++++++++++++++---------------------- compiler/typecheck/TcSMonad.lhs | 1 + 2 files changed, 56 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 7b7cc9ff7d23740ade82a41075a8c29d8d559e2d From git at git.haskell.org Tue Dec 2 20:44:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:44:11 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Test T9117 in typecheck/should_compile/T9117_3 (f996b54) Message-ID: <20141202204411.543743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/f996b542db52570484108c5d4689ea33d08bcbd0/ghc >--------------------------------------------------------------- commit f996b542db52570484108c5d4689ea33d08bcbd0 Author: Richard Eisenberg Date: Mon Dec 1 20:19:29 2014 -0500 Test T9117 in typecheck/should_compile/T9117_3 >--------------------------------------------------------------- f996b542db52570484108c5d4689ea33d08bcbd0 testsuite/tests/typecheck/should_compile/T9117_3.hs | 7 +++++++ testsuite/tests/typecheck/should_compile/all.T | 3 ++- 2 files changed, 9 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/typecheck/should_compile/T9117_3.hs b/testsuite/tests/typecheck/should_compile/T9117_3.hs new file mode 100644 index 0000000..64db035 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9117_3.hs @@ -0,0 +1,7 @@ +module T9117_3 where + +import Data.Type.Coercion +import Data.Coerce + +eta :: Coercible f g => Coercion (f a) (g a) +eta = Coercion diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index e1f4c3f..445aaa2 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -421,7 +421,8 @@ test('MutRec', normal, compile, ['']) test('T8856', normal, compile, ['']) test('T9569a', normal, compile, ['']) test('T9117', normal, compile, ['']) -test('T9117_2', expect_broken('9117'), compile, ['']) +test('T9117_2', normal, compile, ['']) +test('T9117_3', normal, compile, ['']) test('T9708', normal, compile_fail, ['']) test('T9404', normal, compile, ['']) test('T9404b', normal, compile, ['']) From git at git.haskell.org Tue Dec 2 20:44:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:44:14 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: AppTy reflexivity check (9d4cd32) Message-ID: <20141202204414.2336E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/9d4cd3294c09127aef6c8bcaf5475dc44a45d617/ghc >--------------------------------------------------------------- commit 9d4cd3294c09127aef6c8bcaf5475dc44a45d617 Author: Richard Eisenberg Date: Mon Dec 1 20:20:00 2014 -0500 AppTy reflexivity check >--------------------------------------------------------------- 9d4cd3294c09127aef6c8bcaf5475dc44a45d617 compiler/typecheck/TcCanonical.lhs | 50 +++++++++++++++++++++++++++++++++----- 1 file changed, 44 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index 856ad92..2c052a0 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -29,6 +29,7 @@ import RdrName import Util import BasicTypes import Data.Maybe ( isJust ) +import Control.Monad ( liftM ) \end{code} @@ -546,13 +547,25 @@ can_eq_flat_app ev eq_rel swapped s1 t1 ps_ty1 ty2 ps_ty2 | NomEq <- eq_rel , Just (s2,t2) <- tcSplitAppTy_maybe ty2 = unSwap swapped decompose_it (s1,t1) (s2,t2) - | mkAppTy s1 t1 `eqType` ty2 -- this check is necessary for representational - -- equalities, where we might be unable to - -- decompose a reflexive constraint, like - -- Coercible (f a) (f a) - = canEqReflexive ev eq_rel ty2 | otherwise - = unSwap swapped (canEqFailure ev eq_rel) ps_ty1 ps_ty2 + = do { -- See Note [AppTy reflexivity check] + mb <- case eq_rel of + NomEq -> return Nothing + ReprEq -> + do { let fmode = mkFlattenEnv ev FM_FlattenAll + xi1 = mkAppTy s1 t1 + ; (xi2, co2) <- flatten fmode ps_ty2 + ; if xi1 `eqType` xi2 + then Just `liftM` + (rewriteEqEvidence ev eq_rel swapped xi1 xi2 + (mkTcReflCo Representational xi1) co2 + `andWhenContinue` \ new_ev -> + canEqReflexive new_ev eq_rel xi1) + else return Nothing } + ; case mb of + Just res -> return res + Nothing -> -- we're hosed. give up. + unSwap swapped (canEqFailure ev eq_rel) ps_ty1 ps_ty2 } where decompose_it (s1,t1) (s2,t2) = do { let xevcomp [x,y] = EvCoercion (mkTcAppCo (evTermCoercion x) (evTermCoercion y)) @@ -580,6 +593,31 @@ we do this eager reflexivity check. This is necessary only for representational equality because the flattener technology deals with the similar case (recursive type families) for nominal equality. +Note [AppTy reflexivity check] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider trying to prove (f a) ~R (f a). The AppTys in there can't +be decomposed, because representational equality isn't congruent with respect +to AppTy. So, when canonicalising the equality above, we get stuck and +would normally produce a CIrredEvCan. However, we really do want to +be able to solve (f a) ~R (f a). So, in the representational case only, +we do a reflexivity check. + +(This would be sound in the nominal case, but unnecessary, and I [Richard +E.] am worried that it would slow down the common case. Thus, the somewhat +awkward use of Maybe (StopOrContinue CtEvidence).) + +We must additionally be careful to flatten the RHS of the equality before +doing the check. Here is a real case that came from the testsuite (T9117_3): + + work item: [W] c1: f a ~R g a + inert set: [G] c2: g ~R f + +In can_eq_app, we try to flatten the LHS of c1. This causes no effect, +because `f` cannot be rewritten. So, we go to can_eq_flat_app. Without +flattening the RHS, the reflexivity check fails, and we give up. However, +flattening the RHS rewrites `g` to `f`, the reflexivity check succeeds, +and we go on to glory. + \begin{code} ------------------------ From git at git.haskell.org Tue Dec 2 20:44:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:44:16 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Better error messages, now unwraps data instances. (f2e585b) Message-ID: <20141202204416.C485C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/f2e585b3dace1757a83d9a6a1d1ab1fa20a8d21a/ghc >--------------------------------------------------------------- commit f2e585b3dace1757a83d9a6a1d1ab1fa20a8d21a Author: Richard Eisenberg Date: Mon Dec 1 22:03:04 2014 -0500 Better error messages, now unwraps data instances. >--------------------------------------------------------------- f2e585b3dace1757a83d9a6a1d1ab1fa20a8d21a compiler/coreSyn/CoreArity.lhs | 2 +- compiler/deSugar/DsCCall.lhs | 4 +- compiler/stranal/WwLib.hs | 2 +- compiler/typecheck/Inst.lhs | 8 +- compiler/typecheck/TcCanonical.lhs | 43 ++++--- compiler/typecheck/TcErrors.lhs | 36 +++++- compiler/typecheck/TcEvidence.lhs | 27 ++-- compiler/typecheck/TcMType.lhs | 4 + compiler/typecheck/TcRnTypes.lhs | 9 ++ compiler/types/Coercion.hs | 80 ++++++------ compiler/types/FamInstEnv.hs | 143 ++++++++++++--------- .../tests/indexed-types/should_fail/T9580.stderr | 6 +- .../typecheck/should_fail/TcCoercibleFail.stderr | 47 +++---- .../tests/typecheck/should_run/TcCoercible.hs | 13 +- 14 files changed, 244 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 f2e585b3dace1757a83d9a6a1d1ab1fa20a8d21a From git at git.haskell.org Tue Dec 2 20:44:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:44:19 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Lots of bugfixing. (4ef3eeb) Message-ID: <20141202204419.695723A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/4ef3eeb442394eb5dccf092f40dccde285f86b42/ghc >--------------------------------------------------------------- commit 4ef3eeb442394eb5dccf092f40dccde285f86b42 Author: Richard Eisenberg Date: Tue Dec 2 13:26:20 2014 -0500 Lots of bugfixing. The biggest change is the addition of topNormaliseNewTypeTF_maybe, which does exactly what is necessary in the canonicaliser. There's a little code duplication, but this is much cleaner than what I had before, which redundantly unwrapped type families, among other nastiness. >--------------------------------------------------------------- 4ef3eeb442394eb5dccf092f40dccde285f86b42 compiler/typecheck/FamInst.lhs | 73 +----------- compiler/typecheck/TcCanonical.lhs | 116 +++++++++--------- compiler/typecheck/TcErrors.lhs | 28 ++++- compiler/typecheck/TcEvidence.lhs | 138 +++++++++++++++++++++- compiler/typecheck/TcExpr.lhs | 2 +- compiler/typecheck/TcRnTypes.lhs | 9 +- testsuite/tests/deriving/should_fail/T1496.stderr | 14 +-- testsuite/tests/deriving/should_fail/T4846.stderr | 9 +- testsuite/tests/deriving/should_fail/T5498.stderr | 16 +-- testsuite/tests/deriving/should_fail/T6147.stderr | 12 +- testsuite/tests/deriving/should_fail/T7148.stderr | 36 ++---- testsuite/tests/deriving/should_fail/T8851.stderr | 22 ++-- testsuite/tests/gadt/CasePrune.stderr | 12 +- testsuite/tests/ghci/scripts/ghci051.stderr | 2 +- 14 files changed, 286 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 4ef3eeb442394eb5dccf092f40dccde285f86b42 From git at git.haskell.org Tue Dec 2 20:44:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:44:22 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: More bugfixes. The non-stat testsuite should hopefully pass now. (be19c2f) Message-ID: <20141202204422.32F093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/be19c2fa6dc3c6a52e7a28a2fcc41f07e01dc3de/ghc >--------------------------------------------------------------- commit be19c2fa6dc3c6a52e7a28a2fcc41f07e01dc3de Author: Richard Eisenberg Date: Tue Dec 2 14:56:34 2014 -0500 More bugfixes. The non-stat testsuite should hopefully pass now. >--------------------------------------------------------------- be19c2fa6dc3c6a52e7a28a2fcc41f07e01dc3de compiler/typecheck/TcFlatten.lhs | 18 ++- compiler/typecheck/TcValidity.lhs | 8 +- testsuite/tests/roles/should_fail/Roles10.stderr | 11 +- .../tests/roles/should_fail/RolesIArray.stderr | 151 ++++++++++----------- .../typecheck/should_fail/TcCoercibleFail3.stderr | 11 +- 5 files changed, 104 insertions(+), 95 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc be19c2fa6dc3c6a52e7a28a2fcc41f07e01dc3de From git at git.haskell.org Tue Dec 2 20:44:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:44:24 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Remove unnecessary generalization around IsCoercion (ee7a0a0) Message-ID: <20141202204424.EF6AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/ee7a0a07ea427a8484d87b72f63a9d1bf8164342/ghc >--------------------------------------------------------------- commit ee7a0a07ea427a8484d87b72f63a9d1bf8164342 Author: Richard Eisenberg Date: Tue Dec 2 15:12:37 2014 -0500 Remove unnecessary generalization around IsCoercion >--------------------------------------------------------------- ee7a0a07ea427a8484d87b72f63a9d1bf8164342 compiler/typecheck/TcCanonical.lhs | 0 compiler/typecheck/TcEvidence.lhs | 16 +---- compiler/types/Coercion.hs | 42 ++---------- compiler/types/FamInstEnv.hs | 132 +++++++++++++++---------------------- 4 files changed, 59 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 ee7a0a07ea427a8484d87b72f63a9d1bf8164342 From git at git.haskell.org Tue Dec 2 20:44:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 20:44:28 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Test #8984 in deriving/should_fail/T8984 (fc853b9) Message-ID: <20141202204428.3BC233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/fc853b9efaab02a61087b7b97caca8f1ada5bed7/ghc >--------------------------------------------------------------- commit fc853b9efaab02a61087b7b97caca8f1ada5bed7 Author: Richard Eisenberg Date: Tue Dec 2 15:24:27 2014 -0500 Test #8984 in deriving/should_fail/T8984 >--------------------------------------------------------------- fc853b9efaab02a61087b7b97caca8f1ada5bed7 testsuite/tests/deriving/should_fail/T8984.hs | 8 ++++++++ testsuite/tests/deriving/should_fail/T8984.stderr | 11 +++++++++++ testsuite/tests/deriving/should_fail/all.T | 1 + 3 files changed, 20 insertions(+) diff --git a/testsuite/tests/deriving/should_fail/T8984.hs b/testsuite/tests/deriving/should_fail/T8984.hs new file mode 100644 index 0000000..6b0b395 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T8984.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE ConstraintKinds, GeneralizedNewtypeDeriving #-} +module T8984 where + +class C a where + app :: a (a Int) + +newtype N cat a b = MkN (cat a b) deriving( C ) +-- The newtype coercion is N cat ~R cat diff --git a/testsuite/tests/deriving/should_fail/T8984.stderr b/testsuite/tests/deriving/should_fail/T8984.stderr new file mode 100644 index 0000000..6606d66 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T8984.stderr @@ -0,0 +1,11 @@ + +T8984.hs:7:46: + Couldn't match representation of type ?cat a (N cat a Int)? + with that of ?cat a (cat a Int)? + arising from the coercion of the method ?app? + from type ?cat a (cat a Int)? to type ?N cat a (N cat a Int)? + Relevant role signatures: + type role N representational nominal nominal + NB: We cannot know what roles the parameters to ?cat a? have; + we must assume that the role is nominal + When deriving the instance for (C (N cat a)) diff --git a/testsuite/tests/deriving/should_fail/all.T b/testsuite/tests/deriving/should_fail/all.T index 54a6f95..df7957d 100644 --- a/testsuite/tests/deriving/should_fail/all.T +++ b/testsuite/tests/deriving/should_fail/all.T @@ -53,3 +53,4 @@ test('T9071', normal, multimod_compile_fail, ['T9071','']) test('T9071_2', normal, compile_fail, ['']) test('T9687', normal, compile_fail, ['']) +test('T8984', normal, compile_fail, ['']) From git at git.haskell.org Tue Dec 2 21:36:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 21:36:11 +0000 (UTC) Subject: [commit: ghc] master: Declare official GitHub home of libraries/parallel (bf2d754) Message-ID: <20141202213611.332CE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bf2d75417b5be7e8a79a26ee57a81e00682dabd4/ghc >--------------------------------------------------------------- commit bf2d75417b5be7e8a79a26ee57a81e00682dabd4 Author: Herbert Valerio Riedel Date: Tue Dec 2 22:35:36 2014 +0100 Declare official GitHub home of libraries/parallel Effective immediately, pushing to the `libraries/parallel` submodule requires pushing via ssh://git at github.com/haskell/parallel.git. >--------------------------------------------------------------- bf2d75417b5be7e8a79a26ee57a81e00682dabd4 libraries/parallel | 2 +- packages | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/parallel b/libraries/parallel index 50a2b2a..c4863d9 160000 --- a/libraries/parallel +++ b/libraries/parallel @@ -1 +1 @@ -Subproject commit 50a2b2a622898786d623a9f933183525305058d3 +Subproject commit c4863d925c446ba5416aeed6a11012f2e978686e diff --git a/packages b/packages index 50ad970..33137d6 100644 --- a/packages +++ b/packages @@ -71,7 +71,7 @@ libraries/unix - - ssh://g libraries/Win32 - - https://github.com/haskell/win32.git libraries/xhtml - - https://github.com/haskell/xhtml.git nofib nofib - - -libraries/parallel extra - - +libraries/parallel extra - ssh://git at github.com/haskell/parallel.git libraries/stm extra - - libraries/random dph - https://github.com/haskell/random.git libraries/primitive dph - https://github.com/haskell/primitive.git From git at git.haskell.org Tue Dec 2 22:56:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 22:56:37 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate' created Message-ID: <20141202225637.685B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/validate Referencing: 1f85f3fcada2a41a2985f72a2adff9ec90da879e From git at git.haskell.org Tue Dec 2 22:56:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Dec 2014 22:56:40 +0000 (UTC) Subject: [commit: ghc] wip/validate: Make annotations test case cleaning less aggressive (1f85f3f) Message-ID: <20141202225640.0BE993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/validate Link : http://ghc.haskell.org/trac/ghc/changeset/1f85f3fcada2a41a2985f72a2adff9ec90da879e/ghc >--------------------------------------------------------------- commit 1f85f3fcada2a41a2985f72a2adff9ec90da879e Author: Joachim Breitner Date: Tue Dec 2 23:56:52 2014 +0100 Make annotations test case cleaning less aggressive cf. a4ec0c92 >--------------------------------------------------------------- 1f85f3fcada2a41a2985f72a2adff9ec90da879e testsuite/tests/ghc-api/annotations/Makefile | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/ghc-api/annotations/Makefile b/testsuite/tests/ghc-api/annotations/Makefile index d5c7bd4..821aaa0 100644 --- a/testsuite/tests/ghc-api/annotations/Makefile +++ b/testsuite/tests/ghc-api/annotations/Makefile @@ -5,15 +5,18 @@ include $(TOP)/mk/test.mk clean: rm -f *.o *.hi -annotations: clean +annotations: + rm -f annotations.o annotations.hi '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc annotations ./annotations "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" -parseTree: clean +parseTree: + rm -f parseTree.o parseTree.hi '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc parseTree ./parseTree "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" -comments: clean +comments: + rm -f comments.o comments.hi '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc comments ./comments "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" From git at git.haskell.org Wed Dec 3 02:06:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 02:06:04 +0000 (UTC) Subject: [commit: ghc] master: Generate real (but empty) object files for signatures. (46b278f) Message-ID: <20141203020604.39D373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/46b278fb75c708256e0a8cfefb8a2bce10fddef4/ghc >--------------------------------------------------------------- commit 46b278fb75c708256e0a8cfefb8a2bce10fddef4 Author: Edward Z. Yang Date: Mon Dec 1 21:07:33 2014 -0800 Generate real (but empty) object files for signatures. Summary: It's not great, but it preserves a nice invariant that every Haskell source file has an object file (we already have a hack in place ensure this is the case for hs-boot files) and further ensures every package has a library associated with it (which would not be the case if the package had all signatures and we didn't make object files.) Contains Cabal submodule update. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D548 >--------------------------------------------------------------- 46b278fb75c708256e0a8cfefb8a2bce10fddef4 compiler/main/DriverPipeline.hs | 49 ++++++++++++++++++++++++++----- compiler/main/HscMain.hs | 5 +++- compiler/main/HscTypes.lhs | 1 + docs/users_guide/separate_compilation.xml | 6 ++-- libraries/Cabal | 2 +- 5 files changed, 50 insertions(+), 13 deletions(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index eefa0a6..fdec73e 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -240,7 +240,7 @@ compileOne' m_tc_result mHscMessage _ -> case ms_hsc_src summary of - t | isHsBootOrSig t -> + HsBootFile -> do (iface, changed, details) <- hscSimpleIface hsc_env tc_result mb_old_hash hscWriteIface dflags iface changed summary touchObjectFile dflags object_filename @@ -248,7 +248,23 @@ compileOne' m_tc_result mHscMessage hm_iface = iface, hm_linkable = maybe_old_linkable }) - _ -> do guts0 <- hscDesugar hsc_env summary tc_result + HsigFile -> + do (iface, changed, details) <- + hscSimpleIface hsc_env tc_result mb_old_hash + hscWriteIface dflags iface changed summary + compileEmptyStub dflags hsc_env basename location + + -- Same as Hs + o_time <- getModificationUTCTime object_filename + let linkable = + LM o_time this_mod [DotO object_filename] + + return (HomeModInfo{ hm_details = details, + hm_iface = iface, + hm_linkable = Just linkable }) + + HsSrcFile -> + do guts0 <- hscDesugar hsc_env summary tc_result guts <- hscSimplify hsc_env guts0 (iface, changed, details, cgguts) <- hscNormalIface hsc_env guts mb_old_hash hscWriteIface dflags iface changed summary @@ -287,6 +303,21 @@ compileStub hsc_env stub_c = do return stub_o +compileEmptyStub :: DynFlags -> HscEnv -> FilePath -> ModLocation -> IO () +compileEmptyStub dflags hsc_env basename location = do + -- To maintain the invariant that every Haskell file + -- compiles to object code, we make an empty (but + -- valid) stub object file for signatures + empty_stub <- newTempName dflags "c" + writeFile empty_stub "" + _ <- runPipeline StopLn hsc_env + (empty_stub, Nothing) + (Just basename) + Persistent + (Just location) + Nothing + return () + -- --------------------------------------------------------------------------- -- Link @@ -341,11 +372,7 @@ link' dflags batch_attempt_linking hpt LinkStaticLib -> True _ -> platformBinariesAreStaticLibs (targetPlatform dflags) - -- Don't attempt to link hsigs; they don't actually produce objects. - -- This is in contrast to hs-boot files, which will /eventually/ - -- get objects. - home_mod_infos = - filter ((==Nothing).mi_sig_of.hm_iface) (eltsUFM hpt) + home_mod_infos = eltsUFM hpt -- the packages we depend on pkg_deps = concatMap (map fst . dep_pkgs . mi_deps . hm_iface) home_mod_infos @@ -981,6 +1008,14 @@ runPhase (HscOut src_flavour mod_name result) _ dflags = do -- stamp file for the benefit of Make liftIO $ touchObjectFile dflags o_file return (RealPhase next_phase, o_file) + HscUpdateSig -> + do -- We need to create a REAL but empty .o file + -- because we are going to attempt to put it in a library + PipeState{hsc_env=hsc_env'} <- getPipeState + let input_fn = expectJust "runPhase" (ml_hs_file location) + basename = dropExtension input_fn + liftIO $ compileEmptyStub dflags hsc_env' basename location + return (RealPhase next_phase, o_file) HscRecomp cgguts mod_summary -> do output_fn <- phaseOutputFilename next_phase diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index fcf0c48..8f8da02 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -647,7 +647,10 @@ hscCompileOneShot' hsc_env mod_summary src_changed t | isHsBootOrSig t -> do (iface, changed, _) <- hscSimpleIface' tc_result mb_old_hash liftIO $ hscWriteIface dflags iface changed mod_summary - return HscUpdateBoot + return (case t of + HsBootFile -> HscUpdateBoot + HsigFile -> HscUpdateSig + HsSrcFile -> panic "hscCompileOneShot Src") _ -> do guts <- hscSimplify' guts0 (iface, changed, _details, cgguts) <- hscNormalIface' guts mb_old_hash diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs index cf3db52..b6e3a98 100644 --- a/compiler/main/HscTypes.lhs +++ b/compiler/main/HscTypes.lhs @@ -195,6 +195,7 @@ data HscStatus = HscNotGeneratingCode | HscUpToDate | HscUpdateBoot + | HscUpdateSig | HscRecomp CgGuts ModSummary -- ----------------------------------------------------------------------------- diff --git a/docs/users_guide/separate_compilation.xml b/docs/users_guide/separate_compilation.xml index 43ab182..b30eff8 100644 --- a/docs/users_guide/separate_compilation.xml +++ b/docs/users_guide/separate_compilation.xml @@ -966,10 +966,8 @@ ghc -c A.hs Just like hs-boot files, when an hsig file is compiled it is checked for type - consistency against the backing implementation; furthermore, it also - produces a pseudo-object file A.o which you should - not link with. Signature files are also written in a subset - of Haskell similar to essentially identical to that of + consistency against the backing implementation. Signature files are also + written in a subset of Haskell essentially identical to that of hs-boot files. There is one important gotcha with the current implementation: diff --git a/libraries/Cabal b/libraries/Cabal index 6c395bb..ea062bf 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 6c395bb8f22961ce5267df64e6d9351c310fcbb3 +Subproject commit ea062bf522e015f6e643bcc833487098edba8398 From git at git.haskell.org Wed Dec 3 07:58:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 07:58:09 +0000 (UTC) Subject: [commit: ghc] master: Update 32-bit performace numbers (has not been done for ages) (cce292b) Message-ID: <20141203075809.F13393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cce292b2e3489a55bfaad8a78cb42f90e7254292/ghc >--------------------------------------------------------------- commit cce292b2e3489a55bfaad8a78cb42f90e7254292 Author: Simon Peyton Jones Date: Wed Dec 3 07:58:22 2014 +0000 Update 32-bit performace numbers (has not been done for ages) >--------------------------------------------------------------- cce292b2e3489a55bfaad8a78cb42f90e7254292 testsuite/tests/perf/compiler/all.T | 22 +++++++++++++++------- testsuite/tests/perf/haddock/all.T | 13 +++++++------ testsuite/tests/perf/should_run/all.T | 9 +++++++-- testsuite/tests/perf/space_leaks/all.T | 9 ++++++++- 4 files changed, 37 insertions(+), 16 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc cce292b2e3489a55bfaad8a78cb42f90e7254292 From git at git.haskell.org Wed Dec 3 08:12:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 08:12:16 +0000 (UTC) Subject: [commit: ghc] master: Make annotations test case cleaning less aggressive (289e52f) Message-ID: <20141203081216.1FBAE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/289e52f8acd4713df5a4ff5060baadf5fae4b547/ghc >--------------------------------------------------------------- commit 289e52f8acd4713df5a4ff5060baadf5fae4b547 Author: Joachim Breitner Date: Tue Dec 2 23:56:52 2014 +0100 Make annotations test case cleaning less aggressive cf. a4ec0c92 >--------------------------------------------------------------- 289e52f8acd4713df5a4ff5060baadf5fae4b547 testsuite/tests/ghc-api/annotations/Makefile | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/ghc-api/annotations/Makefile b/testsuite/tests/ghc-api/annotations/Makefile index d5c7bd4..821aaa0 100644 --- a/testsuite/tests/ghc-api/annotations/Makefile +++ b/testsuite/tests/ghc-api/annotations/Makefile @@ -5,15 +5,18 @@ include $(TOP)/mk/test.mk clean: rm -f *.o *.hi -annotations: clean +annotations: + rm -f annotations.o annotations.hi '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc annotations ./annotations "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" -parseTree: clean +parseTree: + rm -f parseTree.o parseTree.hi '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc parseTree ./parseTree "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" -comments: clean +comments: + rm -f comments.o comments.hi '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc comments ./comments "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" From git at git.haskell.org Wed Dec 3 08:19:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 08:19:38 +0000 (UTC) Subject: [commit: ghc] branch 'wip/validate' deleted Message-ID: <20141203081938.E1B4A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/validate From git at git.haskell.org Wed Dec 3 13:38:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 13:38:51 +0000 (UTC) Subject: [commit: ghc] master: Comments only (bc9e81c) Message-ID: <20141203133851.6AA8E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bc9e81cfe5aec2484833854ab0c1abfef9c11b0f/ghc >--------------------------------------------------------------- commit bc9e81cfe5aec2484833854ab0c1abfef9c11b0f Author: Simon Peyton Jones Date: Wed Dec 3 13:38:55 2014 +0000 Comments only >--------------------------------------------------------------- bc9e81cfe5aec2484833854ab0c1abfef9c11b0f compiler/typecheck/TcInteract.lhs | 4 ++-- libraries/ghc-prim/GHC/Types.hs | 12 ++++++++---- 2 files changed, 10 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index bfe470d..dcac915 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -1038,8 +1038,8 @@ outer type constructors match. Note [Delicate equality kick-out] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -When adding an work-item CTyEqCan (a ~ xi), we kick out an inert -CTyEqCan (b ~ phi) when +When adding an fully-rewritten work-item CTyEqCan (a ~ xi), we kick +out an inert CTyEqCan (b ~ phi) when a) the work item can rewrite the inert item diff --git a/libraries/ghc-prim/GHC/Types.hs b/libraries/ghc-prim/GHC/Types.hs index e9f1428..0f1d961 100644 --- a/libraries/ghc-prim/GHC/Types.hs +++ b/libraries/ghc-prim/GHC/Types.hs @@ -98,11 +98,11 @@ constraints, but we cannot define them as such in Haskell. But we also cannot just define them only in GHC.Prim (like (->)), because we need a real module for them, e.g. to compile the constructor's info table. -Furthermore the type of MkCoercible cannot be written in Haskell (no syntax for -~#R). +Furthermore the type of MkCoercible cannot be written in Haskell +(no syntax for ~#R). -So we define them as regular data types in GHC.Types, and do magic in GHC to -change the kind and type, in tysWiredIn. +So we define them as regular data types in GHC.Types, and do magic in TysWiredIn, +inside GHC, to change the kind and type. -} @@ -161,6 +161,10 @@ data (~) a b = Eq# ((~#) a b) -- -- /Since: 4.7.0.0/ data Coercible a b = MkCoercible ((~#) a b) +-- It's really ~R# (represntational equality), not ~#, +-- but * we don't yet have syntax for ~R#, +-- * the compiled code is the same either way +-- * TysWiredIn has the truthful types -- Also see Note [Kind-changing of (~) and Coercible] -- | Alias for 'tagToEnum#'. Returns True if its parameter is 1# and False From git at git.haskell.org Wed Dec 3 20:05:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 20:05:56 +0000 (UTC) Subject: [commit: ghc] master: compiler: de-lhs main/ (1389ff5) Message-ID: <20141203200556.F030F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1389ff565d9a41d21eb7e4fc6e2b23d0df08de24/ghc >--------------------------------------------------------------- commit 1389ff565d9a41d21eb7e4fc6e2b23d0df08de24 Author: Austin Seipp Date: Wed Dec 3 12:41:58 2014 -0600 compiler: de-lhs main/ Signed-off-by: Austin Seipp >--------------------------------------------------------------- 1389ff565d9a41d21eb7e4fc6e2b23d0df08de24 compiler/main/{CodeOutput.lhs => CodeOutput.hs} | 73 +++--- compiler/main/{Constants.lhs => Constants.hs} | 9 +- compiler/main/{ErrUtils.lhs => ErrUtils.hs} | 10 +- .../main/{ErrUtils.lhs-boot => ErrUtils.hs-boot} | 3 - compiler/main/{Finder.lhs => Finder.hs} | 9 +- compiler/main/{Hooks.lhs => Hooks.hs} | 19 +- compiler/main/{Hooks.lhs-boot => Hooks.hs-boot} | 4 - compiler/main/{HscTypes.lhs => HscTypes.hs} | 281 ++++++++++----------- compiler/main/{Packages.lhs => Packages.hs} | 8 +- .../main/{Packages.lhs-boot => Packages.hs-boot} | 2 - compiler/main/{SysTools.lhs => SysTools.hs} | 56 ++-- compiler/main/{TidyPgm.lhs => TidyPgm.hs} | 130 +++++----- 12 files changed, 272 insertions(+), 332 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1389ff565d9a41d21eb7e4fc6e2b23d0df08de24 From git at git.haskell.org Wed Dec 3 20:06:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 20:06:01 +0000 (UTC) Subject: [commit: ghc] master: compiler: de-lhs prelude/ (dc00fb1) Message-ID: <20141203200601.E72893A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dc00fb1b5e75fda17384af612a98a8c99f874cff/ghc >--------------------------------------------------------------- commit dc00fb1b5e75fda17384af612a98a8c99f874cff Author: Austin Seipp Date: Wed Dec 3 12:42:24 2014 -0600 compiler: de-lhs prelude/ Signed-off-by: Austin Seipp >--------------------------------------------------------------- dc00fb1b5e75fda17384af612a98a8c99f874cff .../prelude/{ForeignCall.lhs => ForeignCall.hs} | 74 +++---- compiler/prelude/{PrelInfo.lhs => PrelInfo.hs} | 74 ++++--- compiler/prelude/{PrelNames.lhs => PrelNames.hs} | 182 ++++++++--------- .../{PrelNames.lhs-boot => PrelNames.hs-boot} | 3 - compiler/prelude/{PrelRules.lhs => PrelRules.hs} | 84 ++++---- compiler/prelude/{PrimOp.lhs => PrimOp.hs} | 173 +++++++--------- .../prelude/{PrimOp.lhs-boot => PrimOp.hs-boot} | 4 - compiler/prelude/{TysPrim.lhs => TysPrim.hs} | 225 ++++++++++----------- compiler/prelude/{TysWiredIn.lhs => TysWiredIn.hs} | 146 ++++++------- .../{TysWiredIn.lhs-boot => TysWiredIn.hs-boot} | 2 - 10 files changed, 430 insertions(+), 537 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc dc00fb1b5e75fda17384af612a98a8c99f874cff From git at git.haskell.org Wed Dec 3 20:06:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 20:06:06 +0000 (UTC) Subject: [commit: ghc] master: compiler: de-lhs rename/ (9fc4382) Message-ID: <20141203200606.93D513A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9fc4382ced4357b03b169c36934d7acd3ac4dd59/ghc >--------------------------------------------------------------- commit 9fc4382ced4357b03b169c36934d7acd3ac4dd59 Author: Austin Seipp Date: Wed Dec 3 12:42:50 2014 -0600 compiler: de-lhs rename/ Signed-off-by: Austin Seipp >--------------------------------------------------------------- 9fc4382ced4357b03b169c36934d7acd3ac4dd59 compiler/rename/{RnBinds.lhs => RnBinds.hs} | 126 ++++++------ compiler/rename/{RnEnv.lhs => RnEnv.hs} | 165 +++++++-------- compiler/rename/{RnExpr.lhs => RnExpr.hs} | 119 ++++++----- .../rename/{RnExpr.lhs-boot => RnExpr.hs-boot} | 3 - compiler/rename/{RnNames.lhs => RnNames.hs} | 127 ++++++------ compiler/rename/{RnPat.lhs => RnPat.hs} | 97 +++++---- compiler/rename/{RnSource.lhs => RnSource.hs} | 223 ++++++++++----------- compiler/rename/{RnSplice.lhs => RnSplice.hs} | 43 ++-- .../rename/{RnSplice.lhs-boot => RnSplice.hs-boot} | 2 - compiler/rename/{RnTypes.lhs => RnTypes.hs} | 82 ++++---- 10 files changed, 455 insertions(+), 532 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9fc4382ced4357b03b169c36934d7acd3ac4dd59 From git at git.haskell.org Wed Dec 3 20:06:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 20:06:11 +0000 (UTC) Subject: [commit: ghc] master: compiler: de-lhs coreSyn/ (b04296d) Message-ID: <20141203200611.21B713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b04296d3a3a256067787241a7727877e35e5af03/ghc >--------------------------------------------------------------- commit b04296d3a3a256067787241a7727877e35e5af03 Author: Austin Seipp Date: Wed Dec 3 12:43:05 2014 -0600 compiler: de-lhs coreSyn/ Signed-off-by: Austin Seipp >--------------------------------------------------------------- b04296d3a3a256067787241a7727877e35e5af03 compiler/coreSyn/{CoreArity.lhs => CoreArity.hs} | 57 +++--- compiler/coreSyn/{CoreFVs.lhs => CoreFVs.hs} | 86 ++++---- compiler/coreSyn/{CoreLint.lhs => CoreLint.hs} | 169 +++++++--------- compiler/coreSyn/{CorePrep.lhs => CorePrep.hs} | 87 ++++----- compiler/coreSyn/{CoreSubst.lhs => CoreSubst.hs} | 126 ++++++------ compiler/coreSyn/{CoreSyn.lhs => CoreSyn.hs} | 189 ++++++++---------- compiler/coreSyn/{CoreTidy.lhs => CoreTidy.hs} | 42 ++-- compiler/coreSyn/{CoreUnfold.lhs => CoreUnfold.hs} | 100 +++++----- compiler/coreSyn/{CoreUtils.lhs => CoreUtils.hs} | 216 +++++++++------------ compiler/coreSyn/{MkCore.lhs => MkCore.hs} | 134 ++++++------- compiler/coreSyn/{PprCore.lhs => PprCore.hs} | 67 +++---- compiler/coreSyn/{TrieMap.lhs => TrieMap.hs} | 115 +++++------ 12 files changed, 617 insertions(+), 771 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b04296d3a3a256067787241a7727877e35e5af03 From git at git.haskell.org Wed Dec 3 20:06:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 20:06:14 +0000 (UTC) Subject: [commit: ghc] master: compiler: de-lhs utils/ (0c48e17) Message-ID: <20141203200614.2E87C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0c48e172836d6a1e281aed63e42d60063700e6d8/ghc >--------------------------------------------------------------- commit 0c48e172836d6a1e281aed63e42d60063700e6d8 Author: Austin Seipp Date: Wed Dec 3 12:44:03 2014 -0600 compiler: de-lhs utils/ Signed-off-by: Austin Seipp >--------------------------------------------------------------- 0c48e172836d6a1e281aed63e42d60063700e6d8 compiler/utils/{Bag.lhs => Bag.hs} | 17 +- compiler/utils/{Digraph.lhs => Digraph.hs} | 186 +++++++++--------- compiler/utils/{FastBool.lhs => FastBool.hs} | 10 +- .../utils/{FastFunctions.lhs => FastFunctions.hs} | 9 +- compiler/utils/{FastMutInt.lhs => FastMutInt.hs} | 5 - compiler/utils/{FastString.lhs => FastString.hs} | 7 +- compiler/utils/{FastTypes.lhs => FastTypes.hs} | 10 +- compiler/utils/{FiniteMap.lhs => FiniteMap.hs} | 5 +- compiler/utils/{ListSetOps.lhs => ListSetOps.hs} | 65 +++---- compiler/utils/{Maybes.lhs => Maybes.hs} | 49 +++-- compiler/utils/{OrdList.lhs => OrdList.hs} | 11 +- compiler/utils/{Outputable.lhs => Outputable.hs} | 124 ++++++------ .../{Outputable.lhs-boot => Outputable.hs-boot} | 4 - compiler/utils/{Pair.lhs => Pair.hs} | 5 +- compiler/utils/{Panic.lhs => Panic.hs} | 12 +- compiler/utils/{Pretty.lhs => Pretty.hs} | 207 +++++++++----------- .../utils/{StringBuffer.lhs => StringBuffer.hs} | 12 +- compiler/utils/{UniqFM.lhs => UniqFM.hs} | 61 +++--- compiler/utils/{UniqSet.lhs => UniqSet.hs} | 38 ++-- compiler/utils/{Util.lhs => Util.hs} | 208 +++++++++------------ 20 files changed, 442 insertions(+), 603 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0c48e172836d6a1e281aed63e42d60063700e6d8 From git at git.haskell.org Wed Dec 3 20:06:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 20:06:18 +0000 (UTC) Subject: [commit: ghc] master: compiler: de-lhs iface/ (10fdf27) Message-ID: <20141203200618.9BFCA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/10fdf27951dcf4065d749c2916cf91d3ce53a252/ghc >--------------------------------------------------------------- commit 10fdf27951dcf4065d749c2916cf91d3ce53a252 Author: Austin Seipp Date: Wed Dec 3 12:44:13 2014 -0600 compiler: de-lhs iface/ Signed-off-by: Austin Seipp >--------------------------------------------------------------- 10fdf27951dcf4065d749c2916cf91d3ce53a252 compiler/iface/{BuildTyCl.lhs => BuildTyCl.hs} | 19 +- compiler/iface/{IfaceEnv.lhs => IfaceEnv.hs} | 60 +++--- compiler/iface/{IfaceSyn.lhs => IfaceSyn.hs} | 94 +++++---- compiler/iface/{IfaceType.lhs => IfaceType.hs} | 102 +++++----- compiler/iface/{LoadIface.lhs => LoadIface.hs} | 130 ++++++------- compiler/iface/{MkIface.lhs => MkIface.hs} | 84 ++++---- compiler/iface/{TcIface.lhs => TcIface.hs} | 214 ++++++++++----------- .../iface/{TcIface.lhs-boot => TcIface.hs-boot} | 3 - 8 files changed, 315 insertions(+), 391 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 10fdf27951dcf4065d749c2916cf91d3ce53a252 From git at git.haskell.org Wed Dec 3 20:06:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 20:06:22 +0000 (UTC) Subject: [commit: ghc] master: compiler: de-lhs specialise/ (29a5210) Message-ID: <20141203200622.7EFA63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/29a52104776395a5bc802c6ca0b7971795576d46/ghc >--------------------------------------------------------------- commit 29a52104776395a5bc802c6ca0b7971795576d46 Author: Austin Seipp Date: Wed Dec 3 12:44:25 2014 -0600 compiler: de-lhs specialise/ Signed-off-by: Austin Seipp >--------------------------------------------------------------- 29a52104776395a5bc802c6ca0b7971795576d46 compiler/specialise/{Rules.lhs => Rules.hs} | 95 ++++++++++----------- .../specialise/{SpecConstr.lhs => SpecConstr.hs} | 96 ++++++++++----------- .../specialise/{Specialise.lhs => Specialise.hs} | 99 ++++++++++------------ 3 files changed, 136 insertions(+), 154 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 29a52104776395a5bc802c6ca0b7971795576d46 From git at git.haskell.org Wed Dec 3 20:06:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 20:06:26 +0000 (UTC) Subject: [commit: ghc] master: compiler: de-lhs simplCore/ (6ecd27e) Message-ID: <20141203200626.C58963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6ecd27eae6f3a6f3ec3e1a6a66cad09b4eb332be/ghc >--------------------------------------------------------------- commit 6ecd27eae6f3a6f3ec3e1a6a66cad09b4eb332be Author: Austin Seipp Date: Wed Dec 3 12:45:25 2014 -0600 compiler: de-lhs simplCore/ Signed-off-by: Austin Seipp >--------------------------------------------------------------- 6ecd27eae6f3a6f3ec3e1a6a66cad09b4eb332be compiler/simplCore/{CSE.lhs => CSE.hs} | 35 ++-- compiler/simplCore/{CoreMonad.lhs => CoreMonad.hs} | 186 ++++++++------------ compiler/simplCore/{FloatIn.lhs => FloatIn.hs} | 75 ++++---- compiler/simplCore/{FloatOut.lhs => FloatOut.hs} | 69 ++++---- .../{LiberateCase.lhs => LiberateCase.hs} | 71 ++++---- compiler/simplCore/{OccurAnal.lhs => OccurAnal.hs} | 130 +++++++------- compiler/simplCore/{SAT.lhs => SAT.hs} | 43 ++--- compiler/simplCore/{SetLevels.lhs => SetLevels.hs} | 109 ++++++------ compiler/simplCore/{SimplCore.lhs => SimplCore.hs} | 101 +++++------ compiler/simplCore/{SimplEnv.lhs => SimplEnv.hs} | 108 +++++------- .../simplCore/{SimplMonad.lhs => SimplMonad.hs} | 49 +++--- .../simplCore/{SimplUtils.lhs => SimplUtils.hs} | 148 ++++++++-------- compiler/simplCore/{Simplify.lhs => Simplify.hs} | 193 ++++++++++----------- 13 files changed, 598 insertions(+), 719 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6ecd27eae6f3a6f3ec3e1a6a66cad09b4eb332be From git at git.haskell.org Wed Dec 3 20:06:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 20:06:31 +0000 (UTC) Subject: [commit: ghc] master: compiler: de-lhs hsSyn/ (b9b1fab) Message-ID: <20141203200631.777C93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b9b1fab36a3df98bf3796df3090e4d5d8d592f7e/ghc >--------------------------------------------------------------- commit b9b1fab36a3df98bf3796df3090e4d5d8d592f7e Author: Austin Seipp Date: Wed Dec 3 12:45:05 2014 -0600 compiler: de-lhs hsSyn/ Signed-off-by: Austin Seipp >--------------------------------------------------------------- b9b1fab36a3df98bf3796df3090e4d5d8d592f7e compiler/hsSyn/{Convert.lhs => Convert.hs} | 13 +- compiler/hsSyn/{HsBinds.lhs => HsBinds.hs} | 76 ++++---- compiler/hsSyn/{HsDecls.lhs => HsDecls.hs} | 200 +++++++++------------ compiler/hsSyn/{HsExpr.lhs => HsExpr.hs} | 158 +++++++--------- compiler/hsSyn/{HsExpr.lhs-boot => HsExpr.hs-boot} | 2 - compiler/hsSyn/{HsImpExp.lhs => HsImpExp.hs} | 43 ++--- compiler/hsSyn/{HsLit.lhs => HsLit.hs} | 34 ++-- compiler/hsSyn/{HsPat.lhs => HsPat.hs} | 67 ++++--- compiler/hsSyn/{HsPat.lhs-boot => HsPat.hs-boot} | 2 - compiler/hsSyn/{HsSyn.lhs => HsSyn.hs} | 16 +- compiler/hsSyn/{HsTypes.lhs => HsTypes.hs} | 76 ++++---- compiler/hsSyn/{HsUtils.lhs => HsUtils.hs} | 97 +++++----- 12 files changed, 340 insertions(+), 444 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b9b1fab36a3df98bf3796df3090e4d5d8d592f7e From git at git.haskell.org Wed Dec 3 20:06:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 20:06:34 +0000 (UTC) Subject: [commit: ghc] master: compiler: de-lhs basicTypes/ (a56fe4a) Message-ID: <20141203200634.51C263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a56fe4a188dfb284a7d742180963b8dd914cbb5a/ghc >--------------------------------------------------------------- commit a56fe4a188dfb284a7d742180963b8dd914cbb5a Author: Austin Seipp Date: Wed Dec 3 12:44:39 2014 -0600 compiler: de-lhs basicTypes/ Signed-off-by: Austin Seipp >--------------------------------------------------------------- a56fe4a188dfb284a7d742180963b8dd914cbb5a .../basicTypes/{BasicTypes.lhs => BasicTypes.hs} | 295 ++++++++++----------- compiler/basicTypes/{ConLike.lhs => ConLike.hs} | 36 ++- compiler/basicTypes/{DataCon.lhs => DataCon.hs} | 104 ++++---- .../{DataCon.lhs-boot => DataCon.hs-boot} | 2 - compiler/basicTypes/{Demand.lhs => Demand.hs} | 158 +++++------ compiler/basicTypes/{Id.lhs => Id.hs} | 98 ++++--- compiler/basicTypes/{IdInfo.lhs => IdInfo.hs} | 134 +++++----- .../basicTypes/{IdInfo.lhs-boot => IdInfo.hs-boot} | 2 - compiler/basicTypes/{Literal.lhs => Literal.hs} | 74 +++--- compiler/basicTypes/{MkId.lhs => MkId.hs} | 128 ++++----- .../basicTypes/{MkId.lhs-boot => MkId.hs-boot} | 4 - compiler/basicTypes/{Module.lhs => Module.hs} | 81 +++--- .../basicTypes/{Module.lhs-boot => Module.hs-boot} | 2 - compiler/basicTypes/{Name.lhs => Name.hs} | 122 ++++----- .../basicTypes/{Name.lhs-boot => Name.hs-boot} | 2 - compiler/basicTypes/{NameEnv.lhs => NameEnv.hs} | 36 ++- compiler/basicTypes/{NameSet.lhs => NameSet.hs} | 48 ++-- compiler/basicTypes/{OccName.lhs => OccName.hs} | 158 +++++------ .../{OccName.lhs-boot => OccName.hs-boot} | 2 - compiler/basicTypes/{PatSyn.lhs => PatSyn.hs} | 51 ++-- .../basicTypes/{PatSyn.lhs-boot => PatSyn.hs-boot} | 2 - compiler/basicTypes/{RdrName.lhs => RdrName.hs} | 104 ++++---- compiler/basicTypes/{SrcLoc.lhs => SrcLoc.hs} | 134 +++++----- .../basicTypes/{UniqSupply.lhs => UniqSupply.hs} | 48 ++-- compiler/basicTypes/{Unique.lhs => Unique.hs} | 87 +++--- compiler/basicTypes/{Var.lhs => Var.hs} | 83 +++--- compiler/basicTypes/{VarEnv.lhs => VarEnv.hs} | 68 +++-- compiler/basicTypes/{VarSet.lhs => VarSet.hs} | 27 +- 28 files changed, 936 insertions(+), 1154 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a56fe4a188dfb284a7d742180963b8dd914cbb5a From git at git.haskell.org Wed Dec 3 20:06:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 20:06:38 +0000 (UTC) Subject: [commit: ghc] master: compiler: de-lhs stgSyn/ (612e573) Message-ID: <20141203200638.0F3EA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/612e5736077549f56ed4a5048ce7d55d0a2fed8b/ghc >--------------------------------------------------------------- commit 612e5736077549f56ed4a5048ce7d55d0a2fed8b Author: Austin Seipp Date: Wed Dec 3 12:45:40 2014 -0600 compiler: de-lhs stgSyn/ Signed-off-by: Austin Seipp >--------------------------------------------------------------- 612e5736077549f56ed4a5048ce7d55d0a2fed8b compiler/stgSyn/{CoreToStg.lhs => CoreToStg.hs} | 2 - compiler/stgSyn/{StgLint.lhs => StgLint.hs} | 55 ++---- compiler/stgSyn/{StgSyn.lhs => StgSyn.hs} | 228 ++++++++++++------------ 3 files changed, 133 insertions(+), 152 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 612e5736077549f56ed4a5048ce7d55d0a2fed8b From git at git.haskell.org Wed Dec 3 20:06:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 20:06:41 +0000 (UTC) Subject: [commit: ghc] master: compiler: de-lhs simplStg/ (bafba11) Message-ID: <20141203200641.202453A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bafba119387cdba1a84a45b6a4fe616792c94271/ghc >--------------------------------------------------------------- commit bafba119387cdba1a84a45b6a4fe616792c94271 Author: Austin Seipp Date: Wed Dec 3 12:45:58 2014 -0600 compiler: de-lhs simplStg/ Signed-off-by: Austin Seipp >--------------------------------------------------------------- bafba119387cdba1a84a45b6a4fe616792c94271 compiler/simplStg/{SimplStg.lhs => SimplStg.hs} | 11 ++--- compiler/simplStg/{StgStats.lhs => StgStats.hs} | 50 ++++++++++------------ .../simplStg/{UnariseStg.lhs => UnariseStg.hs} | 9 ++-- 3 files changed, 30 insertions(+), 40 deletions(-) diff --git a/compiler/simplStg/SimplStg.lhs b/compiler/simplStg/SimplStg.hs similarity index 96% rename from compiler/simplStg/SimplStg.lhs rename to compiler/simplStg/SimplStg.hs index 4d33e33..b8804a4 100644 --- a/compiler/simplStg/SimplStg.lhs +++ b/compiler/simplStg/SimplStg.hs @@ -1,9 +1,9 @@ -% -% (c) The GRASP/AQUA Project, Glasgow University, 1993-1998 -% +{- +(c) The GRASP/AQUA Project, Glasgow University, 1993-1998 + \section[SimplStg]{Driver for simplifying @STG@ programs} +-} -\begin{code} {-# LANGUAGE CPP #-} module SimplStg ( stg2stg ) where @@ -25,9 +25,7 @@ import SrcLoc import UniqSupply ( mkSplitUniqSupply, splitUniqSupply ) import Outputable import Control.Monad -\end{code} -\begin{code} stg2stg :: DynFlags -- includes spec of what stg-to-stg passes to do -> Module -- module name (profiling only) -> [StgBinding] -- input... @@ -89,4 +87,3 @@ stg2stg dflags module_name binds -- UniqueSupply for the next guy to use -- cost-centres to be declared/registered (specialised) -- add to description of what's happened (reverse order) -\end{code} diff --git a/compiler/simplStg/StgStats.lhs b/compiler/simplStg/StgStats.hs similarity index 79% rename from compiler/simplStg/StgStats.lhs rename to compiler/simplStg/StgStats.hs index 2a77675..4823bae 100644 --- a/compiler/simplStg/StgStats.lhs +++ b/compiler/simplStg/StgStats.hs @@ -1,6 +1,6 @@ -% -% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 -% +{- +(c) The GRASP/AQUA Project, Glasgow University, 1992-1998 + \section[StgStats]{Gathers statistical information about programs} @@ -19,8 +19,8 @@ The program gather statistics about %\item number of top-level CAFs \item number of constructors \end{enumerate} +-} -\begin{code} {-# LANGUAGE CPP #-} module StgStats ( showStgStats ) where @@ -34,9 +34,7 @@ import Panic import Data.Map (Map) import qualified Data.Map as Map -\end{code} -\begin{code} data CounterType = Literals | Applications @@ -53,9 +51,7 @@ data CounterType type Count = Int type StatEnv = Map CounterType Count -\end{code} -\begin{code} emptySE :: StatEnv emptySE = Map.empty @@ -70,15 +66,15 @@ countOne c = Map.singleton c 1 countN :: CounterType -> Int -> StatEnv countN = Map.singleton -\end{code} -%************************************************************************ -%* * +{- +************************************************************************ +* * \subsection{Top-level list of bindings (a ``program'')} -%* * -%************************************************************************ +* * +************************************************************************ +-} -\begin{code} showStgStats :: [StgBinding] -> String showStgStats prog @@ -107,15 +103,15 @@ gatherStgStats :: [StgBinding] -> StatEnv gatherStgStats binds = combineSEs (map (statBinding True{-top-level-}) binds) -\end{code} -%************************************************************************ -%* * +{- +************************************************************************ +* * \subsection{Bindings} -%* * -%************************************************************************ +* * +************************************************************************ +-} -\begin{code} statBinding :: Bool -- True <=> top-level; False <=> nested -> StgBinding -> StatEnv @@ -140,15 +136,15 @@ statRhs top (_, StgRhsClosure _ _ fv u _ _ body) Updatable -> UpdatableBinds top SingleEntry -> SingleEntryBinds top ) -\end{code} -%************************************************************************ -%* * +{- +************************************************************************ +* * \subsection{Expressions} -%* * -%************************************************************************ +* * +************************************************************************ +-} -\begin{code} statExpr :: StgExpr -> StatEnv statExpr (StgApp _ _) = countOne Applications @@ -176,5 +172,3 @@ statExpr (StgCase expr _ _ _ _ _ alts) = combineSEs (map statExpr [ e | (_,_,_,e) <- alts ]) statExpr (StgLam {}) = panic "statExpr StgLam" -\end{code} - diff --git a/compiler/simplStg/UnariseStg.lhs b/compiler/simplStg/UnariseStg.hs similarity index 93% rename from compiler/simplStg/UnariseStg.lhs rename to compiler/simplStg/UnariseStg.hs index 1f121f7..303bfa7 100644 --- a/compiler/simplStg/UnariseStg.lhs +++ b/compiler/simplStg/UnariseStg.hs @@ -1,6 +1,6 @@ -% -% (c) The GRASP/AQUA Project, Glasgow University, 1992-2012 -% +{- +(c) The GRASP/AQUA Project, Glasgow University, 1992-2012 + Note [Unarisation] ~~~~~~~~~~~~~~~~~~ @@ -25,8 +25,8 @@ Because of unarisation, the arity that will be recorded in the generated info ta for an Id may be larger than the idArity. Instead we record what we call the RepArity, which is the Arity taking into account any expanded arguments, and corresponds to the number of (possibly-void) *registers* arguments will arrive in. +-} -\begin{code} {-# LANGUAGE CPP #-} module UnariseStg (unarise) where @@ -220,4 +220,3 @@ unboxedTupleBindersFrom us x tys = zipWith (mkSysLocal fs) (uniqsFromSupply us) concatMapVarSet :: (Var -> [Var]) -> VarSet -> VarSet concatMapVarSet f xs = mkVarSet [x' | x <- varSetElems xs, x' <- f x] -\end{code} \ No newline at end of file From git at git.haskell.org Wed Dec 3 20:06:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 20:06:44 +0000 (UTC) Subject: [commit: ghc] master: compiler: de-lhs typecheck/ (b57ff27) Message-ID: <20141203200644.485343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b57ff272257bba8945b4c9409585b6a1d3bed21b/ghc >--------------------------------------------------------------- commit b57ff272257bba8945b4c9409585b6a1d3bed21b Author: Austin Seipp Date: Wed Dec 3 12:46:17 2014 -0600 compiler: de-lhs typecheck/ Signed-off-by: Austin Seipp >--------------------------------------------------------------- b57ff272257bba8945b4c9409585b6a1d3bed21b compiler/typecheck/{FamInst.lhs => FamInst.hs} | 67 +++--- compiler/typecheck/{FunDeps.lhs => FunDeps.hs} | 63 +++--- compiler/typecheck/{Inst.lhs => Inst.hs} | 116 +++++----- .../{TcAnnotations.lhs => TcAnnotations.hs} | 14 +- compiler/typecheck/{TcArrows.lhs => TcArrows.hs} | 76 +++---- compiler/typecheck/{TcBinds.lhs => TcBinds.hs} | 76 +++---- .../typecheck/{TcCanonical.lhs => TcCanonical.hs} | 91 ++++---- .../typecheck/{TcClassDcl.lhs => TcClassDcl.hs} | 51 ++--- .../typecheck/{TcDefaults.lhs => TcDefaults.hs} | 14 +- compiler/typecheck/{TcDeriv.lhs => TcDeriv.hs} | 132 ++++++----- compiler/typecheck/{TcEnv.lhs => TcEnv.hs} | 134 +++++------ compiler/typecheck/TcEnv.hs-boot | 6 + compiler/typecheck/TcEnv.lhs-boot | 4 - compiler/typecheck/{TcErrors.lhs => TcErrors.hs} | 73 +++--- .../typecheck/{TcEvidence.lhs => TcEvidence.hs} | 68 ++---- compiler/typecheck/{TcExpr.lhs => TcExpr.hs} | 200 ++++++++--------- .../typecheck/{TcExpr.lhs-boot => TcExpr.hs-boot} | 2 - compiler/typecheck/{TcFlatten.lhs => TcFlatten.hs} | 86 ++++--- compiler/typecheck/{TcForeign.lhs => TcForeign.hs} | 75 +++---- .../typecheck/{TcGenDeriv.lhs => TcGenDeriv.hs} | 231 +++++++++---------- .../{TcGenGenerics.lhs => TcGenGenerics.hs} | 47 ++-- compiler/typecheck/{TcHsSyn.lhs => TcHsSyn.hs} | 121 +++++----- compiler/typecheck/{TcHsType.lhs => TcHsType.hs} | 115 +++++----- .../typecheck/{TcInstDcls.lhs => TcInstDcls.hs} | 86 ++++--- .../typecheck/{TcInteract.lhs => TcInteract.hs} | 62 +++-- compiler/typecheck/{TcMType.lhs => TcMType.hs} | 180 +++++++-------- compiler/typecheck/{TcMatches.lhs => TcMatches.hs} | 86 ++++--- .../{TcMatches.lhs-boot => TcMatches.hs-boot} | 2 - compiler/typecheck/{TcPat.lhs => TcPat.hs} | 86 ++++--- compiler/typecheck/{TcPatSyn.lhs => TcPatSyn.hs} | 63 +++--- .../{TcPatSyn.lhs-boot => TcPatSyn.hs-boot} | 2 - .../typecheck/{TcRnDriver.lhs => TcRnDriver.hs} | 176 +++++++-------- compiler/typecheck/{TcRnMonad.lhs => TcRnMonad.hs} | 250 +++++++++------------ compiler/typecheck/{TcRnTypes.lhs => TcRnTypes.hs} | 244 +++++++++----------- compiler/typecheck/{TcRules.lhs => TcRules.hs} | 16 +- compiler/typecheck/{TcSMonad.lhs => TcSMonad.hs} | 120 ++++------ .../typecheck/{TcSimplify.lhs => TcSimplify.hs} | 60 ++--- compiler/typecheck/{TcSplice.lhs => TcSplice.hs} | 167 +++++++------- .../{TcSplice.lhs-boot => TcSplice.hs-boot} | 2 - .../{TcTyClsDecls.lhs => TcTyClsDecls.hs} | 140 ++++++------ compiler/typecheck/{TcTyDecls.lhs => TcTyDecls.hs} | 80 +++---- compiler/typecheck/{TcType.lhs => TcType.hs} | 205 ++++++++--------- .../typecheck/{TcType.lhs-boot => TcType.hs-boot} | 2 - compiler/typecheck/{TcUnify.lhs => TcUnify.hs} | 113 +++++----- .../{TcUnify.lhs-boot => TcUnify.hs-boot} | 2 - .../typecheck/{TcValidity.lhs => TcValidity.hs} | 126 +++++------ 46 files changed, 1866 insertions(+), 2266 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b57ff272257bba8945b4c9409585b6a1d3bed21b From git at git.haskell.org Wed Dec 3 20:06:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Dec 2014 20:06:47 +0000 (UTC) Subject: [commit: ghc] master: compiler: de-lhs deSugar/ (4d5f83a) Message-ID: <20141203200647.1348B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4d5f83a8dcf1f1125863a8fb4f847d78766f1617/ghc >--------------------------------------------------------------- commit 4d5f83a8dcf1f1125863a8fb4f847d78766f1617 Author: Austin Seipp Date: Wed Dec 3 12:46:28 2014 -0600 compiler: de-lhs deSugar/ Signed-off-by: Austin Seipp >--------------------------------------------------------------- 4d5f83a8dcf1f1125863a8fb4f847d78766f1617 compiler/deSugar/{Check.lhs => Check.hs} | 74 +++++++------- compiler/deSugar/{Coverage.lhs => Coverage.hs} | 48 ++++----- compiler/deSugar/{Desugar.lhs => Desugar.hs} | 75 +++++++-------- compiler/deSugar/{DsArrows.lhs => DsArrows.hs} | 74 ++++++-------- compiler/deSugar/{DsBinds.lhs => DsBinds.hs} | 62 ++++++------ compiler/deSugar/{DsCCall.lhs => DsCCall.hs} | 20 ++-- compiler/deSugar/{DsExpr.lhs => DsExpr.hs} | 93 ++++++++---------- .../deSugar/{DsExpr.lhs-boot => DsExpr.hs-boot} | 2 - compiler/deSugar/{DsForeign.lhs => DsForeign.hs} | 83 ++++++++-------- compiler/deSugar/{DsGRHSs.lhs => DsGRHSs.hs} | 36 ++++--- compiler/deSugar/{DsListComp.lhs => DsListComp.hs} | 73 ++++++-------- compiler/deSugar/{DsMonad.lhs => DsMonad.hs} | 63 +++++------- .../deSugar/{DsMonad.lhs-boot => DsMonad.hs-boot} | 5 +- compiler/deSugar/{DsUtils.lhs => DsUtils.hs} | 94 +++++++++--------- compiler/deSugar/{Match.lhs => Match.hs} | 107 ++++++++++----------- compiler/deSugar/{Match.lhs-boot => Match.hs-boot} | 2 - compiler/deSugar/{MatchCon.lhs => MatchCon.hs} | 19 ++-- compiler/deSugar/{MatchLit.lhs => MatchLit.hs} | 93 +++++++++--------- 18 files changed, 453 insertions(+), 570 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4d5f83a8dcf1f1125863a8fb4f847d78766f1617 From git at git.haskell.org Thu Dec 4 08:24:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Dec 2014 08:24:47 +0000 (UTC) Subject: [commit: ghc] master: Comments on TrieMap and unifier. (cc071ec) Message-ID: <20141204082447.442883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cc071ecfab52396e7ecf54eb69abef57c3a63626/ghc >--------------------------------------------------------------- commit cc071ecfab52396e7ecf54eb69abef57c3a63626 Author: Edward Z. Yang Date: Thu Dec 4 00:23:57 2014 -0800 Comments on TrieMap and unifier. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- cc071ecfab52396e7ecf54eb69abef57c3a63626 compiler/coreSyn/TrieMap.hs | 7 +++++++ compiler/types/Unify.hs | 15 ++++++++++++++- 2 files changed, 21 insertions(+), 1 deletion(-) diff --git a/compiler/coreSyn/TrieMap.hs b/compiler/coreSyn/TrieMap.hs index 57f360e..aa9172b 100644 --- a/compiler/coreSyn/TrieMap.hs +++ b/compiler/coreSyn/TrieMap.hs @@ -784,6 +784,13 @@ lookupCME :: CmEnv -> Var -> Maybe BoundVar lookupCME (CME { cme_env = env }) v = lookupVarEnv env v --------- Variable binders ------------- + +-- | A 'BndrMap' is a 'TypeMap' which allows us to distinguish between +-- binding forms whose binders have different types. For example, +-- if we are doing a 'TrieMap' lookup on @\(x :: Int) -> ()@, we should +-- not pick up an entry in the 'TrieMap' for @\(x :: Bool) -> ()@: +-- we can disambiguate this by matching on the type (or kind, if this +-- a binder in a type) of the binder. type BndrMap = TypeMap lkBndr :: CmEnv -> Var -> BndrMap a -> Maybe a diff --git a/compiler/types/Unify.hs b/compiler/types/Unify.hs index 82fdad5..02d3792 100644 --- a/compiler/types/Unify.hs +++ b/compiler/types/Unify.hs @@ -87,7 +87,7 @@ tcMatchTy tmpls ty1 ty2 menv = ME { me_tmpls = tmpls, me_env = mkRnEnv2 in_scope } in_scope = mkInScopeSet (tmpls `unionVarSet` tyVarsOfType ty2) -- We're assuming that all the interesting - -- tyvars in tys1 are in tmpls + -- tyvars in ty1 are in tmpls tcMatchTys :: TyVarSet -- Template tyvars -> [Type] -- Template @@ -139,6 +139,15 @@ ruleMatchTyX menv subst ty1 ty2 = match menv subst ty1 ty2 -- Rename for ex -- Now the internals of matching +-- | Workhorse matching function. Our goal is to find a substitution +-- on all of the template variables (specified by @me_tmpls menv@) such +-- that @ty1@ and @ty2@ unify. This substitution is accumulated in @subst at . +-- If a variable is not a template variable, we don't attempt to find a +-- substitution for it; it must match exactly on both sides. Furthermore, +-- only @ty1@ can have template variables. +-- +-- This function handles binders, see 'RnEnv2' for more details on +-- how that works. match :: MatchEnv -- For the most part this is pushed downwards -> TvSubstEnv -- Substitution so far: -- Domain is subset of template tyvars @@ -160,6 +169,10 @@ match menv subst (TyVarTy tv1) ty2 | tv1' `elemVarSet` me_tmpls menv = if any (inRnEnvR rn_env) (varSetElems (tyVarsOfType ty2)) then Nothing -- Occurs check + -- ezyang: Is this really an occurs check? It seems + -- to just reject matching \x. A against \x. x (maintaining + -- the invariant that the free vars of the range of @subst@ + -- are a subset of the in-scope set in @me_env menv at .) else do { subst1 <- match_kind menv subst (tyVarKind tv1) (typeKind ty2) -- Note [Matching kinds] ; return (extendVarEnv subst1 tv1' ty2) } From git at git.haskell.org Thu Dec 4 13:41:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Dec 2014 13:41:35 +0000 (UTC) Subject: [commit: ghc] master: Prevent solveFlatWanteds from losing insolubles when using typechecker plugins (d6f9276) Message-ID: <20141204134135.A42603A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d6f92769a89c29a05127cdf5f19dee56fc65dc40/ghc >--------------------------------------------------------------- commit d6f92769a89c29a05127cdf5f19dee56fc65dc40 Author: Adam Gundry Date: Thu Dec 4 13:31:08 2014 +0000 Prevent solveFlatWanteds from losing insolubles when using typechecker plugins Summary: I've added a Note explaining the problem. Test Plan: validate; we don't have a very good story for testing plugins yet, but I've verified that this does at least fix the bug in my plugin. Reviewers: simonpj, austin Reviewed By: austin Subscribers: carter, thomie, gridaphobe, yav Differential Revision: https://phabricator.haskell.org/D552 >--------------------------------------------------------------- d6f92769a89c29a05127cdf5f19dee56fc65dc40 compiler/typecheck/TcInteract.hs | 47 +++++++++++++++++++++++++++------------- 1 file changed, 32 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index ed686da..a9ed64a 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -110,6 +110,19 @@ to float. This means that [w] xxx[1] ~ s [W] forall[2] . (xxx[1] ~ Empty) => Intersect (BuriedUnder sub k Empty) inv ~ Empty + +Note [Running plugins on unflattened wanteds] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +There is an annoying mismatch between solveFlatGivens and +solveFlatWanteds, because the latter needs to fiddle with the inert +set, unflatten and and zonk the wanteds. It passes the zonked wanteds +to runTcPluginsWanteds, which produces a replacement set of wanteds, +some additional insolubles and a flag indicating whether to go round +the loop again. If so, prepareInertsForImplications is used to remove +the previous wanteds (which will still be in the inert set). Note +that prepareInertsForImplications will discard the insolubles, so we +must keep track of them separately. -} solveFlatGivens :: CtLoc -> [EvVar] -> TcS () @@ -128,21 +141,25 @@ solveFlatGivens loc givens } solveFlatWanteds :: Cts -> TcS WantedConstraints -solveFlatWanteds wanteds - = do { solveFlats wanteds - ; (implics, tv_eqs, fun_eqs, insols, others) <- getUnsolvedInerts - ; unflattened_eqs <- unflatten tv_eqs fun_eqs - -- See Note [Unflatten after solving the flat wanteds] - - ; zonked <- zonkFlats (others `andCts` unflattened_eqs) - -- Postcondition is that the wl_flats are zonked - - ; (wanteds', insols', rerun) <- runTcPluginsWanted zonked - ; if rerun then do { updInertTcS prepareInertsForImplications - ; solveFlatWanteds wanteds' } - else return (WC { wc_flat = wanteds' - , wc_insol = insols' `unionBags` insols - , wc_impl = implics }) } +solveFlatWanteds = go emptyBag + where + go insols0 wanteds + = do { solveFlats wanteds + ; (implics, tv_eqs, fun_eqs, insols, others) <- getUnsolvedInerts + ; unflattened_eqs <- unflatten tv_eqs fun_eqs + -- See Note [Unflatten after solving the flat wanteds] + + ; zonked <- zonkFlats (others `andCts` unflattened_eqs) + -- Postcondition is that the wl_flats are zonked + + ; (wanteds', insols', rerun) <- runTcPluginsWanted zonked + -- See Note [Running plugins on unflattened wanteds] + ; let all_insols = insols0 `unionBags` insols `unionBags` insols' + ; if rerun then do { updInertTcS prepareInertsForImplications + ; go all_insols wanteds' } + else return (WC { wc_flat = wanteds' + , wc_insol = all_insols + , wc_impl = implics }) } -- The main solver loop implements Note [Basic Simplifier Plan] From git at git.haskell.org Thu Dec 4 16:44:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Dec 2014 16:44:10 +0000 (UTC) Subject: [commit: ghc] master: Cabal submodule update (78edd76) Message-ID: <20141204164410.B3DF33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/78edd76047d255bb543f7ce5517477f371bb2f0b/ghc >--------------------------------------------------------------- commit 78edd76047d255bb543f7ce5517477f371bb2f0b Author: Herbert Valerio Riedel Date: Thu Dec 4 17:19:56 2014 +0100 Cabal submodule update This submodule update pulls in the fix > Build C sources with `-fPIC` when GHC is using dynamic libraries. >--------------------------------------------------------------- 78edd76047d255bb543f7ce5517477f371bb2f0b libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index ea062bf..1d1ecd6 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit ea062bf522e015f6e643bcc833487098edba8398 +Subproject commit 1d1ecd611560dd719642a9ef3e536caf0df1dc8c From git at git.haskell.org Fri Dec 5 10:05:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 Dec 2014 10:05:44 +0000 (UTC) Subject: [commit: ghc] master: Revert "Revert "Make the linker API thread-safe"" (55a2a0b) Message-ID: <20141205100544.98F1E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/55a2a0b4893486e5dde151620d7f46e8035d2af5/ghc >--------------------------------------------------------------- commit 55a2a0b4893486e5dde151620d7f46e8035d2af5 Author: Simon Marlow Date: Thu Dec 4 10:12:01 2014 +0000 Revert "Revert "Make the linker API thread-safe"" Also includes a fix for the segfaults on Windows caused by the original version of this patch. This reverts commit 4b51194df4090d984f02c12128e868077660fb8b. >--------------------------------------------------------------- 55a2a0b4893486e5dde151620d7f46e8035d2af5 docs/users_guide/7.10.1-notes.xml | 6 ++- rts/CheckUnload.c | 4 ++ rts/Linker.c | 109 +++++++++++++++++++++++++------------- rts/LinkerInternals.h | 4 ++ testsuite/tests/rts/Makefile | 8 +-- testsuite/tests/rts/T2615.hs | 1 + testsuite/tests/rts/rdynamic.hs | 2 + 7 files changed, 92 insertions(+), 42 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 55a2a0b4893486e5dde151620d7f46e8035d2af5 From git at git.haskell.org Fri Dec 5 10:05:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 Dec 2014 10:05:47 +0000 (UTC) Subject: [commit: ghc] master: Revert "Revert "Add purgeObj() to remove the symbol table entries for an object"" (a48bee9) Message-ID: <20141205100547.3D2F73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a48bee9fa1cf51c9df3bd87079eb8ff9b222e717/ghc >--------------------------------------------------------------- commit a48bee9fa1cf51c9df3bd87079eb8ff9b222e717 Author: Simon Marlow Date: Thu Dec 4 10:12:26 2014 +0000 Revert "Revert "Add purgeObj() to remove the symbol table entries for an object"" This reverts commit 7932b2adaecac6c86038176d909c20ad1b1f9604. >--------------------------------------------------------------- a48bee9fa1cf51c9df3bd87079eb8ff9b222e717 includes/rts/Linker.h | 3 ++ rts/Linker.c | 74 ++++++++++++++++++++++---------- testsuite/tests/rts/linker_unload.c | 37 ++++++++++++++++ testsuite/tests/rts/linker_unload.stdout | 2 +- 4 files changed, 92 insertions(+), 24 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a48bee9fa1cf51c9df3bd87079eb8ff9b222e717 From git at git.haskell.org Fri Dec 5 10:05:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 Dec 2014 10:05:49 +0000 (UTC) Subject: [commit: ghc] master: Disable T8124 on Windows (uses pthreads) (09af720) Message-ID: <20141205100549.CD8EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/09af720d40a05a8cc70cdfa13b4ec6c2614045ac/ghc >--------------------------------------------------------------- commit 09af720d40a05a8cc70cdfa13b4ec6c2614045ac Author: Simon Marlow Date: Fri Dec 5 09:53:06 2014 +0000 Disable T8124 on Windows (uses pthreads) >--------------------------------------------------------------- 09af720d40a05a8cc70cdfa13b4ec6c2614045ac testsuite/tests/rts/all.T | 1 + 1 file changed, 1 insertion(+) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index 6d08594..7162f4c 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -220,6 +220,7 @@ test('T8242', [ only_ways(threaded_ways), ignore_output ], compile_and_run, ['']) test('T8124', [ only_ways(threaded_ways), omit_ways(['ghci']), + when(opsys('mingw32'), skip), # uses pthreads extra_clean(['T8124_c.o']), pre_cmd('$MAKE -s --no-print-directory T8124_setup') ], # The T8124_setup hack is to ensure that we generate From git at git.haskell.org Fri Dec 5 23:47:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 Dec 2014 23:47:11 +0000 (UTC) Subject: [commit: ghc] master: Add notes about the inert CTyEqCans (9a10107) Message-ID: <20141205234711.8088D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9a1010745e68f7d10692767d8f7a65216618d329/ghc >--------------------------------------------------------------- commit 9a1010745e68f7d10692767d8f7a65216618d329 Author: Simon Peyton Jones Date: Fri Dec 5 23:47:06 2014 +0000 Add notes about the inert CTyEqCans Work with Dimitrios >--------------------------------------------------------------- 9a1010745e68f7d10692767d8f7a65216618d329 compiler/typecheck/Flattening-notes | 150 ++++++++++++++++++++++++++++++++++++ 1 file changed, 150 insertions(+) diff --git a/compiler/typecheck/Flattening-notes b/compiler/typecheck/Flattening-notes index 499a757..6d6d20a 100644 --- a/compiler/typecheck/Flattening-notes +++ b/compiler/typecheck/Flattening-notes @@ -7,3 +7,153 @@ ToDo: * Collapse CNonCanonical and CIrredCan +=========================== + +The inert equalities +~~~~~~~~~~~~~~~~~~~~ + +Definition: can-rewrite relation. +A "can-rewrite" relation between flavours, written f1 >= f2, is a +binary relation with the following properties + + R1. >= is transitive + R2. If f1 >= f, and f2 >= f, + then either f1 >= f2 or f2 >= f1 + +Lemma. If f1 >= f then f1 >= f1 +Proof. By property (R2), with f1=f2 + +Definition: generalised substitution. +A "generalised substitution" S is a set of triples (a -f-> t), where + a is a type variable + t is a type + f is a flavour +such that + (WF) if (a -f1-> t1) in S + (a -f2-> t2) in S + then neither (f1 >= f2) nor (f2 >= f1) hold + +Definition: applying a generalised substitution. +If S is a generalised subsitution + S(f,a) = t, if (a -fs-> t) in S, and fs >= f + = a, otherwise +Application extends naturally to types S(f,t) + +Theorem: S(f,a) is a function. +Proof: Suppose (a -f1-> t1) and (a -f2-> t2) are both in S, + and f1 >= f and f2 >= f + Then by (R2) f1 >= f2 or f2 >= f1, which contradicts (WF) + +Notation: repeated application. + S^0(f,t) = t + S^(n+1)(f,t) = S(f, S^n(t)) + +Definition: inert generalised substitution +A generalised substitution S is "inert" iff + there is an n such that + for every f,t, S^n(f,t) = S^(n+1)(f,t) + +Flavours. In GHC currently drawn from {G,W,D}, but with the coercion +solver the flavours become pairs + { (k,l) | k <- {G,W,D}, l <- {Nom,Rep} } + +---------------------------------------------------------------- +Our main invariant: + the inert CTyEqCans should be an inert generalised subsitution +---------------------------------------------------------------- + +Note that inertness is not the same as idempotence. To apply S to a +type, you may have to apply it recursive. But inertness does +guarantee that this recursive use will terminate. + +The main theorem. + Suppose we have a "work item" + a -fw-> t + and an inert generalised substitution S, + such that + (T1) S(fw,a) = a -- LHS is a fixpoint of S + (T2) S(fw,t) = t -- RHS is a fixpoint of S + (T3) a not in t -- No occurs check in the work item + + (K1) if (a -fs-> s) is in S then not (fw >= fs) + (K2) if (b -fs-> s) is in S, where b /= a, then + (K2a) not (fs >= fs) + or (K2b) not (fw >= fs) + or (K2c) a not in s + or (K3) if (b -fs-> a) is in S then not (fw >= fs) + + then the extended substition T = S+(a -fw-> t) + is an inert genrealised substitution. + +The idea is that +* (T1-2) are guaranteed by exhaustively rewriting the work-item + with S. + +* T3 is guaranteed by a simple occurs-check on the work item. + +* (K1-3) are the "kick-out" criteria. (As stated, they are really the + "keep" criteria.) If the current inert S contains a triple that does + not satisfy (K1-3), then we remove it from S by "kicking it out", + and re-processing it. + +* Note that kicking out is a Bad Thing, becuase it means we have to + re-process a constraint. The less we kick out, the better. + +* Assume we have G>=G, G>=W, D>=D, and that's all. Then, when performing + a unification we add a new given a -G-> ty. But doing so dos not require + us to kick out wanteds that mention a, because of (K2b). + +* Lemma (L1): The conditions of the Main Theorem imply that not (fs >= fw). + Proof. Suppose the contrary (fs >= fw). Then because of (T1), + S(fw,a)=a. But since fs>=fw, S(fw,a) = s, hence s=a. But now we + have (a -fs-> a) in S, since fs>=fw we must have fs>=fs, and hence S + is not inert. + +* (K1) plus (L1) guarantee that the extended substiution satisfies (WF). + +* (K2) is about inertness. Intuitively, any infinite chain T^0(f,t), + T^1(f,t), T^2(f,T).... must pass through the new work item infnitely + often, since the substution without the work item is inert; and must + pass through at least one of the triples in S infnitely often. + + - (K2a): if not(fs>=fs) then there is no f that fs can rewrite (fs>=f), + and hence this triple never plays a role in application S(f,a). + It is always safe to extend S with such a triple. + + (NB: we could strengten K1) in this way too, but see K3. + + - (K2b): If this holds, we can't pass through this triple infinitely + often, because if we did then fs>=f, fw>=f, hence fs>=fw, + contradicting (L1), or fw>=fs contradicting K2b. + + - (K2c): if a not in s, we hae no further opportunity to apply the + work item. + + NB: this reasoning isn't water tight. + + +Completeness +~~~~~~~~~~~~~ +K3: completeness. (K3) is not ncessary for the extended substitution +to be inert. In fact K1 could be made stronger by saying + ... then (not (fw >= fs) or not (fs >= fs)) +But it's not enough for S to be inert; we also want completeness. +That is, we want to be able to solve all soluble wanted equalities. +Suppose we have + + work-item b -G-> a + inert-item a -W-> b + +Assuming (G >= W) but not (W >= W), this fulfills all the conditions, +so we could extend the inerts, thus: + + inert-items b -G-> a + a -W-> b + +But if we kicked-out the inert item, we'd get + + work-item a -W-> b + inert-item b -G-> a + +Then rewrite the work-item gives us (a -W-> a), which is soluble via Refl. +So we add one more clause to the kick-out criteria From git at git.haskell.org Sat Dec 6 00:35:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 Dec 2014 00:35:44 +0000 (UTC) Subject: [commit: ghc] master: renamer: fix trac issue #9778 (87160c1) Message-ID: <20141206003544.694DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/87160c1a5e5c742de176b29d8c3a596fba0983cf/ghc >--------------------------------------------------------------- commit 87160c1a5e5c742de176b29d8c3a596fba0983cf Author: Carlos Tom? Date: Fri Dec 5 14:36:55 2014 -0600 renamer: fix trac issue #9778 Summary: Added flag -fwarn-unticked-promoted-constructors Test Plan: test T9778 under tests/rename/should_compile Reviewers: jstolarek, simonpj, austin Reviewed By: jstolarek, simonpj, austin Subscribers: simonpj, goldfire, jstolarek, thomie, carter Differential Revision: https://phabricator.haskell.org/D534 GHC Trac Issues: #9778 >--------------------------------------------------------------- 87160c1a5e5c742de176b29d8c3a596fba0983cf compiler/main/DynFlags.hs | 3 +++ compiler/rename/RnEnv.hs | 12 ++++++++++- docs/users_guide/flags.xml | 7 +++++++ docs/users_guide/using.xml | 24 ++++++++++++++++++++++ testsuite/tests/rename/should_compile/T9778.hs | 8 ++++++++ testsuite/tests/rename/should_compile/T9778.stderr | 3 +++ testsuite/tests/rename/should_compile/all.T | 1 + 7 files changed, 57 insertions(+), 1 deletion(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index aaa52fe..5f277db 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -505,6 +505,7 @@ data WarningFlag = | Opt_WarnTypedHoles | Opt_WarnPartialTypeSignatures | Opt_WarnMissingExportedSigs + | Opt_WarnUntickedPromotedConstructors deriving (Eq, Show, Enum) data Language = Haskell98 | Haskell2010 @@ -2835,6 +2836,8 @@ fWarningFlags = [ flagSpec "warn-unsupported-calling-conventions" Opt_WarnUnsupportedCallingConventions, flagSpec "warn-unsupported-llvm-version" Opt_WarnUnsupportedLlvmVersion, + flagSpec "warn-unticked-promoted-constructors" + Opt_WarnUntickedPromotedConstructors, flagSpec "warn-unused-binds" Opt_WarnUnusedBinds, flagSpec "warn-unused-do-bind" Opt_WarnUnusedDoBind, flagSpec "warn-unused-imports" Opt_WarnUnusedImports, diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs index 0cea309..eeffe17 100644 --- a/compiler/rename/RnEnv.hs +++ b/compiler/rename/RnEnv.hs @@ -699,7 +699,10 @@ lookup_demoted rdr_name ; case mb_demoted_name of Nothing -> reportUnboundName rdr_name Just demoted_name - | data_kinds -> return demoted_name + | data_kinds -> + do { whenWOptM Opt_WarnUntickedPromotedConstructors $ + addWarn (untickedPromConstrWarn demoted_name) + ; return demoted_name } | otherwise -> unboundNameX WL_Any rdr_name suggest_dk } | otherwise @@ -707,6 +710,13 @@ lookup_demoted rdr_name where suggest_dk = ptext (sLit "A data constructor of that name is in scope; did you mean DataKinds?") + untickedPromConstrWarn name = + text "Unticked promoted constructor" <> colon <+> quotes (ppr name) <> dot + $$ + hsep [ text "Use" + , quotes (char '\'' <> ppr name) + , text "instead of" + , quotes (ppr name) <> dot ] {- Note [Demotion] diff --git a/docs/users_guide/flags.xml b/docs/users_guide/flags.xml index 9ddd271..6ba0c6f 100644 --- a/docs/users_guide/flags.xml +++ b/docs/users_guide/flags.xml @@ -1570,6 +1570,13 @@ + + warn if promoted constructors are not ticked + dynamic + + + + warn about bindings that are unused dynamic diff --git a/docs/users_guide/using.xml b/docs/users_guide/using.xml index 396af6c..8006fff 100644 --- a/docs/users_guide/using.xml +++ b/docs/users_guide/using.xml @@ -1796,6 +1796,30 @@ f "2" = 2 + : + + + promoted constructor, warning + Warn if a promoted data constructor is used without a tick preceding it's name. + + For example: + + +data Nat = Succ Nat | Zero + +data Vec n s where + Nil :: Vec Zero a + Cons :: a -> Vec n a -> Vec (Succ n) a + + Will raise two warnings because Zero + and Succ are not written as 'Zero and + 'Succ. + + This warning is off by default. + + + + : diff --git a/testsuite/tests/rename/should_compile/T9778.hs b/testsuite/tests/rename/should_compile/T9778.hs new file mode 100644 index 0000000..5b32f67 --- /dev/null +++ b/testsuite/tests/rename/should_compile/T9778.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE GADTs #-} +module T9778 where + +data T = A | B + +data G a where + C :: G A diff --git a/testsuite/tests/rename/should_compile/T9778.stderr b/testsuite/tests/rename/should_compile/T9778.stderr new file mode 100644 index 0000000..3d2e40f --- /dev/null +++ b/testsuite/tests/rename/should_compile/T9778.stderr @@ -0,0 +1,3 @@ + T9778.hs:8:10: Warning: + Unticked promoted constructor: ?A?. + Use ?'A? instead of ?A?. diff --git a/testsuite/tests/rename/should_compile/all.T b/testsuite/tests/rename/should_compile/all.T index 7185fba..9265f18 100644 --- a/testsuite/tests/rename/should_compile/all.T +++ b/testsuite/tests/rename/should_compile/all.T @@ -218,3 +218,4 @@ test('T7969', ['$MAKE -s --no-print-directory T7969']) test('T9127', normal, compile, ['']) test('T4426', normal, compile, ['']) +test('T9778', normal, compile, ['-fwarn-unticked-promoted-constructors']) From git at git.haskell.org Sat Dec 6 00:35:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 Dec 2014 00:35:47 +0000 (UTC) Subject: [commit: ghc] master: docs: Update to reflect reality (3ebe304) Message-ID: <20141206003547.0E0DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3ebe304f25ba492403af5cc72500fe0b23a8c3a0/ghc >--------------------------------------------------------------- commit 3ebe304f25ba492403af5cc72500fe0b23a8c3a0 Author: Austin Seipp Date: Fri Dec 5 14:50:45 2014 -0600 docs: Update to reflect reality The documentation on what warnings -W/-Wall enable was slightly out of date, so lets fix that. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 3ebe304f25ba492403af5cc72500fe0b23a8c3a0 docs/users_guide/using.xml | 31 +++++++++++++++---------------- 1 file changed, 15 insertions(+), 16 deletions(-) diff --git a/docs/users_guide/using.xml b/docs/users_guide/using.xml index 8006fff..c9a30fe 100644 --- a/docs/users_guide/using.xml +++ b/docs/users_guide/using.xml @@ -1034,7 +1034,6 @@ test.hs:(5,4)-(6,7): program. These are: , , - , , , , @@ -1048,8 +1047,9 @@ test.hs:(5,4)-(6,7): , , , - , and - . + , + , and + . The following flags are simple ways to select standard “packages” of warnings: @@ -1061,12 +1061,12 @@ test.hs:(5,4)-(6,7): -W option Provides the standard warnings plus - , - , - , + , , - , and - . + , + , + , and + . @@ -1078,14 +1078,13 @@ test.hs:(5,4)-(6,7): suspicious code. The warnings that are not enabled by are - , - , - , - , - , - , - , - . + , + , + , + , + , + , and + . From git at git.haskell.org Sat Dec 6 00:35:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 Dec 2014 00:35:49 +0000 (UTC) Subject: [commit: ghc] master: Add -fwarn-unticked-promoted-constructors to -Wall (7cd6806) Message-ID: <20141206003549.B6C9E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7cd6806635d24694446748f59c97b14b0c47ba89/ghc >--------------------------------------------------------------- commit 7cd6806635d24694446748f59c97b14b0c47ba89 Author: Austin Seipp Date: Fri Dec 5 14:52:29 2014 -0600 Add -fwarn-unticked-promoted-constructors to -Wall Signed-off-by: Austin Seipp >--------------------------------------------------------------- 7cd6806635d24694446748f59c97b14b0c47ba89 compiler/main/DynFlags.hs | 3 ++- docs/users_guide/using.xml | 3 ++- libraries/base/Data/Either.hs | 6 +++--- libraries/base/Data/Type/Bool.hs | 30 ++++++++++++++---------------- libraries/base/Data/Type/Equality.hs | 34 +++++++++++++++++----------------- libraries/base/GHC/TypeLits.hs | 10 +++++----- 6 files changed, 43 insertions(+), 43 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 5f277db..1bac9aa 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -3332,7 +3332,8 @@ minusWallOpts Opt_WarnHiShadows, Opt_WarnOrphans, Opt_WarnUnusedDoBind, - Opt_WarnTrustworthySafe + Opt_WarnTrustworthySafe, + Opt_WarnUntickedPromotedConstructors ] enableGlasgowExts :: DynP () diff --git a/docs/users_guide/using.xml b/docs/users_guide/using.xml index c9a30fe..3059cff 100644 --- a/docs/users_guide/using.xml +++ b/docs/users_guide/using.xml @@ -1084,7 +1084,8 @@ test.hs:(5,4)-(6,7): , , , and - . + , + . diff --git a/libraries/base/Data/Either.hs b/libraries/base/Data/Either.hs index bd85b8f..901c9fd 100644 --- a/libraries/base/Data/Either.hs +++ b/libraries/base/Data/Either.hs @@ -281,9 +281,9 @@ isRight (Right _) = True -- instance for the == Boolean type-level equality operator type family EqEither a b where - EqEither (Left x) (Left y) = x == y - EqEither (Right x) (Right y) = x == y - EqEither a b = False + EqEither ('Left x) ('Left y) = x == y + EqEither ('Right x) ('Right y) = x == y + EqEither a b = 'False type instance a == b = EqEither a b {- diff --git a/libraries/base/Data/Type/Bool.hs b/libraries/base/Data/Type/Bool.hs index 8a80455..320d6a0 100644 --- a/libraries/base/Data/Type/Bool.hs +++ b/libraries/base/Data/Type/Bool.hs @@ -28,30 +28,28 @@ import Data.Bool -- | Type-level "If". @If True a b@ ==> @a@; @If False a b@ ==> @b@ type family If cond tru fls where - If True tru fls = tru - If False tru fls = fls + If 'True tru fls = tru + If 'False tru fls = fls -- | Type-level "and" type family a && b where - False && a = False - True && a = a - a && False = False - a && True = a - a && a = a + 'False && a = 'False + 'True && a = a + a && 'False = 'False + a && 'True = a + a && a = a infixr 3 && -- | Type-level "or" type family a || b where - False || a = a - True || a = True - a || False = a - a || True = True - a || a = a + 'False || a = a + 'True || a = 'True + a || 'False = a + a || 'True = 'True + a || a = a infixr 2 || -- | Type-level "not" type family Not a where - Not False = True - Not True = False - - + Not 'False = 'True + Not 'True = 'False diff --git a/libraries/base/Data/Type/Equality.hs b/libraries/base/Data/Type/Equality.hs index 626e817..2fc327e 100644 --- a/libraries/base/Data/Type/Equality.hs +++ b/libraries/base/Data/Type/Equality.hs @@ -184,37 +184,37 @@ families. -- all of the following closed type families are local to this module type family EqStar (a :: *) (b :: *) where - EqStar a a = True - EqStar a b = False + EqStar a a = 'True + EqStar a b = 'False -- This looks dangerous, but it isn't. This allows == to be defined -- over arbitrary type constructors. type family EqArrow (a :: k1 -> k2) (b :: k1 -> k2) where - EqArrow a a = True - EqArrow a b = False + EqArrow a a = 'True + EqArrow a b = 'False type family EqBool a b where - EqBool True True = True - EqBool False False = True - EqBool a b = False + EqBool 'True 'True = 'True + EqBool 'False 'False = 'True + EqBool a b = 'False type family EqOrdering a b where - EqOrdering LT LT = True - EqOrdering EQ EQ = True - EqOrdering GT GT = True - EqOrdering a b = False + EqOrdering 'LT 'LT = 'True + EqOrdering 'EQ 'EQ = 'True + EqOrdering 'GT 'GT = 'True + EqOrdering a b = 'False -type EqUnit (a :: ()) (b :: ()) = True +type EqUnit (a :: ()) (b :: ()) = 'True type family EqList a b where - EqList '[] '[] = True + EqList '[] '[] = 'True EqList (h1 ': t1) (h2 ': t2) = (h1 == h2) && (t1 == t2) - EqList a b = False + EqList a b = 'False type family EqMaybe a b where - EqMaybe Nothing Nothing = True - EqMaybe (Just x) (Just y) = x == y - EqMaybe a b = False + EqMaybe 'Nothing 'Nothing = 'True + EqMaybe ('Just x) ('Just y) = x == y + EqMaybe a b = 'False type family Eq2 a b where Eq2 '(a1, b1) '(a2, b2) = a1 == a2 && b1 == b2 diff --git a/libraries/base/GHC/TypeLits.hs b/libraries/base/GHC/TypeLits.hs index 8c74481..4dde7a3 100644 --- a/libraries/base/GHC/TypeLits.hs +++ b/libraries/base/GHC/TypeLits.hs @@ -147,13 +147,13 @@ instance Read SomeSymbol where readsPrec p xs = [ (someSymbolVal a, ys) | (a,ys) <- readsPrec p xs ] type family EqNat (a :: Nat) (b :: Nat) where - EqNat a a = True - EqNat a b = False + EqNat a a = 'True + EqNat a b = 'False type instance a == b = EqNat a b type family EqSymbol (a :: Symbol) (b :: Symbol) where - EqSymbol a a = True - EqSymbol a b = False + EqSymbol a a = 'True + EqSymbol a b = 'False type instance a == b = EqSymbol a b -------------------------------------------------------------------------------- @@ -164,7 +164,7 @@ infixl 7 * infixr 8 ^ -- | Comparison of type-level naturals, as a constraint. -type x <= y = (x <=? y) ~ True +type x <= y = (x <=? y) ~ 'True -- | Comparison of type-level symbols, as a function. -- From git at git.haskell.org Sat Dec 6 00:35:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 Dec 2014 00:35:52 +0000 (UTC) Subject: [commit: ghc] master: Implement `calloc{, Bytes, Array, Array0}` allocators (08610c1) Message-ID: <20141206003552.5A9DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/08610c1fdc7816c74faed40f8a7d3c4b4758709e/ghc >--------------------------------------------------------------- commit 08610c1fdc7816c74faed40f8a7d3c4b4758709e Author: Alex Petrov Date: Fri Dec 5 14:56:14 2014 -0600 Implement `calloc{,Bytes,Array,Array0}` allocators Summary: This adds zero-initialising versions of `malloc{,Bytes,Array,Array0}` * Add `calloc` and `callocBytes` to `Foreign.Marshal.Alloc`. * Add `callocArray` and `callocArray0` to `Foreign.Marshal.Array`. Reviewers: ekmett, duncan, austin, hvr Reviewed By: austin, hvr Subscribers: ezyang, simonmar, ekmett, duncan, thomie, carter Projects: #ghc Differential Revision: https://phabricator.haskell.org/D527 GHC Trac Issues: #9859 >--------------------------------------------------------------- 08610c1fdc7816c74faed40f8a7d3c4b4758709e libraries/base/Foreign/Marshal/Alloc.hs | 18 ++++++++++++++++++ libraries/base/Foreign/Marshal/Array.hs | 19 ++++++++++++++++++- libraries/base/changelog.md | 4 ++++ 3 files changed, 40 insertions(+), 1 deletion(-) diff --git a/libraries/base/Foreign/Marshal/Alloc.hs b/libraries/base/Foreign/Marshal/Alloc.hs index d43589f..264c10c 100644 --- a/libraries/base/Foreign/Marshal/Alloc.hs +++ b/libraries/base/Foreign/Marshal/Alloc.hs @@ -49,6 +49,9 @@ module Foreign.Marshal.Alloc ( malloc, mallocBytes, + calloc, + callocBytes, + realloc, reallocBytes, @@ -82,6 +85,15 @@ malloc = doMalloc undefined doMalloc :: Storable b => b -> IO (Ptr b) doMalloc dummy = mallocBytes (sizeOf dummy) +-- |Like 'malloc' but memory is filled with bytes of value zero. +-- +{-# INLINE calloc #-} +calloc :: Storable a => IO (Ptr a) +calloc = doCalloc undefined + where + doCalloc :: Storable b => b -> IO (Ptr b) + doCalloc dummy = callocBytes (sizeOf dummy) + -- |Allocate a block of memory of the given number of bytes. -- The block of memory is sufficiently aligned for any of the basic -- foreign types that fits into a memory block of the allocated size. @@ -92,6 +104,11 @@ malloc = doMalloc undefined mallocBytes :: Int -> IO (Ptr a) mallocBytes size = failWhenNULL "malloc" (_malloc (fromIntegral size)) +-- |Llike 'mallocBytes' but memory is filled with bytes of value zero. +-- +callocBytes :: Int -> IO (Ptr a) +callocBytes size = failWhenNULL "calloc" $ _calloc 1 (fromIntegral size) + -- |@'alloca' f@ executes the computation @f@, passing as argument -- a pointer to a temporarily allocated block of memory sufficient to -- hold values of type @a at . @@ -198,6 +215,7 @@ failWhenNULL name f = do -- basic C routines needed for memory allocation -- foreign import ccall unsafe "stdlib.h malloc" _malloc :: CSize -> IO (Ptr a) +foreign import ccall unsafe "stdlib.h calloc" _calloc :: CSize -> CSize -> IO (Ptr a) foreign import ccall unsafe "stdlib.h realloc" _realloc :: Ptr a -> CSize -> IO (Ptr b) foreign import ccall unsafe "stdlib.h free" _free :: Ptr a -> IO () diff --git a/libraries/base/Foreign/Marshal/Array.hs b/libraries/base/Foreign/Marshal/Array.hs index 8d7dcfb..0aea67b 100644 --- a/libraries/base/Foreign/Marshal/Array.hs +++ b/libraries/base/Foreign/Marshal/Array.hs @@ -30,6 +30,9 @@ module Foreign.Marshal.Array ( reallocArray, reallocArray0, + callocArray, + callocArray0, + -- ** Marshalling -- peekArray, @@ -66,7 +69,7 @@ module Foreign.Marshal.Array ( import Foreign.Ptr (Ptr, plusPtr) import Foreign.Storable (Storable(alignment,sizeOf,peekElemOff,pokeElemOff)) -import Foreign.Marshal.Alloc (mallocBytes, allocaBytesAligned, reallocBytes) +import Foreign.Marshal.Alloc (mallocBytes, callocBytes, allocaBytesAligned, reallocBytes) import Foreign.Marshal.Utils (copyBytes, moveBytes) import GHC.Num @@ -91,6 +94,20 @@ mallocArray = doMalloc undefined mallocArray0 :: Storable a => Int -> IO (Ptr a) mallocArray0 size = mallocArray (size + 1) +-- |Like 'mallocArray', but allocated memory is filled with bytes of value zero. +-- +callocArray :: Storable a => Int -> IO (Ptr a) +callocArray = doCalloc undefined + where + doCalloc :: Storable a' => a' -> Int -> IO (Ptr a') + doCalloc dummy size = callocBytes (size * sizeOf dummy) + +-- |Like 'callocArray0', but allocated memory is filled with bytes of value +-- zero. +-- +callocArray0 :: Storable a => Int -> IO (Ptr a) +callocArray0 size = callocArray (size + 1) + -- |Temporarily allocate space for the given number of elements -- (like 'Foreign.Marshal.Alloc.alloca', but for multiple elements). -- diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index ef3e9ae..3b06dba 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -130,6 +130,10 @@ * Make `read . show = id` for `Data.Fixed` (#9240) + * Add `calloc` and `callocBytes` to `Foreign.Marshal.Alloc`. + + * Add `callocArray` and `callocArray0` to `Foreign.Marshal.Array`. + ## 4.7.0.2 *Dec 2014* * Bundled with GHC 7.8.4 From git at git.haskell.org Sat Dec 6 00:35:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 Dec 2014 00:35:55 +0000 (UTC) Subject: [commit: ghc] master: msse flag handling: fix trac issue #9777 (da98592) Message-ID: <20141206003555.0D7A23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/da98592026154264d529e2e235ff396dfd6e7c51/ghc >--------------------------------------------------------------- commit da98592026154264d529e2e235ff396dfd6e7c51 Author: Denis Redozubov Date: Fri Dec 5 14:55:19 2014 -0600 msse flag handling: fix trac issue #9777 Summary: Signed-off-by: Denis Redozubov SSE version handled by different dynamic flags Signed-off-by: Denis Redozubov Test Plan: validate Reviewers: austin, jstolarek Reviewed By: austin, jstolarek Subscribers: kolmodin, thomie, carter Differential Revision: https://phabricator.haskell.org/D504 GHC Trac Issues: #9777 >--------------------------------------------------------------- da98592026154264d529e2e235ff396dfd6e7c51 compiler/main/CmdLineParser.hs | 12 ------------ compiler/main/DynFlags.hs | 25 ++++++++++++++++--------- 2 files changed, 16 insertions(+), 21 deletions(-) diff --git a/compiler/main/CmdLineParser.hs b/compiler/main/CmdLineParser.hs index 561765e..94c786b 100644 --- a/compiler/main/CmdLineParser.hs +++ b/compiler/main/CmdLineParser.hs @@ -79,8 +79,6 @@ data OptKind m -- Suppose the flag is -f | AnySuffix (String -> EwM m ()) -- -f or -farg; pass entire "-farg" to fn | PrefixPred (String -> Bool) (String -> EwM m ()) | AnySuffixPred (String -> Bool) (String -> EwM m ()) - | VersionSuffix (Int -> Int -> EwM m ()) - -- -f or -f=maj.min; pass major and minor version to fn -------------------------------------------------------- @@ -239,15 +237,6 @@ processOneArg opt_kind rest arg args AnySuffix f -> Right (f dash_arg, args) AnySuffixPred _ f -> Right (f dash_arg, args) - VersionSuffix f | [maj_s, min_s] <- split '.' rest_no_eq, - Just maj <- parseInt maj_s, - Just min <- parseInt min_s -> Right (f maj min, args) - | [maj_s] <- split '.' rest_no_eq, - Just maj <- parseInt maj_s -> Right (f maj 0, args) - | null rest_no_eq -> Right (f 1 0, args) - | otherwise -> Left ("malformed version argument in " ++ dash_arg) - - findArg :: [Flag m] -> String -> Maybe (String, OptKind m) findArg spec arg = case sortBy (compare `on` (length . fst)) -- prefer longest matching flag @@ -273,7 +262,6 @@ arg_ok (OptPrefix _) _ _ = True arg_ok (PassFlag _) rest _ = null rest arg_ok (AnySuffix _) _ _ = True arg_ok (AnySuffixPred p _) _ arg = p arg -arg_ok (VersionSuffix _) _ _ = True -- | Parse an Int -- diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 1bac9aa..64a81fc 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -845,7 +845,7 @@ data DynFlags = DynFlags { nextWrapperNum :: IORef (ModuleEnv Int), -- | Machine dependant flags (-m stuff) - sseVersion :: Maybe (Int, Int), -- (major, minor) + sseVersion :: Maybe SseVersion, avx :: Bool, avx2 :: Bool, avx512cd :: Bool, -- Enable AVX-512 Conflict Detection Instructions. @@ -2503,8 +2503,11 @@ dynamic_flags = [ ------ Machine dependant (-m) stuff --------------------------- - , defGhcFlag "msse" - (versionSuffix (\maj min d -> d{ sseVersion = Just (maj, min) })) + , defGhcFlag "msse" (noArg (\d -> d{ sseVersion = Just SSE1 })) + , defGhcFlag "msse2" (noArg (\d -> d{ sseVersion = Just SSE2 })) + , defGhcFlag "msse3" (noArg (\d -> d{ sseVersion = Just SSE3 })) + , defGhcFlag "msse4" (noArg (\d -> d{ sseVersion = Just SSE4 })) + , defGhcFlag "msse4.2" (noArg (\d -> d{ sseVersion = Just SSE42 })) , defGhcFlag "mavx" (noArg (\d -> d{ avx = True })) , defGhcFlag "mavx2" (noArg (\d -> d{ avx2 = True })) , defGhcFlag "mavx512cd" (noArg (\d -> d{ avx512cd = True })) @@ -3495,9 +3498,6 @@ optIntSuffixM :: (Maybe Int -> DynFlags -> DynP DynFlags) -> OptKind (CmdLineP DynFlags) optIntSuffixM fn = OptIntSuffix (\mi -> updM (fn mi)) -versionSuffix :: (Int -> Int -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags) -versionSuffix fn = VersionSuffix (\maj min -> upd (fn maj min)) - setDumpFlag :: DumpFlag -> OptKind (CmdLineP DynFlags) setDumpFlag dump_flag = NoArg (setDumpFlag' dump_flag) @@ -4036,10 +4036,17 @@ setUnsafeGlobalDynFlags = writeIORef v_unsafeGlobalDynFlags -- check if SSE is enabled, we might have x86-64 imply the -msse2 -- flag. +data SseVersion = SSE1 + | SSE2 + | SSE3 + | SSE4 + | SSE42 + deriving (Eq, Ord) + isSseEnabled :: DynFlags -> Bool isSseEnabled dflags = case platformArch (targetPlatform dflags) of ArchX86_64 -> True - ArchX86 -> sseVersion dflags >= Just (1,0) + ArchX86 -> sseVersion dflags >= Just SSE1 _ -> False isSse2Enabled :: DynFlags -> Bool @@ -4050,11 +4057,11 @@ isSse2Enabled dflags = case platformArch (targetPlatform dflags) of -- calling convention specifies the use of xmm regs, -- and possibly other places. True - ArchX86 -> sseVersion dflags >= Just (2,0) + ArchX86 -> sseVersion dflags >= Just SSE2 _ -> False isSse4_2Enabled :: DynFlags -> Bool -isSse4_2Enabled dflags = sseVersion dflags >= Just (4,2) +isSse4_2Enabled dflags = sseVersion dflags >= Just SSE42 isAvxEnabled :: DynFlags -> Bool isAvxEnabled dflags = avx dflags || avx2 dflags || avx512f dflags From git at git.haskell.org Sat Dec 6 00:35:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 Dec 2014 00:35:57 +0000 (UTC) Subject: [commit: ghc] master: Add references between Data.Traversable.for and Data.Foldable.for_ and co. (d80022d) Message-ID: <20141206003557.AF8CA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d80022d788cb6dc511d16cb12972265b058a292d/ghc >--------------------------------------------------------------- commit d80022d788cb6dc511d16cb12972265b058a292d Author: Baldur Bl?ndal Date: Fri Dec 5 15:15:04 2014 -0600 Add references between Data.Traversable.for and Data.Foldable.for_ and co. Summary: This is an issue that sometimes comes up, see https://www.haskell.org/pipermail/libraries/2013-May/019872.html Reviewers: hvr, ekmett, dfeuer, Mikolaj, austin Reviewed By: ekmett, Mikolaj, austin Subscribers: mjo Projects: #ghc Differential Revision: https://phabricator.haskell.org/D475 >--------------------------------------------------------------- d80022d788cb6dc511d16cb12972265b058a292d libraries/base/Data/Foldable.hs | 40 +++++++++++++++++++++++++++----------- libraries/base/Data/Traversable.hs | 23 ++++++++++++++-------- 2 files changed, 44 insertions(+), 19 deletions(-) diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs index e9246f9..ed32879 100644 --- a/libraries/base/Data/Foldable.hs +++ b/libraries/base/Data/Foldable.hs @@ -323,36 +323,54 @@ foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b foldlM f z0 xs = foldr f' return xs z0 where f' x k z = f z x >>= k --- | Map each element of a structure to an action, evaluate --- these actions from left to right, and ignore the results. +-- | Map each element of a structure to an action, evaluate these +-- actions from left to right, and ignore the results. For a version +-- that doesn't ignore the results see 'Data.Traversable.traverse'. traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f () traverse_ f = foldr ((*>) . f) (pure ()) --- | 'for_' is 'traverse_' with its arguments flipped. +-- | 'for_' is 'traverse_' with its arguments flipped. For a version +-- that doesn't ignore the results see 'Data.Traversable.for'. +-- +-- >>> for_ [1..4] print +-- 1 +-- 2 +-- 3 +-- 4 for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f () {-# INLINE for_ #-} for_ = flip traverse_ -- | Map each element of a structure to a monadic action, evaluate --- these actions from left to right, and ignore the results. As of --- base 4.8.0.0, 'mapM_' is just 'traverse_', specialized to 'Monad'. +-- these actions from left to right, and ignore the results. For a +-- version that doesn't ignore the results see +-- 'Data.Traversable.mapM'. +-- +-- As of base 4.8.0.0, 'mapM_' is just 'traverse_', specialized to +-- 'Monad'. mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m () mapM_ f= foldr ((>>) . f) (return ()) --- | 'forM_' is 'mapM_' with its arguments flipped. As of base --- 4.8.0.0, 'forM_' is just 'for_', specialized to 'Monad'. +-- | 'forM_' is 'mapM_' with its arguments flipped. For a version that +-- doesn't ignore the results see 'Data.Traversable.forM'. +-- +-- As of base 4.8.0.0, 'forM_' is just 'for_', specialized to 'Monad'. forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m () {-# INLINE forM_ #-} forM_ = flip mapM_ --- | Evaluate each action in the structure from left to right, --- and ignore the results. +-- | Evaluate each action in the structure from left to right, and +-- ignore the results. For a version that doesn't ignore the results +-- see 'Data.Traversable.sequenceA'. sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f () sequenceA_ = foldr (*>) (pure ()) -- | Evaluate each monadic action in the structure from left to right, --- and ignore the results. As of base 4.8.0.0, 'sequence_' is just --- 'sequenceA_', specialized to 'Monad'. +-- and ignore the results. For a version that doesn't ignore the +-- results see 'Data.Traversable.sequence'. +-- +-- As of base 4.8.0.0, 'sequence_' is just 'sequenceA_', specialized +-- to 'Monad'. sequence_ :: (Foldable t, Monad m) => t (m a) -> m () sequence_ = foldr (>>) (return ()) diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs index f64d99f..e7caf4e 100644 --- a/libraries/base/Data/Traversable.hs +++ b/libraries/base/Data/Traversable.hs @@ -144,23 +144,28 @@ import qualified GHC.List as List ( foldr ) class (Functor t, Foldable t) => Traversable t where {-# MINIMAL traverse | sequenceA #-} - -- | Map each element of a structure to an action, evaluate + -- | Map each element of a structure to an action, evaluate these -- these actions from left to right, and collect the results. + -- actions from left to right, and collect the results. For a + -- version that ignores the results see 'Data.Foldable.traverse_'. traverse :: Applicative f => (a -> f b) -> t a -> f (t b) traverse f = sequenceA . fmap f - -- | Evaluate each action in the structure from left to right, - -- and collect the results. + -- | Evaluate each action in the structure from left to right, and + -- and collect the results. For a version that ignores the results + -- see 'Data.Foldable.sequenceA_'. sequenceA :: Applicative f => t (f a) -> f (t a) sequenceA = traverse id -- | Map each element of a structure to a monadic action, evaluate - -- these actions from left to right, and collect the results. + -- these actions from left to right, and collect the results. For + -- a version that ignores the results see 'Data.Foldable.mapM_'. mapM :: Monad m => (a -> m b) -> t a -> m (t b) mapM = traverse - -- | Evaluate each monadic action in the structure from left to right, - -- and collect the results. + -- | Evaluate each monadic action in the structure from left to + -- right, and collect the results. For a version that ignores the + -- results see 'Data.Foldable.sequence_'. sequence :: Monad m => t (m a) -> m (t a) sequence = sequenceA @@ -202,12 +207,14 @@ instance Traversable (Const m) where -- general functions --- | 'for' is 'traverse' with its arguments flipped. +-- | 'for' is 'traverse' with its arguments flipped. For a version +-- that ignores the results see 'Data.Foldable.for_'. for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b) {-# INLINE for #-} for = flip traverse --- | 'forM' is 'mapM' with its arguments flipped. +-- | 'forM' is 'mapM' with its arguments flipped. For a version that +-- ignores the results see 'Data.Foldable.forM_'. forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) {-# INLINE forM #-} forM = flip mapM From git at git.haskell.org Sat Dec 6 03:36:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 Dec 2014 03:36:10 +0000 (UTC) Subject: [commit: ghc] master: Portability: wc -l sometimes has leading spaces, trim them off. (9a1779e) Message-ID: <20141206033610.592673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9a1779ebf92c8ae30ff5b00e51b87bc42c4000b6/ghc >--------------------------------------------------------------- commit 9a1779ebf92c8ae30ff5b00e51b87bc42c4000b6 Author: Edward Z. Yang Date: Fri Dec 5 15:50:53 2014 -0800 Portability: wc -l sometimes has leading spaces, trim them off. Summary: Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D557 >--------------------------------------------------------------- 9a1779ebf92c8ae30ff5b00e51b87bc42c4000b6 testsuite/tests/cabal/cabal06/Makefile | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/cabal/cabal06/Makefile b/testsuite/tests/cabal/cabal06/Makefile index 5934b9b..8b918a0 100644 --- a/testsuite/tests/cabal/cabal06/Makefile +++ b/testsuite/tests/cabal/cabal06/Makefile @@ -46,9 +46,9 @@ cabal06: clean cd q && $(SETUP) copy (cd q && $(SETUP) register --print-ipid) > tmp_second_q @echo "Does the first instance of q depend on p-1.0?" - '$(GHC_PKG)' field --ipid `cat tmp_first_q` depends -f tmp.d | grep p-1.0 | wc -l + '$(GHC_PKG)' field --ipid `cat tmp_first_q` depends -f tmp.d | grep p-1.0 | wc -l | sed 's/[[:space:]]//g' @echo "Does the second instance of q depend on p-1.0?" - '$(GHC_PKG)' field --ipid `cat tmp_second_q` depends -f tmp.d | grep p-1.1 | wc -l + '$(GHC_PKG)' field --ipid `cat tmp_second_q` depends -f tmp.d | grep p-1.1 | wc -l | sed 's/[[:space:]]//g' cd r && $(SETUP) clean cd r && ../Setup configure $(CABAL_MINIMAL_BUILD) --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)' --package-db=../tmp.d --dependency="q=`cat ../tmp_first_q`" --constraint="p==1.0" --prefix='$(PWD)/inst-e' --ghc-pkg-options='--enable-multi-instance' cd r && $(SETUP) build From git at git.haskell.org Sat Dec 6 08:31:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 Dec 2014 08:31:20 +0000 (UTC) Subject: [commit: ghc] master: Add ticket-ref to changelog entry (fup to 08610c1) (7383ce9) Message-ID: <20141206083120.EB1743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7383ce98e06a75e416bb8f810932acc9f607f906/ghc >--------------------------------------------------------------- commit 7383ce98e06a75e416bb8f810932acc9f607f906 Author: Herbert Valerio Riedel Date: Sat Dec 6 09:31:16 2014 +0100 Add ticket-ref to changelog entry (fup to 08610c1) [skip ci] >--------------------------------------------------------------- 7383ce98e06a75e416bb8f810932acc9f607f906 libraries/base/changelog.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 3b06dba..00da7ce 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -130,9 +130,9 @@ * Make `read . show = id` for `Data.Fixed` (#9240) - * Add `calloc` and `callocBytes` to `Foreign.Marshal.Alloc`. + * Add `calloc` and `callocBytes` to `Foreign.Marshal.Alloc`. (#9859) - * Add `callocArray` and `callocArray0` to `Foreign.Marshal.Array`. + * Add `callocArray` and `callocArray0` to `Foreign.Marshal.Array`. (#9859) ## 4.7.0.2 *Dec 2014* From git at git.haskell.org Sat Dec 6 17:10:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 Dec 2014 17:10:38 +0000 (UTC) Subject: [commit: ghc] master: Set proper `CTYPE` for POSIX `CGroup` (b9f636b) Message-ID: <20141206171038.2F01D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b9f636b3aa962154c1b1515a3acecfbe9071b308/ghc >--------------------------------------------------------------- commit b9f636b3aa962154c1b1515a3acecfbe9071b308 Author: Herbert Valerio Riedel Date: Sat Dec 6 18:07:25 2014 +0100 Set proper `CTYPE` for POSIX `CGroup` This fixes https://github.com/haskell/unix/issues/20 which is about compile warnings due to incompatible pointer types of the kind warning: passing argument 5 of ?getgrnam_r? from incompatible pointer type HsInt32 ghc...(void* a1, void* a2, void* a3, HsWord64 a4, void** a5) {return getgrnam_r(a1, a2, a3, a4, a5);} note: expected ?struct group ** __restrict__? but argument is of type ?void **? extern int getgrnam_r (const char *__restrict __name, Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- b9f636b3aa962154c1b1515a3acecfbe9071b308 libraries/base/System/Posix/Internals.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/System/Posix/Internals.hs b/libraries/base/System/Posix/Internals.hs index 30bf19c..c49e613 100644 --- a/libraries/base/System/Posix/Internals.hs +++ b/libraries/base/System/Posix/Internals.hs @@ -63,7 +63,7 @@ puts s = withCAStringLen (s ++ "\n") $ \(p, len) -> do -- Types type CFLock = () -type CGroup = () +data {-# CTYPE "struct group" #-} CGroup type CLconv = () type CPasswd = () type CSigaction = () From git at git.haskell.org Sat Dec 6 21:45:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 Dec 2014 21:45:06 +0000 (UTC) Subject: [commit: ghc] master: Update `unix` submodule to latest snapshot (334cb10) Message-ID: <20141206214506.4CA883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/334cb108c17e02b9f83db09a0dc85a1f1c11a134/ghc >--------------------------------------------------------------- commit 334cb108c17e02b9f83db09a0dc85a1f1c11a134 Author: Herbert Valerio Riedel Date: Sat Dec 6 22:45:22 2014 +0100 Update `unix` submodule to latest snapshot >--------------------------------------------------------------- 334cb108c17e02b9f83db09a0dc85a1f1c11a134 libraries/unix | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/unix b/libraries/unix index c46a7fe..256b191 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit c46a7fecc212573cc7864a25a762e9e6849f7257 +Subproject commit 256b19184bcb05c3cd9a6061730b7d67d61c0763 From git at git.haskell.org Sun Dec 7 15:39:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 Dec 2014 15:39:47 +0000 (UTC) Subject: [commit: ghc] master: Added comments to flattening-notes (d629576) Message-ID: <20141207153947.4A3D73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d62957682d72c939e26cf0a29bf0c68726399c20/ghc >--------------------------------------------------------------- commit d62957682d72c939e26cf0a29bf0c68726399c20 Author: Richard Eisenberg Date: Sun Dec 7 10:40:23 2014 -0500 Added comments to flattening-notes >--------------------------------------------------------------- d62957682d72c939e26cf0a29bf0c68726399c20 compiler/typecheck/Flattening-notes | 31 +++++++++++++++++++++++++++++++ 1 file changed, 31 insertions(+) diff --git a/compiler/typecheck/Flattening-notes b/compiler/typecheck/Flattening-notes index 6d6d20a..e7ac786 100644 --- a/compiler/typecheck/Flattening-notes +++ b/compiler/typecheck/Flattening-notes @@ -6,6 +6,8 @@ ToDo: * Consider individual data types for CFunEqCan etc * Collapse CNonCanonical and CIrredCan + * RAE: I think it would be better to split off CNonCanonical into its own + type, and remove it completely from Ct. Then, we would keep CIrredCan =========================== @@ -108,6 +110,7 @@ The idea is that S(fw,a)=a. But since fs>=fw, S(fw,a) = s, hence s=a. But now we have (a -fs-> a) in S, since fs>=fw we must have fs>=fs, and hence S is not inert. +RAE: I don't understand this lemma statement -- fs seems out of scope here. * (K1) plus (L1) guarantee that the extended substiution satisfies (WF). @@ -157,3 +160,31 @@ But if we kicked-out the inert item, we'd get Then rewrite the work-item gives us (a -W-> a), which is soluble via Refl. So we add one more clause to the kick-out criteria + +RAE: To prove that K3 is sufficient for completeness (as opposed to a rule that +looked for `a` *anywhere* on the RHS, not just at the top), we need this property: +All types in the inert set are "rigid". Here, rigid means that a type is one of +two things: a type that can equal only itself, or a type variable. Because the +inert set defines rewritings for type variables, a type variable can be considered +rigid because it will be rewritten only to a rigid type. + +In the current world, this rigidity property is true: all type families are +flattened away before adding equalities to the inert set. But, when we add +representational equality, that is no longer true! Newtypes are not rigid +w.r.t. representational equality. Accordingly, we would to change (K3) thus: + +(K3) If (b -fs-> s) is in S with (fw >= fs), then + (K3a) If the role of fs is nominal: s /= a + (K3b) If the role of fs is representational: EITHER + a not in s, OR + the path from the top of s to a includes at least one non-newtype + +RAE: Do we have evidence to support our belief that kicking out is bad? I can +imagine scenarios where kicking out *more* equalities is more efficient, in that +kicking out a Given, say, might then discover that the Given is reflexive and +thus can be dropped. Once this happens, then the Given is no longer used in +rewriting, making later flattenings faster. I tend to thing that, probably, +kicking out is something to avoid, but it would be nice to have data to support +this conclusion. And, that data is not terribly hard to produce: we can just +twiddle some settings and then time the testsuite in some sort of controlled +environment. From git at git.haskell.org Sun Dec 7 15:57:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 Dec 2014 15:57:52 +0000 (UTC) Subject: [commit: ghc] master: Add -I$1/$2/build/autogen to $1_$2_DIST_CC_OPTS (030ece4) Message-ID: <20141207155752.A794C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/030ece4ee0ef22f85a7b105b86dc102408a0df0f/ghc >--------------------------------------------------------------- commit 030ece4ee0ef22f85a7b105b86dc102408a0df0f Author: Herbert Valerio Riedel Date: Sun Dec 7 16:55:26 2014 +0100 Add -I$1/$2/build/autogen to $1_$2_DIST_CC_OPTS This is closer to how `cabal` behaves and is required for cbits to be able to `#include "cabal_macros.h"` >--------------------------------------------------------------- 030ece4ee0ef22f85a7b105b86dc102408a0df0f rules/distdir-opts.mk | 1 + 1 file changed, 1 insertion(+) diff --git a/rules/distdir-opts.mk b/rules/distdir-opts.mk index a252ce7..3126a88 100644 --- a/rules/distdir-opts.mk +++ b/rules/distdir-opts.mk @@ -51,6 +51,7 @@ $1_$2_DIST_GCC_CC_OPTS = \ $1_$2_DIST_CC_OPTS = \ $$(SRC_CC_OPTS) \ $$($1_CC_OPTS) \ + -I$1/$2/build/autogen \ $$(foreach dir,$$(filter-out /%,$$($1_$2_INCLUDE_DIRS)),-I$1/$$(dir)) \ $$(foreach dir,$$(filter /%,$$($1_$2_INCLUDE_DIRS)),-I$$(dir)) \ $$($1_$2_CC_OPTS) \ From git at git.haskell.org Sun Dec 7 19:09:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 Dec 2014 19:09:43 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Checkpoint in responding to Simon's comments (05cd77d) Message-ID: <20141207190943.06D8C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/05cd77d190feb6413402871e2b324d94ded0e790/ghc >--------------------------------------------------------------- commit 05cd77d190feb6413402871e2b324d94ded0e790 Author: Richard Eisenberg Date: Thu Dec 4 08:29:56 2014 -0500 Checkpoint in responding to Simon's comments >--------------------------------------------------------------- 05cd77d190feb6413402871e2b324d94ded0e790 compiler/typecheck/FamInst.lhs | 135 ++++++++++++++++++++++++++++++++++- compiler/typecheck/Inst.lhs | 7 ++ compiler/typecheck/TcCanonical.lhs | 38 ++++++++-- compiler/typecheck/TcErrors.lhs | 2 +- compiler/typecheck/TcEvidence.lhs | 139 +------------------------------------ compiler/typecheck/TcSMonad.lhs | 10 +-- 6 files changed, 183 insertions(+), 148 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 05cd77d190feb6413402871e2b324d94ded0e790 From git at git.haskell.org Sun Dec 7 19:09:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 Dec 2014 19:09:45 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Further reactions to SPJ's comments. This strikes nextRole. (0f493dd) Message-ID: <20141207190945.B720C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/0f493ddb89a6b068a8caa72d8365e21b6a1d5046/ghc >--------------------------------------------------------------- commit 0f493ddb89a6b068a8caa72d8365e21b6a1d5046 Author: Richard Eisenberg Date: Fri Dec 5 10:13:03 2014 -0500 Further reactions to SPJ's comments. This strikes nextRole. >--------------------------------------------------------------- 0f493ddb89a6b068a8caa72d8365e21b6a1d5046 compiler/deSugar/DsBinds.lhs | 4 +- compiler/typecheck/TcCanonical.lhs | 180 +++++++++++++++++++++---------------- compiler/typecheck/TcErrors.lhs | 14 +-- compiler/typecheck/TcEvidence.lhs | 88 +++++++++++++++++- compiler/typecheck/TcFlatten.lhs | 60 ++++++++----- compiler/typecheck/TcRnTypes.lhs | 3 + compiler/typecheck/TcType.lhs | 2 +- compiler/types/Coercion.hs | 26 +----- compiler/types/Type.hs | 15 +++- 9 files changed, 250 insertions(+), 142 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0f493ddb89a6b068a8caa72d8365e21b6a1d5046 From git at git.haskell.org Sun Dec 7 19:09:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 Dec 2014 19:09:48 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Done responding to SPJ's comments. Still getting the thing to compile. (8542d6c) Message-ID: <20141207190948.75E683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/8542d6c8d4f469c82dda2cdbb818d5257801e212/ghc >--------------------------------------------------------------- commit 8542d6c8d4f469c82dda2cdbb818d5257801e212 Author: Richard Eisenberg Date: Fri Dec 5 11:24:58 2014 -0500 Done responding to SPJ's comments. Still getting the thing to compile. >--------------------------------------------------------------- 8542d6c8d4f469c82dda2cdbb818d5257801e212 compiler/typecheck/FamInst.lhs | 42 ++++++++-------------- compiler/typecheck/TcEvidence.lhs | 37 +++++++------------- compiler/typecheck/TcFlatten.lhs | 12 +++---- compiler/types/Coercion.hs | 73 ++++++++++++++++++++++++++------------- compiler/types/FamInstEnv.hs | 31 ++++------------- compiler/types/Type.hs | 1 + 6 files changed, 89 insertions(+), 107 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8542d6c8d4f469c82dda2cdbb818d5257801e212 From git at git.haskell.org Sun Dec 7 19:09:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 Dec 2014 19:09:51 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Finished integrating SPJ's feedback. (9616426) Message-ID: <20141207190951.32D7D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/9616426649d2cef325f1e93466fe360579e423b0/ghc >--------------------------------------------------------------- commit 9616426649d2cef325f1e93466fe360579e423b0 Author: Richard Eisenberg Date: Fri Dec 5 14:14:06 2014 -0500 Finished integrating SPJ's feedback. >--------------------------------------------------------------- 9616426649d2cef325f1e93466fe360579e423b0 compiler/typecheck/TcExpr.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcExpr.lhs b/compiler/typecheck/TcExpr.lhs index 82c55d0..a1d9b6a 100644 --- a/compiler/typecheck/TcExpr.lhs +++ b/compiler/typecheck/TcExpr.lhs @@ -26,7 +26,7 @@ import TcUnify import BasicTypes import Inst import TcBinds -import FamInst ( tcGetFamInstEnvs ) +import FamInst ( tcGetFamInstEnvs, tcLookupDataFamInst ) import TcEnv import TcArrows import TcMatches From git at git.haskell.org Sun Dec 7 19:09:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 Dec 2014 19:09:53 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Spawn representational equalities from nominals less often. (4cdb10f) Message-ID: <20141207190953.C7A013A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/4cdb10f2429338d0d0b75b6efdb2638eb428314c/ghc >--------------------------------------------------------------- commit 4cdb10f2429338d0d0b75b6efdb2638eb428314c Author: Richard Eisenberg Date: Fri Dec 5 14:48:20 2014 -0500 Spawn representational equalities from nominals less often. Now, in canEqNC, not addInertCan. >--------------------------------------------------------------- 4cdb10f2429338d0d0b75b6efdb2638eb428314c compiler/typecheck/TcCanonical.lhs | 33 ++++++++++++++++++++++++++++++++- compiler/typecheck/TcSMonad.lhs | 33 +++------------------------------ 2 files changed, 35 insertions(+), 31 deletions(-) diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index 116cc52..b441a15 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -387,7 +387,38 @@ canHole ev occ hole_sort \begin{code} canEqNC :: CtEvidence -> EqRel -> Type -> Type -> TcS (StopOrContinue Ct) -canEqNC ev eq_rel ty1 ty2 = can_eq_nc ev eq_rel ty1 ty1 ty2 ty2 +canEqNC ev eq_rel ty1 ty2 + = can_eq_nc ev eq_rel ty1 ty1 ty2 ty2 + `andWhenContinue` \ ct -> + do { emitReprEq ct + ; continueWith ct } + +emitReprEq :: Ct -> TcS () +emitReprEq (CTyEqCan { cc_ev = ev, cc_tyvar = tv, cc_rhs = rhs + , cc_eq_rel = NomEq }) + | Just repr_ev <- sub_ev ev + = emitWorkNC [repr_ev] + where + repr_pred_ty = mkTcReprEqPred (mkTyVarTy tv) rhs + + -- input is a nominal CTyEqCan; output should be representational, + -- if possible + sub_ev :: CtEvidence -> Maybe CtEvidence + sub_ev (CtGiven { ctev_evtm = evtm, ctev_loc = loc }) + = Just $ CtGiven { ctev_pred = repr_pred_ty + , ctev_evtm = EvCoercion $ mkTcSubCo $ + evTermCoercion evtm + , ctev_loc = loc } + + sub_ev (CtDerived { ctev_loc = loc }) + = Just $ CtDerived { ctev_pred = repr_pred_ty + , ctev_loc = loc } + + -- don't include *wanted* nominal equalities! + sub_ev (CtWanted {}) = Nothing + +-- Nothing to do for representational equalities +emitReprEq _ = return () can_eq_nc :: CtEvidence diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index e2f2e26..89860ed 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -501,42 +501,15 @@ addInertCan :: InertCans -> Ct -> InertCans addInertCan ics item@(CTyEqCan { cc_eq_rel = eq_rel , cc_tyvar = tv , cc_rhs = rhs }) - = case (eq_rel, sub_ct item) of - (NomEq, Nothing) -> - ics { inert_eqs = add_eq (inert_eqs ics) item } - (NomEq, Just sub) -> - ics { inert_eqs = add_eq (inert_eqs ics) item - , inert_repr_eqs = add_eq (inert_repr_eqs ics) sub } - (ReprEq, _) -> - ics { inert_repr_eqs = add_eq (inert_repr_eqs ics) item } - + = case eq_rel of + NomEq -> ics { inert_eqs = add_eq (inert_eqs ics) item } + ReprEq -> ics { inert_repr_eqs = add_eq (inert_repr_eqs ics) item } where - repr_pred_ty = mkTcReprEqPred (mkTyVarTy tv) rhs - add_eq :: TyVarEnv EqualCtList -> Ct -> TyVarEnv EqualCtList add_eq old_list it = extendVarEnv_C (\old_eqs _new_eqs -> it : old_eqs) old_list (cc_tyvar it) [it] - -- input is a nominal CTyEqCan; output should be representational, - -- if possible - sub_ct :: Ct -> Maybe Ct - sub_ct ct = fmap (\ev -> ct { cc_ev = ev - , cc_eq_rel = ReprEq }) $ - case cc_ev ct of - CtGiven { ctev_evtm = evtm - , ctev_loc = loc } -> - Just (CtGiven { ctev_pred = repr_pred_ty - , ctev_evtm = EvCoercion $ mkTcSubCo $ - evTermCoercion evtm - , ctev_loc = loc }) - CtDerived { ctev_loc = loc } -> - Just (CtDerived { ctev_pred = repr_pred_ty - , ctev_loc = loc }) - -- don't include *wanted* nominal equalities! - CtWanted {} -> Nothing - - addInertCan ics item@(CFunEqCan { cc_fun = tc, cc_tyargs = tys }) = ics { inert_funeqs = insertFunEq (inert_funeqs ics) tc tys item } From git at git.haskell.org Sun Dec 7 19:09:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 Dec 2014 19:09:56 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Search through equalities when rewriting (7adf24e) Message-ID: <20141207190956.68C143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/7adf24eb072fd3cafbb7da4f4d11e5484982c6c0/ghc >--------------------------------------------------------------- commit 7adf24eb072fd3cafbb7da4f4d11e5484982c6c0 Author: Richard Eisenberg Date: Fri Dec 5 15:52:54 2014 -0500 Search through equalities when rewriting >--------------------------------------------------------------- 7adf24eb072fd3cafbb7da4f4d11e5484982c6c0 compiler/typecheck/TcFlatten.lhs | 10 ++++++---- compiler/typecheck/TcSMonad.lhs | 26 +++++++++++++------------- 2 files changed, 19 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcFlatten.lhs b/compiler/typecheck/TcFlatten.lhs index a070af5..4849332 100644 --- a/compiler/typecheck/TcFlatten.lhs +++ b/compiler/typecheck/TcFlatten.lhs @@ -32,6 +32,7 @@ import MonadUtils ( zipWithAndUnzipM ) import Bag import FastString import Control.Monad( when, liftM ) +import Data.List ( find ) \end{code} @@ -939,10 +940,11 @@ flattenTyVarOuter fmode tv -- See Note [Applying the inert substitution] do { ieqs <- getInertEqs (fe_eq_rel fmode) ; case lookupVarEnv ieqs tv of - Just (ct:_) -- If the first doesn't work, - -- the subsequent ones won't either - | CTyEqCan { cc_ev = ctev, cc_tyvar = tv, cc_rhs = rhs_ty } <- ct - , eqCanRewriteFlavour (ctEvFlavour ctev) (fe_flavour fmode) + Just cts + -- we need to search for one that can rewrite, because you + -- can have, for example, a Derived among a bunch of Wanteds + | Just (CTyEqCan { cc_ev = ctev, cc_tyvar = tv, cc_rhs = rhs_ty }) + <- find ((`eqCanRewriteFlavour` fe_flavour fmode) . ctFlavour) cts -> do { traceTcS "Following inert tyvar" (ppr tv <+> equals <+> ppr rhs_ty $$ ppr ctev) -- See Note [Flattener smelliness] ; return (Right (rhs_ty, mkTcSymCo (ctEvCoercion ctev), False)) } diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index 89860ed..da11cf9 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -423,16 +423,18 @@ data InertCans } type EqualCtList = [Ct] --- EqualCtList invariants: --- * All are equalities --- * All these equalities have the same LHS --- * The list is never empty --- * No element of the list can rewrite any other --- --- From the fourth invariant it follows that the list is --- - A single Given, or --- - Multiple Wanteds, or --- - Multiple Deriveds +{- +Note [EqualCtList invariants] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + * All are equalities + * All these equalities have the same LHS + * The list is never empty + * No element of the list can rewrite any other + + From the fourth invariant it follows that the list is + - A single Given, or + - Any number of Wanteds, along with 0 or 1 Derived +-} -- The Inert Set data InertSet @@ -498,9 +500,7 @@ emptyInert --------------- addInertCan :: InertCans -> Ct -> InertCans -- Precondition: item /is/ canonical -addInertCan ics item@(CTyEqCan { cc_eq_rel = eq_rel - , cc_tyvar = tv - , cc_rhs = rhs }) +addInertCan ics item@(CTyEqCan { cc_eq_rel = eq_rel }) = case eq_rel of NomEq -> ics { inert_eqs = add_eq (inert_eqs ics) item } ReprEq -> ics { inert_repr_eqs = add_eq (inert_repr_eqs ics) item } From git at git.haskell.org Sun Dec 7 19:09:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 Dec 2014 19:09:59 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Checkpoint in removing inert_repr_eqs (3e52f16) Message-ID: <20141207190959.1F3E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/3e52f161d90b2f9076b00d191f173a60c0cf6900/ghc >--------------------------------------------------------------- commit 3e52f161d90b2f9076b00d191f173a60c0cf6900 Author: Richard Eisenberg Date: Sun Dec 7 10:44:52 2014 -0500 Checkpoint in removing inert_repr_eqs >--------------------------------------------------------------- 3e52f161d90b2f9076b00d191f173a60c0cf6900 compiler/typecheck/TcCanonical.lhs | 27 ++--------- compiler/typecheck/TcFlatten.lhs | 59 ++++++++++++++++------- compiler/typecheck/TcInteract.lhs | 30 +++++------- compiler/typecheck/TcSMonad.lhs | 97 +++++--------------------------------- 4 files changed, 72 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 3e52f161d90b2f9076b00d191f173a60c0cf6900 From git at git.haskell.org Sun Dec 7 19:10:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 Dec 2014 19:10:01 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Finished removing inert_repr_eqs (2945111) Message-ID: <20141207191001.AFC203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/2945111811cc9bbc98ff573b2fdad9c27d780e79/ghc >--------------------------------------------------------------- commit 2945111811cc9bbc98ff573b2fdad9c27d780e79 Author: Richard Eisenberg Date: Sun Dec 7 11:31:15 2014 -0500 Finished removing inert_repr_eqs >--------------------------------------------------------------- 2945111811cc9bbc98ff573b2fdad9c27d780e79 compiler/typecheck/TcInteract.lhs | 8 +++--- compiler/typecheck/TcSMonad.lhs | 4 +-- testsuite/tests/deriving/should_fail/T7148.stderr | 30 +++++++++++++--------- testsuite/tests/deriving/should_fail/T7148a.stderr | 19 ++++++++------ 4 files changed, 36 insertions(+), 25 deletions(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index be60594..c95ebe2 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -43,6 +43,7 @@ import Pair (Pair(..)) import Unique( hasKey ) import FastString ( sLit ) import DynFlags +import Data.List ( find ) import Util \end{code} @@ -688,9 +689,10 @@ lookupFlattenTyVar :: TyVarEnv EqualCtList -> TcTyVar -> TcType -- ^ Look up a flatten-tyvar in the inert nominal TyVarEqs; -- this is used only when dealing with a CFunEqCan lookupFlattenTyVar inert_eqs ftv - = case lookupVarEnv inert_eqs ftv of - Just (CTyEqCan { cc_rhs = rhs } : _) -> rhs - _ -> mkTyVarTy ftv + -- TODO (RAE): This is fishy. Why only return one equality? + = case lookupVarEnv inert_eqs ftv >>= find ((== NomEq) . ctEqRel) of + Just (CTyEqCan { cc_rhs = rhs }) -> rhs + _ -> mkTyVarTy ftv reactFunEq :: CtEvidence -> TcTyVar -- From this :: F tys ~ fsk1 -> CtEvidence -> TcTyVar -- Solve this :: F tys ~ fsk2 diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index 3675082..0135893 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -592,7 +592,7 @@ getUnsolvedInerts :: TcS ( Bag Implication , Cts -- Insoluble , Cts ) -- All others getUnsolvedInerts - = do { IC { inert_eqs = tv_eqs + = do { IC { inert_eqs = tv_eqs , inert_funeqs = fun_eqs , inert_irreds = irreds, inert_dicts = idicts , inert_insols = insols } <- getInertCans @@ -748,7 +748,7 @@ removeInertCt is ct = 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 } + is { inert_eqs = delTyEq (inert_eqs is) x ty } CIrredEvCan {} -> panic "removeInertCt: CIrredEvCan" CNonCanonical {} -> panic "removeInertCt: CNonCanonical" diff --git a/testsuite/tests/deriving/should_fail/T7148.stderr b/testsuite/tests/deriving/should_fail/T7148.stderr index 4edb968..ba3a88b 100644 --- a/testsuite/tests/deriving/should_fail/T7148.stderr +++ b/testsuite/tests/deriving/should_fail/T7148.stderr @@ -1,14 +1,20 @@ -T7148a.hs:19:50: - Couldn't match representation of type ?b? with that of ?Result a b? - ?b? is a rigid type variable bound by - the type forall b1. Proxy b1 -> a -> Result a b1 at T7148a.hs:19:50 - arising from the coercion of the method ?coerce? - from type ?forall b. Proxy b -> a -> Result a b? - to type ?forall b. - Proxy b -> IS_NO_LONGER a -> Result (IS_NO_LONGER a) b? +T7148.hs:27:40: + Occurs check: cannot construct the infinite type: b ~ Tagged a b + arising from the coercion of the method ?iso2? + from type ?forall b. SameType b () -> SameType b b? + to type ?forall b. SameType b () -> SameType b (Tagged a b)? Relevant role signatures: - type role IS_NO_LONGER representational - type role Result nominal nominal - type role Proxy phantom - When deriving the instance for (Convert (IS_NO_LONGER a)) + type role Tagged phantom representational + type role SameType nominal nominal + When deriving the instance for (IsoUnit (Tagged a b)) + +T7148.hs:27:40: + Occurs check: cannot construct the infinite type: b ~ Tagged a b + arising from the coercion of the method ?iso1? + from type ?forall b. SameType () b -> SameType b b? + to type ?forall b. SameType () b -> SameType (Tagged a b) b? + Relevant role signatures: + type role Tagged phantom representational + type role SameType nominal nominal + When deriving the instance for (IsoUnit (Tagged a b)) diff --git a/testsuite/tests/deriving/should_fail/T7148a.stderr b/testsuite/tests/deriving/should_fail/T7148a.stderr index 5f865d1..4edb968 100644 --- a/testsuite/tests/deriving/should_fail/T7148a.stderr +++ b/testsuite/tests/deriving/should_fail/T7148a.stderr @@ -1,11 +1,14 @@ T7148a.hs:19:50: - Could not coerce from ?Result a b? to ?b? - because ?Result a b? and ?b? are different types. - arising from the coercion of the method ?coerce? from type - ?forall b. Proxy b -> a -> Result a b? to type - ?forall b. Proxy b -> IS_NO_LONGER a -> Result (IS_NO_LONGER a) b? - Possible fix: - use a standalone 'deriving instance' declaration, - so you can specify the instance context yourself + Couldn't match representation of type ?b? with that of ?Result a b? + ?b? is a rigid type variable bound by + the type forall b1. Proxy b1 -> a -> Result a b1 at T7148a.hs:19:50 + arising from the coercion of the method ?coerce? + from type ?forall b. Proxy b -> a -> Result a b? + to type ?forall b. + Proxy b -> IS_NO_LONGER a -> Result (IS_NO_LONGER a) b? + Relevant role signatures: + type role IS_NO_LONGER representational + type role Result nominal nominal + type role Proxy phantom When deriving the instance for (Convert (IS_NO_LONGER a)) From git at git.haskell.org Sun Dec 7 19:10:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 7 Dec 2014 19:10:04 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Some bugfixing. (894f1e4) Message-ID: <20141207191004.65A3C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/894f1e42f3a3ce1db303827620ff1ad25422a937/ghc >--------------------------------------------------------------- commit 894f1e42f3a3ce1db303827620ff1ad25422a937 Author: Richard Eisenberg Date: Sun Dec 7 14:10:02 2014 -0500 Some bugfixing. >--------------------------------------------------------------- 894f1e42f3a3ce1db303827620ff1ad25422a937 compiler/typecheck/FamInst.lhs | 23 +++--- compiler/typecheck/TcCanonical.lhs | 3 +- compiler/typecheck/TcErrors.lhs | 5 ++ compiler/typecheck/TcValidity.lhs | 3 +- compiler/types/Coercion.hs | 87 ++++++++++++++++------ compiler/types/FamInstEnv.hs | 12 +-- .../typecheck/should_fail/TcCoercibleFail.stderr | 11 ++- 7 files changed, 99 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 894f1e42f3a3ce1db303827620ff1ad25422a937 From git at git.haskell.org Mon Dec 8 03:42:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 03:42:41 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Remove stale comment to self (b9ffbc6) Message-ID: <20141208034241.B6BDF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/b9ffbc61ed9e27a785c4281564b8701a864ce37d/ghc >--------------------------------------------------------------- commit b9ffbc61ed9e27a785c4281564b8701a864ce37d Author: Richard Eisenberg Date: Sun Dec 7 14:11:41 2014 -0500 Remove stale comment to self >--------------------------------------------------------------- b9ffbc61ed9e27a785c4281564b8701a864ce37d compiler/typecheck/TcInteract.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index c95ebe2..51ce56b 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -1628,7 +1628,7 @@ doTopReactFunEq work_item@(CFunEqCan { cc_ev = old_ev, cc_fun = fam_tc try_improvement | Just ops <- isBuiltInSynFamTyCon_maybe fam_tc - = do { inert_eqs <- getInertEqs -- TODO (RAE): I was here. Are the roles OK? + = do { inert_eqs <- getInertEqs ; let eqns = sfInteractTop ops args (lookupFlattenTyVar inert_eqs fsk) ; mapM_ (emitNewDerivedEq loc) eqns } | otherwise From git at git.haskell.org Mon Dec 8 03:42:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 03:42:45 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Merge commit '668a137' into wip/rae-new-coercible (7f722dd) Message-ID: <20141208034245.5A3933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/7f722dda26eb4ee252bc8ef66c914935087cea72/ghc >--------------------------------------------------------------- commit 7f722dda26eb4ee252bc8ef66c914935087cea72 Merge: b9ffbc6 668a137 Author: Richard Eisenberg Date: Sun Dec 7 14:23:30 2014 -0500 Merge commit '668a137' into wip/rae-new-coercible >--------------------------------------------------------------- 7f722dda26eb4ee252bc8ef66c914935087cea72 aclocal.m4 | 3 +- compiler/ghc.mk | 3 - compiler/hsSyn/HsTypes.lhs | 2 +- compiler/parser/Parser.y | 10 +- compiler/rename/RnExpr.lhs | 4 +- compiler/typecheck/TcTyDecls.lhs | 9 +- compiler/types/TyCon.hs | 203 ++++++++++++++++----------- compiler/vectorise/Vectorise/Utils/Base.hs | 6 +- compiler/vectorise/Vectorise/Utils/PADict.hs | 3 +- docs/users_guide/7.10.1-notes.xml | 6 +- includes/rts/Linker.h | 3 - libraries/base/Data/Word.hs | 6 +- rts/CheckUnload.c | 4 - rts/Linker.c | 175 ++++++++--------------- rts/LinkerInternals.h | 4 - testsuite/tests/generics/T5462No1.stderr | 4 +- testsuite/tests/generics/all.T | 6 +- testsuite/tests/polykinds/T7908.hs | 49 +++++++ testsuite/tests/polykinds/all.T | 2 +- testsuite/tests/rts/Makefile | 8 +- testsuite/tests/rts/T2615.hs | 1 - testsuite/tests/rts/linker_unload.c | 37 ----- testsuite/tests/rts/linker_unload.stdout | 2 +- testsuite/tests/rts/rdynamic.hs | 2 - 24 files changed, 259 insertions(+), 293 deletions(-) From git at git.haskell.org Mon Dec 8 03:42:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 03:42:48 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Merge commit '26a3d0f' into wip/rae-new-coercible (1b8a6d7) Message-ID: <20141208034248.B3B993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/1b8a6d7eaa3cfe91e3864a7a6ef38209734b7d58/ghc >--------------------------------------------------------------- commit 1b8a6d7eaa3cfe91e3864a7a6ef38209734b7d58 Merge: 7f722dd 26a3d0f Author: Richard Eisenberg Date: Sun Dec 7 14:26:35 2014 -0500 Merge commit '26a3d0f' into wip/rae-new-coercible Conflicts: compiler/typecheck/TcErrors.lhs compiler/typecheck/TcInteract.lhs >--------------------------------------------------------------- 1b8a6d7eaa3cfe91e3864a7a6ef38209734b7d58 compiler/typecheck/TcBinds.lhs | 8 +-- compiler/typecheck/TcCanonical.lhs | 4 +- compiler/typecheck/TcErrors.lhs | 4 +- compiler/typecheck/TcFlatten.lhs | 14 ++--- compiler/typecheck/TcInteract.lhs | 30 +++++----- compiler/typecheck/TcMType.lhs | 4 +- compiler/typecheck/TcPatSyn.lhs | 8 +-- compiler/typecheck/TcRnDriver.lhs | 6 +- compiler/typecheck/TcRnMonad.lhs | 34 +++++------ compiler/typecheck/TcRnTypes.lhs | 16 ++--- compiler/typecheck/TcRules.lhs | 4 +- compiler/typecheck/TcSMonad.lhs | 38 ++++++------ compiler/typecheck/TcSimplify.lhs | 62 +++++++++---------- compiler/typecheck/TcType.lhs | 118 +++++++++++++++++++------------------ compiler/typecheck/TcUnify.lhs | 10 ++-- 15 files changed, 181 insertions(+), 179 deletions(-) diff --cc compiler/typecheck/TcErrors.lhs index 0b130df,c8406df..94623d8 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@@ -876,8 -792,8 +876,8 @@@ mkTyVarEqErr dflags ctxt extra ct orien -- Nastiest case: attempt to unify an untouchable variable | (implic:_) <- cec_encl ctxt -- Get the innermost context , Implic { ic_env = env, ic_given = given, ic_info = skol_info } <- implic - = do { let msg = misMatchMsg oriented ty1 ty2 + = do { let msg = misMatchMsg oriented eq_rel ty1 ty2 - untch_extra + tclvl_extra = nest 2 $ sep [ quotes (ppr tv1) <+> ptext (sLit "is untouchable") , nest 2 $ ptext (sLit "inside the constraints") <+> pprEvVarTheta given diff --cc compiler/typecheck/TcInteract.lhs index 51ce56b,bfe470d..ebac310 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@@ -830,23 -829,21 +830,23 @@@ interactTyVarEq inerts workItem@(CTyEqC ; stopWith ev "Solved from inert (r)" } | otherwise - = do { untch <- getUntouchables - ; if canSolveByUnification untch ev eq_rel tv rhs + = do { tclvl <- getTcLevel - ; if canSolveByUnification tclvl ev tv rhs ++ ; if canSolveByUnification tclvl ev eq_rel tv rhs then do { solveByUnification ev tv rhs - ; n_kicked <- kickOutRewritable givenFlavour tv - -- givenFlavour because the tv := xi is given + ; n_kicked <- kickOutRewritable Given NomEq tv + -- Given because the tv := xi is given + -- NomEq because only nominal equalities are solved + -- by unification ; return (Stop ev (ptext (sLit "Spontaneously solved") <+> ppr_kicked n_kicked)) } else do { traceTcS "Can't solve tyvar equality" (vcat [ text "LHS:" <+> ppr tv <+> dcolon <+> ppr (tyVarKind tv) , ppWhen (isMetaTyVar tv) $ - nest 4 (text "Untouchable level of" <+> ppr tv - <+> text "is" <+> ppr (metaTyVarUntouchables tv)) + nest 4 (text "TcLevel of" <+> ppr tv + <+> text "is" <+> ppr (metaTyVarTcLevel tv)) , text "RHS:" <+> ppr rhs <+> dcolon <+> ppr (typeKind rhs) - , text "Untouchables =" <+> ppr untch ]) + , text "TcLevel =" <+> ppr tclvl ]) - ; n_kicked <- kickOutRewritable ev tv + ; n_kicked <- kickOutRewritable (ctEvFlavour ev) (ctEvEqRel ev) tv ; updInertCans (\ ics -> addInertCan ics workItem) ; return (Stop ev (ptext (sLit "Kept as inert") <+> ppr_kicked n_kicked)) } } @@@ -855,12 -852,8 +855,12 @@@ interactTyVarEq _ wi = pprPanic "intera -- @trySpontaneousSolve wi@ solves equalities where one side is a -- touchable unification variable. -- Returns True <=> spontaneous solve happened - canSolveByUnification :: Untouchables -> CtEvidence -> EqRel -canSolveByUnification :: TcLevel -> CtEvidence -> TcTyVar -> Xi -> Bool -canSolveByUnification tclvl gw tv xi ++canSolveByUnification :: TcLevel -> CtEvidence -> EqRel + -> TcTyVar -> Xi -> Bool - canSolveByUnification untch gw eq_rel tv xi ++canSolveByUnification tclvl gw eq_rel tv xi + | ReprEq <- eq_rel -- we never solve representational equalities this way. + = False + | isGiven gw -- See Note [Touchables and givens] = False @@@ -1988,12 -1983,20 +1988,12 @@@ matchClassInst _ clas [ ty ] = panicTcS (text "Unexpected evidence for" <+> ppr (className clas) $$ vcat (map (ppr . idType) (classMethods clas))) -matchClassInst _ clas [ _k, ty1, ty2 ] loc - | clas == coercibleClass - = do { traceTcS "matchClassInst for" $ - quotes (pprClassPred clas [ty1,ty2]) <+> text "at depth" <+> ppr (ctLocDepth loc) - ; ev <- getCoercibleInst loc ty1 ty2 - ; traceTcS "matchClassInst returned" $ ppr ev - ; return ev } - matchClassInst inerts clas tys loc = do { dflags <- getDynFlags - ; untch <- getUntouchables + ; tclvl <- getTcLevel ; traceTcS "matchClassInst" $ vcat [ text "pred =" <+> ppr pred , text "inerts=" <+> ppr inerts - , text "untouchables=" <+> ppr untch ] + , text "untouchables=" <+> ppr tclvl ] ; instEnvs <- getInstEnvs ; case lookupInstEnv instEnvs clas tys of ([], _, _) -- Nothing matches From git at git.haskell.org Mon Dec 8 03:42:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 03:42:52 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Merge commit 'bafba11' into wip/rae-new-coercible (85db007) Message-ID: <20141208034252.D238F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/85db007fed4b8a3396d4713ad08e75bc95e1405c/ghc >--------------------------------------------------------------- commit 85db007fed4b8a3396d4713ad08e75bc95e1405c Merge: 1b8a6d7 bafba11 Author: Richard Eisenberg Date: Sun Dec 7 14:29:25 2014 -0500 Merge commit 'bafba11' into wip/rae-new-coercible Conflicts: compiler/basicTypes/DataCon.hs compiler/utils/Util.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 85db007fed4b8a3396d4713ad08e75bc95e1405c From git at git.haskell.org Mon Dec 8 03:42:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 03:42:56 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Merge commit 'b57ff27' into wip/rae-new-coercible (fb10b82) Message-ID: <20141208034256.82C803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/fb10b827e6cefd82f96c66b2cb697f016fe4a48c/ghc >--------------------------------------------------------------- commit fb10b827e6cefd82f96c66b2cb697f016fe4a48c Merge: 85db007 b57ff27 Author: Richard Eisenberg Date: Sun Dec 7 14:46:47 2014 -0500 Merge commit 'b57ff27' into wip/rae-new-coercible Conflicts: compiler/typecheck/FamInst.hs compiler/typecheck/FunDeps.hs compiler/typecheck/TcCanonical.hs compiler/typecheck/TcErrors.hs compiler/typecheck/TcEvidence.hs compiler/typecheck/TcFlatten.hs compiler/typecheck/TcInteract.hs compiler/typecheck/TcRnTypes.hs compiler/typecheck/TcSMonad.hs compiler/typecheck/TcType.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 fb10b827e6cefd82f96c66b2cb697f016fe4a48c From git at git.haskell.org Mon Dec 8 03:42:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 03:42:59 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Merge commit '4d5f83a' into wip/rae-new-coercible (c336539) Message-ID: <20141208034259.E35803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/c3365399437c16ccabe7818bba3d23891680c78d/ghc >--------------------------------------------------------------- commit c3365399437c16ccabe7818bba3d23891680c78d Merge: fb10b82 4d5f83a Author: Richard Eisenberg Date: Sun Dec 7 14:47:25 2014 -0500 Merge commit '4d5f83a' into wip/rae-new-coercible >--------------------------------------------------------------- c3365399437c16ccabe7818bba3d23891680c78d compiler/deSugar/{Check.lhs => Check.hs} | 74 +++++++------- compiler/deSugar/{Coverage.lhs => Coverage.hs} | 48 ++++----- compiler/deSugar/{Desugar.lhs => Desugar.hs} | 75 +++++++-------- compiler/deSugar/{DsArrows.lhs => DsArrows.hs} | 74 ++++++-------- compiler/deSugar/{DsBinds.lhs => DsBinds.hs} | 62 ++++++------ compiler/deSugar/{DsCCall.lhs => DsCCall.hs} | 20 ++-- compiler/deSugar/{DsExpr.lhs => DsExpr.hs} | 93 ++++++++---------- .../deSugar/{DsExpr.lhs-boot => DsExpr.hs-boot} | 2 - compiler/deSugar/{DsForeign.lhs => DsForeign.hs} | 83 ++++++++-------- compiler/deSugar/{DsGRHSs.lhs => DsGRHSs.hs} | 36 ++++--- compiler/deSugar/{DsListComp.lhs => DsListComp.hs} | 73 ++++++-------- compiler/deSugar/{DsMonad.lhs => DsMonad.hs} | 63 +++++------- .../deSugar/{DsMonad.lhs-boot => DsMonad.hs-boot} | 5 +- compiler/deSugar/{DsUtils.lhs => DsUtils.hs} | 94 +++++++++--------- compiler/deSugar/{Match.lhs => Match.hs} | 107 ++++++++++----------- compiler/deSugar/{Match.lhs-boot => Match.hs-boot} | 2 - compiler/deSugar/{MatchCon.lhs => MatchCon.hs} | 19 ++-- compiler/deSugar/{MatchLit.lhs => MatchLit.hs} | 93 +++++++++--------- 18 files changed, 453 insertions(+), 570 deletions(-) From git at git.haskell.org Mon Dec 8 03:43:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 03:43:03 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Merge remote-tracking branch 'origin/master' into wip/rae-new-coercible (ed2aed8) Message-ID: <20141208034303.A51EE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/ed2aed88bfff9e1ac9f78211f9cc88424f1e828b/ghc >--------------------------------------------------------------- commit ed2aed88bfff9e1ac9f78211f9cc88424f1e828b Merge: c336539 030ece4 Author: Richard Eisenberg Date: Sun Dec 7 14:47:44 2014 -0500 Merge remote-tracking branch 'origin/master' into wip/rae-new-coercible >--------------------------------------------------------------- ed2aed88bfff9e1ac9f78211f9cc88424f1e828b compiler/coreSyn/TrieMap.hs | 7 + compiler/main/CmdLineParser.hs | 12 -- compiler/main/DynFlags.hs | 31 ++-- compiler/rename/RnEnv.hs | 12 +- compiler/typecheck/Flattening-notes | 181 +++++++++++++++++++++ compiler/typecheck/TcInteract.hs | 47 ++++-- compiler/types/Unify.hs | 15 +- docs/users_guide/7.10.1-notes.xml | 6 +- docs/users_guide/flags.xml | 7 + docs/users_guide/using.xml | 56 +++++-- includes/rts/Linker.h | 3 + libraries/Cabal | 2 +- libraries/base/Data/Either.hs | 6 +- libraries/base/Data/Foldable.hs | 40 +++-- libraries/base/Data/Traversable.hs | 23 ++- libraries/base/Data/Type/Bool.hs | 30 ++-- libraries/base/Data/Type/Equality.hs | 34 ++-- libraries/base/Foreign/Marshal/Alloc.hs | 18 ++ libraries/base/Foreign/Marshal/Array.hs | 19 ++- libraries/base/GHC/TypeLits.hs | 10 +- libraries/base/System/Posix/Internals.hs | 2 +- libraries/base/changelog.md | 4 + libraries/unix | 2 +- rts/CheckUnload.c | 4 + rts/Linker.c | 179 +++++++++++++------- rts/LinkerInternals.h | 4 + rules/distdir-opts.mk | 1 + testsuite/tests/cabal/cabal06/Makefile | 4 +- testsuite/tests/rename/should_compile/T9778.hs | 8 + testsuite/tests/rename/should_compile/T9778.stderr | 3 + testsuite/tests/rename/should_compile/all.T | 1 + testsuite/tests/rts/Makefile | 8 +- testsuite/tests/rts/T2615.hs | 1 + testsuite/tests/rts/all.T | 1 + testsuite/tests/rts/linker_unload.c | 37 +++++ testsuite/tests/rts/linker_unload.stdout | 2 +- testsuite/tests/rts/rdynamic.hs | 2 + 37 files changed, 637 insertions(+), 185 deletions(-) From git at git.haskell.org Mon Dec 8 03:43:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 03:43:06 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Compile; fix a testsuite failure. (c9c42b1) Message-ID: <20141208034306.427A23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/c9c42b16819f34faf7558328d7036844132973ff/ghc >--------------------------------------------------------------- commit c9c42b16819f34faf7558328d7036844132973ff Author: Richard Eisenberg Date: Sun Dec 7 22:42:50 2014 -0500 Compile; fix a testsuite failure. >--------------------------------------------------------------- c9c42b16819f34faf7558328d7036844132973ff compiler/typecheck/TcCanonical.hs | 12 ++++-------- testsuite/tests/indexed-types/should_fail/T9580.stderr | 1 + 2 files changed, 5 insertions(+), 8 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 9cc847e..abca349 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -569,8 +569,7 @@ can_eq_flat_app ev eq_rel swapped s1 t1 ps_ty1 ty2 ps_ty2 ; xCtEvidence ev (XEvTerm [mkTcEqPred s1 s2, mkTcEqPred t1 t2] xevcomp xevdecomp) ; stopWith ev "Decomposed AppTy" } -\end{code} - +{- Note [Eager reflexivity check] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Suppose we have @@ -613,8 +612,7 @@ we do a reflexivity check. (This would be sound in the nominal case, but unnecessary, and I [Richard E.] am worried that it would slow down the common case.) - -\begin{code} +-} ------------------------ -- | We're able to unwrap a newtype. Update the bits accordingly. @@ -683,8 +681,7 @@ canDecomposableTyConApp ev eq_rel tc1 tys1 tc2 tys2 = do { traceTcS "canDecomposableTyConApp" (ppr ev $$ ppr eq_rel $$ ppr tc1 $$ ppr tys1 $$ ppr tys2) ; canDecomposableTyConAppOK ev eq_rel tc1 tys1 tys2 } -\end{code} - +{- Note [Use canEqFailure in canDecomposableTyConApp] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We must use canEqFailure, not canEqHardFailure here, because there is @@ -715,8 +712,7 @@ or reinsert them back in appropriately. The alternative to this is to have the solver be aware of phantoms and solve them in a top-level reaction. That somehow seems worse than just a little fiddliness right here. - -\begin{code} +-} canDecomposableTyConAppOK :: CtEvidence -> EqRel -> TyCon -> [TcType] -> [TcType] diff --git a/testsuite/tests/indexed-types/should_fail/T9580.stderr b/testsuite/tests/indexed-types/should_fail/T9580.stderr index f3a884e..fdb457a 100644 --- a/testsuite/tests/indexed-types/should_fail/T9580.stderr +++ b/testsuite/tests/indexed-types/should_fail/T9580.stderr @@ -4,6 +4,7 @@ T9580.hs:7:9: Couldn't match representation of type ?Double? with that of ?Dimensional Int Double? + Relevant role signatures: type role Dimensional nominal nominal The data constructor ?T9580a.Quantity'? of newtype ?Dimensional Int v? is not in scope In the expression: coerce x From git at git.haskell.org Mon Dec 8 03:43:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 03:43:08 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible's head updated: Compile; fix a testsuite failure. (c9c42b1) Message-ID: <20141208034308.B8F153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/rae-new-coercible' now includes: 370b0f5 Remove references to Parser.y.pp c34ef46 Test Trac #7908 1d32a85 Fix parser for UNPACK pragmas 2d324dd Fix malformed `configure` script a29e295 Mention existence of 'Natural' in "Data.Word" 9437a24 Uncomment the instance signatures, to activate the test 7932b2a Revert "Add purgeObj() to remove the symbol table entries for an object" 4b51194 Revert "Make the linker API thread-safe" 06eaa64 Fix test suite race on T5462 (solves intermittent T5462Yes1/T5462Yes2/T5462No1 failure) 5d9bb56 Comments and formatting in TyCon 668a137 Remove references to SynTyCon. Fixes #9812 26a3d0f Rename Untouchables to TcLevel 30d2605 Test Trac #4921 2a67fb3 Minor refactoring of Edward's recent orphans patch (Trac #2182) 863854a Fix another bug in deriving( Data ) for data families; Trac #4896 c41d214 Unique-ify the names of top-level auxiliary bindings in derived instances (Trac #7947) 6b063ef Make Natural's (.|.) really an OR operation (#9818) 7c38e98 Make `read . show = id` for Data.Fixed (fix #9240) bf2d754 Declare official GitHub home of libraries/parallel 46b278f Generate real (but empty) object files for signatures. cce292b Update 32-bit performace numbers (has not been done for ages) 289e52f Make annotations test case cleaning less aggressive bc9e81c Comments only 1389ff5 compiler: de-lhs main/ dc00fb1 compiler: de-lhs prelude/ 9fc4382 compiler: de-lhs rename/ b04296d compiler: de-lhs coreSyn/ 0c48e17 compiler: de-lhs utils/ 10fdf27 compiler: de-lhs iface/ 29a5210 compiler: de-lhs specialise/ a56fe4a compiler: de-lhs basicTypes/ b9b1fab compiler: de-lhs hsSyn/ 6ecd27e compiler: de-lhs simplCore/ 612e573 compiler: de-lhs stgSyn/ bafba11 compiler: de-lhs simplStg/ b57ff27 compiler: de-lhs typecheck/ 4d5f83a compiler: de-lhs deSugar/ cc071ec Comments on TrieMap and unifier. d6f9276 Prevent solveFlatWanteds from losing insolubles when using typechecker plugins 78edd76 Cabal submodule update 55a2a0b Revert "Revert "Make the linker API thread-safe"" a48bee9 Revert "Revert "Add purgeObj() to remove the symbol table entries for an object"" 09af720 Disable T8124 on Windows (uses pthreads) 9a10107 Add notes about the inert CTyEqCans 87160c1 renamer: fix trac issue #9778 3ebe304 docs: Update to reflect reality 7cd6806 Add -fwarn-unticked-promoted-constructors to -Wall da98592 msse flag handling: fix trac issue #9777 08610c1 Implement `calloc{,Bytes,Array,Array0}` allocators d80022d Add references between Data.Traversable.for and Data.Foldable.for_ and co. 9a1779e Portability: wc -l sometimes has leading spaces, trim them off. 7383ce9 Add ticket-ref to changelog entry (fup to 08610c1) b9f636b Set proper `CTYPE` for POSIX `CGroup` 334cb10 Update `unix` submodule to latest snapshot d629576 Added comments to flattening-notes 030ece4 Add -I$1/$2/build/autogen to $1_$2_DIST_CC_OPTS b9ffbc6 Remove stale comment to self 7f722dd Merge commit '668a137' into wip/rae-new-coercible 1b8a6d7 Merge commit '26a3d0f' into wip/rae-new-coercible 85db007 Merge commit 'bafba11' into wip/rae-new-coercible fb10b82 Merge commit 'b57ff27' into wip/rae-new-coercible c336539 Merge commit '4d5f83a' into wip/rae-new-coercible ed2aed8 Merge remote-tracking branch 'origin/master' into wip/rae-new-coercible c9c42b1 Compile; fix a testsuite failure. From git at git.haskell.org Mon Dec 8 08:31:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 08:31:04 +0000 (UTC) Subject: [commit: ghc] master: Remove `inline` from integer_gmp_mpn_import1() (e74a9e9) Message-ID: <20141208083104.EA5513A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e74a9e994160f812fb6aba57feff691bd0676bbe/ghc >--------------------------------------------------------------- commit e74a9e994160f812fb6aba57feff691bd0676bbe Author: Herbert Valerio Riedel Date: Mon Dec 8 09:31:19 2014 +0100 Remove `inline` from integer_gmp_mpn_import1() This would cause problems w/ BuildFlavour=quickest >--------------------------------------------------------------- e74a9e994160f812fb6aba57feff691bd0676bbe libraries/integer-gmp2/cbits/wrappers.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/integer-gmp2/cbits/wrappers.c b/libraries/integer-gmp2/cbits/wrappers.c index 0557ff7..cf28e29 100644 --- a/libraries/integer-gmp2/cbits/wrappers.c +++ b/libraries/integer-gmp2/cbits/wrappers.c @@ -417,7 +417,7 @@ integer_gmp_mpn_export1(const mp_limb_t s, * * We can't use GMP's 'mpz_import()' */ -inline HsWord +HsWord integer_gmp_mpn_import1(const uint8_t *srcptr, const HsWord srcofs, const HsWord srclen, const HsInt msbf) { From git at git.haskell.org Mon Dec 8 15:02:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 15:02:05 +0000 (UTC) Subject: [commit: ghc] master: Comments only (7535c83) Message-ID: <20141208150205.39DF83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7535c83b600792fe03235d2da0a6affcbfddde4b/ghc >--------------------------------------------------------------- commit 7535c83b600792fe03235d2da0a6affcbfddde4b Author: Simon Peyton Jones Date: Thu Dec 4 11:03:49 2014 +0000 Comments only >--------------------------------------------------------------- 7535c83b600792fe03235d2da0a6affcbfddde4b libraries/base/GHC/Int.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/libraries/base/GHC/Int.hs b/libraries/base/GHC/Int.hs index 5cb6ceb..f9d5bbe 100644 --- a/libraries/base/GHC/Int.hs +++ b/libraries/base/GHC/Int.hs @@ -897,10 +897,9 @@ instance Ix Int64 where inRange (m,n) i = m <= i && i <= n -{- -Note [Order of tests] - -Suppose we had a definition like: +{- Note [Order of tests] +~~~~~~~~~~~~~~~~~~~~~~~~~ +(See Trac #3065, #5161.) Suppose we had a definition like: quot x y | y == 0 = divZeroError From git at git.haskell.org Mon Dec 8 15:02:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 15:02:07 +0000 (UTC) Subject: [commit: ghc] master: Optimise partitionFunEqs for the 'false' case (37c2ed4) Message-ID: <20141208150207.E24C63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/37c2ed4bc3d4ff0a4681e9d27c7f748886e413f6/ghc >--------------------------------------------------------------- commit 37c2ed4bc3d4ff0a4681e9d27c7f748886e413f6 Author: Simon Peyton Jones Date: Mon Dec 8 11:50:21 2014 +0000 Optimise partitionFunEqs for the 'false' case In the examples from Trac #9872 we were getting a large set of inert CFunEqCans, and partitioning them was taking ages. This patch improves it somewhat by optimising the partition for the case where the predicat is false. The ticket has more info. >--------------------------------------------------------------- 37c2ed4bc3d4ff0a4681e9d27c7f748886e413f6 compiler/typecheck/TcSMonad.hs | 22 ++++++++++++++-------- 1 file changed, 14 insertions(+), 8 deletions(-) diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index 4775394..ffdfb27 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -960,17 +960,23 @@ filterFunEqs = filterTcAppMap insertFunEq :: FunEqMap a -> TyCon -> [Type] -> a -> FunEqMap a insertFunEq m tc tys val = insertTcApp m (getUnique tc) tys val -insertFunEqCt :: FunEqMap Ct -> Ct -> FunEqMap Ct -insertFunEqCt m ct@(CFunEqCan { cc_fun = tc, cc_tyargs = tys }) - = insertFunEq m tc tys ct -insertFunEqCt _ ct = pprPanic "insertFunEqCt" (ppr ct) +-- insertFunEqCt :: FunEqMap Ct -> Ct -> FunEqMap Ct +-- insertFunEqCt m ct@(CFunEqCan { cc_fun = tc, cc_tyargs = tys }) +-- = insertFunEq m tc tys ct +-- insertFunEqCt _ ct = pprPanic "insertFunEqCt" (ppr ct) partitionFunEqs :: (Ct -> Bool) -> FunEqMap Ct -> (Bag Ct, FunEqMap Ct) -partitionFunEqs f m = foldTcAppMap k m (emptyBag, emptyFunEqs) +-- Optimise for the case where the predicate is false +-- partitionFunEqs is called only from kick-out, and kick-out usually +-- kicks out very few equalities, so we want to optimise for that case +partitionFunEqs f m = (yeses, foldrBag del m yeses) where - k ct (yeses, noes) - | f ct = (yeses `snocBag` ct, noes) - | otherwise = (yeses, insertFunEqCt noes ct) + yeses = foldTcAppMap k m emptyBag + k ct yeses | f ct = yeses `snocBag` ct + | otherwise = yeses + del (CFunEqCan { cc_fun = tc, cc_tyargs = tys }) m + = delFunEq m tc tys + del ct _ = pprPanic "partitionFunEqs" (ppr ct) delFunEq :: FunEqMap a -> TyCon -> [Type] -> FunEqMap a delFunEq m tc tys = delTcApp m (getUnique tc) tys From git at git.haskell.org Mon Dec 8 15:02:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 15:02:10 +0000 (UTC) Subject: [commit: ghc] master: Revise the inert-set invariants again (1d44261) Message-ID: <20141208150210.94AD73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1d44261c01fe2b8e455ed454e7c4b49d26c433b2/ghc >--------------------------------------------------------------- commit 1d44261c01fe2b8e455ed454e7c4b49d26c433b2 Author: Simon Peyton Jones Date: Mon Dec 8 13:23:31 2014 +0000 Revise the inert-set invariants again In particular this patch - Accepts that rewriting with the inert CTyEqCans should be done recursively (hence removing the Bool result from flattenTyVarOuter) - Refines the kick-out criterion, in paticular to avoid kick-out of (a -f-> ty) when f cannot rewrite f. This is true of Wanteds and hence reduces kick-outs of Wanteds, perhaps by a lot This stuff is not fully documented because the details are still settling, but it's looking good. (And it validates.) This patch includes the testsuite wibbles. perf/compiler/T5030 and T5837 both improve in bytes-allocated (by 11% and 13% resp), which is good. I'm not sure which of today's short series of patches is responsible, nor do I mind much. (One could find out if necessary.) >--------------------------------------------------------------- 1d44261c01fe2b8e455ed454e7c4b49d26c433b2 compiler/typecheck/TcCanonical.hs | 2 +- compiler/typecheck/TcFlatten.hs | 22 +++++++++----------- compiler/typecheck/TcInteract.hs | 24 +++++++++++++++++----- .../tests/indexed-types/should_compile/GADT1.hs | 14 +++++++++++++ testsuite/tests/perf/compiler/all.T | 6 ++++-- .../typecheck/should_fail/FrozenErrorTests.stderr | 2 +- testsuite/tests/typecheck/should_fail/T7856.hs | 4 ++-- testsuite/tests/typecheck/should_fail/T8603.stderr | 2 +- 8 files changed, 52 insertions(+), 24 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1d44261c01fe2b8e455ed454e7c4b49d26c433b2 From git at git.haskell.org Mon Dec 8 15:02:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 15:02:13 +0000 (UTC) Subject: [commit: ghc] master: Comments and variable names only, in type checking of (e1 $ e2) (d64e682) Message-ID: <20141208150213.3707C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d64e682824631bc2a424f40b2776a2fbf457d122/ghc >--------------------------------------------------------------- commit d64e682824631bc2a424f40b2776a2fbf457d122 Author: Simon Peyton Jones Date: Mon Dec 8 13:10:05 2014 +0000 Comments and variable names only, in type checking of (e1 $ e2) No change in behaviour >--------------------------------------------------------------- d64e682824631bc2a424f40b2776a2fbf457d122 compiler/typecheck/TcExpr.hs | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs index 763be05..9503d2b 100644 --- a/compiler/typecheck/TcExpr.hs +++ b/compiler/typecheck/TcExpr.hs @@ -314,29 +314,29 @@ tcExpr (OpApp arg1 op fix arg2) res_ty ; let doc = ptext (sLit "The first argument of ($) takes") ; (co_arg1, [arg2_ty], op_res_ty) <- matchExpectedFunTys doc 1 arg1_ty - -- arg1_ty = arg2_ty -> op_res_ty - -- And arg2_ty maybe polymorphic; that's the point + + -- We have (arg1 $ arg2) + -- So: arg1_ty = arg2_ty -> op_res_ty + -- where arg2_ty maybe polymorphic; that's the point + + ; arg2' <- tcArg op (arg2, arg2_ty, 2) + ; co_b <- unifyType op_res_ty res_ty -- op_res ~ res -- Make sure that the argument type has kind '*' + -- ($) :: forall (a2:*) (r:Open). (a2->r) -> a2 -> r -- Eg we do not want to allow (D# $ 4.0#) Trac #5570 -- (which gives a seg fault) -- We do this by unifying with a MetaTv; but of course -- it must allow foralls in the type it unifies with (hence ReturnTv)! -- - -- The result type can have any kind (Trac #8739), - -- so we can just use res_ty - - -- ($) :: forall (a:*) (b:Open). (a->b) -> a -> b - ; a_tv <- newReturnTyVar liftedTypeKind - ; let a_ty = mkTyVarTy a_tv + -- The *result* type can have any kind (Trac #8739), + -- so we don't need to check anything for that + ; a2_tv <- newReturnTyVar liftedTypeKind + ; let a2_ty = mkTyVarTy a2_tv + ; co_a <- unifyType arg2_ty a2_ty -- arg2 ~ a2 - ; arg2' <- tcArg op (arg2, arg2_ty, 2) - - ; co_a <- unifyType arg2_ty a_ty -- arg2 ~ a - ; co_b <- unifyType op_res_ty res_ty -- op_res ~ res ; op_id <- tcLookupId op_name - - ; let op' = L loc (HsWrap (mkWpTyApps [a_ty, res_ty]) (HsVar op_id)) + ; let op' = L loc (HsWrap (mkWpTyApps [a2_ty, res_ty]) (HsVar op_id)) ; return $ OpApp (mkLHsWrapCo (mkTcFunCo Nominal co_a co_b) $ mkLHsWrapCo co_arg1 arg1') From git at git.haskell.org Mon Dec 8 15:02:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 15:02:15 +0000 (UTC) Subject: [commit: ghc] master: Improve the treatment of AppTy equalities (15a54be) Message-ID: <20141208150215.CCB033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/15a54bedbbbcfc83a4af5eff7c8b2c1f0181fbd1/ghc >--------------------------------------------------------------- commit 15a54bedbbbcfc83a4af5eff7c8b2c1f0181fbd1 Author: Simon Peyton Jones Date: Mon Dec 8 13:09:27 2014 +0000 Improve the treatment of AppTy equalities This patch is mainly just refactoring, but it improves performance a bit where there is a nested chain of AppTys, and I think it's easier to understand. >--------------------------------------------------------------- 15a54bedbbbcfc83a4af5eff7c8b2c1f0181fbd1 compiler/typecheck/TcCanonical.hs | 124 ++++++++++++++++++++------------------ compiler/typecheck/TcSMonad.hs | 6 +- 2 files changed, 72 insertions(+), 58 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index dc782c1..5232e77 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -452,10 +452,12 @@ can_eq_nc' ev s1@(ForAllTy {}) _ s2@(ForAllTy {}) _ pprEq s1 s2 -- See Note [Do not decompose given polytype equalities] ; stopWith ev "Discard given polytype equality" } -can_eq_nc' ev (AppTy s1 t1) ps_ty1 ty2 ps_ty2 - = can_eq_app ev NotSwapped s1 t1 ps_ty1 ty2 ps_ty2 -can_eq_nc' ev ty1 ps_ty1 (AppTy s2 t2) ps_ty2 - = can_eq_app ev IsSwapped s2 t2 ps_ty2 ty1 ps_ty1 +can_eq_nc' ev (AppTy {}) ps_ty1 _ ps_ty2 + | isGiven ev = try_decompose_app ev ps_ty1 ps_ty2 + | otherwise = can_eq_wanted_app ev ps_ty1 ps_ty2 +can_eq_nc' ev _ ps_ty1 (AppTy {}) ps_ty2 + | isGiven ev = try_decompose_app ev ps_ty1 ps_ty2 + | otherwise = can_eq_wanted_app ev ps_ty1 ps_ty2 -- Everything else is a definite type error, eg LitTy ~ TyConApp can_eq_nc' ev _ ps_ty1 _ ps_ty2 @@ -477,56 +479,67 @@ can_eq_fam_nc ev swapped fn tys rhs ps_rhs Stop ev s -> return (Stop ev s) ContinueWith new_ev -> can_eq_nc new_ev xi_lhs xi_lhs rhs ps_rhs } ------------- -can_eq_app, can_eq_flat_app - :: CtEvidence -> SwapFlag - -> Type -> Type -> Type -- LHS (s1 t2), after and before type-synonym expansion, resp - -> Type -> Type -- RHS (ty2), after and before type-synonym expansion, resp - -> TcS (StopOrContinue Ct) --- See Note [Canonicalising type applications] -can_eq_app ev swapped s1 t1 ps_ty1 ty2 ps_ty2 - = do { traceTcS "can_eq_app 1" $ - vcat [ ppr ev, ppr swapped, ppr s1, ppr t1, ppr ty2 ] - ; let fmode = FE { fe_ev = ev, fe_mode = FM_FlattenAll } - ; (xi_s1, co_s1) <- flatten fmode s1 - ; traceTcS "can_eq_app 2" $ vcat [ ppr ev, ppr xi_s1 ] - ; if s1 `tcEqType` xi_s1 - then can_eq_flat_app ev swapped s1 t1 ps_ty1 ty2 ps_ty2 - else - do { (xi_t1, co_t1) <- flatten fmode t1 - -- We flatten t1 as well so that (xi_s1 xi_t1) is well-kinded - -- If we form (xi_s1 t1) that might (appear) ill-kinded, - -- and then crash in a call to typeKind - ; let xi1 = mkAppTy xi_s1 xi_t1 - co1 = mkTcAppCo co_s1 co_t1 - ; traceTcS "can_eq_app 3" $ vcat [ ppr ev, ppr xi1, ppr co1 ] - ; mb_ct <- rewriteEqEvidence ev swapped xi1 ps_ty2 - co1 (mkTcNomReflCo ps_ty2) - ; traceTcS "can_eq_app 4" $ vcat [ ppr ev, ppr xi1, ppr co1 ] - ; case mb_ct of - Stop ev s -> return (Stop ev s) - ContinueWith new_ev -> can_eq_nc new_ev xi1 xi1 ty2 ps_ty2 }} - --- Preconditions: s1 is already flattened --- ty2 is not a type variable, so flattening --- can't turn it into an application if it --- doesn't look like one already +----------------------------------- +-- Dealing with AppTy -- See Note [Canonicalising type applications] -can_eq_flat_app ev swapped s1 t1 ps_ty1 ty2 ps_ty2 - | Just (s2,t2) <- tcSplitAppTy_maybe ty2 - = unSwap swapped decompose_it (s1,t1) (s2,t2) - | otherwise - = unSwap swapped (canEqFailure ev) ps_ty1 ps_ty2 - where - decompose_it (s1,t1) (s2,t2) - = do { let xevcomp [x,y] = EvCoercion (mkTcAppCo (evTermCoercion x) (evTermCoercion y)) - xevcomp _ = error "canEqAppTy: can't happen" -- Can't happen - xevdecomp x = let xco = evTermCoercion x - in [ EvCoercion (mkTcLRCo CLeft xco) - , EvCoercion (mkTcLRCo CRight xco)] - ; xCtEvidence ev (XEvTerm [mkTcEqPred s1 s2, mkTcEqPred t1 t2] xevcomp xevdecomp) - ; stopWith ev "Decomposed AppTy" } +can_eq_wanted_app :: CtEvidence -> TcType -> TcType + -> TcS (StopOrContinue Ct) +-- One or the other is an App; neither is a type variable +-- See Note [Canonicalising type applications] +can_eq_wanted_app ev ty1 ty2 + = do { let fmode = FE { fe_ev = ev, fe_mode = FM_FlattenAll } + ; (xi1, co1) <- flatten fmode ty1 + ; (xi2, co2) <- flatten fmode ty2 + ; mb_ct <- rewriteEqEvidence ev NotSwapped xi1 xi2 co1 co2 + ; case mb_ct of { + Stop ev s -> return (Stop ev s) ; + ContinueWith new_ev -> try_decompose_app new_ev xi1 xi2 } } + +try_decompose_app :: CtEvidence -> TcType -> TcType -> TcS (StopOrContinue Ct) +-- Preconditions: neither is a type variable +-- so can't turn it into an application if it +-- doesn't look like one already +-- See Note [Canonicalising type applications] +try_decompose_app ev ty1 ty2 + | AppTy s1 t1 <- ty1 + = case tcSplitAppTy_maybe ty2 of + Nothing -> canEqFailure ev ty1 ty2 + Just (s2,t2) -> do_decompose s1 t1 s2 t2 + + | AppTy s2 t2 <- ty2 + = case tcSplitAppTy_maybe ty1 of + Nothing -> canEqFailure ev ty1 ty2 + Just (s1,t1) -> do_decompose s1 t1 s2 t2 + + | otherwise -- Neither is an AppTy + = canEqNC ev ty1 ty2 + where + -- do_decompose is like xCtEvidence, but recurses + -- to try_decompose_app to decompose a chain of AppTys + do_decompose s1 t1 s2 t2 + | CtDerived { ctev_loc = loc } <- ev + = do { emitNewDerived loc (mkTcEqPred t1 t2) + ; try_decompose_app ev s1 s2 } + | CtWanted { ctev_evar = evar, ctev_loc = loc } <- ev + = do { (ev_s,fr_s) <- newWantedEvVar loc (mkTcEqPred s1 s2) + ; (ev_t,fr_t) <- newWantedEvVar loc (mkTcEqPred t1 t2) + ; let co = mkTcAppCo (ctEvCoercion ev_s) (ctEvCoercion ev_t) + ; setEvBind evar (EvCoercion co) + ; when (isFresh fr_t) $ emitWorkNC [ev_t] + ; case fr_s of + Fresh -> try_decompose_app ev_s s1 s2 + Cached -> return (Stop ev (text "Decomposed app")) } + | CtGiven { ctev_evtm = ev_tm, ctev_loc = loc } <- ev + = do { let co = evTermCoercion ev_tm + co_s = mkTcLRCo CLeft co + co_t = mkTcLRCo CRight co + ; evar_s <- newGivenEvVar loc (mkTcEqPred s1 s2, EvCoercion co_s) + ; evar_t <- newGivenEvVar loc (mkTcEqPred t1 t2, EvCoercion co_t) + ; emitWorkNC [evar_t] + ; try_decompose_app evar_s s1 s2 } + | otherwise -- Can't happen + = error "try_decompose_app" ------------------------ canDecomposableTyConApp :: CtEvidence @@ -585,11 +598,8 @@ decompose the application eagerly, yielding we get an error "Can't match Array ~ Maybe", but we'd prefer to get "Can't match Array b ~ Maybe c". -So instead can_eq_app flattens s1. If flattening does something, it -rewrites, and goes round can_eq_nc again. If flattening -does nothing, then (at least with our present state of knowledge) -we can only decompose, and that is what can_eq_flat_app attempts -to do. +So instead can_eq_wanted_app flattens the LHS and RHS before using +try_decompose_app to decompose it. Note [Make sure that insolubles are fully rewritten] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index ffdfb27..0b4d75c 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -39,7 +39,7 @@ module TcSMonad ( setEvBind, XEvTerm(..), - Freshness(..), freshGoals, + Freshness(..), freshGoals, isFresh, StopOrContinue(..), continueWith, stopWith, andWhenContinue, @@ -1562,6 +1562,10 @@ data XEvTerm data Freshness = Fresh | Cached +isFresh :: Freshness -> Bool +isFresh Fresh = True +isFresh Cached = False + freshGoals :: [(CtEvidence, Freshness)] -> [CtEvidence] freshGoals mns = [ ctev | (ctev, Fresh) <- mns ] From git at git.haskell.org Mon Dec 8 15:02:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 15:02:18 +0000 (UTC) Subject: [commit: ghc] master: Revise flattening-notes (ac73d1a) Message-ID: <20141208150218.6BEFB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ac73d1a7d1dbe45da0ea9b71ff99c1e4343d6f40/ghc >--------------------------------------------------------------- commit ac73d1a7d1dbe45da0ea9b71ff99c1e4343d6f40 Author: Simon Peyton Jones Date: Mon Dec 8 15:00:32 2014 +0000 Revise flattening-notes >--------------------------------------------------------------- ac73d1a7d1dbe45da0ea9b71ff99c1e4343d6f40 compiler/typecheck/Flattening-notes | 75 +++++++++++++++++++++++++++---------- 1 file changed, 56 insertions(+), 19 deletions(-) diff --git a/compiler/typecheck/Flattening-notes b/compiler/typecheck/Flattening-notes index e7ac786..35f2f2d 100644 --- a/compiler/typecheck/Flattening-notes +++ b/compiler/typecheck/Flattening-notes @@ -31,9 +31,10 @@ A "generalised substitution" S is a set of triples (a -f-> t), where t is a type f is a flavour such that - (WF) if (a -f1-> t1) in S - (a -f2-> t2) in S + (WF1) if (a -f1-> t1) in S + (a -f2-> t2) in S then neither (f1 >= f2) nor (f2 >= f1) hold + (WF2) if (a -f-> t) is in S, then t /= a Definition: applying a generalised substitution. If S is a generalised subsitution @@ -41,7 +42,7 @@ If S is a generalised subsitution = a, otherwise Application extends naturally to types S(f,t) -Theorem: S(f,a) is a function. +Theorem: S(f,a) is well defined as a function. Proof: Suppose (a -f1-> t1) and (a -f2-> t2) are both in S, and f1 >= f and f2 >= f Then by (R2) f1 >= f2 or f2 >= f1, which contradicts (WF) @@ -52,12 +53,12 @@ Notation: repeated application. Definition: inert generalised substitution A generalised substitution S is "inert" iff - there is an n such that - for every f,t, S^n(f,t) = S^(n+1)(f,t) -Flavours. In GHC currently drawn from {G,W,D}, but with the coercion -solver the flavours become pairs - { (k,l) | k <- {G,W,D}, l <- {Nom,Rep} } + (IG1) there is an n such that + for every f,t, S^n(f,t) = S^(n+1)(f,t) + + (IG2) if (b -f-> t) in S, and f >= f, then S(f,t) = t + that is, each individual binding is "self-stable" ---------------------------------------------------------------- Our main invariant: @@ -73,8 +74,8 @@ The main theorem. a -fw-> t and an inert generalised substitution S, such that - (T1) S(fw,a) = a -- LHS is a fixpoint of S - (T2) S(fw,t) = t -- RHS is a fixpoint of S + (T1) S(fw,a) = a -- LHS of work-item is a fixpoint of S(fw,_) + (T2) S(fw,t) = t -- RHS of work-item is a fixpoint of S(fw,_) (T3) a not in t -- No occurs check in the work item (K1) if (a -fs-> s) is in S then not (fw >= fs) @@ -83,13 +84,14 @@ The main theorem. or (K2b) not (fw >= fs) or (K2c) a not in s or (K3) if (b -fs-> a) is in S then not (fw >= fs) + (a stronger version of (K2)) then the extended substition T = S+(a -fw-> t) - is an inert genrealised substitution. + is an inert generalised substitution. The idea is that * (T1-2) are guaranteed by exhaustively rewriting the work-item - with S. + with S(fw,_). * T3 is guaranteed by a simple occurs-check on the work item. @@ -102,17 +104,19 @@ The idea is that re-process a constraint. The less we kick out, the better. * Assume we have G>=G, G>=W, D>=D, and that's all. Then, when performing - a unification we add a new given a -G-> ty. But doing so dos not require - us to kick out wanteds that mention a, because of (K2b). + a unification we add a new given a -G-> ty. But doing so does NOT require + us to kick out an inert wanted that mentions a, because of (K2a). This + is a common case, hence good not to kick out. -* Lemma (L1): The conditions of the Main Theorem imply that not (fs >= fw). +* Lemma (L1): The conditions of the Main Theorem imply that there is no + (a fs-> t) in S, s.t. (fs >= fw). Proof. Suppose the contrary (fs >= fw). Then because of (T1), S(fw,a)=a. But since fs>=fw, S(fw,a) = s, hence s=a. But now we - have (a -fs-> a) in S, since fs>=fw we must have fs>=fs, and hence S - is not inert. -RAE: I don't understand this lemma statement -- fs seems out of scope here. + have (a -fs-> a) in S, which contradicts (WF2). -* (K1) plus (L1) guarantee that the extended substiution satisfies (WF). +* The extended substitution satisfies (WF1) and (WF2) + - (K1) plus (L1) guarantee that the extended substiution satisfies (WF1). + - (T3) guarantees (WF2). * (K2) is about inertness. Intuitively, any infinite chain T^0(f,t), T^1(f,t), T^2(f,T).... must pass through the new work item infnitely @@ -134,6 +138,10 @@ RAE: I don't understand this lemma statement -- fs seems out of scope here. NB: this reasoning isn't water tight. +Key lemma to make it watertight. + Under the conditions of the Main Theorem, + forall f st fw >= f, a is not in S^k(f,t), for any k + Completeness ~~~~~~~~~~~~~ @@ -161,6 +169,14 @@ But if we kicked-out the inert item, we'd get Then rewrite the work-item gives us (a -W-> a), which is soluble via Refl. So we add one more clause to the kick-out criteria +Another way to understand (K3) is that we treat an inert item + a -f-> b +in the same way as + b -f-> a +So if we kick out one, we should kick out the other. The orientation +is somewhat accidental. + +----------------------- RAE: To prove that K3 is sufficient for completeness (as opposed to a rule that looked for `a` *anywhere* on the RHS, not just at the top), we need this property: All types in the inert set are "rigid". Here, rigid means that a type is one of @@ -179,6 +195,9 @@ w.r.t. representational equality. Accordingly, we would to change (K3) thus: a not in s, OR the path from the top of s to a includes at least one non-newtype +SPJ/DV: this looks important... follow up + +----------------------- RAE: Do we have evidence to support our belief that kicking out is bad? I can imagine scenarios where kicking out *more* equalities is more efficient, in that kicking out a Given, say, might then discover that the Given is reflexive and @@ -188,3 +207,21 @@ kicking out is something to avoid, but it would be nice to have data to support this conclusion. And, that data is not terribly hard to produce: we can just twiddle some settings and then time the testsuite in some sort of controlled environment. + +SPJ: yes it would be good to do that. + +The coercion solver +~~~~~~~~~~~~~~~~~~~~ +Our hope. In GHC currently drawn from {G,W,D}, but with the coercion +solver the flavours become pairs + { (k,l) | k <- {G,W,D}, l <- {Nom,Rep} } + +But can + a -(G,R)-> Int +rewrite + b -(G,R)-> T a +? + +Well, it depends on the roles at which T uses its arguments :-(. +So it may not be enough just to look at (flavour,role) pairs? + From git at git.haskell.org Mon Dec 8 15:31:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 15:31:55 +0000 (UTC) Subject: [commit: ghc] master: RAE's response to SPJ's question in flattening-notes (5818378) Message-ID: <20141208153155.DD7333A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5818378db95a97cb4760afdab41bdf8f6ed07272/ghc >--------------------------------------------------------------- commit 5818378db95a97cb4760afdab41bdf8f6ed07272 Author: Richard Eisenberg Date: Mon Dec 8 10:32:21 2014 -0500 RAE's response to SPJ's question in flattening-notes >--------------------------------------------------------------- 5818378db95a97cb4760afdab41bdf8f6ed07272 compiler/typecheck/Flattening-notes | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/compiler/typecheck/Flattening-notes b/compiler/typecheck/Flattening-notes index 35f2f2d..657e91e 100644 --- a/compiler/typecheck/Flattening-notes +++ b/compiler/typecheck/Flattening-notes @@ -225,3 +225,8 @@ rewrite Well, it depends on the roles at which T uses its arguments :-(. So it may not be enough just to look at (flavour,role) pairs? +RAE: This is true, but it is taken care of by being careful in the +flattening algorithm. Flattening (T a) looks at the roles of +T's parameters, and chooses the role for flattening `a` appropriately. +This is why there must be the [Role] parameter to flattenMany. +Of course, this non-uniform rewriting may gum up the proof works. From git at git.haskell.org Mon Dec 8 15:59:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 15:59:18 +0000 (UTC) Subject: [commit: ghc] master: Fix #9871 by clarifying documentation. (b06908b) Message-ID: <20141208155918.C07FE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b06908b5a120ed56df5416019c38576aadcd21e2/ghc >--------------------------------------------------------------- commit b06908b5a120ed56df5416019c38576aadcd21e2 Author: Richard Eisenberg Date: Mon Dec 8 10:59:48 2014 -0500 Fix #9871 by clarifying documentation. >--------------------------------------------------------------- b06908b5a120ed56df5416019c38576aadcd21e2 docs/users_guide/glasgow_exts.xml | 33 +++++++++++++++++++++++---------- 1 file changed, 23 insertions(+), 10 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 18809fd..2c6cb6a 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -9174,21 +9174,29 @@ f n = \ [haskell|y|] -> y+n - - The type environment seen by reify includes - all the top-level declaration up to the end of the immediately - preceding declaration group, but no more. + + Top-level declaration splices break up a source file into + delcaration groups. A + declaration group is the group of + declarations created by a top-level declaration splice, plus + those following it, down to but not including the next + top-level declaration splice. The first declaration group in a + module includes all top-level definitions down to but not + including the first top-level declaration splice. - A declaration group is the group of - declarations created by a top-level declaration splice, plus - those following it, down to but not including the next top-level - declaration splice. The first declaration group in a module - includes all top-level definitions down to but not including the - first top-level declaration splice. + Each declaration group is mutually recursive only within + the group. Declaration groups can refer to definitions within + previous groups, but not later ones. + + Accordingly, the type environment seen by + reify includes all the top-level + declarations up to the end of the immediately preceding + declaration group, but no more. + Concretely, consider the following code @@ -9206,6 +9214,11 @@ module M where + The body of h would be unable to refer + to the function w. + + + A reify inside the splice $(th1 ..) would see the definition of f. From git at git.haskell.org Mon Dec 8 17:12:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 17:12:37 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Compile; fix a testsuite failure. (494d0db) Message-ID: <20141208171237.D33C43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/494d0dbb31ca82192fff6585dae39efc2cce2a5f/ghc >--------------------------------------------------------------- commit 494d0dbb31ca82192fff6585dae39efc2cce2a5f Author: Richard Eisenberg Date: Sun Dec 7 22:42:50 2014 -0500 Compile; fix a testsuite failure. >--------------------------------------------------------------- 494d0dbb31ca82192fff6585dae39efc2cce2a5f compiler/typecheck/TcCanonical.hs | 12 ++++-------- compiler/typecheck/TcFlatten.hs | 0 testsuite/tests/indexed-types/should_fail/T9580.stderr | 1 + 3 files changed, 5 insertions(+), 8 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 9cc847e..abca349 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -569,8 +569,7 @@ can_eq_flat_app ev eq_rel swapped s1 t1 ps_ty1 ty2 ps_ty2 ; xCtEvidence ev (XEvTerm [mkTcEqPred s1 s2, mkTcEqPred t1 t2] xevcomp xevdecomp) ; stopWith ev "Decomposed AppTy" } -\end{code} - +{- Note [Eager reflexivity check] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Suppose we have @@ -613,8 +612,7 @@ we do a reflexivity check. (This would be sound in the nominal case, but unnecessary, and I [Richard E.] am worried that it would slow down the common case.) - -\begin{code} +-} ------------------------ -- | We're able to unwrap a newtype. Update the bits accordingly. @@ -683,8 +681,7 @@ canDecomposableTyConApp ev eq_rel tc1 tys1 tc2 tys2 = do { traceTcS "canDecomposableTyConApp" (ppr ev $$ ppr eq_rel $$ ppr tc1 $$ ppr tys1 $$ ppr tys2) ; canDecomposableTyConAppOK ev eq_rel tc1 tys1 tys2 } -\end{code} - +{- Note [Use canEqFailure in canDecomposableTyConApp] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We must use canEqFailure, not canEqHardFailure here, because there is @@ -715,8 +712,7 @@ or reinsert them back in appropriately. The alternative to this is to have the solver be aware of phantoms and solve them in a top-level reaction. That somehow seems worse than just a little fiddliness right here. - -\begin{code} +-} canDecomposableTyConAppOK :: CtEvidence -> EqRel -> TyCon -> [TcType] -> [TcType] diff --git a/testsuite/tests/indexed-types/should_fail/T9580.stderr b/testsuite/tests/indexed-types/should_fail/T9580.stderr index f3a884e..fdb457a 100644 --- a/testsuite/tests/indexed-types/should_fail/T9580.stderr +++ b/testsuite/tests/indexed-types/should_fail/T9580.stderr @@ -4,6 +4,7 @@ T9580.hs:7:9: Couldn't match representation of type ?Double? with that of ?Dimensional Int Double? + Relevant role signatures: type role Dimensional nominal nominal The data constructor ?T9580a.Quantity'? of newtype ?Dimensional Int v? is not in scope In the expression: coerce x From git at git.haskell.org Mon Dec 8 17:12:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 17:12:40 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Pass test for #8984 by treating representational equality differently. (59bba57) Message-ID: <20141208171240.747623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/59bba579a2760adf70ca2f4fdc5619a2dc43ba12/ghc >--------------------------------------------------------------- commit 59bba579a2760adf70ca2f4fdc5619a2dc43ba12 Author: Richard Eisenberg Date: Mon Dec 8 11:10:23 2014 -0500 Pass test for #8984 by treating representational equality differently. >--------------------------------------------------------------- 59bba579a2760adf70ca2f4fdc5619a2dc43ba12 compiler/typecheck/TcDeriv.hs | 1 - compiler/typecheck/TcValidity.hs | 14 +++++++++----- 2 files changed, 9 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index d52a721..b0eed2a 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -1807,7 +1807,6 @@ inferInstanceContexts infer_specs do { theta <- simplifyDeriv the_pred tyvars deriv_rhs -- checkValidInstance tyvars theta clas inst_tys -- Not necessary; see Note [Exotic derived instance contexts] - -- in TcSimplify ; traceTc "TcDeriv" (ppr deriv_rhs $$ ppr theta) -- Claim: the result instance declaration is guaranteed valid diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index bc43ad8..de566ea 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -876,12 +876,16 @@ not converge. See Trac #5287. validDerivPred :: TyVarSet -> PredType -> Bool validDerivPred tv_set pred = case classifyPredType pred of - ClassPred _ tys -> hasNoDups fvs - && sizeTypes tys == length fvs - && all (`elemVarSet` tv_set) fvs - TuplePred ps -> all (validDerivPred tv_set) ps - _ -> True -- Non-class predicates are ok + ClassPred _ tys -> check_tys tys + -- EqPred ReprEq is a Coercible constraint; treat + -- like a class + EqPred ReprEq ty1 ty2 -> check_tys [ty1, ty2] + TuplePred ps -> all (validDerivPred tv_set) ps + _ -> True -- Non-class predicates are ok where + check_tys tys = hasNoDups fvs + && sizeTypes tys == length fvs + && all (`elemVarSet` tv_set) fvs fvs = fvType pred {- From git at git.haskell.org Mon Dec 8 17:12:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 17:12:43 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Fix lint errors (only) (1a49889) Message-ID: <20141208171243.250443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/1a49889276183f852520696c40eee0e737153ba6/ghc >--------------------------------------------------------------- commit 1a49889276183f852520696c40eee0e737153ba6 Author: Richard Eisenberg Date: Mon Dec 8 11:54:21 2014 -0500 Fix lint errors (only) >--------------------------------------------------------------- 1a49889276183f852520696c40eee0e737153ba6 compiler/typecheck/TcCanonical.hs | 22 +++++++---- compiler/typecheck/TcEvidence.hs | 7 +++- compiler/typecheck/TcFlatten.hs | 45 ++++++++++++++-------- compiler/typecheck/TcInteract.hs | 18 ++++++--- compiler/typecheck/TcSMonad.hs | 15 +++++--- compiler/typecheck/TcSimplify.hs | 6 +-- compiler/typecheck/TcValidity.hs | 3 +- compiler/types/Coercion.hs | 3 +- compiler/types/Type.hs | 7 ++-- compiler/utils/MonadUtils.hs | 3 +- .../tests/typecheck/should_run/TcCoercible.hs | 6 ++- 11 files changed, 87 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 1a49889276183f852520696c40eee0e737153ba6 From git at git.haskell.org Mon Dec 8 17:12:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 17:12:45 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Drop Derived `canRewrite` Derived, as per discussions with SPJ & DV (1383e0d) Message-ID: <20141208171245.BA9193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/1383e0d72788959c8be9877b7c451e6f271d61f0/ghc >--------------------------------------------------------------- commit 1383e0d72788959c8be9877b7c451e6f271d61f0 Author: Richard Eisenberg Date: Mon Dec 8 12:04:03 2014 -0500 Drop Derived `canRewrite` Derived, as per discussions with SPJ & DV >--------------------------------------------------------------- 1383e0d72788959c8be9877b7c451e6f271d61f0 compiler/typecheck/TcCanonical.hs | 13 ------------- compiler/typecheck/TcFlatten.hs | 2 -- 2 files changed, 15 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index fcf5c4e..f903ba8 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -380,19 +380,6 @@ canHole ev occ hole_sort canEqNC :: CtEvidence -> EqRel -> Type -> Type -> TcS (StopOrContinue Ct) canEqNC ev eq_rel ty1 ty2 = can_eq_nc ev eq_rel ty1 ty1 ty2 ty2 - `andWhenContinue` \ ct -> - do { emitReprEq ct - ; continueWith ct } - -emitReprEq :: Ct -> TcS () -emitReprEq (CTyEqCan { cc_ev = ev@(CtDerived {}), cc_tyvar = tv, cc_rhs = rhs - , cc_eq_rel = NomEq }) - = emitWorkNC [ev { ctev_pred = mkTcReprEqPred (mkTyVarTy tv) rhs }] - -- This works only on Deriveds, because nominal Givens can rewrite - -- representational equalities. See Note [eqCanRewrite] in TcFlatten - --- Nothing to do for other equalities -emitReprEq _ = return () can_eq_nc :: CtEvidence diff --git a/compiler/typecheck/TcFlatten.hs b/compiler/typecheck/TcFlatten.hs index 1b7698c..4a8b026 100644 --- a/compiler/typecheck/TcFlatten.hs +++ b/compiler/typecheck/TcFlatten.hs @@ -1183,8 +1183,6 @@ eqCanRewriteFR :: CtFlavourRole -> CtFlavourRole -> Bool -- See Note [eqCanRewrite] eqCanRewriteFR (Given, NomEq) (_, _) = True eqCanRewriteFR (Given, ReprEq) (_, ReprEq) = True -eqCanRewriteFR (Derived, NomEq) (Derived, NomEq) = True -eqCanRewriteFR (Derived, ReprEq) (Derived, ReprEq) = True eqCanRewriteFR _ _ = False canRewriteOrSame :: CtEvidence -> CtEvidence -> Bool From git at git.haskell.org Mon Dec 8 17:12:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 17:12:48 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Update Note [eqCanRewrite]; don't search in an EqualCtList (eac5875) Message-ID: <20141208171248.595DF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/eac58758c488a0ec8ef9b697f196fd6177bdaa34/ghc >--------------------------------------------------------------- commit eac58758c488a0ec8ef9b697f196fd6177bdaa34 Author: Richard Eisenberg Date: Mon Dec 8 12:11:50 2014 -0500 Update Note [eqCanRewrite]; don't search in an EqualCtList >--------------------------------------------------------------- eac58758c488a0ec8ef9b697f196fd6177bdaa34 compiler/typecheck/TcFlatten.hs | 20 +++++++++++--------- compiler/typecheck/TcInteract.hs | 7 +++---- compiler/typecheck/TcSMonad.hs | 2 +- 3 files changed, 15 insertions(+), 14 deletions(-) diff --git a/compiler/typecheck/TcFlatten.hs b/compiler/typecheck/TcFlatten.hs index 4a8b026..fa03499 100644 --- a/compiler/typecheck/TcFlatten.hs +++ b/compiler/typecheck/TcFlatten.hs @@ -32,7 +32,6 @@ import MonadUtils ( zipWithAndUnzipM ) import Bag import FastString import Control.Monad( when, liftM ) -import Data.List ( find ) {- Note [The flattening story] @@ -952,12 +951,10 @@ flattenTyVarOuter fmode tv -- See Note [Applying the inert substitution] do { ieqs <- getInertEqs ; case lookupVarEnv ieqs tv of - Just cts - -- we need to search for one that can rewrite, because you - -- can have, for example, a Derived among a bunch of Wanteds - | Just (CTyEqCan { cc_ev = ctev, cc_tyvar = tv, cc_rhs = rhs_ty }) - <- find ((`eqCanRewriteFR` feFlavourRole fmode) - . ctFlavourRole) cts + Just (ct:_) -- If the first doesn't work, + -- the subsequent ones won't either + | CTyEqCan { cc_ev = ctev, cc_tyvar = tv, cc_rhs = rhs_ty } <- ct + , ctev `eqCanRewrite` ctxt_ev -> do { traceTcS "Following inert tyvar" (ppr tv <+> equals <+> ppr rhs_ty $$ ppr ctev) ; let rewrite_co1 = mkTcSymCo (ctEvCoercion ctev) rewrite_co = case (ctEvEqRel ctev, fe_eq_rel fmode) of @@ -1193,8 +1190,6 @@ canRewriteOrSame ev1 ev2 = ev1 `eqCanRewrite` ev2 || {- Note [eqCanRewrite] ~~~~~~~~~~~~~~~~~~~ -TODO (RAE): Update this note! - (eqCanRewrite ct1 ct2) holds if the constraint ct1 (a CTyEqCan of form tv ~ ty) can be used to rewrite ct2. @@ -1203,6 +1198,7 @@ The EqCanRewrite Property: then a eqCanRewrite a This is what guarantees that canonicalisation will terminate. See Note [Applying the inert substitution] + But this isn't the whole story; see Note [Flattener smelliness] At the moment we don't allow Wanteds to rewrite Wanteds, because that can give rise to very confusing type error messages. A good example is Trac #8450. @@ -1214,6 +1210,12 @@ Here we get [W] a ~ Bool but we do not want to complain about Bool ~ Char! +Accordingly, we also don't let Deriveds rewrite Deriveds. + +With the solver handling Coercible constraints like equality constraints, +the rewrite conditions must take role into account, never allowing +a representational equality to rewrite a nominal one. + Note [canRewriteOrSame] ~~~~~~~~~~~~~~~~~~~~~~~ canRewriteOrSame is similar but diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index d4f14d1..b0644a3 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -700,10 +700,9 @@ lookupFlattenTyVar :: TyVarEnv EqualCtList -> TcTyVar -> TcType -- ^ Look up a flatten-tyvar in the inert nominal TyVarEqs; -- this is used only when dealing with a CFunEqCan lookupFlattenTyVar inert_eqs ftv - -- TODO (RAE): This is fishy. Why only return one equality? - = case lookupVarEnv inert_eqs ftv >>= find ((== NomEq) . ctEqRel) of - Just (CTyEqCan { cc_rhs = rhs }) -> rhs - _ -> mkTyVarTy ftv + = case lookupVarEnv inert_eqs ftv of + Just (CTyEqCan { cc_rhs = rhs, cc_eq_rel = NomEq } : _) -> rhs + _ -> mkTyVarTy ftv reactFunEq :: CtEvidence -> TcTyVar -- From this :: F tys ~ fsk1 -> CtEvidence -> TcTyVar -- Solve this :: F tys ~ fsk2 diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index 55f75c8..3cd14c5 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -381,7 +381,7 @@ Note [EqualCtList invariants] From the fourth invariant it follows that the list is - A single Given, or - - Any number of Wanteds, along with 0 or 1 Derived + - Any number of Wanteds and/or Deriveds -} -- The Inert Set From git at git.haskell.org Mon Dec 8 17:18:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 17:18:44 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Typo. (6e6b26e) Message-ID: <20141208171844.324233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/6e6b26e466747821d570ca91a81a2fb1f51285fe/ghc >--------------------------------------------------------------- commit 6e6b26e466747821d570ca91a81a2fb1f51285fe Author: Richard Eisenberg Date: Mon Dec 8 12:18:44 2014 -0500 Typo. >--------------------------------------------------------------- 6e6b26e466747821d570ca91a81a2fb1f51285fe compiler/typecheck/TcFlatten.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcFlatten.hs b/compiler/typecheck/TcFlatten.hs index fa03499..d8ac374 100644 --- a/compiler/typecheck/TcFlatten.hs +++ b/compiler/typecheck/TcFlatten.hs @@ -954,7 +954,7 @@ flattenTyVarOuter fmode tv Just (ct:_) -- If the first doesn't work, -- the subsequent ones won't either | CTyEqCan { cc_ev = ctev, cc_tyvar = tv, cc_rhs = rhs_ty } <- ct - , ctev `eqCanRewrite` ctxt_ev + , ctEvFlavourRole ctev `eqCanRewriteFR` feFlavourRole fmode -> do { traceTcS "Following inert tyvar" (ppr tv <+> equals <+> ppr rhs_ty $$ ppr ctev) ; let rewrite_co1 = mkTcSymCo (ctEvCoercion ctev) rewrite_co = case (ctEvEqRel ctev, fe_eq_rel fmode) of From git at git.haskell.org Mon Dec 8 17:28:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 17:28:03 +0000 (UTC) Subject: [commit: ghc] master: Add doctest examples for Data.Maybe (8688f6a) Message-ID: <20141208172803.9B29B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8688f6a5f652e8f41a19faf1a935073d85efffa0/ghc >--------------------------------------------------------------- commit 8688f6a5f652e8f41a19faf1a935073d85efffa0 Author: Michael Orlitzky Date: Mon Dec 8 18:27:16 2014 +0100 Add doctest examples for Data.Maybe To actually *run* the doctests, you need to do a little hacking. Somewhere after the `GHC.Base` import, you'll need to reimport `Maybe(..)` from `Prelude`, clobbering the `GHC.Base` definition. After that, doctest should be runnable from the `Data/` directory. Reviewed By: austin, hvr Differential Revision: https://phabricator.haskell.org/D561 >--------------------------------------------------------------- 8688f6a5f652e8f41a19faf1a935073d85efffa0 libraries/base/Data/Maybe.hs | 189 +++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 189 insertions(+) diff --git a/libraries/base/Data/Maybe.hs b/libraries/base/Data/Maybe.hs index 23d393d..3d9a5a9 100644 --- a/libraries/base/Data/Maybe.hs +++ b/libraries/base/Data/Maybe.hs @@ -33,6 +33,10 @@ module Data.Maybe import GHC.Base +-- $setup +-- Allow the use of some Prelude functions in doctests. +-- >>> import Prelude ( (*), odd, show, sum ) + -- --------------------------------------------------------------------------- -- Functions over Maybe @@ -40,23 +44,105 @@ import GHC.Base -- value. If the 'Maybe' value is 'Nothing', the function returns the -- default value. Otherwise, it applies the function to the value inside -- the 'Just' and returns the result. +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> maybe False odd (Just 3) +-- True +-- +-- >>> maybe False odd Nothing +-- False +-- +-- Read an integer from a string using 'readMaybe'. If we succeed, +-- return twice the integer; that is, apply @(*2)@ to it. If instead +-- we fail to parse an integer, return @0@ by default: +-- +-- >>> import Text.Read ( readMaybe ) +-- >>> maybe 0 (*2) (readMaybe "5") +-- 10 +-- >>> maybe 0 (*2) (readMaybe "") +-- 0 +-- +-- Apply 'show' to a @Maybe Int at . If we have @Just n@, we want to show +-- the underlying 'Int' @n at . But if we have 'Nothing', we return the +-- empty string instead of (for example) \"Nothing\": +-- +-- >>> maybe "" show (Just 5) +-- "5" +-- >>> maybe "" show Nothing +-- "" +-- maybe :: b -> (a -> b) -> Maybe a -> b maybe n _ Nothing = n maybe _ f (Just x) = f x -- | The 'isJust' function returns 'True' iff its argument is of the -- form @Just _ at . +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> isJust (Just 3) +-- True +-- +-- >>> isJust (Just ()) +-- True +-- +-- >>> isJust Nothing +-- False +-- +-- Only the outer constructor is taken into consideration: +-- +-- >>> isJust (Just Nothing) +-- True +-- isJust :: Maybe a -> Bool isJust Nothing = False isJust _ = True -- | The 'isNothing' function returns 'True' iff its argument is 'Nothing'. +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> isNothing (Just 3) +-- False +-- +-- >>> isNothing (Just ()) +-- False +-- +-- >>> isNothing Nothing +-- True +-- +-- Only the outer constructor is taken into consideration: +-- +-- >>> isNothing (Just Nothing) +-- False +-- isNothing :: Maybe a -> Bool isNothing Nothing = True isNothing _ = False -- | The 'fromJust' function extracts the element out of a 'Just' and -- throws an error if its argument is 'Nothing'. +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> fromJust (Just 1) +-- 1 +-- +-- >>> 2 * (fromJust (Just 10)) +-- 20 +-- +-- >>> 2 * (fromJust Nothing) +-- *** Exception: Maybe.fromJust: Nothing +-- fromJust :: Maybe a -> a fromJust Nothing = error "Maybe.fromJust: Nothing" -- yuck fromJust (Just x) = x @@ -64,23 +150,108 @@ fromJust (Just x) = x -- | The 'fromMaybe' function takes a default value and and 'Maybe' -- value. If the 'Maybe' is 'Nothing', it returns the default values; -- otherwise, it returns the value contained in the 'Maybe'. +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> fromMaybe "" (Just "Hello, World!") +-- "Hello, World!" +-- +-- >>> fromMaybe "" Nothing +-- "" +-- +-- Read an integer from a string using 'readMaybe'. If we fail to +-- parse an integer, we want to return @0@ by default: +-- +-- >>> import Text.Read ( readMaybe ) +-- >>> fromMaybe 0 (readMaybe "5") +-- 5 +-- >>> fromMaybe 0 (readMaybe "") +-- 0 +-- fromMaybe :: a -> Maybe a -> a fromMaybe d x = case x of {Nothing -> d;Just v -> v} -- | The 'maybeToList' function returns an empty list when given -- 'Nothing' or a singleton list when not given 'Nothing'. +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> maybeToList (Just 7) +-- [7] +-- +-- >>> maybeToList Nothing +-- [] +-- +-- One can use 'maybeToList' to avoid pattern matching when combined +-- with a function that (safely) works on lists: +-- +-- >>> import Text.Read ( readMaybe ) +-- >>> sum $ maybeToList (readMaybe "3") +-- 3 +-- >>> sum $ maybeToList (readMaybe "") +-- 0 +-- maybeToList :: Maybe a -> [a] maybeToList Nothing = [] maybeToList (Just x) = [x] -- | The 'listToMaybe' function returns 'Nothing' on an empty list -- or @'Just' a@ where @a@ is the first element of the list. +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> listToMaybe [] +-- Nothing +-- +-- >>> listToMaybe [9] +-- Just 9 +-- +-- >>> listToMaybe [1,2,3] +-- Just 1 +-- +-- Composing 'maybeToList' with 'listToMaybe' should be the identity +-- on singleton/empty lists: +-- +-- >>> maybeToList $ listToMaybe [5] +-- [5] +-- >>> maybeToList $ listToMaybe [] +-- [] +-- +-- But not on lists with more than one element: +-- +-- >>> maybeToList $ listToMaybe [1,2,3] +-- [1] +-- listToMaybe :: [a] -> Maybe a listToMaybe [] = Nothing listToMaybe (a:_) = Just a -- | The 'catMaybes' function takes a list of 'Maybe's and returns -- a list of all the 'Just' values. +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> catMaybes [Just 1, Nothing, Just 3] +-- [1,3] +-- +-- When constructing a list of 'Maybe' values, 'catMaybes' can be used +-- to return all of the \"success\" results (if the list is the result +-- of a 'map', then 'mapMaybe' would be more appropriate): +-- +-- >>> import Text.Read ( readMaybe ) +-- >>> [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ] +-- [Just 1,Nothing,Just 3] +-- >>> catMaybes $ [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ] +-- [1,3] +-- catMaybes :: [Maybe a] -> [a] catMaybes ls = [x | Just x <- ls] @@ -89,6 +260,24 @@ catMaybes ls = [x | Just x <- ls] -- something of type @'Maybe' b at . If this is 'Nothing', no element -- is added on to the result list. If it is @'Just' b@, then @b@ is -- included in the result list. +-- +-- ==== __Examples__ +-- +-- Using @'mapMaybe' f x@ is a shortcut for @'catMaybes' $ 'map' f x@ +-- in most cases: +-- +-- >>> import Text.Read ( readMaybe ) +-- >>> let readMaybeInt = readMaybe :: String -> Maybe Int +-- >>> mapMaybe readMaybeInt ["1", "Foo", "3"] +-- [1,3] +-- >>> catMaybes $ map readMaybeInt ["1", "Foo", "3"] +-- [1,3] +-- +-- If we map the 'Just' constructor, the entire list should be returned: +-- +-- >>> mapMaybe Just [1,2,3] +-- [1,2,3] +-- mapMaybe :: (a -> Maybe b) -> [a] -> [b] mapMaybe _ [] = [] mapMaybe f (x:xs) = From git at git.haskell.org Mon Dec 8 22:41:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Dec 2014 22:41:39 +0000 (UTC) Subject: [commit: ghc] master: catch some recent typos (2515686) Message-ID: <20141208224139.B78933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2515686ff695169238b673423f01768f5aaa9750/ghc >--------------------------------------------------------------- commit 2515686ff695169238b673423f01768f5aaa9750 Author: Gabor Greif Date: Mon Dec 8 23:01:55 2014 +0100 catch some recent typos >--------------------------------------------------------------- 2515686ff695169238b673423f01768f5aaa9750 compiler/cmm/CmmType.hs | 2 +- compiler/main/PprTyThing.hs | 2 +- compiler/typecheck/Flattening-notes | 6 +++--- compiler/typecheck/TcCanonical.hs | 2 +- compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcErrors.hs | 2 +- compiler/typecheck/TcGenDeriv.hs | 2 +- compiler/typecheck/TcInteract.hs | 4 ++-- compiler/typecheck/TcType.hs | 2 +- libraries/ghc-prim/GHC/Types.hs | 2 +- testsuite/tests/perf/compiler/all.T | 2 +- 11 files changed, 14 insertions(+), 14 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2515686ff695169238b673423f01768f5aaa9750 From git at git.haskell.org Tue Dec 9 07:18:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Dec 2014 07:18:51 +0000 (UTC) Subject: [commit: ghc] master: Update `process` submodule to pull in Safe Haskell fixes (c2c1888) Message-ID: <20141209071851.15A3C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c2c1888110ef91774bf17e8358aa41537124d7f5/ghc >--------------------------------------------------------------- commit c2c1888110ef91774bf17e8358aa41537124d7f5 Author: David Terei Date: Mon Dec 8 23:18:13 2014 -0800 Update `process` submodule to pull in Safe Haskell fixes >--------------------------------------------------------------- c2c1888110ef91774bf17e8358aa41537124d7f5 libraries/process | 2 +- mk/validate-settings.mk | 1 - 2 files changed, 1 insertion(+), 2 deletions(-) diff --git a/libraries/process b/libraries/process index bc5f234..7139346 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit bc5f2348b982d9e86bf2f15065187a0ba535a1a3 +Subproject commit 71393467c6ee004d3ccdde27df80c90b63926531 diff --git a/mk/validate-settings.mk b/mk/validate-settings.mk index 6a85b79..351ea83 100644 --- a/mk/validate-settings.mk +++ b/mk/validate-settings.mk @@ -169,7 +169,6 @@ libraries/array_dist-install_EXTRA_HC_OPTS += -fno-warn-warnings-deprecations # Turn of trustworthy-safe warning libraries/base_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe libraries/ghc-prim_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe -libraries/process_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe libraries/unix_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe libraries/Win32_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe From git at git.haskell.org Tue Dec 9 16:37:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Dec 2014 16:37:10 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Remove redundant import. Argh. (d02925a) Message-ID: <20141209163710.97D573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/d02925a6ff17a115d27b87d69f82fa036708c2a7/ghc >--------------------------------------------------------------- commit d02925a6ff17a115d27b87d69f82fa036708c2a7 Author: Richard Eisenberg Date: Tue Dec 9 11:33:58 2014 -0500 Remove redundant import. Argh. >--------------------------------------------------------------- d02925a6ff17a115d27b87d69f82fa036708c2a7 compiler/typecheck/TcInteract.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index b0644a3..c377259 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -42,7 +42,6 @@ import Pair (Pair(..)) import Unique( hasKey ) import FastString ( sLit ) import DynFlags -import Data.List ( find ) import Util {- From git at git.haskell.org Tue Dec 9 22:38:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Dec 2014 22:38:44 +0000 (UTC) Subject: [commit: ghc] wip/rae: Add Ord instances to TH (5e4a65c) Message-ID: <20141209223844.D68D93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/5e4a65c20d81a389ddc456b07577a9d31bdd0c81/ghc >--------------------------------------------------------------- commit 5e4a65c20d81a389ddc456b07577a9d31bdd0c81 Author: Richard Eisenberg Date: Tue Dec 9 17:39:11 2014 -0500 Add Ord instances to TH >--------------------------------------------------------------- 5e4a65c20d81a389ddc456b07577a9d31bdd0c81 docs/users_guide/7.10.1-notes.xml | 2 +- .../template-haskell/Language/Haskell/TH/Syntax.hs | 70 +++++++++++----------- 2 files changed, 36 insertions(+), 36 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5e4a65c20d81a389ddc456b07577a9d31bdd0c81 From git at git.haskell.org Tue Dec 9 22:38:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Dec 2014 22:38:48 +0000 (UTC) Subject: [commit: ghc] wip/rae's head updated: Add Ord instances to TH (5e4a65c) Message-ID: <20141209223848.05A843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/rae' now includes: 6efe572 Don't build old-{time,locale} and haskell{98,2010} 86dda8f Delete old-{time,locale} and haskell{98,2010} e888b94 Hide `Data.OldList` module f60eeb4 Export scanl' from Data.OldList and Data.List 067f1e4 Add flag `-fwarn-missing-exported-sigs` 7ed482d Implement #5462 (deriving clause for arbitrary classes) 27f9c74 Unbreak build (fallout from 067f1e4f20e) fec1c30 Revert change to alias handling in ppLlvmGlobal introduced in d87fa34, which requires LLVM 3.6. b0dd347 Rewrite Note [Deriving any class] eac9bbe Comments only e876208 Rejig builders for pattern synonyms, especially unlifted ones 76f5f11 Move all the zonk/tidy stuff together into TcMType (refactoring only) b685542 Implement full co/contra-variant subsumption checking (fixes Trac #9569) 073119e Put the decision of when a unification variable can unify with a polytype 0f5c163 Make the on-the-fly unifier defer forall/forall unification 16d10ae Fix a latent promotion bug in TcSimplify.simplifyInfer 5f39c4d Remove TcMType from compiler_stage2_dll0_MODULES 5760eb5 Test Trac #9318 b82410a Trac #9222 is actually an ambiguous type, now detected e639120 Delete duplicated tests 230b013 Test Trac #9569 7b1a856 Fix up tests for Trac #7220; the old test really was ambiguous 1b6988e Test T2239 actually succeeds without impredicativity, because of the new co/contra subsumption check eaccc72 Wibbles (usually improvements) to error messages 4ba4cc7 Fix Trac #9815 c5a3938 Test Trac #8149 6d40470 Comments only dbf360a Test #7484 in th/T7484 da2fca9 Fix #7484, checking for good binder names in Convert. adb20a0 Test #1476 in th/T1476 d627c5c Test that nested pattern splices don't scope (#1476). 2346de4 Fix #1476 by making splice patterns work. 1b22d9f Release notes for #1476, #7484. 3b3944f Test #9824 in th/T9824 bc05354 Fix #9824 by not warning about unused matches in pattern quotes. cfa574c Update manual for pattern splices (#1476) 7927658 AST changes to prepare for API annotations, for #9628 803fc5d Add API Annotations 3e4f49b Fixes ghci :unset -X so that it doesn't fail to reverse option. (fixes trac #9293) 3793d3b Export more Packages functions a97f90c Add Data.Void to base (re #9814) c0ad5bc Capture original source for literals 3583312 Add 'fillBytes' to Foreign.Marshal.Utils. 6265f1c Add T7220a.stderr 065d433 Update Control.Monad.ST.* for Safe Haskell as now they're safe by default 453ce62 Update Foreign.* for Safe Haskell now that they're safe by default 5f84bd1 Improve Safe Haskell bounds for changes to base over time 2a523eb Be consistent with placement of Safe Haskell mode at top of file e16a342 llvmGen: Compatibility with LLVM 3.5 (re #9142) 3222b7a Add displayException method to Exception (#9822) 02f8f6a Add function for size-checked conversion of Integral types 624a7c5 ghc: allow --show-options and --interactive together 2cc854b Add -fdefer-typed-holes flag which defers hole errors to runtime. 137b331 Deprecate Data.Version.versionTags (#2496) 8a8cdbb Implement `Natural` number type (re #9818) ef5bcc1 Re-center bytes-allocated for `haddock.compiler` 888d75c Revert "Test Trac #9318" be7fb7e integer-gmp2: export `Word`-counterpart of gcdInt 2b71b35 Remove reference to `MIN_VERSION_integer_gmp2` 5ea3ee0 Add gcd/Word RULE-based optimisation 4b65376 Add `isValidNatural` predicate (#9818) b836139 Fix `fromInteger` constructing invalid `Natural` 41300b7 Implement {gcd,lcm}/Natural optimisation (#9818) 96d29b5 Call `popCountBigNat` directly (#9818) cc7a735 Define void using <$ (re #9827) fb061c1 Add `Storable` instances for `Complex` and `Ratio` a9a0dd3 Install `ghc-gmp.h` C include header file (#9281) 6d1c8ec Persist build-time GMP ver to `HsIntegerGmp.h` fd25379 Fix minor typo in 6d1c8ec79adf566d57d2c35aac 41c3545 Update in-tree GMP to version 5.0.4 6a13099 Try to improve Make dependency for `ghc-gmp.h` a7c2972 Use the `patch` command detected by the top-level `configure` 1617a10 accessors to RTS flag values -- #5364 bdeab90 Minor tweaks to API Annotation 3359133 Add `--fwarn-trustworthy-safe` to `-Wall` again. 63d2ada Test #7643 in typecheck/should_compile/T7643. 8459404 Test #8044 in typecheck/should_fail/T8044 5c35415 Test #8031 in th/T8031 8e82857 Changelog entry and /Since/ for alloc-counter ops e159e08 Mark `Data.Typeable.Internal` as Trustworthy after consverstation with ekmett & hvr. e22bc0d Make clearNursery free 452eb80 Add +RTS -n: divide the nursery into chunks 65d1c03 Document +RTS -xq 5fa0186 Update `deepseq` to latest 1.4.0.0 snapshot 4af5748 Replace `STRICT[12345]` macros by `BangPatterns` fb5baaf Insert changelog entries for GHC 7.8.4 4bf055c Define `Data` instance for `Natural` type (#9818) cb9bcec Test Trac #9834 ed56c02 Use {bit,popCount}Integer for `Bits Integer` 4897e70 configure.ac: fix test == bashism b19845d Cabal submodule update: hole support and tests. 7a6fb98 Inline mkModuleToPkgConfAll into mkModuleToPkgConfGeneric. 8c7d20d Change loadSrcInterface to return a list of ModIface d8c437b Don't require PatternSynonyms language extension to just use pattern synonyms (see #9838) a67ebbe Resume reporting incomplete pattern matches for record updates 417b874 Don't require ConstraintKinds at usage sites (Trac #9838) 4721167 Trac #6022 is actually fine now b61091d Test Trac #7243 01f03cb Get the right fixity-env in standalone deriving (Trac #9830) 73e5e2f Embed Git commit id into `ghc --info` output 65cae36 compiler: add new modules pulling in FunFlags 7dd4c12 Improve VERSION/GIT_COMMIT_ID handling for sdist 227a566 Don't discard a bang on a newtype pattern (Trac #9844) 342ebb0 Tidy up tracing somewhat 58dcd5c Re-implement `testPrimeInteger` predicate (#9281) b5e8b3b Make the linker API thread-safe 9e6e479 Add purgeObj() to remove the symbol table entries for an object 8d78311 Re-implement `nextPrimeInteger` predicate (#9281) 2eecf34 Re-activate `integerGmpInternals` test (#9281) 171101b Kind variables in RHS of an associated type instances should be bound on LHS 7460daf Rename some of the functions in NameSet, to make the uniform with VarSet etc d831b6f Implement Partial Type Signatures f0df243 Update submodule 'haddock' to render 'pattern' as a keyword 447f592 Minor refactoring of static C initializers d108a19 Fix testsuite failures after the PartialTypeSignatures merge a809eab More static C initializer refactoring d0d4674 Re-implement `powModInteger` (#9281) 859680f Implement `GHC.Natural.powModNatural` (#9818) 83c4843 Re-implement `recipModInteger` (#9281) c0e0ca4 Reimplement `gcdExtInteger` (#9281) 46c53d5 Special case interactive package key for mkQualPackage. 4c834fd Filter instance visibility based on set of visible orphans, fixes #2182. 6d47ab3 Shorten long lines in DynFlags, add details to ghci usage guide. ed85d7e More Tweaks for API Anotations 643635e Add bash completion and README 383733b Fix obscure problem with using the system linker (#8935) aede9f0 compiler: unlit profiling/ modules 780b061 compiler: fix trac issue #8815 9ece13d Update docs: instance visibility bug is no more. 0c48750 Unlit compiler/cmm/ module(s) 7ad3846 Unlit AsmCodeGen.lhs 0511c0a Revert "Remove RAWCPP_FLAGS" 4b16ff6 unlit compiler/stranal/ modules e992317 unlit compiler/types/ modules e6a2050 Fix the handling of instance signatures (Trac #9582, #9833) e77faac Wibble to the "instance signatures" patch 370b0f5 Remove references to Parser.y.pp c34ef46 Test Trac #7908 1d32a85 Fix parser for UNPACK pragmas 2d324dd Fix malformed `configure` script a29e295 Mention existence of 'Natural' in "Data.Word" 9437a24 Uncomment the instance signatures, to activate the test 7932b2a Revert "Add purgeObj() to remove the symbol table entries for an object" 4b51194 Revert "Make the linker API thread-safe" 06eaa64 Fix test suite race on T5462 (solves intermittent T5462Yes1/T5462Yes2/T5462No1 failure) 5d9bb56 Comments and formatting in TyCon 668a137 Remove references to SynTyCon. Fixes #9812 26a3d0f Rename Untouchables to TcLevel 30d2605 Test Trac #4921 2a67fb3 Minor refactoring of Edward's recent orphans patch (Trac #2182) 863854a Fix another bug in deriving( Data ) for data families; Trac #4896 c41d214 Unique-ify the names of top-level auxiliary bindings in derived instances (Trac #7947) 6b063ef Make Natural's (.|.) really an OR operation (#9818) 7c38e98 Make `read . show = id` for Data.Fixed (fix #9240) bf2d754 Declare official GitHub home of libraries/parallel 46b278f Generate real (but empty) object files for signatures. cce292b Update 32-bit performace numbers (has not been done for ages) 289e52f Make annotations test case cleaning less aggressive bc9e81c Comments only 1389ff5 compiler: de-lhs main/ dc00fb1 compiler: de-lhs prelude/ 9fc4382 compiler: de-lhs rename/ b04296d compiler: de-lhs coreSyn/ 0c48e17 compiler: de-lhs utils/ 10fdf27 compiler: de-lhs iface/ 29a5210 compiler: de-lhs specialise/ a56fe4a compiler: de-lhs basicTypes/ b9b1fab compiler: de-lhs hsSyn/ 6ecd27e compiler: de-lhs simplCore/ 612e573 compiler: de-lhs stgSyn/ bafba11 compiler: de-lhs simplStg/ b57ff27 compiler: de-lhs typecheck/ 4d5f83a compiler: de-lhs deSugar/ cc071ec Comments on TrieMap and unifier. d6f9276 Prevent solveFlatWanteds from losing insolubles when using typechecker plugins 78edd76 Cabal submodule update 55a2a0b Revert "Revert "Make the linker API thread-safe"" a48bee9 Revert "Revert "Add purgeObj() to remove the symbol table entries for an object"" 09af720 Disable T8124 on Windows (uses pthreads) 9a10107 Add notes about the inert CTyEqCans 87160c1 renamer: fix trac issue #9778 3ebe304 docs: Update to reflect reality 7cd6806 Add -fwarn-unticked-promoted-constructors to -Wall da98592 msse flag handling: fix trac issue #9777 08610c1 Implement `calloc{,Bytes,Array,Array0}` allocators d80022d Add references between Data.Traversable.for and Data.Foldable.for_ and co. 9a1779e Portability: wc -l sometimes has leading spaces, trim them off. 7383ce9 Add ticket-ref to changelog entry (fup to 08610c1) b9f636b Set proper `CTYPE` for POSIX `CGroup` 334cb10 Update `unix` submodule to latest snapshot d629576 Added comments to flattening-notes 030ece4 Add -I$1/$2/build/autogen to $1_$2_DIST_CC_OPTS e74a9e9 Remove `inline` from integer_gmp_mpn_import1() 7535c83 Comments only 37c2ed4 Optimise partitionFunEqs for the 'false' case 15a54be Improve the treatment of AppTy equalities d64e682 Comments and variable names only, in type checking of (e1 $ e2) 1d44261 Revise the inert-set invariants again ac73d1a Revise flattening-notes 5818378 RAE's response to SPJ's question in flattening-notes b06908b Fix #9871 by clarifying documentation. 8688f6a Add doctest examples for Data.Maybe 2515686 catch some recent typos c2c1888 Update `process` submodule to pull in Safe Haskell fixes 5e4a65c Add Ord instances to TH From git at git.haskell.org Wed Dec 10 01:11:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 01:11:15 +0000 (UTC) Subject: [commit: ghc] master: Proposal for Backpack file format [skip ci] (e5974f8) Message-ID: <20141210011115.60F2B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e5974f8f53de4c97cfaad228eedfca8b31b53887/ghc >--------------------------------------------------------------- commit e5974f8f53de4c97cfaad228eedfca8b31b53887 Author: Edward Z. Yang Date: Tue Dec 9 17:11:57 2014 -0800 Proposal for Backpack file format [skip ci] Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- e5974f8f53de4c97cfaad228eedfca8b31b53887 docs/backpack/backpack-manual.pdf | Bin 181875 -> 188738 bytes docs/backpack/backpack-manual.tex | 128 +++++++++++++++++++++++++++++++++----- 2 files changed, 111 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 e5974f8f53de4c97cfaad228eedfca8b31b53887 From git at git.haskell.org Wed Dec 10 01:58:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 01:58:34 +0000 (UTC) Subject: [commit: ghc] master: Link pre-ARMv6 spinlocks into all RTS variants (df1307f) Message-ID: <20141210015834.631613A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/df1307f079ae69dcd735e0973de987b141d509da/ghc >--------------------------------------------------------------- commit df1307f079ae69dcd735e0973de987b141d509da Author: Joachim Breitner Date: Tue Dec 9 18:18:11 2014 -0600 Link pre-ARMv6 spinlocks into all RTS variants Summary: For compatibility with ARM machines from pre v6, the RTS provides implementations of certain atomic operations. Previously, these were only included in the threaded RTS. But ghc (the library) contains the code in compiler/cbits/genSym.c, which uses these operations if there is more than one capability. But there is only one libHSghc, so the linker wants to resolve these symbols in every case. By providing these operations in all RTSs, the linker is happy. The only downside is a small amount of dead code in the non-threaded RTS on old ARM machines. Test Plan: It helped here. Reviewers: bgamari, austin Reviewed By: bgamari, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D564 GHC Trac Issues: #8951 >--------------------------------------------------------------- df1307f079ae69dcd735e0973de987b141d509da includes/stg/SMP.h | 4 ++-- rts/OldARMAtomic.c | 10 ++++++---- 2 files changed, 8 insertions(+), 6 deletions(-) diff --git a/includes/stg/SMP.h b/includes/stg/SMP.h index 732ac53..f6fd394 100644 --- a/includes/stg/SMP.h +++ b/includes/stg/SMP.h @@ -14,13 +14,13 @@ #ifndef SMP_H #define SMP_H -#if defined(THREADED_RTS) - #if arm_HOST_ARCH && defined(arm_HOST_ARCH_PRE_ARMv6) void arm_atomic_spin_lock(void); void arm_atomic_spin_unlock(void); #endif +#if defined(THREADED_RTS) + /* ---------------------------------------------------------------------------- Atomic operations ------------------------------------------------------------------------- */ diff --git a/rts/OldARMAtomic.c b/rts/OldARMAtomic.c index a28d2bc..3c60e6d 100644 --- a/rts/OldARMAtomic.c +++ b/rts/OldARMAtomic.c @@ -5,6 +5,12 @@ * Inefficient but necessary atomic locks used for implementing atomic * operations on ARM architectures pre-ARMv6. * + * These operations are not only referenced in the threaded RTS, but also in + * ghc (the library), via the operations in compiler/cbits/genSym.c. + * They are not actually called in a non-threaded environment, but we still + * need them in every RTS to make the linker happy, hence no + * #if defined(THREADED_RTS) here. See #8951. + * * -------------------------------------------------------------------------- */ #include "PosixSource.h" @@ -14,8 +20,6 @@ #include #endif -#if defined(THREADED_RTS) - #if arm_HOST_ARCH && defined(arm_HOST_ARCH_PRE_ARMv6) static volatile int atomic_spin = 0; @@ -51,5 +55,3 @@ void arm_atomic_spin_unlock() } #endif /* arm_HOST_ARCH && defined(arm_HOST_ARCH_PRE_ARMv6) */ - -#endif /* defined(THREADED_RTS) */ From git at git.haskell.org Wed Dec 10 01:58:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 01:58:37 +0000 (UTC) Subject: [commit: ghc] master: Document splitAt deviation from the Report (8b480d3) Message-ID: <20141210015837.036CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8b480d3192e6eff6183934d7bbcc2054611c3651/ghc >--------------------------------------------------------------- commit 8b480d3192e6eff6183934d7bbcc2054611c3651 Author: David Feuer Date: Tue Dec 9 18:12:33 2014 -0600 Document splitAt deviation from the Report Summary: `splitAt` is stricter than the Report specifies, so we should say so. Reviewers: hvr, austin Reviewed By: austin Subscribers: carter, thomie Projects: #ghc Differential Revision: https://phabricator.haskell.org/D562 GHC Trac Issues: #9870 >--------------------------------------------------------------- 8b480d3192e6eff6183934d7bbcc2054611c3651 docs/users_guide/bugs.xml | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/docs/users_guide/bugs.xml b/docs/users_guide/bugs.xml index 2d6fc65..30770f0 100644 --- a/docs/users_guide/bugs.xml +++ b/docs/users_guide/bugs.xml @@ -292,6 +292,17 @@ checking for duplicates. The reason for this is efficiency, pure and simple. + splitAt semantics + Data.List.splitAt is stricter than specified in the + Report. Specifically, the Report specifies that +splitAt n xs = (take n xs, drop n xs) + which implies that +splitAt undefined undefined = (undefined, undefined) + but GHC's implementation is strict in its first argument, so +splitAt undefined [] = undefined + + + zip and zipWith semantics zip and zipWith can give less defined results than the Report specifies in certain cases. This deviation From git at git.haskell.org Wed Dec 10 01:58:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 01:58:39 +0000 (UTC) Subject: [commit: ghc] master: Implement -XStaticValues (fc45f32) Message-ID: <20141210015839.D0C6C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fc45f32491313d2a44e72d8d59cdf95b1660189d/ghc >--------------------------------------------------------------- commit fc45f32491313d2a44e72d8d59cdf95b1660189d Author: Facundo Dom?nguez Date: Tue Dec 9 18:10:18 2014 -0600 Implement -XStaticValues Summary: As proposed in [1], this extension introduces a new syntactic form `static e`, where `e :: a` can be any closed expression. The static form produces a value of type `StaticPtr a`, which works as a reference that programs can "dereference" to get the value of `e` back. References are like `Ptr`s, except that they are stable across invocations of a program. The relevant wiki pages are [2, 3], which describe the motivation/ideas and implementation plan respectively. [1] Jeff Epstein, Andrew P. Black, and Simon Peyton-Jones. Towards Haskell in the cloud. SIGPLAN Not., 46(12):118?129, September 2011. ISSN 0362-1340. [2] https://ghc.haskell.org/trac/ghc/wiki/StaticPointers [3] https://ghc.haskell.org/trac/ghc/wiki/StaticPointers/ImplementationPlan Authored-by: Facundo Dom?nguez Authored-by: Mathieu Boespflug Authored-by: Alexander Vershilov Test Plan: `./validate` Reviewers: hvr, simonmar, simonpj, austin Reviewed By: simonpj, austin Subscribers: qnikst, bgamari, mboes, carter, thomie, goldfire Differential Revision: https://phabricator.haskell.org/D550 GHC Trac Issues: #7015 >--------------------------------------------------------------- fc45f32491313d2a44e72d8d59cdf95b1660189d compiler/deSugar/Coverage.hs | 3 + compiler/deSugar/Desugar.hs | 12 +- compiler/deSugar/DsExpr.hs | 109 ++++++++++++++++++ compiler/deSugar/DsMeta.hs | 9 +- compiler/deSugar/DsMonad.hs | 25 ++++- compiler/deSugar/StaticPtrTable.hs | 75 +++++++++++++ compiler/ghc.cabal.in | 1 + compiler/hsSyn/Convert.hs | 1 + compiler/hsSyn/HsExpr.hs | 7 ++ compiler/main/DynFlags.hs | 2 + compiler/parser/Lexer.x | 7 ++ compiler/parser/Parser.y | 2 + compiler/prelude/PrelNames.hs | 50 +++++++++ compiler/rename/RnExpr.hs | 37 ++++++ compiler/typecheck/TcBinds.hs | 2 +- compiler/typecheck/TcExpr.hs | 22 ++++ compiler/typecheck/TcHsSyn.hs | 4 + compiler/typecheck/TcRnDriver.hs | 21 +++- compiler/typecheck/TcRnMonad.hs | 4 +- compiler/typecheck/TcRnTypes.hs | 8 +- docs/users_guide/glasgow_exts.xml | 125 +++++++++++++++++++++ includes/HsFFI.h | 4 + includes/Rts.h | 1 + includes/rts/StaticPtrTable.h | 32 ++++++ libraries/base/GHC/StaticPtr.hs | 122 ++++++++++++++++++++ libraries/base/base.cabal | 1 + libraries/template-haskell/Language/Haskell/TH.hs | 2 +- .../template-haskell/Language/Haskell/TH/Lib.hs | 4 + .../template-haskell/Language/Haskell/TH/Ppr.hs | 2 + .../template-haskell/Language/Haskell/TH/Syntax.hs | 1 + rts/Hash.c | 23 ++++ rts/Hash.h | 7 ++ rts/Linker.c | 4 + rts/RtsStartup.c | 4 + rts/StaticPtrTable.c | 57 ++++++++++ rts/StaticPtrTable.h | 19 ++++ .../tests/codeGen/should_run/CgStaticPointers.hs | 36 ++++++ .../codeGen/should_run/CgStaticPointers.stdout | 5 + testsuite/tests/codeGen/should_run/all.T | 3 + .../tests/deSugar/should_run/DsStaticPointers.hs | 30 +++++ .../deSugar/should_run/DsStaticPointers.stdout | 5 + testsuite/tests/deSugar/should_run/all.T | 2 + testsuite/tests/driver/T4437.hs | 3 +- .../parser/should_compile/RdrNoStaticPointers01.hs | 7 ++ testsuite/tests/parser/should_compile/all.T | 1 + .../rename/should_fail/RnStaticPointersFail01.hs | 5 + .../should_fail/RnStaticPointersFail01.stderr | 6 + .../rename/should_fail/RnStaticPointersFail02.hs | 7 ++ .../should_fail/RnStaticPointersFail02.stderr | 8 ++ .../rename/should_fail/RnStaticPointersFail03.hs | 5 + .../should_fail/RnStaticPointersFail03.stderr | 6 + testsuite/tests/rename/should_fail/all.T | 6 + testsuite/tests/rts/GcStaticPointers.hs | 33 ++++++ testsuite/tests/rts/GcStaticPointers.stdout | 3 + testsuite/tests/rts/ListStaticPointers.hs | 26 +++++ testsuite/tests/rts/all.T | 7 ++ testsuite/tests/th/TH_StaticPointers.hs | 11 ++ testsuite/tests/th/TH_StaticPointers.stdout | 1 + testsuite/tests/th/TH_StaticPointers02.hs | 21 ++++ testsuite/tests/th/TH_StaticPointers02.stderr | 10 ++ testsuite/tests/th/all.T | 6 + .../typecheck/should_compile/TcStaticPointers01.hs | 17 +++ .../typecheck/should_compile/TcStaticPointers02.hs | 37 ++++++ testsuite/tests/typecheck/should_compile/all.T | 2 + .../should_fail/TcStaticPointersFail01.hs | 11 ++ .../should_fail/TcStaticPointersFail01.stderr | 6 + .../should_fail/TcStaticPointersFail02.hs | 12 ++ .../should_fail/TcStaticPointersFail02.stderr | 14 +++ .../should_fail/TcStaticPointersFail03.hs | 9 ++ .../should_fail/TcStaticPointersFail03.stderr | 6 + testsuite/tests/typecheck/should_fail/all.T | 6 + 71 files changed, 1163 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 fc45f32491313d2a44e72d8d59cdf95b1660189d From git at git.haskell.org Wed Dec 10 01:58:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 01:58:43 +0000 (UTC) Subject: [commit: ghc] master: fix misleading error message regarding function arity (09b7943) Message-ID: <20141210015843.1E2E13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/09b7943321f89b945d10f8a914f4c2cbf73dff91/ghc >--------------------------------------------------------------- commit 09b7943321f89b945d10f8a914f4c2cbf73dff91 Author: Yuras Shumovich Date: Tue Dec 9 18:11:44 2014 -0600 fix misleading error message regarding function arity Summary: The error reports something like: The function ?f? is applied to three arguments, but its type ?Int -> Float -> Char -> Bool? has only three The original type was "Monad m => Int -> Float -> m Bool", but "m" was unified with "-> Char". Now it looks better: The function ?f? is applied to three arguments, its type is ?Int -> Float -> m0 Bool?, it is specialized to ?Int -> Float -> Char -> Bool? Test Plan: T9605 Reviewers: simonpj, austin Reviewed By: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D556 GHC Trac Issues: #9605 >--------------------------------------------------------------- 09b7943321f89b945d10f8a914f4c2cbf73dff91 compiler/typecheck/TcUnify.hs | 34 ++++++++++++++++------ testsuite/tests/typecheck/should_fail/T9605.hs | 7 +++++ testsuite/tests/typecheck/should_fail/T9605.stderr | 11 +++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 4 files changed, 44 insertions(+), 9 deletions(-) diff --git a/compiler/typecheck/TcUnify.hs b/compiler/typecheck/TcUnify.hs index b75f0e8..5c80769 100644 --- a/compiler/typecheck/TcUnify.hs +++ b/compiler/typecheck/TcUnify.hs @@ -145,8 +145,19 @@ matchExpectedFunTys herald arity orig_ty -- In all other cases we bale out into ordinary unification -- However unlike the meta-tyvar case, we are sure that the - -- number of arrows doesn't match up, so we can add a bit - -- more context to the error message (cf Trac #7869) + -- number of arguments doesn't match arity of the original + -- type, so we can add a bit more context to the error message + -- (cf Trac #7869). + -- + -- It is not always an error, because specialized type may have + -- different arity, for example: + -- + -- > f1 = f2 'a' + -- > f2 :: Monad m => m Bool + -- > f2 = undefined + -- + -- But in that case we add specialized type into error context + -- anyway, because it may be useful. See also Trac #9605. go n_req ty = addErrCtxtM mk_ctxt $ defer n_req ty @@ -160,16 +171,21 @@ matchExpectedFunTys herald arity orig_ty ------------ mk_ctxt :: TidyEnv -> TcM (TidyEnv, MsgDoc) - mk_ctxt env = do { (env', orig_ty) <- zonkTidyTcType env orig_ty - ; let (args, _) = tcSplitFunTys orig_ty + mk_ctxt env = do { (env', ty) <- zonkTidyTcType env orig_ty + ; let (args, _) = tcSplitFunTys ty n_actual = length args - ; return (env', mk_msg orig_ty n_actual) } + (env'', orig_ty') = tidyOpenType env' orig_ty + ; return (env'', mk_msg orig_ty' ty n_actual) } - mk_msg ty n_args + mk_msg orig_ty ty n_args = herald <+> speakNOf arity (ptext (sLit "argument")) <> comma $$ - sep [ptext (sLit "but its type") <+> quotes (pprType ty), - if n_args == 0 then ptext (sLit "has none") - else ptext (sLit "has only") <+> speakN n_args] + if n_args == arity + then ptext (sLit "its type is") <+> quotes (pprType orig_ty) <> + comma $$ + ptext (sLit "it is specialized to") <+> quotes (pprType ty) + else sep [ptext (sLit "but its type") <+> quotes (pprType ty), + if n_args == 0 then ptext (sLit "has none") + else ptext (sLit "has only") <+> speakN n_args] {- Note [Foralls to left of arrow] diff --git a/testsuite/tests/typecheck/should_fail/T9605.hs b/testsuite/tests/typecheck/should_fail/T9605.hs new file mode 100644 index 0000000..b94afb4 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9605.hs @@ -0,0 +1,7 @@ +module T9605 where + +f1 :: Monad m => m Bool +f1 = undefined + +f2 :: Monad m => m Bool +f2 = f1 undefined diff --git a/testsuite/tests/typecheck/should_fail/T9605.stderr b/testsuite/tests/typecheck/should_fail/T9605.stderr new file mode 100644 index 0000000..4ba1d33 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9605.stderr @@ -0,0 +1,11 @@ + +T9605.hs:7:6: + Couldn't match type ?Bool? with ?m Bool? + Expected type: t0 -> m Bool + Actual type: t0 -> Bool + Relevant bindings include f2 :: m Bool (bound at T9605.hs:7:1) + The function ?f1? is applied to one argument, + its type is ?m0 Bool?, + it is specialized to ?t0 -> Bool? + In the expression: f1 undefined + In an equation for ?f2?: f2 = f1 undefined diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 1546b3a..27dbef9 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -352,3 +352,4 @@ test('T9109', normal, compile_fail, ['']) test('T9497d', normal, compile_fail, ['-fdefer-type-errors -fno-defer-typed-holes']) test('T8044', normal, compile_fail, ['']) test('T4921', normal, compile_fail, ['']) +test('T9605', normal, compile_fail, ['']) From git at git.haskell.org Wed Dec 10 03:16:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 03:16:47 +0000 (UTC) Subject: [commit: ghc] wip/rae: Only *one* Ord instance for Name. (908240d) Message-ID: <20141210031647.D03043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/908240d92f4415cde738887c0cde6b47b86200d4/ghc >--------------------------------------------------------------- commit 908240d92f4415cde738887c0cde6b47b86200d4 Author: Richard Eisenberg Date: Tue Dec 9 22:17:17 2014 -0500 Only *one* Ord instance for Name. >--------------------------------------------------------------- 908240d92f4415cde738887c0cde6b47b86200d4 libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 25ba7fa..e491476 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -660,7 +660,7 @@ Names constructed using @newName@ and @mkName@ may be used in bindings (such as @let x = ...@ or @\x -> ...@), but names constructed using @lookupValueName@, @lookupTypeName@, @'f@, @''T@ may not. -} -data Name = Name OccName NameFlavour deriving (Typeable, Data, Eq, Ord, Generic) +data Name = Name OccName NameFlavour deriving (Typeable, Data, Eq, Generic) instance Ord Name where -- check if unique is different before looking at strings From git at git.haskell.org Wed Dec 10 07:57:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 07:57:33 +0000 (UTC) Subject: [commit: ghc] master: Add proper expected output for T5435_dyn_asm on Darwin (659ec2c) Message-ID: <20141210075733.C75713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/659ec2ce347d8d612dfde4eec88a04de71e2bc15/ghc >--------------------------------------------------------------- commit 659ec2ce347d8d612dfde4eec88a04de71e2bc15 Author: Edward Z. Yang Date: Tue Dec 9 23:58:04 2014 -0800 Add proper expected output for T5435_dyn_asm on Darwin Summary: Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D565 >--------------------------------------------------------------- 659ec2ce347d8d612dfde4eec88a04de71e2bc15 testsuite/tests/rts/all.T | 2 ++ 1 file changed, 2 insertions(+) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index b997a57..89f1da8 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -142,6 +142,8 @@ def checkDynAsm(actual_file, normaliser): elif actual == ['ctors1', 'ctors2', 'initArray1', 'initArray2', 'success']: if_verbose(1, 'T5435_dyn_asm detected old-style dlopen, see #8458') return 1 + elif opsys('darwin') and actual == ['modInitFunc1', 'modInitFunc2', 'success']: + return 1 elif opsys('mingw32') and actual == ['ctors1', 'ctors2', 'success']: return 1 else: From git at git.haskell.org Wed Dec 10 08:08:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 08:08:28 +0000 (UTC) Subject: [commit: ghc] master: Only run subsections_via_symbols test when LLVM is available. (4d1c452) Message-ID: <20141210080828.57EEB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4d1c452daf54e0ed04ee66d6d3ea9078924afd51/ghc >--------------------------------------------------------------- commit 4d1c452daf54e0ed04ee66d6d3ea9078924afd51 Author: Edward Z. Yang Date: Wed Dec 10 00:08:31 2014 -0800 Only run subsections_via_symbols test when LLVM is available. Summary: Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D567 >--------------------------------------------------------------- 4d1c452daf54e0ed04ee66d6d3ea9078924afd51 testsuite/tests/llvm/should_run/subsections_via_symbols/all.T | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/testsuite/tests/llvm/should_run/subsections_via_symbols/all.T b/testsuite/tests/llvm/should_run/subsections_via_symbols/all.T index 2ecbaa5..9d5fc75 100644 --- a/testsuite/tests/llvm/should_run/subsections_via_symbols/all.T +++ b/testsuite/tests/llvm/should_run/subsections_via_symbols/all.T @@ -3,6 +3,10 @@ if config.os == 'darwin': else: only_darwin = skip +def f( name, opts ): + opts.only_ways = ['optllvm', 'llvm', 'debugllvm'] + +setTestOpts(f) # Note [_ffi_call_unix64] # From git at git.haskell.org Wed Dec 10 10:19:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 10:19:17 +0000 (UTC) Subject: [commit: ghc] master: compiler: fix trac issue #9817 (7ca5bb0) Message-ID: <20141210101917.116853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7ca5bb090ff78141fbe275b058a9e35ee496bd58/ghc >--------------------------------------------------------------- commit 7ca5bb090ff78141fbe275b058a9e35ee496bd58 Author: Marios Titas Date: Wed Dec 10 04:17:22 2014 -0600 compiler: fix trac issue #9817 Summary: When we call runHandlers, we must pass it a ForeignPtr. To ensure that this happens, we introduce a wrapper that receives a plain Ptr and converts it into a ForeignPtr. Then we adjust startSignalHandlers in rts/posix/Signals.c to call the wrapper instead of calling runHandlers directly. Reviewers: hvr, austin, rwbarton, simonmar Reviewed By: austin, simonmar Subscribers: simonmar, thomie, carter Differential Revision: https://phabricator.haskell.org/D515 GHC Trac Issues: #9817 >--------------------------------------------------------------- 7ca5bb090ff78141fbe275b058a9e35ee496bd58 libraries/base/GHC/Conc/Signal.hs | 11 ++++++++++- rts/Prelude.h | 4 ++-- rts/RtsStartup.c | 2 +- rts/package.conf.in | 4 ++-- rts/posix/Signals.c | 2 +- 5 files changed, 16 insertions(+), 7 deletions(-) diff --git a/libraries/base/GHC/Conc/Signal.hs b/libraries/base/GHC/Conc/Signal.hs index 3f5eacb..4afccf2 100644 --- a/libraries/base/GHC/Conc/Signal.hs +++ b/libraries/base/GHC/Conc/Signal.hs @@ -6,15 +6,17 @@ module GHC.Conc.Signal , HandlerFun , setHandler , runHandlers + , runHandlersPtr ) where import Control.Concurrent.MVar (MVar, newMVar, withMVar) import Data.Dynamic (Dynamic) import Foreign.C.Types (CInt) -import Foreign.ForeignPtr (ForeignPtr) +import Foreign.ForeignPtr (ForeignPtr, newForeignPtr) import Foreign.StablePtr (castPtrToStablePtr, castStablePtrToPtr, deRefStablePtr, freeStablePtr, newStablePtr) import Foreign.Ptr (Ptr, castPtr) +import Foreign.Marshal.Alloc (finalizerFree) import GHC.Arr (inRange) import GHC.Base import GHC.Conc.Sync (forkIO) @@ -70,6 +72,13 @@ runHandlers p_info sig = do Just (f,_) -> do _ <- forkIO (f p_info) return () +-- It is our responsibility to free the memory buffer, so we create a +-- foreignPtr. +runHandlersPtr :: Ptr Word8 -> Signal -> IO () +runHandlersPtr p s = do + fp <- newForeignPtr finalizerFree p + runHandlers fp s + -- Machinery needed to ensure that we only have one copy of certain -- CAFs in this module even when the base package is present twice, as -- it is when base is dynamically loaded into GHCi. The RTS keeps diff --git a/rts/Prelude.h b/rts/Prelude.h index 614c255..ae1e9cb 100644 --- a/rts/Prelude.h +++ b/rts/Prelude.h @@ -48,7 +48,7 @@ PRELUDE_CLOSURE(base_GHCziEventziThread_blockedOnBadFD_closure); PRELUDE_CLOSURE(base_GHCziConcziSync_runSparks_closure); PRELUDE_CLOSURE(base_GHCziConcziIO_ensureIOManagerIsRunning_closure); PRELUDE_CLOSURE(base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure); -PRELUDE_CLOSURE(base_GHCziConcziSignal_runHandlers_closure); +PRELUDE_CLOSURE(base_GHCziConcziSignal_runHandlersPtr_closure); PRELUDE_CLOSURE(base_GHCziTopHandler_flushStdHandles_closure); @@ -96,7 +96,7 @@ PRELUDE_INFO(base_GHCziStable_StablePtr_con_info); #define runSparks_closure DLL_IMPORT_DATA_REF(base_GHCziConcziSync_runSparks_closure) #define ensureIOManagerIsRunning_closure DLL_IMPORT_DATA_REF(base_GHCziConcziIO_ensureIOManagerIsRunning_closure) #define ioManagerCapabilitiesChanged_closure DLL_IMPORT_DATA_REF(base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure) -#define runHandlers_closure DLL_IMPORT_DATA_REF(base_GHCziConcziSignal_runHandlers_closure) +#define runHandlersPtr_closure DLL_IMPORT_DATA_REF(base_GHCziConcziSignal_runHandlersPtr_closure) #define flushStdHandles_closure DLL_IMPORT_DATA_REF(base_GHCziTopHandler_flushStdHandles_closure) diff --git a/rts/RtsStartup.c b/rts/RtsStartup.c index 490f2ea..1900882 100644 --- a/rts/RtsStartup.c +++ b/rts/RtsStartup.c @@ -223,7 +223,7 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config) getStablePtr((StgPtr)ioManagerCapabilitiesChanged_closure); #ifndef mingw32_HOST_OS getStablePtr((StgPtr)blockedOnBadFD_closure); - getStablePtr((StgPtr)runHandlers_closure); + getStablePtr((StgPtr)runHandlersPtr_closure); #endif /* initialise the shared Typeable store */ diff --git a/rts/package.conf.in b/rts/package.conf.in index ce44a09..2670fae 100644 --- a/rts/package.conf.in +++ b/rts/package.conf.in @@ -109,7 +109,7 @@ ld-options: , "-Wl,-u,_base_GHCziConcziIO_ensureIOManagerIsRunning_closure" , "-Wl,-u,_base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure" , "-Wl,-u,_base_GHCziConcziSync_runSparks_closure" - , "-Wl,-u,_base_GHCziConcziSignal_runHandlers_closure" + , "-Wl,-u,_base_GHCziConcziSignal_runHandlersPtr_closure" #else "-Wl,-u,ghczmprim_GHCziTypes_Izh_static_info" , "-Wl,-u,ghczmprim_GHCziTypes_Czh_static_info" @@ -151,7 +151,7 @@ ld-options: , "-Wl,-u,base_GHCziConcziIO_ensureIOManagerIsRunning_closure" , "-Wl,-u,base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure" , "-Wl,-u,base_GHCziConcziSync_runSparks_closure" - , "-Wl,-u,base_GHCziConcziSignal_runHandlers_closure" + , "-Wl,-u,base_GHCziConcziSignal_runHandlersPtr_closure" #endif /* Pick up static libraries in preference over dynamic if in earlier search diff --git a/rts/posix/Signals.c b/rts/posix/Signals.c index 36a72a5..44bd0b6 100644 --- a/rts/posix/Signals.c +++ b/rts/posix/Signals.c @@ -473,7 +473,7 @@ startSignalHandlers(Capability *cap) RtsFlags.GcFlags.initialStkSize, rts_apply(cap, rts_apply(cap, - &base_GHCziConcziSignal_runHandlers_closure, + &base_GHCziConcziSignal_runHandlersPtr_closure, rts_mkPtr(cap, info)), rts_mkInt(cap, info->si_signo)))); } From git at git.haskell.org Wed Dec 10 15:12:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 15:12:00 +0000 (UTC) Subject: [commit: ghc] master: Add Ord instances to TH (b006a1a) Message-ID: <20141210151200.430DD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b006a1af0c1b92f1f339da36b6059baa264ce2b9/ghc >--------------------------------------------------------------- commit b006a1af0c1b92f1f339da36b6059baa264ce2b9 Author: Richard Eisenberg Date: Tue Dec 9 17:39:11 2014 -0500 Add Ord instances to TH >--------------------------------------------------------------- b006a1af0c1b92f1f339da36b6059baa264ce2b9 docs/users_guide/7.10.1-notes.xml | 2 +- .../template-haskell/Language/Haskell/TH/Syntax.hs | 68 +++++++++++----------- 2 files changed, 35 insertions(+), 35 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b006a1af0c1b92f1f339da36b6059baa264ce2b9 From git at git.haskell.org Wed Dec 10 16:00:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 16:00:25 +0000 (UTC) Subject: [commit: ghc] master: Reorganise the work list, so that flattening goals are treated in the right order (13b0b46) Message-ID: <20141210160025.CA9E13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/13b0b460d365828c7d41b39d2ce7d5bbe4c69f98/ghc >--------------------------------------------------------------- commit 13b0b460d365828c7d41b39d2ce7d5bbe4c69f98 Author: Simon Peyton Jones Date: Tue Dec 9 17:38:12 2014 +0000 Reorganise the work list, so that flattening goals are treated in the right order Trac #9872 showed the importance of processing goals in depth-first, so that we do not build up a huge pool of suspended function calls, waiting for their children to fire. There is a detailed explanation in Note [The flattening work list] in TcFlatten The effect for Trac #9872 (slow1.hs) is dramatic. We go from too long to wait down to 28Gbyte allocation. GHC 7.8.3 did 116Gbyte allocation! >--------------------------------------------------------------- 13b0b460d365828c7d41b39d2ce7d5bbe4c69f98 compiler/typecheck/TcCanonical.hs | 32 +-- compiler/typecheck/TcFlatten.hs | 97 ++++---- compiler/typecheck/TcInteract.hs | 15 +- compiler/typecheck/TcRnMonad.hs | 10 +- compiler/typecheck/TcSMonad.hs | 246 +++++++++++++-------- .../indexed-types/should_fail/NoMatchErr.stderr | 2 +- .../tests/indexed-types/should_fail/T2544.stderr | 21 +- .../tests/indexed-types/should_fail/T2627b.stderr | 4 +- .../tests/indexed-types/should_fail/T4093a.hs | 24 +- .../tests/indexed-types/should_fail/T4093a.stderr | 4 +- .../tests/indexed-types/should_fail/T7010.stderr | 2 +- .../tests/indexed-types/should_fail/T9036.stderr | 4 +- .../typecheck/should_fail/FrozenErrorTests.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5853.stderr | 25 ++- 14 files changed, 288 insertions(+), 200 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 13b0b460d365828c7d41b39d2ce7d5bbe4c69f98 From git at git.haskell.org Wed Dec 10 16:00:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 16:00:28 +0000 (UTC) Subject: [commit: ghc] master: Get rid of TcMType.newWantedEvVar(s) (1496598) Message-ID: <20141210160028.684603A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/149659817afc0ffe4148af483c4ec44994b03107/ghc >--------------------------------------------------------------- commit 149659817afc0ffe4148af483c4ec44994b03107 Author: Simon Peyton Jones Date: Wed Dec 10 13:12:11 2014 +0000 Get rid of TcMType.newWantedEvVar(s) Hardly used, not helpful. Use newEvVar instead. >--------------------------------------------------------------- 149659817afc0ffe4148af483c4ec44994b03107 compiler/typecheck/Inst.hs | 2 +- compiler/typecheck/TcMType.hs | 9 +-------- 2 files changed, 2 insertions(+), 9 deletions(-) diff --git a/compiler/typecheck/Inst.hs b/compiler/typecheck/Inst.hs index a059c50..afe466b 100644 --- a/compiler/typecheck/Inst.hs +++ b/compiler/typecheck/Inst.hs @@ -73,7 +73,7 @@ emitWanteds origin theta = mapM (emitWanted origin) theta emitWanted :: CtOrigin -> TcPredType -> TcM EvVar emitWanted origin pred = do { loc <- getCtLoc origin - ; ev <- newWantedEvVar pred + ; ev <- newEvVar pred ; emitFlat $ mkNonCanonical $ CtWanted { ctev_pred = pred, ctev_evar = ev, ctev_loc = loc } ; return ev } diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index d5a2781..b95e0c3 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -29,7 +29,6 @@ module TcMType ( -------------------------------- -- Creating new evidence variables newEvVar, newEvVars, newEq, newDict, - newWantedEvVar, newWantedEvVars, newTcEvBinds, addTcEvBind, newFlatWanted, newFlatWanteds, @@ -124,12 +123,6 @@ newMetaKindVars n = mapM (\ _ -> newMetaKindVar) (nOfThem n ()) newEvVars :: TcThetaType -> TcM [EvVar] newEvVars theta = mapM newEvVar theta -newWantedEvVar :: TcPredType -> TcM EvVar -newWantedEvVar = newEvVar - -newWantedEvVars :: TcThetaType -> TcM [EvVar] -newWantedEvVars theta = mapM newWantedEvVar theta - -------------- newEvVar :: TcPredType -> TcM EvVar @@ -165,7 +158,7 @@ predTypeOccName ty = case classifyPredType ty of newFlatWanted :: CtOrigin -> PredType -> TcM Ct newFlatWanted orig pty = do loc <- getCtLoc orig - v <- newWantedEvVar pty + v <- newEvVar pty return $ mkNonCanonical $ CtWanted { ctev_evar = v , ctev_pred = pty From git at git.haskell.org Wed Dec 10 16:00:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 16:00:31 +0000 (UTC) Subject: [commit: ghc] master: Fix type-variable details naming (fixes misleading debug output) (3e234f7) Message-ID: <20141210160031.13A9C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3e234f73c0a5537bdaf518d0ace375541f158a47/ghc >--------------------------------------------------------------- commit 3e234f73c0a5537bdaf518d0ace375541f158a47 Author: Simon Peyton Jones Date: Wed Dec 10 13:12:47 2014 +0000 Fix type-variable details naming (fixes misleading debug output) >--------------------------------------------------------------- 3e234f73c0a5537bdaf518d0ace375541f158a47 compiler/typecheck/TcType.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index 5945bde..a00cd3b 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -522,8 +522,8 @@ pprTcTyVarDetails (MetaTv { mtv_info = info, mtv_tclvl = tclvl }) where pp_info = case info of ReturnTv -> ptext (sLit "ret") - TauTv True -> ptext (sLit "tau") - TauTv False -> ptext (sLit "twc") + TauTv True -> ptext (sLit "twc") + TauTv False -> ptext (sLit "tau") SigTv -> ptext (sLit "sig") FlatMetaTv -> ptext (sLit "fuv") From git at git.haskell.org Wed Dec 10 16:00:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 16:00:33 +0000 (UTC) Subject: [commit: ghc] master: When flattening, try reducing type-family applications eagerly (bcb967a) Message-ID: <20141210160033.A29A03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bcb967abaaa51df281b70d905df915b6b4bb31cc/ghc >--------------------------------------------------------------- commit bcb967abaaa51df281b70d905df915b6b4bb31cc Author: Simon Peyton Jones Date: Wed Dec 10 13:54:17 2014 +0000 When flattening, try reducing type-family applications eagerly This short-cut can improve performance quite a bit, by short-circuiting the process of creating a fresh constraint and binding for each reduction. See Note [Reduce type family applications eagerly] in TcFlatten To do this I had to generalise the inert_flat_cache a bit, so that the rhs is not necessarily a type variable; but nothing fundamental. >--------------------------------------------------------------- bcb967abaaa51df281b70d905df915b6b4bb31cc compiler/typecheck/TcCanonical.hs | 2 +- compiler/typecheck/TcFlatten.hs | 47 +++++++++++++++++++++++++++++++-------- compiler/typecheck/TcSMonad.hs | 19 +++++++++------- 3 files changed, 50 insertions(+), 18 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 669dc06..4042fe8 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -649,7 +649,7 @@ canCFunEqCan ev fn tys fsk Stop ev s -> return (Stop ev s) ; ContinueWith ev' -> - do { extendFlatCache fn tys' (ctEvCoercion ev', fsk) + do { extendFlatCache fn tys' (ctEvCoercion ev', fsk_ty, ev') ; continueWith (CFunEqCan { cc_ev = ev', cc_fun = fn , cc_tyargs = tys', cc_fsk = fsk }) } } } diff --git a/compiler/typecheck/TcFlatten.hs b/compiler/typecheck/TcFlatten.hs index 6ab8b22..f8d2148 100644 --- a/compiler/typecheck/TcFlatten.hs +++ b/compiler/typecheck/TcFlatten.hs @@ -798,20 +798,32 @@ flatten_exact_fam_app_fully fmode tc tys ; mb_ct <- lookupFlatCache tc xis ; case mb_ct of - Just (co, fsk) -- co :: F xis ~ fsk - | isFskTyVar fsk || not (isGiven ctxt_ev) + Just (co, rhs_ty, ev) -- co :: F xis ~ fsk + | ev `canRewriteOrSame` ctxt_ev -> -- Usable hit in the flat-cache - -- isFskTyVar checks for a "given" in the cache - do { traceTcS "flatten/flat-cache hit" $ (ppr tc <+> ppr xis $$ ppr fsk $$ ppr co) - ; (fsk_xi, fsk_co) <- flattenTyVar fmode fsk + -- We certainly *can* use a Wanted for a Wanted + do { traceTcS "flatten/flat-cache hit" $ (ppr tc <+> ppr xis $$ ppr rhs_ty $$ ppr co) + ; (fsk_xi, fsk_co) <- flatten_one fmode rhs_ty -- The fsk may already have been unified, so flatten it -- fsk_co :: fsk_xi ~ fsk ; return (fsk_xi, fsk_co `mkTcTransCo` mkTcSymCo co `mkTcTransCo` ret_co) } -- :: fsk_xi ~ F xis - _ -> do { let fam_ty = mkTyConApp tc xis + -- Try to reduce the family application right now + -- See Note [Reduce type family applications eagerly] + _ -> do { mb_match <- matchFam tc xis + ; case mb_match of { + Just (norm_co, norm_ty) + -> do { (xi, final_co) <- flatten_one fmode norm_ty + ; let co = norm_co `mkTcTransCo` mkTcSymCo final_co + ; extendFlatCache tc xis (co, xi, ctxt_ev) + ; return (xi, mkTcSymCo co `mkTcTransCo` ret_co) } ; + Nothing -> + do { let fam_ty = mkTyConApp tc xis ; (ev, fsk) <- newFlattenSkolem ctxt_ev fam_ty - ; extendFlatCache tc xis (ctEvCoercion ev, fsk) + ; let fsk_ty = mkTyVarTy fsk + co = ctEvCoercion ev + ; extendFlatCache tc xis (co, fsk_ty, ev) -- The new constraint (F xis ~ fsk) is not necessarily inert -- (e.g. the LHS may be a redex) so we must put it in the work list @@ -822,9 +834,26 @@ flatten_exact_fam_app_fully fmode tc tys ; emitFlatWork ct ; traceTcS "flatten/flat-cache miss" $ (ppr fam_ty $$ ppr fsk $$ ppr ev) - ; return (mkTyVarTy fsk, mkTcSymCo (ctEvCoercion ev) `mkTcTransCo` ret_co) } } + ; return (fsk_ty, mkTcSymCo co `mkTcTransCo` ret_co) } + } } } + +{- Note [Reduce type family applications eagerly] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +If we come across a type-family application like (Append (Cons x Nil) t), +then, rather than flattening to a skolem etc, we may as well just reduce +it on the spot to (Cons x t). This saves a lot of intermediate steps. +Examples that are helped are tests T9872, and T5321Fun. + +So just before we create the new skolem, we attempt to reduce it by one +step (using matchFam). If that works, then recursively flatten the rhs, +which may in turn do lots more reductions. + +Once we've got a flat rhs, we extend the flatten-cache to record the +result. Doing so can save lots of work when the same redex shows up +more than once. Note that we record the link from the redex all the +way to its *final* value, not just the single step reduction. + -{- ************************************************************************ * * Flattening a type variable diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index 204a471..cba8e24 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -430,10 +430,13 @@ data InertSet -- Canonical Given, Wanted, Derived (no Solved) -- Sometimes called "the inert set" - , inert_flat_cache :: FunEqMap (TcCoercion, TcTyVar) + , inert_flat_cache :: FunEqMap (TcCoercion, TcType, CtEvidence) -- See Note [Type family equations] - -- If F tys :-> (co, fsk), - -- then co :: F tys ~ fsk + -- If F tys :-> (co, ty, ev), + -- then co :: F tys ~ ty + -- + -- The 'ev' field is just for the G/W/D flavour, nothing more! + -- -- Just a hash-cons cache for use when flattening only -- These include entirely un-processed goals, so don't use -- them to solve a top-level goal, else you may end up solving @@ -799,7 +802,7 @@ checkAllSolved || unsolved_dicts || unsolved_funeqs || not (isEmptyBag (inert_insols icans)))) } -lookupFlatCache :: TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcTyVar)) +lookupFlatCache :: TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcType, CtEvidence)) lookupFlatCache fam_tc tys = do { IS { inert_flat_cache = flat_cache , inert_cans = IC { inert_funeqs = inert_funeqs } } <- getTcSInerts @@ -809,7 +812,7 @@ lookupFlatCache fam_tc tys lookup_inerts inert_funeqs | Just (CFunEqCan { cc_ev = ctev, cc_fsk = fsk }) <- findFunEqs inert_funeqs fam_tc tys - = Just (ctEvCoercion ctev, fsk) + = Just (ctEvCoercion ctev, mkTyVarTy fsk, ctev) | otherwise = Nothing lookup_flats flat_cache = findFunEq flat_cache fam_tc tys @@ -1546,12 +1549,12 @@ newFlattenSkolem ctxt_ev fam_ty where loc = ctEvLoc ctxt_ev -extendFlatCache :: TyCon -> [Type] -> (TcCoercion, TcTyVar) -> TcS () -extendFlatCache tc xi_args (co, fsk) +extendFlatCache :: TyCon -> [Type] -> (TcCoercion, TcType, CtEvidence) -> TcS () +extendFlatCache tc xi_args stuff = do { dflags <- getDynFlags ; when (gopt Opt_FlatCache dflags) $ updInertTcS $ \ is@(IS { inert_flat_cache = fc }) -> - is { inert_flat_cache = insertFunEq fc tc xi_args (co, fsk) } } + is { inert_flat_cache = insertFunEq fc tc xi_args stuff } } -- Instantiations -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ From git at git.haskell.org Wed Dec 10 16:00:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 16:00:36 +0000 (UTC) Subject: [commit: ghc] master: Implement a fast path for new constraints looking like (a~b), namely unifyWanted (832f8db) Message-ID: <20141210160036.571073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/832f8db2ee13120d5914149bd86f81df7e377b75/ghc >--------------------------------------------------------------- commit 832f8db2ee13120d5914149bd86f81df7e377b75 Author: Simon Peyton Jones Date: Wed Dec 10 14:11:51 2014 +0000 Implement a fast path for new constraints looking like (a~b), namely unifyWanted Looking at some typechecker traces I could see places where we were laboriously creating a Refl coercion. This patch short-circuits the process. See TcCanonical: Note [unifyWanted and unifyDerived] Note [Decomposing TyConApps] I ended up with some refactoring, notably * I moved xCtEvidence, rewriteEvidence, rewriteEqEvidence from TcSMonad to TcCanonical There are some knock-on effects, but only minor ones. >--------------------------------------------------------------- 832f8db2ee13120d5914149bd86f81df7e377b75 compiler/typecheck/TcCanonical.hs | 387 ++++++++++++++++++++++++++++++++++++-- compiler/typecheck/TcInteract.hs | 17 +- compiler/typecheck/TcSMonad.hs | 353 ++++++---------------------------- 3 files changed, 436 insertions(+), 321 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 832f8db2ee13120d5914149bd86f81df7e377b75 From git at git.haskell.org Wed Dec 10 16:00:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 16:00:39 +0000 (UTC) Subject: [commit: ghc] master: Tests for Trac #9872 (fca85c9) Message-ID: <20141210160039.A34B23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fca85c9b1617417a6170f3591a29d1fe36d35da5/ghc >--------------------------------------------------------------- commit fca85c9b1617417a6170f3591a29d1fe36d35da5 Author: Simon Peyton Jones Date: Wed Dec 10 14:36:47 2014 +0000 Tests for Trac #9872 >--------------------------------------------------------------- fca85c9b1617417a6170f3591a29d1fe36d35da5 testsuite/tests/perf/compiler/T9872a.hs | 167 ++++++++++++++++++++++++++++ testsuite/tests/perf/compiler/T9872a.stderr | 66 +++++++++++ testsuite/tests/perf/compiler/T9872b.hs | 115 +++++++++++++++++++ testsuite/tests/perf/compiler/T9872b.stderr | 24 ++++ testsuite/tests/perf/compiler/all.T | 20 ++++ 5 files changed, 392 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 fca85c9b1617417a6170f3591a29d1fe36d35da5 From git at git.haskell.org Wed Dec 10 16:00:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 16:00:42 +0000 (UTC) Subject: [commit: ghc] master: Testsuite wibbles from constraint-solver improvements (37b3646) Message-ID: <20141210160042.406053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/37b3646c9da4da62ae95aa3a9152335e485b261e/ghc >--------------------------------------------------------------- commit 37b3646c9da4da62ae95aa3a9152335e485b261e Author: Simon Peyton Jones Date: Wed Dec 10 14:35:54 2014 +0000 Testsuite wibbles from constraint-solver improvements >--------------------------------------------------------------- 37b3646c9da4da62ae95aa3a9152335e485b261e .../tests/indexed-types/should_fail/T4179.stderr | 6 +- .../tests/indexed-types/should_fail/T7729.stderr | 5 +- .../tests/indexed-types/should_fail/T7729a.stderr | 5 +- .../tests/indexed-types/should_fail/T9662.stderr | 72 +++++++++++----------- testsuite/tests/perf/compiler/T5837.stderr | 9 ++- testsuite/tests/perf/compiler/all.T | 16 +++-- testsuite/tests/typecheck/should_compile/T9708.hs | 3 + .../tests/typecheck/should_compile/T9708.stderr | 17 ----- testsuite/tests/typecheck/should_compile/all.T | 2 +- .../typecheck/should_fail/ContextStack2.stderr | 6 +- .../typecheck/should_fail/FrozenErrorTests.stderr | 2 +- 11 files changed, 68 insertions(+), 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 37b3646c9da4da62ae95aa3a9152335e485b261e From git at git.haskell.org Wed Dec 10 16:00:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Dec 2014 16:00:44 +0000 (UTC) Subject: [commit: ghc] master: Comments only: move flattening notes to TcFlatten (a225c70) Message-ID: <20141210160044.D5C413A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a225c70e00586e2f38a0e27fae698324ae81b006/ghc >--------------------------------------------------------------- commit a225c70e00586e2f38a0e27fae698324ae81b006 Author: Simon Peyton Jones Date: Wed Dec 10 14:56:30 2014 +0000 Comments only: move flattening notes to TcFlatten >--------------------------------------------------------------- a225c70e00586e2f38a0e27fae698324ae81b006 compiler/typecheck/Flattening-notes | 202 +--------------------------- compiler/typecheck/TcFlatten.hs | 253 +++++++++++++++++++++++++++++------- compiler/typecheck/TcInteract.hs | 49 +------ 3 files changed, 207 insertions(+), 297 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a225c70e00586e2f38a0e27fae698324ae81b006 From git at git.haskell.org Thu Dec 11 03:20:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Dec 2014 03:20:33 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Merge remote-tracking branch 'origin/master' into wip/rae-new-coercible (f0bb9e9) Message-ID: <20141211032033.57B183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/f0bb9e98c1316869a14feed97bcb3f48256c335a/ghc >--------------------------------------------------------------- commit f0bb9e98c1316869a14feed97bcb3f48256c335a Merge: d02925a a225c70 Author: Richard Eisenberg Date: Wed Dec 10 15:17:02 2014 -0500 Merge remote-tracking branch 'origin/master' into wip/rae-new-coercible Conflicts: compiler/typecheck/TcCanonical.hs compiler/typecheck/TcFlatten.hs compiler/typecheck/TcInteract.hs compiler/typecheck/TcSMonad.hs testsuite/tests/typecheck/should_compile/all.T >--------------------------------------------------------------- Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f0bb9e98c1316869a14feed97bcb3f48256c335a From git at git.haskell.org Thu Dec 11 03:20:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Dec 2014 03:20:35 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Sequelae from previous merge. (ad0e495) Message-ID: <20141211032035.EC7603A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/ad0e495c32934ccd19fa515ef48cd3820205f084/ghc >--------------------------------------------------------------- commit ad0e495c32934ccd19fa515ef48cd3820205f084 Author: Richard Eisenberg Date: Wed Dec 10 16:37:21 2014 -0500 Sequelae from previous merge. >--------------------------------------------------------------- ad0e495c32934ccd19fa515ef48cd3820205f084 compiler/typecheck/TcCanonical.hs | 55 ++++++++---- compiler/typecheck/TcFlatten.hs | 181 ++++++++++++++------------------------ compiler/typecheck/TcInteract.hs | 9 +- compiler/typecheck/TcSMonad.hs | 14 ++- compiler/typecheck/TcType.hs | 8 +- compiler/utils/MonadUtils.hs | 6 +- 6 files changed, 121 insertions(+), 152 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ad0e495c32934ccd19fa515ef48cd3820205f084 From git at git.haskell.org Thu Dec 11 03:20:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Dec 2014 03:20:38 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Flat constraint --> Simple constraint (418806d) Message-ID: <20141211032038.C124F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/418806d0247bdf4c62bff5d7fc6f4028be9e51a3/ghc >--------------------------------------------------------------- commit 418806d0247bdf4c62bff5d7fc6f4028be9e51a3 Author: Richard Eisenberg Date: Wed Dec 10 16:58:09 2014 -0500 Flat constraint --> Simple constraint >--------------------------------------------------------------- 418806d0247bdf4c62bff5d7fc6f4028be9e51a3 compiler/typecheck/Inst.hs | 6 +-- compiler/typecheck/TcCanonical.hs | 2 +- compiler/typecheck/TcDeriv.hs | 8 +-- compiler/typecheck/TcErrors.hs | 30 +++++------ compiler/typecheck/TcInteract.hs | 50 +++++++++---------- compiler/typecheck/TcMType.hs | 28 +++++------ compiler/typecheck/TcRnMonad.hs | 12 ++--- compiler/typecheck/TcRnTypes.hs | 42 ++++++++-------- compiler/typecheck/TcSMonad.hs | 20 ++++---- compiler/typecheck/TcSimplify.hs | 102 +++++++++++++++++++------------------- compiler/typecheck/TcType.hs | 2 +- compiler/typecheck/TcUnify.hs | 2 +- 12 files changed, 152 insertions(+), 152 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 418806d0247bdf4c62bff5d7fc6f4028be9e51a3 From git at git.haskell.org Thu Dec 11 03:20:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Dec 2014 03:20:41 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Don't look under newtypes when unifying representationally. (2005d52) Message-ID: <20141211032041.695B13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/2005d52a4028ed78a99fd02e8055da1dc9fba64f/ghc >--------------------------------------------------------------- commit 2005d52a4028ed78a99fd02e8055da1dc9fba64f Author: Richard Eisenberg Date: Wed Dec 10 22:20:12 2014 -0500 Don't look under newtypes when unifying representationally. >--------------------------------------------------------------- 2005d52a4028ed78a99fd02e8055da1dc9fba64f compiler/typecheck/TcCanonical.hs | 1 + testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs | 6 ++---- .../tests/typecheck/should_fail/TcCoercibleFail.stderr | 13 ++++++++++--- 3 files changed, 13 insertions(+), 7 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index bc3e280..cfb2d89 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -1593,6 +1593,7 @@ unifyWanted loc role orig_ty1 orig_ty2 ; return (mkTcTyConAppCo role funTyCon [co_s,co_t]) } go (TyConApp tc1 tys1) (TyConApp tc2 tys2) | tc1 == tc2, isDecomposableTyCon tc1, tys1 `equalLength` tys2 + , not (isNewTyCon tc1) || role == Nominal -- don't look under newtypes! = do { cos <- zipWith3M (unifyWanted loc) (tyConRolesX role tc1) tys1 tys2 ; return (mkTcTyConAppCo role tc1 cos) } go (TyVarTy tv) ty2 diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs b/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs index 0431eee..c102da5 100644 --- a/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs +++ b/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs @@ -20,10 +20,8 @@ foo4 = coerce $ one :: Down Int newtype Void = Void Void foo5 = coerce :: Void -> () --- Do not test this; fills up memory ---newtype VoidBad a = VoidBad (VoidBad (a,a)) ---foo5 = coerce :: (VoidBad ()) -> () - +newtype VoidBad a = VoidBad (VoidBad (a,a)) +foo5' = coerce :: (VoidBad ()) -> () -- This shoul fail with a context stack overflow newtype Fix f = Fix (f (Fix f)) diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFail.stderr b/testsuite/tests/typecheck/should_fail/TcCoercibleFail.stderr index 6d1cee2..52d2c25 100644 --- a/testsuite/tests/typecheck/should_fail/TcCoercibleFail.stderr +++ b/testsuite/tests/typecheck/should_fail/TcCoercibleFail.stderr @@ -39,15 +39,22 @@ TcCoercibleFail.hs:21:8: In the expression: coerce :: Void -> () In an equation for ?foo5?: foo5 = coerce :: Void -> () -TcCoercibleFail.hs:30:8: +TcCoercibleFail.hs:24:9: + Couldn't match representation of type ?()? + with that of ?VoidBad ()? + Relevant role signatures: type role VoidBad phantom + In the expression: coerce :: (VoidBad ()) -> () + In an equation for ?foo5'?: foo5' = coerce :: (VoidBad ()) -> () + +TcCoercibleFail.hs:28:8: Context reduction stack overflow; size = 101 Use -fcontext-stack=N to increase stack size to N - Coercible Int Age + Coercible (Fix (Either Int)) (Fix (Either Age)) In the expression: coerce :: Fix (Either Int) -> Fix (Either Age) In an equation for ?foo6?: foo6 = coerce :: Fix (Either Int) -> Fix (Either Age) -TcCoercibleFail.hs:31:8: +TcCoercibleFail.hs:29:8: Couldn't match representation of type ?()? with that of ?Either Int (Fix (Either Int))? arising from trying to show that the representations of From git at git.haskell.org Thu Dec 11 03:20:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Dec 2014 03:20:43 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible's head updated: Don't look under newtypes when unifying representationally. (2005d52) Message-ID: <20141211032043.BE5AC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/rae-new-coercible' now includes: e74a9e9 Remove `inline` from integer_gmp_mpn_import1() 7535c83 Comments only 37c2ed4 Optimise partitionFunEqs for the 'false' case 15a54be Improve the treatment of AppTy equalities d64e682 Comments and variable names only, in type checking of (e1 $ e2) 1d44261 Revise the inert-set invariants again ac73d1a Revise flattening-notes 5818378 RAE's response to SPJ's question in flattening-notes b06908b Fix #9871 by clarifying documentation. 8688f6a Add doctest examples for Data.Maybe 2515686 catch some recent typos c2c1888 Update `process` submodule to pull in Safe Haskell fixes e5974f8 Proposal for Backpack file format [skip ci] fc45f32 Implement -XStaticValues 09b7943 fix misleading error message regarding function arity 8b480d3 Document splitAt deviation from the Report df1307f Link pre-ARMv6 spinlocks into all RTS variants 659ec2c Add proper expected output for T5435_dyn_asm on Darwin 4d1c452 Only run subsections_via_symbols test when LLVM is available. 7ca5bb0 compiler: fix trac issue #9817 b006a1a Add Ord instances to TH 13b0b46 Reorganise the work list, so that flattening goals are treated in the right order 1496598 Get rid of TcMType.newWantedEvVar(s) 3e234f7 Fix type-variable details naming (fixes misleading debug output) bcb967a When flattening, try reducing type-family applications eagerly 832f8db Implement a fast path for new constraints looking like (a~b), namely unifyWanted 37b3646 Testsuite wibbles from constraint-solver improvements fca85c9 Tests for Trac #9872 a225c70 Comments only: move flattening notes to TcFlatten f0bb9e9 Merge remote-tracking branch 'origin/master' into wip/rae-new-coercible ad0e495 Sequelae from previous merge. 418806d Flat constraint --> Simple constraint 2005d52 Don't look under newtypes when unifying representationally. From git at git.haskell.org Thu Dec 11 10:11:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Dec 2014 10:11:06 +0000 (UTC) Subject: [commit: ghc] master: White space wibble only (d45edfb) Message-ID: <20141211101106.C78E13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d45edfb396798e8e729fb7d3dc235b9ac1e63a17/ghc >--------------------------------------------------------------- commit d45edfb396798e8e729fb7d3dc235b9ac1e63a17 Author: Simon Peyton Jones Date: Thu Dec 11 08:39:10 2014 +0000 White space wibble only >--------------------------------------------------------------- d45edfb396798e8e729fb7d3dc235b9ac1e63a17 compiler/typecheck/TcFlatten.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcFlatten.hs b/compiler/typecheck/TcFlatten.hs index 5cb12bd..99eb915 100644 --- a/compiler/typecheck/TcFlatten.hs +++ b/compiler/typecheck/TcFlatten.hs @@ -882,7 +882,7 @@ A "generalised substitution" S is a set of triples (a -f-> t), where f is a flavour such that (WF1) if (a -f1-> t1) in S - (a -f2-> t2) in S + (a -f2-> t2) in S then neither (f1 >= f2) nor (f2 >= f1) hold (WF2) if (a -f-> t) is in S, then t /= a From git at git.haskell.org Thu Dec 11 10:11:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Dec 2014 10:11:09 +0000 (UTC) Subject: [commit: ghc] master: Add a third test variant to Trac #9872 (7256213) Message-ID: <20141211101109.9F7DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7256213843b80d75a86f033be77516a62d56044a/ghc >--------------------------------------------------------------- commit 7256213843b80d75a86f033be77516a62d56044a Author: Simon Peyton Jones Date: Thu Dec 11 10:11:41 2014 +0000 Add a third test variant to Trac #9872 >--------------------------------------------------------------- 7256213843b80d75a86f033be77516a62d56044a testsuite/tests/perf/compiler/T9872c.hs | 131 +++++++++++++++++++++ .../perf/compiler/{T9872a.stderr => T9872c.stderr} | 2 +- testsuite/tests/perf/compiler/all.T | 9 ++ 3 files changed, 141 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/T9872c.hs b/testsuite/tests/perf/compiler/T9872c.hs new file mode 100644 index 0000000..b6a0f0d --- /dev/null +++ b/testsuite/tests/perf/compiler/T9872c.hs @@ -0,0 +1,131 @@ +{- + - Instant Insanity using Closed Type Families, but no DataKinds + - + - See: http://stackoverflow.com/questions/26538595 + -} + +{-# OPTIONS_GHC -ftype-function-depth=400 #-} + +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE UndecidableInstances #-} + +import Prelude hiding (all, flip, map, filter ) + +data Proxy a = Proxy + +main = print (Proxy :: Proxy (Solutions Cubes)) + +data R -- Red +data G -- Green +data B -- Blue +data W -- White + +data Cube u f r b l d + +data True +data False + +type family And b1 b2 :: * where + And True True = True + And b1 b2 = False + +type family NE x y :: * where + NE x x = False + NE x y = True + +type family EQ x y :: * where + EQ a a = True + EQ a b = False + +data Nil = Nil +data Cons x xs = Cons x xs + +type family All l :: * where + All Nil = True + All (Cons False xs) = False + All (Cons True xs) = All xs + +type family ListConcat xs ys :: * where + ListConcat Nil ys = ys + ListConcat (Cons x xs) ys = Cons x (ListConcat xs ys) + +type family AppendIf b a as :: * where + AppendIf False a as = as + AppendIf True a as = Cons a as + +data Rotate +data Twist +data Flip + +type family Apply f a :: * where + Apply Rotate (Cube u f r b l d) = (Cube u r b l f d) + Apply Twist (Cube u f r b l d) = (Cube f r u l d b) + Apply Flip (Cube u f r b l d) = (Cube d l b r f u) + +type family Map f as :: * where + Map f Nil = Nil + Map f (Cons a as) = Cons (Apply f a) (Map f as) + +type family MapAppend f as :: * where + MapAppend f xs = ListConcat xs (Map f xs) + +type family MapAppend2 f as :: * where + MapAppend2 f xs = ListConcat xs (MapAppend f (Map f xs)) + +type family MapAppend3 f as :: * where + MapAppend3 f xs = ListConcat xs (MapAppend2 f (Map f xs)) + +type family Iterate2 f as :: * where + Iterate2 f Nil = Nil + Iterate2 f (Cons a as) = ListConcat (Cons (Apply f a) (Cons a Nil)) (Iterate2 f as) + +type family Iterate3 f as :: * where + Iterate3 f (Cons a as) = + ListConcat (Cons a + (Cons (Apply f a) + (Cons (Apply f (Apply f a)) + Nil))) + (Iterate3 f as) + +type family Iterate4 f as :: * where + Iterate4 f Nil = Nil + Iterate4 f (Cons a as) = + ListConcat (Cons a + (Cons (Apply f a) + (Cons (Apply f (Apply f a)) + (Cons (Apply f (Apply f (Apply f a))) + Nil)))) + (Iterate4 f as) + +type family Orientations c :: * where + Orientations c = MapAppend3 Rotate (MapAppend2 Twist (MapAppend Flip (Cons c Nil))) + +type Cube1 = Cube B G W G B R +type Cube2 = Cube W G B W R R +type Cube3 = Cube G W R B R R +type Cube4 = Cube B R G G W W + +type Cubes = Cons Cube1 (Cons Cube2 (Cons Cube3 (Cons Cube4 Nil))) + +type family Compatible c d :: * where + Compatible (Cube u1 f1 r1 b1 l1 d1) (Cube u2 f2 r2 b2 l2 d2) = + All (Cons (NE f1 f2) (Cons (NE r1 r2) (Cons (NE b1 b2) (Cons (NE l1 l2) Nil)))) + +type family Allowed c cs :: * where + Allowed c Nil = True + Allowed c (Cons s ss) = And (Compatible c s) (Allowed c ss) + +type family MatchingOrientations as sol :: * where + MatchingOrientations Nil sol = Nil + MatchingOrientations (Cons o os) sol = + AppendIf (Allowed o sol) (Cons o sol) (MatchingOrientations os sol) + +type family AllowedCombinations os sols :: * where + AllowedCombinations os Nil = Nil + AllowedCombinations os (Cons sol sols) = + ListConcat (MatchingOrientations os sol) (AllowedCombinations os sols) + +type family Solutions c :: * where + Solutions Nil = Cons Nil Nil + Solutions (Cons c cs) = AllowedCombinations (Orientations c) (Solutions cs) diff --git a/testsuite/tests/perf/compiler/T9872a.stderr b/testsuite/tests/perf/compiler/T9872c.stderr similarity index 99% copy from testsuite/tests/perf/compiler/T9872a.stderr copy to testsuite/tests/perf/compiler/T9872c.stderr index b38fcae..121e54d 100644 --- a/testsuite/tests/perf/compiler/T9872a.stderr +++ b/testsuite/tests/perf/compiler/T9872c.stderr @@ -1,5 +1,5 @@ -T9872a.hs:16:8: +T9872c.hs:17:8: No instance for (Show (Proxy (Cons diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 104741a..3d3f6b1 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -565,3 +565,12 @@ test('T9872b', ], compile_fail, ['']) +test('T9872c', + [ only_ways(['normal']), + compiler_stats_num_field('bytes allocated', + [(wordsize(64), 5495850096, 5) + # 2014-12-10 5495850096 Initally created + ]), + ], + compile_fail, + ['']) From git at git.haskell.org Thu Dec 11 10:44:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Dec 2014 10:44:43 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #9090 (8c82563) Message-ID: <20141211104443.C59863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8c825633135e24f6a0bbcc2c4097afada6ad6167/ghc >--------------------------------------------------------------- commit 8c825633135e24f6a0bbcc2c4097afada6ad6167 Author: Simon Peyton Jones Date: Thu Dec 11 10:44:32 2014 +0000 Test Trac #9090 >--------------------------------------------------------------- 8c825633135e24f6a0bbcc2c4097afada6ad6167 .../tests/indexed-types/should_compile/T9090.hs | 28 ++++++++++++++++++++++ testsuite/tests/indexed-types/should_compile/all.T | 1 + 2 files changed, 29 insertions(+) diff --git a/testsuite/tests/indexed-types/should_compile/T9090.hs b/testsuite/tests/indexed-types/should_compile/T9090.hs new file mode 100644 index 0000000..6d2b6ba --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T9090.hs @@ -0,0 +1,28 @@ +{-# LANGUAGE RankNTypes, ConstraintKinds, TypeFamilies #-} +module T9090 where + +import GHC.Exts (Constraint) + +type family F (c :: Constraint) :: Constraint +type instance F (Eq a) = Eq a + +-- checks +f :: Eq b => (forall a. F (Eq a) => f a -> Bool) -> f b -> Bool +f = error "urk" -- g x = g x + +-- checks +f' :: Eq b => (forall a. Eq a => f a -> Bool) -> f b -> Bool +f' = f + +-- checks, so GHC seems to think that both types are interchangeable +f'' :: Eq b => (forall a. F (Eq a) => f a -> Bool) -> f b -> Bool +f'' = f' + +-- checks +test' y = f' (\ (Just x) -> x /= x) y + +-- fails +test y = f (\ (Just x) -> x /= x) y + +-- fails too, unsurprisingly +test'' y = f'' (\ (Just x) -> x /= x) y diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index 4c48d3e..ae15c27 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -250,3 +250,4 @@ test('Sock', normal, compile, ['']) test('T9211', normal, compile, ['']) test('T9747', normal, compile, ['']) test('T9582', normal, compile, ['']) +test('T9090', normal, compile, ['']) From git at git.haskell.org Thu Dec 11 17:12:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Dec 2014 17:12:07 +0000 (UTC) Subject: [commit: ghc] master: Fix an obscure but terrible bug in the simplifier (Trac #9567) (b8392ae) Message-ID: <20141211171207.313BC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b8392ae76a6d39c57be94b5ba041c450ab479e2b/ghc >--------------------------------------------------------------- commit b8392ae76a6d39c57be94b5ba041c450ab479e2b Author: Simon Peyton Jones Date: Thu Dec 11 17:12:49 2014 +0000 Fix an obscure but terrible bug in the simplifier (Trac #9567) The issue was that contInputType simply gave the wrong answer for type applications. There was no way to fix contInputType; it just didn't have enough information. So I did this: * Split the ApplyTo constructor of SimplUtils.SimplCont into ApplyToVal ApplyToTy I used record syntax for them; we should do this for some of the other constructors too. * The latter carries a sc_hole_ty, which is the type of the continuation's "hole" * Maintaining this type meant that I had do to something similar for SimplUtils.ArgSpec. * I renamed contInputType to contHoleType for consistency. * I did a bit of refactoring around the call to tryRules in Simplify, which was jolly confusing before. The resulting code is quite nice now. And it has the additional merit that it works. The tests are simply tc124 and T7891 with -O enabled. >--------------------------------------------------------------- b8392ae76a6d39c57be94b5ba041c450ab479e2b compiler/simplCore/SimplUtils.hs | 337 +++++++++++++--------- compiler/simplCore/Simplify.hs | 140 +++++---- testsuite/tests/typecheck/should_compile/T7891.hs | 2 + testsuite/tests/typecheck/should_compile/tc124.hs | 2 + 4 files changed, 292 insertions(+), 189 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b8392ae76a6d39c57be94b5ba041c450ab479e2b From git at git.haskell.org Thu Dec 11 23:19:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Dec 2014 23:19:20 +0000 (UTC) Subject: [commit: ghc] master: 32-bit performance changes following constraint solver improvements (058262b) Message-ID: <20141211231920.B08EB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/058262bac0bbcd65f40703bf8047238ffa30d2c3/ghc >--------------------------------------------------------------- commit 058262bac0bbcd65f40703bf8047238ffa30d2c3 Author: Simon Peyton Jones Date: Thu Dec 11 20:32:02 2014 +0000 32-bit performance changes following constraint solver improvements Things get faster, except T5030 >--------------------------------------------------------------- 058262bac0bbcd65f40703bf8047238ffa30d2c3 testsuite/tests/perf/compiler/all.T | 19 +++++++++++++------ testsuite/tests/perf/haddock/all.T | 3 ++- 2 files changed, 15 insertions(+), 7 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 3d3f6b1..b98a9bc 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -311,10 +311,13 @@ test('T4007', test('T5030', [compiler_stats_num_field('bytes allocated', - [(wordsize(32), 198573456, 10), + [(wordsize(32), 227205560, 10), # previous: 196457520 # 2012-10-08: 259547660 (x86/Linux, new codegen) # 2013-11-21: 198573456 (x86 Windows, 64 bit machine) + # 2014-12-10: 227205560 constraint solver got worse again; more agressive solving + # of family-applications leads to less sharing, I think + (wordsize(64), 449042120, 10)]), # Previously 530000000 (+/- 10%) # 17/1/13: 602993184 (x86_64/Linux) @@ -397,11 +400,12 @@ test('T783', test('T5321Fun', [ only_ways(['normal']), # no optimisation for this one compiler_stats_num_field('bytes allocated', - [(wordsize(32), 299656164, 10), + [(wordsize(32), 206406188, 10), # prev: 300000000 # 2012-10-08: 344416344 x86/Linux # (increase due to new codegen) # 2014-09-03: 299656164 (specialisation and inlining) + # 10/12/2014: 206406188 # Improvements in constraint solver (wordsize(64), 408110888, 10)]) # prev: 585521080 # 29/08/2012: 713385808 # (increase due to new codegen) @@ -443,10 +447,11 @@ test('T5321FD', test('T5642', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(32), 753045568, 10), + [(wordsize(32), 641085256, 10), # sample from x86/Linux # prev: 650000000 # 2014-09-03: 753045568 + # 2014-12-10: 641085256 Improvements in constraints solver (wordsize(64), 1282916024, 10)]) # prev: 1300000000 @@ -465,11 +470,12 @@ test('T5642', test('T5837', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(32), 135914136, 10), + [(wordsize(32), 115905208, 10), # 40000000 (x86/Linux) - # 2013-11-13: 45520936 (x86/Windows, 64bit machine) - # 2014-09-03: 37096484 (Windows laptop, w/w for INLINABLE things + # 2013-11-13: 45520936 (x86/Windows, 64bit machine) + # 2014-09-03: 37096484 (Windows laptop, w/w for INLINABLE things # 2014-12-01: 135914136 (Windows laptop, regression see below) + # 2014-12-08 115905208 Constraint solver perf improvements (esp kick-out) (wordsize(64), 234790312, 10)]) # sample: 3926235424 (amd64/Linux, 15/2/2012) @@ -541,6 +547,7 @@ test('T9675', compiler_stats_num_field('bytes allocated', [(wordsize(64), 544489040, 10) # 2014-10-13 544489040 + ,(wordsize(32), 250000000, 10) ]), ], compile, diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index 58900ff..027686e 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -88,11 +88,12 @@ test('haddock.compiler', # 2012-11-27: 28708374824 (amd64/Linux) # 2014-09-10: 30353349160 (amd64/Linux) post-AMP cleanup # 2014-11-22: 33562468736 (amd64/Linux) - ,(platform('i386-unknown-mingw32'), 104140852, 10) + ,(platform('i386-unknown-mingw32'), 217933548, 10) # 2012-10-30: 13773051312 (x86/Windows) # 2013-02-10: 14925262356 (x86/Windows) # 2013-11-13: 14328363592 (x86/Windows, 64bit machine) # 2014-12-01: 104140852 (x86/Windows, sudden shrinkage!) + # 2014-12-10: 217933548 increased again ,(wordsize(32), 15110426000, 1)]) # 2012-08-14: 13471797488 (x86/OSX) # 2014-01-22: 14581475024 (x86/Linux - new haddock) From git at git.haskell.org Fri Dec 12 19:08:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Dec 2014 19:08:31 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Bugfixing (5bc717e) Message-ID: <20141212190831.979673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/5bc717e9374c3d1c5b24fe676696f7a377e0068d/ghc >--------------------------------------------------------------- commit 5bc717e9374c3d1c5b24fe676696f7a377e0068d Author: Richard Eisenberg Date: Fri Dec 12 10:40:18 2014 -0500 Bugfixing >--------------------------------------------------------------- 5bc717e9374c3d1c5b24fe676696f7a377e0068d compiler/typecheck/TcCanonical.hs | 4 +++- testsuite/tests/typecheck/should_compile/T9708.hs | 9 ++++++++- testsuite/tests/typecheck/should_compile/all.T | 2 +- 3 files changed, 12 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index cfb2d89..cc1197d 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -1593,7 +1593,8 @@ unifyWanted loc role orig_ty1 orig_ty2 ; return (mkTcTyConAppCo role funTyCon [co_s,co_t]) } go (TyConApp tc1 tys1) (TyConApp tc2 tys2) | tc1 == tc2, isDecomposableTyCon tc1, tys1 `equalLength` tys2 - , not (isNewTyCon tc1) || role == Nominal -- don't look under newtypes! + , (not (isNewTyCon tc1) && not (isDataFamilyTyCon tc1)) || role == Nominal + -- don't look under newtypes! = do { cos <- zipWith3M (unifyWanted loc) (tyConRolesX role tc1) tys1 tys2 ; return (mkTcTyConAppCo role tc1 cos) } go (TyVarTy tv) ty2 @@ -1637,6 +1638,7 @@ unify_derived loc role orig_ty1 orig_ty2 ; unify_derived loc role t1 t2 } go (TyConApp tc1 tys1) (TyConApp tc2 tys2) | tc1 == tc2, isDecomposableTyCon tc1, tys1 `equalLength` tys2 + , (not (isNewTyCon tc1) && not (isDataFamilyTyCon tc1)) || role == Nominal = unifyDeriveds loc (tyConRolesX role tc1) tys1 tys2 go (TyVarTy tv) ty2 = do { mb_ty <- isFilledMetaTyVar_maybe tv diff --git a/testsuite/tests/typecheck/should_compile/T9708.hs b/testsuite/tests/typecheck/should_compile/T9708.hs index b170ef3..61928d4 100644 --- a/testsuite/tests/typecheck/should_compile/T9708.hs +++ b/testsuite/tests/typecheck/should_compile/T9708.hs @@ -7,7 +7,14 @@ import Data.Proxy type family SomeFun (n :: Nat) -- See the Trac ticket; whether this suceeds or fails is distintly random --- Currently it succeeds + +-- upon creation, commit f861fc6ad8e5504a4fecfc9bb0945fe2d313687c, this failed + +-- with Simon's optimization to the flattening algorithm, commit +-- 37b3646c9da4da62ae95aa3a9152335e485b261e, this succeeded + +-- with the change to stop Deriveds from rewriting Deriveds (around Dec. 12, 2014), +-- this failed again ti7 :: (x <= y, y <= x) => Proxy (SomeFun x) -> Proxy y -> () ti7 _ _ = () diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index f2337db..7d33ad5 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -425,7 +425,7 @@ test('T9569a', normal, compile, ['']) test('T9117', normal, compile, ['']) test('T9117_2', normal, compile, ['']) test('T9117_3', normal, compile, ['']) -test('T9708', normal, compile, ['']) +test('T9708', expect_broken(9708), compile, ['']) test('T9404', normal, compile, ['']) test('T9404b', normal, compile, ['']) test('T7220', normal, compile, ['']) From git at git.haskell.org Fri Dec 12 19:08:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Dec 2014 19:08:34 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Change kick_out_eq to match statement of proof. (d9e7055) Message-ID: <20141212190834.4C6093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/d9e7055ce46b2368e34f5084ae23f767105c9cdb/ghc >--------------------------------------------------------------- commit d9e7055ce46b2368e34f5084ae23f767105c9cdb Author: Richard Eisenberg Date: Fri Dec 12 10:40:31 2014 -0500 Change kick_out_eq to match statement of proof. >--------------------------------------------------------------- d9e7055ce46b2368e34f5084ae23f767105c9cdb compiler/typecheck/TcInteract.hs | 43 +++++++++++++++++++++------------------- 1 file changed, 23 insertions(+), 20 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 18ca682..8949dc7 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1014,26 +1014,29 @@ kick_out new_flavour new_eq_rel new_tv (IC { inert_eqs = tv_eqs [] -> acc_in (eq1:_) -> extendVarEnv acc_in (cc_tyvar eq1) eqs_in) where - (eqs_out, eqs_in) = partition kick_out_eq eqs - - -- kick_out_eq implements kick-out criteria (K1-3) - -- in the main theorem of Note [The inert equalities] in TcFlatten - kick_out_eq (CTyEqCan { cc_tyvar = tv, cc_rhs = rhs_ty, cc_ev = ev - , cc_eq_rel = eq_rel }) - = can_rewrite ev - && (tv == new_tv - || (ev `eqCanRewrite` ev && new_tv `elemVarSet` tyVarsOfType rhs_ty) - || exposes_new_tv eq_rel rhs_ty) - - kick_out_eq ct = pprPanic "kick_out_eq" (ppr ct) - - -- implements rule (K3) the main theorem of Note [The inert equalities] - -- in TcFlatten - exposes_new_tv NomEq rhs - = case getTyVar_maybe rhs of - Just tv_r -> tv_r == new_tv - Nothing -> False - exposes_new_tv ReprEq rhs = isTyVarExposed new_tv rhs + (eqs_in, eqs_out) = partition keep_eq eqs + + -- implements criteria K1-K3 in Note [The inert equalities] in TcFlatten + keep_eq (CTyEqCan { cc_tyvar = tv, cc_rhs = rhs_ty, cc_ev = ev + , cc_eq_rel = eq_rel }) + | tv == new_tv + = not (can_rewrite ev) -- (K1) + + | otherwise + = check_k2 && check_k3 + where + check_k2 = not (ev `eqCanRewrite` ev) + || not (can_rewrite ev) + || not (new_tv `elemVarSet` tyVarsOfType rhs_ty) + + check_k3 + | can_rewrite ev + = case eq_rel of + NomEq -> not (rhs_ty `eqType` mkTyVarTy new_tv) + ReprEq -> isTyVarExposed new_tv rhs_ty + + | otherwise + = True {- Note [Kicking out inert constraints] From git at git.haskell.org Fri Dec 12 19:08:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Dec 2014 19:08:36 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Fix warning (f7ebbbf) Message-ID: <20141212190836.F41D53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/f7ebbbf549c5ef347a65976d02beced501b3f3c8/ghc >--------------------------------------------------------------- commit f7ebbbf549c5ef347a65976d02beced501b3f3c8 Author: Richard Eisenberg Date: Fri Dec 12 10:46:47 2014 -0500 Fix warning >--------------------------------------------------------------- f7ebbbf549c5ef347a65976d02beced501b3f3c8 compiler/typecheck/TcInteract.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 8949dc7..c67e437 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1038,6 +1038,8 @@ kick_out new_flavour new_eq_rel new_tv (IC { inert_eqs = tv_eqs | otherwise = True + keep_eq ct = pprPanic "keep_eq" (ppr ct) + {- Note [Kicking out inert constraints] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ From git at git.haskell.org Fri Dec 12 19:08:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Dec 2014 19:08:39 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Remove IsCoercion (f48795d) Message-ID: <20141212190839.B42903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/f48795d5073b7bdaf39477e780f531d0d4a3654e/ghc >--------------------------------------------------------------- commit f48795d5073b7bdaf39477e780f531d0d4a3654e Author: Richard Eisenberg Date: Fri Dec 12 11:17:02 2014 -0500 Remove IsCoercion >--------------------------------------------------------------- f48795d5073b7bdaf39477e780f531d0d4a3654e compiler/deSugar/DsBinds.hs | 1 + compiler/typecheck/FamInst.hs | 14 ++++---- compiler/typecheck/TcEvidence.hs | 13 +++++--- compiler/typecheck/TcHsSyn.hs | 3 ++ compiler/types/Coercion.hs | 69 ++++++++++++---------------------------- 5 files changed, 40 insertions(+), 60 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f48795d5073b7bdaf39477e780f531d0d4a3654e From git at git.haskell.org Fri Dec 12 19:08:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Dec 2014 19:08:42 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Zonk Coercions embedded in TcCoercions; they *might* have TcTyVars! (1900380) Message-ID: <20141212190842.6023F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/190038033778925092b03169d33e29f4c8e5fb05/ghc >--------------------------------------------------------------- commit 190038033778925092b03169d33e29f4c8e5fb05 Author: Richard Eisenberg Date: Fri Dec 12 12:01:58 2014 -0500 Zonk Coercions embedded in TcCoercions; they *might* have TcTyVars! >--------------------------------------------------------------- 190038033778925092b03169d33e29f4c8e5fb05 compiler/typecheck/TcHsSyn.hs | 31 ++++++++++++++++++++++++++++--- 1 file changed, 28 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs index 4b7b930..a0433f9 100644 --- a/compiler/typecheck/TcHsSyn.hs +++ b/compiler/typecheck/TcHsSyn.hs @@ -1411,7 +1411,7 @@ zonkTcTypeToType env ty -- The two interesting cases! go (TyVarTy tv) = zonkTyVarOcc env tv - go (ForAllTy tv ty) = ASSERT( isImmutableTyVar tv ) do + go (ForAllTy tv ty) = ASSERT( isImmutableTyVar tv ) do { (env', tv') <- zonkTyBndrX env tv ; ty' <- zonkTcTypeToType env' ty ; return (ForAllTy tv' ty') } @@ -1419,6 +1419,32 @@ zonkTcTypeToType env ty zonkTcTypeToTypes :: ZonkEnv -> [TcType] -> TcM [Type] zonkTcTypeToTypes env tys = mapM (zonkTcTypeToType env) tys +zonkCoToCo :: ZonkEnv -> Coercion -> TcM Coercion +zonkCoToCo env co + = go co + where + go (Refl r ty) = mkReflCo r <$> zonkTcTypeToType env ty + go (TyConAppCo r tc args) = mkTyConAppCo r tc <$> mapM go args + go (AppCo co arg) = mkAppCo <$> go co <*> go arg + go (AxiomInstCo ax ind args) = mkAxiomInstCo ax ind <$> mapM go args + go (UnivCo r ty1 ty2) = mkUnivCo r <$> zonkTcTypeToType env ty1 + <*> zonkTcTypeToType env ty2 + go (SymCo co) = mkSymCo <$> go co + go (TransCo co1 co2) = mkTransCo <$> go co1 <*> go co2 + go (NthCo n co) = mkNthCo n <$> go co + go (LRCo lr co) = mkLRCo lr <$> go co + go (InstCo co arg) = mkInstCo <$> go co <*> zonkCoArgToCoArg env arg + go (SubCo co) = mkSubCo <$> go co + go (AxiomRuleCo ax ts cs) = AxiomRuleCo ax <$> mapM (zonkTcTypeToType env) ts + <*> mapM go cs + + -- The two interesting cases! + go (CoVarCo cv) = return (mkCoVarCo $ zonkIdOcc env cv) + go (ForAllCo tv co) = ASSERT( isImmutableTyVar tv ) + do { (env', tv') <- zonkTyBndrX env tv + ; co' <- zonkCoToCo env' co + ; return (mkForAllCo tv' co') } + zonkTvCollecting :: TcRef TyVarSet -> UnboundTyVarZonker -- This variant collects unbound type variables in a mutable variable -- Works on both types and kinds @@ -1481,5 +1507,4 @@ zonkTcCoToCo env co ; cs' <- mapM go cs ; return (TcAxiomRuleCo co ts' cs') } - go c@(TcCoercion _co) = ASSERT( isEmptyVarSet (coVarsOfCo _co) ) - return c -- these can't contain TcTyVars + go (TcCoercion co) = do { co' <- zonkCoToCo co; return (TcCoercion co') } From git at git.haskell.org Fri Dec 12 19:08:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Dec 2014 19:08:45 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Allow multiple type family instances to match in reduceTyFamApp_maybe (f49e19b) Message-ID: <20141212190845.070BA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/f49e19b9f65a00e767ae45d60e1766f4a4f82973/ghc >--------------------------------------------------------------- commit f49e19b9f65a00e767ae45d60e1766f4a4f82973 Author: Richard Eisenberg Date: Fri Dec 12 12:02:31 2014 -0500 Allow multiple type family instances to match in reduceTyFamApp_maybe >--------------------------------------------------------------- f49e19b9f65a00e767ae45d60e1766f4a4f82973 compiler/types/FamInstEnv.hs | 6 ++++-- testsuite/tests/ghci/scripts/GhciKinds.hs | 4 ++++ testsuite/tests/ghci/scripts/GhciKinds.script | 5 +++++ testsuite/tests/ghci/scripts/GhciKinds.stdout | 6 ++++++ 4 files changed, 19 insertions(+), 2 deletions(-) diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs index e366037..2578726 100644 --- a/compiler/types/FamInstEnv.hs +++ b/compiler/types/FamInstEnv.hs @@ -806,8 +806,10 @@ reduceTyFamApp_maybe envs role tc tys -- (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 + , FamInstMatch { fim_instance = fam_inst + , fim_tys = inst_tys } : _ <- lookupFamInstEnv envs tc ntys + -- NB: Allow multiple matches because of compatible overlap + = let ax = famInstAxiom fam_inst co = mkUnbranchedAxInstCo role ax inst_tys ty = pSnd (coercionKind co) diff --git a/testsuite/tests/ghci/scripts/GhciKinds.hs b/testsuite/tests/ghci/scripts/GhciKinds.hs index 4945814..8e1af37 100644 --- a/testsuite/tests/ghci/scripts/GhciKinds.hs +++ b/testsuite/tests/ghci/scripts/GhciKinds.hs @@ -4,3 +4,7 @@ module GhciKinds where type family F a :: * type instance F [a] = a -> F a type instance F Int = Bool + +-- test ":kind!" in the presence of compatible overlap +type instance F (Maybe a) = Char +type instance F (Maybe Int) = Char diff --git a/testsuite/tests/ghci/scripts/GhciKinds.script b/testsuite/tests/ghci/scripts/GhciKinds.script index 310c2a8..fa94015 100644 --- a/testsuite/tests/ghci/scripts/GhciKinds.script +++ b/testsuite/tests/ghci/scripts/GhciKinds.script @@ -3,3 +3,8 @@ :l GhciKinds :kind F [[[Int]]] :kind! F [[[Int]]] +:kind! F (Maybe Int) +:kind! F (Maybe Bool) + +:seti -XRankNTypes +:kind! forall a. F (Maybe a) diff --git a/testsuite/tests/ghci/scripts/GhciKinds.stdout b/testsuite/tests/ghci/scripts/GhciKinds.stdout index 3961994..e34b84a 100644 --- a/testsuite/tests/ghci/scripts/GhciKinds.stdout +++ b/testsuite/tests/ghci/scripts/GhciKinds.stdout @@ -3,3 +3,9 @@ Maybe :: * -> * F [[[Int]]] :: * F [[[Int]]] :: * = [[Int]] -> [Int] -> Int -> Bool +F (Maybe Int) :: * += Char +F (Maybe Bool) :: * += Char +forall a. F (Maybe a) :: * += Char From git at git.haskell.org Fri Dec 12 19:08:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Dec 2014 19:08:47 +0000 (UTC) Subject: [commit: ghc] wip/rae-new-coercible: Use reduceTyFamApp_maybe in TcInteract.matchFam (b35a19e) Message-ID: <20141212190847.A12EB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae-new-coercible Link : http://ghc.haskell.org/trac/ghc/changeset/b35a19e72dc71a756e6f8c1d4e0641dd2dbfa49c/ghc >--------------------------------------------------------------- commit b35a19e72dc71a756e6f8c1d4e0641dd2dbfa49c Author: Richard Eisenberg Date: Fri Dec 12 14:02:44 2014 -0500 Use reduceTyFamApp_maybe in TcInteract.matchFam >--------------------------------------------------------------- b35a19e72dc71a756e6f8c1d4e0641dd2dbfa49c compiler/typecheck/TcHsSyn.hs | 9 +++++---- compiler/typecheck/TcSMonad.hs | 31 +++---------------------------- compiler/types/FamInstEnv.hs | 3 ++- 3 files changed, 10 insertions(+), 33 deletions(-) diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs index a0433f9..16d4bfc 100644 --- a/compiler/typecheck/TcHsSyn.hs +++ b/compiler/typecheck/TcHsSyn.hs @@ -38,7 +38,7 @@ import TypeRep -- We can see the representation of types import TcType import TcMType ( defaultKindVarToStar, zonkQuantifiedTyVar, writeMetaTyVar ) import TcEvidence -import Coercion ( coVarsOfCo ) +import Coercion import TysPrim import TysWiredIn import Type @@ -1426,14 +1426,14 @@ zonkCoToCo env co go (Refl r ty) = mkReflCo r <$> zonkTcTypeToType env ty go (TyConAppCo r tc args) = mkTyConAppCo r tc <$> mapM go args go (AppCo co arg) = mkAppCo <$> go co <*> go arg - go (AxiomInstCo ax ind args) = mkAxiomInstCo ax ind <$> mapM go args + go (AxiomInstCo ax ind args) = AxiomInstCo ax ind <$> mapM go args go (UnivCo r ty1 ty2) = mkUnivCo r <$> zonkTcTypeToType env ty1 <*> zonkTcTypeToType env ty2 go (SymCo co) = mkSymCo <$> go co go (TransCo co1 co2) = mkTransCo <$> go co1 <*> go co2 go (NthCo n co) = mkNthCo n <$> go co go (LRCo lr co) = mkLRCo lr <$> go co - go (InstCo co arg) = mkInstCo <$> go co <*> zonkCoArgToCoArg env arg + go (InstCo co arg) = mkInstCo <$> go co <*> zonkTcTypeToType env arg go (SubCo co) = mkSubCo <$> go co go (AxiomRuleCo ax ts cs) = AxiomRuleCo ax <$> mapM (zonkTcTypeToType env) ts <*> mapM go cs @@ -1507,4 +1507,5 @@ zonkTcCoToCo env co ; cs' <- mapM go cs ; return (TcAxiomRuleCo co ts' cs') } - go (TcCoercion co) = do { co' <- zonkCoToCo co; return (TcCoercion co') } + go (TcCoercion co) = do { co' <- zonkCoToCo env co + ; return (TcCoercion co') } diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index 0e37bc1..a0dda96 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -106,7 +106,6 @@ import Kind import TcType import DynFlags import Type -import CoAxiom(sfMatchFam) import TcEvidence import Class @@ -132,11 +131,11 @@ import UniqFM import Maybes ( orElse, firstJusts ) import TrieMap +import Control.Arrow ( first ) import Control.Monad( ap, when, unless, MonadPlus(..) ) import MonadUtils import Data.IORef import Data.List ( partition, foldl' ) -import Pair #ifdef DEBUG import Digraph @@ -1742,33 +1741,9 @@ instDFunConstraints loc = mapM (newWantedEvVar loc) matchFam :: TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcType)) -- Given (F tys) return (ty, co), where co :: F tys ~ ty matchFam tycon args - | isOpenTypeFamilyTyCon tycon = do { fam_envs <- getFamInstEnvs - ; let mb_match = tcLookupFamInst fam_envs tycon args - ; traceTcS "lookupFamInst" $ - vcat [ ppr tycon <+> ppr args - , pprTvBndrs (varSetElems (tyVarsOfTypes args)) - , ppr mb_match ] - ; case mb_match of - Nothing -> return Nothing - Just (FamInstMatch { fim_instance = famInst - , fim_tys = inst_tys }) - -> let co = mkTcUnbranchedAxInstCo Nominal (famInstAxiom famInst) inst_tys - ty = pSnd $ tcCoercionKind co - in return $ Just (co, ty) } - - | Just ax <- isClosedSynFamilyTyCon_maybe tycon - , Just (ind, inst_tys) <- chooseBranch ax args - = let co = mkTcAxInstCo Nominal ax ind inst_tys - ty = pSnd (tcCoercionKind co) - in return $ Just (co, ty) - - | Just ops <- isBuiltInSynFamTyCon_maybe tycon = - return $ do (r,ts,ty) <- sfMatchFam ops args - return (mkTcAxiomRuleCo r ts [], ty) - - | otherwise - = return Nothing + ; return $ fmap (first TcCoercion) $ + reduceTyFamApp_maybe fam_envs Nominal tycon args } {- Note [Residual implications] diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs index 2578726..0b5bf2b 100644 --- a/compiler/types/FamInstEnv.hs +++ b/compiler/types/FamInstEnv.hs @@ -20,11 +20,12 @@ module FamInstEnv ( FamInstMatch(..), lookupFamInstEnv, lookupFamInstEnvConflicts, - chooseBranch, isDominatedBy, + isDominatedBy, -- Normalisation topNormaliseType, topNormaliseType_maybe, normaliseType, normaliseTcApp, + reduceTyFamApp_maybe, -- Flattening flattenTys From git at git.haskell.org Fri Dec 12 22:56:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Dec 2014 22:56:14 +0000 (UTC) Subject: [commit: ghc] master: Rewrite `Coercible` solver (0cc47eb) Message-ID: <20141212225614.3A5F53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0cc47eb90805f3e166ac4d3991e66d3346ca05e7/ghc >--------------------------------------------------------------- commit 0cc47eb90805f3e166ac4d3991e66d3346ca05e7 Author: Richard Eisenberg Date: Fri Dec 12 17:19:21 2014 -0500 Rewrite `Coercible` solver Summary: This is a rewrite of the algorithm to solve for Coercible "instances". A preliminary form of these ideas is at https://ghc.haskell.org/trac/ghc/wiki/Design/NewCoercibleSolver The basic idea here is that the `EqPred` constructor of `PredTree` now is parameterised by a new type `EqRel` (where `data EqRel = NomEq | ReprEq`). Thus, every equality constraint can now talk about nominal equality (the usual case) or representational equality (the `Coercible` case). This is a change from the previous behavior where `Coercible` was just considered a regular class with a special case in `matchClassInst`. Because of this change, representational equalities are now canonicalized just like nominal ones, allowing more equalities to be solved -- in particular, the case at the top of #9117. A knock-on effect is that the flattener must be aware of the choice of equality relation, because the inert set now stores both representational inert equalities alongside the nominal inert equalities. Of course, we can use representational equalities to rewrite only within another representational equality -- thus the parameterization of the flattener. A nice side effect of this change is that I've introduced a new type `CtFlavour`, which tracks G vs. W vs. D, removing some ugliness in the flattener. This commit includes some refactoring as discussed on D546. It also removes the ability of Deriveds to rewrite Deriveds. This fixes bugs #9117 and #8984. Reviewers: simonpj, austin, nomeata Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D546 GHC Trac Issues: #9117, #8984 >--------------------------------------------------------------- 0cc47eb90805f3e166ac4d3991e66d3346ca05e7 compiler/basicTypes/DataCon.hs | 6 +- compiler/deSugar/DsBinds.hs | 5 +- compiler/typecheck/FamInst.hs | 93 ++- compiler/typecheck/FunDeps.hs | 6 +- compiler/typecheck/Inst.hs | 15 +- compiler/typecheck/TcCanonical.hs | 691 +++++++++++++++------ compiler/typecheck/TcDeriv.hs | 1 - compiler/typecheck/TcErrors.hs | 209 ++++--- compiler/typecheck/TcEvidence.hs | 161 ++++- compiler/typecheck/TcFlatten.hs | 358 +++++++---- compiler/typecheck/TcHsSyn.hs | 32 +- compiler/typecheck/TcInteract.hs | 343 +++------- compiler/typecheck/TcMType.hs | 6 +- compiler/typecheck/TcRnTypes.hs | 68 +- compiler/typecheck/TcSMonad.hs | 163 +++-- compiler/typecheck/TcSimplify.hs | 19 +- compiler/typecheck/TcType.hs | 34 +- compiler/typecheck/TcValidity.hs | 61 +- compiler/types/Coercion.hs | 125 ++-- compiler/types/FamInstEnv.hs | 71 +-- compiler/types/Type.hs | 62 +- compiler/utils/MonadUtils.hs | 14 +- compiler/utils/Util.hs | 11 + testsuite/tests/deriving/should_fail/T1496.stderr | 14 +- testsuite/tests/deriving/should_fail/T4846.stderr | 9 +- testsuite/tests/deriving/should_fail/T5498.stderr | 16 +- testsuite/tests/deriving/should_fail/T6147.stderr | 12 +- testsuite/tests/deriving/should_fail/T7148.stderr | 32 +- testsuite/tests/deriving/should_fail/T7148a.stderr | 19 +- testsuite/tests/deriving/should_fail/T8851.stderr | 22 +- testsuite/tests/deriving/should_fail/T8984.hs | 8 + testsuite/tests/deriving/should_fail/T8984.stderr | 11 + testsuite/tests/deriving/should_fail/all.T | 1 + testsuite/tests/gadt/CasePrune.stderr | 12 +- testsuite/tests/ghci/scripts/GhciKinds.hs | 4 + testsuite/tests/ghci/scripts/GhciKinds.script | 5 + testsuite/tests/ghci/scripts/GhciKinds.stdout | 6 + testsuite/tests/ghci/scripts/ghci051.stderr | 2 +- .../tests/indexed-types/should_fail/T9580.stderr | 7 +- testsuite/tests/roles/should_fail/Roles10.stderr | 11 +- .../tests/roles/should_fail/RolesIArray.stderr | 151 +++-- .../tests/typecheck/should_compile/T9117_3.hs | 7 + testsuite/tests/typecheck/should_compile/T9708.hs | 9 +- testsuite/tests/typecheck/should_compile/all.T | 5 +- .../tests/typecheck/should_fail/TcCoercibleFail.hs | 6 +- .../typecheck/should_fail/TcCoercibleFail.stderr | 65 +- .../typecheck/should_fail/TcCoercibleFail3.stderr | 11 +- .../tests/typecheck/should_run/TcCoercible.hs | 15 +- 48 files changed, 1861 insertions(+), 1153 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0cc47eb90805f3e166ac4d3991e66d3346ca05e7 From git at git.haskell.org Fri Dec 12 22:56:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Dec 2014 22:56:17 +0000 (UTC) Subject: [commit: ghc] master: Flat constraint --> Simple constraint (8a0de69) Message-ID: <20141212225617.045BE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8a0de692bd56b255adacc869e284424becdc9902/ghc >--------------------------------------------------------------- commit 8a0de692bd56b255adacc869e284424becdc9902 Author: Richard Eisenberg Date: Wed Dec 10 16:58:09 2014 -0500 Flat constraint --> Simple constraint >--------------------------------------------------------------- 8a0de692bd56b255adacc869e284424becdc9902 compiler/typecheck/Inst.hs | 6 +-- compiler/typecheck/TcCanonical.hs | 2 +- compiler/typecheck/TcDeriv.hs | 8 +-- compiler/typecheck/TcErrors.hs | 30 +++++------ compiler/typecheck/TcInteract.hs | 50 +++++++++---------- compiler/typecheck/TcMType.hs | 28 +++++------ compiler/typecheck/TcRnMonad.hs | 12 ++--- compiler/typecheck/TcRnTypes.hs | 42 ++++++++-------- compiler/typecheck/TcSMonad.hs | 20 ++++---- compiler/typecheck/TcSimplify.hs | 102 +++++++++++++++++++------------------- compiler/typecheck/TcType.hs | 2 +- compiler/typecheck/TcUnify.hs | 2 +- 12 files changed, 152 insertions(+), 152 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8a0de692bd56b255adacc869e284424becdc9902 From git at git.haskell.org Sat Dec 13 14:54:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 13 Dec 2014 14:54:57 +0000 (UTC) Subject: [commit: ghc] wip/rae: reduceTyFamApp_maybe should *not* normalise arguments first. (3ec9391) Message-ID: <20141213145457.9C3D03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/3ec9391711f30e9610c4babcff61e126ccc590ab/ghc >--------------------------------------------------------------- commit 3ec9391711f30e9610c4babcff61e126ccc590ab Author: Richard Eisenberg Date: Sat Dec 13 09:54:53 2014 -0500 reduceTyFamApp_maybe should *not* normalise arguments first. Doing so made the solver gobble up tons of memory, now that matchFam calls reduceTyFamApp_maybe. But, I don't know why, yet! Will look more closely at this soon. >--------------------------------------------------------------- 3ec9391711f30e9610c4babcff61e126ccc590ab compiler/types/FamInstEnv.hs | 45 +++++++++++++++++++++----------------------- 1 file changed, 21 insertions(+), 24 deletions(-) diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs index 0b5bf2b..7fd2ef6 100644 --- a/compiler/types/FamInstEnv.hs +++ b/compiler/types/FamInstEnv.hs @@ -25,7 +25,7 @@ module FamInstEnv ( -- Normalisation topNormaliseType, topNormaliseType_maybe, normaliseType, normaliseTcApp, - reduceTyFamApp_maybe, + reduceTyFamApp_maybe, chooseBranch, -- Flattening flattenTys @@ -788,10 +788,9 @@ reduceTyFamApp_maybe :: FamInstEnvs -- 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 +-- It does *not* normlise the type arguments first, so this may not +-- go as far as you want. If you want normalised type arguments, +-- use normaliseTcArgs first. -- -- The TyCon can be oversaturated. -- Works on both open and closed families @@ -808,32 +807,28 @@ reduceTyFamApp_maybe envs role tc tys -- 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 + , fim_tys = inst_tys } : _ <- lookupFamInstEnv envs tc tys -- NB: Allow multiple matches because of compatible overlap = let ax = famInstAxiom fam_inst co = mkUnbranchedAxInstCo role ax inst_tys ty = pSnd (coercionKind co) - in Just (args_co `mkTransCo` co, ty) + in Just (co, ty) | Just ax <- isClosedSynFamilyTyCon_maybe tc - , Just (ind, inst_tys) <- chooseBranch ax ntys + , Just (ind, inst_tys) <- chooseBranch ax tys = let co = mkAxInstCo role ax ind inst_tys ty = pSnd (coercionKind co) - in Just (args_co `mkTransCo` co, ty) + in Just (co, ty) | Just ax <- isBuiltInSynFamTyCon_maybe tc - , Just (coax,ts,ty) <- sfMatchFam ax ntys + , Just (coax,ts,ty) <- sfMatchFam ax tys = let co = mkAxiomRuleCo coax ts [] - in Just (args_co `mkTransCo` co, ty) + in Just (co, ty) | otherwise = Nothing - where - (args_co, ntys) = normaliseTcArgs envs role tc tys - - -- The axiom can be oversaturated. (Closed families only.) chooseBranch :: CoAxiom Branched -> [Type] -> Maybe (BranchIndex, [Type]) chooseBranch axiom tys @@ -908,8 +903,9 @@ topNormaliseType_maybe env ty = unwrapNewTypeStepper `composeSteppers` \ rec_nts tc tys -> - case reduceTyFamApp_maybe env Representational tc tys of - Just (co, rhs) -> NS_Step rec_nts rhs co + let (args_co, ntys) = normaliseTcArgs env Representational tc tys in + case reduceTyFamApp_maybe env Representational tc ntys of + Just (co, rhs) -> NS_Step rec_nts rhs (args_co `mkTransCo` co) Nothing -> NS_Done --------------- @@ -917,20 +913,21 @@ 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') + = if isReflCo co2 then (args_co, mkTyConApp tc ntys) + else (args_co `mkTransCo` co2, mkAppTys ninst_rhs ntys') - | Just (first_co, ty') <- reduceTyFamApp_maybe env role tc tys + | Just (first_co, ty') <- reduceTyFamApp_maybe env role tc ntys , (rest_co,nty) <- normaliseType env role ty' - = (first_co `mkTransCo` rest_co, nty) + = (args_co `mkTransCo` first_co `mkTransCo` rest_co, nty) | otherwise -- No unique matching family instance exists; -- we do not do anything - = let (co, ntys) = normaliseTcArgs env role tc tys in - (co, mkTyConApp tc ntys) + = (args_co, mkTyConApp tc ntys) + + where + (args_co, ntys) = normaliseTcArgs env role tc tys --------------- From git at git.haskell.org Sat Dec 13 14:54:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 13 Dec 2014 14:54:59 +0000 (UTC) Subject: [commit: ghc] wip/rae's head updated: reduceTyFamApp_maybe should *not* normalise arguments first. (3ec9391) Message-ID: <20141213145459.EED843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/rae' now includes: e5974f8 Proposal for Backpack file format [skip ci] fc45f32 Implement -XStaticValues 09b7943 fix misleading error message regarding function arity 8b480d3 Document splitAt deviation from the Report df1307f Link pre-ARMv6 spinlocks into all RTS variants 659ec2c Add proper expected output for T5435_dyn_asm on Darwin 4d1c452 Only run subsections_via_symbols test when LLVM is available. 7ca5bb0 compiler: fix trac issue #9817 b006a1a Add Ord instances to TH 13b0b46 Reorganise the work list, so that flattening goals are treated in the right order 1496598 Get rid of TcMType.newWantedEvVar(s) 3e234f7 Fix type-variable details naming (fixes misleading debug output) bcb967a When flattening, try reducing type-family applications eagerly 832f8db Implement a fast path for new constraints looking like (a~b), namely unifyWanted 37b3646 Testsuite wibbles from constraint-solver improvements fca85c9 Tests for Trac #9872 a225c70 Comments only: move flattening notes to TcFlatten d45edfb White space wibble only 7256213 Add a third test variant to Trac #9872 8c82563 Test Trac #9090 b8392ae Fix an obscure but terrible bug in the simplifier (Trac #9567) 058262b 32-bit performance changes following constraint solver improvements 0cc47eb Rewrite `Coercible` solver 8a0de69 Flat constraint --> Simple constraint 3ec9391 reduceTyFamApp_maybe should *not* normalise arguments first. From git at git.haskell.org Sat Dec 13 15:54:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 13 Dec 2014 15:54:08 +0000 (UTC) Subject: [commit: ghc] master's head updated: reduceTyFamApp_maybe should *not* normalise arguments first. (3ec9391) Message-ID: <20141213155408.3AE5C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: 3ec9391 reduceTyFamApp_maybe should *not* normalise arguments first. From git at git.haskell.org Sat Dec 13 21:05:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 13 Dec 2014 21:05:05 +0000 (UTC) Subject: [commit: ghc] master: Parser: remove unused rule (copy/paste error) (288c7c6) Message-ID: <20141213210505.42E513A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/288c7c6ad40dbb81bf559c826fbc480f7882f250/ghc >--------------------------------------------------------------- commit 288c7c6ad40dbb81bf559c826fbc480f7882f250 Author: Sergei Trofimovich Date: Sat Dec 13 21:05:42 2014 +0000 Parser: remove unused rule (copy/paste error) Summary: Found out when tracking down conflicts reported by happy. It was accidentally introduced in large Api Annotations patch: 803fc5db31f084b73713342cdceaed5a9c664267 Before: unused rules: 1 shift/reduce conflicts: 60 reduce/reduce conflicts: 16 After: shift/reduce conflicts: 60 reduce/reduce conflicts: 12 Unused rule is seen in happy's --info= output as: rule 180 is unused ... decl_cls -> 'default' infixexp '::' sigtypedoc (180) decl_cls -> 'default' infixexp '::' sigtypedoc (181) While at it removed 'q' typo in parser conflict log :) Signed-off-by: Sergei Trofimovich Reviewers: simonmar, austin, alanz Reviewed By: alanz Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D569 >--------------------------------------------------------------- 288c7c6ad40dbb81bf559c826fbc480f7882f250 compiler/parser/Parser.y | 8 +------- 1 file changed, 1 insertion(+), 7 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index ed111c0..1849fb4 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -121,7 +121,7 @@ would think the two should never occur in the same context. Conflicts: 34 shift/reduce 1 reduce/reduce -q + The reduce/reduce conflict is weird. It's between tyconsym and consym, and I would think the two should never occur in the same context. @@ -1067,12 +1067,6 @@ decl_cls : at_decl_cls { sLL $1 $> (unitOL $1) } ; ams (sLL $1 $> $ unitOL (sLL $1 $> $ SigD (GenericSig l ty))) [mj AnnDefault $1,mj AnnDcolon $3] } } - -- A 'default' signature used with the generic-programming extension - | 'default' infixexp '::' sigtypedoc - {% do { (TypeSig l ty _) <- checkValSig $2 $4 - ; ams (sLL $1 $> $ unitOL (sLL $1 $> $ SigD (GenericSig l ty))) - [mj AnnDefault $1,mj AnnDcolon $3] } } - decls_cls :: { Located (OrdList (LHsDecl RdrName)) } -- Reversed : decls_cls ';' decl_cls {% addAnnotation (oll (unLoc $1)) AnnSemi (gl $2) >> return (sLL $1 $> ((unLoc $1) `appOL` From git at git.haskell.org Sun Dec 14 08:03:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 08:03:34 +0000 (UTC) Subject: [commit: ghc] master: Only use -fasm on platforms with an NCG (Closes: #9884). (1886fca) Message-ID: <20141214080334.AE9EC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1886fca9a92fd820f201a57c7afbc157e95f582c/ghc >--------------------------------------------------------------- commit 1886fca9a92fd820f201a57c7afbc157e95f582c Author: Erik de Castro Lopo Date: Sun Dec 14 08:04:28 2014 +0000 Only use -fasm on platforms with an NCG (Closes: #9884). Summary: Signed-off-by: Erik de Castro Lopo Reviewers: austin, carter Reviewed By: carter Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D570 GHC Trac Issues: #9884 >--------------------------------------------------------------- 1886fca9a92fd820f201a57c7afbc157e95f582c mk/build.mk.sample | 51 +++++++++++++++++++++++++++------------------------ 1 file changed, 27 insertions(+), 24 deletions(-) diff --git a/mk/build.mk.sample b/mk/build.mk.sample index 9d80fa9..c87d6f4 100644 --- a/mk/build.mk.sample +++ b/mk/build.mk.sample @@ -71,6 +71,9 @@ V = 1 GhcLibWays = $(if $(filter $(DYNAMIC_GHC_PROGRAMS),YES),v dyn,v) +# Only use -fasm by default on platforms that support it. +GhcFAsm = $(if $(filter $(GhcWithNativeCodeGen),YES),-fasm,) + # ----------- A Performance/Distribution build -------------------------------- ifeq "$(BuildFlavour)" "perf" @@ -78,8 +81,8 @@ ifeq "$(BuildFlavour)" "perf" # perf matches the default settings, repeated here for comparison: SRC_HC_OPTS = -O -H64m -GhcStage1HcOpts = -O -fasm -GhcStage2HcOpts = -O2 -fasm +GhcStage1HcOpts = -O $(GhcFAsm) +GhcStage2HcOpts = -O2 $(GhcFAsm) GhcHcOpts = -Rghc-timing GhcLibHcOpts = -O2 GhcLibWays += p @@ -130,10 +133,10 @@ endif ifeq "$(BuildFlavour)" "quickest" -SRC_HC_OPTS = -H64m -O0 -fasm -GhcStage1HcOpts = -O -fasm -GhcStage2HcOpts = -O0 -fasm -GhcLibHcOpts = -O0 -fasm +SRC_HC_OPTS = -H64m -O0 $(GhcFAsm) +GhcStage1HcOpts = -O $(GhcFAsm) +GhcStage2HcOpts = -O0 $(GhcFAsm) +GhcLibHcOpts = -O0 $(GhcFAsm) SplitObjs = NO HADDOCK_DOCS = NO BUILD_DOCBOOK_HTML = NO @@ -146,10 +149,10 @@ endif ifeq "$(BuildFlavour)" "quick" -SRC_HC_OPTS = -H64m -O0 -fasm -GhcStage1HcOpts = -O -fasm -GhcStage2HcOpts = -O0 -fasm -GhcLibHcOpts = -O -fasm +SRC_HC_OPTS = -H64m -O0 $(GhcFAsm) +GhcStage1HcOpts = -O $(GhcFAsm) +GhcStage2HcOpts = -O0 $(GhcFAsm) +GhcLibHcOpts = -O $(GhcFAsm) SplitObjs = NO HADDOCK_DOCS = NO BUILD_DOCBOOK_HTML = NO @@ -199,10 +202,10 @@ endif ifeq "$(BuildFlavour)" "prof" -SRC_HC_OPTS = -H64m -O0 -fasm -GhcStage1HcOpts = -O -fasm -GhcStage2HcOpts = -O -fasm -GhcLibHcOpts = -O -fasm +SRC_HC_OPTS = -H64m -O0 $(GhcFAsm) +GhcStage1HcOpts = -O $(GhcFAsm) +GhcStage2HcOpts = -O $(GhcFAsm) +GhcLibHcOpts = -O $(GhcFAsm) GhcLibWays += p GhcProfiled = YES @@ -219,10 +222,10 @@ endif ifeq "$(BuildFlavour)" "devel1" -SRC_HC_OPTS = -H64m -O -fasm +SRC_HC_OPTS = -H64m -O $(GhcFAsm) GhcLibHcOpts = -O -dcore-lint GhcStage1HcOpts = -Rghc-timing -O0 -DDEBUG -GhcStage2HcOpts = -Rghc-timing -O -fasm +GhcStage2HcOpts = -Rghc-timing -O $(GhcFAsm) SplitObjs = NO HADDOCK_DOCS = NO BUILD_DOCBOOK_HTML = NO @@ -236,9 +239,9 @@ endif ifeq "$(BuildFlavour)" "devel2" -SRC_HC_OPTS = -H64m -O -fasm +SRC_HC_OPTS = -H64m -O $(GhcFAsm) GhcLibHcOpts = -O -dcore-lint -GhcStage1HcOpts = -Rghc-timing -O -fasm +GhcStage1HcOpts = -Rghc-timing -O $(GhcFAsm) GhcStage2HcOpts = -Rghc-timing -O0 -DDEBUG SplitObjs = NO HADDOCK_DOCS = NO @@ -254,9 +257,9 @@ endif ifeq "$(BuildFlavour)" "bench" SRC_HC_OPTS = -O -H64m -GhcStage1HcOpts = -O -fasm -GhcStage2HcOpts = -O0 -fasm -GhcLibHcOpts = -O2 -fasm +GhcStage1HcOpts = -O $(GhcFAsm) +GhcStage2HcOpts = -O0 $(GhcFAsm) +GhcLibHcOpts = -O2 $(GhcFAsm) SplitObjs = NO HADDOCK_DOCS = NO BUILD_DOCBOOK_HTML = NO @@ -286,9 +289,9 @@ endif ifeq "$(BuildFlavour)" "bench-cross" SRC_HC_OPTS = -O -H64m -GhcStage1HcOpts = -O -fasm -GhcStage2HcOpts = -O0 -fasm -GhcLibHcOpts = -O2 -fasm +GhcStage1HcOpts = -O $(GhcFAsm) +GhcStage2HcOpts = -O0 $(GhcFAsm) +GhcLibHcOpts = -O2 $(GhcFAsm) SplitObjs = NO INTEGER_LIBRARY = integer-simple Stage1Only = YES From git at git.haskell.org Sun Dec 14 09:40:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 09:40:19 +0000 (UTC) Subject: [commit: ghc] master: Update Haddock submodule to latest `master` tip (7f63432) Message-ID: <20141214094019.8A8D93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7f634320a2c39f4f81f631deb844acbaebaced66/ghc >--------------------------------------------------------------- commit 7f634320a2c39f4f81f631deb844acbaebaced66 Author: Herbert Valerio Riedel Date: Sun Dec 14 10:33:43 2014 +0100 Update Haddock submodule to latest `master` tip This also updates the perf-numbers for `haddock.base` and `haddock.Cabal` NB: this switches from `ghc-head` to `master` branch temporarily until GHC 7.10 has been properly branched off. >--------------------------------------------------------------- 7f634320a2c39f4f81f631deb844acbaebaced66 testsuite/tests/perf/haddock/all.T | 6 ++++-- utils/haddock | 2 +- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index 027686e..d7162f5 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), 8322584616, 5) + [(wordsize(64), 9503888920, 5) # 2012-08-14: 5920822352 (amd64/Linux) # 2012-09-20: 5829972376 (amd64/Linux) # 2012-10-08: 5902601224 (amd64/Linux) @@ -21,6 +21,7 @@ test('haddock.base', # 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) + # 2014-12-14: 9503888920 (x86_64/Linux) - Update to Haddock 2.16 ,(platform('i386-unknown-mingw32'), 4202377432, 5) # 2013-02-10: 3358693084 (x86/Windows) # 2013-11-13: 3097751052 (x86/Windows, 64bit machine) @@ -41,7 +42,7 @@ test('haddock.base', test('haddock.Cabal', [unless(in_tree_compiler(), skip) ,stats_num_field('bytes allocated', - [(wordsize(64), 6019839624, 5) + [(wordsize(64), 6387320816, 5) # 2012-08-14: 3255435248 (amd64/Linux) # 2012-08-29: 3324606664 (amd64/Linux, new codegen) # 2012-10-08: 3373401360 (amd64/Linux) @@ -59,6 +60,7 @@ test('haddock.Cabal', # 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) + # 2014-12-14: 6387320816 (x86_64/Linux) - Update to Haddock 2.16 ,(platform('i386-unknown-mingw32'), 3088635556, 5) # 2012-10-30: 1733638168 (x86/Windows) diff --git a/utils/haddock b/utils/haddock index b94ab90..8cd72a0 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit b94ab9034367f51b978904d60f2604db10abbd9f +Subproject commit 8cd72a05e857388e3ca184fbef3f04d3bffbc5b4 From git at git.haskell.org Sun Dec 14 12:44:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 12:44:21 +0000 (UTC) Subject: [commit: ghc] master: Revert "Update Haddock submodule to latest `master` tip" (ef7eb8f) Message-ID: <20141214124421.568993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ef7eb8f30532c8f85f05b318c85c7d819f61d715/ghc >--------------------------------------------------------------- commit ef7eb8f30532c8f85f05b318c85c7d819f61d715 Author: Herbert Valerio Riedel Date: Sun Dec 14 13:43:23 2014 +0100 Revert "Update Haddock submodule to latest `master` tip" This reverts commit 7f634320a2c39f4f81f631deb844acbaebaced66 again for now as it causes validate's bindist phase to fail with haddock: internal error: .../install dir/lib/ghc-7.9.20141214/html: getDirectoryContents: does not exist (No such file or directory) >--------------------------------------------------------------- ef7eb8f30532c8f85f05b318c85c7d819f61d715 testsuite/tests/perf/haddock/all.T | 6 ++---- utils/haddock | 2 +- 2 files changed, 3 insertions(+), 5 deletions(-) diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index d7162f5..027686e 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), 9503888920, 5) + [(wordsize(64), 8322584616, 5) # 2012-08-14: 5920822352 (amd64/Linux) # 2012-09-20: 5829972376 (amd64/Linux) # 2012-10-08: 5902601224 (amd64/Linux) @@ -21,7 +21,6 @@ test('haddock.base', # 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) - # 2014-12-14: 9503888920 (x86_64/Linux) - Update to Haddock 2.16 ,(platform('i386-unknown-mingw32'), 4202377432, 5) # 2013-02-10: 3358693084 (x86/Windows) # 2013-11-13: 3097751052 (x86/Windows, 64bit machine) @@ -42,7 +41,7 @@ test('haddock.base', test('haddock.Cabal', [unless(in_tree_compiler(), skip) ,stats_num_field('bytes allocated', - [(wordsize(64), 6387320816, 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) @@ -60,7 +59,6 @@ test('haddock.Cabal', # 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) - # 2014-12-14: 6387320816 (x86_64/Linux) - Update to Haddock 2.16 ,(platform('i386-unknown-mingw32'), 3088635556, 5) # 2012-10-30: 1733638168 (x86/Windows) diff --git a/utils/haddock b/utils/haddock index 8cd72a0..b94ab90 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 8cd72a05e857388e3ca184fbef3f04d3bffbc5b4 +Subproject commit b94ab9034367f51b978904d60f2604db10abbd9f From git at git.haskell.org Sun Dec 14 14:30:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 14:30:27 +0000 (UTC) Subject: [commit: ghc] master: powerpc: fix and enable shared libraries by default on linux (fa31e8f) Message-ID: <20141214143027.03A233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fa31e8f4a0f853848d96549a429083941877bf8d/ghc >--------------------------------------------------------------- commit fa31e8f4a0f853848d96549a429083941877bf8d Author: Sergei Trofimovich Date: Sun Dec 14 14:30:12 2014 +0000 powerpc: fix and enable shared libraries by default on linux Summary: And fix things all the way down to it. Namely: - remove 'r30' from free registers, it's an .LCTOC1 register for gcc. generated .plt stubs expect it to be initialised. - fix PicBase computation, which originally forgot to use 'tmp' reg in 'initializePicBase_ppc.fetchPC' - mark 'ForeighTarget's as implicitly using 'PicBase' register (see comment for details) - add 64-bit MO_Sub and test on alloclimit3/4 regtests - fix dynamic label offsets to match with .LCTOC1 offset Signed-off-by: Sergei Trofimovich Test Plan: validate passes equal amount of vanilla/dyn tests Reviewers: simonmar, erikd, austin Reviewed By: erikd, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D560 GHC Trac Issues: #8024, #9831 >--------------------------------------------------------------- fa31e8f4a0f853848d96549a429083941877bf8d compiler/cmm/CLabel.hs | 3 ++- compiler/nativeGen/PIC.hs | 45 +++++++++++++++--------------------- compiler/nativeGen/PPC/CodeGen.hs | 48 ++++++++++++++++++++++++++++++++++++--- compiler/nativeGen/PPC/Instr.hs | 9 ++++++++ compiler/nativeGen/PPC/Ppr.hs | 12 ++++++++++ compiler/nativeGen/PPC/Regs.hs | 6 +++-- includes/CodeGen.Platform.hs | 2 ++ mk/config.mk.in | 2 +- 8 files changed, 93 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 fa31e8f4a0f853848d96549a429083941877bf8d From git at git.haskell.org Sun Dec 14 17:31:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:31:32 +0000 (UTC) Subject: [commit: ghc] master: Re-Update Haddock submodule to latest `master` tip (0c9c2d8) Message-ID: <20141214173132.388E93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0c9c2d899e63b810e7ab6b486f7244826b4a2e33/ghc >--------------------------------------------------------------- commit 0c9c2d899e63b810e7ab6b486f7244826b4a2e33 Author: Herbert Valerio Riedel Date: Sun Dec 14 10:33:43 2014 +0100 Re-Update Haddock submodule to latest `master` tip The previous attempt failed, but hopefully this one succeeds... This also updates the perf-numbers for `haddock.base` and `haddock.Cabal` NB: this switches from `ghc-head` to `master` branch temporarily until GHC 7.10 has been properly branched off. >--------------------------------------------------------------- 0c9c2d899e63b810e7ab6b486f7244826b4a2e33 testsuite/tests/perf/haddock/all.T | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index 027686e..d7162f5 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), 8322584616, 5) + [(wordsize(64), 9503888920, 5) # 2012-08-14: 5920822352 (amd64/Linux) # 2012-09-20: 5829972376 (amd64/Linux) # 2012-10-08: 5902601224 (amd64/Linux) @@ -21,6 +21,7 @@ test('haddock.base', # 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) + # 2014-12-14: 9503888920 (x86_64/Linux) - Update to Haddock 2.16 ,(platform('i386-unknown-mingw32'), 4202377432, 5) # 2013-02-10: 3358693084 (x86/Windows) # 2013-11-13: 3097751052 (x86/Windows, 64bit machine) @@ -41,7 +42,7 @@ test('haddock.base', test('haddock.Cabal', [unless(in_tree_compiler(), skip) ,stats_num_field('bytes allocated', - [(wordsize(64), 6019839624, 5) + [(wordsize(64), 6387320816, 5) # 2012-08-14: 3255435248 (amd64/Linux) # 2012-08-29: 3324606664 (amd64/Linux, new codegen) # 2012-10-08: 3373401360 (amd64/Linux) @@ -59,6 +60,7 @@ test('haddock.Cabal', # 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) + # 2014-12-14: 6387320816 (x86_64/Linux) - Update to Haddock 2.16 ,(platform('i386-unknown-mingw32'), 3088635556, 5) # 2012-10-30: 1733638168 (x86/Windows) From git at git.haskell.org Sun Dec 14 17:53:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:53:58 +0000 (UTC) Subject: [commit: packages/binary] master: Implement `isolate` for reading fixed-size blocks. (4ecce94) Message-ID: <20141214175358.9C8DF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/4ecce94041b3f8e5b7e9e2f1e7d0b57280659916 >--------------------------------------------------------------- commit 4ecce94041b3f8e5b7e9e2f1e7d0b57280659916 Author: Stephen Paul Weber Date: Tue Sep 10 18:14:05 2013 -0500 Implement `isolate` for reading fixed-size blocks. Closes #32 >--------------------------------------------------------------- 4ecce94041b3f8e5b7e9e2f1e7d0b57280659916 src/Data/Binary/Get.hs | 1 + src/Data/Binary/Get/Internal.hs | 22 ++++++++++++++++++++++ 2 files changed, 23 insertions(+) diff --git a/src/Data/Binary/Get.hs b/src/Data/Binary/Get.hs index 656b712..1487447 100644 --- a/src/Data/Binary/Get.hs +++ b/src/Data/Binary/Get.hs @@ -144,6 +144,7 @@ module Data.Binary.Get ( , skip , isEmpty , bytesRead + , isolate , lookAhead , lookAheadM , lookAheadE diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs index 7dac47d..91f8ed7 100644 --- a/src/Data/Binary/Get/Internal.hs +++ b/src/Data/Binary/Get/Internal.hs @@ -18,6 +18,7 @@ module Data.Binary.Get.Internal ( -- * Parsing , skip , bytesRead + , isolate , get , put @@ -179,6 +180,27 @@ prompt inp kf ks = bytesRead :: Get Int64 bytesRead = C $ \inp k -> BytesRead (fromIntegral $ B.length inp) (k inp) +-- | Isolate an action to operating within a fixed block of bytes. +isolate :: Int -- ^ The action much consume this many bytes + -> Bool -- ^ Optionally discard bytes that are left unconsumed + -> Get a -- ^ The action to isolate + -> Get a +isolate n discard (C go) + | n < 0 = fail "isolate: negative n" + | otherwise = do + ensureN n + C (\inp k -> isolate' n discard inp k (go (B.unsafeTake n inp) Done)) + +isolate' :: Int -> Bool -> B.ByteString -> Success a r -> Decoder a -> Decoder r +isolate' n discard inp k = go + where + go (Done left x) + | B.null left || discard = k (B.unsafeDrop n inp) x + | otherwise = Fail inp "isolate: action read less than block size" + go (Partial resume) = go (resume Nothing) + go (Fail bs err) = Fail bs err + go (BytesRead r resume) = go (resume (fromIntegral n - r)) + -- | Demand more input. If none available, fail. demandInput :: Get () demandInput = C $ \inp ks -> From git at git.haskell.org Sun Dec 14 17:54:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:00 +0000 (UTC) Subject: [commit: packages/binary] master: Test that look-ahead is independent of chunking (0b454d1) Message-ID: <20141214175400.A32563A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/0b454d1b3906a1590332511d7e821f295078e4c6 >--------------------------------------------------------------- commit 0b454d1b3906a1590332511d7e821f295078e4c6 Author: Edsko de Vries Date: Tue Sep 17 14:21:52 2013 +0100 Test that look-ahead is independent of chunking >--------------------------------------------------------------- 0b454d1b3906a1590332511d7e821f295078e4c6 tests/QC.hs | 90 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 90 insertions(+) diff --git a/tests/QC.hs b/tests/QC.hs index c3d4d58..d9b2cd8 100644 --- a/tests/QC.hs +++ b/tests/QC.hs @@ -199,6 +199,93 @@ prop_readTooMuch x = mustThrowError $ x == a && x /= b (a,b) = decode (encode x) _types = [a,b] +-- In binary-0.5 the Get monad looked like +-- +-- > data S = S {-# UNPACK #-} !B.ByteString +-- > L.ByteString +-- > {-# UNPACK #-} !Int64 +-- > +-- > newtype Get a = Get { unGet :: S -> (# a, S #) } +-- +-- with a helper function +-- +-- > mkState :: L.ByteString -> Int64 -> S +-- > mkState l = case l of +-- > L.Empty -> S B.empty L.empty +-- > L.Chunk x xs -> S x xs +-- +-- Note that mkState is strict in its first argument. This goes wrong in this +-- function: +-- +-- > getBytes :: Int -> Get B.ByteString +-- > getBytes n = do +-- > S s ss bytes <- traceNumBytes n $ get +-- > if n <= B.length s +-- > then do let (consume,rest) = B.splitAt n s +-- > put $! S rest ss (bytes + fromIntegral n) +-- > return $! consume +-- > else +-- > case L.splitAt (fromIntegral n) (s `join` ss) of +-- > (consuming, rest) -> +-- > do let now = B.concat . L.toChunks $ consuming +-- > put $ mkState rest (bytes + fromIntegral n) +-- > -- forces the next chunk before this one is returned +-- > if (B.length now < n) +-- > then +-- > fail "too few bytes" +-- > else +-- > return now +-- +-- Consider the else-branch of this function; suppose we ask for n bytes; +-- the call to L.splitAt gives us a lazy bytestring 'consuming' of precisely @n@ +-- bytes (unless we don't have enough data, in which case we fail); but then +-- the strict evaluation of mkState on 'rest' means we look ahead too far. +-- +-- Although this is all done completely differently in binary-0.7 it is +-- important that the same bug does not get introduced in some other way. The +-- test is basically the same test that already exists in this test suite, +-- verifying that +-- +-- > decode . refragment . encode == id +-- +-- However, we use a different 'refragment', one that introduces an exception +-- as the tail of the bytestring after rechunking. If we don't look ahead too +-- far then this should make no difference, but if we do then this will throw +-- an exception (for instance, in binary-0.5, this will throw an exception for +-- certain rechunkings, but not for others). +-- +-- To make sure that the property holds no matter what refragmentation we use, +-- we test exhaustively for a single chunk, and all ways to break the string +-- into 2, 3 and 4 chunks. +prop_lookAheadIndepOfChunking :: (Eq a, Binary a) => a -> Property +prop_lookAheadIndepOfChunking testInput = + forAll (testCuts (L.length (encode testInput))) $ + roundTrip testInput . rechunk + where + testCuts :: forall a. (Num a, Enum a) => a -> Gen [a] + testCuts len = elements $ [ [] ] + ++ [ [i] + | i <- [0 .. len] ] + ++ [ [i, j] + | i <- [0 .. len] + , j <- [0 .. len - i] ] + ++ [ [i, j, k] + | i <- [0 .. len] + , j <- [0 .. len - i] + , k <- [0 .. len - i - j] ] + + -- Rechunk a bytestring, leaving the tail as an exception rather than Empty + rechunk :: forall a. Integral a => [a] -> L.ByteString -> L.ByteString + rechunk cuts = fromChunks . cut cuts . B.concat . L.toChunks + where + cut :: [a] -> B.ByteString -> [B.ByteString] + cut [] bs = [bs] + cut (i:is) bs = let (bs0, bs1) = B.splitAt (fromIntegral i) bs + in bs0 : cut is bs1 + + fromChunks :: [B.ByteString] -> L.ByteString + fromChunks [] = error "Binary should not have to ask for this chunk!" + fromChunks (bs:bss) = L.Chunk bs (fromChunks bss) -- String utilities @@ -304,6 +391,9 @@ tests = , testGroup "Boundaries" [ testProperty "read to much" (p (prop_readTooMuch :: B Word8)) , testProperty "read negative length" (p (prop_getByteString_negative :: T Int)) + , -- Arbitrary test input + let testInput :: [Int] ; testInput = [0 .. 10] + in testProperty "look-ahead independent of chunking" (p (prop_lookAheadIndepOfChunking testInput)) ] , testGroup "Partial" From git at git.haskell.org Sun Dec 14 17:54:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:02 +0000 (UTC) Subject: [commit: packages/binary] master: Merge pull request #38 from edsko/look-ahead-indep-of-chunking (dc1b7fc) Message-ID: <20141214175402.A9EBD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/dc1b7fc32745a6539b08590cb6b5828ca836a2bb >--------------------------------------------------------------- commit dc1b7fc32745a6539b08590cb6b5828ca836a2bb Merge: 2799c25 0b454d1 Author: Lennart Kolmodin Date: Tue Sep 17 11:59:58 2013 -0700 Merge pull request #38 from edsko/look-ahead-indep-of-chunking Test that look-ahead is independent of chunking >--------------------------------------------------------------- dc1b7fc32745a6539b08590cb6b5828ca836a2bb tests/QC.hs | 90 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 90 insertions(+) From git at git.haskell.org Sun Dec 14 17:54:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:04 +0000 (UTC) Subject: [commit: packages/binary] master: Typo. (44f3b24) Message-ID: <20141214175404.B03C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/44f3b24075c01b9d1a86469fd143e6032fe628d8 >--------------------------------------------------------------- commit 44f3b24075c01b9d1a86469fd143e6032fe628d8 Author: Mikhail Glushenkov Date: Tue Nov 12 02:13:19 2013 +0100 Typo. >--------------------------------------------------------------- 44f3b24075c01b9d1a86469fd143e6032fe628d8 src/Data/Binary/Get.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Data/Binary/Get.hs b/src/Data/Binary/Get.hs index 656b712..261e6ab 100644 --- a/src/Data/Binary/Get.hs +++ b/src/Data/Binary/Get.hs @@ -255,7 +255,7 @@ calculateOffset r0 = go r0 0 go (k $! (acc - unused)) acc -- | DEPRECATED. Provides compatibility with previous versions of this library. --- Run a 'Get' monad and return a tuple with thee values. +-- Run a 'Get' monad and return a tuple with three values. -- The first value is the result of the decoder. The second and third are the -- unused input, and the number of consumed bytes. {-# DEPRECATED runGetState "Use runGetIncremental instead. This function will be removed." #-} From git at git.haskell.org Sun Dec 14 17:54:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:06 +0000 (UTC) Subject: [commit: packages/binary] master: Whitespace. (cf64b8a) Message-ID: <20141214175406.B6F2B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/cf64b8ac5a3eb404600e7f32392df4ea4be8f86f >--------------------------------------------------------------- commit cf64b8ac5a3eb404600e7f32392df4ea4be8f86f Author: Mikhail Glushenkov Date: Tue Nov 12 02:47:16 2013 +0100 Whitespace. >--------------------------------------------------------------- cf64b8ac5a3eb404600e7f32392df4ea4be8f86f src/Data/Binary/Get.hs | 0 1 file changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Sun Dec 14 17:54:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:08 +0000 (UTC) Subject: [commit: packages/binary] master: Update the example that uses 'runGetState' to new API. (fc61b89) Message-ID: <20141214175408.BCA973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/fc61b8913a73fa66491a486755778a1de006594d >--------------------------------------------------------------- commit fc61b8913a73fa66491a486755778a1de006594d Author: Mikhail Glushenkov Date: Tue Nov 12 02:51:13 2013 +0100 Update the example that uses 'runGetState' to new API. Fixes #30. >--------------------------------------------------------------- fc61b8913a73fa66491a486755778a1de006594d src/Data/Binary/Get.hs | 28 +++++++++++++++++++++++----- 1 file changed, 23 insertions(+), 5 deletions(-) diff --git a/src/Data/Binary/Get.hs b/src/Data/Binary/Get.hs index 028d07a..bef3b28 100644 --- a/src/Data/Binary/Get.hs +++ b/src/Data/Binary/Get.hs @@ -103,11 +103,29 @@ -- -- @ -- example2 :: BL.ByteString -> [Trade] --- example2 input --- | BL.null input = [] --- | otherwise = --- let (trade, rest, _) = 'runGetState' getTrade input 0 --- in trade : example2 rest +-- example2 input = go (runGetIncremental getTrade) input +-- where +-- decoder = runGetIncremental getTrade +-- +-- go :: Decoder Trade -> BL.ByteString -> [Trade] +-- go (Done leftover _consumed trade) input' = +-- trade : go decoder (BL.chunk leftover input') +-- go (Partial k) input' = +-- go (k . takeHeadChunk $ input') (dropHeadChunk input') +-- go (Fail _leftover _consumed msg) _input' = +-- error msg +-- +-- takeHeadChunk :: BL.ByteString -> Maybe BS.ByteString +-- takeHeadChunk lbs = +-- case lbs of +-- (BL.Chunk bs _) -> Just bs +-- _ -> Nothing +-- +-- dropHeadChunk :: BL.ByteString -> BL.ByteString +-- dropHeadChunk lbs = +-- case lbs of +-- (BL.Chunk _ lbs') -> lbs' +-- _ -> BL.Empty -- @ -- -- Both these examples use lazy I/O to read the file from the disk, which is From git at git.haskell.org Sun Dec 14 17:54:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:10 +0000 (UTC) Subject: [commit: packages/binary] master: Typo. (73d00b3) Message-ID: <20141214175410.C209D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/73d00b3c92e38d9f6954ceb9d2e59a245118802f >--------------------------------------------------------------- commit 73d00b3c92e38d9f6954ceb9d2e59a245118802f Author: Mikhail Glushenkov Date: Tue Nov 12 03:11:14 2013 +0100 Typo. >--------------------------------------------------------------- 73d00b3c92e38d9f6954ceb9d2e59a245118802f src/Data/Binary/Get.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Data/Binary/Get.hs b/src/Data/Binary/Get.hs index bef3b28..63398f9 100644 --- a/src/Data/Binary/Get.hs +++ b/src/Data/Binary/Get.hs @@ -98,7 +98,7 @@ -- it knows it could decode without any decoder errors. -- -- You could also refactor to a left-fold, to decode in a more streaming fashion, --- and get the following decoder. It will start to return data without knowning +-- and get the following decoder. It will start to return data without knowing -- that it can decode all input. -- -- @ From git at git.haskell.org Sun Dec 14 17:54:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:12 +0000 (UTC) Subject: [commit: packages/binary] master: Add haddock annotation, clarify some documentation. (b45b125) Message-ID: <20141214175412.C930C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/b45b125bda4dcb5ce947268f675c4d3ae9d1bd0f >--------------------------------------------------------------- commit b45b125bda4dcb5ce947268f675c4d3ae9d1bd0f Author: Lennart Kolmodin Date: Tue Nov 12 23:05:27 2013 +0400 Add haddock annotation, clarify some documentation. >--------------------------------------------------------------- b45b125bda4dcb5ce947268f675c4d3ae9d1bd0f src/Data/Binary/Get.hs | 36 +++++++++++++++++------------------- 1 file changed, 17 insertions(+), 19 deletions(-) diff --git a/src/Data/Binary/Get.hs b/src/Data/Binary/Get.hs index 63398f9..e5d7219 100644 --- a/src/Data/Binary/Get.hs +++ b/src/Data/Binary/Get.hs @@ -73,7 +73,7 @@ -- Let's first define a function that decodes many @Trade at s. -- -- @ --- getTrades :: Get ['Trade'] +-- getTrades :: Get [Trade] -- getTrades = do -- empty <- 'isEmpty' -- if empty @@ -86,11 +86,10 @@ -- Finally, we run the decoder: -- -- @ --- example :: IO () --- example = do +-- lazyIOExample :: IO [Trade] +-- lazyIOExample = do -- input <- BL.readFile \"trades.bin\" --- let trades = runGet getTrades input --- print trades +-- return ('runGet' getTrades input) -- @ -- -- This decoder has the downside that it will need to read all the input before @@ -102,17 +101,16 @@ -- that it can decode all input. -- -- @ --- example2 :: BL.ByteString -> [Trade] --- example2 input = go (runGetIncremental getTrade) input +-- incrementalExample :: BL.ByteString -> [Trade] +-- incrementalExample input0 = go decoder input0 -- where --- decoder = runGetIncremental getTrade --- --- go :: Decoder Trade -> BL.ByteString -> [Trade] --- go (Done leftover _consumed trade) input' = --- trade : go decoder (BL.chunk leftover input') --- go (Partial k) input' = --- go (k . takeHeadChunk $ input') (dropHeadChunk input') --- go (Fail _leftover _consumed msg) _input' = +-- decoder = 'runGetIncremental' getTrade +-- go :: 'Decoder' Trade -> BL.ByteString -> [Trade] +-- go ('Done' leftover _consumed trade) input = +-- trade : go decoder (BL.chunk leftover input) +-- go ('Partial' k) input = +-- go (k . takeHeadChunk $ input) (dropHeadChunk input) +-- go ('Fail' _leftover _consumed msg) _input = -- error msg -- -- takeHeadChunk :: BL.ByteString -> Maybe BS.ByteString @@ -128,12 +126,12 @@ -- _ -> BL.Empty -- @ -- --- Both these examples use lazy I/O to read the file from the disk, which is +-- The @lazyIOExample@ uses lazy I/O to read the file from the disk, which is -- not suitable in all applications, and certainly not if you need to read -- from a socket which has higher likelihood to fail. To address these needs, --- use the incremental input method. --- For an example of this, see the implementation of 'decodeFileOrFail' in --- "Data.Binary". +-- use the incremental input method like in @incrementalExample at . +-- For an example of how to read incrementally from a Handle, +-- see the implementation of 'decodeFileOrFail' in "Data.Binary". ----------------------------------------------------------------------------- From git at git.haskell.org Sun Dec 14 17:54:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:14 +0000 (UTC) Subject: [commit: packages/binary] master: Remove indentation of sample code in haddock. (043f0f3) Message-ID: <20141214175414.D06C33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/043f0f3d713469dfd1a17d2f37939d6a4339293e >--------------------------------------------------------------- commit 043f0f3d713469dfd1a17d2f37939d6a4339293e Author: Lennart Kolmodin Date: Tue Nov 12 23:15:38 2013 +0400 Remove indentation of sample code in haddock. The rendered layout breaks when a code segment has multiple functions, it renders without the given indentation. In this commit we set the base indentation to 0 spaces, and thus it renders correctly. >--------------------------------------------------------------- 043f0f3d713469dfd1a17d2f37939d6a4339293e src/Data/Binary/Get.hs | 116 ++++++++++++++++++++++++------------------------- 1 file changed, 58 insertions(+), 58 deletions(-) diff --git a/src/Data/Binary/Get.hs b/src/Data/Binary/Get.hs index e5d7219..ce6ab9d 100644 --- a/src/Data/Binary/Get.hs +++ b/src/Data/Binary/Get.hs @@ -32,13 +32,13 @@ -- -- A corresponding Haskell value looks like this: -- --- @ --- data Trade = Trade --- { timestamp :: !'Word32' --- , price :: !'Word32' --- , qty :: !'Word16' --- } deriving ('Show') --- @ +--@ +--data Trade = Trade +-- { timestamp :: !'Word32' +-- , price :: !'Word32' +-- , qty :: !'Word16' +-- } deriving ('Show') +--@ -- -- The fields in @Trade@ are marked as strict (using @!@) since we don't need -- laziness here. In practise, you would probably consider using the UNPACK @@ -47,21 +47,21 @@ -- -- Now, let's have a look at a decoder for this format. -- --- @ --- getTrade :: 'Get' Trade --- getTrade = do --- timestamp <- 'getWord32le' --- price <- 'getWord32le' --- quantity <- 'getWord16le' --- return '$!' Trade timestamp price quantity --- @ +--@ +--getTrade :: 'Get' Trade +--getTrade = do +-- timestamp <- 'getWord32le' +-- price <- 'getWord32le' +-- quantity <- 'getWord16le' +-- return '$!' Trade timestamp price quantity +--@ -- -- Or even simpler using applicative style: -- --- @ --- getTrade' :: 'Get' Trade --- getTrade' = Trade '<$>' 'getWord32le' '<*>' 'getWord32le' '<*>' 'getWord16le' --- @ +--@ +--getTrade' :: 'Get' Trade +--getTrade' = Trade '<$>' 'getWord32le' '<*>' 'getWord32le' '<*>' 'getWord16le' +--@ -- -- The applicative style can sometimes result in faster code, as @binary@ -- will try to optimize the code by grouping the reads together. @@ -72,25 +72,25 @@ -- -- Let's first define a function that decodes many @Trade at s. -- --- @ --- getTrades :: Get [Trade] --- getTrades = do --- empty <- 'isEmpty' --- if empty --- then return [] --- else do trade <- getTrade --- trades <- getTrades --- return (trade:trades) --- @ +--@ +--getTrades :: Get [Trade] +--getTrades = do +-- empty <- 'isEmpty' +-- if empty +-- then return [] +-- else do trade <- getTrade +-- trades <- getTrades +-- return (trade:trades) +--@ -- -- Finally, we run the decoder: -- --- @ --- lazyIOExample :: IO [Trade] --- lazyIOExample = do --- input <- BL.readFile \"trades.bin\" --- return ('runGet' getTrades input) --- @ +--@ +--lazyIOExample :: IO [Trade] +--lazyIOExample = do +-- input <- BL.readFile \"trades.bin\" +-- return ('runGet' getTrades input) +--@ -- -- This decoder has the downside that it will need to read all the input before -- it can return. On the other hand, it will not return anything until @@ -100,31 +100,31 @@ -- and get the following decoder. It will start to return data without knowing -- that it can decode all input. -- --- @ --- incrementalExample :: BL.ByteString -> [Trade] --- incrementalExample input0 = go decoder input0 --- where --- decoder = 'runGetIncremental' getTrade --- go :: 'Decoder' Trade -> BL.ByteString -> [Trade] --- go ('Done' leftover _consumed trade) input = --- trade : go decoder (BL.chunk leftover input) --- go ('Partial' k) input = --- go (k . takeHeadChunk $ input) (dropHeadChunk input) --- go ('Fail' _leftover _consumed msg) _input = --- error msg +--@ +--incrementalExample :: BL.ByteString -> [Trade] +--incrementalExample input0 = go decoder input0 +-- where +-- decoder = 'runGetIncremental' getTrade +-- go :: 'Decoder' Trade -> BL.ByteString -> [Trade] +-- go ('Done' leftover _consumed trade) input = +-- trade : go decoder (BL.chunk leftover input) +-- go ('Partial' k) input = +-- go (k . takeHeadChunk $ input) (dropHeadChunk input) +-- go ('Fail' _leftover _consumed msg) _input = +-- error msg -- --- takeHeadChunk :: BL.ByteString -> Maybe BS.ByteString --- takeHeadChunk lbs = --- case lbs of --- (BL.Chunk bs _) -> Just bs --- _ -> Nothing +--takeHeadChunk :: BL.ByteString -> Maybe BS.ByteString +--takeHeadChunk lbs = +-- case lbs of +-- (BL.Chunk bs _) -> Just bs +-- _ -> Nothing -- --- dropHeadChunk :: BL.ByteString -> BL.ByteString --- dropHeadChunk lbs = --- case lbs of --- (BL.Chunk _ lbs') -> lbs' --- _ -> BL.Empty --- @ +--dropHeadChunk :: BL.ByteString -> BL.ByteString +--dropHeadChunk lbs = +-- case lbs of +-- (BL.Chunk _ lbs') -> lbs' +-- _ -> BL.Empty +--@ -- -- The @lazyIOExample@ uses lazy I/O to read the file from the disk, which is -- not suitable in all applications, and certainly not if you need to read From git at git.haskell.org Sun Dec 14 17:54:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:16 +0000 (UTC) Subject: [commit: packages/binary] master: Code block indicators must be indented. (e7c2bc3) Message-ID: <20141214175416.D71003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/e7c2bc313ee4503663a93ecfc5479554ab5080c8 >--------------------------------------------------------------- commit e7c2bc313ee4503663a93ecfc5479554ab5080c8 Author: Lennart Kolmodin Date: Wed Nov 13 08:58:05 2013 +0400 Code block indicators must be indented. Or GHC will barf. >--------------------------------------------------------------- e7c2bc313ee4503663a93ecfc5479554ab5080c8 src/Data/Binary/Get.hs | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/src/Data/Binary/Get.hs b/src/Data/Binary/Get.hs index ce6ab9d..626c05c 100644 --- a/src/Data/Binary/Get.hs +++ b/src/Data/Binary/Get.hs @@ -32,13 +32,13 @@ -- -- A corresponding Haskell value looks like this: -- ---@ +-- @ --data Trade = Trade -- { timestamp :: !'Word32' -- , price :: !'Word32' -- , qty :: !'Word16' -- } deriving ('Show') ---@ +-- @ -- -- The fields in @Trade@ are marked as strict (using @!@) since we don't need -- laziness here. In practise, you would probably consider using the UNPACK @@ -47,21 +47,21 @@ -- -- Now, let's have a look at a decoder for this format. -- ---@ +-- @ --getTrade :: 'Get' Trade --getTrade = do -- timestamp <- 'getWord32le' -- price <- 'getWord32le' -- quantity <- 'getWord16le' -- return '$!' Trade timestamp price quantity ---@ +-- @ -- -- Or even simpler using applicative style: -- ---@ +-- @ --getTrade' :: 'Get' Trade --getTrade' = Trade '<$>' 'getWord32le' '<*>' 'getWord32le' '<*>' 'getWord16le' ---@ +-- @ -- -- The applicative style can sometimes result in faster code, as @binary@ -- will try to optimize the code by grouping the reads together. @@ -72,7 +72,7 @@ -- -- Let's first define a function that decodes many @Trade at s. -- ---@ +-- @ --getTrades :: Get [Trade] --getTrades = do -- empty <- 'isEmpty' @@ -81,16 +81,16 @@ -- else do trade <- getTrade -- trades <- getTrades -- return (trade:trades) ---@ +-- @ -- -- Finally, we run the decoder: -- ---@ +-- @ --lazyIOExample :: IO [Trade] --lazyIOExample = do --- input <- BL.readFile \"trades.bin\" --- return ('runGet' getTrades input) ---@ +-- input <- BL.readFile \"trades.bin\" +-- return ('runGet' getTrades input) +-- @ -- -- This decoder has the downside that it will need to read all the input before -- it can return. On the other hand, it will not return anything until @@ -100,7 +100,7 @@ -- and get the following decoder. It will start to return data without knowing -- that it can decode all input. -- ---@ +-- @ --incrementalExample :: BL.ByteString -> [Trade] --incrementalExample input0 = go decoder input0 -- where @@ -124,7 +124,7 @@ -- case lbs of -- (BL.Chunk _ lbs') -> lbs' -- _ -> BL.Empty ---@ +-- @ -- -- The @lazyIOExample@ uses lazy I/O to read the file from the disk, which is -- not suitable in all applications, and certainly not if you need to read From git at git.haskell.org Sun Dec 14 17:54:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:18 +0000 (UTC) Subject: [commit: packages/binary] master: [fix] preprocessor errors on clang ghc 7.6.3 (4efc2db) Message-ID: <20141214175418.DCC263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/4efc2db61f9f810de3ff0d9a8775ca005badcf8a >--------------------------------------------------------------- commit 4efc2db61f9f810de3ff0d9a8775ca005badcf8a Author: Lennart Melzer Date: Thu Feb 27 23:35:12 2014 +0100 [fix] preprocessor errors on clang ghc 7.6.3 >--------------------------------------------------------------- 4efc2db61f9f810de3ff0d9a8775ca005badcf8a src/Data/Binary/Builder/Base.hs | 4 +--- src/Data/Binary/Get.hs | 3 +-- src/Data/Binary/Get/Internal.hs | 3 +-- 3 files changed, 3 insertions(+), 7 deletions(-) diff --git a/src/Data/Binary/Builder/Base.hs b/src/Data/Binary/Builder/Base.hs index d6bb32a..6dd5b75 100644 --- a/src/Data/Binary/Builder/Base.hs +++ b/src/Data/Binary/Builder/Base.hs @@ -508,7 +508,5 @@ shiftr_w64 = shiftR append (ensureFree a) (ensureFree b) = ensureFree (max a b) "flush/flush" - append flush flush = flush - - #-} + append flush flush = flush #-} #endif diff --git a/src/Data/Binary/Get.hs b/src/Data/Binary/Get.hs index 626c05c..4f8f7b4 100644 --- a/src/Data/Binary/Get.hs +++ b/src/Data/Binary/Get.hs @@ -435,8 +435,7 @@ getWord8 = readN 1 B.unsafeHead "getWord32be/readN" getWord32be = readN 4 word32be "getWord32le/readN" getWord32le = readN 4 word32le "getWord64be/readN" getWord64be = readN 8 word64be -"getWord64le/readN" getWord64le = readN 8 word64le - #-} +"getWord64le/readN" getWord64le = readN 8 word64le #-} -- | Read a Word16 in big endian format getWord16be :: Get Word16 diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs index 7dac47d..2f656f1 100644 --- a/src/Data/Binary/Get/Internal.hs +++ b/src/Data/Binary/Get/Internal.hs @@ -321,8 +321,7 @@ readN !n f = ensureN n >> unsafeReadN n f returnG f = readN 0 (const f) "readN 0/returnG swapback" [1] forall f. - readN 0 f = returnG (f B.empty) - #-} + readN 0 f = returnG (f B.empty) #-} -- | Ensure that there are at least @n@ bytes available. If not, the -- computation will escape with 'Partial'. From git at git.haskell.org Sun Dec 14 17:54:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:20 +0000 (UTC) Subject: [commit: packages/binary] master: Merge pull request #48 from lennart/master (7f72b1a) Message-ID: <20141214175420.E4F703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/7f72b1a62ab7fd633e8a5d098d8d818d06460d9a >--------------------------------------------------------------- commit 7f72b1a62ab7fd633e8a5d098d8d818d06460d9a Merge: e7c2bc3 4efc2db Author: Lennart Kolmodin Date: Sat Mar 15 09:49:38 2014 +0300 Merge pull request #48 from lennart/master [fix] preprocessor errors on clang ghc 7.6.3 >--------------------------------------------------------------- 7f72b1a62ab7fd633e8a5d098d8d818d06460d9a src/Data/Binary/Builder/Base.hs | 4 +--- src/Data/Binary/Get.hs | 3 +-- src/Data/Binary/Get/Internal.hs | 3 +-- 3 files changed, 3 insertions(+), 7 deletions(-) From git at git.haskell.org Sun Dec 14 17:54:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:22 +0000 (UTC) Subject: [commit: packages/binary] master: Add function 'label'. (ab88a9d) Message-ID: <20141214175422.EBBA83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/ab88a9db0ca3eac9f3d32d094c01745fb710f776 >--------------------------------------------------------------- commit ab88a9db0ca3eac9f3d32d094c01745fb710f776 Author: Lennart Kolmodin Date: Thu Mar 20 22:11:39 2014 +0400 Add function 'label'. 'label :: String -> Get a -> Get a' adds the given string to the error message string if the given decoder fails. Fixes #16. >--------------------------------------------------------------- ab88a9db0ca3eac9f3d32d094c01745fb710f776 src/Data/Binary/Get.hs | 1 + src/Data/Binary/Get/Internal.hs | 13 ++++++++ tests/Action.hs | 69 ++++++++++++++++++++++++++++++++++++----- tests/QC.hs | 5 ++- 4 files changed, 77 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 ab88a9db0ca3eac9f3d32d094c01745fb710f776 From git at git.haskell.org Sun Dec 14 17:54:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:24 +0000 (UTC) Subject: [commit: packages/binary] master: Remove commented out code, and style imports. (5e9a93c) Message-ID: <20141214175424.F2C863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/5e9a93c817c44a377fe8f87361017cc88f7eeec1 >--------------------------------------------------------------- commit 5e9a93c817c44a377fe8f87361017cc88f7eeec1 Author: Lennart Kolmodin Date: Thu Mar 20 22:26:41 2014 +0400 Remove commented out code, and style imports. >--------------------------------------------------------------- 5e9a93c817c44a377fe8f87361017cc88f7eeec1 tests/Action.hs | 25 ++++++++++---------- tests/QC.hs | 71 ++++++++++++++++++--------------------------------------- 2 files changed, 34 insertions(+), 62 deletions(-) diff --git a/tests/Action.hs b/tests/Action.hs index 673eb3e..5981b6b 100644 --- a/tests/Action.hs +++ b/tests/Action.hs @@ -1,19 +1,18 @@ {-# LANGUAGE BangPatterns #-} module Action where -import Data.List (intersperse) -import Control.Applicative -import Control.Monad -import Test.Framework -import Test.Framework.Providers.QuickCheck2 -import Test.QuickCheck - -import qualified Data.ByteString as B -import qualified Data.ByteString.Lazy as L - -import qualified Data.Binary.Get as Binary - -import Arbitrary() +import Control.Applicative +import Control.Monad +import qualified Data.ByteString as B +import qualified Data.ByteString.Lazy as L +import Data.List (intersperse) + +import Test.Framework +import Test.Framework.Providers.QuickCheck2 +import Test.QuickCheck + +import Arbitrary () +import qualified Data.Binary.Get as Binary tests :: [Test] tests = [ testProperty "action" prop_action diff --git a/tests/QC.hs b/tests/QC.hs index 30addd3..fbaded1 100644 --- a/tests/QC.hs +++ b/tests/QC.hs @@ -1,46 +1,26 @@ {-# LANGUAGE ScopedTypeVariables #-} -module Main where - -import Data.Binary -import Data.Binary.Put -import Data.Binary.Get - -import Control.Applicative -import Control.Monad (unless) - -import qualified Data.ByteString as B --- import qualified Data.ByteString.Internal as B --- import qualified Data.ByteString.Unsafe as B -import qualified Data.ByteString.Lazy as L -import qualified Data.ByteString.Lazy.Internal as L --- import qualified Data.Map as Map --- import qualified Data.Set as Set --- import qualified Data.IntMap as IntMap --- import qualified Data.IntSet as IntSet - --- import Data.Array (Array) --- import Data.Array.IArray --- import Data.Array.Unboxed (UArray) - --- import Data.Word -import Data.Int -import Data.Ratio - -import Control.Exception as C (catch,evaluate,SomeException) --- import Control.Monad --- import System.Environment --- import System.IO -import System.IO.Unsafe - -import Test.QuickCheck --- import Text.Printf - -import Test.Framework -import Test.Framework.Providers.QuickCheck2 --- import Data.Monoid - -import qualified Action (tests) -import Arbitrary() +module Main ( main ) where + +import Control.Applicative +import Control.Exception as C (SomeException, + catch, evaluate) +import Control.Monad (unless) +import qualified Data.ByteString as B +import qualified Data.ByteString.Lazy as L +import qualified Data.ByteString.Lazy.Internal as L +import Data.Int +import Data.Ratio +import System.IO.Unsafe + +import Test.Framework +import Test.Framework.Providers.QuickCheck2 +import Test.QuickCheck + +import qualified Action (tests) +import Arbitrary () +import Data.Binary +import Data.Binary.Get +import Data.Binary.Put ------------------------------------------------------------------------ @@ -490,10 +470,6 @@ tests = p (test :: T (Int,Int,Int,Int,Int,Int,Int,Int,Int))) , ("(Int,Int,Int,Int,Int,Int,Int,Int,Int,Int)", p (test :: T (Int,Int,Int,Int,Int,Int,Int,Int,Int,Int))) - {- - , ("IntSet", p (test :: T IntSet.IntSet )) - , ("IntMap ByteString", p (test :: T (IntMap.IntMap B.ByteString) )) - -} , ("B.ByteString", p (test :: T B.ByteString )) , ("L.ByteString", p (test :: T L.ByteString )) @@ -506,6 +482,3 @@ tests = , ("[L.ByteString] invariant", p (prop_invariant :: B [L.ByteString] )) ] ] - --- GHC only: --- ,("Sequence", p (roundTrip :: Seq.Seq Int64 -> Bool)) From git at git.haskell.org Sun Dec 14 17:54:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:27 +0000 (UTC) Subject: [commit: packages/binary] master: Label test samples in prop_label. (23f64d9) Message-ID: <20141214175427.054393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/23f64d90ab2404baa5479667ce93b33a2760b400 >--------------------------------------------------------------- commit 23f64d90ab2404baa5479667ce93b33a2760b400 Author: Lennart Kolmodin Date: Sun Mar 23 10:26:29 2014 +0400 Label test samples in prop_label. >--------------------------------------------------------------- 23f64d90ab2404baa5479667ce93b33a2760b400 tests/Action.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/tests/Action.hs b/tests/Action.hs index 5981b6b..f32d748 100644 --- a/tests/Action.hs +++ b/tests/Action.hs @@ -138,8 +138,10 @@ prop_label = Nothing -> error "expected labels" expectedMsg | null labels = "fail" | otherwise = concat $ intersperse "\n" ("fail":labels) - in if (msg == expectedMsg) then True else error (show msg ++ " vs. " ++ show expectedMsg) - Right (inp, off, value) -> True + in if (msg == expectedMsg) + then label ("labels: " ++ show (length labels)) True + else error (show msg ++ " vs. " ++ show expectedMsg) + Right (inp, off, value) -> label "test case without 'fail'" True collectLabels :: [Action] -> Maybe [String] collectLabels = go [] @@ -216,7 +218,9 @@ eval inp acts0 = go 0 acts0 >> return () Just offset -> return offset gen_actions :: Bool -> Gen [Action] -gen_actions genFail = sized (go False) +gen_actions genFail = do + acts <- sized (go False) + return (if genFail then (acts ++ [Fail]) else acts) where go :: Bool -> Int -> Gen [Action] go _ 0 = return [] From git at git.haskell.org Sun Dec 14 17:54:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:29 +0000 (UTC) Subject: [commit: packages/binary] master: Add test to check error position and remaining input. (6076e2f) Message-ID: <20141214175429.0C3D63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/6076e2f5882fe742111ccae0ad080e5b8b713f0e >--------------------------------------------------------------- commit 6076e2f5882fe742111ccae0ad080e5b8b713f0e Author: Lennart Kolmodin Date: Sun Mar 23 20:54:08 2014 +0400 Add test to check error position and remaining input. >--------------------------------------------------------------- 6076e2f5882fe742111ccae0ad080e5b8b713f0e tests/Action.hs | 101 ++++++++++++++++++++++++++++++++++++++++++-------------- 1 file changed, 76 insertions(+), 25 deletions(-) diff --git a/tests/Action.hs b/tests/Action.hs index f32d748..d26c776 100644 --- a/tests/Action.hs +++ b/tests/Action.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE BangPatterns, PatternGuards #-} module Action where import Control.Applicative @@ -16,7 +16,8 @@ import qualified Data.Binary.Get as Binary tests :: [Test] tests = [ testProperty "action" prop_action - , testProperty "label" prop_label ] + , testProperty "label" prop_label + , testProperty "fail" prop_fail ] data Action = Actions [Action] @@ -125,6 +126,8 @@ prop_action = case Binary.runGet (eval allInput actions) lbs of () -> True +-- | When a decoder aborts with 'fail', check that all relevant uses of 'label' +-- are respected. prop_label :: Property prop_label = forAllShrink (gen_actions True) shrink $ \ actions -> @@ -132,36 +135,84 @@ prop_label = L.length lbs >= fromIntegral (max_len actions) ==> let allInput = B.concat (L.toChunks lbs) in case Binary.runGetOrFail (eval allInput actions) lbs of - Left (inp, off, msg) -> - let labels = case collectLabels actions of - Just labels -> labels + Left (_inp, _off, msg) -> + let lbls = case collectLabels actions of + Just lbls' -> lbls' Nothing -> error "expected labels" - expectedMsg | null labels = "fail" - | otherwise = concat $ intersperse "\n" ("fail":labels) + expectedMsg | null lbls = "fail" + | otherwise = concat $ intersperse "\n" ("fail":lbls) in if (msg == expectedMsg) - then label ("labels: " ++ show (length labels)) True + then label ("labels: " ++ show (length lbls)) True else error (show msg ++ " vs. " ++ show expectedMsg) - Right (inp, off, value) -> label "test case without 'fail'" True + Right (_inp, _off, _value) -> label "test case without 'fail'" True +-- | When a decoder aborts with 'fail', check the fail position and +-- remaining input. +prop_fail :: Property +prop_fail = + forAllShrink (gen_actions True) shrink $ \ actions -> + forAll arbitrary $ \ lbs -> + L.length lbs >= fromIntegral (max_len actions) ==> + let allInput = B.concat (L.toChunks lbs) in + case Binary.runGetOrFail (eval allInput actions) lbs of + Left (inp, off, _msg) -> + case () of + _ | Just off /= findFailPosition actions -> + error ("fail position incorrect, expected " ++ + show (findFailPosition actions) ++ + " but got " ++ show off) + | inp /= L.drop (fromIntegral off) lbs -> + error "remaining output incorrect" + | otherwise -> property True + Right (_inp, _off, _value) -> label "test case without 'fail'" True + +-- | Collect all the labels up to a 'fail', or Nothing if the +-- decoder will not fail. collectLabels :: [Action] -> Maybe [String] collectLabels = go [] where - go labels [] = Nothing - go labels (Fail:xs) = Just labels - go labels (Label str a:xs) = - case go (str:labels) a of - Just labels' -> Just labels' - Nothing -> go labels xs - go labels (Try a b:xs) = - case (go labels a, go labels b) of - (Just _, Just labels') -> Just labels' - (Just _, Nothing) -> go labels xs - (Nothing, _) -> go labels xs - go labels (Actions a:xs) = go labels (a++xs) - go labels (LookAhead a:xs) = go labels (a++xs) - go labels (LookAheadM _ a:xs) = go labels (a++xs) - go labels (LookAheadE _ a:xs) = go labels (a++xs) - go labels (_:xs) = go labels xs + go _ [] = Nothing + go lbls (Fail:_) = Just lbls + go lbls (Label str a:xs) = + case go (str:lbls) a of + Just lbls' -> Just lbls' + Nothing -> go lbls xs + go lbls (Try a b:xs) = + case (go lbls a, go lbls b) of + (Just _, Just lbls') -> Just lbls' + (Just _, Nothing) -> go lbls xs + (Nothing, _) -> go lbls xs + go lbls (Actions a:xs) = go lbls (a++xs) + go lbls (LookAhead a:xs) = go lbls (a++xs) + go lbls (LookAheadM _ a:xs) = go lbls (a++xs) + go lbls (LookAheadE _ a:xs) = go lbls (a++xs) + go lbls (_:xs) = go lbls xs + +-- | Finds at which byte offset the decoder will fail, +-- or Nothing if it won't fail. +findFailPosition :: [Action] -> Maybe Binary.ByteOffset +findFailPosition = either (const Nothing) Just . go (0::Binary.ByteOffset) + where + go pos [] = Left pos + go pos (x:xs) = + case x of + Actions a -> go pos (a++xs) + GetByteString n -> go (pos + fromIntegral n) xs + BytesRead -> go pos xs + Fail -> Right pos + Label _ a -> go pos (a++xs) + LookAhead a -> either (const (go pos xs)) Right (go pos a) + LookAheadM consume a -> + let pos' False = go pos (LookAhead a : xs) + pos' True = go pos (a++xs) + in pos' consume + LookAheadE consume a -> + let pos' False = go pos (LookAhead a : xs) + pos' True = go pos (a++xs) + in pos' consume + Try a b + | Left pos' <- go pos a -> go pos' xs + | otherwise -> go pos (b++xs) -- | Evaluate (run) the model. -- First argument is all the input that will be used when executing From git at git.haskell.org Sun Dec 14 17:54:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:31 +0000 (UTC) Subject: [commit: packages/binary] master: Add changelog.md (96591b0) Message-ID: <20141214175431.13B693A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/96591b07ba070969543df5300881ca6826431336 >--------------------------------------------------------------- commit 96591b07ba070969543df5300881ca6826431336 Author: Lennart Kolmodin Date: Sun Mar 30 17:31:26 2014 +0400 Add changelog.md >--------------------------------------------------------------- 96591b07ba070969543df5300881ca6826431336 changelog.md | 49 +++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 49 insertions(+) diff --git a/changelog.md b/changelog.md new file mode 100644 index 0000000..31059dd --- /dev/null +++ b/changelog.md @@ -0,0 +1,49 @@ +binary +====== + +binary-0.7.1.0 +-------------- + +- Add `lookAheadE :: Get (Either a b) -> Get (Either a b)`. +- Add MonadPlus instance for Get. + + +binary-0.7.0.1 +-------------- + +- Updates to documentation. + +binary-0.7.0.0 +-------------- + +- Add `lookAhead :: Get a -> Get a`. +- Add `lookAheadM :: Get (Maybe a) -> Get (Maybe a)`. +- Add Alternative instance for Get (provides `<|>`). +- Add `decodeOrFail :: Binary a => L.ByteString -> Either (L.ByteString, ByteOffset, String) (L.ByteString, ByteOffset, a)` +- Add `decodeFileOrFail :: Binary a => FilePath -> IO (Either (ByteOffset, String) a)`. +- Remove `Ord` class constraint from `Set` and `Map` Binary instances. + +binary-0.6.4 +------------ + +- Add `runGetOrFail :: Get a -> L.ByteString -> Either (L.ByteString, ByteOffset, String) (L.ByteString, ByteOffset, a)`. + +binary-0.6.3 +------------ + +- Documentation tweeks, internal restructuring, more tests. + +binary-0.6.2 +------------ + +- `some` and `many` more efficient. +- Fix bug where `bytesRead` returned the wrong value. +- Documentation improvements. + +binary-0.6.1 +------------ + +- Fix bug where a decoder could return with `Partial` after the previous reply was `Nothing`. + +binary-0.6.0.0 +-------------- From git at git.haskell.org Sun Dec 14 17:54:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:33 +0000 (UTC) Subject: [commit: packages/binary] master: Merge branch 'isolate' of github.com:singpolyma/binary into singpolyma-isolate (1d9bb4c) Message-ID: <20141214175433.1C76D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/1d9bb4cce0788b9cb8c99cf2978c874a8756ca54 >--------------------------------------------------------------- commit 1d9bb4cce0788b9cb8c99cf2978c874a8756ca54 Merge: 96591b0 4ecce94 Author: Lennart Kolmodin Date: Thu Apr 3 00:21:04 2014 +0400 Merge branch 'isolate' of github.com:singpolyma/binary into singpolyma-isolate >--------------------------------------------------------------- 1d9bb4cce0788b9cb8c99cf2978c874a8756ca54 src/Data/Binary/Get.hs | 1 + src/Data/Binary/Get/Internal.hs | 22 ++++++++++++++++++++++ 2 files changed, 23 insertions(+) From git at git.haskell.org Sun Dec 14 17:54:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:35 +0000 (UTC) Subject: [commit: packages/binary] master: Add function 'isolate'. (1279d92) Message-ID: <20141214175435.239073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/1279d9202dde6ab7ad51d24f8f09f23a1be9abf9 >--------------------------------------------------------------- commit 1279d9202dde6ab7ad51d24f8f09f23a1be9abf9 Author: Lennart Kolmodin Date: Mon Apr 14 23:10:53 2014 +0400 Add function 'isolate'. isolate :: Int -> Get a -> Get a Isolates a decoder to a fixed number of bytes. >--------------------------------------------------------------- 1279d9202dde6ab7ad51d24f8f09f23a1be9abf9 src/Data/Binary/Get/Internal.hs | 51 ++++--- tests/Action.hs | 323 ++++++++++++++++++++++------------------ 2 files changed, 214 insertions(+), 160 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1279d9202dde6ab7ad51d24f8f09f23a1be9abf9 From git at git.haskell.org Sun Dec 14 17:54:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:37 +0000 (UTC) Subject: [commit: packages/binary] master: Update changelog. (ae21381) Message-ID: <20141214175437.2ED5C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/ae213813089160aecae3d1ad9fee24824d9e0c73 >--------------------------------------------------------------- commit ae213813089160aecae3d1ad9fee24824d9e0c73 Author: Lennart Kolmodin Date: Sat Apr 19 11:09:07 2014 +0400 Update changelog. >--------------------------------------------------------------- ae213813089160aecae3d1ad9fee24824d9e0c73 changelog.md | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/changelog.md b/changelog.md index 31059dd..2b1e9cd 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,13 @@ binary ====== + +binary-HEAD +----------- + +- Add `isolate :: Int -> Get a -> Get a`. +- Add `label :: String -> Get a -> Get a`. + binary-0.7.1.0 -------------- From git at git.haskell.org Sun Dec 14 17:54:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:39 +0000 (UTC) Subject: [commit: packages/binary] master: Make tests compile on GHC 7.4.1. (dd48ed1) Message-ID: <20141214175439.37C343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/dd48ed1683013cc08013ca7ea79d752c731a5362 >--------------------------------------------------------------- commit dd48ed1683013cc08013ca7ea79d752c731a5362 Author: Lennart Kolmodin Date: Sat Apr 19 11:13:38 2014 +0400 Make tests compile on GHC 7.4.1. >--------------------------------------------------------------- dd48ed1683013cc08013ca7ea79d752c731a5362 tests/Action.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/Action.hs b/tests/Action.hs index df632ec..1013a9b 100644 --- a/tests/Action.hs +++ b/tests/Action.hs @@ -115,7 +115,7 @@ randomInput n = do s <- vectorOf m $ choose ('a', 'z') let b = B.pack $ map (fromIntegral.ord) s rest <- randomInput (n-m) - return (L.append (L.fromStrict b) rest) + return (L.append (L.fromChunks [b]) rest) -- | Build binary programs and compare running them to running a (hopefully) -- identical model. From git at git.haskell.org Sun Dec 14 17:54:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:41 +0000 (UTC) Subject: [commit: packages/binary] master: Add LANGUAGE extensions for inferred signatures. (334d872) Message-ID: <20141214175441.3E45F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/334d8729d10abdd8c663a5fc9f7568d5d7b20cbc >--------------------------------------------------------------- commit 334d8729d10abdd8c663a5fc9f7568d5d7b20cbc Author: Jan Stolarek Date: Sat Apr 19 09:04:02 2014 +0200 Add LANGUAGE extensions for inferred signatures. Some of the inferred signatures required LANGUAGE extensions that were not enabled. Since now GHC checks that we have to explicitly list required extensions. >--------------------------------------------------------------- 334d8729d10abdd8c663a5fc9f7568d5d7b20cbc src/Data/Binary/Get/Internal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs index 7dac47d..292a179 100644 --- a/src/Data/Binary/Get/Internal.hs +++ b/src/Data/Binary/Get/Internal.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, RankNTypes, MagicHash, BangPatterns #-} +{-# LANGUAGE CPP, RankNTypes, MagicHash, BangPatterns, TypeFamilies #-} -- CPP C style pre-precessing, the #if defined lines -- RankNTypes forall r. statement From git at git.haskell.org Sun Dec 14 17:54:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:43 +0000 (UTC) Subject: [commit: packages/binary] master: Merge pull request #54 from jstolarek/T8883 (3ea38d0) Message-ID: <20141214175443.472EB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/3ea38d010933cac73e5fcd513b00766af8d86091 >--------------------------------------------------------------- commit 3ea38d010933cac73e5fcd513b00766af8d86091 Merge: dd48ed1 334d872 Author: Lennart Kolmodin Date: Fri Apr 25 09:38:12 2014 +0400 Merge pull request #54 from jstolarek/T8883 Add LANGUAGE extensions for inferred signatures. >--------------------------------------------------------------- 3ea38d010933cac73e5fcd513b00766af8d86091 src/Data/Binary/Get/Internal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Sun Dec 14 17:54:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:45 +0000 (UTC) Subject: [commit: packages/binary] master: Bug fix isolate; decoder must use all input (521705c) Message-ID: <20141214175445.4CDE93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/521705c08c4608fadf34b19e2e04d694625b24a5 >--------------------------------------------------------------- commit 521705c08c4608fadf34b19e2e04d694625b24a5 Author: Lennart Kolmodin Date: Sun May 11 13:20:12 2014 +0400 Bug fix isolate; decoder must use all input A decoder could have been given the final chuck, but not used all its input, and still succeed. This change corrects the behavior and makes sure that isolate must use all input in order to succeed. >--------------------------------------------------------------- 521705c08c4608fadf34b19e2e04d694625b24a5 src/Data/Binary/Get/Internal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs index 85f56df..7d9a518 100644 --- a/src/Data/Binary/Get/Internal.hs +++ b/src/Data/Binary/Get/Internal.hs @@ -194,7 +194,7 @@ isolate n0 act | otherwise = go n0 (runCont act B.empty Done) where go !n (Done left x) - | n == 0 = return x + | n == 0 && B.null left = return x | otherwise = do pushFront left let consumed = n0 - n From git at git.haskell.org Sun Dec 14 17:54:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:47 +0000 (UTC) Subject: [commit: packages/binary] master: Improve model tests (510bf8b) Message-ID: <20141214175447.5506A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/510bf8b5f55624dbbc7a02369d132afafea1d15c >--------------------------------------------------------------- commit 510bf8b5f55624dbbc7a02369d132afafea1d15c Author: Lennart Kolmodin Date: Sun May 11 13:16:57 2014 +0400 Improve model tests In the model tests, generate more kinds of programs. Previously, only programs that failed by using 'fail' were generated. Now we also fail decoders by running out of input, using too much or too little input in a isolate block. Also correct the tests when they check for labels. This change exposes some bugs in isolate. >--------------------------------------------------------------- 510bf8b5f55624dbbc7a02369d132afafea1d15c binary.cabal | 4 +-- tests/Action.hs | 110 ++++++++++++++++++++++++++++++++++++++++---------------- 2 files changed, 82 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 510bf8b5f55624dbbc7a02369d132afafea1d15c From git at git.haskell.org Sun Dec 14 17:54:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:49 +0000 (UTC) Subject: [commit: packages/binary] master: Bug fix isolate; keep labels from within failing isolate (f7ffedd) Message-ID: <20141214175449.5A8BF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/f7ffeddd183984bf88b98c7d444b109dd156c8a1 >--------------------------------------------------------------- commit f7ffeddd183984bf88b98c7d444b109dd156c8a1 Author: Lennart Kolmodin Date: Sun May 11 13:24:01 2014 +0400 Bug fix isolate; keep labels from within failing isolate When an isolated decoder failed due to over consuming input, any labels set within that decoder were lost since demanding more input would fail within the isolate-decoder runner and not in the isolated decoder itself. With this change the signal of lack of more input is passed into the isolated decoder which in turn will fail, keeping any labels up to that point. >--------------------------------------------------------------- f7ffeddd183984bf88b98c7d444b109dd156c8a1 src/Data/Binary/Get/Internal.hs | 15 ++++++++++----- 1 file changed, 10 insertions(+), 5 deletions(-) diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs index 84ae199..03305ea 100644 --- a/src/Data/Binary/Get/Internal.hs +++ b/src/Data/Binary/Get/Internal.hs @@ -202,11 +202,16 @@ isolate n0 act " which is less than the expected " ++ show n0 ++ " bytes" go 0 (Partial resume) = go 0 (resume Nothing) go n (Partial resume) = do - ensureN 1 - inp <- get - let (inp', out) = B.splitAt n inp - put out - go (n - B.length inp') (resume (Just inp')) + inp <- C $ \inp k -> do + let takeLimited str = + let (inp', out) = B.splitAt n str + in k out (Just inp') + case not (B.null inp) of + True -> takeLimited inp + False -> prompt inp (k B.empty Nothing) takeLimited + case inp of + Nothing -> go n (resume Nothing) + Just str -> go (n - B.length str) (resume (Just str)) go _ (Fail bs err) = pushFront bs >> fail err go n (BytesRead r resume) = go n (resume $! fromIntegral n0 - fromIntegral n - r) From git at git.haskell.org Sun Dec 14 17:54:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:51 +0000 (UTC) Subject: [commit: packages/binary] master: Bug fix isolate; use correct offset in error message (d99097a) Message-ID: <20141214175451.615B63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/d99097a008c1bc41331da48756485bbc9edb3fe9 >--------------------------------------------------------------- commit d99097a008c1bc41331da48756485bbc9edb3fe9 Author: Lennart Kolmodin Date: Sun May 11 13:22:12 2014 +0400 Bug fix isolate; use correct offset in error message When a isolate decoder fails, it includes information about the offsets of how far in the decoding it got in the error message. With this change the offset is now correct. >--------------------------------------------------------------- d99097a008c1bc41331da48756485bbc9edb3fe9 src/Data/Binary/Get/Internal.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs index 7d9a518..84ae199 100644 --- a/src/Data/Binary/Get/Internal.hs +++ b/src/Data/Binary/Get/Internal.hs @@ -197,8 +197,8 @@ isolate n0 act | n == 0 && B.null left = return x | otherwise = do pushFront left - let consumed = n0 - n - fail $ "isolate: decoder consumed " ++ show consumed ++ + let consumed = n0 - n - B.length left + fail $ "isolate: the decoder consumed " ++ show consumed ++ " bytes" ++ " which is less than the expected " ++ show n0 ++ " bytes" go 0 (Partial resume) = go 0 (resume Nothing) go n (Partial resume) = do From git at git.haskell.org Sun Dec 14 17:54:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:53 +0000 (UTC) Subject: [commit: packages/binary] master: In test-suites and benchmarks, depend on source (d9e361f) Message-ID: <20141214175453.680A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/d9e361fd92e3183a8b536a74508e64726538b437 >--------------------------------------------------------------- commit d9e361fd92e3183a8b536a74508e64726538b437 Author: Lennart Kolmodin Date: Sun May 11 15:00:31 2014 +0400 In test-suites and benchmarks, depend on source Depend directly on the source of binary, instead of the library itself. This is unfortunate as it complicates the cabal file, but we have to in order to remove circular dependencies when installing dependencies of the test-suites and benchmarks. >--------------------------------------------------------------- d9e361fd92e3183a8b536a74508e64726538b437 binary.cabal | 32 ++++++++++++++++++++------------ 1 file changed, 20 insertions(+), 12 deletions(-) diff --git a/binary.cabal b/binary.cabal index e9b6bde..8ed0e95 100644 --- a/binary.cabal +++ b/binary.cabal @@ -56,78 +56,86 @@ library ghc-options: -O2 -Wall -fliberate-case-threshold=1000 +-- Due to circular dependency, we cannot make any of the test-suites or +-- benchmark depend on the binary library. Instead, for each test-suite and +-- benchmark, we include the source directory of binary and build-depend on all +-- the dependencies binary has. + test-suite qc type: exitcode-stdio-1.0 - hs-source-dirs: tests + hs-source-dirs: src tests main-is: QC.hs other-modules: Action Arbitrary build-depends: - array, base >= 3.0 && < 5, bytestring >= 0.9, - containers, random>=1.0.1.0, test-framework, test-framework-quickcheck2 >= 0.3, QuickCheck>=2.7 + -- build dependencies from using binary source rather than depending on the library + build-depends: array, containers ghc-options: -Wall -O2 -threaded - hs-source-dirs: src test-suite read-write-file type: exitcode-stdio-1.0 - hs-source-dirs: tests + hs-source-dirs: src tests main-is: File.hs build-depends: base >= 3.0 && < 5, bytestring >= 0.9, - binary, Cabal, directory, filepath, HUnit + -- build dependencies from using binary source rather than depending on the library + build-depends: array, containers ghc-options: -Wall benchmark bench type: exitcode-stdio-1.0 - hs-source-dirs: benchmarks + hs-source-dirs: src benchmarks main-is: Benchmark.hs other-modules: MemBench build-depends: base >= 3.0 && < 5, - binary, bytestring + -- build dependencies from using binary source rather than depending on the library + build-depends: array, containers c-sources: benchmarks/CBenchmark.c include-dirs: benchmarks ghc-options: -O2 benchmark get type: exitcode-stdio-1.0 - hs-source-dirs: benchmarks + hs-source-dirs: src benchmarks main-is: Get.hs build-depends: attoparsec, base >= 3.0 && < 5, - binary, bytestring, cereal, criterion, deepseq, mtl + -- build dependencies from using binary source rather than depending on the library + build-depends: array, containers ghc-options: -O2 benchmark builder type: exitcode-stdio-1.0 - hs-source-dirs: benchmarks + hs-source-dirs: src benchmarks main-is: Builder.hs build-depends: base >= 3.0 && < 5, - binary, bytestring, criterion, deepseq, mtl + -- build dependencies from using binary source rather than depending on the library + build-depends: array, containers ghc-options: -O2 From git at git.haskell.org Sun Dec 14 17:54:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:55 +0000 (UTC) Subject: [commit: packages/binary] master: binary.cabal: update list with which GHCs we've tested (b84dd93) Message-ID: <20141214175455.6DD3B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/b84dd93b62388bc3c0b5ae1f11dfb2f892711db8 >--------------------------------------------------------------- commit b84dd93b62388bc3c0b5ae1f11dfb2f892711db8 Author: Lennart Kolmodin Date: Sun May 11 15:02:35 2014 +0400 binary.cabal: update list with which GHCs we've tested >--------------------------------------------------------------- b84dd93b62388bc3c0b5ae1f11dfb2f892711db8 binary.cabal | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/binary.cabal b/binary.cabal index 8ed0e95..d38922c 100644 --- a/binary.cabal +++ b/binary.cabal @@ -18,7 +18,7 @@ category: Data, Parsing stability: provisional build-type: Simple cabal-version: >= 1.8 -tested-with: GHC == 7.0.4, GHC == 7.4.1, GHC == 7.6.1 +tested-with: GHC == 7.4.2, GHC == 7.6.3, GHC == 7.8.2 extra-source-files: README.md index.html docs/hcar/binary-Lb.tex tools/derive/*.hs tests/Makefile benchmarks/Makefile @@ -31,9 +31,6 @@ source-repository head type: git location: git://github.com/kolmodin/binary.git -flag development - default: False - library build-depends: base >= 3.0 && < 5, bytestring >= 0.9, containers, array hs-source-dirs: src From git at git.haskell.org Sun Dec 14 17:54:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:57 +0000 (UTC) Subject: [commit: packages/binary] master: Update .gitignore and .hgignore with cabal sandbox files (89fcbdb) Message-ID: <20141214175457.7612B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/89fcbdb7b35800805283cc1b9efda6024f7a4485 >--------------------------------------------------------------- commit 89fcbdb7b35800805283cc1b9efda6024f7a4485 Author: Lennart Kolmodin Date: Sun May 11 15:06:37 2014 +0400 Update .gitignore and .hgignore with cabal sandbox files >--------------------------------------------------------------- 89fcbdb7b35800805283cc1b9efda6024f7a4485 .gitignore | 2 ++ .hgignore | 2 ++ 2 files changed, 4 insertions(+) diff --git a/.gitignore b/.gitignore index 55b46d0..d69f072 100644 --- a/.gitignore +++ b/.gitignore @@ -3,6 +3,7 @@ *.p_hi *.prof *.tix +*.swp .hpc/ /benchmarks/bench /benchmarks/builder @@ -13,3 +14,4 @@ dist-boot dist-install ghc.mk .cabal-sandbox +cabal.sandbox.config diff --git a/.hgignore b/.hgignore index 8a876d7..f136aef 100644 --- a/.hgignore +++ b/.hgignore @@ -3,3 +3,5 @@ syntax: glob .*.swp *~ \#* +.cabal-sandbox +cabal.sandbox.config From git at git.haskell.org Sun Dec 14 17:54:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:54:59 +0000 (UTC) Subject: [commit: packages/binary] master: Version bump to 0.7.2.0 (5b4f5cf) Message-ID: <20141214175459.7B2EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/5b4f5cf0874915d7f03353ee615f3747592f843f >--------------------------------------------------------------- commit 5b4f5cf0874915d7f03353ee615f3747592f843f Author: Lennart Kolmodin Date: Sun May 11 15:08:50 2014 +0400 Version bump to 0.7.2.0 >--------------------------------------------------------------- 5b4f5cf0874915d7f03353ee615f3747592f843f binary.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/binary.cabal b/binary.cabal index d38922c..6995ac9 100644 --- a/binary.cabal +++ b/binary.cabal @@ -1,5 +1,5 @@ name: binary -version: 0.7.1.0 +version: 0.7.2.0 license: BSD3 license-file: LICENSE author: Lennart Kolmodin From git at git.haskell.org Sun Dec 14 17:55:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:01 +0000 (UTC) Subject: [commit: packages/binary] master: First attempt at adding Travis CI support. (a569af5) Message-ID: <20141214175501.83F793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/a569af5ee7693c49af401000a9c5dacc2bfa3ad7 >--------------------------------------------------------------- commit a569af5ee7693c49af401000a9c5dacc2bfa3ad7 Author: Lennart Kolmodin Date: Sun May 11 15:09:42 2014 +0400 First attempt at adding Travis CI support. >--------------------------------------------------------------- a569af5ee7693c49af401000a9c5dacc2bfa3ad7 .travis.yml | 35 +++++++++++++++++++++++++++++++++++ 1 file changed, 35 insertions(+) diff --git a/.travis.yml b/.travis.yml new file mode 100644 index 0000000..eb4be6f --- /dev/null +++ b/.travis.yml @@ -0,0 +1,35 @@ +# NB: don't set `language: haskell` here +# See https://github.com/hvr/multi-ghc-travis for more information + +env: + - GHCVER=7.4.2 + - GHCVER=7.6.3 + - GHCVER=7.8.2 + +before_install: + - sudo add-apt-repository -y ppa:hvr/ghc + - sudo apt-get update + - sudo apt-get install cabal-install-1.20 ghc-$GHCVER + - export PATH=/opt/ghc/$GHCVER/bin:$PATH + +install: + - cabal-1.20 update +# can't use "cabal install --only-dependencies --enable-tests --enable-benchmarks" due to dep-cycle + - cabal-1.20 install criterion deepseq mtl "QuickCheck >= 2.7.3" HUnit "test-framework-quickcheck2 >= 0.3" "random >= 1.0.1.0" attoparsec cereal -j + +script: + - cabal-1.20 configure --enable-tests --enable-benchmarks -v2 + - cabal-1.20 build + - cabal-1.20 test +# "cabal check" disabled due to -O2 warning +# - cabal-1.20 check + - cabal-1.20 sdist +# check that the generated source-distribution can be built & installed + - export SRC_TGZ=$(cabal-1.20 info . | awk '{print $2 ".tar.gz";exit}') ; + cd dist/; + if [ -f "$SRC_TGZ" ]; then + cabal-1.20 install "$SRC_TGZ"; + else + echo "expected '$SRC_TGZ' not found"; + exit 1; + fi From git at git.haskell.org Sun Dec 14 17:55:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:03 +0000 (UTC) Subject: [commit: packages/binary] master: Link to contributors. (448d24e) Message-ID: <20141214175503.8B3F63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/448d24edf4aeab423034f3c3eff765f48afdd9c4 >--------------------------------------------------------------- commit 448d24edf4aeab423034f3c3eff765f48afdd9c4 Author: Lennart Kolmodin Date: Sun May 11 15:24:42 2014 +0400 Link to contributors. >--------------------------------------------------------------- 448d24edf4aeab423034f3c3eff765f48afdd9c4 README.md | 3 +++ 1 file changed, 3 insertions(+) diff --git a/README.md b/README.md index 0d6f294..7ff84c3 100644 --- a/README.md +++ b/README.md @@ -106,3 +106,6 @@ provided in tools/derive. Here's an example of its use. * Bryan O'Sullivan * Bas van Dijk * Florian Weimer + +For a full list of contributors, see +[here](https://github.com/kolmodin/binary/graphs/contributors). From git at git.haskell.org Sun Dec 14 17:55:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:05 +0000 (UTC) Subject: [commit: packages/binary] master: Add Travis CI build status image to the README (159e8e2) Message-ID: <20141214175505.927B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/159e8e2553c363796db49033195a87d32c2aa318 >--------------------------------------------------------------- commit 159e8e2553c363796db49033195a87d32c2aa318 Author: Lennart Kolmodin Date: Sun May 11 16:05:28 2014 +0400 Add Travis CI build status image to the README >--------------------------------------------------------------- 159e8e2553c363796db49033195a87d32c2aa318 README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index 7ff84c3..5234835 100644 --- a/README.md +++ b/README.md @@ -1,5 +1,7 @@ # binary package # +[![Build Status](https://api.travis-ci.org/kolmodin/binary.png?branch=master)](http://travis-ci.org/kolmodin/binary) + *Efficient, pure binary serialisation using lazy ByteStrings.* The ``binary`` package provides Data.Binary, containing the Binary class, From git at git.haskell.org Sun Dec 14 17:55:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:07 +0000 (UTC) Subject: [commit: packages/binary] master: Update README's example about deriving instances (cb344c2) Message-ID: <20141214175507.99AF03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/cb344c27889e5cbb42dad36e2c6f1780b3c9cea2 >--------------------------------------------------------------- commit cb344c27889e5cbb42dad36e2c6f1780b3c9cea2 Author: Lennart Kolmodin Date: Sun May 11 16:13:00 2014 +0400 Update README's example about deriving instances Demonstrate how to use GHC's Generics. >--------------------------------------------------------------- cb344c27889e5cbb42dad36e2c6f1780b3c9cea2 README.md | 48 ++++++++++++++---------------------------------- 1 file changed, 14 insertions(+), 34 deletions(-) diff --git a/README.md b/README.md index 5234835..b32d7ff 100644 --- a/README.md +++ b/README.md @@ -54,42 +54,22 @@ the ``Get`` and ``Put`` monads. More information in the haddock documentation. -## Deriving binary instances ## +## Deriving binary instances using GHC's Generic ## -It is possible to mechanically derive new instances of Binary for your -types, if they support the Data and Typeable classes. A script is -provided in tools/derive. Here's an example of its use. +Beginning with GHC 7.2, it is possible to use binary serialization without +writing any instance boilerplate code. - $ cd binary - $ cd tools/derive - - $ ghci -fglasgow-exts BinaryDerive.hs - - *BinaryDerive> :l Example.hs - - *Main> deriveM (undefined :: Exp) - - instance Binary Main.Exp where - put (ExpOr a b) = putWord8 0 >> put a >> put b - put (ExpAnd a b) = putWord8 1 >> put a >> put b - put (ExpEq a b) = putWord8 2 >> put a >> put b - put (ExpNEq a b) = putWord8 3 >> put a >> put b - put (ExpAdd a b) = putWord8 4 >> put a >> put b - put (ExpSub a b) = putWord8 5 >> put a >> put b - put (ExpVar a) = putWord8 6 >> put a - put (ExpInt a) = putWord8 7 >> put a - get = do - tag_ <- getWord8 - case tag_ of - 0 -> get >>= \a -> get >>= \b -> return (ExpOr a b) - 1 -> get >>= \a -> get >>= \b -> return (ExpAnd a b) - 2 -> get >>= \a -> get >>= \b -> return (ExpEq a b) - 3 -> get >>= \a -> get >>= \b -> return (ExpNEq a b) - 4 -> get >>= \a -> get >>= \b -> return (ExpAdd a b) - 5 -> get >>= \a -> get >>= \b -> return (ExpSub a b) - 6 -> get >>= \a -> return (ExpVar a) - 7 -> get >>= \a -> return (ExpInt a) - _ -> fail "no decoding" +```haskell +{-# LANGUAGE DeriveGeneric #-} + +import Data.Binary +import GHC.Generics (Generic) + +data Foo = Foo deriving (Generic) + +-- GHC will automatically fill out the instance +instance Binary Foo +``` ## Contributors ## From git at git.haskell.org Sun Dec 14 17:55:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:09 +0000 (UTC) Subject: [commit: packages/binary] master: Update changelog.md with changes of 0.7.2.0. (ff5971b) Message-ID: <20141214175509.A18293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/ff5971b41d503a713d542080fa4409dac48f5778 >--------------------------------------------------------------- commit ff5971b41d503a713d542080fa4409dac48f5778 Author: Lennart Kolmodin Date: Sun May 11 16:29:40 2014 +0400 Update changelog.md with changes of 0.7.2.0. >--------------------------------------------------------------- ff5971b41d503a713d542080fa4409dac48f5778 changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index 2b1e9cd..b1d2abe 100644 --- a/changelog.md +++ b/changelog.md @@ -2,7 +2,7 @@ binary ====== -binary-HEAD +binary-0.7.2.0 ----------- - Add `isolate :: Int -> Get a -> Get a`. From git at git.haskell.org Sun Dec 14 17:55:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:11 +0000 (UTC) Subject: [commit: packages/binary] master: Improve Travis integration. (0e2d466) Message-ID: <20141214175511.A7C113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/0e2d4660732add5d3fe290b0dc326057dbdf6de8 >--------------------------------------------------------------- commit 0e2d4660732add5d3fe290b0dc326057dbdf6de8 Author: Lennart Kolmodin Date: Sun May 11 21:46:21 2014 +0400 Improve Travis integration. >--------------------------------------------------------------- 0e2d4660732add5d3fe290b0dc326057dbdf6de8 .travis.yml | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/.travis.yml b/.travis.yml index eb4be6f..23870bf 100644 --- a/.travis.yml +++ b/.travis.yml @@ -14,6 +14,7 @@ before_install: install: - cabal-1.20 update + - cabal-1.20 sandbox init # can't use "cabal install --only-dependencies --enable-tests --enable-benchmarks" due to dep-cycle - cabal-1.20 install criterion deepseq mtl "QuickCheck >= 2.7.3" HUnit "test-framework-quickcheck2 >= 0.3" "random >= 1.0.1.0" attoparsec cereal -j @@ -27,9 +28,14 @@ script: # check that the generated source-distribution can be built & installed - export SRC_TGZ=$(cabal-1.20 info . | awk '{print $2 ".tar.gz";exit}') ; cd dist/; + cabal-1.20 sandbox init; if [ -f "$SRC_TGZ" ]; then cabal-1.20 install "$SRC_TGZ"; else echo "expected '$SRC_TGZ' not found"; exit 1; fi + +notifications: + email: + - kolmodin at gmail.com From git at git.haskell.org Sun Dec 14 17:55:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:13 +0000 (UTC) Subject: [commit: packages/binary] master: Fix to compile with GHC 6.10.4 (d4568ca) Message-ID: <20141214175513.AFF123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/d4568cae23e31e8d222de843f5f6f269983b92ba >--------------------------------------------------------------- commit d4568cae23e31e8d222de843f5f6f269983b92ba Author: Lennart Kolmodin Date: Sun May 18 12:58:33 2014 +0400 Fix to compile with GHC 6.10.4 Before base-4.2.0.0 Alternative didn't define 'many' and 'some'. Use conditional to exclude those definitions on GHC < 6.12.1. This issue was reported in issue #55. >--------------------------------------------------------------- d4568cae23e31e8d222de843f5f6f269983b92ba src/Data/Binary/Get/Internal.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs index 03305ea..9b53831 100644 --- a/src/Data/Binary/Get/Internal.hs +++ b/src/Data/Binary/Get/Internal.hs @@ -248,12 +248,14 @@ instance Alternative Get where Done inp x -> C $ \_ ks -> ks inp x Fail _ _ -> pushBack bs >> g _ -> error "Binary: impossible" +#if MIN_VERSION_base(4,2,0) some p = (:) <$> p <*> many p many p = do v <- (Just <$> p) <|> pure Nothing case v of Nothing -> pure [] Just x -> (:) x <$> many p +#endif -- | Run a decoder and keep track of all the input it consumes. -- Once it's finished, return the final decoder (always 'Done' or 'Fail'), From git at git.haskell.org Sun Dec 14 17:55:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:15 +0000 (UTC) Subject: [commit: packages/binary] master: Bump version to 0.7.2.1. (94718e3) Message-ID: <20141214175515.B67F73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/94718e3615fd370b0cad498939f215a2ac7548e9 >--------------------------------------------------------------- commit 94718e3615fd370b0cad498939f215a2ac7548e9 Author: Lennart Kolmodin Date: Sun May 18 13:04:06 2014 +0400 Bump version to 0.7.2.1. Also update changelog. >--------------------------------------------------------------- 94718e3615fd370b0cad498939f215a2ac7548e9 binary.cabal | 2 +- changelog.md | 6 +++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/binary.cabal b/binary.cabal index 6995ac9..9b0888c 100644 --- a/binary.cabal +++ b/binary.cabal @@ -1,5 +1,5 @@ name: binary -version: 0.7.2.0 +version: 0.7.2.1 license: BSD3 license-file: LICENSE author: Lennart Kolmodin diff --git a/changelog.md b/changelog.md index b1d2abe..5320922 100644 --- a/changelog.md +++ b/changelog.md @@ -1,9 +1,13 @@ binary ====== +binary-0.7.2.1 +-------------- + +- Fix to compile on GHC 6.10.4 and older, see issue #55. binary-0.7.2.0 ------------ +-------------- - Add `isolate :: Int -> Get a -> Get a`. - Add `label :: String -> Get a -> Get a`. From git at git.haskell.org Sun Dec 14 17:55:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:17 +0000 (UTC) Subject: [commit: packages/binary] master: Simplify the shrinking of Action in QC tests. (2afa267) Message-ID: <20141214175517.BE3173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/2afa267edd0ce894fc4cd079d3e38ac806126dd7 >--------------------------------------------------------------- commit 2afa267edd0ce894fc4cd079d3e38ac806126dd7 Author: Lennart Kolmodin Date: Thu Jul 17 15:10:43 2014 +0400 Simplify the shrinking of Action in QC tests. >--------------------------------------------------------------- 2afa267edd0ce894fc4cd079d3e38ac806126dd7 tests/Action.hs | 27 +++++++++++---------------- 1 file changed, 11 insertions(+), 16 deletions(-) diff --git a/tests/Action.hs b/tests/Action.hs index a849269..bfd69f6 100644 --- a/tests/Action.hs +++ b/tests/Action.hs @@ -42,24 +42,19 @@ instance Arbitrary Action where Actions as -> [ Actions as' | as' <- shrink as ] BytesRead -> [] Fail -> [] - GetByteString n -> [ GetByteString n' | n' <- shrink n, n >= 0 ] - Isolate 0 as -> [ Isolate 0 as' | as' <- shrink as ] - Isolate 1 as -> [ Isolate 0 as' | as' <- shrink as ] - Isolate n0 as -> nub $ - let ns as' = filter (>=0) $ (n0 - 1) : [ 0 .. max_len as' + 1 ] - in Actions as : [ Isolate n' as' - | as' <- [] : shrink as - , n' <- ns as' ] - Label str a -> Actions a : [ Label str a' | a' <- [] : shrink a, a /= []] - LookAhead a -> Actions a : [ LookAhead a' | a' <- [] : shrink a, a /= []] - LookAheadM b a -> Actions a : [ LookAheadM b a' | a' <- [] : shrink a, a /= []] - LookAheadE b a -> Actions a : [ LookAheadE b a' | a' <- [] : shrink a, a /= []] - Try [Fail] b -> Actions b : [ Try [Fail] b' | b' <- [] : shrink b ] + GetByteString n -> [ GetByteString n' | n' <- shrink n ] + Isolate n as -> nub $ Actions as : + [ Isolate n' as' | (n',as') <- shrink (n,as) + , n' >= 0 + , n' <= max_len as' + 1 ] + Label str a -> Actions a : [ Label str a' | a' <- shrink a ] + LookAhead a -> Actions a : [ LookAhead a' | a' <- shrink a ] + LookAheadM b a -> Actions a : [ LookAheadM b a' | a' <- shrink a ] + LookAheadE b a -> Actions a : [ LookAheadE b a' | a' <- shrink a ] + Try [Fail] b -> Actions b : [ Try [Fail] b' | b' <- shrink b ] Try a b -> [Actions a | not (willFail' a)] - ++ [ Try a' b' | a' <- [] : shrink a, b' <- [] : shrink b ] - ++ [ Try a' b | a' <- [] : shrink a ] - ++ [ Try a b' | b' <- [] : shrink b ] + ++ [ Try a' b' | (a',b') <- shrink (a,b) ] willFail :: Int -> [Action] -> Bool willFail inp xxs = From git at git.haskell.org Sun Dec 14 17:55:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:19 +0000 (UTC) Subject: [commit: packages/binary] master: Use explicit import-list for `GHC.Base` import (37daf32) Message-ID: <20141214175519.C66063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/37daf32fbd3b9882b83aef07e0f4177a29d7a71e >--------------------------------------------------------------- commit 37daf32fbd3b9882b83aef07e0f4177a29d7a71e Author: Herbert Valerio Riedel Date: Wed Sep 17 22:48:38 2014 +0200 Use explicit import-list for `GHC.Base` import `base` is currently being restructured in GHC HEAD which will very likely break this unqualified `GHC.Base` import. So this simple change will make that import statement future-proof. >--------------------------------------------------------------- 37daf32fbd3b9882b83aef07e0f4177a29d7a71e src/Data/Binary/Builder/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Data/Binary/Builder/Base.hs b/src/Data/Binary/Builder/Base.hs index 6dd5b75..897aa2b 100644 --- a/src/Data/Binary/Builder/Base.hs +++ b/src/Data/Binary/Builder/Base.hs @@ -81,7 +81,7 @@ import qualified Data.ByteString.Lazy.Internal as L #endif #if defined(__GLASGOW_HASKELL__) && !defined(__HADDOCK__) -import GHC.Base +import GHC.Base (ord,Int(..),uncheckedShiftRL#) import GHC.Word (Word32(..),Word16(..),Word64(..)) # if WORD_SIZE_IN_BITS < 64 import GHC.Word (uncheckedShiftRL64#) From git at git.haskell.org Sun Dec 14 17:55:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:21 +0000 (UTC) Subject: [commit: packages/binary] master: Fix compilation issue with criterion-1. (0508d4a) Message-ID: <20141214175521.CCDBE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/0508d4af712ee05166dfb60a24476c68e96ec1b2 >--------------------------------------------------------------- commit 0508d4af712ee05166dfb60a24476c68e96ec1b2 Author: Lennart Kolmodin Date: Thu Sep 25 15:49:53 2014 +0400 Fix compilation issue with criterion-1. >--------------------------------------------------------------- 0508d4af712ee05166dfb60a24476c68e96ec1b2 benchmarks/Builder.hs | 1 - benchmarks/Get.hs | 1 - binary.cabal | 4 ++-- 3 files changed, 2 insertions(+), 4 deletions(-) diff --git a/benchmarks/Builder.hs b/benchmarks/Builder.hs index bc5eff6..08c6d46 100644 --- a/benchmarks/Builder.hs +++ b/benchmarks/Builder.hs @@ -9,7 +9,6 @@ module Main (main) where import Control.DeepSeq import Control.Exception (evaluate) import Control.Monad.Trans (liftIO) -import Criterion.Config import Criterion.Main hiding (run) import qualified Data.ByteString as S import qualified Data.ByteString.Char8 as C diff --git a/benchmarks/Get.hs b/benchmarks/Get.hs index 57616c9..cb3ca51 100644 --- a/benchmarks/Get.hs +++ b/benchmarks/Get.hs @@ -9,7 +9,6 @@ module Main where import Control.DeepSeq import Control.Exception (evaluate) import Control.Monad.Trans (liftIO) -import Criterion.Config import Criterion.Main hiding (run) import qualified Data.ByteString as S import qualified Data.ByteString.Char8 as C8 diff --git a/binary.cabal b/binary.cabal index 9b0888c..ccce933 100644 --- a/binary.cabal +++ b/binary.cabal @@ -116,7 +116,7 @@ benchmark get base >= 3.0 && < 5, bytestring, cereal, - criterion, + criterion == 1.*, deepseq, mtl -- build dependencies from using binary source rather than depending on the library @@ -130,7 +130,7 @@ benchmark builder build-depends: base >= 3.0 && < 5, bytestring, - criterion, + criterion == 1.*, deepseq, mtl -- build dependencies from using binary source rather than depending on the library From git at git.haskell.org Sun Dec 14 17:55:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:23 +0000 (UTC) Subject: [commit: packages/binary] master: In Travis CI, ghc 7.8.2 -> 7.8.3. (2b2f61c) Message-ID: <20141214175523.D29E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/2b2f61c164c6efbc1a932cf46d89b8bc92b428a2 >--------------------------------------------------------------- commit 2b2f61c164c6efbc1a932cf46d89b8bc92b428a2 Author: Lennart Kolmodin Date: Thu Sep 25 15:52:41 2014 +0400 In Travis CI, ghc 7.8.2 -> 7.8.3. >--------------------------------------------------------------- 2b2f61c164c6efbc1a932cf46d89b8bc92b428a2 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 23870bf..a7f86f3 100644 --- a/.travis.yml +++ b/.travis.yml @@ -4,7 +4,7 @@ env: - GHCVER=7.4.2 - GHCVER=7.6.3 - - GHCVER=7.8.2 + - GHCVER=7.8.3 before_install: - sudo add-apt-repository -y ppa:hvr/ghc From git at git.haskell.org Sun Dec 14 17:55:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:25 +0000 (UTC) Subject: [commit: packages/binary] master: GHC < 7.6 fails when hiding a function that doesn't exists. (b545d19) Message-ID: <20141214175525.DA8853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/b545d190f5dad175dbdfe1a4131641f36c784b96 >--------------------------------------------------------------- commit b545d190f5dad175dbdfe1a4131641f36c784b96 Author: Lennart Kolmodin Date: Thu Sep 25 16:17:29 2014 +0400 GHC < 7.6 fails when hiding a function that doesn't exists. >--------------------------------------------------------------- b545d190f5dad175dbdfe1a4131641f36c784b96 benchmarks/Builder.hs | 2 +- benchmarks/Get.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/benchmarks/Builder.hs b/benchmarks/Builder.hs index 08c6d46..151d282 100644 --- a/benchmarks/Builder.hs +++ b/benchmarks/Builder.hs @@ -9,7 +9,7 @@ module Main (main) where import Control.DeepSeq import Control.Exception (evaluate) import Control.Monad.Trans (liftIO) -import Criterion.Main hiding (run) +import Criterion.Main import qualified Data.ByteString as S import qualified Data.ByteString.Char8 as C import qualified Data.ByteString.Lazy as L diff --git a/benchmarks/Get.hs b/benchmarks/Get.hs index cb3ca51..fd18acf 100644 --- a/benchmarks/Get.hs +++ b/benchmarks/Get.hs @@ -9,7 +9,7 @@ module Main where import Control.DeepSeq import Control.Exception (evaluate) import Control.Monad.Trans (liftIO) -import Criterion.Main hiding (run) +import Criterion.Main import qualified Data.ByteString as S import qualified Data.ByteString.Char8 as C8 import qualified Data.ByteString.Lazy as L From git at git.haskell.org Sun Dec 14 17:55:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:27 +0000 (UTC) Subject: [commit: packages/binary] master: Conditionally instantiate NFData depending on bytestring version. (036b34f) Message-ID: <20141214175527.E11EA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/036b34f0ec8cac8c1284eb2031ebac8835a0775b >--------------------------------------------------------------- commit 036b34f0ec8cac8c1284eb2031ebac8835a0775b Author: Lennart Kolmodin Date: Thu Sep 25 17:21:26 2014 +0400 Conditionally instantiate NFData depending on bytestring version. Should fix #61. >--------------------------------------------------------------- 036b34f0ec8cac8c1284eb2031ebac8835a0775b benchmarks/Builder.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/benchmarks/Builder.hs b/benchmarks/Builder.hs index 151d282..042b371 100644 --- a/benchmarks/Builder.hs +++ b/benchmarks/Builder.hs @@ -19,8 +19,10 @@ import Data.Word (Word8) import Data.Binary.Builder -#if __GLASGOW_HASKELL__ < 706 +#if !MIN_VERSION_bytestring(0,10,0) instance NFData S.ByteString +instance NFData L.ByteString where + rnf = rnf . L.toChunks #endif main :: IO () From git at git.haskell.org Sun Dec 14 17:55:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:29 +0000 (UTC) Subject: [commit: packages/binary] master: Add -fno-spec-constr when building on Travis CI. (8287e4d) Message-ID: <20141214175529.E82EE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/8287e4dbaf6a7109735ca659047e9c2e08bc2aa3 >--------------------------------------------------------------- commit 8287e4dbaf6a7109735ca659047e9c2e08bc2aa3 Author: Lennart Kolmodin Date: Thu Sep 25 20:47:03 2014 +0400 Add -fno-spec-constr when building on Travis CI. It should save a lot of memory, and hopefully make the builds succeed more often. >--------------------------------------------------------------- 8287e4dbaf6a7109735ca659047e9c2e08bc2aa3 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index a7f86f3..2c4c95a 100644 --- a/.travis.yml +++ b/.travis.yml @@ -19,7 +19,7 @@ install: - cabal-1.20 install criterion deepseq mtl "QuickCheck >= 2.7.3" HUnit "test-framework-quickcheck2 >= 0.3" "random >= 1.0.1.0" attoparsec cereal -j script: - - cabal-1.20 configure --enable-tests --enable-benchmarks -v2 + - cabal-1.20 configure --enable-tests --enable-benchmarks -v2 --ghc-options=-fno-spec-constr - cabal-1.20 build - cabal-1.20 test # "cabal check" disabled due to -O2 warning From git at git.haskell.org Sun Dec 14 17:55:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:31 +0000 (UTC) Subject: [commit: packages/binary] master: Merge pull request #59 from hvr/pr-ghc-base (2fa8b1f) Message-ID: <20141214175531.EFB273A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/2fa8b1fd263b074d41cbce235c70ee73a94ae2c8 >--------------------------------------------------------------- commit 2fa8b1fd263b074d41cbce235c70ee73a94ae2c8 Merge: 8287e4d 37daf32 Author: Lennart Kolmodin Date: Thu Sep 25 22:46:18 2014 +0400 Merge pull request #59 from hvr/pr-ghc-base Use explicit import-list for `GHC.Base` import >--------------------------------------------------------------- 2fa8b1fd263b074d41cbce235c70ee73a94ae2c8 src/Data/Binary/Builder/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Sun Dec 14 17:55:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:34 +0000 (UTC) Subject: [commit: packages/binary] master: Bump version to 0.7.2.2. (169c71f) Message-ID: <20141214175534.01D0D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/169c71fb57f1b0088a29d2df99c70381666fcce8 >--------------------------------------------------------------- commit 169c71fb57f1b0088a29d2df99c70381666fcce8 Author: Lennart Kolmodin Date: Thu Sep 25 23:06:34 2014 +0400 Bump version to 0.7.2.2. >--------------------------------------------------------------- 169c71fb57f1b0088a29d2df99c70381666fcce8 binary.cabal | 2 +- changelog.md | 7 ++++++- 2 files changed, 7 insertions(+), 2 deletions(-) diff --git a/binary.cabal b/binary.cabal index ccce933..06aeb35 100644 --- a/binary.cabal +++ b/binary.cabal @@ -1,5 +1,5 @@ name: binary -version: 0.7.2.1 +version: 0.7.2.2 license: BSD3 license-file: LICENSE author: Lennart Kolmodin diff --git a/changelog.md b/changelog.md index 5320922..69dccf5 100644 --- a/changelog.md +++ b/changelog.md @@ -1,10 +1,15 @@ binary ====== +binary-0.7.2.2 +-------------- + +- Make import of GHC.Base future-proof (https://github.com/kolmodin/binary/pull/59). + binary-0.7.2.1 -------------- -- Fix to compile on GHC 6.10.4 and older, see issue #55. +- Fix to compile on GHC 6.10.4 and older (https://github.com/kolmodin/binary/issues/55). binary-0.7.2.0 -------------- From git at git.haskell.org Sun Dec 14 17:55:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:36 +0000 (UTC) Subject: [commit: packages/binary] master: Remove INLINEs from GBinary/GSum methods (48c0296) Message-ID: <20141214175536.07D283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/48c02966512a67b018fcdf093fab8d34bddf9a69 >--------------------------------------------------------------- commit 48c02966512a67b018fcdf093fab8d34bddf9a69 Author: Herbert Valerio Riedel Date: Thu Sep 25 22:07:13 2014 +0200 Remove INLINEs from GBinary/GSum methods These interact very badly with GHC 7.9.x's simplifier See also - https://ghc.haskell.org/trac/ghc/ticket/9630 and - https://ghc.haskell.org/trac/ghc/ticket/9583 >--------------------------------------------------------------- 48c02966512a67b018fcdf093fab8d34bddf9a69 src/Data/Binary/Generic.hs | 6 ------ 1 file changed, 6 deletions(-) diff --git a/src/Data/Binary/Generic.hs b/src/Data/Binary/Generic.hs index 03ce711..a2eb6ea 100644 --- a/src/Data/Binary/Generic.hs +++ b/src/Data/Binary/Generic.hs @@ -72,13 +72,11 @@ instance ( GSum a, GSum b | otherwise = sizeError "encode" size where size = unTagged (sumSize :: Tagged (a :+: b) Word64) - {-# INLINE gput #-} gget | GETSUM(Word8) | GETSUM(Word16) | GETSUM(Word32) | GETSUM(Word64) | otherwise = sizeError "decode" size where size = unTagged (sumSize :: Tagged (a :+: b) Word64) - {-# INLINE gget #-} sizeError :: Show size => String -> size -> error sizeError s size = @@ -102,7 +100,6 @@ instance (GSum a, GSum b, GBinary a, GBinary b) => GSum (a :+: b) where where sizeL = size `shiftR` 1 sizeR = size - sizeL - {-# INLINE getSum #-} putSum !code !size s = case s of L1 x -> putSum code sizeL x @@ -110,14 +107,11 @@ instance (GSum a, GSum b, GBinary a, GBinary b) => GSum (a :+: b) where where sizeL = size `shiftR` 1 sizeR = size - sizeL - {-# INLINE putSum #-} instance GBinary a => GSum (C1 c a) where getSum _ _ = gget - {-# INLINE getSum #-} putSum !code _ x = put code *> gput x - {-# INLINE putSum #-} ------------------------------------------------------------------------ From git at git.haskell.org Sun Dec 14 17:55:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:38 +0000 (UTC) Subject: [commit: packages/binary] master: Merge pull request #62 from hvr/pr-binary (b62c01e) Message-ID: <20141214175538.107FE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/b62c01edd101fc6cfb0e8ff8eefed27ea15a5c28 >--------------------------------------------------------------- commit b62c01edd101fc6cfb0e8ff8eefed27ea15a5c28 Merge: 169c71f 48c0296 Author: Lennart Kolmodin Date: Sun Dec 14 00:13:17 2014 +0300 Merge pull request #62 from hvr/pr-binary Remove INLINEs from GBinary/GSum methods >--------------------------------------------------------------- b62c01edd101fc6cfb0e8ff8eefed27ea15a5c28 src/Data/Binary/Generic.hs | 6 ------ 1 file changed, 6 deletions(-) From git at git.haskell.org Sun Dec 14 17:55:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:40 +0000 (UTC) Subject: [commit: packages/binary] master: Update changelog for 0.7.2.3 (64353af) Message-ID: <20141214175540.16D163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/64353afa6546a88cf0e8dee7457147a1e6933c60 >--------------------------------------------------------------- commit 64353afa6546a88cf0e8dee7457147a1e6933c60 Author: Lennart Kolmodin Date: Sun Dec 14 00:26:48 2014 +0300 Update changelog for 0.7.2.3 >--------------------------------------------------------------- 64353afa6546a88cf0e8dee7457147a1e6933c60 changelog.md | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/changelog.md b/changelog.md index 69dccf5..5d54fec 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,15 @@ binary ====== +binary-0.7.2.3 +-------------- + +- Remove INLINEs from GBinary/GSum methods. These interact very badly with the + GHC 7.9.x simplifier. See also; + - https://github.com/kolmodin/binary/pull/62 + - https://ghc.haskell.org/trac/ghc/ticket/9630 + - https://ghc.haskell.org/trac/ghc/ticket/9583 + binary-0.7.2.2 -------------- From git at git.haskell.org Sun Dec 14 17:55:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 17:55:42 +0000 (UTC) Subject: [commit: packages/binary] master: Bump version to 0.7.2.3 (a3edce4) Message-ID: <20141214175542.1D4433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/a3edce4b95b82388997929424ce98b1d7a75350d >--------------------------------------------------------------- commit a3edce4b95b82388997929424ce98b1d7a75350d Author: Lennart Kolmodin Date: Sun Dec 14 00:27:45 2014 +0300 Bump version to 0.7.2.3 >--------------------------------------------------------------- a3edce4b95b82388997929424ce98b1d7a75350d binary.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/binary.cabal b/binary.cabal index 06aeb35..cf3ed2e 100644 --- a/binary.cabal +++ b/binary.cabal @@ -1,5 +1,5 @@ name: binary -version: 0.7.2.2 +version: 0.7.2.3 license: BSD3 license-file: LICENSE author: Lennart Kolmodin From git at git.haskell.org Sun Dec 14 18:48:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 18:48:50 +0000 (UTC) Subject: [commit: ghc] master: Update `time` submodule to final 1.5.0.1 release (8dc7549) Message-ID: <20141214184850.4CA7E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8dc75498b4f5dfbe454b04f324feab4ae613e475/ghc >--------------------------------------------------------------- commit 8dc75498b4f5dfbe454b04f324feab4ae613e475 Author: Herbert Valerio Riedel Date: Sun Dec 14 10:58:26 2014 +0100 Update `time` submodule to final 1.5.0.1 release >--------------------------------------------------------------- 8dc75498b4f5dfbe454b04f324feab4ae613e475 libraries/time | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/time b/libraries/time index ab6475c..8d3c90a 160000 --- a/libraries/time +++ b/libraries/time @@ -1 +1 @@ -Subproject commit ab6475cb94260f4303afbbd4b770cbd14ec2f57e +Subproject commit 8d3c90a420c8985dcc439766c028821cea7dc848 From git at git.haskell.org Sun Dec 14 18:48:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 18:48:52 +0000 (UTC) Subject: [commit: ghc] master: Update `filepath` submodule to current 1.3.1.0 RC (c7d559d) Message-ID: <20141214184852.E84F63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c7d559d40432cbd5f7e22df64885a435dbcfe2f9/ghc >--------------------------------------------------------------- commit c7d559d40432cbd5f7e22df64885a435dbcfe2f9 Author: Herbert Valerio Riedel Date: Sun Dec 14 14:01:13 2014 +0100 Update `filepath` submodule to current 1.3.1.0 RC >--------------------------------------------------------------- c7d559d40432cbd5f7e22df64885a435dbcfe2f9 libraries/filepath | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/filepath b/libraries/filepath index 83b6d8c..c1a3aec 160000 --- a/libraries/filepath +++ b/libraries/filepath @@ -1 +1 @@ -Subproject commit 83b6d8c555d278f5bb79cef6661d02bc38e72c1e +Subproject commit c1a3aec04cb93315dbc9725139c54d71e5134426 From git at git.haskell.org Sun Dec 14 18:48:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 18:48:55 +0000 (UTC) Subject: [commit: ghc] master: Update `binary` submodule to final 0.7.2.3 release (b037981) Message-ID: <20141214184855.EF3B13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b0379819e46796047c1574a6abccf186afd27afa/ghc >--------------------------------------------------------------- commit b0379819e46796047c1574a6abccf186afd27afa Author: Herbert Valerio Riedel Date: Sun Dec 14 18:59:00 2014 +0100 Update `binary` submodule to final 0.7.2.3 release This also introduces a "bootstrap" `cabal_macros.h` header to provide the `MIN_VERSION_base()` macro during Cabal bootstrapping which as it is now used by `binary`. >--------------------------------------------------------------- b0379819e46796047c1574a6abccf186afd27afa libraries/binary | 2 +- utils/ghc-cabal/cabal_macros_boot.h | 21 +++++++++++++++++++++ utils/ghc-cabal/ghc.mk | 1 + 3 files changed, 23 insertions(+), 1 deletion(-) diff --git a/libraries/binary b/libraries/binary index 03adb0a..a3edce4 160000 --- a/libraries/binary +++ b/libraries/binary @@ -1 +1 @@ -Subproject commit 03adb0aa2c17ce044586e3a30edc13e5cc83f69e +Subproject commit a3edce4b95b82388997929424ce98b1d7a75350d diff --git a/utils/ghc-cabal/cabal_macros_boot.h b/utils/ghc-cabal/cabal_macros_boot.h new file mode 100644 index 0000000..41cddb1 --- /dev/null +++ b/utils/ghc-cabal/cabal_macros_boot.h @@ -0,0 +1,21 @@ +/* defines a few MIN_VERSION_...() macros used by some of the bootstrap packages */ + +#if __GLASGOW_HASKELL__ >= 709 +/* package base-4.8.0.0 */ +# define MIN_VERSION_base(major1,major2,minor) (\ + (major1) < 4 || \ + (major1) == 4 && (major2) < 8 || \ + (major1) == 4 && (major2) == 8 && (minor) <= 0) +#elif __GLASGOW_HASKELL__ >= 707 +/* package base-4.7.0 */ +# define MIN_VERSION_base(major1,major2,minor) (\ + (major1) < 4 || \ + (major1) == 4 && (major2) < 7 || \ + (major1) == 4 && (major2) == 7 && (minor) <= 0) +#elif __GLASGOW_HASKELL__ >= 705 +/* package base-4.6.0 */ +# define MIN_VERSION_base(major1,major2,minor) (\ + (major1) < 4 || \ + (major1) == 4 && (major2) < 6 || \ + (major1) == 4 && (major2) == 6 && (minor) <= 0) +#endif diff --git a/utils/ghc-cabal/ghc.mk b/utils/ghc-cabal/ghc.mk index b8d54ab..3ac864f 100644 --- a/utils/ghc-cabal/ghc.mk +++ b/utils/ghc-cabal/ghc.mk @@ -39,6 +39,7 @@ $(ghc-cabal_DIST_BINARY): utils/ghc-cabal/Main.hs $(TOUCH_DEP) | $$(dir $$@)/. b -Wall -fno-warn-unused-imports -fno-warn-warnings-deprecations \ -DCABAL_VERSION=$(CABAL_VERSION) \ -DBOOTSTRAPPING \ + -optP-include -optPutils/ghc-cabal/cabal_macros_boot.h \ -odir bootstrapping \ -hidir bootstrapping \ -ilibraries/Cabal/Cabal \ From git at git.haskell.org Sun Dec 14 19:37:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 19:37:28 +0000 (UTC) Subject: [commit: ghc] master: Fixup bad haddock.base perf-num bump in 0c9c2d89 (87c4e18) Message-ID: <20141214193728.12BFB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/87c4e183d083c7a18090afa562710717a6faea2a/ghc >--------------------------------------------------------------- commit 87c4e183d083c7a18090afa562710717a6faea2a Author: Herbert Valerio Riedel Date: Sun Dec 14 20:35:12 2014 +0100 Fixup bad haddock.base perf-num bump in 0c9c2d89 >--------------------------------------------------------------- 87c4e183d083c7a18090afa562710717a6faea2a testsuite/tests/perf/haddock/all.T | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index d7162f5..e4a8d88 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), 9503888920, 5) + [(wordsize(64), 8792433208, 5) # 2012-08-14: 5920822352 (amd64/Linux) # 2012-09-20: 5829972376 (amd64/Linux) # 2012-10-08: 5902601224 (amd64/Linux) @@ -21,7 +21,7 @@ test('haddock.base', # 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) - # 2014-12-14: 9503888920 (x86_64/Linux) - Update to Haddock 2.16 + # 2014-12-14: 8792433208 (x86_64/Linux) - Update to Haddock 2.16 ,(platform('i386-unknown-mingw32'), 4202377432, 5) # 2013-02-10: 3358693084 (x86/Windows) # 2013-11-13: 3097751052 (x86/Windows, 64bit machine) From git at git.haskell.org Sun Dec 14 19:37:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Dec 2014 19:37:30 +0000 (UTC) Subject: [commit: ghc] master: Update `bytestring` submodule to 0.10.6.0 RC (71105ae) Message-ID: <20141214193730.B08033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/71105aea894d9c39c35248865907207e169f819d/ghc >--------------------------------------------------------------- commit 71105aea894d9c39c35248865907207e169f819d Author: Herbert Valerio Riedel Date: Sun Dec 14 20:36:33 2014 +0100 Update `bytestring` submodule to 0.10.6.0 RC NB: this still carries the wrong version number 0.10.5.0 but will be released as 0.10.6.0 >--------------------------------------------------------------- 71105aea894d9c39c35248865907207e169f819d libraries/bytestring | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/bytestring b/libraries/bytestring index 7a7602a..cb85a53 160000 --- a/libraries/bytestring +++ b/libraries/bytestring @@ -1 +1 @@ -Subproject commit 7a7602a142a1deae2e4f73782d88a91f39a0fa98 +Subproject commit cb85a5360bc540c88b3ae1886d07c741bec3cdaa From git at git.haskell.org Mon Dec 15 10:06:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 10:06:03 +0000 (UTC) Subject: [commit: ghc] master: Pattern-synonym matcher and builder Ids must be *LocalIds* (fbb42b2) Message-ID: <20141215100603.BFDD03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fbb42b2ea42b6467135f26db47d9c296e7ad75a3/ghc >--------------------------------------------------------------- commit fbb42b2ea42b6467135f26db47d9c296e7ad75a3 Author: Simon Peyton Jones Date: Sat Dec 13 22:47:01 2014 +0000 Pattern-synonym matcher and builder Ids must be *LocalIds* This easy-to-make mistake meant that pattern-synonym matcher and builder Ids weren't being treated as locally defined by the simpplier. That meant that we never looked up them up in the environment, got an out-of-date unfolding, which made the Simplifier fall into an infinite loop. This was the cause of Trac #98587, but it was quite tricky to find! In a separate patch I'll make Lint check for locally-bound GlobalIds, since they are always an error. >--------------------------------------------------------------- fbb42b2ea42b6467135f26db47d9c296e7ad75a3 compiler/basicTypes/Id.hs | 5 +- compiler/typecheck/TcPatSyn.hs | 7 +- testsuite/tests/patsyn/should_compile/T9857.hs | 162 +++++++++++++++++++++++++ testsuite/tests/patsyn/should_compile/all.T | 1 + 4 files changed, 172 insertions(+), 3 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fbb42b2ea42b6467135f26db47d9c296e7ad75a3 From git at git.haskell.org Mon Dec 15 10:06:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 10:06:06 +0000 (UTC) Subject: [commit: ghc] master: Make Core Lint check for locally-bound GlobalIds (d59c59f) Message-ID: <20141215100606.712B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d59c59f4d106a5d0dff0ecb164f7a669bee03c13/ghc >--------------------------------------------------------------- commit d59c59f4d106a5d0dff0ecb164f7a669bee03c13 Author: Simon Peyton Jones Date: Sat Dec 13 22:53:54 2014 +0000 Make Core Lint check for locally-bound GlobalIds There should be no bindings in this module for a GlobalId; except after CoreTidy, when top-level bindings are globalised. To check for this, I had to make the CoreToDo pass part of the environment that Core Lint caries. But CoreToDo is defined in CoreMonad, which (before this patch) called CoreLint. So I had to do quite a bit of refactoring, moving some lint-invoking code into CoreLint itself. Crucially, I also more tcLookupImported_maybe, importDecl, and checkwiredInTyCon from TcIface (which use CoreLint) to LoadIface (which doesn't). This is probably better structure anyway. So most of this patch is refactoring. The actual check for GlobalIds is in CoreLint.lintAndScopeId >--------------------------------------------------------------- d59c59f4d106a5d0dff0ecb164f7a669bee03c13 compiler/coreSyn/CoreLint.hs | 358 ++++++++++++++++++++++++++++++++++------ compiler/coreSyn/CorePrep.hs | 3 +- compiler/deSugar/Desugar.hs | 3 +- compiler/iface/LoadIface.hs | 156 +++++++++++++++++ compiler/iface/TcIface.hs | 149 ----------------- compiler/main/HscMain.hs | 2 +- compiler/main/TidyPgm.hs | 7 +- compiler/simplCore/CoreMonad.hs | 205 ----------------------- compiler/simplCore/SimplCore.hs | 1 + compiler/typecheck/TcEnv.hs | 2 +- 10 files changed, 470 insertions(+), 416 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d59c59f4d106a5d0dff0ecb164f7a669bee03c13 From git at git.haskell.org Mon Dec 15 13:17:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 13:17:11 +0000 (UTC) Subject: [commit: packages/haskeline] master: Fix TODO: messageState param not needed anymore (e18a11f) Message-ID: <20141215131711.6F7AC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/e18a11fa2a23f34b40ee5b661932da6fdd990f3f >--------------------------------------------------------------- commit e18a11fa2a23f34b40ee5b661932da6fdd990f3f Author: Philip Dexter Date: Sat Sep 27 11:46:22 2014 -0400 Fix TODO: messageState param not needed anymore >--------------------------------------------------------------- e18a11fa2a23f34b40ee5b661932da6fdd990f3f System/Console/Haskeline/Command/Completion.hs | 4 ++-- System/Console/Haskeline/LineState.hs | 5 ++--- 2 files changed, 4 insertions(+), 5 deletions(-) diff --git a/System/Console/Haskeline/Command/Completion.hs b/System/Console/Haskeline/Command/Completion.hs index 2f42b2b..97a887b 100644 --- a/System/Console/Haskeline/Command/Completion.hs +++ b/System/Console/Haskeline/Command/Completion.hs @@ -85,7 +85,7 @@ askFirst :: Monad m => Prefs -> Int -> CmdM m () -> CmdM m () askFirst prefs n cmd | maybe False (< n) (completionPromptLimit prefs) = do - _ <- setState (Message () $ "Display all " ++ show n + _ <- setState (Message $ "Display all " ++ show n ++ " possibilities? (y or n)") keyChoiceCmdM [ simpleChar 'y' +> cmd @@ -96,7 +96,7 @@ askFirst prefs n cmd pageCompletions :: MonadReader Layout m => [String] -> CmdM m () pageCompletions [] = return () pageCompletions wws@(w:ws) = do - _ <- setState $ Message () "----More----" + _ <- setState $ Message "----More----" keyChoiceCmdM [ simpleChar '\n' +> oneLine , simpleKey DownKey +> oneLine diff --git a/System/Console/Haskeline/LineState.hs b/System/Console/Haskeline/LineState.hs index 4f15898..79537bf 100644 --- a/System/Console/Haskeline/LineState.hs +++ b/System/Console/Haskeline/LineState.hs @@ -356,10 +356,9 @@ applyCmdArg :: (InsertMode -> InsertMode) -> ArgMode CommandMode -> CommandMode applyCmdArg f am = withCommandMode (repeatN (arg am) f) (argState am) --------------- --- TODO: messageState param not needed anymore. -data Message s = Message {messageState :: s, messageText :: String} +newtype Message = Message {messageText :: String} -instance LineState (Message s) where +instance LineState Message where beforeCursor _ = stringToGraphemes . messageText afterCursor _ = [] From git at git.haskell.org Mon Dec 15 13:17:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 13:17:13 +0000 (UTC) Subject: [commit: packages/haskeline] master: Merge pull request #12 from philipdexter/master (f41a750) Message-ID: <20141215131713.73DAD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/f41a7502a9b8d4a5a39f76716d5bedb5744487ef >--------------------------------------------------------------- commit f41a7502a9b8d4a5a39f76716d5bedb5744487ef Merge: bf1a30f e18a11f Author: Judah Jacobson Date: Sat Sep 27 13:07:53 2014 -0700 Merge pull request #12 from philipdexter/master Fix TODO: messageState param not needed anymore >--------------------------------------------------------------- f41a7502a9b8d4a5a39f76716d5bedb5744487ef System/Console/Haskeline/Command/Completion.hs | 4 ++-- System/Console/Haskeline/LineState.hs | 5 ++--- 2 files changed, 4 insertions(+), 5 deletions(-) From git at git.haskell.org Mon Dec 15 14:54:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 14:54:57 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Link pre-ARMv6 spinlocks into all RTS variants (615d03a) Message-ID: <20141215145457.AB8AD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/615d03a4cab16d7818cf6f64aaa9032514b2b36e/ghc >--------------------------------------------------------------- commit 615d03a4cab16d7818cf6f64aaa9032514b2b36e Author: Joachim Breitner Date: Tue Dec 9 18:18:11 2014 -0600 Link pre-ARMv6 spinlocks into all RTS variants Summary: For compatibility with ARM machines from pre v6, the RTS provides implementations of certain atomic operations. Previously, these were only included in the threaded RTS. But ghc (the library) contains the code in compiler/cbits/genSym.c, which uses these operations if there is more than one capability. But there is only one libHSghc, so the linker wants to resolve these symbols in every case. By providing these operations in all RTSs, the linker is happy. The only downside is a small amount of dead code in the non-threaded RTS on old ARM machines. Test Plan: It helped here. Reviewers: bgamari, austin Reviewed By: bgamari, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D564 GHC Trac Issues: #8951 (cherry picked from commit df1307f079ae69dcd735e0973de987b141d509da) >--------------------------------------------------------------- 615d03a4cab16d7818cf6f64aaa9032514b2b36e includes/stg/SMP.h | 4 ++-- rts/OldARMAtomic.c | 11 ++++++----- 2 files changed, 8 insertions(+), 7 deletions(-) diff --git a/includes/stg/SMP.h b/includes/stg/SMP.h index 01663dd..7e39e5a 100644 --- a/includes/stg/SMP.h +++ b/includes/stg/SMP.h @@ -14,13 +14,13 @@ #ifndef SMP_H #define SMP_H -#if defined(THREADED_RTS) - #if arm_HOST_ARCH && defined(arm_HOST_ARCH_PRE_ARMv6) void arm_atomic_spin_lock(void); void arm_atomic_spin_unlock(void); #endif +#if defined(THREADED_RTS) + /* ---------------------------------------------------------------------------- Atomic operations ------------------------------------------------------------------------- */ diff --git a/rts/OldARMAtomic.c b/rts/OldARMAtomic.c index b2c52fc..1ca635e 100644 --- a/rts/OldARMAtomic.c +++ b/rts/OldARMAtomic.c @@ -5,6 +5,12 @@ * Inefficient but necessary atomic locks used for implementing atomic * operations on ARM architectures pre-ARMv6. * + * These operations are not only referenced in the threaded RTS, but also in + * ghc (the library), via the operations in compiler/cbits/genSym.c. + * They are not actually called in a non-threaded environment, but we still + * need them in every RTS to make the linker happy, hence no + * #if defined(THREADED_RTS) here. See #8951. + * * -------------------------------------------------------------------------- */ #include "PosixSource.h" @@ -14,8 +20,6 @@ #include #endif -#if defined(THREADED_RTS) - #if arm_HOST_ARCH && defined(arm_HOST_ARCH_PRE_ARMv6) static volatile int atomic_spin = 0; @@ -51,6 +55,3 @@ void arm_atomic_spin_unlock() } #endif /* arm_HOST_ARCH && defined(arm_HOST_ARCH_PRE_ARMv6) */ - -#endif /* defined(THREADED_RTS) */ - From git at git.haskell.org Mon Dec 15 14:55:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 14:55:00 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: compiler: fix trac issue #9817 (7be1eb7) Message-ID: <20141215145500.65E823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/7be1eb7d8e3f064e3407795afcebfb76770a3c34/ghc >--------------------------------------------------------------- commit 7be1eb7d8e3f064e3407795afcebfb76770a3c34 Author: Austin Seipp Date: Mon Dec 15 08:44:32 2014 -0600 compiler: fix trac issue #9817 Summary: When we call runHandlers, we must pass it a ForeignPtr. To ensure that this happens, we introduce a wrapper that receives a plain Ptr and converts it into a ForeignPtr. Then we adjust startSignalHandlers in rts/posix/Signals.c to call the wrapper instead of calling runHandlers directly. Reviewers: hvr, austin, rwbarton, simonmar Reviewed By: austin, simonmar Subscribers: simonmar, thomie, carter Differential Revision: https://phabricator.haskell.org/D515 GHC Trac Issues: #9817 (cherry picked from commit 7ca5bb090ff78141fbe275b058a9e35ee496bd58) >--------------------------------------------------------------- 7be1eb7d8e3f064e3407795afcebfb76770a3c34 rts/Prelude.h | 4 ++-- rts/RtsStartup.c | 2 +- rts/package.conf.in | 4 ++-- rts/posix/Signals.c | 2 +- 4 files changed, 6 insertions(+), 6 deletions(-) diff --git a/rts/Prelude.h b/rts/Prelude.h index 89e80a0..5923da2 100644 --- a/rts/Prelude.h +++ b/rts/Prelude.h @@ -46,7 +46,7 @@ PRELUDE_CLOSURE(base_ControlziExceptionziBase_nestedAtomically_closure); PRELUDE_CLOSURE(base_GHCziConcziSync_runSparks_closure); PRELUDE_CLOSURE(base_GHCziConcziIO_ensureIOManagerIsRunning_closure); PRELUDE_CLOSURE(base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure); -PRELUDE_CLOSURE(base_GHCziConcziSignal_runHandlers_closure); +PRELUDE_CLOSURE(base_GHCziConcziSignal_runHandlersPtr_closure); PRELUDE_CLOSURE(base_GHCziTopHandler_flushStdHandles_closure); @@ -94,7 +94,7 @@ PRELUDE_INFO(base_GHCziStable_StablePtr_con_info); #define runSparks_closure DLL_IMPORT_DATA_REF(base_GHCziConcziSync_runSparks_closure) #define ensureIOManagerIsRunning_closure DLL_IMPORT_DATA_REF(base_GHCziConcziIO_ensureIOManagerIsRunning_closure) #define ioManagerCapabilitiesChanged_closure DLL_IMPORT_DATA_REF(base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure) -#define runHandlers_closure DLL_IMPORT_DATA_REF(base_GHCziConcziSignal_runHandlers_closure) +#define runHandlersPtr_closure DLL_IMPORT_DATA_REF(base_GHCziConcziSignal_runHandlersPtr_closure) #define flushStdHandles_closure DLL_IMPORT_DATA_REF(base_GHCziTopHandler_flushStdHandles_closure) diff --git a/rts/RtsStartup.c b/rts/RtsStartup.c index 15e48a6..24d50ee 100644 --- a/rts/RtsStartup.c +++ b/rts/RtsStartup.c @@ -214,7 +214,7 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config) getStablePtr((StgPtr)ensureIOManagerIsRunning_closure); getStablePtr((StgPtr)ioManagerCapabilitiesChanged_closure); #ifndef mingw32_HOST_OS - getStablePtr((StgPtr)runHandlers_closure); + getStablePtr((StgPtr)runHandlersPtr_closure); #endif /* initialise the shared Typeable store */ diff --git a/rts/package.conf.in b/rts/package.conf.in index 4c8686f..a364fd3 100644 --- a/rts/package.conf.in +++ b/rts/package.conf.in @@ -106,7 +106,7 @@ ld-options: , "-Wl,-u,_base_GHCziConcziIO_ensureIOManagerIsRunning_closure" , "-Wl,-u,_base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure" , "-Wl,-u,_base_GHCziConcziSync_runSparks_closure" - , "-Wl,-u,_base_GHCziConcziSignal_runHandlers_closure" + , "-Wl,-u,_base_GHCziConcziSignal_runHandlersPtr_closure" #else "-Wl,-u,ghczmprim_GHCziTypes_Izh_static_info" , "-Wl,-u,ghczmprim_GHCziTypes_Czh_static_info" @@ -146,7 +146,7 @@ ld-options: , "-Wl,-u,base_GHCziConcziIO_ensureIOManagerIsRunning_closure" , "-Wl,-u,base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure" , "-Wl,-u,base_GHCziConcziSync_runSparks_closure" - , "-Wl,-u,base_GHCziConcziSignal_runHandlers_closure" + , "-Wl,-u,base_GHCziConcziSignal_runHandlersPtr_closure" #endif /* Pick up static libraries in preference over dynamic if in earlier search diff --git a/rts/posix/Signals.c b/rts/posix/Signals.c index f4a8341..6ebbfd3 100644 --- a/rts/posix/Signals.c +++ b/rts/posix/Signals.c @@ -448,7 +448,7 @@ startSignalHandlers(Capability *cap) RtsFlags.GcFlags.initialStkSize, rts_apply(cap, rts_apply(cap, - &base_GHCziConcziSignal_runHandlers_closure, + &base_GHCziConcziSignal_runHandlersPtr_closure, rts_mkPtr(cap, info)), rts_mkInt(cap, info->si_signo)))); } From git at git.haskell.org Mon Dec 15 14:55:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 14:55:03 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: cabal: Update to fix notorious '-fPIC' bug (92510cf5) Message-ID: <20141215145503.0DECE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/92510cf5b902bfc66238972fe989fe878577d39a/ghc >--------------------------------------------------------------- commit 92510cf5b902bfc66238972fe989fe878577d39a Author: Austin Seipp Date: Mon Dec 15 08:49:00 2014 -0600 cabal: Update to fix notorious '-fPIC' bug This sentence contains the word 'submodule' because it is a requirement. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 92510cf5b902bfc66238972fe989fe878577d39a libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index c226c0d..5462f48 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit c226c0de042999bbe4c5c339c6c28a9be7f0c6d1 +Subproject commit 5462f486f0ac344b5714382b1a7498ad6d85d085 From git at git.haskell.org Mon Dec 15 14:55:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 14:55:05 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix detection of GNU gold linker if invoked via gcc with parameters (550877a) Message-ID: <20141215145505.C4D433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/550877a8496d57dcab30f7864a84833df5e13d19/ghc >--------------------------------------------------------------- commit 550877a8496d57dcab30f7864a84833df5e13d19 Author: Sebastian Dr?ge Date: Tue Nov 18 12:40:20 2014 -0600 Fix detection of GNU gold linker if invoked via gcc with parameters Previously the linker was called without any commandline parameters to detect whether bfd or gold is used. However the -fuse-ld parameter can be used to switch between gold and bfd and should be taken into account here. Trac #9336 Signed-off-by: Austin Seipp (cherry picked from commit e7b414a3cc0e27049f2608f5e0a00c47146cc46d) >--------------------------------------------------------------- 550877a8496d57dcab30f7864a84833df5e13d19 compiler/main/SysTools.lhs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/main/SysTools.lhs b/compiler/main/SysTools.lhs index cd9b9f5..8c02cc4 100644 --- a/compiler/main/SysTools.lhs +++ b/compiler/main/SysTools.lhs @@ -739,7 +739,10 @@ getLinkerInfo' :: DynFlags -> IO LinkerInfo getLinkerInfo' dflags = do let platform = targetPlatform dflags os = platformOS platform - (pgm,_) = pgm_l dflags + (pgm,args0) = pgm_l dflags + args1 = map Option (getOpts dflags opt_l) + args2 = args0 ++ args1 + args3 = filter notNull (map showOpt args2) -- Try to grab the info from the process output. parseLinkerInfo stdo _stde _exitc @@ -790,7 +793,7 @@ getLinkerInfo' dflags = do -- In practice, we use the compiler as the linker here. Pass -- -Wl,--version to get linker version info. (exitc, stdo, stde) <- readProcessEnvWithExitCode pgm - ["-Wl,--version"] + (["-Wl,--version"] ++ args3) en_locale_env -- Split the output by lines to make certain kinds -- of processing easier. In particular, 'clang' and 'gcc' From git at git.haskell.org Mon Dec 15 14:55:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 14:55:08 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Make libffi install into a predictable directory (#9620) (3b65fb4) Message-ID: <20141215145508.7FF3F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/3b65fb4f440f8e8da14f3285fa41fc06ff5b909a/ghc >--------------------------------------------------------------- commit 3b65fb4f440f8e8da14f3285fa41fc06ff5b909a Author: Reid Barton Date: Sun Sep 21 08:53:37 2014 -0400 Make libffi install into a predictable directory (#9620) On some systems (depending on gcc multilib configuration) libffi would install into libffi/build/inst/lib64 even though we configure it with --libdir=libffi/build/inst/lib. There appears to be no way to get libffi to install to a predictable directory "out of the box", so we apply a small patch to Makefile.in. This is the same fix used in Gentoo's ebuild (https://bugs.gentoo.org/show_bug.cgi?id=462814). (cherry picked from commit 835d874df1973b7e1c602a747b42b77095592a9c) >--------------------------------------------------------------- 3b65fb4f440f8e8da14f3285fa41fc06ff5b909a libffi/ghc.mk | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/libffi/ghc.mk b/libffi/ghc.mk index bc62ad9..4e177d2 100644 --- a/libffi/ghc.mk +++ b/libffi/ghc.mk @@ -69,6 +69,13 @@ $(libffi_STAMP_CONFIGURE): $(TOUCH_DEP) mv libffi/build/Makefile.in libffi/build/Makefile.in.orig sed "s/-MD/-MMD/" < libffi/build/Makefile.in.orig > libffi/build/Makefile.in + # We attempt to specify the installation directory below with --libdir, + # but libffi installs into 'toolexeclibdir' instead, which may differ + # on systems where gcc has multilib support. Force libffi to use libdir. + # (https://sourceware.org/ml/libffi-discuss/2014/msg00016.html) + mv libffi/build/Makefile.in libffi/build/Makefile.in.orig + sed 's:@toolexeclibdir@:$$(libdir):g' < libffi/build/Makefile.in.orig > libffi/build/Makefile.in + # Their cmd invocation only works on msys. On cygwin it starts # a cmd interactive shell. The replacement works in both environments. mv libffi/build/ltmain.sh libffi/build/ltmain.sh.orig From git at git.haskell.org Mon Dec 15 14:55:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 14:55:11 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: fix inconsistency in exported functions from TcSplice.lhs/lhs-boot files when GHCI is not defined (c845391) Message-ID: <20141215145511.37DDD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/c84539177e048c159a0de3be25eba27078d87a20/ghc >--------------------------------------------------------------- commit c84539177e048c159a0de3be25eba27078d87a20 Author: Karel Gardas Date: Fri Jul 18 23:54:52 2014 -0500 fix inconsistency in exported functions from TcSplice.lhs/lhs-boot files when GHCI is not defined Summary: This patch fixes inconsistency in exported functions from TcSplice.lhs and TcSplice.lhs-boot files. It looks like only GHC HEAD is sensitive to it and complains about it while bootstraping another HEAD. At least this is what happening on Solaris/AMD64 builder machine where GHC 7.9.20140620 is used as a boostrap compiler. The failure does not happen on another builders. Test Plan: validate Reviewers: austin Reviewed By: austin Subscribers: phaskell, simonmar, relrod, carter Differential Revision: https://phabricator.haskell.org/D74 (cherry picked from commit d996a1bb4db84727fbf1a8e9461a032e04e544e7) >--------------------------------------------------------------- c84539177e048c159a0de3be25eba27078d87a20 compiler/typecheck/TcSplice.lhs-boot | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcSplice.lhs-boot b/compiler/typecheck/TcSplice.lhs-boot index c496aed..dccc669 100644 --- a/compiler/typecheck/TcSplice.lhs-boot +++ b/compiler/typecheck/TcSplice.lhs-boot @@ -3,7 +3,6 @@ module TcSplice where import HsSyn ( HsSplice, HsBracket, HsQuasiQuote, HsExpr, LHsType, LHsExpr, LPat, LHsDecl ) import HsExpr ( PendingRnSplice ) -import Id ( Id ) import Name ( Name ) import RdrName ( RdrName ) import TcRnTypes( TcM, TcId ) @@ -11,6 +10,7 @@ import TcType ( TcRhoType ) import Annotations ( Annotation, CoreAnnTarget ) #ifdef GHCI +import Id ( Id ) import qualified Language.Haskell.TH as TH #endif @@ -26,20 +26,20 @@ tcTypedBracket :: HsBracket Name -> TcRhoType -> TcM (HsExpr TcId) -tcTopSpliceExpr :: Bool -> TcM (LHsExpr Id) -> TcM (LHsExpr Id) - runQuasiQuoteDecl :: HsQuasiQuote RdrName -> TcM [LHsDecl RdrName] runQuasiQuoteExpr :: HsQuasiQuote RdrName -> TcM (LHsExpr RdrName) runQuasiQuoteType :: HsQuasiQuote RdrName -> TcM (LHsType RdrName) runQuasiQuotePat :: HsQuasiQuote RdrName -> TcM (LPat RdrName) runAnnotation :: CoreAnnTarget -> LHsExpr Name -> TcM Annotation +#ifdef GHCI +tcTopSpliceExpr :: Bool -> TcM (LHsExpr Id) -> TcM (LHsExpr Id) + runMetaE :: LHsExpr Id -> TcM (LHsExpr RdrName) runMetaP :: LHsExpr Id -> TcM (LPat RdrName) runMetaT :: LHsExpr Id -> TcM (LHsType RdrName) runMetaD :: LHsExpr Id -> TcM [LHsDecl RdrName] -#ifdef GHCI lookupThName_maybe :: TH.Name -> TcM (Maybe Name) runQuasi :: TH.Q a -> TcM a #endif From git at git.haskell.org Mon Dec 15 14:55:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 14:55:13 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: ghc.mk: fix list for dll-split on GHCi-less builds (04b3b14) Message-ID: <20141215145513.E836D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/04b3b14c2cab2f7b833a6814de7e3fd6554e7b8a/ghc >--------------------------------------------------------------- commit 04b3b14c2cab2f7b833a6814de7e3fd6554e7b8a 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 (cherry picked from commit 2a8ea4745d6ff79d6ce17961a64d9013243fc3c6) >--------------------------------------------------------------- 04b3b14c2cab2f7b833a6814de7e3fd6554e7b8a compiler/ghc.mk | 90 ++++++++++++++++++++++++++++++--------------------------- 1 file changed, 48 insertions(+), 42 deletions(-) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index 389543f..58b5ab3 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -461,36 +461,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 \ @@ -514,7 +493,6 @@ compiler_stage2_dll0_MODULES = \ Exception \ ExtsCompat46 \ FamInstEnv \ - FastBool \ FastFunctions \ FastMutInt \ FastString \ @@ -524,8 +502,6 @@ compiler_stage2_dll0_MODULES = \ FiniteMap \ ForeignCall \ Hooks \ - Hoopl \ - Hoopl.Dataflow \ HsBinds \ HsDecls \ HsDoc \ @@ -544,14 +520,12 @@ compiler_stage2_dll0_MODULES = \ IfaceSyn \ IfaceType \ InstEnv \ - InteractiveEvalTypes \ Kind \ ListSetOps \ Literal \ LoadIface \ Maybes \ MkCore \ - MkGraph \ MkId \ Module \ MonadUtils \ @@ -571,9 +545,6 @@ compiler_stage2_dll0_MODULES = \ PipelineMonad \ Platform \ PlatformConstants \ - PprCmm \ - PprCmmDecl \ - PprCmmExpr \ PprCore \ PrelInfo \ PrelNames \ @@ -581,23 +552,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 \ @@ -621,6 +579,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 Mon Dec 15 14:55:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 14:55:24 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: Fix base component of #9817 (ghc-7.8 7be1eb7) (c738f99) Message-ID: <20141215145524.51DE33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/c738f9933c64cda99eda6edf0ed2178ba8376f35/base >--------------------------------------------------------------- commit c738f9933c64cda99eda6edf0ed2178ba8376f35 Author: Austin Seipp Date: Mon Dec 15 08:46:00 2014 -0600 Fix base component of #9817 (ghc-7.8 7be1eb7) Signed-off-by: Austin Seipp >--------------------------------------------------------------- c738f9933c64cda99eda6edf0ed2178ba8376f35 GHC/Conc/Signal.hs | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/GHC/Conc/Signal.hs b/GHC/Conc/Signal.hs index 2d70419..4e2c8ee 100644 --- a/GHC/Conc/Signal.hs +++ b/GHC/Conc/Signal.hs @@ -6,16 +6,18 @@ module GHC.Conc.Signal , HandlerFun , setHandler , runHandlers + , runHandlersPtr ) where import Control.Concurrent.MVar (MVar, newMVar, withMVar) import Data.Dynamic (Dynamic) import Data.Maybe (Maybe(..)) import Foreign.C.Types (CInt) -import Foreign.ForeignPtr (ForeignPtr) +import Foreign.ForeignPtr (ForeignPtr, newForeignPtr) import Foreign.StablePtr (castPtrToStablePtr, castStablePtrToPtr, deRefStablePtr, freeStablePtr, newStablePtr) import Foreign.Ptr (Ptr, castPtr) +import Foreign.Marshal.Alloc (finalizerFree) import GHC.Arr (inRange) import GHC.Base import GHC.Conc.Sync (forkIO) @@ -71,6 +73,13 @@ runHandlers p_info sig = do Just (f,_) -> do _ <- forkIO (f p_info) return () +-- It is our responsibility to free the memory buffer, so we create a +-- foreignPtr. +runHandlersPtr :: Ptr Word8 -> Signal -> IO () +runHandlersPtr p s = do + fp <- newForeignPtr finalizerFree p + runHandlers fp s + -- Machinery needed to ensure that we only have one copy of certain -- CAFs in this module even when the base package is present twice, as -- it is when base is dynamically loaded into GHCi. The RTS keeps From git at git.haskell.org Mon Dec 15 14:55:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 14:55:26 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: Fix typo (f2b441d) Message-ID: <20141215145526.5C6403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/f2b441d6671cd619bd6a3843b8499f5cd958a509/base >--------------------------------------------------------------- commit f2b441d6671cd619bd6a3843b8499f5cd958a509 Author: Austin Seipp Date: Mon Dec 15 08:53:52 2014 -0600 Fix typo Signed-off-by: Austin Seipp >--------------------------------------------------------------- f2b441d6671cd619bd6a3843b8499f5cd958a509 GHC/Generics.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/GHC/Generics.hs b/GHC/Generics.hs index 1c81858..594b631 100644 --- a/GHC/Generics.hs +++ b/GHC/Generics.hs @@ -163,7 +163,7 @@ module GHC.Generics ( -- type 'D1' = 'M1' 'D' -- @ -- --- The types 'S', 'C' and 'R' are once again type-level proxies, just used to create +-- The types 'S', 'C' and 'D' are once again type-level proxies, just used to create -- several variants of 'M1'. -- *** Additional generic representation type constructors From git at git.haskell.org Mon Dec 15 15:03:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 15:03:48 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix #9415. (8a91cad) Message-ID: <20141215150348.946573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/8a91cad2521659060d5e4c0cc9a6e2fb6850ed57/ghc >--------------------------------------------------------------- commit 8a91cad2521659060d5e4c0cc9a6e2fb6850ed57 Author: Richard Eisenberg Date: Wed Aug 6 09:51:26 2014 -0400 Fix #9415. Abort typechecking when we detect a superclass cycle error, as ambiguity checking in the presence of superclass cycle errors can cause a loop. (cherry picked from commit 1b1388697e687154c2bf1943639e75f3ccf5bc59) >--------------------------------------------------------------- 8a91cad2521659060d5e4c0cc9a6e2fb6850ed57 compiler/typecheck/TcTyClsDecls.lhs | 17 ++++++++++++++++- 1 file changed, 16 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcTyClsDecls.lhs b/compiler/typecheck/TcTyClsDecls.lhs index f416067..62a4dc6 100644 --- a/compiler/typecheck/TcTyClsDecls.lhs +++ b/compiler/typecheck/TcTyClsDecls.lhs @@ -1340,10 +1340,24 @@ 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) $ mapM_ recClsErr cls_cycles + = unless (null cls_cycles) $ + do { mapM_ recClsErr cls_cycles + ; failM } -- See Note [Abort when superclass cycle is detected] where cls_cycles = calcClassCycles cls checkValidTyCl :: TyThing -> TcM () @@ -1589,6 +1603,7 @@ checkValidClass cls ; checkValidTheta (ClassSCCtxt (className cls)) theta -- Now check for cyclic superclasses + -- If there are superclass cycles, checkClassCycleErrs bails. ; checkClassCycleErrs cls -- Check the class operations From git at git.haskell.org Mon Dec 15 15:03:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 15:03:52 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Test #9415 (typecheck/should_fail/T9415) (d269a4f) Message-ID: <20141215150352.0252A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/d269a4fc56d575ce01f8c0b11f7028421fabe06d/ghc >--------------------------------------------------------------- commit d269a4fc56d575ce01f8c0b11f7028421fabe06d Author: Richard Eisenberg Date: Wed Aug 6 09:54:37 2014 -0400 Test #9415 (typecheck/should_fail/T9415) (cherry picked from commit 1a3e19d061c1e5a1db9789572eca3a0ade450954) >--------------------------------------------------------------- d269a4fc56d575ce01f8c0b11f7028421fabe06d testsuite/tests/typecheck/should_fail/T9415.hs | 5 +++++ testsuite/tests/typecheck/should_fail/T9415.stderr | 8 ++++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 14 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T9415.hs b/testsuite/tests/typecheck/should_fail/T9415.hs new file mode 100644 index 0000000..db77ff0 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9415.hs @@ -0,0 +1,5 @@ +module T9415 where + +class D a => C a where + meth :: D a => () +class C a => D a diff --git a/testsuite/tests/typecheck/should_fail/T9415.stderr b/testsuite/tests/typecheck/should_fail/T9415.stderr new file mode 100644 index 0000000..516759e --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9415.stderr @@ -0,0 +1,8 @@ + +T9415.hs:3:1: + Cycle in class declaration (via superclasses): C -> D -> C + In the class declaration for ?C? + +T9415.hs:5:1: + Cycle in class declaration (via superclasses): D -> C -> D + In the class declaration for ?D? diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 37546d6..1248e03 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -330,3 +330,4 @@ test('T8570', extra_clean(['T85570a.o', 'T8570a.hi','T85570b.o', 'T8570b.hi']), multimod_compile_fail, ['T8570', '-v0']) test('T8603', normal, compile_fail, ['']) test('T8912', normal, compile_fail, ['']) +test('T9415', normal, compile_fail, ['']) From git at git.haskell.org Mon Dec 15 15:03:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 15:03:54 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix Trac #9371. (683d13a) Message-ID: <20141215150354.B43C43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/683d13aa16d4bb6b3ad758998b7f5b0dece1dee7/ghc >--------------------------------------------------------------- commit 683d13aa16d4bb6b3ad758998b7f5b0dece1dee7 Author: Richard Eisenberg Date: Sun Aug 3 18:40:30 2014 -0400 Fix Trac #9371. This was very simple: lists of different lengths are *maybe* apart, not *surely* apart. (cherry picked from commit f29bdfbcedda6cb33ab05d884c151f2b31f4e4e0) >--------------------------------------------------------------- 683d13aa16d4bb6b3ad758998b7f5b0dece1dee7 compiler/types/Unify.lhs | 22 +++++++++++++++++++++- 1 file changed, 21 insertions(+), 1 deletion(-) diff --git a/compiler/types/Unify.lhs b/compiler/types/Unify.lhs index f2b45e8..2acbb24 100644 --- a/compiler/types/Unify.lhs +++ b/compiler/types/Unify.lhs @@ -415,6 +415,26 @@ substituted, we can't properly unify the types. But, that skolem variable may later be instantiated with a unifyable type. So, we return maybeApart in these cases. +Note [Lists of different lengths are MaybeApart] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +It is unusual to call tcUnifyTys or tcUnifyTysFG with lists of different +lengths. The place where we know this can happen is from compatibleBranches in +FamInstEnv, when checking data family instances. Data family instances may be +eta-reduced; see Note [Eta reduction for data family axioms] in TcInstDcls. + +We wish to say that + + D :: * -> * -> * + axDF1 :: D Int ~ DFInst1 + axDF2 :: D Int Bool ~ DFInst2 + +overlap. If we conclude that lists of different lengths are SurelyApart, then +it will look like these do *not* overlap, causing disaster. See Trac #9371. + +In usages of tcUnifyTys outside of family instances, we always use tcUnifyTys, +which can't tell the difference between MaybeApart and SurelyApart, so those +usages won't notice this design choice. + \begin{code} tcUnifyTy :: Type -> Type -- All tyvars are bindable -> Maybe TvSubst -- A regular one-shot (idempotent) substitution @@ -590,7 +610,7 @@ unifyList subst orig_xs orig_ys go subst [] [] = return subst go subst (x:xs) (y:ys) = do { subst' <- unify subst x y ; go subst' xs ys } - go _ _ _ = surelyApart + go subst _ _ = maybeApart subst -- See Note [Lists of different lengths are MaybeApart] --------------------------------- uVar :: TvSubstEnv -- An existing substitution to extend From git at git.haskell.org Mon Dec 15 15:03:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 15:03:57 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Test #9371 (indexed-types/should_fail/T9371) (2085bd3) Message-ID: <20141215150357.F13913A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/2085bd38a84777edc64fc50ac8ed2f45d513de07/ghc >--------------------------------------------------------------- commit 2085bd38a84777edc64fc50ac8ed2f45d513de07 Author: Richard Eisenberg Date: Sun Aug 3 17:54:54 2014 -0400 Test #9371 (indexed-types/should_fail/T9371) (cherry picked from commit a09508b792eed24fc4d8a363df2635026bfa2de6) >--------------------------------------------------------------- 2085bd38a84777edc64fc50ac8ed2f45d513de07 testsuite/tests/indexed-types/should_fail/T9371.hs | 25 ++++++++++++++++++++++ .../tests/indexed-types/should_fail/T9371.stderr | 5 +++++ testsuite/tests/indexed-types/should_fail/all.T | 1 + 3 files changed, 31 insertions(+) diff --git a/testsuite/tests/indexed-types/should_fail/T9371.hs b/testsuite/tests/indexed-types/should_fail/T9371.hs new file mode 100644 index 0000000..cfec4c0 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T9371.hs @@ -0,0 +1,25 @@ +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE UndecidableInstances #-} + +module T9371 where + +import Data.Monoid + +class C x where + data D x :: * + makeD :: D x + +instance {-# OVERLAPPABLE #-} Monoid x => C x where + data D x = D1 (Either x ()) + makeD = D1 (Left mempty) + +instance (Monoid x, Monoid y) => C (x, y) where + data D (x,y) = D2 (x,y) + makeD = D2 (mempty, mempty) + +instance Show x => Show (D x) where + show (D1 x) = show x + + +main = print (makeD :: D (String, String)) diff --git a/testsuite/tests/indexed-types/should_fail/T9371.stderr b/testsuite/tests/indexed-types/should_fail/T9371.stderr new file mode 100644 index 0000000..695a7b4 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T9371.stderr @@ -0,0 +1,5 @@ + +T9371.hs:14:10: + Conflicting family instance declarations: + D -- Defined at T9371.hs:14:10 + D (x, y) -- Defined at T9371.hs:18:10 diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index dde335d..cca56db 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -121,3 +121,4 @@ test('T8368a', normal, compile_fail, ['']) test('T8518', normal, compile_fail, ['']) test('T9160', normal, compile_fail, ['']) test('T9433', normal, compile_fail, ['']) +test('T9371', normal, compile_fail, ['']) From git at git.haskell.org Mon Dec 15 15:04:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 15:04:00 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: When desugaring Use the smart mkCoreConApps and friends (fea3853) Message-ID: <20141215150400.A68AE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/fea3853ff2880ee22eb633bb90f949232679a1c7/ghc >--------------------------------------------------------------- commit fea3853ff2880ee22eb633bb90f949232679a1c7 Author: Simon Peyton Jones Date: Fri Aug 1 16:56:10 2014 +0100 When desugaring Use the smart mkCoreConApps and friends This is actually the bug that triggered Trac #9390. We had an unboxed tuple (# writeArray# ..., () #), and that writeArray# argument isn't ok-for-speculation, so disobeys the invariant. The desugaring of unboxed tuples was to blame; the fix is easy. (cherry picked from commit 1fc60ea1f1fd89b90c2992d060aecb5b5a65f8c0) >--------------------------------------------------------------- fea3853ff2880ee22eb633bb90f949232679a1c7 compiler/deSugar/DsArrows.lhs | 4 ++-- compiler/deSugar/DsCCall.lhs | 6 +++--- compiler/deSugar/DsExpr.lhs | 6 +++--- compiler/deSugar/DsMeta.hs | 2 +- compiler/deSugar/MatchLit.lhs | 2 +- 5 files changed, 10 insertions(+), 10 deletions(-) diff --git a/compiler/deSugar/DsArrows.lhs b/compiler/deSugar/DsArrows.lhs index f878776..0ea18d1 100644 --- a/compiler/deSugar/DsArrows.lhs +++ b/compiler/deSugar/DsArrows.lhs @@ -465,8 +465,8 @@ dsCmd ids local_vars stack_ty res_ty (HsCmdIf mb_fun cond then_cmd else_cmd) left_con <- dsLookupDataCon leftDataConName right_con <- dsLookupDataCon rightDataConName - let mk_left_expr ty1 ty2 e = mkConApp left_con [Type ty1, Type ty2, e] - mk_right_expr ty1 ty2 e = mkConApp right_con [Type ty1, Type ty2, e] + let mk_left_expr ty1 ty2 e = mkCoreConApps left_con [Type ty1, Type ty2, e] + mk_right_expr ty1 ty2 e = mkCoreConApps right_con [Type ty1, Type ty2, e] in_ty = envStackType env_ids stack_ty then_ty = envStackType then_ids stack_ty diff --git a/compiler/deSugar/DsCCall.lhs b/compiler/deSugar/DsCCall.lhs index f3f0adc..69735f1 100644 --- a/compiler/deSugar/DsCCall.lhs +++ b/compiler/deSugar/DsCCall.lhs @@ -236,9 +236,9 @@ boxResult result_ty _ -> [] return_result state anss - = mkConApp (tupleCon UnboxedTuple (2 + length extra_result_tys)) - (map Type (realWorldStatePrimTy : io_res_ty : extra_result_tys) - ++ (state : anss)) + = mkCoreConApps (tupleCon UnboxedTuple (2 + length extra_result_tys)) + (map Type (realWorldStatePrimTy : io_res_ty : extra_result_tys) + ++ (state : anss)) ; (ccall_res_ty, the_alt) <- mk_alt return_result res diff --git a/compiler/deSugar/DsExpr.lhs b/compiler/deSugar/DsExpr.lhs index a9b7003..5d8f34b 100644 --- a/compiler/deSugar/DsExpr.lhs +++ b/compiler/deSugar/DsExpr.lhs @@ -291,8 +291,8 @@ dsExpr (ExplicitTuple tup_args boxity) -- The reverse is because foldM goes left-to-right ; return $ mkCoreLams lam_vars $ - mkConApp (tupleCon (boxityNormalTupleSort boxity) (length tup_args)) - (map (Type . exprType) args ++ args) } + mkCoreConApps (tupleCon (boxityNormalTupleSort boxity) (length tup_args)) + (map (Type . exprType) args ++ args) } dsExpr (HsSCC cc expr@(L loc _)) = do mod_name <- getModule @@ -433,7 +433,7 @@ dsExpr (RecordCon (L _ data_con_id) con_expr rbinds) = do then mapM unlabelled_bottom arg_tys else mapM mk_arg (zipEqual "dsExpr:RecordCon" arg_tys labels) - return (mkApps con_expr' con_args) + return (mkCoreApps con_expr' con_args) \end{code} Record update is a little harder. Suppose we have the decl: diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs index 65bb935..8514325 100644 --- a/compiler/deSugar/DsMeta.hs +++ b/compiler/deSugar/DsMeta.hs @@ -1490,7 +1490,7 @@ rep2 n xs = do { id <- dsLookupGlobalId n dataCon' :: Name -> [CoreExpr] -> DsM (Core a) dataCon' n args = do { id <- dsLookupDataCon n - ; return $ MkC $ mkConApp id args } + ; return $ MkC $ mkCoreConApps id args } dataCon :: Name -> DsM (Core a) dataCon n = dataCon' n [] diff --git a/compiler/deSugar/MatchLit.lhs b/compiler/deSugar/MatchLit.lhs index 9652bdf..ff834e6 100644 --- a/compiler/deSugar/MatchLit.lhs +++ b/compiler/deSugar/MatchLit.lhs @@ -90,7 +90,7 @@ dsLit (HsInt i) = do dflags <- getDynFlags dsLit (HsRat r ty) = do num <- mkIntegerExpr (numerator (fl_value r)) denom <- mkIntegerExpr (denominator (fl_value r)) - return (mkConApp ratio_data_con [Type integer_ty, num, denom]) + return (mkCoreConApps ratio_data_con [Type integer_ty, num, denom]) where (ratio_data_con, integer_ty) = case tcSplitTyConApp ty of From git at git.haskell.org Mon Dec 15 15:04:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 15:04:03 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Test Trac #9390 (50f7931) Message-ID: <20141215150403.9E80D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/50f79311b34a555c91f26adab7b9f0a9093ea0f1/ghc >--------------------------------------------------------------- commit 50f79311b34a555c91f26adab7b9f0a9093ea0f1 Author: Simon Peyton Jones Date: Thu Aug 7 10:08:00 2014 +0100 Test Trac #9390 (cherry picked from commit 2990e97f008c9703eb4b47e24a29d052d5735f00) >--------------------------------------------------------------- 50f79311b34a555c91f26adab7b9f0a9093ea0f1 testsuite/tests/simplCore/should_run/T9390.hs | 27 +++++++++++++++++++++++ testsuite/tests/simplCore/should_run/T9390.stdout | 1 + testsuite/tests/simplCore/should_run/all.T | 1 + 3 files changed, 29 insertions(+) diff --git a/testsuite/tests/simplCore/should_run/T9390.hs b/testsuite/tests/simplCore/should_run/T9390.hs new file mode 100644 index 0000000..04b4da0 --- /dev/null +++ b/testsuite/tests/simplCore/should_run/T9390.hs @@ -0,0 +1,27 @@ +{-# LANGUAGE MagicHash, UnboxedTuples #-} +module Main(main ) where + +import GHC.IO (IO (..)) +import GHC.Prim + +writeB :: MutableArray# RealWorld Char -> IO () +writeB arr# = IO $ \s0# -> (# writeArray# arr# 0# 'B' s0#, () #) + +inlineWriteB :: MutableArray# RealWorld Char -> () +inlineWriteB arr# = + case f realWorld# of + (# _, x #) -> x + where + IO f = writeB arr# + +test :: IO Char +test = IO $ \s0# -> + case newArray# 1# 'A' s0# of + (# s1#, arr# #) -> + case seq# (inlineWriteB arr#) s1# of + (# s2#, () #) -> + readArray# arr# 0# s2# + +main :: IO () +main = test >>= print + diff --git a/testsuite/tests/simplCore/should_run/T9390.stdout b/testsuite/tests/simplCore/should_run/T9390.stdout new file mode 100644 index 0000000..69349b4 --- /dev/null +++ b/testsuite/tests/simplCore/should_run/T9390.stdout @@ -0,0 +1 @@ +'B' diff --git a/testsuite/tests/simplCore/should_run/all.T b/testsuite/tests/simplCore/should_run/all.T index ed7de1c..606078c 100644 --- a/testsuite/tests/simplCore/should_run/all.T +++ b/testsuite/tests/simplCore/should_run/all.T @@ -65,3 +65,4 @@ test('T7924', exit_code(1), compile_and_run, ['']) test('T457', [ only_ways(['normal','optasm']), exit_code(1) ], compile_and_run, ['']) test('T9128', normal, compile_and_run, ['']) +test('T9390', normal, compile_and_run, ['']) From git at git.haskell.org Mon Dec 15 15:13:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 15:13:03 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Set llc and opt commands on all platforms (3e55077) Message-ID: <20141215151303.93F293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/3e550770dff6a2852ecdbe755a63b29b3efa8dd1/ghc >--------------------------------------------------------------- commit 3e550770dff6a2852ecdbe755a63b29b3efa8dd1 Author: Austin Seipp Date: Mon Sep 1 15:14:07 2014 -0500 Set llc and opt commands on all platforms Summary: LLVM llc and opt commands should be set on all platforms, including Windows. If they're not, GHC tries to execute an unnamed executable, resulting in error messages such as: Error (figuring out LLVM version): : runInteractiveProcess: invalid argument (Invalid argument) : Warning: Couldn't figure out LLVM version! Make sure you have installed LLVM This regression was introduced in e6bfc596. Test Plan: Build GHC and test if --info shows sensible values of "LLVM llc command" and "LLVM opt command" Reviewers: austin, #ghc Reviewed By: austin, #ghc Subscribers: austin Projects: #ghc Differential Revision: https://phabricator.haskell.org/D190 GHC Trac Issues: #7143 (cherry picked from commit 918719b936b878ab660f20ceef8afc9e3a898c5a) >--------------------------------------------------------------- 3e550770dff6a2852ecdbe755a63b29b3efa8dd1 aclocal.m4 | 24 ++++++++++++------------ 1 file changed, 12 insertions(+), 12 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 7224cd5..4916212 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -470,18 +470,18 @@ AC_DEFUN([FP_SETTINGS], SettingsWindresCommand="/bin/false" SettingsLibtoolCommand="libtool" SettingsTouchCommand='touch' - if test -z "$LlcCmd" - then - SettingsLlcCommand="llc" - else - SettingsLlcCommand="$LlcCmd" - fi - if test -z "$OptCmd" - then - SettingsOptCommand="opt" - else - SettingsOptCommand="$OptCmd" - fi + fi + if test -z "$LlcCmd" + then + SettingsLlcCommand="llc" + else + SettingsLlcCommand="$LlcCmd" + fi + if test -z "$OptCmd" + then + SettingsOptCommand="opt" + else + SettingsOptCommand="$OptCmd" fi SettingsCCompilerFlags="$CONF_CC_OPTS_STAGE2" SettingsCCompilerLinkFlags="$CONF_GCC_LINKER_OPTS_STAGE2" From git at git.haskell.org Mon Dec 15 15:13:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 15:13:52 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix support for deriving Generic1 for data families (FIX #9563) (553dc4f) Message-ID: <20141215151352.394203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/553dc4fa427d1ba50c5cfbaa6ce7ea7677cd88ce/ghc >--------------------------------------------------------------- commit 553dc4fa427d1ba50c5cfbaa6ce7ea7677cd88ce Author: Jose Pedro Magalhaes Date: Fri Sep 12 17:44:12 2014 +0100 Fix support for deriving Generic1 for data families (FIX #9563) (cherry picked from commit 946cbcefab9bc02e12b741e5b070d7521b37ba1a) >--------------------------------------------------------------- 553dc4fa427d1ba50c5cfbaa6ce7ea7677cd88ce compiler/typecheck/TcGenGenerics.lhs | 9 +++++---- testsuite/tests/generics/T9563.hs | 18 ++++++++++++++++++ testsuite/tests/generics/all.T | 1 + 3 files changed, 24 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcGenGenerics.lhs b/compiler/typecheck/TcGenGenerics.lhs index 35bf424..923d71f 100644 --- a/compiler/typecheck/TcGenGenerics.lhs +++ b/compiler/typecheck/TcGenGenerics.lhs @@ -491,10 +491,11 @@ tc_mkRepFamInsts gk tycon metaDts mod = -- `appT` = D Int a b (data families case) Just (famtycon, apps) -> -- `fam` = D - -- `apps` = [Int, a] - let allApps = apps ++ - drop (length apps + length tyvars - - tyConArity famtycon) tyvar_args + -- `apps` = [Int, a, b] + let allApps = case gk of + Gen0 -> apps + Gen1 -> ASSERT(not $ null apps) + init apps in [mkTyConApp famtycon allApps] -- `appT` = D a b (normal case) Nothing -> [mkTyConApp tycon tyvar_args] diff --git a/testsuite/tests/generics/T9563.hs b/testsuite/tests/generics/T9563.hs new file mode 100644 index 0000000..fd12865 --- /dev/null +++ b/testsuite/tests/generics/T9563.hs @@ -0,0 +1,18 @@ +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE StandaloneDeriving #-} + +module T9563 where + +import GHC.Generics + +data family F typ :: * -> * +data A +data instance F A a = AData a + deriving (Generic, Generic1) + +data family G a b c d +data instance G Int b Float d = H deriving Generic + +deriving instance Generic1 (G Int b Float) diff --git a/testsuite/tests/generics/all.T b/testsuite/tests/generics/all.T index 1231c61..df95fa6 100644 --- a/testsuite/tests/generics/all.T +++ b/testsuite/tests/generics/all.T @@ -32,3 +32,4 @@ test('T7878', extra_clean(['T7878A.o' ,'T7878A.hi' test('T8468', normal, compile_fail, ['']) test('T8479', normal, compile, ['']) +test('T9563', normal, compile, ['']) From git at git.haskell.org Mon Dec 15 15:32:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 15:32:35 +0000 (UTC) Subject: [commit: packages/stm] master: Add mkWeakTMVar to Control.Concurrent.STM.TMVar (ed5d29d) Message-ID: <20141215153235.5F3FF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm On branch : master Link : http://git.haskell.org/packages/stm.git/commitdiff/ed5d29d1e8c658427728ff1d9dece2ddd3bba8e9 >--------------------------------------------------------------- commit ed5d29d1e8c658427728ff1d9dece2ddd3bba8e9 Author: Bas van Dijk Date: Mon Dec 15 09:33:17 2014 -0600 Add mkWeakTMVar to Control.Concurrent.STM.TMVar >--------------------------------------------------------------- ed5d29d1e8c658427728ff1d9dece2ddd3bba8e9 Control/Concurrent/STM/TMVar.hs | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/Control/Concurrent/STM/TMVar.hs b/Control/Concurrent/STM/TMVar.hs index 8458d40..a861bb1 100644 --- a/Control/Concurrent/STM/TMVar.hs +++ b/Control/Concurrent/STM/TMVar.hs @@ -34,12 +34,15 @@ module Control.Concurrent.STM.TMVar ( swapTMVar, tryTakeTMVar, tryPutTMVar, - isEmptyTMVar + isEmptyTMVar, + mkWeakTMVar #endif ) where #ifdef __GLASGOW_HASKELL__ +import GHC.Base import GHC.Conc +import GHC.Weak import Data.Typeable (Typeable) @@ -150,4 +153,10 @@ isEmptyTMVar (TMVar t) = do case m of Nothing -> return True Just _ -> return False + +-- | Make a 'Weak' pointer to a 'TMVar', using the second argument as +-- a finalizer to run when the 'TMVar' is garbage-collected. +mkWeakTMVar :: TMVar a -> IO () -> IO (Weak (TMVar a)) +mkWeakTMVar tmv@(TMVar (TVar t#)) f = IO $ \s -> + case mkWeak# t# tmv f s of (# s1, w #) -> (# s1, Weak w #) #endif From git at git.haskell.org Mon Dec 15 15:33:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 15:33:37 +0000 (UTC) Subject: [commit: ghc] master: stm: update submodule for #9169 addition (8afdf27) Message-ID: <20141215153337.468B03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8afdf274194e77e85e6a08dc4963022c56fc29d8/ghc >--------------------------------------------------------------- commit 8afdf274194e77e85e6a08dc4963022c56fc29d8 Author: Austin Seipp Date: Mon Dec 15 09:34:05 2014 -0600 stm: update submodule for #9169 addition Signed-off-by: Austin Seipp >--------------------------------------------------------------- 8afdf274194e77e85e6a08dc4963022c56fc29d8 libraries/stm | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/stm b/libraries/stm index 6b63e91..ed5d29d 160000 --- a/libraries/stm +++ b/libraries/stm @@ -1 +1 @@ -Subproject commit 6b63e91b2b0b7d7b4bef654117da62c22cac34da +Subproject commit ed5d29d1e8c658427728ff1d9dece2ddd3bba8e9 From git at git.haskell.org Mon Dec 15 17:08:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 17:08:02 +0000 (UTC) Subject: [commit: ghc] master: Fix dll-split problem with patch 'Make Core Lint check for locally-bound GlobalId' (3f87866) Message-ID: <20141215170802.545243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3f87866ad536d1c20fa477aa124fe1267fb36a43/ghc >--------------------------------------------------------------- commit 3f87866ad536d1c20fa477aa124fe1267fb36a43 Author: Simon Peyton Jones Date: Mon Dec 15 17:03:47 2014 +0000 Fix dll-split problem with patch 'Make Core Lint check for locally-bound GlobalId' The trouble was that my changes made a lot more files transitively link with DynFlags, which is the root module for the revolting Windows dll-split stuff. Anyway this patch fixes it, in a good way: - Make GHC/Hooks *not* import DsMonad, because DsMonad imports too much other stuff (notably tcLookup variants). Really, Hooks depends only on *types* not *code*. - To do this I need the DsM type, and the types it depends on, not to be part of DsMonad. So I moved it to TcRnTypes, which is where the similar pieces for the TcM and IfM monads live. - We can then delete DsMonad.hs-boot - There are a bunch of knock-on change, of no great significance >--------------------------------------------------------------- 3f87866ad536d1c20fa477aa124fe1267fb36a43 compiler/deSugar/DsMeta.hs | 18 ++-- compiler/deSugar/DsMonad.hs | 82 ++------------ compiler/deSugar/DsMonad.hs-boot | 32 ------ compiler/ghc.mk | 11 -- compiler/main/Hooks.hs | 6 +- compiler/typecheck/TcEnv.hs | 2 +- compiler/typecheck/TcExpr.hs | 2 +- compiler/typecheck/TcRnTypes.hs | 227 +++++++++++++++++++++++++-------------- compiler/typecheck/TcSplice.hs | 2 +- 9 files changed, 172 insertions(+), 210 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3f87866ad536d1c20fa477aa124fe1267fb36a43 From git at git.haskell.org Mon Dec 15 17:08:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 17:08:05 +0000 (UTC) Subject: [commit: ghc] master: Improve documentation of syntax for promoted lists (a972bdd) Message-ID: <20141215170805.21CC13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a972bddfc8115d80d774383a55202a293dc68595/ghc >--------------------------------------------------------------- commit a972bddfc8115d80d774383a55202a293dc68595 Author: Simon Peyton Jones Date: Mon Dec 15 17:08:29 2014 +0000 Improve documentation of syntax for promoted lists THe documentation in 7.9.4 of promoted list and tuple types was misleading, which led to Trac #9882. This patch makes explicit that only type-level with two or more elements can have the quote omitted. >--------------------------------------------------------------- a972bddfc8115d80d774383a55202a293dc68595 compiler/parser/Parser.y | 8 ++++++-- docs/users_guide/glasgow_exts.xml | 19 ++++++++++++++++--- 2 files changed, 22 insertions(+), 5 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index bffe6e1..235d34a 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -1483,6 +1483,10 @@ atype :: { LHsType RdrName } [mo $2,mc $4] } | SIMPLEQUOTE var { sLL $1 $> $ HsTyVar $ unLoc $2 } + -- Two or more [ty, ty, ty] must be a promoted list type, just as + -- if you had written '[ty, ty, ty] + -- (One means a list type, zero means the list type constructor, + -- so you have to quote those.) | '[' ctype ',' comma_types1 ']' {% ams (sLL $1 $> $ HsExplicitListTy placeHolderKind ($2 : $4)) [mo $1, mj AnnComma $3,mc $5] } @@ -1503,11 +1507,11 @@ inst_types1 :: { [LHsType RdrName] } | inst_type ',' inst_types1 {% addAnnotation (gl $1) AnnComma (gl $2) >> return ($1 : $3) } -comma_types0 :: { [LHsType RdrName] } +comma_types0 :: { [LHsType RdrName] } -- Zero or more: ty,ty,ty : comma_types1 { $1 } | {- empty -} { [] } -comma_types1 :: { [LHsType RdrName] } +comma_types1 :: { [LHsType RdrName] } -- One or more: ty,ty,ty : ctype { [$1] } | ctype ',' comma_types1 {% addAnnotation (gl $1) AnnComma (gl $2) >> return ($1 : $3) } diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index e12703f..7edca07 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -6882,9 +6882,9 @@ is a single quote. From git at git.haskell.org Mon Dec 15 17:39:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 17:39:52 +0000 (UTC) Subject: [commit: ghc] master: Wibbles to documentation for promoted lists and tuples (Trac #9882) (a3e6915) Message-ID: <20141215173952.1C2A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a3e6915431f93ebc0aaee22b7b9f118bffb01cae/ghc >--------------------------------------------------------------- commit a3e6915431f93ebc0aaee22b7b9f118bffb01cae Author: Simon Peyton Jones Date: Mon Dec 15 17:40:45 2014 +0000 Wibbles to documentation for promoted lists and tuples (Trac #9882) >--------------------------------------------------------------- a3e6915431f93ebc0aaee22b7b9f118bffb01cae docs/users_guide/glasgow_exts.xml | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 7edca07..a502262 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -6884,7 +6884,7 @@ is a single quote. From git at git.haskell.org Mon Dec 15 17:51:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 17:51:02 +0000 (UTC) Subject: [commit: packages/stm] master: Fix build breakage bogons, due to bad patch application (eadf716) Message-ID: <20141215175102.8ACA23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm On branch : master Link : http://git.haskell.org/packages/stm.git/commitdiff/eadf71656bb1a75e2355aee1bd07843c8bd3482a >--------------------------------------------------------------- commit eadf71656bb1a75e2355aee1bd07843c8bd3482a Author: Austin Seipp Date: Mon Dec 15 11:51:18 2014 -0600 Fix build breakage bogons, due to bad patch application Signed-off-by: Austin Seipp >--------------------------------------------------------------- eadf71656bb1a75e2355aee1bd07843c8bd3482a Control/Concurrent/STM/TMVar.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Control/Concurrent/STM/TMVar.hs b/Control/Concurrent/STM/TMVar.hs index a861bb1..932d4ca 100644 --- a/Control/Concurrent/STM/TMVar.hs +++ b/Control/Concurrent/STM/TMVar.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, DeriveDataTypeable #-} +{-# LANGUAGE CPP, DeriveDataTypeable, MagicHash, UnboxedTuples #-} #if __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Trustworthy #-} From git at git.haskell.org Mon Dec 15 17:51:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 17:51:44 +0000 (UTC) Subject: [commit: ghc] master: stm: Update submodule (again) to fix build breakage (2a18019) Message-ID: <20141215175144.E372B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2a180195f588458a77dcac859b7c793119a57784/ghc >--------------------------------------------------------------- commit 2a180195f588458a77dcac859b7c793119a57784 Author: Austin Seipp Date: Mon Dec 15 11:52:34 2014 -0600 stm: Update submodule (again) to fix build breakage Signed-off-by: Austin Seipp >--------------------------------------------------------------- 2a180195f588458a77dcac859b7c793119a57784 libraries/stm | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/stm b/libraries/stm index ed5d29d..eadf716 160000 --- a/libraries/stm +++ b/libraries/stm @@ -1 +1 @@ -Subproject commit ed5d29d1e8c658427728ff1d9dece2ddd3bba8e9 +Subproject commit eadf71656bb1a75e2355aee1bd07843c8bd3482a From git at git.haskell.org Mon Dec 15 22:39:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Dec 2014 22:39:18 +0000 (UTC) Subject: [commit: ghc] master: comment about why this program exists (a30dbc6) Message-ID: <20141215223918.54A6D3A302@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a30dbc64e21c09008e8500f6ff41d76a52e57d46/ghc >--------------------------------------------------------------- commit a30dbc64e21c09008e8500f6ff41d76a52e57d46 Author: Simon Marlow Date: Fri Dec 13 10:32:29 2013 +0000 comment about why this program exists >--------------------------------------------------------------- a30dbc64e21c09008e8500f6ff41d76a52e57d46 utils/deriveConstants/DeriveConstants.hs | 17 ++++++++++++++++- 1 file changed, 16 insertions(+), 1 deletion(-) diff --git a/utils/deriveConstants/DeriveConstants.hs b/utils/deriveConstants/DeriveConstants.hs index c793e84..ccf9028 100644 --- a/utils/deriveConstants/DeriveConstants.hs +++ b/utils/deriveConstants/DeriveConstants.hs @@ -1,4 +1,3 @@ - {- ------------------------------------------------------------------------ (c) The GHC Team, 1992-2012 @@ -8,6 +7,22 @@ declarations in the header files (primarily struct field offsets) and generates various files, such as a header file that can be #included into non-C source containing this information. +We want to get information about code generated by the C compiler, +such as the sizes of types, and offsets of struct fields. We need +this because the layout of certain runtime objects is defined in C +headers (e.g. includes/rts/storage/Closures.h), but we need access to +the layout of these structures from a Haskell program (GHC). + +One way to do this is to compile and run a C program that includes the +header files and prints out the sizes and offsets. However, when we +are cross-compiling, we can't run a C program compiled for the target +platform. + +So, this program works as follows: we generate a C program that when +compiled to an object file, has the information we need encoded as +symbol sizes. This means that we can extract the information without +needing to run the program, by inspecting the object file using 'nm'. + ------------------------------------------------------------------------ -} import Control.Monad (when, unless) From git at git.haskell.org Tue Dec 16 07:01:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 07:01:15 +0000 (UTC) Subject: [commit: packages/haskeline] master: Bump version to 0.7.1.4. (090963d) Message-ID: <20141216070115.6EFB33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/090963df66942f5e28eb9eebba2f64fe53f4b532 >--------------------------------------------------------------- commit 090963df66942f5e28eb9eebba2f64fe53f4b532 Author: Judah Jacobson Date: Mon Dec 15 20:18:40 2014 -0800 Bump version to 0.7.1.4. >--------------------------------------------------------------- 090963df66942f5e28eb9eebba2f64fe53f4b532 haskeline.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/haskeline.cabal b/haskeline.cabal index 404bf65..97d835f 100644 --- a/haskeline.cabal +++ b/haskeline.cabal @@ -1,6 +1,6 @@ Name: haskeline Cabal-Version: >=1.16 -Version: 0.7.1.3 +Version: 0.7.1.4 Category: User Interfaces License: BSD3 License-File: LICENSE From git at git.haskell.org Tue Dec 16 07:01:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 07:01:17 +0000 (UTC) Subject: [commit: packages/haskeline] master: Bump version to 0.7.2.0. (9d032a3) Message-ID: <20141216070117.740E93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/9d032a3ad4e652357212dda1e02c4baa3579f111 >--------------------------------------------------------------- commit 9d032a3ad4e652357212dda1e02c4baa3579f111 Author: Judah Jacobson Date: Mon Dec 15 20:20:58 2014 -0800 Bump version to 0.7.2.0. >--------------------------------------------------------------- 9d032a3ad4e652357212dda1e02c4baa3579f111 haskeline.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/haskeline.cabal b/haskeline.cabal index 97d835f..f8ab65c 100644 --- a/haskeline.cabal +++ b/haskeline.cabal @@ -1,6 +1,6 @@ Name: haskeline Cabal-Version: >=1.16 -Version: 0.7.1.4 +Version: 0.7.2.0 Category: User Interfaces License: BSD3 License-File: LICENSE From git at git.haskell.org Tue Dec 16 07:27:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 07:27:45 +0000 (UTC) Subject: [commit: packages/terminfo] master: Bump version to 0.4.0.1. (83cb515) Message-ID: <20141216072745.88CE83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/terminfo On branch : master Link : http://git.haskell.org/packages/terminfo.git/commitdiff/83cb51568234910c66a1ec6fd69ba127f6177194 >--------------------------------------------------------------- commit 83cb51568234910c66a1ec6fd69ba127f6177194 Author: Judah Jacobson Date: Mon Dec 15 20:13:12 2014 -0800 Bump version to 0.4.0.1. >--------------------------------------------------------------- 83cb51568234910c66a1ec6fd69ba127f6177194 terminfo.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/terminfo.cabal b/terminfo.cabal index 7c88f52..31d84fa 100644 --- a/terminfo.cabal +++ b/terminfo.cabal @@ -1,6 +1,6 @@ Name: terminfo Cabal-Version: >=1.10 -Version: 0.4.0.0 +Version: 0.4.0.1 Category: User Interfaces License: BSD3 License-File: LICENSE From git at git.haskell.org Tue Dec 16 07:28:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 07:28:01 +0000 (UTC) Subject: [commit: ghc] master: Update haskeline/terminfo submodules to master (493bf37) Message-ID: <20141216072801.0BA3F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/493bf375abf3ac75b4272cbe7961574ebc5a266b/ghc >--------------------------------------------------------------- commit 493bf375abf3ac75b4272cbe7961574ebc5a266b Author: Herbert Valerio Riedel Date: Mon Dec 15 14:42:32 2014 +0100 Update haskeline/terminfo submodules to master >--------------------------------------------------------------- 493bf375abf3ac75b4272cbe7961574ebc5a266b libraries/haskeline | 2 +- libraries/terminfo | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/haskeline b/libraries/haskeline index bf1a30f..9d032a3 160000 --- a/libraries/haskeline +++ b/libraries/haskeline @@ -1 +1 @@ -Subproject commit bf1a30ff7e25406359db9b0146a104248d058008 +Subproject commit 9d032a3ad4e652357212dda1e02c4baa3579f111 diff --git a/libraries/terminfo b/libraries/terminfo index de93eba..83cb515 160000 --- a/libraries/terminfo +++ b/libraries/terminfo @@ -1 +1 @@ -Subproject commit de93eba74cd4537771b65117d4ad00db9943657d +Subproject commit 83cb51568234910c66a1ec6fd69ba127f6177194 From git at git.haskell.org Tue Dec 16 07:28:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 07:28:03 +0000 (UTC) Subject: [commit: ghc] master: Update unix submodule to latest 2.7.1.0 snapshot (b317904) Message-ID: <20141216072803.AC13C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b31790487b191055bce53aff8707b35efb5835ef/ghc >--------------------------------------------------------------- commit b31790487b191055bce53aff8707b35efb5835ef Author: Herbert Valerio Riedel Date: Mon Dec 15 23:36:06 2014 +0100 Update unix submodule to latest 2.7.1.0 snapshot >--------------------------------------------------------------- b31790487b191055bce53aff8707b35efb5835ef libraries/unix | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/unix b/libraries/unix index 256b191..757bf44 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit 256b19184bcb05c3cd9a6061730b7d67d61c0763 +Subproject commit 757bf44bb4895fc561a2e5dd2f602168478741ec From git at git.haskell.org Tue Dec 16 07:28:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 07:28:06 +0000 (UTC) Subject: [commit: ghc] master: Update process submodule to latest 1.2.1.0 RC (f0cf7af) Message-ID: <20141216072806.83EF43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f0cf7aff878e0190fa53836f6589965b1225158f/ghc >--------------------------------------------------------------- commit f0cf7aff878e0190fa53836f6589965b1225158f Author: Herbert Valerio Riedel Date: Tue Dec 16 08:05:06 2014 +0100 Update process submodule to latest 1.2.1.0 RC >--------------------------------------------------------------- f0cf7aff878e0190fa53836f6589965b1225158f libraries/process | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/process b/libraries/process index 7139346..0246baf 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 71393467c6ee004d3ccdde27df80c90b63926531 +Subproject commit 0246baf953e6b0d1b511f4d831528a9a5e8b71e2 From git at git.haskell.org Tue Dec 16 09:10:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 09:10:49 +0000 (UTC) Subject: [commit: ghc] master: Typo in feature description (abd2ada) Message-ID: <20141216091049.C57D43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/abd2adaaf20f9361a5331b0beca78a0323656aec/ghc >--------------------------------------------------------------- commit abd2adaaf20f9361a5331b0beca78a0323656aec Author: Gabor Greif Date: Tue Dec 16 10:08:19 2014 +0100 Typo in feature description >--------------------------------------------------------------- abd2adaaf20f9361a5331b0beca78a0323656aec docs/users_guide/7.10.1-notes.xml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index dc8d9d6..f87b0cc 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -34,7 +34,7 @@ There is a new extension, StaticPointers, which allows you to create pointers to expressions which - remain valid accross processes. This is useful for + remain valid across processes. This is useful for referencing higher-order values in distributed systems. The pointers are created with a new keyword static as in From git at git.haskell.org Tue Dec 16 09:54:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 09:54:22 +0000 (UTC) Subject: [commit: ghc] branch 'wip/llvm-3.5-on-travis' created Message-ID: <20141216095422.0FADE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/llvm-3.5-on-travis Referencing: 1a16f3ff0c61baff65078671846db615a155059a From git at git.haskell.org Tue Dec 16 09:54:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 09:54:24 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.5-on-travis: Use llvm-3.5 on Travis (1a16f3f) Message-ID: <20141216095424.BA9893A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.5-on-travis Link : http://ghc.haskell.org/trac/ghc/changeset/1a16f3ff0c61baff65078671846db615a155059a/ghc >--------------------------------------------------------------- commit 1a16f3ff0c61baff65078671846db615a155059a Author: Joachim Breitner Date: Tue Dec 16 10:54:36 2014 +0100 Use llvm-3.5 on Travis to avoid a build failure with T5681(optllvm). According to Ben Gamari, llvm-3.4 is known to be not working with GHC HEAD. >--------------------------------------------------------------- 1a16f3ff0c61baff65078671846db615a155059a .travis.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index cc9ac3f..f101623 100644 --- a/.travis.yml +++ b/.travis.yml @@ -13,8 +13,8 @@ env: before_install: - travis_retry sudo add-apt-repository -y ppa:hvr/ghc - travis_retry sudo apt-get update - - travis_retry sudo apt-get install cabal-install-1.18 ghc-7.6.3 alex-3.1.3 happy-1.19.4 - - export PATH=/opt/ghc/7.6.3/bin:/opt/cabal/1.18/bin:/opt/alex/3.1.3/bin:/opt/happy/1.19.4/bin:$PATH + - travis_retry sudo apt-get install cabal-install-1.18 ghc-7.6.3 alex-3.1.3 happy-1.19.4 llvm-3.5 + - export PATH=/opt/ghc/7.6.3/bin:/opt/cabal/1.18/bin:/opt/alex/3.1.3/bin:/opt/happy/1.19.4/bin:/usr/lib/llvm-3.5/bin:$PATH - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ From git at git.haskell.org Tue Dec 16 10:00:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 10:00:41 +0000 (UTC) Subject: [commit: ghc] master: *Really* Re-Update Haddock submodule (06ba981) Message-ID: <20141216100041.298343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/06ba9818e2f99ff3ce0430a61a2be9df618d6488/ghc >--------------------------------------------------------------- commit 06ba9818e2f99ff3ce0430a61a2be9df618d6488 Author: Herbert Valerio Riedel Date: Tue Dec 16 08:56:37 2014 +0100 *Really* Re-Update Haddock submodule The actual gitlink update got lost in 0c9c2d899e63b810e7ab6b486f7244826b4a2e33 >--------------------------------------------------------------- 06ba9818e2f99ff3ce0430a61a2be9df618d6488 testsuite/tests/perf/haddock/all.T | 4 ++-- utils/haddock | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index e4a8d88..905ab91 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), 8792433208, 5) + [(wordsize(64), 9502647104, 5) # 2012-08-14: 5920822352 (amd64/Linux) # 2012-09-20: 5829972376 (amd64/Linux) # 2012-10-08: 5902601224 (amd64/Linux) @@ -21,7 +21,7 @@ test('haddock.base', # 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) - # 2014-12-14: 8792433208 (x86_64/Linux) - Update to Haddock 2.16 + # 2014-12-14: 9502647104 (x86_64/Linux) - Update to Haddock 2.16 ,(platform('i386-unknown-mingw32'), 4202377432, 5) # 2013-02-10: 3358693084 (x86/Windows) # 2013-11-13: 3097751052 (x86/Windows, 64bit machine) diff --git a/utils/haddock b/utils/haddock index b94ab90..179a3fa 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit b94ab9034367f51b978904d60f2604db10abbd9f +Subproject commit 179a3faca1524f6cb1cd21e0cefc2000bb6480be From git at git.haskell.org Tue Dec 16 10:01:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 10:01:21 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.5-on-travis: Use llvm-3.5 on Travis (4c96ec6) Message-ID: <20141216100121.6EF853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.5-on-travis Link : http://ghc.haskell.org/trac/ghc/changeset/4c96ec67668b5493cd34313e819634b9887f0473/ghc >--------------------------------------------------------------- commit 4c96ec67668b5493cd34313e819634b9887f0473 Author: Joachim Breitner Date: Tue Dec 16 10:54:36 2014 +0100 Use llvm-3.5 on Travis to avoid a build failure with T5681(optllvm). According to Ben Gamari, llvm-3.4 is known to be not working with GHC HEAD. >--------------------------------------------------------------- 4c96ec67668b5493cd34313e819634b9887f0473 .travis.yml | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index cc9ac3f..55fd589 100644 --- a/.travis.yml +++ b/.travis.yml @@ -14,7 +14,9 @@ before_install: - travis_retry sudo add-apt-repository -y ppa:hvr/ghc - travis_retry sudo apt-get update - travis_retry sudo apt-get install cabal-install-1.18 ghc-7.6.3 alex-3.1.3 happy-1.19.4 - - export PATH=/opt/ghc/7.6.3/bin:/opt/cabal/1.18/bin:/opt/alex/3.1.3/bin:/opt/happy/1.19.4/bin:$PATH + - travis_retry sudo add-apt-repository -y ppa:h-rayflood/llvm + - travis_retry sudo apt-get install llvm-3.5 + - export PATH=/opt/ghc/7.6.3/bin:/opt/cabal/1.18/bin:/opt/alex/3.1.3/bin:/opt/happy/1.19.4/bin:/usr/lib/llvm-3.5/bin:$PATH - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ From git at git.haskell.org Tue Dec 16 10:05:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 10:05:26 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.5-on-travis: Use llvm-3.5 on Travis (39c2b2d) Message-ID: <20141216100526.A2E1C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.5-on-travis Link : http://ghc.haskell.org/trac/ghc/changeset/39c2b2d834c2c3b51d0b9baf39f6fdfc5a997d87/ghc >--------------------------------------------------------------- commit 39c2b2d834c2c3b51d0b9baf39f6fdfc5a997d87 Author: Joachim Breitner Date: Tue Dec 16 10:54:36 2014 +0100 Use llvm-3.5 on Travis to avoid a build failure with T5681(optllvm). According to Ben Gamari, llvm-3.4 is known to be not working with GHC HEAD. >--------------------------------------------------------------- 39c2b2d834c2c3b51d0b9baf39f6fdfc5a997d87 .travis.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index cc9ac3f..a869cf0 100644 --- a/.travis.yml +++ b/.travis.yml @@ -12,9 +12,10 @@ env: before_install: - travis_retry sudo add-apt-repository -y ppa:hvr/ghc + - travis_retry sudo add-apt-repository -y ppa:h-rayflood/llvm - travis_retry sudo apt-get update - - travis_retry sudo apt-get install cabal-install-1.18 ghc-7.6.3 alex-3.1.3 happy-1.19.4 - - export PATH=/opt/ghc/7.6.3/bin:/opt/cabal/1.18/bin:/opt/alex/3.1.3/bin:/opt/happy/1.19.4/bin:$PATH + - travis_retry sudo apt-get install cabal-install-1.18 ghc-7.6.3 alex-3.1.3 happy-1.19.4 llvm-3.5 + - export PATH=/opt/ghc/7.6.3/bin:/opt/cabal/1.18/bin:/opt/alex/3.1.3/bin:/opt/happy/1.19.4/bin:/usr/lib/llvm-3.5/bin:$PATH - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ From git at git.haskell.org Tue Dec 16 10:08:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 10:08:06 +0000 (UTC) Subject: [commit: ghc] wip/llvm-3.5-on-travis: Use llvm-3.5 on Travis (4ec289d) Message-ID: <20141216100806.AEBA43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/llvm-3.5-on-travis Link : http://ghc.haskell.org/trac/ghc/changeset/4ec289d76c9b36d13b4e6434bb5ac4d0806e3628/ghc >--------------------------------------------------------------- commit 4ec289d76c9b36d13b4e6434bb5ac4d0806e3628 Author: Joachim Breitner Date: Tue Dec 16 10:54:36 2014 +0100 Use llvm-3.5 on Travis to avoid a build failure with T5681(optllvm). According to Ben Gamari, llvm-3.4 is known to be not working with GHC HEAD. >--------------------------------------------------------------- 4ec289d76c9b36d13b4e6434bb5ac4d0806e3628 .travis.yml | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index cc9ac3f..dd4606f 100644 --- a/.travis.yml +++ b/.travis.yml @@ -12,9 +12,11 @@ env: before_install: - travis_retry sudo add-apt-repository -y ppa:hvr/ghc + - travis_retry sudo add-apt-repository -y ppa:h-rayflood/gcc-upper + - travis_retry sudo add-apt-repository -y ppa:h-rayflood/llvm-upper - travis_retry sudo apt-get update - - travis_retry sudo apt-get install cabal-install-1.18 ghc-7.6.3 alex-3.1.3 happy-1.19.4 - - export PATH=/opt/ghc/7.6.3/bin:/opt/cabal/1.18/bin:/opt/alex/3.1.3/bin:/opt/happy/1.19.4/bin:$PATH + - travis_retry sudo apt-get install cabal-install-1.18 ghc-7.6.3 alex-3.1.3 happy-1.19.4 llvm-3.5 + - export PATH=/opt/ghc/7.6.3/bin:/opt/cabal/1.18/bin:/opt/alex/3.1.3/bin:/opt/happy/1.19.4/bin:/usr/lib/llvm-3.5/bin:$PATH - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ From git at git.haskell.org Tue Dec 16 11:31:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 11:31:30 +0000 (UTC) Subject: [commit: ghc] branch 'wip/llvm-3.5-on-travis' deleted Message-ID: <20141216113130.D07C13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/llvm-3.5-on-travis From git at git.haskell.org Tue Dec 16 11:31:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 11:31:33 +0000 (UTC) Subject: [commit: ghc] master: Use llvm-3.5 on Travis (4a7489b) Message-ID: <20141216113133.6B8A83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4a7489b186de351410a3676c7f1d85b426431dc0/ghc >--------------------------------------------------------------- commit 4a7489b186de351410a3676c7f1d85b426431dc0 Author: Joachim Breitner Date: Tue Dec 16 10:54:36 2014 +0100 Use llvm-3.5 on Travis to avoid a build failure with T5681(optllvm). According to Ben Gamari, llvm-3.4 is known to be not working with GHC HEAD. >--------------------------------------------------------------- 4a7489b186de351410a3676c7f1d85b426431dc0 .travis.yml | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index cc9ac3f..dd4606f 100644 --- a/.travis.yml +++ b/.travis.yml @@ -12,9 +12,11 @@ env: before_install: - travis_retry sudo add-apt-repository -y ppa:hvr/ghc + - travis_retry sudo add-apt-repository -y ppa:h-rayflood/gcc-upper + - travis_retry sudo add-apt-repository -y ppa:h-rayflood/llvm-upper - travis_retry sudo apt-get update - - travis_retry sudo apt-get install cabal-install-1.18 ghc-7.6.3 alex-3.1.3 happy-1.19.4 - - export PATH=/opt/ghc/7.6.3/bin:/opt/cabal/1.18/bin:/opt/alex/3.1.3/bin:/opt/happy/1.19.4/bin:$PATH + - travis_retry sudo apt-get install cabal-install-1.18 ghc-7.6.3 alex-3.1.3 happy-1.19.4 llvm-3.5 + - export PATH=/opt/ghc/7.6.3/bin:/opt/cabal/1.18/bin:/opt/alex/3.1.3/bin:/opt/happy/1.19.4/bin:/usr/lib/llvm-3.5/bin:$PATH - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ From git at git.haskell.org Tue Dec 16 12:29:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 12:29:14 +0000 (UTC) Subject: [commit: ghc] master: Convert `/Since: .../` to new `@since ...` syntax (554aeda) Message-ID: <20141216122914.312D03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/554aedab646075e12e53b44df04bcfbccbe03a73/ghc >--------------------------------------------------------------- commit 554aedab646075e12e53b44df04bcfbccbe03a73 Author: Herbert Valerio Riedel Date: Tue Dec 16 12:07:10 2014 +0100 Convert `/Since: .../` to new `@since ...` syntax Starting with Haddock 2.16 there's a new built-in support for since-annotations Note: This exposes a bug in the `@since` implementation (see e.g. `Data.Bits`) >--------------------------------------------------------------- 554aedab646075e12e53b44df04bcfbccbe03a73 libraries/base/Control/Concurrent.hs | 6 ++-- libraries/base/Control/Concurrent/MVar.hs | 8 ++--- libraries/base/Control/Exception.hs | 2 +- libraries/base/Control/Monad.hs | 2 +- libraries/base/Data/Bifunctor.hs | 4 +-- libraries/base/Data/Bits.hs | 28 +++++++-------- libraries/base/Data/Bool.hs | 2 +- libraries/base/Data/Coerce.hs | 2 +- libraries/base/Data/Either.hs | 4 +-- libraries/base/Data/Fixed.hs | 2 +- libraries/base/Data/Function.hs | 2 +- libraries/base/Data/Functor.hs | 2 +- libraries/base/Data/Functor/Identity.hs | 4 +-- libraries/base/Data/IORef.hs | 6 ++-- libraries/base/Data/List.hs | 2 +- libraries/base/Data/Monoid.hs | 4 +-- libraries/base/Data/OldList.hs | 4 +-- libraries/base/Data/Ord.hs | 2 +- libraries/base/Data/Proxy.hs | 2 +- libraries/base/Data/STRef.hs | 2 +- libraries/base/Data/Type/Bool.hs | 2 +- libraries/base/Data/Type/Coercion.hs | 4 +-- libraries/base/Data/Type/Equality.hs | 4 +-- libraries/base/Data/Typeable.hs | 2 +- libraries/base/Data/Typeable/Internal.hs | 8 ++--- libraries/base/Data/Void.hs | 8 ++--- libraries/base/Debug/Trace.hs | 20 +++++------ libraries/base/Foreign/C/Error.hs | 2 +- libraries/base/Foreign/C/Types.hs | 4 +-- libraries/base/Foreign/Marshal/Utils.hs | 2 +- libraries/base/GHC/Conc/Sync.hs | 24 ++++++------- libraries/base/GHC/Exception.hs | 4 +-- libraries/base/GHC/Exts.hs | 4 +-- libraries/base/GHC/Fingerprint.hs | 2 +- libraries/base/GHC/Generics.hs | 2 +- libraries/base/GHC/IO.hs | 2 +- libraries/base/GHC/IO/Encoding.hs | 12 +++---- libraries/base/GHC/IO/Encoding/Latin1.hs | 4 +-- libraries/base/GHC/IO/Encoding/Types.hs | 4 +-- libraries/base/GHC/IO/Encoding/UTF16.hs | 6 ++-- libraries/base/GHC/IO/Encoding/UTF32.hs | 6 ++-- libraries/base/GHC/IO/Encoding/UTF8.hs | 2 +- libraries/base/GHC/IO/Exception.hs | 8 ++--- libraries/base/GHC/IO/Handle/FD.hs | 2 +- libraries/base/GHC/IP.hs | 2 +- libraries/base/GHC/List.hs | 2 +- libraries/base/GHC/MVar.hs | 2 +- libraries/base/GHC/Natural.hs | 20 +++++------ libraries/base/GHC/Profiling.hs | 2 +- libraries/base/GHC/RTS/Flags.hsc | 2 +- libraries/base/GHC/Stack.hsc | 8 ++--- libraries/base/GHC/Stats.hsc | 8 ++--- libraries/base/GHC/TypeLits.hs | 32 ++++++++--------- libraries/base/GHC/Word.hs | 6 ++-- libraries/base/Numeric.hs | 4 +-- libraries/base/Numeric/Natural.hs | 2 +- libraries/base/System/Environment.hs | 6 ++-- .../base/System/Environment/ExecutablePath.hsc | 4 +-- libraries/base/System/Exit.hs | 2 +- libraries/base/System/IO/Error.hs | 4 +-- libraries/base/System/IO/Unsafe.hs | 2 +- libraries/base/System/Mem.hs | 4 +-- libraries/base/System/Mem/StableName.hs | 2 +- libraries/base/Text/Printf.hs | 42 +++++++++++----------- libraries/base/Text/Read.hs | 4 +-- libraries/base/Text/Read/Lex.hs | 14 ++++---- libraries/ghc-prim/GHC/Types.hs | 2 +- .../integer-gmp2/src/GHC/Integer/GMP/Internals.hs | 24 ++++++------- libraries/integer-gmp2/src/GHC/Integer/Type.hs | 24 ++++++------- 69 files changed, 226 insertions(+), 226 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 554aedab646075e12e53b44df04bcfbccbe03a73 From git at git.haskell.org Tue Dec 16 12:29:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 12:29:16 +0000 (UTC) Subject: [commit: ghc] master: Fix broken Haddock markup in `Monad` documentation (45a9696) Message-ID: <20141216122916.D151E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/45a9696c550c5fe5e891b6d4710179272dc9f6db/ghc >--------------------------------------------------------------- commit 45a9696c550c5fe5e891b6d4710179272dc9f6db Author: Herbert Valerio Riedel Date: Tue Dec 16 13:27:18 2014 +0100 Fix broken Haddock markup in `Monad` documentation >--------------------------------------------------------------- 45a9696c550c5fe5e891b6d4710179272dc9f6db libraries/base/GHC/Base.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index 25596e0..44085a2 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -444,10 +444,10 @@ Furthermore, the 'Monad' and 'Applicative' operations should relate as follows: * @'pure' = 'return'@ * @('<*>') = 'ap'@ -The above laws imply that +The above laws imply: -* @'fmap' f xs = xs '>>=' 'return' . f@, -* @('>>') = ('*>') +* @'fmap' f xs = xs '>>=' 'return' . f@ +* @('>>') = ('*>')@ and that 'pure' and ('<*>') satisfy the applicative functor laws. From git at git.haskell.org Tue Dec 16 13:40:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 13:40:50 +0000 (UTC) Subject: [commit: ghc] master: Make annotations-literals test case cleaning less aggressive (1b5d758) Message-ID: <20141216134050.5806B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1b5d758359ef1fec6974d4d67eaf31599ec0309b/ghc >--------------------------------------------------------------- commit 1b5d758359ef1fec6974d4d67eaf31599ec0309b Author: Joachim Breitner Date: Tue Dec 16 14:41:16 2014 +0100 Make annotations-literals test case cleaning less aggressive cf. a4ec0c92 and 289e52f8 >--------------------------------------------------------------- 1b5d758359ef1fec6974d4d67eaf31599ec0309b testsuite/tests/ghc-api/annotations-literals/Makefile | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/ghc-api/annotations-literals/Makefile b/testsuite/tests/ghc-api/annotations-literals/Makefile index 0a65083..875d063 100644 --- a/testsuite/tests/ghc-api/annotations-literals/Makefile +++ b/testsuite/tests/ghc-api/annotations-literals/Makefile @@ -5,11 +5,13 @@ include $(TOP)/mk/test.mk clean: rm -f *.o *.hi -literals: clean +literals: + rm -f literals.o literals.hi '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc literals ./literals "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" -parsed: clean +parsed: + rm -f parsed.o parsed.hi '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc parsed ./parsed "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" From git at git.haskell.org Tue Dec 16 21:02:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 21:02:06 +0000 (UTC) Subject: [commit: ghc] master: Source notes (Core support) (993975d) Message-ID: <20141216210206.CA9DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/993975d3a532887b38618eb604efe6502f3c66f8/ghc >--------------------------------------------------------------- commit 993975d3a532887b38618eb604efe6502f3c66f8 Author: Peter Wortmann Date: Mon Dec 1 20:21:47 2014 +0100 Source notes (Core support) This patch introduces "SourceNote" tickishs that link Core to the source code that generated it. The idea is to retain these source code links throughout code transformations so we can eventually relate object code all the way back to the original source (which we can, say, encode as DWARF information to allow debugging). We generate these SourceNotes like other tickshs in the desugaring phase. The activating command line flag is "-g", consistent with the flag other compilers use to decide DWARF generation. Keeping ticks from getting into the way of Core transformations is tricky, but doable. The changes in this patch produce identical Core in all cases I tested -- which at this point is GHC, all libraries and nofib. Also note that this pass creates *lots* of tick nodes, which we reduce somewhat by removing duplicated and overlapping source ticks. This will still cause significant Tick "clumps" - a possible future optimization could be to make Tick carry a list of Tickishs instead of one at a time. (From Phabricator D169) >--------------------------------------------------------------- 993975d3a532887b38618eb604efe6502f3c66f8 compiler/basicTypes/SrcLoc.hs | 30 +++-- compiler/coreSyn/CoreArity.hs | 39 +++++- compiler/coreSyn/CoreFVs.hs | 2 +- compiler/coreSyn/CorePrep.hs | 31 +++-- compiler/coreSyn/CoreSubst.hs | 34 +++-- compiler/coreSyn/CoreSyn.hs | 269 +++++++++++++++++++++++++++++++++----- compiler/coreSyn/CoreUnfold.hs | 9 +- compiler/coreSyn/CoreUtils.hs | 266 +++++++++++++++++++++++++++---------- compiler/coreSyn/PprCore.hs | 10 +- compiler/deSugar/Coverage.hs | 19 ++- compiler/deSugar/Desugar.hs | 1 + compiler/iface/IfaceSyn.hs | 21 +++ compiler/iface/MkIface.hs | 1 + compiler/iface/TcIface.hs | 1 + compiler/main/DynFlags.hs | 10 +- compiler/main/HscMain.hs | 6 +- compiler/simplCore/CSE.hs | 28 ++-- compiler/simplCore/FloatIn.hs | 17 +-- compiler/simplCore/FloatOut.hs | 14 +- compiler/simplCore/OccurAnal.hs | 84 ++++++------ compiler/simplCore/SetLevels.hs | 2 + compiler/simplCore/SimplCore.hs | 45 +++++-- compiler/simplCore/SimplEnv.hs | 20 ++- compiler/simplCore/SimplUtils.hs | 54 +++++--- compiler/simplCore/Simplify.hs | 99 +++++++------- compiler/specialise/Rules.hs | 61 ++++++--- compiler/specialise/SpecConstr.hs | 9 +- compiler/stgSyn/CoreToStg.hs | 3 + compiler/utils/OrdList.hs | 10 ++ 29 files changed, 873 insertions(+), 322 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 993975d3a532887b38618eb604efe6502f3c66f8 From git at git.haskell.org Tue Dec 16 21:02:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 21:02:09 +0000 (UTC) Subject: [commit: ghc] master: Generalized Coverage pass to allow adding multiple types of Tickishs (3b893f3) Message-ID: <20141216210209.88CAF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3b893f386b086a6cbac81d277a5aceaf1ee39e42/ghc >--------------------------------------------------------------- commit 3b893f386b086a6cbac81d277a5aceaf1ee39e42 Author: Peter Wortmann Date: Thu Jan 9 19:12:30 2014 +0000 Generalized Coverage pass to allow adding multiple types of Tickishs This allows having, say, HPC ticks, automatic cost centres and source notes active at the same time. We especially take care to un-tangle the infrastructure involved in generating them. (From Phabricator D169) >--------------------------------------------------------------- 3b893f386b086a6cbac81d277a5aceaf1ee39e42 compiler/deSugar/Coverage.hs | 227 +++++++++++++++++++++++------------------ compiler/deSugar/Desugar.hs | 9 +- compiler/deSugar/DsUtils.hs | 9 +- compiler/hsSyn/Convert.hs | 2 +- compiler/hsSyn/HsBinds.hs | 13 ++- compiler/hsSyn/HsUtils.hs | 4 +- compiler/parser/Parser.y | 2 +- compiler/parser/RdrHsSyn.hs | 9 +- compiler/typecheck/TcBinds.hs | 11 +- compiler/typecheck/TcPatSyn.hs | 4 +- 10 files changed, 158 insertions(+), 132 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3b893f386b086a6cbac81d277a5aceaf1ee39e42 From git at git.haskell.org Tue Dec 16 21:02:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 21:02:12 +0000 (UTC) Subject: [commit: ghc] master: Annotation linting (07d604f) Message-ID: <20141216210212.5E5C23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/07d604fa1dba7caa39cdc4bc3d90844c600adb70/ghc >--------------------------------------------------------------- commit 07d604fa1dba7caa39cdc4bc3d90844c600adb70 Author: Peter Wortmann Date: Tue Oct 14 00:09:59 2014 +0200 Annotation linting This adds a way by which we can make sure that the Core passes treat annotations right: We run them twice and compare the results. The main problem here is that Core equivalence is awkward: We do not want the comparison to care about the order of, say, top-level or recursive bindings. This is important even if GHC generally generates the bindings in the right order - after all, if something goes wrong we don't want linting to dump out the whole program as the offense. So instead we do some heuristic matching - first greedily match everything that's easy, then match the rest by label order. This should work as long as GHC generates the labels in roughly the same order for both pass runs. In practice it seems to work alright. We also check that IdInfos match, as this might cause hard-to-spot bugs down the line (I had at least one bug because unfolding guidance didn't match!). We especially check unfoldings up until the point where it might get us into an infinite loop. (From Phabricator D169) >--------------------------------------------------------------- 07d604fa1dba7caa39cdc4bc3d90844c600adb70 compiler/basicTypes/BasicTypes.hs | 3 + compiler/coreSyn/CoreLint.hs | 64 ++++++++++++++++ compiler/coreSyn/CoreSyn.hs | 1 + compiler/coreSyn/CoreUtils.hs | 155 ++++++++++++++++++++++++++++++++++++-- compiler/main/DynFlags.hs | 3 + compiler/simplCore/SimplCore.hs | 5 +- 6 files changed, 224 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 07d604fa1dba7caa39cdc4bc3d90844c600adb70 From git at git.haskell.org Tue Dec 16 21:02:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 21:02:15 +0000 (UTC) Subject: [commit: ghc] master: Source notes (CorePrep and Stg support) (4cdbf80) Message-ID: <20141216210215.1B74F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4cdbf80250da2d3ba1c63451e5fbc9b5ca9cbfe9/ghc >--------------------------------------------------------------- commit 4cdbf80250da2d3ba1c63451e5fbc9b5ca9cbfe9 Author: Peter Wortmann Date: Tue Jan 14 18:25:16 2014 +0000 Source notes (CorePrep and Stg support) This is basically just about continuing maintaining source notes after the Core stage. Unfortunately, this is more involved as it might seem, as there are more restrictions on where ticks are allowed to show up. Notes: * We replace the StgTick / StgSCC constructors with a unified StgTick that can carry any tickish. * For handling constructor or lambda applications, we generally float ticks out. * Note that thanks to the NonLam placement, we know that source notes can never appear on lambdas. This means that as long as we are careful to always use mkTick, we will never violate CorePrep invariants. * This is however not automatically true for eta expansion, which needs to somewhat awkwardly strip, then re-tick the expression in question. * Where CorePrep floats out lets, we make sure to wrap them in the same spirit as FloatOut. * Detecting selector thunks becomes a bit more involved, as we can run into ticks at multiple points. (From Phabricator D169) >--------------------------------------------------------------- 4cdbf80250da2d3ba1c63451e5fbc9b5ca9cbfe9 compiler/codeGen/StgCmmBind.hs | 39 ++++++----- compiler/codeGen/StgCmmExpr.hs | 21 ++++-- compiler/coreSyn/CorePrep.hs | 95 ++++++++++++++++++++++---- compiler/profiling/SCCfinal.hs | 20 +++--- compiler/simplStg/StgStats.hs | 3 +- compiler/simplStg/UnariseStg.hs | 6 +- compiler/stgSyn/CoreToStg.hs | 145 +++++++++++++++++++--------------------- compiler/stgSyn/StgLint.hs | 4 +- compiler/stgSyn/StgSyn.hs | 60 +++++++---------- 9 files changed, 226 insertions(+), 167 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4cdbf80250da2d3ba1c63451e5fbc9b5ca9cbfe9 From git at git.haskell.org Tue Dec 16 21:02:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 21:02:17 +0000 (UTC) Subject: [commit: ghc] master: Strip source ticks from iface code if DWARF is disabled (a0895fc) Message-ID: <20141216210217.CE5643A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a0895fcb8c47949aac2c5e4a509d69de57582e76/ghc >--------------------------------------------------------------- commit a0895fcb8c47949aac2c5e4a509d69de57582e76 Author: Peter Wortmann Date: Tue Oct 22 16:05:16 2013 +0100 Strip source ticks from iface code if DWARF is disabled They would be unneeded at minimum. Not completely sure this is the right place to do this. (From Phabricator D169) >--------------------------------------------------------------- a0895fcb8c47949aac2c5e4a509d69de57582e76 compiler/iface/TcIface.hs | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/compiler/iface/TcIface.hs b/compiler/iface/TcIface.hs index 96e72df..cf0dc5b 100644 --- a/compiler/iface/TcIface.hs +++ b/compiler/iface/TcIface.hs @@ -1009,8 +1009,14 @@ tcIfaceExpr (IfaceLet (IfaceRec pairs) body) tcIfaceExpr (IfaceTick tickish expr) = do expr' <- tcIfaceExpr expr - tickish' <- tcIfaceTickish tickish - return (Tick tickish' expr') + -- If debug flag is not set: Ignore source notes + dbgFlag <- fmap (gopt Opt_Debug) getDynFlags + case tickish of + IfaceSource{} | not dbgFlag + -> return expr' + _otherwise -> do + tickish' <- tcIfaceTickish tickish + return (Tick tickish' expr') ------------------------- tcIfaceApps :: IfaceExpr -> IfaceExpr -> IfL CoreExpr From git at git.haskell.org Tue Dec 16 21:02:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 21:02:20 +0000 (UTC) Subject: [commit: ghc] master: Source notes (Cmm support) (7ceaf96) Message-ID: <20141216210220.B3ADE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7ceaf96fde63bd45dfc1e08a975cba0ee280eb7b/ghc >--------------------------------------------------------------- commit 7ceaf96fde63bd45dfc1e08a975cba0ee280eb7b Author: Peter Wortmann Date: Tue Oct 14 23:11:43 2014 +0200 Source notes (Cmm support) This patch adds CmmTick nodes to Cmm code. This is relatively straight-forward, but also not very useful, as many blocks will simply end up with no annotations whatosever. Notes: * We use this design over, say, putting ticks into the entry node of all blocks, as it seems to work better alongside existing optimisations. Now granted, the reason for this is that currently GHC's main Cmm optimisations seem to mainly reorganize and merge code, so this might change in the future. * We have the Cmm parser generate a few source notes as well. This is relatively easy to do - worst part is that it complicates the CmmParse implementation a bit. (From Phabricator D169) >--------------------------------------------------------------- 7ceaf96fde63bd45dfc1e08a975cba0ee280eb7b compiler/cmm/CmmCommonBlockElim.hs | 35 +++++++++++++++++++++++++---- compiler/cmm/CmmLint.hs | 1 + compiler/cmm/CmmNode.hs | 14 +++++++++++- compiler/cmm/CmmParse.y | 30 +++++++++++++++++++------ compiler/cmm/CmmUtils.hs | 20 ++++++++++++++++- compiler/cmm/PprC.hs | 2 ++ compiler/cmm/PprCmm.hs | 10 ++++++++- compiler/codeGen/StgCmmExpr.hs | 1 + compiler/codeGen/StgCmmExtCode.hs | 40 ++++++++++++++++++++------------- compiler/codeGen/StgCmmMonad.hs | 4 ++++ compiler/coreSyn/CoreSyn.hs | 1 - compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 1 + compiler/nativeGen/PPC/CodeGen.hs | 1 + compiler/nativeGen/SPARC/CodeGen.hs | 1 + compiler/nativeGen/X86/CodeGen.hs | 1 + 15 files changed, 132 insertions(+), 30 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7ceaf96fde63bd45dfc1e08a975cba0ee280eb7b From git at git.haskell.org Tue Dec 16 21:02:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 21:02:23 +0000 (UTC) Subject: [commit: ghc] master: Tick scopes (5fecd76) Message-ID: <20141216210223.8A7323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5fecd767309f318e0ec6797667ca6442a54ea451/ghc >--------------------------------------------------------------- commit 5fecd767309f318e0ec6797667ca6442a54ea451 Author: Peter Wortmann Date: Sat Dec 6 17:11:42 2014 +0100 Tick scopes This patch solves the scoping problem of CmmTick nodes: If we just put CmmTicks into blocks we have no idea what exactly they are meant to cover. Here we introduce tick scopes, which allow us to create sub-scopes and merged scopes easily. Notes: * Given that the code often passes Cmm around "head-less", we have to make sure that its intended scope does not get lost. To keep the amount of passing-around to a minimum we define a CmmAGraphScoped type synonym here that just bundles the scope with a portion of Cmm to be assembled later. * We introduce new scopes at somewhat random places, aligning with getCode calls. This works surprisingly well, but we might have to add new scopes into the mix later on if we find things too be too coarse-grained. (From Phabricator D169) >--------------------------------------------------------------- 5fecd767309f318e0ec6797667ca6442a54ea451 compiler/cmm/CmmCommonBlockElim.hs | 19 +++-- compiler/cmm/CmmContFlowOpt.hs | 12 ++- compiler/cmm/CmmLayoutStack.hs | 25 +++--- compiler/cmm/CmmNode.hs | 135 ++++++++++++++++++++++++++++++-- compiler/cmm/CmmParse.y | 6 +- compiler/cmm/CmmProcPoint.hs | 4 +- compiler/cmm/CmmUtils.hs | 10 +-- compiler/cmm/MkGraph.hs | 60 +++++++------- compiler/cmm/PprC.hs | 6 +- compiler/cmm/PprCmm.hs | 4 +- compiler/codeGen/StgCmmBind.hs | 4 +- compiler/codeGen/StgCmmExpr.hs | 20 ++--- compiler/codeGen/StgCmmExtCode.hs | 14 +++- compiler/codeGen/StgCmmForeign.hs | 3 +- compiler/codeGen/StgCmmHeap.hs | 8 +- compiler/codeGen/StgCmmLayout.hs | 14 ++-- compiler/codeGen/StgCmmMonad.hs | 88 ++++++++++++++++----- compiler/codeGen/StgCmmUtils.hs | 50 ++++++------ compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 3 +- compiler/nativeGen/PPC/CodeGen.hs | 3 +- compiler/nativeGen/SPARC/CodeGen.hs | 3 +- compiler/nativeGen/X86/CodeGen.hs | 3 +- 22 files changed, 349 insertions(+), 145 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5fecd767309f318e0ec6797667ca6442a54ea451 From git at git.haskell.org Tue Dec 16 21:02:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 21:02:26 +0000 (UTC) Subject: [commit: ghc] master: Add unwind information to Cmm (711a51a) Message-ID: <20141216210226.3F2EC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/711a51adcf8b32801289478443549947eedd49a2/ghc >--------------------------------------------------------------- commit 711a51adcf8b32801289478443549947eedd49a2 Author: Peter Wortmann Date: Tue Oct 14 01:14:14 2014 +0200 Add unwind information to Cmm Unwind information allows the debugger to discover more information about a program state, by allowing it to "reconstruct" other states of the program. In practice, this means that we explain to the debugger how to unravel stack frames, which comes down mostly to explaining how to find their Sp and Ip register values. * We declare yet another new constructor for CmmNode - and this time there's actually little choice, as unwind information can and will change mid-block. We don't actually make use of these capabilities, and back-end support would be tricky (generate new labels?), but it feels like the right way to do it. * Even though we only use it for Sp so far, we allow CmmUnwind to specify unwind information for any register. This is pretty cheap and could come in useful in future. * We allow full CmmExpr expressions for specifying unwind values. The advantage here is that we don't have to make up new syntax, and can e.g. use the WDS macro directly. On the other hand, the back-end will now have to simplify the expression until it can sensibly be converted into DWARF byte code - a process which might fail, yielding NCG panics. On the other hand, when you're writing Cmm by hand you really ought to know what you're doing. (From Phabricator D169) >--------------------------------------------------------------- 711a51adcf8b32801289478443549947eedd49a2 compiler/cmm/CmmCommonBlockElim.hs | 1 + compiler/cmm/CmmLayoutStack.hs | 7 +++++++ compiler/cmm/CmmLex.x | 2 ++ compiler/cmm/CmmLint.hs | 1 + compiler/cmm/CmmNode.hs | 10 ++++++++++ compiler/cmm/CmmParse.y | 3 +++ compiler/cmm/PprCmm.hs | 4 ++++ compiler/codeGen/StgCmmMonad.hs | 8 +++++++- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 1 + compiler/nativeGen/PPC/CodeGen.hs | 1 + compiler/nativeGen/SPARC/CodeGen.hs | 1 + compiler/nativeGen/X86/CodeGen.hs | 1 + rts/Exception.cmm | 1 + rts/StgMiscClosures.cmm | 1 + utils/genapply/GenApply.hs | 1 + 15 files changed, 42 insertions(+), 1 deletion(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 711a51adcf8b32801289478443549947eedd49a2 From git at git.haskell.org Tue Dec 16 21:02:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 21:02:29 +0000 (UTC) Subject: [commit: ghc] master: Debug data extraction (NCG support) (f46aa73) Message-ID: <20141216210229.67BB23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f46aa7338cd0318e8cd7b3a760dd6024576e0fbb/ghc >--------------------------------------------------------------- commit f46aa7338cd0318e8cd7b3a760dd6024576e0fbb Author: Peter Wortmann Date: Sat Nov 29 00:07:48 2014 +0100 Debug data extraction (NCG support) The purpose of the Debug module is to collect all required information to generate debug information (DWARF etc.) in the back-ends. Our main data structure is the "debug block", which carries all information we have about a block of code that is going to get produced. Notes: * Debug blocks are arranged into a tree according to tick scopes. This makes it easier to reason about inheritance rules. Note however that tick scopes are not guaranteed to form a tree, which requires us to "copy" ticks to not lose them. * This is also where we decide what source location we regard as representing a code block the "best". The heuristic is basically that we want the most specific source reference that comes from the same file we are currently compiling. This seems to be the most useful choice in my experience. * We are careful to not be too lazy so we don't end up breaking streaming. Debug data will be kept alive until the end of codegen, after all. * We change native assembler dumps to happen right away for every Cmm group. This simplifies the code somewhat and is consistent with how pretty much all of GHC handles dumps with respect to streamed code. (From Phabricator D169) >--------------------------------------------------------------- f46aa7338cd0318e8cd7b3a760dd6024576e0fbb compiler/cmm/Debug.hs | 309 +++++++++++++++++++++++++++++++++++++++ compiler/ghc.cabal.in | 1 + compiler/main/CodeOutput.hs | 11 +- compiler/main/DynFlags.hs | 2 + compiler/nativeGen/AsmCodeGen.hs | 135 ++++++++++------- 5 files changed, 404 insertions(+), 54 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f46aa7338cd0318e8cd7b3a760dd6024576e0fbb From git at git.haskell.org Tue Dec 16 21:02:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 21:02:32 +0000 (UTC) Subject: [commit: ghc] master: Debug test case and test suite way (c630614) Message-ID: <20141216210232.B112B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c63061402291ece9ba7fd460e6b95e0ab7c729df/ghc >--------------------------------------------------------------- commit c63061402291ece9ba7fd460e6b95e0ab7c729df Author: Peter Wortmann Date: Sun Dec 7 01:04:05 2014 +0100 Debug test case and test suite way Adds a test way for debug (-g -dannot-lint) as well as a test covering basic source tick functionality. The debug way fails for a number of test cases because of annotation linting: Tracing simplification (e.g. rule firings) will see duplicated output, and sometimes expression matching might take so long that the test case timeouts. We blacklist these tests. (From Phabricator D169) >--------------------------------------------------------------- c63061402291ece9ba7fd460e6b95e0ab7c729df libraries/base/tests/all.T | 3 ++- testsuite/config/ghc | 5 ++++- testsuite/tests/codeGen/should_compile/Makefile | 25 ++++++++++++++++++++++ testsuite/tests/codeGen/should_compile/all.T | 4 ++++ testsuite/tests/codeGen/should_compile/debug.hs | 6 ++++++ .../tests/codeGen/should_compile/debug.stdout | 24 +++++++++++++++++++++ testsuite/tests/programs/barton-mangler-bug/test.T | 4 +++- testsuite/tests/typecheck/should_run/all.T | 2 +- 8 files changed, 69 insertions(+), 4 deletions(-) diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T index d4686e5..1154a53 100644 --- a/libraries/base/tests/all.T +++ b/libraries/base/tests/all.T @@ -174,7 +174,8 @@ test('T8766', test('T9111', normal, compile, ['']) test('T9395', normal, compile_and_run, ['']) -test('T9532', normal, compile_and_run, ['']) +# Fails for debug way due to annotation linting timeout +test('T9532', omit_ways(['debug']), compile_and_run, ['']) test('T9586', normal, compile, ['']) test('T9681', normal, compile_fail, ['']) test('T8089', normal, compile_and_run, ['']) diff --git a/testsuite/config/ghc b/testsuite/config/ghc index 84b89d4..10565dd 100644 --- a/testsuite/config/ghc +++ b/testsuite/config/ghc @@ -28,7 +28,8 @@ config.other_ways = ['prof', 'llvm', 'debugllvm', 'profllvm', 'profoptllvm', 'profthreadedllvm', 'threaded1llvm', 'threaded2llvm', - 'dynllvm'] + 'dynllvm', + 'debug'] if (ghc_with_native_codegen == 1): config.compile_ways.append('optasm') @@ -104,6 +105,7 @@ config.way_flags = lambda name : { 'prof_hr' : ['-O', '-prof', '-static', '-auto-all'], 'dyn' : ['-O', '-dynamic'], 'static' : ['-O', '-static'], + 'debug' : ['-O', '-g', '-dannot-lint'], # llvm variants... 'profllvm' : ['-prof', '-static', '-auto-all', '-fllvm'], 'profoptllvm' : ['-O', '-prof', '-static', '-auto-all', '-fllvm'], @@ -136,6 +138,7 @@ config.way_rts_flags = { 'prof_hr' : ['-hr'], 'dyn' : [], 'static' : [], + 'debug' : [], # llvm variants... 'profllvm' : ['-p'], 'profoptllvm' : ['-hc', '-p'], diff --git a/testsuite/tests/codeGen/should_compile/Makefile b/testsuite/tests/codeGen/should_compile/Makefile index c804a12..b186e0d 100644 --- a/testsuite/tests/codeGen/should_compile/Makefile +++ b/testsuite/tests/codeGen/should_compile/Makefile @@ -5,3 +5,28 @@ include $(TOP)/mk/test.mk T2578: '$(TEST_HC)' $(TEST_HC_OPTS) --make T2578 -fforce-recomp -v0 +debug: + # Without optimisations, we should get annotations for basically + # all expressions in the example program. + echo == Dbg == + '$(TEST_HC)' $(TEST_HC_OPTS) debug -fforce-recomp -g -dppr-ticks -ddump-cmm \ + | grep -o src\ | sort -u + ./debug + + # With optimisations we will get fewer annotations. + echo == Dbg -O2 == + '$(TEST_HC)' $(TEST_HC_OPTS) debug -fforce-recomp -g -dppr-ticks -ddump-cmm -O2 \ + > debug.cmm + cat debug.cmm | grep -o src\ | sort -u + + # Common block elimination should elimation should merge the + # blocks corresponding to alternatives 1 and 2, therefore there + # must be a block containing exactly these two annotations + # directly next to each other. + echo == CBE == + cat debug.cmm | grep -A1 -B1 src\ \ + | grep src\ \ + | grep -o src\<.*\> | sort -u + + ./debug + rm debug diff --git a/testsuite/tests/codeGen/should_compile/all.T b/testsuite/tests/codeGen/should_compile/all.T index a6b6894..b571839 100644 --- a/testsuite/tests/codeGen/should_compile/all.T +++ b/testsuite/tests/codeGen/should_compile/all.T @@ -25,3 +25,7 @@ test('T8205', normal, compile, ['-O0']) test('T9155', normal, compile, ['-O2']) test('T9303', normal, compile, ['-O2']) test('T9329', [cmm_src], compile, ['']) + +test('debug', extra_clean(['debug.cmm']), + run_command, + ['$MAKE -s --no-print-directory debug']) diff --git a/testsuite/tests/codeGen/should_compile/debug.hs b/testsuite/tests/codeGen/should_compile/debug.hs new file mode 100644 index 0000000..dfb6d60 --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/debug.hs @@ -0,0 +1,6 @@ +module Main where +fib :: Int -> Int +fib 0 = 1 -- GHC should merge the blocks +fib 1 = 1 -- of these two alternatives +fib n = fib (n-1) + fib (n-2) +main = print $ fib 10 diff --git a/testsuite/tests/codeGen/should_compile/debug.stdout b/testsuite/tests/codeGen/should_compile/debug.stdout new file mode 100644 index 0000000..59332ff --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/debug.stdout @@ -0,0 +1,24 @@ +== Dbg == +src +src +src +src +src +src +src +src +src +src +src +89 +== Dbg -O2 == +src +src +src +src +src +src +src +== CBE == +src +89 diff --git a/testsuite/tests/programs/barton-mangler-bug/test.T b/testsuite/tests/programs/barton-mangler-bug/test.T index bb140f56f..f6ad425 100644 --- a/testsuite/tests/programs/barton-mangler-bug/test.T +++ b/testsuite/tests/programs/barton-mangler-bug/test.T @@ -9,6 +9,8 @@ test('barton-mangler-bug', 'Plot.hi', 'Plot.o', 'PlotExample.hi', 'PlotExample.o', 'TypesettingTricks.hi', 'TypesettingTricks.o']), - omit_compiler_types(['hugs'])], + omit_compiler_types(['hugs']), + omit_ways('debug') # Fails for debug way due to annotation linting timeout + ], multimod_compile_and_run, ['Main', '']) diff --git a/testsuite/tests/typecheck/should_run/all.T b/testsuite/tests/typecheck/should_run/all.T index 53c97ea..5b20034 100755 --- a/testsuite/tests/typecheck/should_run/all.T +++ b/testsuite/tests/typecheck/should_run/all.T @@ -107,7 +107,7 @@ test('T6117', normal, compile_and_run, ['']) test('T5751', normal, compile_and_run, ['']) test('T5913', normal, compile_and_run, ['']) test('T7748', normal, compile_and_run, ['']) -test('T7861', exit_code(1), compile_and_run, ['']) +test('T7861', [omit_ways('debug'), exit_code(1)], compile_and_run, ['']) test('TcTypeNatSimpleRun', normal, compile_and_run, ['']) test('T8119', normal, ghci_script, ['T8119.script']) test('T8492', normal, compile_and_run, ['']) From git at git.haskell.org Tue Dec 16 21:49:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 21:49:26 +0000 (UTC) Subject: [commit: ghc] master: update containers submodules to 0.5.6.1 release (5444560) Message-ID: <20141216214926.A96113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5444560b26a14750ae59578d354d98eaff9c7a41/ghc >--------------------------------------------------------------- commit 5444560b26a14750ae59578d354d98eaff9c7a41 Author: Herbert Valerio Riedel Date: Mon Dec 15 23:38:13 2014 +0100 update containers submodules to 0.5.6.1 release >--------------------------------------------------------------- 5444560b26a14750ae59578d354d98eaff9c7a41 libraries/containers | 2 +- testsuite/tests/package/package01e.stderr | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/containers b/libraries/containers index c802c36..ddf4e4a 160000 --- a/libraries/containers +++ b/libraries/containers @@ -1 +1 @@ -Subproject commit c802c36dbed4b800d8c2131181f5af3db837aded +Subproject commit ddf4e4a7abbfb81161251437a6a5bbe8167a7cde diff --git a/testsuite/tests/package/package01e.stderr b/testsuite/tests/package/package01e.stderr index 232ec6c..54f501c 100644 --- a/testsuite/tests/package/package01e.stderr +++ b/testsuite/tests/package/package01e.stderr @@ -1,10 +1,10 @@ package01e.hs:2:1: Failed to load interface for ?Data.Map? - It is a member of the hidden package ?containers-0.5.5.1?. + It is a member of the hidden package ?containers-0.5.6.1?. Use -v to see a list of the files searched for. package01e.hs:3:1: Failed to load interface for ?Data.IntMap? - It is a member of the hidden package ?containers-0.5.5.1?. + It is a member of the hidden package ?containers-0.5.6.1?. Use -v to see a list of the files searched for. From git at git.haskell.org Tue Dec 16 22:46:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Dec 2014 22:46:04 +0000 (UTC) Subject: [commit: ghc] master: Parser: use 'error' token in error reporting rules (ea788f0) Message-ID: <20141216224604.1131E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ea788f0fc53000afd264f0452f23b597887df9f9/ghc >--------------------------------------------------------------- commit ea788f0fc53000afd264f0452f23b597887df9f9 Author: Sergei Trofimovich Date: Tue Dec 16 22:16:42 2014 +0000 Parser: use 'error' token in error reporting rules Summary: It exempts us from 11 reduce/reduce conflicts and 12 shift/reduce conflicts. Signed-off-by: Sergei Trofimovich Reviewers: simonpj, mikeizbicki, austin, simonmar Reviewed By: simonmar Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D571 >--------------------------------------------------------------- ea788f0fc53000afd264f0452f23b597887df9f9 compiler/parser/Parser.y | 33 ++++++++++++++++++++------------- 1 file changed, 20 insertions(+), 13 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 023ea46..e990abb 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -88,6 +88,12 @@ import TysWiredIn ( unitTyCon, unitDataCon, tupleTyCon, tupleCon, nilDataC {- ----------------------------------------------------------------------------- +14 Dec 2014 + +Conflicts: 48 shift/reduce + 1 reduce/reduce + +----------------------------------------------------------------------------- 20 Nov 2014 Conflicts: 60 shift/reduce @@ -1969,33 +1975,34 @@ exp10 :: { LHsExpr RdrName } | fexp { $1 } -- parsing error messages go below here - | '\\' apat apats opt_asig '->' {% parseErrorSDoc (combineLocs $1 $5) $ text + | '\\' apat apats opt_asig '->' error {% parseErrorSDoc (combineLocs $1 $5) $ text "parse error in lambda: no expression after '->'" } - | '\\' {% parseErrorSDoc (getLoc $1) $ text + | '\\' error {% parseErrorSDoc (getLoc $1) $ text "parse error: naked lambda expression '\'" } - | 'let' binds 'in' {% parseErrorSDoc (combineLocs $1 $2) $ text + | 'let' binds 'in' error {% parseErrorSDoc (combineLocs $1 $2) $ text "parse error in let binding: missing expression after 'in'" } - | 'let' binds {% parseErrorSDoc (combineLocs $1 $2) $ text + | 'let' binds error {% parseErrorSDoc (combineLocs $1 $2) $ text "parse error in let binding: missing required 'in'" } - | 'let' {% parseErrorSDoc (getLoc $1) $ text + | 'let' error {% parseErrorSDoc (getLoc $1) $ text "parse error: naked let binding" } - | 'if' exp optSemi 'then' exp optSemi 'else' {% hintIf (combineLocs $1 $5) "else clause empty" } - | 'if' exp optSemi 'then' exp optSemi {% hintIf (combineLocs $1 $5) "missing required else clause" } - | 'if' exp optSemi 'then' {% hintIf (combineLocs $1 $2) "then clause empty" } - | 'if' exp optSemi {% hintIf (combineLocs $1 $2) "missing required then and else clauses" } - | 'if' {% hintIf (getLoc $1) "naked if statement" } - | 'case' exp 'of' {% parseErrorSDoc (combineLocs $1 $2) $ text + | 'if' exp optSemi 'then' exp optSemi + 'else' error {% hintIf (combineLocs $1 $5) "else clause empty" } + | 'if' exp optSemi 'then' exp optSemi error {% hintIf (combineLocs $1 $5) "missing required else clause" } + | 'if' exp optSemi 'then' error {% hintIf (combineLocs $1 $2) "then clause empty" } + | 'if' exp optSemi error {% hintIf (combineLocs $1 $2) "missing required then and else clauses" } + | 'if' error {% hintIf (getLoc $1) "naked if statement" } + | 'case' exp 'of' error {% parseErrorSDoc (combineLocs $1 $2) $ text "parse error in case statement: missing list after '->'" } - | 'case' exp {% parseErrorSDoc (combineLocs $1 $2) $ text + | 'case' exp error {% parseErrorSDoc (combineLocs $1 $2) $ text "parse error in case statement: missing required 'of'" } - | 'case' {% parseErrorSDoc (getLoc $1) $ text + | 'case' error {% parseErrorSDoc (getLoc $1) $ text "parse error: naked case statement" } optSemi :: { ([Located a],Bool) } From git at git.haskell.org Wed Dec 17 00:33:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 00:33:10 +0000 (UTC) Subject: [commit: ghc] master: Generate .loc/.file directives from source ticks (64678e9) Message-ID: <20141217003310.BD2A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/64678e9e8ff0107cac956f0c7b799a1dd317b963/ghc >--------------------------------------------------------------- commit 64678e9e8ff0107cac956f0c7b799a1dd317b963 Author: Peter Wortmann Date: Mon Dec 8 16:54:16 2014 +0100 Generate .loc/.file directives from source ticks This generates DWARF, albeit indirectly using the assembler. This is the easiest (and, apparently, quite standard) method of generating the .debug_line DWARF section. Notes: * Note we have to make sure that .file directives appear correctly before the respective .loc. Right now we ppr them manually, which makes them absent from dumps. Fixing this would require .file to become a native instruction. * We have to pass a lot of things around the native code generator. I know Ian did quite a bit of refactoring already, but having one common monad could *really* simplify things here... * To support SplitObjcs, we need to emit/reset all DWARF data at every split. We use the occassion to move split marker generation to cmmNativeGenStream as well, so debug data extraction doesn't have to choke on it. (From Phabricator D396) >--------------------------------------------------------------- 64678e9e8ff0107cac956f0c7b799a1dd317b963 compiler/nativeGen/AsmCodeGen.hs | 129 +++++++++++++++++------------ compiler/nativeGen/NCGMonad.hs | 37 ++++++++- compiler/nativeGen/RegAlloc/Linear/Main.hs | 4 +- compiler/nativeGen/X86/CodeGen.hs | 13 ++- compiler/nativeGen/X86/Instr.hs | 6 ++ compiler/nativeGen/X86/Ppr.hs | 5 ++ 6 files changed, 137 insertions(+), 57 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 64678e9e8ff0107cac956f0c7b799a1dd317b963 From git at git.haskell.org Wed Dec 17 00:33:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 00:33:13 +0000 (UTC) Subject: [commit: ghc] master: Generate DWARF unwind information (edd6d67) Message-ID: <20141217003313.9D5773A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/edd6d676847b94648c18b7f3790852ab4043759d/ghc >--------------------------------------------------------------- commit edd6d676847b94648c18b7f3790852ab4043759d Author: Peter Wortmann Date: Wed Dec 10 12:00:49 2014 +0100 Generate DWARF unwind information This tells debuggers such as GDB how to "unwind" a program state, which allows them to walk the stack up. Notes: * The code is quite general, perhaps unnecessarily so. Unless we get more unwind information, only the first case of pprSetUnwind will get used - and pprUnwindExpr and pprUndefUnwind will never be called. It just so happens that this is a point where we can get a lot of features cheaply, even if we don't use them. * When determining what location to show for a return address, most debuggers check the map for "rip-1", assuming that's where the "call" instruction is. For tables-next-to-code, that happens to always be the end of an info table. We therefore cheat a bit here by shifting .debug_frame information so it covers the end of the info table, as well as generating a .loc directive for the info table data. Debuggers will still show the wrong label for the return address, though. Haven't found a way around that one yet. (From Phabricator D396) >--------------------------------------------------------------- edd6d676847b94648c18b7f3790852ab4043759d compiler/nativeGen/Dwarf.hs | 45 ++++++- compiler/nativeGen/Dwarf/Constants.hs | 64 ++++++++- compiler/nativeGen/Dwarf/Types.hs | 236 +++++++++++++++++++++++++++++++++- compiler/nativeGen/X86/Ppr.hs | 6 + 4 files changed, 347 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 edd6d676847b94648c18b7f3790852ab4043759d From git at git.haskell.org Wed Dec 17 00:33:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 00:33:16 +0000 (UTC) Subject: [commit: ghc] master: Generate DWARF info section (cc481ec) Message-ID: <20141217003316.C3E803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cc481ec8657e0b91e2f8f9a9eeb3f9ee030635ae/ghc >--------------------------------------------------------------- commit cc481ec8657e0b91e2f8f9a9eeb3f9ee030635ae Author: Peter Wortmann Date: Tue Dec 9 20:59:07 2014 +0100 Generate DWARF info section This is where we actually make GHC emit DWARF code. The info section contains all the general meta information bits as well as an entry for every block of native code. Notes: * We need quite a few new labels in order to properly address starts and ends of blocks. * Thanks to Nathan Howell for taking the iniative to get our own Haskell language ID for DWARF! (From Phabricator D396) >--------------------------------------------------------------- cc481ec8657e0b91e2f8f9a9eeb3f9ee030635ae compiler/cmm/CLabel.hs | 30 ++++-- compiler/ghc.cabal.in | 3 + compiler/nativeGen/AsmCodeGen.hs | 73 +++++++------ compiler/nativeGen/Dwarf.hs | 120 ++++++++++++++++++++++ compiler/nativeGen/Dwarf/Constants.hs | 132 ++++++++++++++++++++++++ compiler/nativeGen/Dwarf/Types.hs | 186 ++++++++++++++++++++++++++++++++++ compiler/nativeGen/X86/Ppr.hs | 15 ++- 7 files changed, 519 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 cc481ec8657e0b91e2f8f9a9eeb3f9ee030635ae From git at git.haskell.org Wed Dec 17 10:04:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 10:04:43 +0000 (UTC) Subject: [commit: ghc] master: Update Haddock submodule (78ab79a) Message-ID: <20141217100443.DF44A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/78ab79aa9602f574c30d0c4782075c6402aca907/ghc >--------------------------------------------------------------- commit 78ab79aa9602f574c30d0c4782075c6402aca907 Author: Herbert Valerio Riedel Date: Wed Dec 17 11:04:55 2014 +0100 Update Haddock submodule This pulls in the fix for the broken `@since`-rendering >--------------------------------------------------------------- 78ab79aa9602f574c30d0c4782075c6402aca907 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 179a3fa..b8ffb16 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 179a3faca1524f6cb1cd21e0cefc2000bb6480be +Subproject commit b8ffb16aa4e146855c78594879662dc606ffe0b1 From git at git.haskell.org Wed Dec 17 10:48:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 10:48:28 +0000 (UTC) Subject: [commit: packages/stm] master: Add `@since` annotations (33238be) Message-ID: <20141217104828.744D83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm On branch : master Link : http://git.haskell.org/packages/stm.git/commitdiff/33238be50b8e7a18c0d39c4fefaf623763c41c4a >--------------------------------------------------------------- commit 33238be50b8e7a18c0d39c4fefaf623763c41c4a Author: Herbert Valerio Riedel Date: Wed Dec 17 11:40:36 2014 +0100 Add `@since` annotations >--------------------------------------------------------------- 33238be50b8e7a18c0d39c4fefaf623763c41c4a Control/Concurrent/STM/TBQueue.hs | 5 +++++ Control/Concurrent/STM/TChan.hs | 6 ++++++ Control/Concurrent/STM/TMVar.hs | 2 ++ Control/Concurrent/STM/TQueue.hs | 3 +++ Control/Concurrent/STM/TSem.hs | 2 ++ Control/Concurrent/STM/TVar.hs | 2 ++ 6 files changed, 20 insertions(+) diff --git a/Control/Concurrent/STM/TBQueue.hs b/Control/Concurrent/STM/TBQueue.hs index 00a7b51..bfe4a6b 100644 --- a/Control/Concurrent/STM/TBQueue.hs +++ b/Control/Concurrent/STM/TBQueue.hs @@ -24,6 +24,7 @@ -- queue representation that uses two lists to obtain amortised /O(1)/ -- enqueue and dequeue operations. -- +-- @since 2.4 ----------------------------------------------------------------------------- module Control.Concurrent.STM.TBQueue ( @@ -47,6 +48,8 @@ import GHC.Conc #define _UPK_(x) {-# UNPACK #-} !(x) -- | 'TBQueue' is an abstract type representing a bounded FIFO channel. +-- +-- @since 2.4 data TBQueue a = TBQueue _UPK_(TVar Int) -- CR: read capacity _UPK_(TVar [a]) -- R: elements waiting to be read @@ -180,6 +183,8 @@ isEmptyTBQueue (TBQueue _rsize read _wsize write) = do _ -> return False -- |Returns 'True' if the supplied 'TBQueue' is full. +-- +-- @since 2.4.3 isFullTBQueue :: TBQueue a -> STM Bool isFullTBQueue (TBQueue rsize _read wsize _write) = do w <- readTVar wsize diff --git a/Control/Concurrent/STM/TChan.hs b/Control/Concurrent/STM/TChan.hs index 8ca1734..af06fb4 100644 --- a/Control/Concurrent/STM/TChan.hs +++ b/Control/Concurrent/STM/TChan.hs @@ -95,6 +95,8 @@ newTChanIO = do -- it is only written to and never read, items will pile up in memory. By -- using 'newBroadcastTChan' to create the broadcast channel, items can be -- garbage collected after clients have seen them. +-- +-- @since 2.4 newBroadcastTChan :: STM (TChan a) newBroadcastTChan = do write_hole <- newTVar TNil @@ -103,6 +105,8 @@ newBroadcastTChan = do return (TChan read write) -- | @IO@ version of 'newBroadcastTChan'. +-- +-- @since 2.4 newBroadcastTChanIO :: IO (TChan a) newBroadcastTChanIO = do write_hole <- newTVarIO TNil @@ -189,6 +193,8 @@ isEmptyTChan (TChan read _write) = do -- |Clone a 'TChan': similar to dupTChan, but the cloned channel starts with the -- same content available as the original channel. +-- +-- @since 2.4 cloneTChan :: TChan a -> STM (TChan a) cloneTChan (TChan read write) = do readpos <- readTVar read diff --git a/Control/Concurrent/STM/TMVar.hs b/Control/Concurrent/STM/TMVar.hs index 932d4ca..e9477df 100644 --- a/Control/Concurrent/STM/TMVar.hs +++ b/Control/Concurrent/STM/TMVar.hs @@ -156,6 +156,8 @@ isEmptyTMVar (TMVar t) = do -- | Make a 'Weak' pointer to a 'TMVar', using the second argument as -- a finalizer to run when the 'TMVar' is garbage-collected. +-- +-- @since 2.4.4 mkWeakTMVar :: TMVar a -> IO () -> IO (Weak (TMVar a)) mkWeakTMVar tmv@(TMVar (TVar t#)) f = IO $ \s -> case mkWeak# t# tmv f s of (# s1, w #) -> (# s1, Weak w #) diff --git a/Control/Concurrent/STM/TQueue.hs b/Control/Concurrent/STM/TQueue.hs index 0b13ccd..c5c6cc6 100644 --- a/Control/Concurrent/STM/TQueue.hs +++ b/Control/Concurrent/STM/TQueue.hs @@ -28,6 +28,7 @@ -- queue representation that uses two lists to obtain amortised /O(1)/ -- enqueue and dequeue operations. -- +-- @since 2.4 ----------------------------------------------------------------------------- module Control.Concurrent.STM.TQueue ( @@ -49,6 +50,8 @@ import GHC.Conc import Data.Typeable (Typeable) -- | 'TQueue' is an abstract type representing an unbounded FIFO channel. +-- +-- @since 2.4 data TQueue a = TQueue {-# UNPACK #-} !(TVar [a]) {-# UNPACK #-} !(TVar [a]) deriving Typeable diff --git a/Control/Concurrent/STM/TSem.hs b/Control/Concurrent/STM/TSem.hs index 53f7f05..8f1d565 100644 --- a/Control/Concurrent/STM/TSem.hs +++ b/Control/Concurrent/STM/TSem.hs @@ -10,6 +10,7 @@ -- -- 'TSem': transactional semaphores. -- +-- @since 2.4.2 ----------------------------------------------------------------------------- {-# LANGUAGE DeriveDataTypeable #-} @@ -34,6 +35,7 @@ import Data.Typeable -- resource. However, like other STM abstractions, 'TSem' is -- composable. -- +-- @since 2.4.2 newtype TSem = TSem (TVar Int) deriving (Eq, Typeable) diff --git a/Control/Concurrent/STM/TVar.hs b/Control/Concurrent/STM/TVar.hs index 41888d4..709a7ca 100644 --- a/Control/Concurrent/STM/TVar.hs +++ b/Control/Concurrent/STM/TVar.hs @@ -73,6 +73,8 @@ swapTVar var new = do -- | Make a 'Weak' pointer to a 'TVar', using the second argument as -- a finalizer to run when 'TVar' is garbage-collected +-- +-- @since 2.4.3 mkWeakTVar :: TVar a -> IO () -> IO (Weak (TVar a)) mkWeakTVar t@(TVar t#) f = IO $ \s -> case mkWeak# t# t f s of (# s1, w #) -> (# s1, Weak w #) From git at git.haskell.org Wed Dec 17 10:48:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 10:48:30 +0000 (UTC) Subject: [commit: packages/stm] master: Bump to 2.4.4 and update changelog (b5cb4c4) Message-ID: <20141217104830.78E843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm On branch : master Link : http://git.haskell.org/packages/stm.git/commitdiff/b5cb4c462e008c666631c14435df0dd90fb20517 >--------------------------------------------------------------- commit b5cb4c462e008c666631c14435df0dd90fb20517 Author: Herbert Valerio Riedel Date: Wed Dec 17 11:41:23 2014 +0100 Bump to 2.4.4 and update changelog >--------------------------------------------------------------- b5cb4c462e008c666631c14435df0dd90fb20517 changelog.md | 8 +++++++- stm.cabal | 5 ++++- 2 files changed, 11 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md index faf959b..92b2a7f 100644 --- a/changelog.md +++ b/changelog.md @@ -1,9 +1,15 @@ # Changelog for [`stm` package](http://hackage.haskell.org/package/stm) -## 2.4.3.1 *TBA* +## 2.4.4 *Dec 2014* * Add support for `base-4.8.0.0` + * Tighten Safe Haskell bounds + + * Add `mkWeakTMVar` to `Control.Concurrent.STM.TMVar` + + * Add `@since`-annotations + ## 2.4.3 *Mar 2014* * Update behaviour of `newBroadcastTChanIO` to match diff --git a/stm.cabal b/stm.cabal index 5ea002a..668bb9d 100644 --- a/stm.cabal +++ b/stm.cabal @@ -1,5 +1,6 @@ name: stm -version: 2.4.3.1 +version: 2.4.4 +-- don't forget to update changelog.md file! license: BSD3 license-file: LICENSE maintainer: libraries at haskell.org @@ -29,6 +30,8 @@ library UnboxedTuples if impl(ghc >= 7.2) other-extensions: Trustworthy + if impl(ghc >= 7.9) + other-extensions: Safe build-depends: base >= 4.2 && < 4.9, From git at git.haskell.org Wed Dec 17 10:48:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 10:48:32 +0000 (UTC) Subject: [commit: packages/stm] master: Avoid AMP-caused redundant import warning (87c4dea) Message-ID: <20141217104832.7EDA73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm On branch : master Link : http://git.haskell.org/packages/stm.git/commitdiff/87c4dea145cb65258e93ce396480f371ffa85c0f >--------------------------------------------------------------- commit 87c4dea145cb65258e93ce396480f371ffa85c0f Author: Herbert Valerio Riedel Date: Wed Dec 17 11:48:04 2014 +0100 Avoid AMP-caused redundant import warning >--------------------------------------------------------------- 87c4dea145cb65258e93ce396480f371ffa85c0f Control/Sequential/STM.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/Control/Sequential/STM.hs b/Control/Sequential/STM.hs index 226c788..e855a61 100644 --- a/Control/Sequential/STM.hs +++ b/Control/Sequential/STM.hs @@ -19,7 +19,9 @@ module Control.Sequential.STM ( #if __GLASGOW_HASKELL__ < 705 import Prelude hiding (catch) #endif +#if __GLASGOW_HASKELL__ < 709 import Control.Applicative (Applicative(pure, (<*>))) +#endif import Control.Exception import Data.IORef From git at git.haskell.org Wed Dec 17 11:02:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 11:02:19 +0000 (UTC) Subject: [commit: packages/stm] tag 'stm-2.4.4-release' created Message-ID: <20141217110219.B42EA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm New tag : stm-2.4.4-release Referencing: 23e1fc3fe86a152a9f553d6ee7b3652940f0ea73 From git at git.haskell.org Wed Dec 17 11:04:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 11:04:56 +0000 (UTC) Subject: [commit: ghc] master: Update stm submodule to 2.4.4 release (0ac059d) Message-ID: <20141217110456.6ED873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0ac059dcd53bb41fdeb2a20af74ecc046a519b8f/ghc >--------------------------------------------------------------- commit 0ac059dcd53bb41fdeb2a20af74ecc046a519b8f Author: Herbert Valerio Riedel Date: Wed Dec 17 12:04:58 2014 +0100 Update stm submodule to 2.4.4 release >--------------------------------------------------------------- 0ac059dcd53bb41fdeb2a20af74ecc046a519b8f libraries/stm | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/stm b/libraries/stm index eadf716..b5cb4c4 160000 --- a/libraries/stm +++ b/libraries/stm @@ -1 +1 @@ -Subproject commit eadf71656bb1a75e2355aee1bd07843c8bd3482a +Subproject commit b5cb4c462e008c666631c14435df0dd90fb20517 From git at git.haskell.org Wed Dec 17 11:38:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 11:38:28 +0000 (UTC) Subject: [commit: ghc] master: Update deepseq submodule to 1.4.0.0 release (3745f42) Message-ID: <20141217113828.3B7DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3745f421753bb9e3d87e7166c866930c8385fa5d/ghc >--------------------------------------------------------------- commit 3745f421753bb9e3d87e7166c866930c8385fa5d Author: Herbert Valerio Riedel Date: Wed Dec 17 12:38:51 2014 +0100 Update deepseq submodule to 1.4.0.0 release >--------------------------------------------------------------- 3745f421753bb9e3d87e7166c866930c8385fa5d libraries/deepseq | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/deepseq b/libraries/deepseq index 8dc617d..a79bee5 160000 --- a/libraries/deepseq +++ b/libraries/deepseq @@ -1 +1 @@ -Subproject commit 8dc617dad456e16c67b0f629495dcf266a58ab0a +Subproject commit a79bee5f5da25353b88759cf5ed8d0df2b59946c From git at git.haskell.org Wed Dec 17 12:27:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 12:27:00 +0000 (UTC) Subject: [commit: ghc] master: Typos in comments (c9a0228) Message-ID: <20141217122700.73A0C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c9a02287a5cd14b71ac8a97711e018e9daa0abfc/ghc >--------------------------------------------------------------- commit c9a02287a5cd14b71ac8a97711e018e9daa0abfc Author: Gabor Greif Date: Wed Dec 17 12:36:07 2014 +0100 Typos in comments >--------------------------------------------------------------- c9a02287a5cd14b71ac8a97711e018e9daa0abfc compiler/codeGen/StgCmmMonad.hs | 2 +- testsuite/tests/codeGen/should_compile/Makefile | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/codeGen/StgCmmMonad.hs b/compiler/codeGen/StgCmmMonad.hs index fff8e28..f7a13f9 100644 --- a/compiler/codeGen/StgCmmMonad.hs +++ b/compiler/codeGen/StgCmmMonad.hs @@ -285,7 +285,7 @@ data ReturnKind -- clean up. -- -- There are some rarer cases of common blocks that we don't catch --- this way, but that's ok. Common-block-elimation is still available +-- this way, but that's ok. Common-block-elimination is still available -- to catch them when optimisation is enabled. Some examples are: -- -- - when both the True and False branches do a heap check, we diff --git a/testsuite/tests/codeGen/should_compile/Makefile b/testsuite/tests/codeGen/should_compile/Makefile index b186e0d..412c902 100644 --- a/testsuite/tests/codeGen/should_compile/Makefile +++ b/testsuite/tests/codeGen/should_compile/Makefile @@ -19,8 +19,8 @@ debug: > debug.cmm cat debug.cmm | grep -o src\ | sort -u - # Common block elimination should elimation should merge the - # blocks corresponding to alternatives 1 and 2, therefore there + # Common block elimination should merge the blocks + # corresponding to alternatives 1 and 2, therefore there # must be a block containing exactly these two annotations # directly next to each other. echo == CBE == From git at git.haskell.org Wed Dec 17 12:27:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 12:27:03 +0000 (UTC) Subject: [commit: ghc] master: Role problems pervent GND from happening (75c211e) Message-ID: <20141217122703.0E6043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/75c211ecafad890854f4a1f3e527bd42b13fc516/ghc >--------------------------------------------------------------- commit 75c211ecafad890854f4a1f3e527bd42b13fc516 Author: Gabor Greif Date: Wed Dec 17 12:49:51 2014 +0100 Role problems pervent GND from happening with GHC HEAD. Reworked using deriving instance. >--------------------------------------------------------------- 75c211ecafad890854f4a1f3e527bd42b13fc516 compiler/utils/UniqFM.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/compiler/utils/UniqFM.hs b/compiler/utils/UniqFM.hs index 8f962d4..e24c717 100644 --- a/compiler/utils/UniqFM.hs +++ b/compiler/utils/UniqFM.hs @@ -23,7 +23,9 @@ of arguments of combining function. {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveTraversable #-} +{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE StandaloneDeriving #-} {-# OPTIONS_GHC -Wall #-} module UniqFM ( @@ -211,9 +213,11 @@ instance Monoid (UniqFM a) where -} newtype UniqFM ele = UFM (M.IntMap ele) - deriving (Data, Eq, Foldable.Foldable, Functor, Traversable.Traversable, + deriving (Data, Eq, Functor, Traversable.Traversable, Typeable) +deriving instance Foldable.Foldable UniqFM + emptyUFM = UFM M.empty isNullUFM (UFM m) = M.null m unitUFM k v = UFM (M.singleton (getKey $ getUnique k) v) From git at git.haskell.org Wed Dec 17 14:07:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 14:07:37 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T9889' created Message-ID: <20141217140737.A99AD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T9889 Referencing: 7f801ff8b1286c330466c5de65fca1b5c19d07f1 From git at git.haskell.org Wed Dec 17 14:07:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 14:07:40 +0000 (UTC) Subject: [commit: ghc] wip/T9889: Pattern synonym names need to be in scope before renaming bindings (#9889) (7f801ff) Message-ID: <20141217140740.8F9B03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9889 Link : http://ghc.haskell.org/trac/ghc/changeset/7f801ff8b1286c330466c5de65fca1b5c19d07f1/ghc >--------------------------------------------------------------- commit 7f801ff8b1286c330466c5de65fca1b5c19d07f1 Author: Dr. ERDI Gergo Date: Wed Dec 17 22:05:05 2014 +0800 Pattern synonym names need to be in scope before renaming bindings (#9889) >--------------------------------------------------------------- 7f801ff8b1286c330466c5de65fca1b5c19d07f1 compiler/hsSyn/HsUtils.hs | 30 +++++++++++++++----------- compiler/rename/RnBinds.hs | 6 +++--- compiler/rename/RnNames.hs | 11 +++++++--- compiler/rename/RnSource.hs | 2 +- testsuite/tests/patsyn/should_compile/T9889.hs | 5 +++++ testsuite/tests/patsyn/should_compile/all.T | 1 + 6 files changed, 36 insertions(+), 19 deletions(-) diff --git a/compiler/hsSyn/HsUtils.hs b/compiler/hsSyn/HsUtils.hs index 6694138..77e2c93 100644 --- a/compiler/hsSyn/HsUtils.hs +++ b/compiler/hsSyn/HsUtils.hs @@ -61,6 +61,7 @@ module HsUtils( -- Collecting binders collectLocalBinders, collectHsValBinders, collectHsBindListBinders, + collectHsValNewBinders, collectHsBindsBinders, collectHsBindBinders, collectMethodBinders, collectPatBinders, collectPatsBinders, collectLStmtsBinders, collectStmtsBinders, @@ -604,31 +605,36 @@ collectHsValBinders :: HsValBindsLR idL idR -> [idL] collectHsValBinders (ValBindsIn binds _) = collectHsBindsBinders binds collectHsValBinders (ValBindsOut binds _) = foldr collect_one [] binds where - collect_one (_,binds) acc = collect_binds binds acc + collect_one (_,binds) acc = collect_binds False binds acc + +collectHsValNewBinders :: HsValBindsLR Name idR -> [Name] +collectHsValNewBinders (ValBindsIn binds _) = collect_binds True binds [] +collectHsValNewBinders ValBindsOut{} = panic "collectHsValNewBinders" collectHsBindBinders :: HsBindLR idL idR -> [idL] -collectHsBindBinders b = collect_bind b [] +collectHsBindBinders b = collect_bind False b [] -collect_bind :: HsBindLR idL idR -> [idL] -> [idL] -collect_bind (PatBind { pat_lhs = p }) acc = collect_lpat p acc -collect_bind (FunBind { fun_id = L _ f }) acc = f : acc -collect_bind (VarBind { var_id = f }) acc = f : acc -collect_bind (AbsBinds { abs_exports = dbinds, abs_binds = _binds }) acc +collect_bind :: Bool -> HsBindLR idL idR -> [idL] -> [idL] +collect_bind _ (PatBind { pat_lhs = p }) acc = collect_lpat p acc +collect_bind _ (FunBind { fun_id = L _ f }) acc = f : acc +collect_bind _ (VarBind { var_id = f }) acc = f : acc +collect_bind _ (AbsBinds { abs_exports = dbinds, abs_binds = _binds }) acc = map abe_poly dbinds ++ acc -- ++ foldr collect_bind acc binds -- I don't think we want the binders from the nested binds -- The only time we collect binders from a typechecked -- binding (hence see AbsBinds) is in zonking in TcHsSyn -collect_bind (PatSynBind (PSB { psb_id = L _ ps })) acc = ps : acc +collect_bind omitPatSyn (PatSynBind (PSB { psb_id = L _ ps })) acc = + if omitPatSyn then acc else ps : acc collectHsBindsBinders :: LHsBindsLR idL idR -> [idL] -collectHsBindsBinders binds = collect_binds binds [] +collectHsBindsBinders binds = collect_binds False binds [] collectHsBindListBinders :: [LHsBindLR idL idR] -> [idL] -collectHsBindListBinders = foldr (collect_bind . unLoc) [] +collectHsBindListBinders = foldr (collect_bind False . unLoc) [] -collect_binds :: LHsBindsLR idL idR -> [idL] -> [idL] -collect_binds binds acc = foldrBag (collect_bind . unLoc) acc binds +collect_binds :: Bool -> LHsBindsLR idL idR -> [idL] -> [idL] +collect_binds omitPatSyn binds acc = foldrBag (collect_bind omitPatSyn . unLoc) acc binds collectMethodBinders :: LHsBindsLR RdrName idR -> [Located RdrName] -- Used exclusively for the bindings of an instance decl which are all FunBinds diff --git a/compiler/rename/RnBinds.hs b/compiler/rename/RnBinds.hs index 1af93f3..edbcc9c 100644 --- a/compiler/rename/RnBinds.hs +++ b/compiler/rename/RnBinds.hs @@ -436,12 +436,12 @@ rnBindLHS name_maker _ bind@(FunBind { fun_id = name@(L nameLoc _) }) ; return (bind { fun_id = L nameLoc newname , bind_fvs = placeHolderNamesTc }) } -rnBindLHS name_maker _ (PatSynBind psb at PSB{ psb_id = rdrname@(L nameLoc _) }) +rnBindLHS name_maker _ (PatSynBind psb at PSB{ psb_id = rdrname }) = do { unless (isTopRecNameMaker name_maker) $ addErr localPatternSynonymErr ; addLocM checkConName rdrname - ; name <- applyNameMaker name_maker rdrname - ; return (PatSynBind psb{ psb_id = L nameLoc name }) } + ; name <- lookupLocatedTopBndrRn rdrname + ; return (PatSynBind psb{ psb_id = name }) } where localPatternSynonymErr :: SDoc localPatternSynonymErr diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs index bff2ed0..237e6c3 100644 --- a/compiler/rename/RnNames.hs +++ b/compiler/rename/RnNames.hs @@ -40,6 +40,7 @@ import ErrUtils import Util import FastString import ListSetOps +import Bag import Control.Monad import Data.Map ( Map ) @@ -507,11 +508,11 @@ getLocalNonValBinders fixity_env ; nti_avails <- concatMapM new_assoc inst_decls -- Finish off with value binders: - -- foreign decls for an ordinary module + -- foreign decls and pattern synonyms for an ordinary module -- type sigs in case of a hs-boot file only ; is_boot <- tcIsHsBootOrSig ; let val_bndrs | is_boot = hs_boot_sig_bndrs - | otherwise = for_hs_bndrs + | otherwise = for_hs_bndrs ++ patsyn_hs_bndrs ; val_avails <- mapM new_simple val_bndrs ; let avails = nti_avails ++ val_avails @@ -525,11 +526,15 @@ getLocalNonValBinders fixity_env for_hs_bndrs = [ L decl_loc (unLoc nm) | L decl_loc (ForeignImport nm _ _ _) <- foreign_decls] + patsyn_hs_bndrs :: [Located RdrName] + patsyn_hs_bndrs = [ L decl_loc (unLoc n) + | L decl_loc (PatSynBind PSB{ psb_id = n }) <- bagToList val_bag] + -- In a hs-boot file, the value binders come from the -- *signatures*, and there should be no foreign binders hs_boot_sig_bndrs = [ L decl_loc (unLoc n) | L decl_loc (TypeSig ns _ _) <- val_sigs, n <- ns] - ValBindsIn _ val_sigs = val_binds + ValBindsIn val_bag val_sigs = val_binds -- the SrcSpan attached to the input should be the span of the -- declaration, not just the name diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index 95211cb..4395329 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -114,7 +114,7 @@ rnSrcDecls extra_deps group@(HsGroup { hs_valds = val_decls, -- It uses the fixity env from (A) to bind fixities for view patterns. new_lhs <- rnTopBindsLHS local_fix_env val_decls ; -- bind the LHSes (and their fixities) in the global rdr environment - let { val_binders = collectHsValBinders new_lhs ; + let { val_binders = collectHsValNewBinders new_lhs ; all_bndrs = extendNameSetList tc_bndrs val_binders ; val_avails = map Avail val_binders } ; traceRn (text "rnSrcDecls" <+> ppr val_avails) ; diff --git a/testsuite/tests/patsyn/should_compile/T9889.hs b/testsuite/tests/patsyn/should_compile/T9889.hs new file mode 100644 index 0000000..f418a51 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T9889.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE PatternSynonyms #-} + +pattern Id x = x + +Id x = True diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index 91c0012..db6cfb5 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -20,3 +20,4 @@ test('T8968-2', normal, compile, ['']) test('T8968-3', normal, compile, ['']) test('ImpExp_Imp', [extra_clean(['ImpExp_Exp.hi', 'ImpExp_Exp.o'])], multimod_compile, ['ImpExp_Imp', '-v0']) test('T9857', normal, compile, ['']) +test('T9889', normal, compile, ['']) From git at git.haskell.org Wed Dec 17 14:11:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 14:11:39 +0000 (UTC) Subject: [commit: ghc] wip/T9889: Pattern synonym names need to be in scope before renaming bindings (#9889) (e5f429c) Message-ID: <20141217141139.4C1C43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9889 Link : http://ghc.haskell.org/trac/ghc/changeset/e5f429cbc02df745df1517d53c8ca170de41757b/ghc >--------------------------------------------------------------- commit e5f429cbc02df745df1517d53c8ca170de41757b Author: Dr. ERDI Gergo Date: Wed Dec 17 22:09:06 2014 +0800 Pattern synonym names need to be in scope before renaming bindings (#9889) >--------------------------------------------------------------- e5f429cbc02df745df1517d53c8ca170de41757b compiler/hsSyn/HsUtils.hs | 30 +++++++++++++--------- compiler/rename/RnBinds.hs | 6 ++--- compiler/rename/RnNames.hs | 11 +++++--- compiler/rename/RnSource.hs | 2 +- .../patsyn/should_compile/{num.hs => T9889.hs} | 6 ++--- testsuite/tests/patsyn/should_compile/all.T | 1 + testsuite/tests/patsyn/should_fail/local.stderr | 2 ++ 7 files changed, 36 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 e5f429cbc02df745df1517d53c8ca170de41757b From git at git.haskell.org Wed Dec 17 14:45:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 14:45:39 +0000 (UTC) Subject: [commit: ghc] master: Fix the scope-nesting for arrows (f50d62b) Message-ID: <20141217144539.542CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f50d62bb6c0357991fabf938bc971d528bbf5cc4/ghc >--------------------------------------------------------------- commit f50d62bb6c0357991fabf938bc971d528bbf5cc4 Author: Simon Peyton Jones Date: Tue Dec 16 17:34:26 2014 +0000 Fix the scope-nesting for arrows Previously we were capturing the *entire environment* when moving under a 'proc', for the newArrowScope/escapeArrowScope thing. But that a blunderbuss, and in any case isn't right (the untouchable-type-varaible invariant gets invalidated). So I fixed it to be much more refined: just the LocalRdrEnv and constraints are captured. I think this is right; but if not we should just add more fields to ArrowCtxt, not return to the blunderbuss. This patch fixes the ASSERT failure in Trac #5267 >--------------------------------------------------------------- f50d62bb6c0357991fabf938bc971d528bbf5cc4 compiler/typecheck/TcArrows.hs | 3 +- compiler/typecheck/TcRnMonad.hs | 22 ++++++++++++++ compiler/typecheck/TcRnTypes.hs | 34 ++++++++++------------ testsuite/tests/arrows/should_fail/T5380.stderr | 2 +- testsuite/tests/arrows/should_fail/all.T | 7 +++-- .../tests/arrows/should_fail/arrowfail001.stderr | 5 ++-- 6 files changed, 45 insertions(+), 28 deletions(-) diff --git a/compiler/typecheck/TcArrows.hs b/compiler/typecheck/TcArrows.hs index f1546b4..b4c3bcc 100644 --- a/compiler/typecheck/TcArrows.hs +++ b/compiler/typecheck/TcArrows.hs @@ -197,8 +197,6 @@ tc_cmd env cmd@(HsCmdArrApp fun arg _ ho_app lr) (_, res_ty) do { arg_ty <- newFlexiTyVarTy openTypeKind ; let fun_ty = mkCmdArrTy env arg_ty res_ty ; fun' <- select_arrow_scope (tcMonoExpr fun fun_ty) - -- ToDo: There should be no need for the escapeArrowScope stuff - -- See Note [Escaping the arrow scope] in TcRnTypes ; arg' <- tcMonoExpr arg arg_ty @@ -208,6 +206,7 @@ tc_cmd env cmd@(HsCmdArrApp fun arg _ ho_app lr) (_, res_ty) -- proc for the (-<) case. -- Local bindings, inside the enclosing proc, are not in scope -- inside f. In the higher-order case (-<<), they are. + -- See Note [Escaping the arrow scope] in TcRnTypes select_arrow_scope tc = case ho_app of HsHigherOrderApp -> tc HsFirstOrderApp -> escapeArrowScope tc diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs index 013b8a4..77f2f61 100644 --- a/compiler/typecheck/TcRnMonad.hs +++ b/compiler/typecheck/TcRnMonad.hs @@ -380,6 +380,28 @@ getEpsAndHpt = do { env <- getTopEnv; eps <- readMutVar (hsc_EPS env) {- ************************************************************************ * * + Arrow scopes +* * +************************************************************************ +-} + +newArrowScope :: TcM a -> TcM a +newArrowScope + = updLclEnv $ \env -> env { tcl_arrow_ctxt = ArrowCtxt (tcl_rdr env) (tcl_lie env) } + +-- Return to the stored environment (from the enclosing proc) +escapeArrowScope :: TcM a -> TcM a +escapeArrowScope + = updLclEnv $ \ env -> + case tcl_arrow_ctxt env of + NoArrowCtxt -> env + ArrowCtxt rdr_env lie -> env { tcl_arrow_ctxt = NoArrowCtxt + , tcl_lie = lie + , tcl_rdr = rdr_env } + +{- +************************************************************************ +* * Unique supply * * ************************************************************************ diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index 7035bf3..260a636 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -45,7 +45,7 @@ module TcRnTypes( ThLevel, impLevel, outerLevel, thLevel, -- Arrows - ArrowCtxt(NoArrowCtxt), newArrowScope, escapeArrowScope, + ArrowCtxt(..), -- Canonical constraints Xi, Ct(..), Cts, emptyCts, andCts, andManyCts, pprCts, @@ -603,7 +603,7 @@ data TcLclEnv -- Changes as we move inside an expression = TcLclEnv { tcl_loc :: SrcSpan, -- Source span tcl_ctxt :: [ErrCtxt], -- Error context, innermost on top - tcl_tclvl :: TcLevel, -- Birthplace for new unification variables + tcl_tclvl :: TcLevel, -- Birthplace for new unification variables tcl_th_ctxt :: ThStage, -- Template Haskell context tcl_th_bndrs :: ThBindEnv, -- Binding level of in-scope Names @@ -761,26 +761,22 @@ recording the environment when passing a proc (using newArrowScope), and returning to that (using escapeArrowScope) on the left of -< and the head of (|..|). -All this can be dealt with by the *renamer*; by the time we get to -the *type checker* we have sorted out the scopes +All this can be dealt with by the *renamer*. But the type checker needs +to be involved too. Example (arrowfail001) + class Foo a where foo :: a -> () + data Bar = forall a. Foo a => Bar a + get :: Bar -> () + get = proc x -> case x of Bar a -> foo -< a +Here the call of 'foo' gives rise to a (Foo a) constraint that should not +be captured by the pattern match on 'Bar'. Rather it should join the +constraints from further out. So we must capture the constraint bag +from further out in the ArrowCtxt that we push inwards. -} -data ArrowCtxt +data ArrowCtxt -- Note [Escaping the arrow scope] = NoArrowCtxt - | ArrowCtxt (Env TcGblEnv TcLclEnv) - --- Record the current environment (outside a proc) -newArrowScope :: TcM a -> TcM a -newArrowScope - = updEnv $ \env -> - env { env_lcl = (env_lcl env) { tcl_arrow_ctxt = ArrowCtxt env } } - --- Return to the stored environment (from the enclosing proc) -escapeArrowScope :: TcM a -> TcM a -escapeArrowScope - = updEnv $ \ env -> case tcl_arrow_ctxt (env_lcl env) of - NoArrowCtxt -> env - ArrowCtxt env' -> env' + | ArrowCtxt LocalRdrEnv (TcRef WantedConstraints) + --------------------------- -- TcTyThing diff --git a/testsuite/tests/arrows/should_fail/T5380.stderr b/testsuite/tests/arrows/should_fail/T5380.stderr index 02e65c5..1f8d451 100644 --- a/testsuite/tests/arrows/should_fail/T5380.stderr +++ b/testsuite/tests/arrows/should_fail/T5380.stderr @@ -24,4 +24,4 @@ T5380.hs:7:34: testB :: not_bool -> (() -> ()) -> () -> not_unit (bound at T5380.hs:7:1) In the expression: f - In the expression: proc () -> if b then f -< () else f -< () + In the command: f -< () diff --git a/testsuite/tests/arrows/should_fail/all.T b/testsuite/tests/arrows/should_fail/all.T index 6b7920d..b798860 100644 --- a/testsuite/tests/arrows/should_fail/all.T +++ b/testsuite/tests/arrows/should_fail/all.T @@ -1,12 +1,13 @@ setTestOpts(only_compiler_types(['ghc'])) test('arrowfail001', - when(compiler_debugged(), expect_broken(5267)), + normal, compile_fail, ['']) - # arrowfail001 gets an ASSERT error in the stage1 compiler + # arrowfail001 got an ASSERT error in the stage1 compiler # because we simply are not typechecking arrow commands - # correcly. See Trac #5267, #5609, #5605 + # correctly. See Trac #5267, #5609, #5605 + # The fix is patch 'Fix the scope-nesting for arrows' Dec 2014 test('arrowfail002', normal, compile_fail, ['']) test('arrowfail003', normal, compile_fail, ['']) diff --git a/testsuite/tests/arrows/should_fail/arrowfail001.stderr b/testsuite/tests/arrows/should_fail/arrowfail001.stderr index 5c448c7..7805f80 100644 --- a/testsuite/tests/arrows/should_fail/arrowfail001.stderr +++ b/testsuite/tests/arrows/should_fail/arrowfail001.stderr @@ -2,6 +2,5 @@ arrowfail001.hs:16:36: No instance for (Foo a) arising from a use of ?foo? In the expression: foo - In the expression: proc x -> case x of { Bar a -> foo -< a } - In an equation for ?get?: - get = proc x -> case x of { Bar a -> foo -< a } + In the command: foo -< a + In a case alternative: Bar a -> foo -< a From git at git.haskell.org Wed Dec 17 14:45:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 14:45:41 +0000 (UTC) Subject: [commit: ghc] master: Improve an ASSERT (082cf13) Message-ID: <20141217144541.E50F53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/082cf137fdec4d5534e01e45a4e64fd157326db8/ghc >--------------------------------------------------------------- commit 082cf137fdec4d5534e01e45a4e64fd157326db8 Author: Simon Peyton Jones Date: Tue Dec 16 17:34:49 2014 +0000 Improve an ASSERT >--------------------------------------------------------------- 082cf137fdec4d5534e01e45a4e64fd157326db8 compiler/codeGen/StgCmmExpr.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/codeGen/StgCmmExpr.hs index ee63550..e54ae46 100644 --- a/compiler/codeGen/StgCmmExpr.hs +++ b/compiler/codeGen/StgCmmExpr.hs @@ -642,7 +642,7 @@ cgConApp con stg_args ; emitReturn arg_exprs } | otherwise -- Boxed constructors; allocate and return - = ASSERT( stg_args `lengthIs` dataConRepRepArity con ) + = ASSERT2( stg_args `lengthIs` dataConRepRepArity con, ppr con <+> ppr stg_args ) do { (idinfo, fcode_init) <- buildDynCon (dataConWorkId con) False currentCCS con stg_args -- The first "con" says that the name bound to this From git at git.haskell.org Wed Dec 17 14:45:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 14:45:44 +0000 (UTC) Subject: [commit: ghc] master: Use the new LintFlags to suppress Lint warnings for INLINE loop breakers (c436537) Message-ID: <20141217144544.820F23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c43653722ed89f30dae29e7a2117afbc2f269b76/ghc >--------------------------------------------------------------- commit c43653722ed89f30dae29e7a2117afbc2f269b76 Author: Simon Peyton Jones Date: Tue Dec 16 17:36:01 2014 +0000 Use the new LintFlags to suppress Lint warnings for INLINE loop breakers See Note [Checking for INLINE loop breakers] >--------------------------------------------------------------- c43653722ed89f30dae29e7a2117afbc2f269b76 compiler/coreSyn/CoreLint.hs | 36 ++++++++++++++++++++++++++---------- 1 file changed, 26 insertions(+), 10 deletions(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index 7b57ba2..ea1befe 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -249,11 +249,6 @@ displayLintResults dflags pass warns errs binds ; Err.ghcExit dflags 1 } | not (isEmptyBag warns) - , not (case pass of { CoreDesugar -> True; _ -> False }) - -- Suppress warnings after desugaring pass because some - -- are legitimate. Notably, the desugarer generates instance - -- methods with INLINE pragmas that form a mutually recursive - -- group. Only afer a round of simplification are they unravelled. , not opt_NoDebugOutput , showLintWarnings pass = log_action dflags dflags Err.SevDump noSrcSpan defaultDumpStyle @@ -337,7 +332,8 @@ lintCoreBindings pass local_in_scope binds ; checkL (null ext_dups) (dupExtVars ext_dups) ; mapM lint_bind binds } where - flags = LF { lf_check_global_ids = check_globals } + flags = LF { lf_check_global_ids = check_globals + , lf_check_inline_loop_breakers = check_lbs } -- See Note [Checking for global Ids] check_globals = case pass of @@ -345,6 +341,12 @@ lintCoreBindings pass local_in_scope binds CorePrep -> False _ -> True + -- See Note [Checking for INLINE loop breakers] + check_lbs = case pass of + CoreDesugar -> False + CoreDesugarOpt -> False + _ -> True + binders = bindersOfBinds binds (_, dups) = removeDups compare binders @@ -446,7 +448,10 @@ lintSingleBinding top_lvl_flag rec_flag (binder,rhs) -- Check whether binder's specialisations contain any out-of-scope variables ; mapM_ (checkBndrIdInScope binder) bndr_vars - ; when (isStrongLoopBreaker (idOccInfo binder) && isInlinePragma (idInlinePragma binder)) + ; flags <- getLintFlags + ; when (lf_check_inline_loop_breakers flags + && isStrongLoopBreaker (idOccInfo binder) + && isInlinePragma (idInlinePragma binder)) (addWarnL (ptext (sLit "INLINE binder is (non-rule) loop breaker:") <+> ppr binder)) -- Only non-rule loop breakers inhibit inlining @@ -482,6 +487,15 @@ lintIdUnfolding _ _ _ = return () -- We could check more {- +Note [Checking for INLINE loop breakers] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +It's very suspicious if a strong loop breaker is marked INLINE. + +However, the desugarer generates instance methods with INLINE pragmas +that form a mutually recursive group. Only afer a round of +simplification are they unravelled. So we suppress the test for +the desugarer. + ************************************************************************ * * \subsection[lintCoreExpr]{lintCoreExpr} @@ -1277,12 +1291,14 @@ data LintEnv } -- to keep track of all the variables in scope, -- both Ids and TyVars -newtype LintFlags -- Currently only one flag - = LF { lf_check_global_ids :: Bool -- See Note [Checking for global Ids] +data LintFlags + = LF { lf_check_global_ids :: Bool -- See Note [Checking for global Ids] + , lf_check_inline_loop_breakers :: Bool -- See Note [Checking for INLINE loop breakers] } defaultLintFlags :: LintFlags -defaultLintFlags = LF { lf_check_global_ids = False } +defaultLintFlags = LF { lf_check_global_ids = False + , lf_check_inline_loop_breakers = True } newtype LintM a = LintM { unLintM :: From git at git.haskell.org Wed Dec 17 14:45:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 14:45:47 +0000 (UTC) Subject: [commit: ghc] master: Fix GHCi/GHC-API tidying and modules (Trac #9424, #9426) (67a0cab) Message-ID: <20141217144547.3DB193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/67a0cab6b501e2d6280b51655af66ad448b3deef/ghc >--------------------------------------------------------------- commit 67a0cab6b501e2d6280b51655af66ad448b3deef Author: Simon Peyton Jones Date: Tue Dec 16 17:46:06 2014 +0000 Fix GHCi/GHC-API tidying and modules (Trac #9424, #9426) There were two related bugs here Trac #9426 We must increment the ic_mod_index field of the InteractiveContext if we have new instances, because we maek DFunIds that should be distinct from previous ones. Previously we were only incrementing when defining new user-visible Ids. The main change is in HscTypes.extendInteractiveContext, which now alwyas bumps the ic_mod_index. I also added a specialised extendInteractiveContextWithIds for the case where we are *only* adding new user-visible Ids. Trac #9424 In HscMain.hscDeclsWithLocations we were failing to use the *tidied* ClsInsts; but the un-tidied ones are LocalIds which causes a later ASSERT error. On the way I realised that, to behave consistently, the tcg_insts and tcg_fam_insts field of TcGblEnv should really only contain instances from the current GHCi command, not all the ones to date. That in turn meant I had to move the code for deleting replacement instances from addLocalInst, addLocalFamInst to HscTypes.extendInteractiveContext >--------------------------------------------------------------- 67a0cab6b501e2d6280b51655af66ad448b3deef compiler/ghci/Debugger.hs | 6 +-- compiler/main/HscMain.hs | 18 ++++----- compiler/main/HscTypes.hs | 84 ++++++++++++++++++++++++++++++---------- compiler/main/InteractiveEval.hs | 12 +++--- compiler/main/TidyPgm.hs | 8 ++-- compiler/typecheck/FamInst.hs | 11 +++--- compiler/typecheck/Inst.hs | 17 ++++---- compiler/typecheck/TcRnDriver.hs | 2 - compiler/typecheck/TcRnTypes.hs | 5 ++- compiler/types/FamInstEnv.hs | 10 ++--- compiler/types/InstEnv.hs | 13 ++++--- docs/users_guide/ghci.xml | 7 ++-- 12 files changed, 117 insertions(+), 76 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 67a0cab6b501e2d6280b51655af66ad448b3deef From git at git.haskell.org Wed Dec 17 14:45:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 14:45:50 +0000 (UTC) Subject: [commit: ghc] master: Improve TidyPgm.hasCafRefs to account for Integer literals (Trac #8525) (6b11bab) Message-ID: <20141217144550.17B453A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6b11bab6961a1518a15eaa3d3b4ce40702724ca5/ghc >--------------------------------------------------------------- commit 6b11bab6961a1518a15eaa3d3b4ce40702724ca5 Author: Simon Peyton Jones Date: Tue Dec 16 17:53:00 2014 +0000 Improve TidyPgm.hasCafRefs to account for Integer literals (Trac #8525) See Note [Disgusting computation of CafRefs] in TidyPgm. Also affects CoreUtils.rhsIsStatic. The real solution here is to compute CAF and arity information from the STG-program, and feed it back to tidied program for the interface file and later GHCi clients. A battle for another day. But at least this commit reduces the number of gratuitous CAFs, and hence SRT entries. And kills off a batch of ASSERT failures. >--------------------------------------------------------------- 6b11bab6961a1518a15eaa3d3b4ce40702724ca5 compiler/coreSyn/CorePrep.hs | 2 + compiler/coreSyn/CoreUtils.hs | 25 ++++++---- compiler/main/TidyPgm.hs | 100 +++++++++++++++++++++----------------- testsuite/tests/lib/integer/all.T | 3 +- 4 files changed, 74 insertions(+), 56 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6b11bab6961a1518a15eaa3d3b4ce40702724ca5 From git at git.haskell.org Wed Dec 17 14:45:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 14:45:52 +0000 (UTC) Subject: [commit: ghc] master: Comment in test (2469f85) Message-ID: <20141217144552.BC4873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2469f854e6457d6723f12a61b88a6d9c7766ab4f/ghc >--------------------------------------------------------------- commit 2469f854e6457d6723f12a61b88a6d9c7766ab4f Author: Simon Peyton Jones Date: Tue Dec 16 17:53:15 2014 +0000 Comment in test >--------------------------------------------------------------- 2469f854e6457d6723f12a61b88a6d9c7766ab4f testsuite/tests/stranal/should_compile/T9208.hs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/testsuite/tests/stranal/should_compile/T9208.hs b/testsuite/tests/stranal/should_compile/T9208.hs index d3415bb..2252617 100644 --- a/testsuite/tests/stranal/should_compile/T9208.hs +++ b/testsuite/tests/stranal/should_compile/T9208.hs @@ -1,6 +1,16 @@ {-# LANGUAGE CPP, LambdaCase, BangPatterns, MagicHash, TupleSections, ScopedTypeVariables #-} {-# OPTIONS_GHC -w #-} -- Suppress warnings for unimplemented methods +------------- WARNING --------------------- +-- +-- This program is utterly bogus. It takes a value of type () +-- and unsafe-coerces it to a function, and applies it. +-- This is caught by an ASSERT with a debug compiler. +-- +-- See Trac #9208 for discussio +-- +-------------------------------------------- + {- | Evaluate Template Haskell splices on node.js, using pipes to communicate with GHCJS -} From git at git.haskell.org Wed Dec 17 14:45:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 14:45:55 +0000 (UTC) Subject: [commit: ghc] master: Fix egregious bug in the new canonicalisation code for AppTy (517908f) Message-ID: <20141217144555.B2ED33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/517908fce0cdae9d0ae987fa7474ee235533c77a/ghc >--------------------------------------------------------------- commit 517908fce0cdae9d0ae987fa7474ee235533c77a Author: Simon Peyton Jones Date: Wed Dec 17 14:20:51 2014 +0000 Fix egregious bug in the new canonicalisation code for AppTy Fixes Trac #9892. Must form part of 7.10.1 >--------------------------------------------------------------- 517908fce0cdae9d0ae987fa7474ee235533c77a compiler/typecheck/TcCanonical.hs | 12 +++++++----- testsuite/tests/typecheck/should_compile/T9892.hs | 16 ++++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 2 ++ 3 files changed, 25 insertions(+), 5 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index cc1197d..493e742 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -626,7 +626,9 @@ try_decompose_app :: CtEvidence -> EqRel -- so can't turn it into an application if it -- doesn't look like one already -- See Note [Canonicalising type applications] -try_decompose_app ev NomEq ty1 ty2 = try_decompose_nom_app ev ty1 ty2 +try_decompose_app ev NomEq ty1 ty2 + = try_decompose_nom_app ev ty1 ty2 + try_decompose_app ev ReprEq ty1 ty2 | ty1 `eqType` ty2 -- See Note [AppTy reflexivity check] = canEqReflexive ev ReprEq ty1 @@ -654,17 +656,17 @@ try_decompose_nom_app ev ty1 ty2 = canEqNC ev NomEq ty1 ty2 where -- do_decompose is like xCtEvidence, but recurses - -- to try_decompose_app to decompose a chain of AppTys + -- to try_decompose_nom_app to decompose a chain of AppTys do_decompose s1 t1 s2 t2 | CtDerived { ctev_loc = loc } <- ev = do { emitNewDerived loc (mkTcEqPred t1 t2) - ; try_decompose_nom_app ev s1 s2 } + ; canEqNC ev NomEq s1 s2 } | CtWanted { ctev_evar = evar, ctev_loc = loc } <- ev = do { ev_s <- newWantedEvVarNC loc (mkTcEqPred s1 s2) ; co_t <- unifyWanted loc Nominal t1 t2 ; let co = mkTcAppCo (ctEvCoercion ev_s) co_t ; setEvBind evar (EvCoercion co) - ; try_decompose_nom_app ev_s s1 s2 } + ; canEqNC ev_s NomEq s1 s2 } | CtGiven { ctev_evtm = ev_tm, ctev_loc = loc } <- ev = do { let co = evTermCoercion ev_tm co_s = mkTcLRCo CLeft co @@ -672,7 +674,7 @@ try_decompose_nom_app ev ty1 ty2 ; evar_s <- newGivenEvVar loc (mkTcEqPred s1 s2, EvCoercion co_s) ; evar_t <- newGivenEvVar loc (mkTcEqPred t1 t2, EvCoercion co_t) ; emitWorkNC [evar_t] - ; try_decompose_nom_app evar_s s1 s2 } + ; canEqNC evar_s NomEq s1 s2 } | otherwise -- Can't happen = error "try_decompose_app" diff --git a/testsuite/tests/typecheck/should_compile/T9892.hs b/testsuite/tests/typecheck/should_compile/T9892.hs new file mode 100644 index 0000000..adb0f29 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T9892.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE UndecidableInstances #-} + +module T9892 where + +import Control.Applicative +import Control.Category +import Prelude hiding ((.),id) + +newtype FocusingPlus w k s a = FocusingPlus { unfocusingPlus :: k (s, w) a } + +instance Functor (k (s, w)) => Functor (FocusingPlus w k s) where + fmap f (FocusingPlus as) = FocusingPlus (fmap f as) + +instance Applicative (k (s, w)) => Applicative (FocusingPlus w k s) where + pure = FocusingPlus . pure + FocusingPlus kf <*> FocusingPlus ka = FocusingPlus (kf <*> ka) diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 7d33ad5..d1b3796 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -436,3 +436,5 @@ test('T9497b', normal, compile, ['-fdefer-typed-holes -fno-warn-typed-holes']) test('T9497c', normal, compile, ['-fdefer-type-errors -fno-warn-typed-holes']) test('T7643', normal, compile, ['']) test('T9834', normal, compile, ['']) +test('T9892', normal, compile, ['']) + From git at git.haskell.org Wed Dec 17 14:45:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 14:45:58 +0000 (UTC) Subject: [commit: ghc] master: Wibble error message (ea22a8f) Message-ID: <20141217144558.4F3183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ea22a8f721f440458554c7500686baef57da4d4d/ghc >--------------------------------------------------------------- commit ea22a8f721f440458554c7500686baef57da4d4d Author: Simon Peyton Jones Date: Wed Dec 17 14:30:28 2014 +0000 Wibble error message >--------------------------------------------------------------- ea22a8f721f440458554c7500686baef57da4d4d testsuite/tests/indexed-types/should_fail/T7729.stderr | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/indexed-types/should_fail/T7729.stderr b/testsuite/tests/indexed-types/should_fail/T7729.stderr index 053d54e..1f3d19d 100644 --- a/testsuite/tests/indexed-types/should_fail/T7729.stderr +++ b/testsuite/tests/indexed-types/should_fail/T7729.stderr @@ -1,6 +1,6 @@ T7729.hs:36:14: - Couldn't match type ?t0 (BasePrimMonad m)? with ?BasePrimMonad m? + Couldn't match type ?BasePrimMonad m? with ?t0 (BasePrimMonad m)? The type variable ?t0? is ambiguous Expected type: t0 (BasePrimMonad m) a -> Rand m a Actual type: BasePrimMonad (Rand m) a -> Rand m a From git at git.haskell.org Wed Dec 17 15:46:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 15:46:24 +0000 (UTC) Subject: [commit: ghc] master: Performance enhancements in TcFlatten. (922168f) Message-ID: <20141217154624.171FA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/922168fda3b3a3b96033a9c5d38f3fe70a99fd63/ghc >--------------------------------------------------------------- commit 922168fda3b3a3b96033a9c5d38f3fe70a99fd63 Author: Richard Eisenberg Date: Tue Dec 16 16:35:43 2014 -0500 Performance enhancements in TcFlatten. This commit fixes some performance regressions introduced by 0cc47eb, adding more `Coercible` magic to the solver. See Note [flatten_many performance] in TcFlatten for more info. The improvements do not quite restore the old numbers. Given that the solver is really more involved now, I am accepting this regression. The way forward (I believe) would be to have *two* flatteners: one that deals only with nominal equalities and thus never checks roles, and the more general one. A nice design of keeping this performant without duplicating code eludes me, but someone else is welcome to take a stab. >--------------------------------------------------------------- 922168fda3b3a3b96033a9c5d38f3fe70a99fd63 compiler/typecheck/TcFlatten.hs | 83 ++++++++++++++++++++++++++++++++----- compiler/utils/MonadUtils.hs | 3 ++ testsuite/tests/perf/compiler/all.T | 16 ++++--- 3 files changed, 87 insertions(+), 15 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 922168fda3b3a3b96033a9c5d38f3fe70a99fd63 From git at git.haskell.org Wed Dec 17 16:23:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 16:23:27 +0000 (UTC) Subject: [commit: ghc] master: Typos in comments (ae1f271) Message-ID: <20141217162327.60F743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ae1f2718e795feb908fdeba87b4945f5566d6d1a/ghc >--------------------------------------------------------------- commit ae1f2718e795feb908fdeba87b4945f5566d6d1a Author: Gabor Greif Date: Wed Dec 17 16:13:26 2014 +0100 Typos in comments >--------------------------------------------------------------- ae1f2718e795feb908fdeba87b4945f5566d6d1a compiler/simplCore/Simplify.hs | 2 +- compiler/typecheck/TcHsType.hs | 2 +- compiler/typecheck/TcSimplify.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index b950f57..db7f5a6 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -2644,7 +2644,7 @@ Note [Funky mkPiTypes] ~~~~~~~~~~~~~~~~~~~~~~ Notice the funky mkPiTypes. If the contructor has existentials it's possible that the join point will be abstracted over -type varaibles as well as term variables. +type variables as well as term variables. Example: Suppose we have data T = forall t. C [t] Then faced with diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 44ba79b..1221b7f 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -1374,7 +1374,7 @@ Here the type of x's first component is called 'a1' in one branch and they definitely won't have the sane lexical Name. I think we could solve this by recording in a SigTv a list of all the -in-scope varaibles that it should not unify with, but it's fiddly. +in-scope variables that it should not unify with, but it's fiddly. ************************************************************************ diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 7e9c408..01da61f 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -634,7 +634,7 @@ and if so refrain from quantifying over *any* equalites. simplifyRule :: RuleName -> WantedConstraints -- Constraints from LHS -> WantedConstraints -- Constraints from RHS - -> TcM ([EvVar], WantedConstraints) -- LHS evidence varaibles + -> TcM ([EvVar], WantedConstraints) -- LHS evidence variables -- See Note [Simplifying RULE constraints] in TcRule simplifyRule name lhs_wanted rhs_wanted = do { -- We allow ourselves to unify environment diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 2ff482c..595e853 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1095,7 +1095,7 @@ Then in the family instance we want to KindFam (Maybe k) k' a b = T k k' a b -> Int Notice that in the third step we quantify over all the visibly-mentioned -type variables (a,b), but also over the implicitly mentioned kind varaibles +type variables (a,b), but also over the implicitly mentioned kind variables (k, k'). In this case one is bound explicitly but often there will be none. The role of the kind signature (a :: Maybe k) is to add a constraint that 'a' must have that kind, and to bring 'k' into scope. From git at git.haskell.org Wed Dec 17 16:23:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 16:23:50 +0000 (UTC) Subject: [commit: ghc] master: Typo in note (7719b63) Message-ID: <20141217162350.AAF493A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7719b637863a34532606c42419adef82b46cb808/ghc >--------------------------------------------------------------- commit 7719b637863a34532606c42419adef82b46cb808 Author: Gabor Greif Date: Wed Dec 17 16:26:39 2014 +0100 Typo in note >--------------------------------------------------------------- 7719b637863a34532606c42419adef82b46cb808 compiler/coreSyn/CoreLint.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index ea1befe..7c636b4 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -492,7 +492,7 @@ Note [Checking for INLINE loop breakers] It's very suspicious if a strong loop breaker is marked INLINE. However, the desugarer generates instance methods with INLINE pragmas -that form a mutually recursive group. Only afer a round of +that form a mutually recursive group. Only after a round of simplification are they unravelled. So we suppress the test for the desugarer. From git at git.haskell.org Wed Dec 17 16:23:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Dec 2014 16:23:53 +0000 (UTC) Subject: [commit: ghc] master: Minor typo in comment (9868622) Message-ID: <20141217162353.483783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/98686223db4df7268cf2fcda99011431519d2a89/ghc >--------------------------------------------------------------- commit 98686223db4df7268cf2fcda99011431519d2a89 Author: Gabor Greif Date: Wed Dec 17 17:04:24 2014 +0100 Minor typo in comment >--------------------------------------------------------------- 98686223db4df7268cf2fcda99011431519d2a89 testsuite/tests/stranal/should_compile/T9208.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/stranal/should_compile/T9208.hs b/testsuite/tests/stranal/should_compile/T9208.hs index 2252617..f587da7 100644 --- a/testsuite/tests/stranal/should_compile/T9208.hs +++ b/testsuite/tests/stranal/should_compile/T9208.hs @@ -7,7 +7,7 @@ -- and unsafe-coerces it to a function, and applies it. -- This is caught by an ASSERT with a debug compiler. -- --- See Trac #9208 for discussio +-- See Trac #9208 for discussion -- -------------------------------------------- From git at git.haskell.org Thu Dec 18 02:45:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Dec 2014 02:45:37 +0000 (UTC) Subject: [commit: ghc] master: Add a provenance field to universal coercions. (1d4e94d) Message-ID: <20141218024537.4B8763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1d4e94d1ab18e2f089cd17b1a1f9ebd3cd6b7879/ghc >--------------------------------------------------------------- commit 1d4e94d1ab18e2f089cd17b1a1f9ebd3cd6b7879 Author: Iavor S. Diatchki Date: Wed Dec 17 18:46:36 2014 -0800 Add a provenance field to universal coercions. Universal coercions allow casting between arbitrary types, so it is a good idea to keep track where they came from, which now we can do by using the provenance field in `UnivCo`. This is also handy for type-checker plugins that provide functionality beyond what's expressible by GHC's standard coercions: such plugins can generate universal coercions, but they should still tag them, so that if something goes wrong we can link the casts to the plugin. >--------------------------------------------------------------- 1d4e94d1ab18e2f089cd17b1a1f9ebd3cd6b7879 compiler/coreSyn/CoreLint.hs | 2 +- compiler/coreSyn/TrieMap.hs | 7 +++++-- compiler/deSugar/DsBinds.hs | 2 +- compiler/iface/IfaceSyn.hs | 2 +- compiler/iface/IfaceType.hs | 14 ++++++++------ compiler/iface/TcIface.hs | 2 +- compiler/typecheck/TcHsSyn.hs | 4 ++-- compiler/typecheck/TcType.hs | 2 +- compiler/types/Coercion.hs | 43 +++++++++++++++++++++++-------------------- compiler/types/OptCoercion.hs | 20 ++++++++++---------- 10 files changed, 53 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 1d4e94d1ab18e2f089cd17b1a1f9ebd3cd6b7879 From git at git.haskell.org Thu Dec 18 04:33:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Dec 2014 04:33:22 +0000 (UTC) Subject: [commit: ghc] wip/rae: Consider equality contexts exotic, uninferrable by "deriving" (9b22b72) Message-ID: <20141218043322.EE5E83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/9b22b72bbf5a83a99b0ea998f0aa3b3d4d7fb79a/ghc >--------------------------------------------------------------- commit 9b22b72bbf5a83a99b0ea998f0aa3b3d4d7fb79a Author: Richard Eisenberg Date: Tue Dec 16 17:15:49 2014 -0500 Consider equality contexts exotic, uninferrable by "deriving" See comments in #8984. This takes back the fix for #6088. >--------------------------------------------------------------- 9b22b72bbf5a83a99b0ea998f0aa3b3d4d7fb79a compiler/typecheck/TcValidity.hs | 4 +--- testsuite/tests/indexed-types/should_compile/all.T | 1 - .../tests/indexed-types/{should_compile => should_fail}/T6088.hs | 0 testsuite/tests/indexed-types/should_fail/all.T | 1 + 4 files changed, 2 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index 8575cf8..ca8b63a 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -878,10 +878,8 @@ validDerivPred :: TyVarSet -> PredType -> Bool validDerivPred tv_set pred = case classifyPredType pred of ClassPred _ tys -> check_tys tys - -- EqPred ReprEq is a Coercible constraint; treat - -- like a class - EqPred ReprEq ty1 ty2 -> check_tys [ty1, ty2] TuplePred ps -> all (validDerivPred tv_set) ps + EqPred {} -> False -- reject equality constraints _ -> True -- Non-class predicates are ok where check_tys tys = hasNoDups fvs diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index ae15c27..928a70d 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -194,7 +194,6 @@ test('T6152', run_command, ['$MAKE -s --no-print-directory T6152']) -test('T6088', normal, compile, ['']) test('T7082', normal, compile, ['']) test('Overlap1', normal, compile, ['']) diff --git a/testsuite/tests/indexed-types/should_compile/T6088.hs b/testsuite/tests/indexed-types/should_fail/T6088.hs similarity index 100% rename from testsuite/tests/indexed-types/should_compile/T6088.hs rename to testsuite/tests/indexed-types/should_fail/T6088.hs diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index 93085af..fd4001a 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -131,3 +131,4 @@ test('BadSock', normal, compile_fail, ['']) test('T9580', normal, multimod_compile_fail, ['T9580', '']) test('T9662', normal, compile_fail, ['']) test('T7862', normal, compile_fail, ['']) +test('T6088', normal, compile_fail, ['']) From git at git.haskell.org Thu Dec 18 04:33:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Dec 2014 04:33:25 +0000 (UTC) Subject: [commit: ghc] wip/rae: Merge some instances from th-orphans. (830989a) Message-ID: <20141218043325.833443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/830989a17071b7d594ea6a72ac680f093e386974/ghc >--------------------------------------------------------------- commit 830989a17071b7d594ea6a72ac680f093e386974 Author: Richard Eisenberg Date: Tue Dec 16 17:17:06 2014 -0500 Merge some instances from th-orphans. >--------------------------------------------------------------- 830989a17071b7d594ea6a72ac680f093e386974 libraries/template-haskell/Language/Haskell/TH/Ppr.hs | 14 ++++++++++++++ libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 3 +++ 2 files changed, 17 insertions(+) diff --git a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs index 0f828eb..63fa80b 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs @@ -211,6 +211,9 @@ pprBody eq body = case body of | otherwise = arrow ------------------------------ +instance Ppr Lit where + ppr = pprLit noPrec + pprLit :: Precedence -> Lit -> Doc pprLit i (IntPrimL x) = parensIf (i > noPrec && x < 0) (integer x <> char '#') @@ -576,3 +579,14 @@ hashParens d = text "(# " <> d <> text " #)" quoteParens :: Doc -> Doc quoteParens d = text "'(" <> d <> text ")" + +----------------------------- +instance Ppr Loc where + ppr (Loc { loc_module = mod + , loc_package = pkg + , loc_start = (start_ln, start_col) + , loc_end = (end_ln, end_col) }) + = hcat [ text pkg, colon, text mod, colon + , parens $ int start_ln <> comma <> int start_col + , text "-" + , parens $ int end_ln <> comma <> int end_col ] diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 3634ef7..abdde2d 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -457,6 +457,9 @@ instance Lift Integer where instance Lift Int where lift x = return (LitE (IntegerL (fromIntegral x))) +instance Lift Word8 where + lift x = return (LitE (IntegerL (fromIntegral x))) + instance Lift Rational where lift x = return (LitE (RationalL x)) From git at git.haskell.org Thu Dec 18 04:33:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Dec 2014 04:33:28 +0000 (UTC) Subject: [commit: ghc] wip/rae: Clarify that declaration splices exist at top level only. (#9880) (383a95f) Message-ID: <20141218043328.1D07F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/383a95f909cca6cfdea43c2b8955bcc432d1709d/ghc >--------------------------------------------------------------- commit 383a95f909cca6cfdea43c2b8955bcc432d1709d Author: Richard Eisenberg Date: Tue Dec 16 17:21:42 2014 -0500 Clarify that declaration splices exist at top level only. (#9880) >--------------------------------------------------------------- 383a95f909cca6cfdea43c2b8955bcc432d1709d docs/users_guide/glasgow_exts.xml | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index a502262..86ceb06 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -9015,11 +9015,13 @@ Wiki page. have type Q Pat a type; the spliced expression must have type Q Type - a list of declarations; the spliced expression + a list of declarations at top level; the spliced expression must have type Q [Dec] Inside a splice you can only call functions defined in imported modules, - not functions defined elsewhere in the same module. + not functions defined elsewhere in the same module. Note that + declaration splices are not allowed anywhere except at top level + (outside any other declarations). A expression quotation is written in Oxford brackets, thus: From git at git.haskell.org Thu Dec 18 04:33:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Dec 2014 04:33:30 +0000 (UTC) Subject: [commit: ghc] wip/rae's head updated: Clarify that declaration splices exist at top level only. (#9880) (383a95f) Message-ID: <20141218043330.8B3093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/rae' now includes: 288c7c6 Parser: remove unused rule (copy/paste error) 1886fca Only use -fasm on platforms with an NCG (Closes: #9884). 7f63432 Update Haddock submodule to latest `master` tip ef7eb8f Revert "Update Haddock submodule to latest `master` tip" fa31e8f powerpc: fix and enable shared libraries by default on linux 0c9c2d8 Re-Update Haddock submodule to latest `master` tip 8dc7549 Update `time` submodule to final 1.5.0.1 release c7d559d Update `filepath` submodule to current 1.3.1.0 RC b037981 Update `binary` submodule to final 0.7.2.3 release 87c4e18 Fixup bad haddock.base perf-num bump in 0c9c2d89 71105ae Update `bytestring` submodule to 0.10.6.0 RC fbb42b2 Pattern-synonym matcher and builder Ids must be *LocalIds* d59c59f Make Core Lint check for locally-bound GlobalIds 8afdf27 stm: update submodule for #9169 addition f44333e Changing prefetch primops to have a `seq`-like interface bd0f9e1 Write release notes for -XStaticPointers. 4822283 Fix panic on [t| _ |] (Trac #9879) 3f87866 Fix dll-split problem with patch 'Make Core Lint check for locally-bound GlobalId' a972bdd Improve documentation of syntax for promoted lists a3e6915 Wibbles to documentation for promoted lists and tuples (Trac #9882) 2a18019 stm: Update submodule (again) to fix build breakage feab4e2 Fix comments (#8254) a30dbc6 comment about why this program exists 192128d comments 493bf37 Update haskeline/terminfo submodules to master b317904 Update unix submodule to latest 2.7.1.0 snapshot f0cf7af Update process submodule to latest 1.2.1.0 RC abd2ada Typo in feature description 06ba981 *Really* Re-Update Haddock submodule 4a7489b Use llvm-3.5 on Travis 45a9696 Fix broken Haddock markup in `Monad` documentation 554aeda Convert `/Since: .../` to new `@since ...` syntax 1b5d758 Make annotations-literals test case cleaning less aggressive 993975d Source notes (Core support) 3b893f3 Generalized Coverage pass to allow adding multiple types of Tickishs 07d604f Annotation linting 4cdbf80 Source notes (CorePrep and Stg support) a0895fc Strip source ticks from iface code if DWARF is disabled 7ceaf96 Source notes (Cmm support) 5fecd76 Tick scopes 711a51a Add unwind information to Cmm f46aa73 Debug data extraction (NCG support) c630614 Debug test case and test suite way 9b22b72 Consider equality contexts exotic, uninferrable by "deriving" 830989a Merge some instances from th-orphans. 383a95f Clarify that declaration splices exist at top level only. (#9880) From git at git.haskell.org Thu Dec 18 07:31:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Dec 2014 07:31:10 +0000 (UTC) Subject: [commit: ghc] master: Update Haddock submodule (a11987a) Message-ID: <20141218073110.8DD183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a11987add29b2134fb53f17f0e97bb95616d8aa9/ghc >--------------------------------------------------------------- commit a11987add29b2134fb53f17f0e97bb95616d8aa9 Author: Mateusz Kowalczyk Date: Thu Dec 18 07:32:07 2014 +0000 Update Haddock submodule >--------------------------------------------------------------- a11987add29b2134fb53f17f0e97bb95616d8aa9 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index b8ffb16..60ccf50 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit b8ffb16aa4e146855c78594879662dc606ffe0b1 +Subproject commit 60ccf50433d823f18ee63e9c25c979e7b81f2fc1 From git at git.haskell.org Thu Dec 18 08:56:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Dec 2014 08:56:58 +0000 (UTC) Subject: [commit: ghc] master: Amend TcPluginM interface (726ea08) Message-ID: <20141218085658.66E8D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/726ea08a6e5899ccefe9b9bd65738141f257fc13/ghc >--------------------------------------------------------------- commit 726ea08a6e5899ccefe9b9bd65738141f257fc13 Author: Adam Gundry Date: Thu Dec 18 08:04:20 2014 +0000 Amend TcPluginM interface Summary: Expose some new functions in TcPluginM and remove one, in the light of experience writing plugins. In particular, I've removed lookupRdrName because using it to import modules containing instances leads to subtle bugs; I've expanded on the lookupRdrNameInModuleForPlugins comments. Test Plan: validate Reviewers: simonpj, austin Reviewed By: austin Subscribers: goldfire, ezyang, carter, thomie, yav, gridaphobe Differential Revision: https://phabricator.haskell.org/D553 Conflicts: compiler/typecheck/TcSMonad.hs >--------------------------------------------------------------- 726ea08a6e5899ccefe9b9bd65738141f257fc13 compiler/main/DynamicLoading.hs | 14 ++++++++++---- compiler/typecheck/TcPluginM.hs | 31 +++++++++++++++++++++++-------- compiler/typecheck/TcSMonad.hs | 9 ++++++--- 3 files changed, 39 insertions(+), 15 deletions(-) diff --git a/compiler/main/DynamicLoading.hs b/compiler/main/DynamicLoading.hs index 95321cf..82081bf 100644 --- a/compiler/main/DynamicLoading.hs +++ b/compiler/main/DynamicLoading.hs @@ -184,14 +184,20 @@ lessUnsafeCoerce dflags context what = do return output --- | Finds the 'Name' corresponding to the given 'RdrName' in the context of the 'ModuleName'. Returns @Nothing@ if no --- such 'Name' could be found. Any other condition results in an exception: +-- | Finds the 'Name' corresponding to the given 'RdrName' in the +-- context of the 'ModuleName'. Returns @Nothing@ if no such 'Name' +-- could be found. Any other condition results in an exception: -- -- * If the module could not be found -- * If we could not determine the imports of the module -- --- Can only be used for lookuping up names while handling plugins. --- This was introduced by 57d6798. +-- Can only be used for looking up names while loading plugins (and is +-- *not* suitable for use within plugins). The interface file is +-- loaded very partially: just enough that it can be used, without its +-- rules and instances affecting (and being linked from!) the module +-- being compiled. This was introduced by 57d6798. +-- +-- See Note [Care with plugin imports] in LoadIface. lookupRdrNameInModuleForPlugins :: HscEnv -> ModuleName -> RdrName -> IO (Maybe Name) lookupRdrNameInModuleForPlugins hsc_env mod_name rdr_name = do -- First find the package the module resides in by searching exposed packages and home modules diff --git a/compiler/typecheck/TcPluginM.hs b/compiler/typecheck/TcPluginM.hs index 9ba89cc..5acf1b8 100644 --- a/compiler/typecheck/TcPluginM.hs +++ b/compiler/typecheck/TcPluginM.hs @@ -10,8 +10,12 @@ module TcPluginM ( tcPluginTrace, unsafeTcPluginTcM, - -- * Lookup - lookupRdrName, + -- * Finding Modules and Names + FindResult(..), + findImportedModule, + lookupOrig, + + -- * Looking up Names in the typechecking environment tcLookupGlobal, tcLookupTyCon, tcLookupDataCon, @@ -24,6 +28,7 @@ module TcPluginM ( getEnvs, getInstEnvs, getFamInstEnvs, + matchFam, -- * Type variables newFlexiTyVar, @@ -37,29 +42,32 @@ module TcPluginM ( #ifdef GHCI import qualified TcRnMonad +import qualified TcSMonad import qualified TcEnv import qualified TcMType import qualified Inst import qualified FamInst +import qualified IfaceEnv +import qualified Finder import FamInstEnv ( FamInstEnv ) import TcRnMonad ( TcGblEnv, TcLclEnv, Ct, TcPluginM , unsafeTcPluginTcM, liftIO, traceTc ) import TcMType ( TcTyVar, TcType ) import TcEnv ( TcTyThing ) +import TcEvidence ( TcCoercion ) import Module import Name -import RdrName import TyCon import DataCon import Class import HscTypes import Outputable import Type -import DynamicLoading import Id import InstEnv +import FastString -- | Perform some IO, typically to interact with an external tool. @@ -71,10 +79,14 @@ tcPluginTrace :: String -> SDoc -> TcPluginM () tcPluginTrace a b = unsafeTcPluginTcM (traceTc a b) -lookupRdrName :: ModuleName -> RdrName -> TcPluginM (Maybe Name) -lookupRdrName mod rdr = do - hsc_env <- getTopEnv - tcPluginIO $ lookupRdrNameInModuleForPlugins hsc_env mod rdr +findImportedModule :: ModuleName -> Maybe FastString -> TcPluginM FindResult +findImportedModule mod_name mb_pkg = do + hsc_env <- getTopEnv + tcPluginIO $ Finder.findImportedModule hsc_env mod_name mb_pkg + +lookupOrig :: Module -> OccName -> TcPluginM Name +lookupOrig mod = unsafeTcPluginTcM . IfaceEnv.lookupOrig mod + tcLookupGlobal :: Name -> TcPluginM TyThing tcLookupGlobal = unsafeTcPluginTcM . TcEnv.tcLookupGlobal @@ -107,6 +119,9 @@ getInstEnvs = unsafeTcPluginTcM Inst.tcGetInstEnvs getFamInstEnvs :: TcPluginM (FamInstEnv, FamInstEnv) getFamInstEnvs = unsafeTcPluginTcM FamInst.tcGetFamInstEnvs +matchFam :: TyCon -> [Type] -> TcPluginM (Maybe (TcCoercion, TcType)) +matchFam tycon args = unsafeTcPluginTcM $ TcSMonad.matchFamTcM tycon args + newFlexiTyVar :: Kind -> TcPluginM TcTyVar newFlexiTyVar = unsafeTcPluginTcM . TcMType.newFlexiTyVar diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index a0dda96..4c9ab2f 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -80,7 +80,7 @@ module TcSMonad ( -- Misc getDefaultInfo, getDynFlags, getGlobalRdrEnvTcS, - matchFam, + matchFam, matchFamTcM, checkWellStagedDFun, pprEq -- Smaller utils, re-exported from TcM -- TODO (DV): these are only really used in the @@ -1739,9 +1739,12 @@ instDFunConstraints loc = mapM (newWantedEvVar loc) matchFam :: TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcType)) +matchFam tycon args = wrapTcS $ matchFamTcM tycon args + +matchFamTcM :: TyCon -> [Type] -> TcM (Maybe (TcCoercion, TcType)) -- Given (F tys) return (ty, co), where co :: F tys ~ ty -matchFam tycon args - = do { fam_envs <- getFamInstEnvs +matchFamTcM tycon args + = do { fam_envs <- FamInst.tcGetFamInstEnvs ; return $ fmap (first TcCoercion) $ reduceTyFamApp_maybe fam_envs Nominal tycon args } From git at git.haskell.org Thu Dec 18 11:19:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Dec 2014 11:19:03 +0000 (UTC) Subject: [commit: ghc] master: Fix wrong-kind-of-family error message (Trac #9896) (6ec9e95) Message-ID: <20141218111903.A32C53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6ec9e958d6a6693dedbcbfc74f164d38e5fb5381/ghc >--------------------------------------------------------------- commit 6ec9e958d6a6693dedbcbfc74f164d38e5fb5381 Author: Simon Peyton Jones Date: Thu Dec 18 11:19:14 2014 +0000 Fix wrong-kind-of-family error message (Trac #9896) >--------------------------------------------------------------- 6ec9e958d6a6693dedbcbfc74f164d38e5fb5381 compiler/typecheck/TcTyClsDecls.hs | 4 ++-- testsuite/tests/indexed-types/should_fail/SimpleFail3a.stderr | 2 +- testsuite/tests/indexed-types/should_fail/T9896.hs | 8 ++++++++ testsuite/tests/indexed-types/should_fail/T9896.stderr | 5 +++++ testsuite/tests/indexed-types/should_fail/all.T | 1 + testsuite/tests/typecheck/should_fail/AssocTyDef03.stderr | 2 +- 6 files changed, 18 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 595e853..6545e7b 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -2223,8 +2223,8 @@ wrongKindOfFamily family = ptext (sLit "Wrong category of family instance; declaration was for a") <+> kindOfFamily where - kindOfFamily | isTypeSynonymTyCon family = text "type synonym" - | isAlgTyCon family = text "data type" + kindOfFamily | isTypeFamilyTyCon family = text "type family" + | isDataFamilyTyCon family = text "data family" | otherwise = pprPanic "wrongKindOfFamily" (ppr family) wrongNumberOfParmsErr :: Arity -> SDoc diff --git a/testsuite/tests/indexed-types/should_fail/SimpleFail3a.stderr b/testsuite/tests/indexed-types/should_fail/SimpleFail3a.stderr index 7db6f3b..795188e 100644 --- a/testsuite/tests/indexed-types/should_fail/SimpleFail3a.stderr +++ b/testsuite/tests/indexed-types/should_fail/SimpleFail3a.stderr @@ -1,5 +1,5 @@ SimpleFail3a.hs:10:3: - Wrong category of family instance; declaration was for a data type + Wrong category of family instance; declaration was for a data family In the type instance declaration for ?S1? In the instance declaration for ?C1 Int? diff --git a/testsuite/tests/indexed-types/should_fail/T9896.hs b/testsuite/tests/indexed-types/should_fail/T9896.hs new file mode 100644 index 0000000..ca5238e --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T9896.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE TypeFamilies #-} +module T9896 where + +class Test a where + type TestT a :: * + +instance Test Bool where + newtype TestT Bool = Int diff --git a/testsuite/tests/indexed-types/should_fail/T9896.stderr b/testsuite/tests/indexed-types/should_fail/T9896.stderr new file mode 100644 index 0000000..f46e406 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T9896.stderr @@ -0,0 +1,5 @@ + +T9896.hs:8:3: + Wrong category of family instance; declaration was for a type family + In the newtype instance declaration for ?TestT? + In the instance declaration for ?Test Bool? diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index 93085af..821342c 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -131,3 +131,4 @@ test('BadSock', normal, compile_fail, ['']) test('T9580', normal, multimod_compile_fail, ['T9580', '']) test('T9662', normal, compile_fail, ['']) test('T7862', normal, compile_fail, ['']) +test('T9896', normal, compile_fail, ['']) diff --git a/testsuite/tests/typecheck/should_fail/AssocTyDef03.stderr b/testsuite/tests/typecheck/should_fail/AssocTyDef03.stderr index c0950bc..0f0c951 100644 --- a/testsuite/tests/typecheck/should_fail/AssocTyDef03.stderr +++ b/testsuite/tests/typecheck/should_fail/AssocTyDef03.stderr @@ -1,5 +1,5 @@ AssocTyDef03.hs:6:5: - Wrong category of family instance; declaration was for a data type + Wrong category of family instance; declaration was for a data family In the default type instance declaration for ?Typ? In the class declaration for ?Cls? From git at git.haskell.org Thu Dec 18 20:49:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Dec 2014 20:49:12 +0000 (UTC) Subject: [commit: ghc] master: Update `bytestring` submodule (989831d) Message-ID: <20141218204912.39FBD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/989831d41d1e47795aa3cba45e580511e0590b18/ghc >--------------------------------------------------------------- commit 989831d41d1e47795aa3cba45e580511e0590b18 Author: Herbert Valerio Riedel Date: Thu Dec 18 21:49:17 2014 +0100 Update `bytestring` submodule this just pulls in the version bump to 0.10.6 >--------------------------------------------------------------- 989831d41d1e47795aa3cba45e580511e0590b18 libraries/bytestring | 2 +- testsuite/tests/safeHaskell/check/pkg01/ImpSafe03.stderr | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/bytestring b/libraries/bytestring index cb85a53..fa7e1cc 160000 --- a/libraries/bytestring +++ b/libraries/bytestring @@ -1 +1 @@ -Subproject commit cb85a5360bc540c88b3ae1886d07c741bec3cdaa +Subproject commit fa7e1cc94982c0da85a022a501eadb1b347ea60c diff --git a/testsuite/tests/safeHaskell/check/pkg01/ImpSafe03.stderr b/testsuite/tests/safeHaskell/check/pkg01/ImpSafe03.stderr index 0a012f7..74b08a9 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/ImpSafe03.stderr +++ b/testsuite/tests/safeHaskell/check/pkg01/ImpSafe03.stderr @@ -1,4 +1,4 @@ [2 of 2] Compiling Main ( ImpSafe03.hs, ImpSafe03.o ) : - The package (bytestring-0.10.5.0) is required to be trusted but it isn't! + The package (bytestring-0.10.6.0) is required to be trusted but it isn't! From git at git.haskell.org Thu Dec 18 22:14:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Dec 2014 22:14:53 +0000 (UTC) Subject: [commit: ghc] master: Update Cabal submodule to 1.22 version (4c02b6f) Message-ID: <20141218221453.722EA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4c02b6f5dc4385369aa62160acd6037a32922f84/ghc >--------------------------------------------------------------- commit 4c02b6f5dc4385369aa62160acd6037a32922f84 Author: Herbert Valerio Riedel Date: Thu Dec 18 23:15:03 2014 +0100 Update Cabal submodule to 1.22 version >--------------------------------------------------------------- 4c02b6f5dc4385369aa62160acd6037a32922f84 libraries/Cabal | 2 +- testsuite/tests/driver/T4437.hs | 1 - utils/ghc-cabal/Main.hs | 4 ++-- utils/ghc-cabal/ghc-cabal.cabal | 2 +- utils/ghctags/ghctags.cabal | 2 +- 5 files changed, 5 insertions(+), 6 deletions(-) diff --git a/libraries/Cabal b/libraries/Cabal index 1d1ecd6..82d2fe1 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 1d1ecd611560dd719642a9ef3e536caf0df1dc8c +Subproject commit 82d2fe1f5083e56f0b2d2c2409a3f673a56a5fe4 diff --git a/testsuite/tests/driver/T4437.hs b/testsuite/tests/driver/T4437.hs index 250eae1..72f5f58 100644 --- a/testsuite/tests/driver/T4437.hs +++ b/testsuite/tests/driver/T4437.hs @@ -34,7 +34,6 @@ expectedGhcOnlyExtensions = ["RelaxedLayout", "AlternativeLayoutRule", "AlternativeLayoutRuleTransitional", "DeriveAnyClass", - "JavaScriptFFI", "PatternSynonyms", "PartialTypeSignatures", "NamedWildcards", diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index 8729fd4..6724f3a 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -10,6 +10,7 @@ import Distribution.System import Distribution.Simple import Distribution.Simple.Configure import Distribution.Simple.LocalBuildInfo +import Distribution.Simple.GHC import Distribution.Simple.Program import Distribution.Simple.Program.HcPkg import Distribution.Simple.Setup (ConfigFlags(configStripLibs), fromFlag, toFlag) @@ -224,8 +225,7 @@ doRegister directory distDir ghc ghcpkg topdir configurePrograms ps conf = foldM (flip (configureProgram verbosity)) conf ps progs' <- configurePrograms [ghcProgram', ghcPkgProgram'] progs - let Just ghcPkgProg = lookupProgram ghcPkgProgram' progs' - instInfos <- dump verbosity ghcPkgProg GlobalPackageDB + instInfos <- dump (hcPkgInfo progs') verbosity GlobalPackageDB let installedPkgs' = PackageIndex.fromList instInfos let updateComponentConfig (cn, clbi, deps) = (cn, updateComponentLocalBuildInfo clbi, deps) diff --git a/utils/ghc-cabal/ghc-cabal.cabal b/utils/ghc-cabal/ghc-cabal.cabal index 2641f19..f963c7c 100644 --- a/utils/ghc-cabal/ghc-cabal.cabal +++ b/utils/ghc-cabal/ghc-cabal.cabal @@ -17,7 +17,7 @@ Executable ghc-cabal Build-Depends: base >= 3 && < 5, bytestring >= 0.10 && < 0.11, - Cabal >= 1.20 && < 1.22, + Cabal >= 1.22 && < 1.24, directory >= 1.1 && < 1.3, filepath >= 1.2 && < 1.4 diff --git a/utils/ghctags/ghctags.cabal b/utils/ghctags/ghctags.cabal index cfa841d..7901aa2 100644 --- a/utils/ghctags/ghctags.cabal +++ b/utils/ghctags/ghctags.cabal @@ -18,6 +18,6 @@ Executable ghctags Build-Depends: base >= 4 && < 5, containers, - Cabal >= 1.20 && <1.22, + Cabal >= 1.22 && <1.24, ghc From git at git.haskell.org Fri Dec 19 02:50:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 02:50:26 +0000 (UTC) Subject: [commit: ghc] wip/rae: Finish fixing validDerivPred change (040ad38) Message-ID: <20141219025026.7F0DF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/040ad38d2aeb7957cad83731bae03cdcdb5cd664/ghc >--------------------------------------------------------------- commit 040ad38d2aeb7957cad83731bae03cdcdb5cd664 Author: Richard Eisenberg Date: Thu Dec 18 20:24:59 2014 -0500 Finish fixing validDerivPred change >--------------------------------------------------------------- 040ad38d2aeb7957cad83731bae03cdcdb5cd664 compiler/typecheck/TcDeriv.hs | 12 ++++++++++- compiler/typecheck/TcErrors.hs | 24 ++++++++++++---------- .../tests/indexed-types/should_fail/T6088.stderr | 11 ++++++++++ 3 files changed, 35 insertions(+), 12 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 8b7af86..8b2e6dc 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -1880,7 +1880,17 @@ simplifyDeriv pred tvs theta -- constraints. They'll come up again when we typecheck the -- generated instance declaration ; defer <- goptM Opt_DeferTypeErrors - ; unless defer (reportAllUnsolved (residual_wanted { wc_simple = bad })) + ; unless defer $ reportAllUnsolved (residual_wanted { wc_simple = bad }) + ; ifErrsM (do { let bad_preds = [ ctPred bad_ct + | bad_ct <- bagToList bad + , isWantedCt bad_ct ] -- omit Deriveds + inf_theta = bagToList good ++ bad_preds + ; setErrCtxt [] $ addErr $ + hang (hsep [ text "The full inferred context for" + , doc, text "is" ]) + 2 (pprTheta inf_theta) $$ + text "Try using this context for standalone-deriving." }) + (return ()) -- do nothing if there are no errors ; let min_theta = mkMinimalBySCs (bagToList good) ; return (substTheta subst_skol min_theta) } diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 3fdf4e9..8fda2c8 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -676,7 +676,8 @@ mkEqErr1 ctxt ct ; dflags <- getDynFlags ; traceTc "mkEqErr1" (ppr ct $$ pprCtOrigin (ctLocOrigin loc) $$ pprCtOrigin tidy_orig) ; mkEqErr_help dflags (ctxt {cec_tidy = env1}) - (wanted_msg $$ coercible_msg $$ binds_msg) + (vcat [ wanted_msg, coercible_msg, binds_msg + , show_fixes (drv_fixes tidy_orig) ]) ct is_oriented ty1 ty2 } where ev = ctEvidence ct @@ -1206,7 +1207,7 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) , vcat (pp_givens givens) , ppWhen (has_ambig_tvs && not (null unifiers && null givens)) (vcat [ ambig_msg, binds_msg, potential_msg ]) - , show_fixes (add_to_ctxt_fixes has_ambig_tvs ++ drv_fixes) ] + , show_fixes (add_to_ctxt_fixes has_ambig_tvs ++ drv_fixes orig) ] potential_msg = ppWhen (not (null unifiers) && want_potential orig) $ @@ -1251,15 +1252,6 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) type_has_arrow (ForAllTy _ t) = type_has_arrow t type_has_arrow (LitTy _) = False - drv_fixes = case orig of - DerivOrigin -> [drv_fix] - DerivOriginDC {} -> [drv_fix] - DerivOriginCoerce {} -> [drv_fix] - _ -> [] - - drv_fix = hang (ptext (sLit "use a standalone 'deriving instance' declaration,")) - 2 (ptext (sLit "so you can specify the instance context yourself")) - -- Normal overlap error overlap_msg = ASSERT( not (null matches) ) @@ -1348,6 +1340,16 @@ show_fixes [] = empty show_fixes (f:fs) = sep [ ptext (sLit "Possible fix:") , nest 2 (vcat (f : map (ptext (sLit "or") <+>) fs))] +drv_fixes :: CtOrigin -> [SDoc] +drv_fixes orig = case orig of + DerivOrigin -> [drv_fix] + DerivOriginDC {} -> [drv_fix] + DerivOriginCoerce {} -> [drv_fix] + _ -> [] + where + drv_fix = hang (ptext (sLit "use a standalone 'deriving instance' declaration,")) + 2 (ptext (sLit "so you can specify the instance context yourself")) + ppr_insts :: [ClsInst] -> SDoc ppr_insts insts = pprInstances (take 3 insts) $$ dot_dot_message diff --git a/testsuite/tests/indexed-types/should_fail/T6088.stderr b/testsuite/tests/indexed-types/should_fail/T6088.stderr new file mode 100644 index 0000000..d9aeee6 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T6088.stderr @@ -0,0 +1,11 @@ + +T6088.hs:16:33: + Couldn't match type ?Pos n? with ?True? + Possible fix: + use a standalone 'deriving instance' declaration, + so you can specify the instance context yourself + When deriving the instance for (C (B n)) + +T6088.hs:16:33: + The full inferred context for deriving (C (B n)) is (Pos n ~ True) + Try using this context for standalone-deriving. From git at git.haskell.org Fri Dec 19 02:50:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 02:50:29 +0000 (UTC) Subject: [commit: ghc] wip/rae: Fix warning in Ppr (30eb9ec) Message-ID: <20141219025029.3BC683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/30eb9ec0208f099fb8a92347578df49b8157e333/ghc >--------------------------------------------------------------- commit 30eb9ec0208f099fb8a92347578df49b8157e333 Author: Richard Eisenberg Date: Thu Dec 18 20:25:32 2014 -0500 Fix warning in Ppr >--------------------------------------------------------------- 30eb9ec0208f099fb8a92347578df49b8157e333 libraries/template-haskell/Language/Haskell/TH/Ppr.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs index 63fa80b..4ba43f3 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs @@ -582,11 +582,11 @@ quoteParens d = text "'(" <> d <> text ")" ----------------------------- instance Ppr Loc where - ppr (Loc { loc_module = mod + ppr (Loc { loc_module = md , loc_package = pkg , loc_start = (start_ln, start_col) , loc_end = (end_ln, end_col) }) - = hcat [ text pkg, colon, text mod, colon + = hcat [ text pkg, colon, text md, colon , parens $ int start_ln <> comma <> int start_col , text "-" , parens $ int end_ln <> comma <> int end_col ] From git at git.haskell.org Fri Dec 19 04:54:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 04:54:53 +0000 (UTC) Subject: [commit: ghc] master: Some Dwarf generation fixes (f85db75) Message-ID: <20141219045453.C20083A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f85db7567210bc2ff7036064a26d6ba29998f025/ghc >--------------------------------------------------------------- commit f85db7567210bc2ff7036064a26d6ba29998f025 Author: Peter Wortmann Date: Thu Dec 18 21:11:23 2014 +0100 Some Dwarf generation fixes - Make abbrev offset absolute on Non-Mac systems - Add another termination byte at the end of the abbrev section (readelf complains) - Scope combination was wrong for the simpler cases - Shouldn't have a "global/" in front of all scopes >--------------------------------------------------------------- f85db7567210bc2ff7036064a26d6ba29998f025 compiler/cmm/CmmNode.hs | 11 +++++++---- compiler/nativeGen/Dwarf.hs | 4 ++-- compiler/nativeGen/Dwarf/Types.hs | 18 ++++++++++++++++-- 3 files changed, 25 insertions(+), 8 deletions(-) diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index b405360..0f26d37 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -660,6 +660,8 @@ instance Ord CmmTickScope where instance Outputable CmmTickScope where ppr GlobalScope = text "global" + ppr (SubScope us GlobalScope) + = ppr us ppr (SubScope us s) = ppr s <> char '/' <> ppr us ppr combined = parens $ hcat $ punctuate (char '+') $ map (hcat . punctuate (char '/') . map ppr . reverse) $ @@ -675,10 +677,11 @@ isTickSubScope = cmp cmp s (CombinedScope s1' s2') = cmp s s1' || cmp s s2' cmp (SubScope u s) s'@(SubScope u' _) = u == u' || cmp s s' --- | Combine two tick scopes. This smart constructor will catch cases --- where one tick scope is a sub-scope of the other already. +-- | Combine two tick scopes. The new scope should be sub-scope of +-- both parameters. We simplfy automatically if one tick scope is a +-- sub-scope of the other already. combineTickScopes :: CmmTickScope -> CmmTickScope -> CmmTickScope combineTickScopes s1 s2 - | s1 `isTickSubScope` s2 = s2 - | s2 `isTickSubScope` s1 = s1 + | s1 `isTickSubScope` s2 = s1 + | s2 `isTickSubScope` s1 = s2 | otherwise = CombinedScope s1 s2 diff --git a/compiler/nativeGen/Dwarf.hs b/compiler/nativeGen/Dwarf.hs index 4f9bdb6..70fca4f 100644 --- a/compiler/nativeGen/Dwarf.hs +++ b/compiler/nativeGen/Dwarf.hs @@ -83,8 +83,8 @@ compileUnitHeader unitU = sdocWithPlatform $ \plat -> in vcat [ ptext (sLit "\t.long ") <> length -- compilation unit size , ppr cuLabel <> colon , ptext (sLit "\t.word 3") -- DWARF version - , pprDwWord (ptext dwarfAbbrevLabel <> char '-' <> - ptext dwarfAbbrevLabel) -- pointer to our abbrevs + , pprDwWord (sectionOffset dwarfAbbrevLabel dwarfAbbrevLabel) + -- abbrevs offset , ptext (sLit "\t.byte ") <> ppr (platformWordSize plat) -- word size ] diff --git a/compiler/nativeGen/Dwarf/Types.hs b/compiler/nativeGen/Dwarf/Types.hs index 96fea0a..47e0bd1 100644 --- a/compiler/nativeGen/Dwarf/Types.hs +++ b/compiler/nativeGen/Dwarf/Types.hs @@ -14,6 +14,7 @@ module Dwarf.Types , pprLEBWord , pprLEBInt , wordAlign + , sectionOffset ) where @@ -94,7 +95,9 @@ pprAbbrevDecls haveDebugLine = [ (dW_AT_name, dW_FORM_string) , (dW_AT_low_pc, dW_FORM_addr) , (dW_AT_high_pc, dW_FORM_addr) - ] + ] $$ + pprByte 0 + -- | Generate assembly for DWARF data pprDwarfInfo :: Bool -> DwarfInfo -> SDoc pprDwarfInfo haveSrc d @@ -113,7 +116,7 @@ pprDwarfInfoOpen haveSrc (DwarfCompileUnit _ name producer compDir lineLbl) = $$ pprData4 dW_LANG_Haskell $$ pprString compDir $$ if haveSrc - then pprData4' (ptext lineLbl <> char '-' <> ptext dwarfLineLabel) + then pprData4' (sectionOffset lineLbl dwarfLineLabel) else empty pprDwarfInfoOpen _ (DwarfSubprogram _ name label) = sdocWithDynFlags $ \df -> pprAbbrev DwAbbrSubprogram @@ -416,3 +419,14 @@ pprString = pprString' . hcat . map escape char (intToDigit (ch `div` 64)) <> char (intToDigit ((ch `div` 8) `mod` 8)) <> char (intToDigit (ch `mod` 8)) + +-- | Generate an offset into another section. This is tricky because +-- this is handled differently depending on platform: Mac Os expects +-- us to calculate the offset using assembler arithmetic. Meanwhile, +-- GNU tools expect us to just reference the target directly, and will +-- figure out on their own that we actually need an offset. +sectionOffset :: LitString -> LitString -> SDoc +sectionOffset target section = sdocWithPlatform $ \plat -> + case platformOS plat of + OSDarwin -> ptext target <> char '-' <> ptext section + _other -> ptext target From git at git.haskell.org Fri Dec 19 09:59:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 09:59:29 +0000 (UTC) Subject: [commit: ghc] master: Update process and unix submodules (7844dd7) Message-ID: <20141219095929.E67E83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7844dd7ac5358efc2269b14a9fba74518cabee98/ghc >--------------------------------------------------------------- commit 7844dd7ac5358efc2269b14a9fba74518cabee98 Author: Herbert Valerio Riedel Date: Fri Dec 19 10:57:03 2014 +0100 Update process and unix submodules This updates the submodules to the respective final releases, - `unix-2.7.1.0`, and - `process-1.2.1.0` >--------------------------------------------------------------- 7844dd7ac5358efc2269b14a9fba74518cabee98 libraries/process | 2 +- libraries/unix | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/process b/libraries/process index 0246baf..1a62f86 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 0246baf953e6b0d1b511f4d831528a9a5e8b71e2 +Subproject commit 1a62f86e77118520143985d9baf62d31a9d1c748 diff --git a/libraries/unix b/libraries/unix index 757bf44..4260c25 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit 757bf44bb4895fc561a2e5dd2f602168478741ec +Subproject commit 4260c25687d3a4bc1ffacdacfbe7e47082ff2550 From git at git.haskell.org Fri Dec 19 10:10:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 10:10:16 +0000 (UTC) Subject: [commit: ghc] master: Relocate bash completion scripts to utils/ (cf594fd) Message-ID: <20141219101016.2378E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cf594fd204f951f849e876cf28f6ac1604184ae7/ghc >--------------------------------------------------------------- commit cf594fd204f951f849e876cf28f6ac1604184ae7 Author: Jan Stolarek Date: Fri Dec 19 11:10:50 2014 +0100 Relocate bash completion scripts to utils/ >--------------------------------------------------------------- cf594fd204f951f849e876cf28f6ac1604184ae7 {completion => utils/completion}/README | 0 {completion => utils/completion}/ghc.bash | 0 2 files changed, 0 insertions(+), 0 deletions(-) diff --git a/completion/README b/utils/completion/README similarity index 100% rename from completion/README rename to utils/completion/README diff --git a/completion/ghc.bash b/utils/completion/ghc.bash similarity index 100% rename from completion/ghc.bash rename to utils/completion/ghc.bash From git at git.haskell.org Fri Dec 19 12:12:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 12:12:32 +0000 (UTC) Subject: [commit: ghc] master: Add Data.Version.makeVersion & `IsList Version` (5b8fa46) Message-ID: <20141219121232.388613A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5b8fa46ca37caa9ec83b217a697628135da34506/ghc >--------------------------------------------------------------- commit 5b8fa46ca37caa9ec83b217a697628135da34506 Author: Herbert Valerio Riedel Date: Fri Dec 19 11:08:09 2014 +0100 Add Data.Version.makeVersion & `IsList Version` These two facilities provide some means to avoid the double-breakage caused by first by the deprecation (see #2496), and then again by the actual future field-removal. See also https://groups.google.com/d/msg/haskell-core-libraries/q9H-QlL_gnE/4lbb_mBjre8J for details about this library addition. Reviewed By: ekmett Differential Revision: https://phabricator.haskell.org/D577 >--------------------------------------------------------------- 5b8fa46ca37caa9ec83b217a697628135da34506 libraries/base/Data/Version.hs | 8 ++++++++ libraries/base/GHC/Exts.hs | 7 +++++++ libraries/base/changelog.md | 6 ++++++ .../overloadedlists/should_fail/overloadedlistsfail01.stderr | 9 ++++++--- 4 files changed, 27 insertions(+), 3 deletions(-) diff --git a/libraries/base/Data/Version.hs b/libraries/base/Data/Version.hs index 3761d81..1a14fd0 100644 --- a/libraries/base/Data/Version.hs +++ b/libraries/base/Data/Version.hs @@ -32,6 +32,8 @@ module Data.Version ( Version(..), -- * A concrete representation of @Version@ showVersion, parseVersion, + -- * Constructor function + makeVersion ) where import Control.Monad ( Monad(..), liftM ) @@ -121,3 +123,9 @@ parseVersion :: ReadP Version parseVersion = do branch <- sepBy1 (liftM read (munch1 isDigit)) (char '.') tags <- many (char '-' >> munch1 isAlphaNum) return Version{versionBranch=branch, versionTags=tags} + +-- | Construct tag-less 'Version' +-- +-- @since 4.8.0.0 +makeVersion :: [Int] -> Version +makeVersion b = Version b [] diff --git a/libraries/base/GHC/Exts.hs b/libraries/base/GHC/Exts.hs index 93de419..2942678 100755 --- a/libraries/base/GHC/Exts.hs +++ b/libraries/base/GHC/Exts.hs @@ -84,6 +84,7 @@ import Data.String import Data.OldList import Data.Data import Data.Ord +import Data.Version ( Version(..), makeVersion ) import qualified Debug.Trace -- XXX This should really be in Data.Tuple, where the definitions are @@ -177,3 +178,9 @@ instance IsList [a] where type (Item [a]) = a fromList = id toList = id + +-- | @since 4.8.0.0 +instance IsList Version where + type (Item Version) = Int + fromList = makeVersion + toList = versionBranch diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 00da7ce..76a6a19 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -12,6 +12,12 @@ * Add `System.Exit.die` + * Deprecate `versionTags` field of `Data.Version.Version`. + Add `makeVersion :: [Int] -> Version` constructor function to aid + migration to a future `versionTags`-less `Version`. + + * Add `IsList Version` instance + * Weaken RealFloat constraints on some `Data.Complex` functions * Add `Control.Monad.(<$!>)` as a strict version of `(<$>)` diff --git a/testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr b/testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr index 9f3a832..6516beb 100644 --- a/testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr +++ b/testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr @@ -3,10 +3,11 @@ overloadedlistsfail01.hs:5:8: No instance for (Show a0) arising from a use of ?print? The type variable ?a0? is ambiguous Note: there are several potential instances: + instance [safe] Show Data.Version.Version + -- Defined in ?Data.Version? instance Show a => Show (Maybe a) -- Defined in ?GHC.Show? instance Show Ordering -- Defined in ?GHC.Show? - instance Show Integer -- Defined in ?GHC.Show? - ...plus 22 others + ...plus 23 others In the expression: print [1] In an equation for ?main?: main = print [1] @@ -14,7 +15,9 @@ overloadedlistsfail01.hs:5:14: No instance for (GHC.Exts.IsList a0) arising from an overloaded list The type variable ?a0? is ambiguous - Note: there is a potential instance available: + Note: there are several potential instances: + instance GHC.Exts.IsList Data.Version.Version + -- Defined in ?GHC.Exts? instance GHC.Exts.IsList [a] -- Defined in ?GHC.Exts? In the first argument of ?print?, namely ?[1]? In the expression: print [1] From git at git.haskell.org Fri Dec 19 13:02:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 13:02:00 +0000 (UTC) Subject: [commit: ghc] wip/rae: Revert "Finish fixing validDerivPred change" (c0b488a) Message-ID: <20141219130200.33A6D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/rae Link : http://ghc.haskell.org/trac/ghc/changeset/c0b488a171a3632ab3db1bd1950212f98703a499/ghc >--------------------------------------------------------------- commit c0b488a171a3632ab3db1bd1950212f98703a499 Author: Richard Eisenberg Date: Fri Dec 19 08:02:52 2014 -0500 Revert "Finish fixing validDerivPred change" This reverts commit 040ad38d2aeb7957cad83731bae03cdcdb5cd664. >--------------------------------------------------------------- c0b488a171a3632ab3db1bd1950212f98703a499 compiler/typecheck/TcDeriv.hs | 12 +---------- compiler/typecheck/TcErrors.hs | 24 ++++++++++------------ .../tests/indexed-types/should_fail/T6088.stderr | 11 ---------- 3 files changed, 12 insertions(+), 35 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 8b2e6dc..8b7af86 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -1880,17 +1880,7 @@ simplifyDeriv pred tvs theta -- constraints. They'll come up again when we typecheck the -- generated instance declaration ; defer <- goptM Opt_DeferTypeErrors - ; unless defer $ reportAllUnsolved (residual_wanted { wc_simple = bad }) - ; ifErrsM (do { let bad_preds = [ ctPred bad_ct - | bad_ct <- bagToList bad - , isWantedCt bad_ct ] -- omit Deriveds - inf_theta = bagToList good ++ bad_preds - ; setErrCtxt [] $ addErr $ - hang (hsep [ text "The full inferred context for" - , doc, text "is" ]) - 2 (pprTheta inf_theta) $$ - text "Try using this context for standalone-deriving." }) - (return ()) -- do nothing if there are no errors + ; unless defer (reportAllUnsolved (residual_wanted { wc_simple = bad })) ; let min_theta = mkMinimalBySCs (bagToList good) ; return (substTheta subst_skol min_theta) } diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 8fda2c8..3fdf4e9 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -676,8 +676,7 @@ mkEqErr1 ctxt ct ; dflags <- getDynFlags ; traceTc "mkEqErr1" (ppr ct $$ pprCtOrigin (ctLocOrigin loc) $$ pprCtOrigin tidy_orig) ; mkEqErr_help dflags (ctxt {cec_tidy = env1}) - (vcat [ wanted_msg, coercible_msg, binds_msg - , show_fixes (drv_fixes tidy_orig) ]) + (wanted_msg $$ coercible_msg $$ binds_msg) ct is_oriented ty1 ty2 } where ev = ctEvidence ct @@ -1207,7 +1206,7 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) , vcat (pp_givens givens) , ppWhen (has_ambig_tvs && not (null unifiers && null givens)) (vcat [ ambig_msg, binds_msg, potential_msg ]) - , show_fixes (add_to_ctxt_fixes has_ambig_tvs ++ drv_fixes orig) ] + , show_fixes (add_to_ctxt_fixes has_ambig_tvs ++ drv_fixes) ] potential_msg = ppWhen (not (null unifiers) && want_potential orig) $ @@ -1252,6 +1251,15 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) type_has_arrow (ForAllTy _ t) = type_has_arrow t type_has_arrow (LitTy _) = False + drv_fixes = case orig of + DerivOrigin -> [drv_fix] + DerivOriginDC {} -> [drv_fix] + DerivOriginCoerce {} -> [drv_fix] + _ -> [] + + drv_fix = hang (ptext (sLit "use a standalone 'deriving instance' declaration,")) + 2 (ptext (sLit "so you can specify the instance context yourself")) + -- Normal overlap error overlap_msg = ASSERT( not (null matches) ) @@ -1340,16 +1348,6 @@ show_fixes [] = empty show_fixes (f:fs) = sep [ ptext (sLit "Possible fix:") , nest 2 (vcat (f : map (ptext (sLit "or") <+>) fs))] -drv_fixes :: CtOrigin -> [SDoc] -drv_fixes orig = case orig of - DerivOrigin -> [drv_fix] - DerivOriginDC {} -> [drv_fix] - DerivOriginCoerce {} -> [drv_fix] - _ -> [] - where - drv_fix = hang (ptext (sLit "use a standalone 'deriving instance' declaration,")) - 2 (ptext (sLit "so you can specify the instance context yourself")) - ppr_insts :: [ClsInst] -> SDoc ppr_insts insts = pprInstances (take 3 insts) $$ dot_dot_message diff --git a/testsuite/tests/indexed-types/should_fail/T6088.stderr b/testsuite/tests/indexed-types/should_fail/T6088.stderr deleted file mode 100644 index d9aeee6..0000000 --- a/testsuite/tests/indexed-types/should_fail/T6088.stderr +++ /dev/null @@ -1,11 +0,0 @@ - -T6088.hs:16:33: - Couldn't match type ?Pos n? with ?True? - Possible fix: - use a standalone 'deriving instance' declaration, - so you can specify the instance context yourself - When deriving the instance for (C (B n)) - -T6088.hs:16:33: - The full inferred context for deriving (C (B n)) is (Pos n ~ True) - Try using this context for standalone-deriving. From git at git.haskell.org Fri Dec 19 15:02:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 15:02:15 +0000 (UTC) Subject: [commit: ghc] master: Consider equality contexts exotic, uninferrable by "deriving" (02b4845) Message-ID: <20141219150215.1E8953A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/02b4845e07ef7110b2f735f323eb8748903330ff/ghc >--------------------------------------------------------------- commit 02b4845e07ef7110b2f735f323eb8748903330ff Author: Richard Eisenberg Date: Tue Dec 16 17:15:49 2014 -0500 Consider equality contexts exotic, uninferrable by "deriving" See comments in #8984. This takes back the fix for #6088. >--------------------------------------------------------------- 02b4845e07ef7110b2f735f323eb8748903330ff compiler/typecheck/TcValidity.hs | 4 +--- testsuite/tests/indexed-types/should_compile/all.T | 1 - .../tests/indexed-types/{should_compile => should_fail}/T6088.hs | 0 testsuite/tests/indexed-types/should_fail/T6088.stderr | 4 ++++ testsuite/tests/indexed-types/should_fail/all.T | 2 ++ 5 files changed, 7 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index 8575cf8..ca8b63a 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -878,10 +878,8 @@ validDerivPred :: TyVarSet -> PredType -> Bool validDerivPred tv_set pred = case classifyPredType pred of ClassPred _ tys -> check_tys tys - -- EqPred ReprEq is a Coercible constraint; treat - -- like a class - EqPred ReprEq ty1 ty2 -> check_tys [ty1, ty2] TuplePred ps -> all (validDerivPred tv_set) ps + EqPred {} -> False -- reject equality constraints _ -> True -- Non-class predicates are ok where check_tys tys = hasNoDups fvs diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index ae15c27..928a70d 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -194,7 +194,6 @@ test('T6152', run_command, ['$MAKE -s --no-print-directory T6152']) -test('T6088', normal, compile, ['']) test('T7082', normal, compile, ['']) test('Overlap1', normal, compile, ['']) diff --git a/testsuite/tests/indexed-types/should_compile/T6088.hs b/testsuite/tests/indexed-types/should_fail/T6088.hs similarity index 100% rename from testsuite/tests/indexed-types/should_compile/T6088.hs rename to testsuite/tests/indexed-types/should_fail/T6088.hs diff --git a/testsuite/tests/indexed-types/should_fail/T6088.stderr b/testsuite/tests/indexed-types/should_fail/T6088.stderr new file mode 100644 index 0000000..221dd32 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T6088.stderr @@ -0,0 +1,4 @@ + +T6088.hs:16:33: + Couldn't match type ?Pos n? with ?True? + When deriving the instance for (C (B n)) diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index 821342c..a52e621 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -132,3 +132,5 @@ test('T9580', normal, multimod_compile_fail, ['T9580', '']) test('T9662', normal, compile_fail, ['']) test('T7862', normal, compile_fail, ['']) test('T9896', normal, compile_fail, ['']) +test('T6088', normal, compile_fail, ['']) + From git at git.haskell.org Fri Dec 19 15:02:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 15:02:17 +0000 (UTC) Subject: [commit: ghc] master: Clarify that declaration splices exist at top level only. (#9880) (53599b3) Message-ID: <20141219150217.C6FD63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/53599b3f515227f3407991913781fc8ea79d9638/ghc >--------------------------------------------------------------- commit 53599b3f515227f3407991913781fc8ea79d9638 Author: Richard Eisenberg Date: Tue Dec 16 17:21:42 2014 -0500 Clarify that declaration splices exist at top level only. (#9880) >--------------------------------------------------------------- 53599b3f515227f3407991913781fc8ea79d9638 docs/users_guide/glasgow_exts.xml | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index a502262..86ceb06 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -9015,11 +9015,13 @@ Wiki page. have type Q Pat a type; the spliced expression must have type Q Type - a list of declarations; the spliced expression + a list of declarations at top level; the spliced expression must have type Q [Dec] Inside a splice you can only call functions defined in imported modules, - not functions defined elsewhere in the same module. + not functions defined elsewhere in the same module. Note that + declaration splices are not allowed anywhere except at top level + (outside any other declarations). A expression quotation is written in Oxford brackets, thus: From git at git.haskell.org Fri Dec 19 15:02:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 15:02:20 +0000 (UTC) Subject: [commit: ghc] master: Merge some instances from th-orphans. (c190b73) Message-ID: <20141219150220.BE3633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c190b73f972abdeefc48469eb7c23837f43b3425/ghc >--------------------------------------------------------------- commit c190b73f972abdeefc48469eb7c23837f43b3425 Author: Richard Eisenberg Date: Tue Dec 16 17:17:06 2014 -0500 Merge some instances from th-orphans. >--------------------------------------------------------------- c190b73f972abdeefc48469eb7c23837f43b3425 .../template-haskell/Language/Haskell/TH/Ppr.hs | 14 ++++ .../template-haskell/Language/Haskell/TH/Syntax.hs | 46 +++++++++++-- testsuite/tests/th/TH_Lift.hs | 75 ++++++++++++++++++++++ testsuite/tests/th/all.T | 1 + 4 files changed, 130 insertions(+), 6 deletions(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs index 0f828eb..4ba43f3 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs @@ -211,6 +211,9 @@ pprBody eq body = case body of | otherwise = arrow ------------------------------ +instance Ppr Lit where + ppr = pprLit noPrec + pprLit :: Precedence -> Lit -> Doc pprLit i (IntPrimL x) = parensIf (i > noPrec && x < 0) (integer x <> char '#') @@ -576,3 +579,14 @@ hashParens d = text "(# " <> d <> text " #)" quoteParens :: Doc -> Doc quoteParens d = text "'(" <> d <> text ")" + +----------------------------- +instance Ppr Loc where + ppr (Loc { loc_module = md + , loc_package = pkg + , loc_start = (start_ln, start_col) + , loc_end = (end_ln, end_col) }) + = hcat [ text pkg, colon, text md, colon + , parens $ int start_ln <> comma <> int start_col + , text "-" + , parens $ int end_ln <> comma <> int end_col ] diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 3634ef7..8e4b344 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -1,6 +1,5 @@ {-# LANGUAGE CPP, DeriveDataTypeable, PolymorphicComponents, - RoleAnnotations, DeriveGeneric, TypeSynonymInstances, - FlexibleInstances #-} + RoleAnnotations, DeriveGeneric, FlexibleInstances #-} ----------------------------------------------------------------------------- -- | @@ -27,7 +26,9 @@ import System.IO.Unsafe ( unsafePerformIO ) import Control.Monad (liftM) import System.IO ( hPutStrLn, stderr ) import Data.Char ( isAlpha, isAlphaNum, isUpper ) -import Data.Word ( Word8 ) +import Data.Int +import Data.Word +import Data.Ratio import GHC.Generics ( Generic ) ----------------------------------------------------- @@ -36,7 +37,7 @@ import GHC.Generics ( Generic ) -- ----------------------------------------------------- -class (Monad m, Applicative m) => Quasi m where +class Monad m => Quasi m where qNewName :: String -> m Name -- ^ Fresh names @@ -457,8 +458,41 @@ instance Lift Integer where instance Lift Int where lift x = return (LitE (IntegerL (fromIntegral x))) -instance Lift Rational where - lift x = return (LitE (RationalL x)) +instance Lift Int8 where + lift x = return (LitE (IntegerL (fromIntegral x))) + +instance Lift Int16 where + lift x = return (LitE (IntegerL (fromIntegral x))) + +instance Lift Int32 where + lift x = return (LitE (IntegerL (fromIntegral x))) + +instance Lift Int64 where + lift x = return (LitE (IntegerL (fromIntegral x))) + +instance Lift Word where + lift x = return (LitE (IntegerL (fromIntegral x))) + +instance Lift Word8 where + lift x = return (LitE (IntegerL (fromIntegral x))) + +instance Lift Word16 where + lift x = return (LitE (IntegerL (fromIntegral x))) + +instance Lift Word32 where + lift x = return (LitE (IntegerL (fromIntegral x))) + +instance Lift Word64 where + lift x = return (LitE (IntegerL (fromIntegral x))) + +instance Integral a => Lift (Ratio a) where + lift x = return (LitE (RationalL (toRational x))) + +instance Lift Float where + lift x = return (LitE (RationalL (toRational x))) + +instance Lift Double where + lift x = return (LitE (RationalL (toRational x))) instance Lift Char where lift x = return (LitE (CharL x)) diff --git a/testsuite/tests/th/TH_Lift.hs b/testsuite/tests/th/TH_Lift.hs new file mode 100644 index 0000000..fd30af7 --- /dev/null +++ b/testsuite/tests/th/TH_Lift.hs @@ -0,0 +1,75 @@ +-- test Lifting instances + +{-# LANGUAGE TemplateHaskell #-} + +module TH_Lift where + +import Language.Haskell.TH.Syntax +import Data.Ratio +import Data.Word +import Data.Int + +a :: Integer +a = $( (\x -> [| x |]) (5 :: Integer) ) + +b :: Int +b = $( (\x -> [| x |]) (5 :: Int) ) + +b1 :: Int8 +b1 = $( (\x -> [| x |]) (5 :: Int8) ) + +b2 :: Int16 +b2 = $( (\x -> [| x |]) (5 :: Int16) ) + +b3 :: Int32 +b3 = $( (\x -> [| x |]) (5 :: Int32) ) + +b4 :: Int64 +b4 = $( (\x -> [| x |]) (5 :: Int64) ) + +c :: Word +c = $( (\x -> [| x |]) (5 :: Word) ) + +d :: Word8 +d = $( (\x -> [| x |]) (5 :: Word8) ) + +e :: Word16 +e = $( (\x -> [| x |]) (5 :: Word16) ) + +f :: Word32 +f = $( (\x -> [| x |]) (5 :: Word32) ) + +g :: Word64 +g = $( (\x -> [| x |]) (5 :: Word64) ) + +h :: Rational +h = $( (\x -> [| x |]) (5 % 3 :: Rational) ) + +h1 :: Float +h1 = $( (\x -> [| x |]) (pi :: Float) ) + +h2 :: Double +h2 = $( (\x -> [| x |]) (pi :: Double) ) + +i :: Char +i = $( (\x -> [| x |]) 'x' ) + +j :: Bool +j = $( (\x -> [| x |]) True ) + +k :: Maybe Char +k = $( (\x -> [| x |]) (Just 'x') ) + +l :: Either Char Bool +l = $( (\x -> [| x |]) (Right False :: Either Char Bool) ) + +m :: [Char] +m = $( (\x -> [| x |]) "hi!") + +n :: () +n = $( (\x -> [| x |]) () ) + +o :: (Bool, Char, Int) +o = $( (\x -> [| x |]) (True, 'x', 4 :: Int) ) + + diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 4c8023e..021afd9 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -354,3 +354,4 @@ test('T1476', normal, compile, ['-v0']) test('T1476b', normal, compile_fail, ['-v0']) test('T9824', normal, compile, ['-v0']) test('T8031', normal, compile, ['-v0']) +test('TH_Lift', normal, compile, ['-v0']) From git at git.haskell.org Fri Dec 19 15:19:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 15:19:37 +0000 (UTC) Subject: [commit: ghc] master: Update release notes for recent language and TH changes. (3fffd32) Message-ID: <20141219151937.1646F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3fffd32c1329e6e21e3e1eefd776a24e503fcefe/ghc >--------------------------------------------------------------- commit 3fffd32c1329e6e21e3e1eefd776a24e503fcefe Author: Richard Eisenberg Date: Fri Dec 19 10:19:55 2014 -0500 Update release notes for recent language and TH changes. >--------------------------------------------------------------- 3fffd32c1329e6e21e3e1eefd776a24e503fcefe docs/users_guide/7.10.1-notes.xml | 41 ++++++++++++++++++++++++++++++++++++++- 1 file changed, 40 insertions(+), 1 deletion(-) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index f87b0cc..58d7bdf 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -72,6 +72,17 @@ [t|forall a. Ord a => a|]. + + + + Instance contexts inferred while processing deriving + directives attached to data and newtype + declarations now forbid equality constraints. This is a regression in + obscure cases, but it will yield better error messages in more common + cases. Users caught by the regression can simply use standalone-deriving, + where you specify the context yourself. + + @@ -191,7 +202,9 @@ Added support for generating LINE pragma declarations (). + + The type Pred (which stores a type constraint) is now a synonym for Type, @@ -199,17 +212,23 @@ extension. This is a breaking change and may require some rewriting of Template Haskell code. + + Pattern splices now work. + + reifyInstances now treats unbound type variables as univerally quantified, allowing lookup of, say, the instance for Eq [a]. + + More kind annotations appear in reified types, in order to disambiguate types that would otherwise be ambiguous in the @@ -218,22 +237,40 @@ KindedTVs. (This does not affect Template Haskell quotations, just calls to reify.) + + Various features unsupported in quotations were previously silently ignored. These now cause errors. + + Lift instances were added for - () and Ratio. + many more types: all of the IntXX + and WordXX types, Ratio a, + (), Float, and + Double. + + All Template Haskell datatypes now have Generic and Ord instances. + + + + + Ppr instances were added for Lit + and Loc. + + + Two new declaration forms are now supported: standalone-deriving declarations and generic method @@ -241,7 +278,9 @@ a class). This means an expansion to the Dec type. + + Template Haskell is now more pedantic about splicing in bogus variable names, like those containing whitespace. If you From git at git.haskell.org Fri Dec 19 15:24:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 15:24:58 +0000 (UTC) Subject: [commit: ghc] master: Add Jan Stolarek's test for Trac #9872 (dd1b6d4) Message-ID: <20141219152458.BB9033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dd1b6d4fc96bc2779beaca836d1b9e4b158c1597/ghc >--------------------------------------------------------------- commit dd1b6d4fc96bc2779beaca836d1b9e4b158c1597 Author: Simon Peyton Jones Date: Fri Dec 19 15:25:51 2014 +0000 Add Jan Stolarek's test for Trac #9872 >--------------------------------------------------------------- dd1b6d4fc96bc2779beaca836d1b9e4b158c1597 testsuite/tests/perf/compiler/T9872d.hs | 148 ++++++++++++++++++++++++++++++++ testsuite/tests/perf/compiler/all.T | 9 ++ 2 files changed, 157 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 dd1b6d4fc96bc2779beaca836d1b9e4b158c1597 From git at git.haskell.org Fri Dec 19 15:44:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 15:44:00 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: More release notes (ba53ab5) Message-ID: <20141219154400.3D93D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/ba53ab574bbbba69a2cc5c773ce51bdbc0ad1b48/ghc >--------------------------------------------------------------- commit ba53ab574bbbba69a2cc5c773ce51bdbc0ad1b48 Author: Austin Seipp Date: Fri Dec 19 09:32:06 2014 -0600 More release notes Signed-off-by: Austin Seipp >--------------------------------------------------------------- ba53ab574bbbba69a2cc5c773ce51bdbc0ad1b48 docs/users_guide/7.8.4-notes.xml | 48 ++++++++++++++++++++++++++++++++++++++++ 1 file changed, 48 insertions(+) diff --git a/docs/users_guide/7.8.4-notes.xml b/docs/users_guide/7.8.4-notes.xml index 27e7ee8..376f795 100644 --- a/docs/users_guide/7.8.4-notes.xml +++ b/docs/users_guide/7.8.4-notes.xml @@ -98,6 +98,54 @@ type family applications has been fixed (issue #9433). + + + Several bugs have been fixed causing problems with + building GHC on ARM (issues #8951, #9620, #9336, and + #9552). + + + + + A bug in the typechecker that could cause an infinite loop + when using superclasses in a cycle has been fixed (issue #9415). + + + + + A bug causing corruption in signal handling with the + single-threaded runtime system has been fixed (issue + #9817). + + + + + A bug that could cause compiled programs to crash due to + use of overlapping type families has been fixed (issue + #9371). + + + + + A bug in the inliner that caused certain expressions + within unboxed tuples to not be properly evaluated has + been fixed (issue #9390). + + + + + A bug that caused the compiler to not always properly + detect LLVM tools (particularly on Windows) has been fixed + (issue #7143). + + + + + A bug that prevented GHC from deriving + Generic1 instances for data families + has been fixed (#9563). + + From git at git.haskell.org Fri Dec 19 15:44:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 15:44:02 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Add package flags to --show-options output (dd52a54) Message-ID: <20141219154402.DC68A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/dd52a54279005c3a994114950e378c884e1fee02/ghc >--------------------------------------------------------------- commit dd52a54279005c3a994114950e378c884e1fee02 Author: Lennart Kolmodin Date: Fri Dec 19 09:35:21 2014 -0600 Add package flags to --show-options output Summary: --show-options will now include the package flags. Test Plan: Pass --show-options to ghc, it should include -package-id. Reviewers: austin, jstolarek Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D554 GHC Trac Issues: #9860 >--------------------------------------------------------------- dd52a54279005c3a994114950e378c884e1fee02 ghc/Main.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc/Main.hs b/ghc/Main.hs index d8be08a..b633d06 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -704,7 +704,7 @@ showOptions = putStr (unlines availableOptions) where availableOptions = map ((:) '-') $ getFlagNames mode_flags ++ - getFlagNames flagsDynamic ++ + getFlagNames flagsAll ++ (filterUnwantedStatic . getFlagNames $ flagsStatic) ++ flagsStaticNames getFlagNames opts = map getFlagName opts From git at git.haskell.org Fri Dec 19 15:44:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 15:44:05 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Further improvements to floating equalities (e9382e3) Message-ID: <20141219154405.E5FB43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/e9382e3dab2246a33675ffeae31a105d7cf7f426/ghc >--------------------------------------------------------------- commit e9382e3dab2246a33675ffeae31a105d7cf7f426 Author: Simon Peyton Jones Date: Fri Jul 18 09:35:24 2014 +0100 Further improvements to floating equalities This equality-floating stuff is horribly delicate! Trac #9316 showed up yet another corner case. The main changes are * include CTyVarEqs when "growing" the skolem set * do not include the kind argument to (~) when growing the skolem set I added a lot more comments as well (cherry picked from commit 4b3df0bb705c9287046c07bbc6c038960fbf8d53) >--------------------------------------------------------------- e9382e3dab2246a33675ffeae31a105d7cf7f426 compiler/typecheck/TcSimplify.lhs | 311 +++++++++++++-------- .../tests/indexed-types/should_compile/T9316.hs | 87 ++++++ testsuite/tests/indexed-types/should_compile/all.T | 1 + 3 files changed, 279 insertions(+), 120 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e9382e3dab2246a33675ffeae31a105d7cf7f426 From git at git.haskell.org Fri Dec 19 15:44:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 15:44:08 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: One more documentation note. (7fa9d83) Message-ID: <20141219154408.A71213A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/7fa9d836e3b3e16d3d69a8954cf500dfaa3ea54e/ghc >--------------------------------------------------------------- commit 7fa9d836e3b3e16d3d69a8954cf500dfaa3ea54e Author: Austin Seipp Date: Fri Dec 19 09:44:50 2014 -0600 One more documentation note. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 7fa9d836e3b3e16d3d69a8954cf500dfaa3ea54e docs/users_guide/bugs.xml | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/docs/users_guide/bugs.xml b/docs/users_guide/bugs.xml index dba0d86..8bb9772 100644 --- a/docs/users_guide/bugs.xml +++ b/docs/users_guide/bugs.xml @@ -466,6 +466,15 @@ checking for duplicates. The reason for this is efficiency, pure and simple. + GHC has a bug in 7.8 that causes the new extension + -XAutoDeriveTypeable to not take affect - + however, you can easily work around this by merely using + -XDeriveDataTypeable and using + deriving Typeable instead. See GHC issue + #9575. + + + GHC can warn about non-exhaustive or overlapping patterns (see ), and usually does so correctly. But not always. It gets confused by From git at git.haskell.org Fri Dec 19 15:46:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 15:46:49 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: One _more_ documentation note. (96b7ff1) Message-ID: <20141219154649.AB9B63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/96b7ff1c9f02d805f754da02ccf6a9f0ff3b92c5/ghc >--------------------------------------------------------------- commit 96b7ff1c9f02d805f754da02ccf6a9f0ff3b92c5 Author: Austin Seipp Date: Fri Dec 19 09:47:54 2014 -0600 One _more_ documentation note. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 96b7ff1c9f02d805f754da02ccf6a9f0ff3b92c5 docs/users_guide/7.8.4-notes.xml | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/docs/users_guide/7.8.4-notes.xml b/docs/users_guide/7.8.4-notes.xml index 376f795..7aab9a5 100644 --- a/docs/users_guide/7.8.4-notes.xml +++ b/docs/users_guide/7.8.4-notes.xml @@ -146,6 +146,13 @@ has been fixed (#9563). + + + A bug that caused type inference to infer the incorrect + type in the presence of certain type families and + constraints has been fixed (issue #9316). + + From git at git.haskell.org Fri Dec 19 16:05:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 16:05:33 +0000 (UTC) Subject: [commit: ghc] master: Add instance Lift Natural (2e28c82) Message-ID: <20141219160533.8039B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2e28c8262f8e329c3b5cf0c6782a4a810e490e82/ghc >--------------------------------------------------------------- commit 2e28c8262f8e329c3b5cf0c6782a4a810e490e82 Author: Richard Eisenberg Date: Fri Dec 19 10:29:54 2014 -0500 Add instance Lift Natural >--------------------------------------------------------------- 2e28c8262f8e329c3b5cf0c6782a4a810e490e82 libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 5 +++++ testsuite/tests/th/TH_Lift.hs | 4 ++++ 2 files changed, 9 insertions(+) diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 8e4b344..29be27a 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -29,6 +29,7 @@ import Data.Char ( isAlpha, isAlphaNum, isUpper ) import Data.Int import Data.Word import Data.Ratio +import Numeric.Natural import GHC.Generics ( Generic ) ----------------------------------------------------- @@ -452,6 +453,7 @@ sequenceQ = sequence class Lift t where lift :: t -> Q Exp +-- If you add any instances here, consider updating test th/TH_Lift instance Lift Integer where lift x = return (LitE (IntegerL x)) @@ -485,6 +487,9 @@ instance Lift Word32 where instance Lift Word64 where lift x = return (LitE (IntegerL (fromIntegral x))) +instance Lift Natural where + lift x = return (LitE (IntegerL (fromIntegral x))) + instance Integral a => Lift (Ratio a) where lift x = return (LitE (RationalL (toRational x))) diff --git a/testsuite/tests/th/TH_Lift.hs b/testsuite/tests/th/TH_Lift.hs index fd30af7..eff0f1b 100644 --- a/testsuite/tests/th/TH_Lift.hs +++ b/testsuite/tests/th/TH_Lift.hs @@ -8,6 +8,7 @@ import Language.Haskell.TH.Syntax import Data.Ratio import Data.Word import Data.Int +import Numeric.Natural a :: Integer a = $( (\x -> [| x |]) (5 :: Integer) ) @@ -42,6 +43,9 @@ f = $( (\x -> [| x |]) (5 :: Word32) ) g :: Word64 g = $( (\x -> [| x |]) (5 :: Word64) ) +g1 :: Natural +g1 = $( (\x -> [| x |]) (5 :: Natural) ) + h :: Rational h = $( (\x -> [| x |]) (5 % 3 :: Rational) ) From git at git.haskell.org Fri Dec 19 16:35:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 16:35:17 +0000 (UTC) Subject: [commit: ghc] master: Update Cabal submodule to latest 1.22 branch tip (e080546) Message-ID: <20141219163517.86E773A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e08054602a3f8f630aa2510f3d60512c997454db/ghc >--------------------------------------------------------------- commit e08054602a3f8f630aa2510f3d60512c997454db Author: Herbert Valerio Riedel Date: Fri Dec 19 17:35:24 2014 +0100 Update Cabal submodule to latest 1.22 branch tip >--------------------------------------------------------------- e08054602a3f8f630aa2510f3d60512c997454db libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 82d2fe1..4aabb4f 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 82d2fe1f5083e56f0b2d2c2409a3f673a56a5fe4 +Subproject commit 4aabb4f4b1c7fb6446ce619ddfdfa0d19516c721 From git at git.haskell.org Fri Dec 19 21:40:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 21:40:56 +0000 (UTC) Subject: [commit: ghc] master: Update directory submodule to latest snapshot (5cf7618) Message-ID: <20141219214056.557893A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5cf76186d373842bf64d49cecb09e0a9ddce3203/ghc >--------------------------------------------------------------- commit 5cf76186d373842bf64d49cecb09e0a9ddce3203 Author: Herbert Valerio Riedel Date: Fri Dec 19 21:36:18 2014 +0100 Update directory submodule to latest snapshot This pulls in > make `getModificationTime` support sub-second resolution on windows >--------------------------------------------------------------- 5cf76186d373842bf64d49cecb09e0a9ddce3203 libraries/directory | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/directory b/libraries/directory index bcb8c40..e22771f 160000 --- a/libraries/directory +++ b/libraries/directory @@ -1 +1 @@ -Subproject commit bcb8c40b5e0a17030bcc085b46bf8718ea713107 +Subproject commit e22771f4e9fbd30b2ed4af75cf4b19b9e4e94c7c From git at git.haskell.org Fri Dec 19 21:40:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 21:40:58 +0000 (UTC) Subject: [commit: ghc] master: Update Cabal submodule to latest 1.22 branch tip (c2fd51b) Message-ID: <20141219214058.EF6503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c2fd51b553ddf43d0d1fbb6e7b93626754a8c19f/ghc >--------------------------------------------------------------- commit c2fd51b553ddf43d0d1fbb6e7b93626754a8c19f Author: Herbert Valerio Riedel Date: Fri Dec 19 21:37:58 2014 +0100 Update Cabal submodule to latest 1.22 branch tip >--------------------------------------------------------------- c2fd51b553ddf43d0d1fbb6e7b93626754a8c19f libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 4aabb4f..d920a43 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 4aabb4f4b1c7fb6446ce619ddfdfa0d19516c721 +Subproject commit d920a43faba148ef63dff4d4a748ac5343380465 From git at git.haskell.org Fri Dec 19 22:33:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 22:33:30 +0000 (UTC) Subject: [commit: packages/hoopl] master: Prepare for 3.10.0.2 release (c9185a2) Message-ID: <20141219223330.591C33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hoopl On branch : master Link : http://git.haskell.org/packages/hoopl.git/commitdiff/c9185a27af3be3161644711a79164baeff4377b9 >--------------------------------------------------------------- commit c9185a27af3be3161644711a79164baeff4377b9 Author: Herbert Valerio Riedel Date: Fri Dec 19 23:30:38 2014 +0100 Prepare for 3.10.0.2 release >--------------------------------------------------------------- c9185a27af3be3161644711a79164baeff4377b9 changelog.md | 4 +++- hoopl.cabal | 2 +- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md index 234c993..b5b6382 100644 --- a/changelog.md +++ b/changelog.md @@ -1,9 +1,11 @@ # Changelog for [`hoopl` package](http://hackage.haskell.org/package/hoopl) -## 3.10.0.2 *TBA* +## 3.10.0.2 *Dec 2014* - Add support for `base-4.8.0.0` package version + - Mark a few modules as Safe rather than Trustworthy + ## 3.10.0.1 *Mar 2014* - Remove UTF8 character from hoopl.cabal to workaround issue diff --git a/hoopl.cabal b/hoopl.cabal index d487d49..559c443 100644 --- a/hoopl.cabal +++ b/hoopl.cabal @@ -17,7 +17,7 @@ Build-Type: Simple Cabal-Version: >=1.10 Synopsis: A library to support dataflow analysis and optimization Category: Compilers/Interpreters -Tested-With: GHC==7.6.3, GHC==7.6.2, GHC==7.6.1, GHC==7.4.2, GHC==7.4.1, GHC==7.2.2, GHC==7.0.4, GHC==7.0.3, GHC==7.0.2, GHC==7.0.1 +Tested-With: GHC>=7.0.1 Extra-Source-Files: README, hoopl.pdf, changelog.md Source-repository head From git at git.haskell.org Fri Dec 19 22:33:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 22:33:41 +0000 (UTC) Subject: [commit: packages/hoopl] tag 'hoopl-3.10.0.2-release' created Message-ID: <20141219223341.8BBC63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hoopl New tag : hoopl-3.10.0.2-release Referencing: 01e4c5162fe2c422bb907bceccb8d163771e58b1 From git at git.haskell.org Fri Dec 19 22:36:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Dec 2014 22:36:10 +0000 (UTC) Subject: [commit: ghc] master: Update hoopl submodule to 3.10.0.2 rls (8448635) Message-ID: <20141219223610.7E86F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8448635229733c890af837605865bf13c39aeb28/ghc >--------------------------------------------------------------- commit 8448635229733c890af837605865bf13c39aeb28 Author: Herbert Valerio Riedel Date: Fri Dec 19 23:36:14 2014 +0100 Update hoopl submodule to 3.10.0.2 rls [skip ci] >--------------------------------------------------------------- 8448635229733c890af837605865bf13c39aeb28 libraries/hoopl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/hoopl b/libraries/hoopl index a90a3af..c9185a2 160000 --- a/libraries/hoopl +++ b/libraries/hoopl @@ -1 +1 @@ -Subproject commit a90a3af92be400af8912555bce21b041a1c48ad4 +Subproject commit c9185a27af3be3161644711a79164baeff4377b9 From git at git.haskell.org Sat Dec 20 02:23:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Dec 2014 02:23:35 +0000 (UTC) Subject: [commit: ghc] master: Improved Backpack IR description. [skip ci] (68f717c) Message-ID: <20141220022335.51F1A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/68f717c05ea88e31f1a2abc9e82ed41b5ac02bee/ghc >--------------------------------------------------------------- commit 68f717c05ea88e31f1a2abc9e82ed41b5ac02bee Author: Edward Z. Yang Date: Fri Dec 19 21:23:52 2014 -0500 Improved Backpack IR description. [skip ci] Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 68f717c05ea88e31f1a2abc9e82ed41b5ac02bee docs/backpack/backpack-manual.pdf | Bin 188738 -> 199748 bytes docs/backpack/backpack-manual.tex | 206 ++++++++++++++++++++++++++++++-------- 2 files changed, 164 insertions(+), 42 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 68f717c05ea88e31f1a2abc9e82ed41b5ac02bee From git at git.haskell.org Sat Dec 20 02:40:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Dec 2014 02:40:45 +0000 (UTC) Subject: [commit: ghc] master: Optimize flattener by trying to reduce a TF before reducing its args. (8e2d858) Message-ID: <20141220024045.44F063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8e2d858bb837a322f26face78df1b6ef3898e762/ghc >--------------------------------------------------------------- commit 8e2d858bb837a322f26face78df1b6ef3898e762 Author: Richard Eisenberg Date: Wed Dec 17 23:30:15 2014 -0500 Optimize flattener by trying to reduce a TF before reducing its args. This has a demonstrated 2x speed boost on the T9872{a,b,c} tests. (#9872) >--------------------------------------------------------------- 8e2d858bb837a322f26face78df1b6ef3898e762 compiler/typecheck/TcFlatten.hs | 47 ++++++++++++++++++++++++++----------- testsuite/tests/perf/compiler/all.T | 14 +++++++---- 2 files changed, 42 insertions(+), 19 deletions(-) diff --git a/compiler/typecheck/TcFlatten.hs b/compiler/typecheck/TcFlatten.hs index 818965d..2c72c93 100644 --- a/compiler/typecheck/TcFlatten.hs +++ b/compiler/typecheck/TcFlatten.hs @@ -900,7 +900,9 @@ flatten_exact_fam_app fmode tc tys roles = tyConRolesX (feRole fmode) tc flatten_exact_fam_app_fully fmode tc tys - = do { (xis, cos) <- flatten_many_nom (setFEEqRel (setFEMode fmode FM_FlattenAll) NomEq) tys + -- See Note [Reduce type family applications eagerly] + = try_to_reduce tc tys False id $ + do { (xis, cos) <- flatten_many_nom (setFEEqRel (setFEMode fmode FM_FlattenAll) NomEq) tys ; let ret_co = mkTcTyConAppCo (feRole fmode) tc cos -- ret_co :: F xis ~ F tys @@ -922,15 +924,7 @@ flatten_exact_fam_app_fully fmode tc tys -- Try to reduce the family application right now -- See Note [Reduce type family applications eagerly] - _ -> do { mb_match <- matchFam tc xis - ; case mb_match of { - Just (norm_co, norm_ty) - -> do { (xi, final_co) <- flatten_one fmode norm_ty - ; let co = norm_co `mkTcTransCo` mkTcSymCo final_co - ; extendFlatCache tc xis ( co, xi - , fe_flavour fmode ) - ; return (xi, mkTcSymCo co `mkTcTransCo` ret_co) } ; - Nothing -> + _ -> try_to_reduce tc xis True (`mkTcTransCo` ret_co) $ do { let fam_ty = mkTyConApp tc xis ; (ev, fsk) <- newFlattenSkolem (fe_flavour fmode) (fe_loc fmode) @@ -951,7 +945,28 @@ flatten_exact_fam_app_fully fmode tc tys ; return (fsk_ty, maybeTcSubCo (fe_eq_rel fmode) (mkTcSymCo co) `mkTcTransCo` ret_co) } - } } } + } + + where + try_to_reduce :: TyCon -- F, family tycon + -> [Type] -- args, not necessarily flattened + -> Bool -- add to the flat cache? + -> ( TcCoercion -- :: xi ~ F args + -> TcCoercion ) -- what to return from outer function + -> TcS (Xi, TcCoercion) -- continuation upon failure + -> TcS (Xi, TcCoercion) + try_to_reduce tc tys cache update_co k + = do { mb_match <- matchFam tc tys + ; case mb_match of + Just (norm_co, norm_ty) + -> do { traceTcS "Eager T.F. reduction success" $ + vcat [ppr tc, ppr tys, ppr norm_ty, ppr cache] + ; (xi, final_co) <- flatten_one fmode norm_ty + ; let co = norm_co `mkTcTransCo` mkTcSymCo final_co + ; when cache $ + extendFlatCache tc tys (co, xi, fe_flavour fmode) + ; return (xi, update_co $ mkTcSymCo co) } + Nothing -> k } {- Note [Reduce type family applications eagerly] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -960,9 +975,13 @@ then, rather than flattening to a skolem etc, we may as well just reduce it on the spot to (Cons x t). This saves a lot of intermediate steps. Examples that are helped are tests T9872, and T5321Fun. -So just before we create the new skolem, we attempt to reduce it by one -step (using matchFam). If that works, then recursively flatten the rhs, -which may in turn do lots more reductions. +Performance testing indicates that it's best to try this *twice*, once +before flattening arguments and once after flattening arguments. +Adding the extra reduction attempt before flattening arguments cut +the allocation amounts for the T9872{a,b,c} tests by half. Testing +also indicated that the early reduction should not use the flat-cache, +but that the later reduction should. It's possible that with more +examples, we might learn that these knobs should be set differently. Once we've got a flat rhs, we extend the flatten-cache to record the result. Doing so can save lots of work when the same redex shows up diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 45fc504..517d284 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -559,9 +559,10 @@ test('T9675', test('T9872a', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 5848657456, 5) + [(wordsize(64), 2680733672, 5) # 2014-12-10 5521332656 Initally created # 2014-12-16 5848657456 Flattener parameterized over roles + # 2014-12-18 2680733672 Reduce type families even more eagerly ]), ], compile_fail, @@ -570,9 +571,10 @@ test('T9872a', test('T9872b', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 6892251912, 5) + [(wordsize(64), 3480212048, 5) # 2014-12-10 6483306280 Initally created # 2014-12-16 6892251912 Flattener parameterized over roles + # 2014-12-18 3480212048 Reduce type families even more eagerly ]), ], compile_fail, @@ -580,9 +582,10 @@ test('T9872b', test('T9872c', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 5842024784, 5) + [(wordsize(64), 2963554096, 5) # 2014-12-10 5495850096 Initally created # 2014-12-16 5842024784 Flattener parameterized over roles + # 2014-12-18 2963554096 Reduce type families even more eagerly ]), ], compile_fail, @@ -590,8 +593,9 @@ test('T9872c', test('T9872d', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 796071864, 5) - # 2014-12-19 796071864 Initally created + [(wordsize(64), 739189056, 5) + # 2014-12-18 796071864 Initally created + # 2014-12-18 739189056 Reduce type families even more eagerly ]), ], compile, From git at git.haskell.org Sat Dec 20 02:53:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Dec 2014 02:53:31 +0000 (UTC) Subject: [commit: ghc] branch 'wip/pattern-synonym-backport' created Message-ID: <20141220025331.91C693A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/pattern-synonym-backport Referencing: a91a2afa3a7e06f2f78ec4d479cc7ed527d305c5 From git at git.haskell.org Sat Dec 20 02:53:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Dec 2014 02:53:34 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonym-backport: In pattern synonym matchers, support unboxed continuation results (fixes #9783). (a91a2af) Message-ID: <20141220025334.CE4C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/pattern-synonym-backport Link : http://ghc.haskell.org/trac/ghc/changeset/a91a2afa3a7e06f2f78ec4d479cc7ed527d305c5/ghc >--------------------------------------------------------------- commit a91a2afa3a7e06f2f78ec4d479cc7ed527d305c5 Author: Dr. ERDI Gergo Date: Sat Dec 20 10:51:09 2014 +0800 In pattern synonym matchers, support unboxed continuation results (fixes #9783). This requires ensuring the continuations have arguments by adding a dummy Void# argument when needed. This is so that matching on a pattern synonym is lazy even when the result is unboxed, e.g. pattern P = () f P = 0# In this case, without dummy arguments, the generated matcher's type would be $mP :: forall (r :: ?). () -> r -> r -> r which is called in `f` at type `() -> Int# -> Int# -> Int#`, so it would be strict, in particular, in the failure continuation of `patError`. We work around this by making sure both continuations have arguments: $mP :: forall (r :: ?). () -> (Void# -> r) -> (Void# -> r) -> r Of course, if `P` (and thus, the success continuation) has any arguments, we are only adding the extra dummy argument to the failure continuation. (cherry picked from commit 474e535b6b121809a8d75df5a4c37dc574d3d302) >--------------------------------------------------------------- a91a2afa3a7e06f2f78ec4d479cc7ed527d305c5 compiler/basicTypes/PatSyn.lhs | 29 ++++++++++++++------ compiler/deSugar/DsUtils.lhs | 7 ++++- compiler/typecheck/TcPatSyn.lhs | 31 +++++++++++----------- testsuite/tests/patsyn/should_run/.gitignore | 1 + testsuite/tests/patsyn/should_run/T9783.hs | 15 +++++++++++ .../should_run/T9783.stdout} | 2 +- testsuite/tests/patsyn/should_run/all.T | 1 + 7 files changed, 61 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 a91a2afa3a7e06f2f78ec4d479cc7ed527d305c5 From git at git.haskell.org Sat Dec 20 03:34:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Dec 2014 03:34:55 +0000 (UTC) Subject: [commit: ghc] master: Change performance numbers for T3064 (397048a) Message-ID: <20141220033455.E70B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/397048afee42f086f14569048f80669c3b8c4436/ghc >--------------------------------------------------------------- commit 397048afee42f086f14569048f80669c3b8c4436 Author: Richard Eisenberg Date: Fri Dec 19 22:35:03 2014 -0500 Change performance numbers for T3064 >--------------------------------------------------------------- 397048afee42f086f14569048f80669c3b8c4436 testsuite/tests/perf/compiler/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 517d284..ce48c11 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -259,7 +259,7 @@ test('T3064', # 2014-01-22: 162457940 (x86/Linux) # 2014-12-01: 162457940 (Windows) - (wordsize(64), 363103840, 5)]), + (wordsize(64), 350418600, 5)]), # (amd64/Linux) (28/06/2011): 73259544 # (amd64/Linux) (07/02/2013): 224798696 # (amd64/Linux) (02/08/2013): 236404384, increase from roles @@ -273,6 +273,7 @@ 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) # (amd64/Linux) (10/12/2014): 363103840, improvements in constraint solver + # (Mac) (18/12/2014): 350418600, improvements to flattener ################################### # deactivated for now, as this metric became too volatile recently From git at git.haskell.org Sat Dec 20 08:46:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Dec 2014 08:46:45 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonym-backport: nlHsTyApps: for applying a function both on type- and term-level arguments (8ad7f1a) Message-ID: <20141220084645.BD1C73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/pattern-synonym-backport Link : http://ghc.haskell.org/trac/ghc/changeset/8ad7f1a049ffb4ce9bf6f72ee868185c7979285e/ghc >--------------------------------------------------------------- commit 8ad7f1a049ffb4ce9bf6f72ee868185c7979285e Author: Dr. ERDI Gergo Date: Sat Dec 20 10:56:07 2014 +0800 nlHsTyApps: for applying a function both on type- and term-level arguments (cherry picked from commit faeb0a687ea291cb2d497a7042af4829f55e223d) >--------------------------------------------------------------- 8ad7f1a049ffb4ce9bf6f72ee868185c7979285e compiler/hsSyn/HsUtils.lhs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/compiler/hsSyn/HsUtils.lhs b/compiler/hsSyn/HsUtils.lhs index a5ffda2..23a3cac 100644 --- a/compiler/hsSyn/HsUtils.lhs +++ b/compiler/hsSyn/HsUtils.lhs @@ -30,7 +30,7 @@ module HsUtils( mkHsOpApp, mkHsDo, mkHsComp, mkHsWrapPat, mkHsWrapPatCo, mkLHsPar, mkHsCmdCast, - nlHsTyApp, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, + nlHsTyApp, nlHsTyApps, nlHsVar, nlHsLit, nlHsApp, nlHsApps, nlHsIntLit, nlHsVarApps, nlHsDo, nlHsOpApp, nlHsLam, nlHsPar, nlHsIf, nlHsCase, nlList, mkLHsTupleExpr, mkLHsVarTuple, missingTupArg, toHsType, toHsKind, @@ -164,6 +164,9 @@ mkSimpleHsAlt pat expr nlHsTyApp :: name -> [Type] -> LHsExpr name nlHsTyApp fun_id tys = noLoc (HsWrap (mkWpTyApps tys) (HsVar fun_id)) +nlHsTyApps :: name -> [Type] -> [LHsExpr name] -> LHsExpr name +nlHsTyApps fun_id tys xs = foldl nlHsApp (nlHsTyApp fun_id tys) xs + --------- Adding parens --------- mkLHsPar :: LHsExpr name -> LHsExpr name -- Wrap in parens if hsExprNeedsParens says it needs them From git at git.haskell.org Sat Dec 20 08:46:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Dec 2014 08:46:48 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonym-backport: Refactor PatSynBind so that we can pass around PSBs instead of several arguments (846d930) Message-ID: <20141220084648.749D23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/pattern-synonym-backport Link : http://ghc.haskell.org/trac/ghc/changeset/846d93023ef94217620caab56d41cafb73c51a3a/ghc >--------------------------------------------------------------- commit 846d93023ef94217620caab56d41cafb73c51a3a Author: Dr. ERDI Gergo Date: Sat Dec 20 12:00:01 2014 +0800 Refactor PatSynBind so that we can pass around PSBs instead of several arguments (cherry picked from commit 893a261c8c15783c8f86c74f4e8c57df9c44a155) >--------------------------------------------------------------- 846d93023ef94217620caab56d41cafb73c51a3a compiler/hsSyn/HsBinds.lhs | 46 ++++++++++++++++-------------- compiler/hsSyn/HsUtils.lhs | 14 ++++++---- compiler/rename/RnBinds.lhs | 54 +++++++++++++++++++++--------------- compiler/typecheck/TcBinds.lhs | 9 +++--- compiler/typecheck/TcHsSyn.lhs | 17 ++++++------ compiler/typecheck/TcPatSyn.lhs | 8 ++---- compiler/typecheck/TcPatSyn.lhs-boot | 8 ++---- utils/ghctags/Main.hs | 2 +- 8 files changed, 84 insertions(+), 74 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 846d93023ef94217620caab56d41cafb73c51a3a From git at git.haskell.org Sat Dec 20 08:46:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Dec 2014 08:46:51 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonym-backport: When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments (263644d) Message-ID: <20141220084651.17CA23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/pattern-synonym-backport Link : http://ghc.haskell.org/trac/ghc/changeset/263644d7a15ad28def18173a23729262728a6515/ghc >--------------------------------------------------------------- commit 263644d7a15ad28def18173a23729262728a6515 Author: Dr. ERDI Gergo Date: Thu Nov 13 17:47:18 2014 +0800 When calling the success continuation of a matcher, pass existential tyvars as type arguments, not value arguments (cherry picked from commit 638991114f9358ee78f32d5d5c98bb3001b52ec9) >--------------------------------------------------------------- 263644d7a15ad28def18173a23729262728a6515 compiler/typecheck/TcPatSyn.lhs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 385c44f..17fe40b 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -32,7 +32,6 @@ import Data.Monoid import Bag import TcEvidence import BuildTyCl -import TypeRep #include "HsVersions.h" \end{code} @@ -126,7 +125,7 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; let tv_name = mkInternalName uniq (mkTyVarOcc "r") loc ; return $ mkTcTyVar tv_name openTypeKind (SkolemTv False) } ; matcher_name <- newImplicitBinder name mkMatcherOcc - ; let res_ty = TyVarTy res_tv + ; let res_ty = mkTyVarTy res_tv cont_args = if null args then [voidPrimId] else args cont_ty = mkSigmaTy ex_tvs prov_theta $ mkFunTys (map varType cont_args) res_ty @@ -141,7 +140,8 @@ tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_d ; scrutinee <- mkId "scrut" pat_ty ; cont <- mkId "cont" cont_ty - ; let cont' = nlHsApps cont $ map nlHsVar (ex_tvs ++ prov_dicts ++ cont_args) + ; let cont' = nlHsTyApps cont (map mkTyVarTy ex_tvs) $ + map nlHsVar (prov_dicts ++ cont_args) ; fail <- mkId "fail" fail_ty ; let fail' = nlHsApps fail [nlHsVar voidPrimId] From git at git.haskell.org Sat Dec 20 08:46:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Dec 2014 08:46:53 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonym-backport: Group PatSyn req/prov arguments together so that they're not all over the place (125d4a5) Message-ID: <20141220084653.B51923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/pattern-synonym-backport Link : http://ghc.haskell.org/trac/ghc/changeset/125d4a5300ec1fa049fab296bc364ff51cbff106/ghc >--------------------------------------------------------------- commit 125d4a5300ec1fa049fab296bc364ff51cbff106 Author: Dr. ERDI Gergo Date: Thu Nov 6 19:01:38 2014 +0800 Group PatSyn req/prov arguments together so that they're not all over the place (cherry picked from commit 65dc594b156c9cc5c2e9bc640f0762beaf3ca6ca) >--------------------------------------------------------------- 125d4a5300ec1fa049fab296bc364ff51cbff106 compiler/basicTypes/PatSyn.lhs | 27 ++++++++++++++------------- compiler/iface/BuildTyCl.lhs | 38 ++++++++++++++++++++------------------ compiler/iface/TcIface.lhs | 3 ++- compiler/typecheck/TcPatSyn.lhs | 4 ++-- 4 files changed, 38 insertions(+), 34 deletions(-) diff --git a/compiler/basicTypes/PatSyn.lhs b/compiler/basicTypes/PatSyn.lhs index e679fdd..528b95a 100644 --- a/compiler/basicTypes/PatSyn.lhs +++ b/compiler/basicTypes/PatSyn.lhs @@ -127,9 +127,9 @@ data PatSyn psInfix :: Bool, -- True <=> declared infix psUnivTyVars :: [TyVar], -- Universially-quantified type variables + psReqTheta :: ThetaType, -- Required dictionaries psExTyVars :: [TyVar], -- Existentially-quantified type vars psProvTheta :: ThetaType, -- Provided dictionaries - psReqTheta :: ThetaType, -- Required dictionaries psOrigResTy :: Type, -- Mentions only psUnivTyVars -- See Note [Matchers and wrappers for pattern synonyms] @@ -206,19 +206,20 @@ instance Data.Data PatSyn where \begin{code} -- | Build a new pattern synonym mkPatSyn :: Name - -> Bool -- ^ Is the pattern synonym declared infix? - -> [Type] -- ^ Original arguments - -> [TyVar] -- ^ Universially-quantified type variables - -> [TyVar] -- ^ Existentially-quantified type variables - -> ThetaType -- ^ Wanted dicts - -> ThetaType -- ^ Given dicts - -> Type -- ^ Original result type - -> Id -- ^ Name of matcher - -> Maybe Id -- ^ Name of wrapper + -> Bool -- ^ Is the pattern synonym declared infix? + -> ([TyVar], ThetaType) -- ^ Universially-quantified type variables + -- and required dicts + -> ([TyVar], ThetaType) -- ^ Existentially-quantified type variables + -- and provided dicts + -> [Type] -- ^ Original arguments + -> Type -- ^ Original result type + -> Id -- ^ Name of matcher + -> Maybe Id -- ^ Name of wrapper -> PatSyn -mkPatSyn name declared_infix orig_args - univ_tvs ex_tvs - prov_theta req_theta +mkPatSyn name declared_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) + orig_args orig_res_ty matcher wrapper = MkPatSyn {psName = name, psUnique = getUnique name, diff --git a/compiler/iface/BuildTyCl.lhs b/compiler/iface/BuildTyCl.lhs index fa46a73..31be15b 100644 --- a/compiler/iface/BuildTyCl.lhs +++ b/compiler/iface/BuildTyCl.lhs @@ -185,27 +185,29 @@ mkDataConStupidTheta tycon arg_tys univ_tvs ------------------------------------------------------ buildPatSyn :: Name -> Bool -> Id -> Maybe Id - -> [Type] - -> [TyVar] -> [TyVar] -- Univ and ext - -> ThetaType -> ThetaType -- Prov and req - -> Type -- Result type + -> ([TyVar], ThetaType) -- ^ Univ and req + -> ([TyVar], ThetaType) -- ^ Ex and prov + -> [Type] -- ^ Argument types + -> Type -- ^ Result type -> PatSyn buildPatSyn src_name declared_infix matcher wrapper - args univ_tvs ex_tvs prov_theta req_theta pat_ty - = mkPatSyn src_name declared_infix - args - univ_tvs ex_tvs - prov_theta req_theta - pat_ty - matcher - wrapper + (univ_tvs, req_theta) (ex_tvs, prov_theta) arg_tys pat_ty + = ASSERT((and [ univ_tvs == univ_tvs' + , ex_tvs == ex_tvs' + , pat_ty `eqType` pat_ty' + , prov_theta `eqTypes` prov_theta' + , req_theta `eqTypes` req_theta' + , arg_tys `eqTypes` arg_tys' + ])) + mkPatSyn src_name declared_infix + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty + matcher wrapper where - -- TODO: assert that these match the ones in the parameters - ((_:_univ_tvs'), _req_theta', tau) = tcSplitSigmaTy $ idType matcher - ([_pat_ty', cont_sigma, _], _) = tcSplitFunTys tau - (_ex_tvs', _prov_theta', cont_tau) = tcSplitSigmaTy cont_sigma - (_args', _) = tcSplitFunTys cont_tau - + ((_:univ_tvs'), req_theta', tau) = tcSplitSigmaTy $ idType matcher + ([pat_ty', cont_sigma, _], _) = tcSplitFunTys tau + (ex_tvs', prov_theta', cont_tau) = tcSplitSigmaTy cont_sigma + (arg_tys', _) = tcSplitFunTys cont_tau \end{code} diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index 398ae4e..873fdc1 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -608,7 +608,8 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name ; pat_ty <- tcIfaceType pat_ty ; arg_tys <- mapM tcIfaceType args ; return $ buildPatSyn name is_infix matcher wrapper - arg_tys univ_tvs ex_tvs prov_theta req_theta pat_ty } + (univ_tvs, req_theta) (ex_tvs, prov_theta) + arg_tys pat_ty } ; return $ AConLike . PatSynCon $ patsyn }}} where mk_doc n = ptext (sLit "Pattern synonym") <+> ppr n diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 17fe40b..55ec6b7 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -98,9 +98,9 @@ tcPatSynDecl lname@(L _ name) details lpat dir ; traceTc "tcPatSynDecl }" $ ppr name ; let patSyn = mkPatSyn name is_infix + (univ_tvs, req_theta) + (ex_tvs, prov_theta) (map varType args) - univ_tvs ex_tvs - prov_theta req_theta pat_ty matcher_id (fmap fst m_wrapper) ; return (patSyn, binds) } From git at git.haskell.org Sat Dec 20 08:46:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Dec 2014 08:46:56 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonym-backport: Rejig builders for pattern synonyms, especially unlifted ones (0f1f3e1) Message-ID: <20141220084656.8CB423A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/pattern-synonym-backport Link : http://ghc.haskell.org/trac/ghc/changeset/0f1f3e1db73fc528ebd53938e2c39af62263c739/ghc >--------------------------------------------------------------- commit 0f1f3e1db73fc528ebd53938e2c39af62263c739 Author: Dr. ERDI Gergo Date: Sat Dec 20 16:44:20 2014 +0800 Rejig builders for pattern synonyms, especially unlifted ones When a pattern synonym is for an unlifted pattern, its "builder" would naturally be a top-level unlifted binding, which isn't allowed. So we give it an extra Void# argument. Our Plan A involved then making *two* Ids for these builders, with some consequential fuss in the desugarer. This was more pain than I liked, so I've re-jigged it. * There is just one builder for a pattern synonym. * It may have an extra Void# arg, but this decision is signalled by the Bool in the psBuilder field. I did the same for the psMatcher field. Both Bools are serialised into interface files, so there is absolutely no doubt whether that extra Void# argument is required. * I renamed "wrapper" to "builder". We have too may "wrappers" * In order to deal with typecchecking occurrences of P in expressions, I refactored the tcInferId code in TcExpr. All of this allowed me to revert 5fe872 "Apply compulsory unfoldings during desugaring, except for `seq` which is special." which turned out to be a rather messy hack in DsBinds (cherry picked from commit e876208117a34fb58f7f1e470de2f954b3ca303d) >--------------------------------------------------------------- 0f1f3e1db73fc528ebd53938e2c39af62263c739 compiler/basicTypes/PatSyn.lhs | 171 +++++++++++++++---------- compiler/deSugar/DsUtils.lhs | 10 +- compiler/iface/BuildTyCl.lhs | 8 +- compiler/iface/IfaceSyn.lhs | 14 +-- compiler/iface/MkIface.lhs | 9 +- compiler/iface/TcIface.lhs | 17 ++- compiler/typecheck/TcBinds.lhs | 4 - compiler/typecheck/TcExpr.lhs | 27 ++-- compiler/typecheck/TcPatSyn.lhs | 264 +++++++++++++++++++++++++-------------- compiler/typecheck/TcRnMonad.lhs | 5 + 10 files changed, 316 insertions(+), 213 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0f1f3e1db73fc528ebd53938e2c39af62263c739 From git at git.haskell.org Sat Dec 20 13:36:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Dec 2014 13:36:42 +0000 (UTC) Subject: [commit: ghc] master: Use a new $b prefix for pattern synonym builder names, instead of re-using $W from wrappers (5326348) Message-ID: <20141220133642.A07053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5326348076b9ba091b5af8f5dababdb2a9ea1977/ghc >--------------------------------------------------------------- commit 5326348076b9ba091b5af8f5dababdb2a9ea1977 Author: Dr. ERDI Gergo Date: Sat Dec 20 21:34:08 2014 +0800 Use a new $b prefix for pattern synonym builder names, instead of re-using $W from wrappers >--------------------------------------------------------------- 5326348076b9ba091b5af8f5dababdb2a9ea1977 compiler/basicTypes/OccName.hs | 9 +++++++-- compiler/basicTypes/PatSyn.hs | 12 ++++++------ compiler/typecheck/TcPatSyn.hs | 2 +- 3 files changed, 14 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/OccName.hs b/compiler/basicTypes/OccName.hs index b7da021..0c23ddc 100644 --- a/compiler/basicTypes/OccName.hs +++ b/compiler/basicTypes/OccName.hs @@ -53,7 +53,9 @@ module OccName ( -- ** Derived 'OccName's isDerivedOccName, - mkDataConWrapperOcc, mkWorkerOcc, mkMatcherOcc, mkDefaultMethodOcc, + mkDataConWrapperOcc, mkWorkerOcc, + mkMatcherOcc, mkBuilderOcc, + mkDefaultMethodOcc, mkGenDefMethodOcc, mkDerivedTyConOcc, mkNewTyCoOcc, mkClassOpAuxOcc, mkCon2TagOcc, mkTag2ConOcc, mkMaxTagOcc, @@ -595,7 +597,9 @@ isDerivedOccName occ = ':':c:_ | isAlphaNum c -> True _other -> False -mkDataConWrapperOcc, mkWorkerOcc, mkMatcherOcc, mkDefaultMethodOcc, +mkDataConWrapperOcc, mkWorkerOcc, + mkMatcherOcc, mkBuilderOcc, + mkDefaultMethodOcc, mkGenDefMethodOcc, mkDerivedTyConOcc, mkClassDataConOcc, mkDictOcc, mkIPOcc, mkSpecOcc, mkForeignExportOcc, mkRepEqOcc, mkGenOcc1, mkGenOcc2, mkGenD, mkGenR, mkGen1R, mkGenRCo, @@ -608,6 +612,7 @@ mkDataConWrapperOcc, mkWorkerOcc, mkMatcherOcc, mkDefaultMethodOcc, mkDataConWrapperOcc = mk_simple_deriv varName "$W" mkWorkerOcc = mk_simple_deriv varName "$w" mkMatcherOcc = mk_simple_deriv varName "$m" +mkBuilderOcc = mk_simple_deriv varName "$b" mkDefaultMethodOcc = mk_simple_deriv varName "$dm" mkGenDefMethodOcc = mk_simple_deriv varName "$gdm" mkClassOpAuxOcc = mk_simple_deriv varName "$c" diff --git a/compiler/basicTypes/PatSyn.hs b/compiler/basicTypes/PatSyn.hs index f2cef7b..081968a 100644 --- a/compiler/basicTypes/PatSyn.hs +++ b/compiler/basicTypes/PatSyn.hs @@ -83,7 +83,7 @@ data PatSyn psBuilder :: Maybe (Id, Bool) -- Nothing => uni-directional pattern synonym -- Just (builder, is_unlifted) => bi-directional - -- Wrapper function, of type + -- Builder function, of type -- forall univ_tvs, ex_tvs. (prov_theta, req_theta) -- => arg_tys -> res_ty -- See Note [Builder for pattern synonyms with unboxed type] @@ -161,12 +161,12 @@ For *bidirectional* pattern synonyms, we also generate a "builder" function which implements the pattern synonym in an expression context. For our running example, it will be: - $WP :: forall t b. (Show (Maybe t), Ord b, Eq t, Num t) + $bP :: forall t b. (Show (Maybe t), Ord b, Eq t, Num t) => b -> T (Maybe t) - $WP x = MkT [x] (Just 42) + $bP x = MkT [x] (Just 42) NB: the existential/universal and required/provided split does not -apply to the wrapper since you are only putting stuff in, not getting +apply to the builder since you are only putting stuff in, not getting stuff out. Injectivity of bidirectional pattern synonyms is checked in @@ -181,8 +181,8 @@ would be a top-level declaration with an unboxed type. pattern P = 0# - $WP :: Void# -> Int# - $WP _ = 0# + $bP :: Void# -> Int# + $bP _ = 0# This means that when typechecking an occurrence of P in an expression, we must remember that the builder has this void argument. This is diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index 4c49fb6..9287757 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -326,7 +326,7 @@ mkPatSynBuilderId dir (L _ name) qtvs theta arg_tys pat_ty | isUnidirectional dir = return Nothing | otherwise - = do { builder_name <- newImplicitBinder name mkDataConWorkerOcc + = do { builder_name <- newImplicitBinder name mkBuilderOcc ; let builder_sigma = mkSigmaTy qtvs theta (mkFunTys builder_arg_tys pat_ty) builder_id = mkExportedLocalId VanillaId builder_name builder_sigma -- See Note [Exported LocalIds] in Id From git at git.haskell.org Sat Dec 20 21:09:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Dec 2014 21:09:56 +0000 (UTC) Subject: [commit: ghc] master: add runMeta hook (e7eef00) Message-ID: <20141220210956.4F3EC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e7eef005c1743d5fdc1162d717e98b304cd9fc5e/ghc >--------------------------------------------------------------- commit e7eef005c1743d5fdc1162d717e98b304cd9fc5e Author: Luite Stegeman Date: Fri Dec 19 18:28:17 2014 -0600 add runMeta hook Summary: The runMeta hook can be used to override how metaprogramming expressions are evaluated. It makes the metaprogramming request types explicit and has access to the TcM monad. This makes it a much more convenient starting point for implementing out of process Template Haskell than the existing hscCompileCoreExpr hook. Reviewers: hvr, edsko, austin, simonpj Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D501 >--------------------------------------------------------------- e7eef005c1743d5fdc1162d717e98b304cd9fc5e compiler/main/Hooks.hs | 3 + compiler/main/HscTypes.hs | 48 ++++++++++++++++ compiler/typecheck/TcSplice.hs | 123 +++++++++++++++++++++-------------------- 3 files changed, 114 insertions(+), 60 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e7eef005c1743d5fdc1162d717e98b304cd9fc5e From git at git.haskell.org Sat Dec 20 21:09:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Dec 2014 21:09:59 +0000 (UTC) Subject: [commit: ghc] master: trac #9744, make program name and product version configurable through DynFlags/Settings (4523d66) Message-ID: <20141220210959.03BAC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4523d669989ab3b08e360016a315d6f9cd4808b0/ghc >--------------------------------------------------------------- commit 4523d669989ab3b08e360016a315d6f9cd4808b0 Author: Luite Stegeman Date: Fri Dec 19 18:30:08 2014 -0600 trac #9744, make program name and product version configurable through DynFlags/Settings Summary: This allows GHC API clients to use a package database and dynamic library names that do not clash with those of the host GHC This also updates the Haddock submodule. Reviewers: hvr, austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D496 >--------------------------------------------------------------- 4523d669989ab3b08e360016a315d6f9cd4808b0 compiler/ghci/Linker.hs | 3 +-- compiler/main/DynFlags.hs | 11 ++++++++--- compiler/main/Packages.hs | 13 +++++++------ compiler/main/SysTools.hs | 2 ++ utils/haddock | 2 +- 5 files changed, 19 insertions(+), 12 deletions(-) diff --git a/compiler/ghci/Linker.hs b/compiler/ghci/Linker.hs index 8573f6a..3a91fc1 100644 --- a/compiler/ghci/Linker.hs +++ b/compiler/ghci/Linker.hs @@ -50,7 +50,6 @@ import SrcLoc import qualified Maybes import UniqSet import FastString -import Config import Platform import SysTools @@ -1217,7 +1216,7 @@ locateLib dflags is_hs dirs lib mk_dyn_obj_path dir = dir (lib <.> "dyn_o") mk_arch_path dir = dir ("lib" ++ lib <.> "a") - hs_dyn_lib_name = lib ++ "-ghc" ++ cProjectVersion + hs_dyn_lib_name = lib ++ '-':programName dflags ++ projectVersion dflags mk_hs_dyn_lib_path dir = dir mkHsSOName platform hs_dyn_lib_name so_name = mkSOName platform lib diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 239eed4..fca8219 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -65,7 +65,7 @@ module DynFlags ( -- ** System tool settings and locations Settings(..), - targetPlatform, + targetPlatform, programName, projectVersion, ghcUsagePath, ghciUsagePath, topDir, tmpDir, rawSettings, extraGccViaCFlags, systemPackageConfig, pgm_L, pgm_P, pgm_F, pgm_c, pgm_s, pgm_a, pgm_l, pgm_dll, pgm_T, @@ -901,6 +901,8 @@ data Settings = Settings { sGhciUsagePath :: FilePath, -- ditto sTopDir :: FilePath, sTmpDir :: String, -- no trailing '/' + sProgramName :: String, + sProjectVersion :: String, -- You shouldn't need to look things up in rawSettings directly. -- They should have their own fields instead. sRawSettings :: [(String, String)], @@ -941,7 +943,10 @@ data Settings = Settings { targetPlatform :: DynFlags -> Platform targetPlatform dflags = sTargetPlatform (settings dflags) - +programName :: DynFlags -> String +programName dflags = sProgramName (settings dflags) +projectVersion :: DynFlags -> String +projectVersion dflags = sProjectVersion (settings dflags) ghcUsagePath :: DynFlags -> FilePath ghcUsagePath dflags = sGhcUsagePath (settings dflags) ghciUsagePath :: DynFlags -> FilePath @@ -3914,7 +3919,7 @@ compilerInfo dflags -- in the settings file (as "lookup" uses the first match for the -- key) : rawSettings dflags - ++ [("Project version", cProjectVersion), + ++ [("Project version", projectVersion dflags), ("Project Git commit id", cProjectGitCommitId), ("Booter version", cBooterVersion), ("Stage", cStage), diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index 0a875b2..0ffa680 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -53,7 +53,6 @@ where import GHC.PackageDb import PackageConfig import DynFlags -import Config ( cProjectVersion ) import Name ( Name, nameModule_maybe ) import UniqFM import Module @@ -72,6 +71,7 @@ import System.Directory import System.FilePath as FilePath import qualified System.FilePath.Posix as FilePath.Posix import Control.Monad +import Data.Char ( toUpper ) import Data.List as List import Data.Map (Map) #if __GLASGOW_HASKELL__ < 709 @@ -338,7 +338,7 @@ getPackageConfRefs :: DynFlags -> IO [PkgConfRef] getPackageConfRefs dflags = do let system_conf_refs = [UserPkgConf, GlobalPkgConf] - e_pkg_path <- tryIO (getEnv "GHC_PACKAGE_PATH") + e_pkg_path <- tryIO (getEnv $ map toUpper (programName dflags) ++ "_PACKAGE_PATH") let base_conf_refs = case e_pkg_path of Left _ -> system_conf_refs Right path @@ -354,9 +354,9 @@ getPackageConfRefs dflags = do resolvePackageConfig :: DynFlags -> PkgConfRef -> IO (Maybe FilePath) resolvePackageConfig dflags GlobalPkgConf = return $ Just (systemPackageConfig dflags) -resolvePackageConfig _ UserPkgConf = handleIO (\_ -> return Nothing) $ do - appdir <- getAppUserDataDirectory "ghc" - let dir = appdir (TARGET_ARCH ++ '-':TARGET_OS ++ '-':cProjectVersion) +resolvePackageConfig dflags UserPkgConf = handleIO (\_ -> return Nothing) $ do + appdir <- getAppUserDataDirectory (programName dflags) + let dir = appdir (TARGET_ARCH ++ '-':TARGET_OS ++ '-':projectVersion dflags) pkgconf = dir "package.conf.d" exist <- doesDirectoryExist pkgconf return $ if exist then Just pkgconf else Nothing @@ -1107,7 +1107,8 @@ packageHsLibs dflags p = map (mkDynName . addSuffix) (hsLibraries p) mkDynName x | gopt Opt_Static dflags = x - | "HS" `isPrefixOf` x = x ++ "-ghc" ++ cProjectVersion + | "HS" `isPrefixOf` x = + x ++ '-':programName dflags ++ projectVersion dflags -- For non-Haskell libraries, we use the name "Cfoo". The .a -- file is libCfoo.a, and the .so is libfoo.so. That way the -- linker knows what we mean for the vanilla (-lCfoo) and dyn diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs index 375cf2e..7b6c82f 100644 --- a/compiler/main/SysTools.hs +++ b/compiler/main/SysTools.hs @@ -325,6 +325,8 @@ initSysTools mbMinusB sLdSupportsBuildId = ldSupportsBuildId, sLdSupportsFilelist = ldSupportsFilelist, sLdIsGnuLd = ldIsGnuLd, + sProgramName = "ghc", + sProjectVersion = cProjectVersion, sPgm_L = unlit_path, sPgm_P = (cpp_prog, cpp_args), sPgm_F = "", diff --git a/utils/haddock b/utils/haddock index 60ccf50..7f23bd5 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 60ccf50433d823f18ee63e9c25c979e7b81f2fc1 +Subproject commit 7f23bd526a6dd6ed0a2ddeeb30724606ea058ef5 From git at git.haskell.org Sun Dec 21 07:43:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 21 Dec 2014 07:43:59 +0000 (UTC) Subject: [commit: ghc] master: Check dflags for language extensions when deciding if "foreign " and "deriving " look like prefixes of valid declarations (fixes #9915) (3b497dd) Message-ID: <20141221074359.58D583A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3b497ddb231981bc6aeb5533426bf632ba126e39/ghc >--------------------------------------------------------------- commit 3b497ddb231981bc6aeb5533426bf632ba126e39 Author: Dr. ERDI Gergo Date: Sun Dec 21 15:07:43 2014 +0800 Check dflags for language extensions when deciding if "foreign " and "deriving " look like prefixes of valid declarations (fixes #9915) >--------------------------------------------------------------- 3b497ddb231981bc6aeb5533426bf632ba126e39 ghc/InteractiveUI.hs | 51 +++++++++++++++++----------- testsuite/tests/ghci/should_run/T9915.script | 5 +++ testsuite/tests/ghci/should_run/all.T | 1 + 3 files changed, 38 insertions(+), 19 deletions(-) diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index a1f0dba..4a296da 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -877,9 +877,17 @@ enqueueCommands cmds = do -- | If we one of these strings prefixes a command, then we treat it as a decl -- rather than a stmt. -declPrefixes :: [String] -declPrefixes = ["class ","data ","newtype ","type ","instance ", "deriving ", - "foreign ", "default ", "default("] +declPrefixes :: DynFlags -> [String] +declPrefixes dflags = keywords ++ concat opt_keywords + where + keywords = [ "class ", "instance " + , "data ", "newtype ", "type " + , "default ", "default(" + ] + + opt_keywords = [ ["foreign " | xopt Opt_ForeignFunctionInterface dflags] + , ["deriving " | xopt Opt_StandaloneDeriving dflags] + ] -- | Entry point to execute some haskell code from user runStmt :: String -> SingleStep -> GHCi Bool @@ -892,23 +900,28 @@ runStmt stmt step | "import " `isPrefixOf` stmt = do addImportToContext stmt; return False - -- data, class, newtype... - | any (flip isPrefixOf stmt) declPrefixes - = do _ <- liftIO $ tryIO $ hFlushAll stdin - result <- GhciMonad.runDecls stmt - afterRunStmt (const True) (GHC.RunOk result) - | otherwise - = do -- In the new IO library, read handles buffer data even if the Handle - -- is set to NoBuffering. This causes problems for GHCi where there - -- are really two stdin Handles. So we flush any bufferred data in - -- GHCi's stdin Handle here (only relevant if stdin is attached to - -- a file, otherwise the read buffer can't be flushed). - _ <- liftIO $ tryIO $ hFlushAll stdin - m_result <- GhciMonad.runStmt stmt step - case m_result of - Nothing -> return False - Just result -> afterRunStmt (const True) result + = do dflags <- getDynFlags + if any (`isPrefixOf` stmt) (declPrefixes dflags) + then run_decl + else run_stmt + where + run_decl = + do _ <- liftIO $ tryIO $ hFlushAll stdin + result <- GhciMonad.runDecls stmt + afterRunStmt (const True) (GHC.RunOk result) + + run_stmt = + do -- In the new IO library, read handles buffer data even if the Handle + -- is set to NoBuffering. This causes problems for GHCi where there + -- are really two stdin Handles. So we flush any bufferred data in + -- GHCi's stdin Handle here (only relevant if stdin is attached to + -- a file, otherwise the read buffer can't be flushed). + _ <- liftIO $ tryIO $ hFlushAll stdin + m_result <- GhciMonad.runStmt stmt step + case m_result of + Nothing -> return False + Just result -> afterRunStmt (const True) result -- | Clean up the GHCi environment after a statement has run afterRunStmt :: (SrcSpan -> Bool) -> GHC.RunResult -> GHCi Bool diff --git a/testsuite/tests/ghci/should_run/T9915.script b/testsuite/tests/ghci/should_run/T9915.script new file mode 100644 index 0000000..d504e05 --- /dev/null +++ b/testsuite/tests/ghci/should_run/T9915.script @@ -0,0 +1,5 @@ +:set -XHaskell98 +foreign = 42 +let foreign = 42 +foreign +foreign -- Note extra space after name! diff --git a/testsuite/tests/ghci/should_run/all.T b/testsuite/tests/ghci/should_run/all.T index c42681f..effad6a 100644 --- a/testsuite/tests/ghci/should_run/all.T +++ b/testsuite/tests/ghci/should_run/all.T @@ -20,3 +20,4 @@ test('T3171', test('ghcirun004', just_ghci, compile_and_run, ['']) test('T8377', just_ghci, compile_and_run, ['']) +test('T9915', just_ghci, ghci_script, ['T9915.script']) From git at git.haskell.org Sun Dec 21 08:22:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 21 Dec 2014 08:22:04 +0000 (UTC) Subject: [commit: ghc] master: Add expected output to T9915 test (6713f0d) Message-ID: <20141221082204.7F14F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6713f0d9ad4a2d875d8f7b245c1c0ca77ce1617f/ghc >--------------------------------------------------------------- commit 6713f0d9ad4a2d875d8f7b245c1c0ca77ce1617f Author: Dr. ERDI Gergo Date: Sun Dec 21 16:19:42 2014 +0800 Add expected output to T9915 test >--------------------------------------------------------------- 6713f0d9ad4a2d875d8f7b245c1c0ca77ce1617f testsuite/tests/ghci/should_run/T9915.stderr | 2 ++ .../{array/should_run/arr020.stdout => ghci/should_run/T9915.stdout} | 0 2 files changed, 2 insertions(+) diff --git a/testsuite/tests/ghci/should_run/T9915.stderr b/testsuite/tests/ghci/should_run/T9915.stderr new file mode 100644 index 0000000..de2c5cb --- /dev/null +++ b/testsuite/tests/ghci/should_run/T9915.stderr @@ -0,0 +1,2 @@ + +:3:9: parse error on input ?=? diff --git a/testsuite/tests/array/should_run/arr020.stdout b/testsuite/tests/ghci/should_run/T9915.stdout similarity index 100% copy from testsuite/tests/array/should_run/arr020.stdout copy to testsuite/tests/ghci/should_run/T9915.stdout From git at git.haskell.org Sun Dec 21 11:22:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 21 Dec 2014 11:22:35 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T9900' created Message-ID: <20141221112235.4F2AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T9900 Referencing: 20acaa7785d910d36d46c4eae9e9cce4000635d1 From git at git.haskell.org Sun Dec 21 11:22:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 21 Dec 2014 11:22:38 +0000 (UTC) Subject: [commit: ghc] wip/T9900: Support pattern synonyms in GHCi (fixes #9900) (20acaa7) Message-ID: <20141221112238.74FE43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9900 Link : http://ghc.haskell.org/trac/ghc/changeset/20acaa7785d910d36d46c4eae9e9cce4000635d1/ghc >--------------------------------------------------------------- commit 20acaa7785d910d36d46c4eae9e9cce4000635d1 Author: Dr. ERDI Gergo Date: Sun Dec 21 15:01:15 2014 +0800 Support pattern synonyms in GHCi (fixes #9900) This involves recognizing lines starting with `"pattern "` as declarations, keeping non-exported pattern synonyms in `deSugar`, and including pattern synonyms in the result of `hscDeclsWithLocation`. >--------------------------------------------------------------- 20acaa7785d910d36d46c4eae9e9cce4000635d1 compiler/deSugar/Desugar.hs | 2 +- compiler/main/HscMain.hs | 6 ++++-- compiler/main/HscTypes.hs | 5 +++-- ghc/InteractiveUI.hs | 1 + testsuite/tests/patsyn/should_run/all.T | 5 +++++ testsuite/tests/patsyn/should_run/ghci.script | 8 ++++++++ testsuite/tests/patsyn/should_run/ghci.stderr | 2 ++ testsuite/tests/patsyn/should_run/ghci.stdout | 3 +++ 8 files changed, 27 insertions(+), 5 deletions(-) diff --git a/compiler/deSugar/Desugar.hs b/compiler/deSugar/Desugar.hs index ac35464..4695543 100644 --- a/compiler/deSugar/Desugar.hs +++ b/compiler/deSugar/Desugar.hs @@ -184,7 +184,7 @@ deSugar hsc_env mg_fam_insts = fam_insts, mg_inst_env = inst_env, mg_fam_inst_env = fam_inst_env, - mg_patsyns = filter ((`elemNameSet` export_set) . patSynName) patsyns, + mg_patsyns = patsyns, mg_rules = ds_rules_for_imps, mg_binds = ds_binds, mg_foreign = ds_fords, diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index c5cb9a1..5af28cb 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -128,6 +128,7 @@ import CostCentre import ProfInit import TyCon import Name +import ConLike import SimplStg ( stg2stg ) import Cmm import CmmParse ( parseCmmFile ) @@ -1505,6 +1506,7 @@ hscDeclsWithLocation hsc_env0 str source linenumber = liftIO $ linkDecls hsc_env src_span cbc let tcs = filterOut isImplicitTyCon (mg_tcs simpl_mg) + patsyns = mg_patsyns simpl_mg ext_ids = [ id | id <- bindersOfBinds core_binds , isExternalName (idName id) @@ -1515,11 +1517,11 @@ hscDeclsWithLocation hsc_env0 str source linenumber = -- The DFunIds are in 'cls_insts' (see Note [ic_tythings] in HscTypes -- Implicit Ids are implicit in tcs - tythings = map AnId ext_ids ++ map ATyCon tcs + tythings = map AnId ext_ids ++ map ATyCon tcs ++ map (AConLike . PatSynCon) patsyns let icontext = hsc_IC hsc_env ictxt = extendInteractiveContext icontext ext_ids tcs - cls_insts fam_insts defaults + cls_insts fam_insts defaults patsyns return (tythings, ictxt) hscImport :: HscEnv -> String -> IO (ImportDecl RdrName) diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs index 909004e..29ee78c 100644 --- a/compiler/main/HscTypes.hs +++ b/compiler/main/HscTypes.hs @@ -1403,8 +1403,9 @@ extendInteractiveContext :: InteractiveContext -> [Id] -> [TyCon] -> [ClsInst] -> [FamInst] -> Maybe [Type] + -> [PatSyn] -> InteractiveContext -extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults +extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults new_patsyns = ictxt { ic_mod_index = ic_mod_index ictxt + 1 -- Always bump this; even instances should create -- a new mod_index (Trac #9426) @@ -1413,7 +1414,7 @@ extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults , ic_instances = (new_cls_insts ++ old_cls_insts, new_fam_insts ++ old_fam_insts) , ic_default = defaults } where - new_tythings = map AnId ids ++ map ATyCon tcs + new_tythings = map AnId ids ++ map ATyCon tcs ++ map (AConLike . PatSynCon) new_patsyns old_tythings = filterOut (shadowed_by ids) (ic_tythings ictxt) -- Discard old instances that have been fully overrridden diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 4a296da..b66db24 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -887,6 +887,7 @@ declPrefixes dflags = keywords ++ concat opt_keywords opt_keywords = [ ["foreign " | xopt Opt_ForeignFunctionInterface dflags] , ["deriving " | xopt Opt_StandaloneDeriving dflags] + , ["pattern " | xopt Opt_PatternSynonyms dflags] ] -- | Entry point to execute some haskell code from user diff --git a/testsuite/tests/patsyn/should_run/all.T b/testsuite/tests/patsyn/should_run/all.T index 40ec3e3..2f496a6 100644 --- a/testsuite/tests/patsyn/should_run/all.T +++ b/testsuite/tests/patsyn/should_run/all.T @@ -1,3 +1,7 @@ +# We only want to run these tests with GHCi +def just_ghci( name, opts ): + opts.only_ways = ['ghci'] + test('eval', normal, compile_and_run, ['']) test('match', normal, compile_and_run, ['']) test('ex-prov-run', normal, compile_and_run, ['']) @@ -6,3 +10,4 @@ test('bidir-explicit-scope', normal, compile_and_run, ['']) test('T9783', normal, compile_and_run, ['']) test('match-unboxed', normal, compile_and_run, ['']) test('unboxed-wrapper', normal, compile_and_run, ['']) +test('ghci', just_ghci, ghci_script, ['ghci.script']) diff --git a/testsuite/tests/patsyn/should_run/ghci.script b/testsuite/tests/patsyn/should_run/ghci.script new file mode 100644 index 0000000..cd71e33 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/ghci.script @@ -0,0 +1,8 @@ +:set -XPatternSynonyms + +pattern Single x = [x] +:i Single +let foo (Single x) = Single (not x) +:t foo +foo [True] +foo [True, False] diff --git a/testsuite/tests/patsyn/should_run/ghci.stderr b/testsuite/tests/patsyn/should_run/ghci.stderr new file mode 100644 index 0000000..9593b15 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/ghci.stderr @@ -0,0 +1,2 @@ +*** Exception: :6:5-35: Non-exhaustive patterns in function foo + diff --git a/testsuite/tests/patsyn/should_run/ghci.stdout b/testsuite/tests/patsyn/should_run/ghci.stdout new file mode 100644 index 0000000..796aa72 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/ghci.stdout @@ -0,0 +1,3 @@ +pattern Single :: t -> [t] -- Defined at :4:9 +foo :: [Bool] -> [Bool] +[False] From git at git.haskell.org Mon Dec 22 11:04:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 11:04:34 +0000 (UTC) Subject: [commit: ghc] master: Strip leading whitespace before checking if a statement looks like a declaration (fixes #9914) (707fb3a) Message-ID: <20141222110434.7FA7E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/707fb3aa2b058cb4245708d6a63019b3e32f795c/ghc >--------------------------------------------------------------- commit 707fb3aa2b058cb4245708d6a63019b3e32f795c Author: Dr. ERDI Gergo Date: Mon Dec 22 19:01:37 2014 +0800 Strip leading whitespace before checking if a statement looks like a declaration (fixes #9914) >--------------------------------------------------------------- 707fb3aa2b058cb4245708d6a63019b3e32f795c ghc/InteractiveUI.hs | 6 ++++-- testsuite/tests/ghci/should_run/T9914.script | 9 +++++++++ testsuite/tests/ghci/should_run/T9914.stdout | 5 +++++ testsuite/tests/ghci/should_run/all.T | 1 + 4 files changed, 19 insertions(+), 2 deletions(-) diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 4a296da..7d6c9ba 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -897,12 +897,12 @@ runStmt stmt step = return False -- import - | "import " `isPrefixOf` stmt + | stmt `looks_like` "import " = do addImportToContext stmt; return False | otherwise = do dflags <- getDynFlags - if any (`isPrefixOf` stmt) (declPrefixes dflags) + if any (stmt `looks_like`) (declPrefixes dflags) then run_decl else run_stmt where @@ -923,6 +923,8 @@ runStmt stmt step Nothing -> return False Just result -> afterRunStmt (const True) result + s `looks_like` prefix = prefix `isPrefixOf` dropWhile isSpace s + -- | Clean up the GHCi environment after a statement has run afterRunStmt :: (SrcSpan -> Bool) -> GHC.RunResult -> GHCi Bool afterRunStmt _ (GHC.RunException e) = liftIO $ Exception.throwIO e diff --git a/testsuite/tests/ghci/should_run/T9914.script b/testsuite/tests/ghci/should_run/T9914.script new file mode 100644 index 0000000..d40f46f --- /dev/null +++ b/testsuite/tests/ghci/should_run/T9914.script @@ -0,0 +1,9 @@ +let x = 1 +x + let x = 2 -- Note leading whitespace +x +2 +data T1 = MkT1 +:i T1 + data T2 = MkT2 -- Note leading whitespace +:i T2 diff --git a/testsuite/tests/ghci/should_run/T9914.stdout b/testsuite/tests/ghci/should_run/T9914.stdout new file mode 100644 index 0000000..3dd5aff --- /dev/null +++ b/testsuite/tests/ghci/should_run/T9914.stdout @@ -0,0 +1,5 @@ +1 +2 +2 +data T1 = MkT1 -- Defined at :7:1 +data T2 = MkT2 -- Defined at :9:2 diff --git a/testsuite/tests/ghci/should_run/all.T b/testsuite/tests/ghci/should_run/all.T index effad6a..b28e4a3 100644 --- a/testsuite/tests/ghci/should_run/all.T +++ b/testsuite/tests/ghci/should_run/all.T @@ -20,4 +20,5 @@ test('T3171', test('ghcirun004', just_ghci, compile_and_run, ['']) test('T8377', just_ghci, compile_and_run, ['']) +test('T9914', just_ghci, ghci_script, ['T9914.script']) test('T9915', just_ghci, ghci_script, ['T9915.script']) From git at git.haskell.org Mon Dec 22 11:45:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 11:45:11 +0000 (UTC) Subject: [commit: ghc] master: Update pretty and random submodules (4f80084) Message-ID: <20141222114511.0159B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4f800847c4f5ae65d7bc0426e24005488492b62e/ghc >--------------------------------------------------------------- commit 4f800847c4f5ae65d7bc0426e24005488492b62e Author: Herbert Valerio Riedel Date: Mon Dec 22 12:44:33 2014 +0100 Update pretty and random submodules This updates those two packages to their most recent respective proper releases. >--------------------------------------------------------------- 4f800847c4f5ae65d7bc0426e24005488492b62e libraries/pretty | 2 +- libraries/random | 2 +- testsuite/tests/th/TH_Roles2.stderr | 5 +++-- 3 files changed, 5 insertions(+), 4 deletions(-) diff --git a/libraries/pretty b/libraries/pretty index 110b105..c59e1df 160000 --- a/libraries/pretty +++ b/libraries/pretty @@ -1 +1 @@ -Subproject commit 110b105c491387a73dd37b4f86a686ed131767b2 +Subproject commit c59e1df384b2bc7710c5efcb80a9341d172a7ff1 diff --git a/libraries/random b/libraries/random index 180aa65..cfdfe6f 160000 --- a/libraries/random +++ b/libraries/random @@ -1 +1 @@ -Subproject commit 180aa65507d5b7c63d9f438ff908774bafc88d0d +Subproject commit cfdfe6f09ad414fde5b855cc5f90207533413241 diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index 3426537..adf820c 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -4,8 +4,9 @@ TYPE CONSTRUCTORS data T (a :: k) COERCION AXIOMS Dependent modules: [] -Dependent packages: [base-4.8.0.0, ghc-prim-0.3.1.0, - integer-gmp-0.5.1.0, pretty-1.1.1.1, template-haskell-2.10.0.0] +Dependent packages: [array-0.5.0.1, base-4.8.0.0, deepseq-1.4.0.0, + ghc-prim-0.3.1.0, integer-gmp-1.0.0.0, pretty-1.1.1.3, + template-haskell-2.10.0.0] ==================== Typechecker ==================== From git at git.haskell.org Mon Dec 22 11:45:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 11:45:13 +0000 (UTC) Subject: [commit: ghc] master: Update containers submodule to 0.5.6.2 release (2ba36b6) Message-ID: <20141222114513.93B673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2ba36b656f7f0522d702ae0cc92b5fbe289f1333/ghc >--------------------------------------------------------------- commit 2ba36b656f7f0522d702ae0cc92b5fbe289f1333 Author: Herbert Valerio Riedel Date: Mon Dec 22 12:45:34 2014 +0100 Update containers submodule to 0.5.6.2 release >--------------------------------------------------------------- 2ba36b656f7f0522d702ae0cc92b5fbe289f1333 libraries/containers | 2 +- testsuite/tests/package/package01e.stderr | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/containers b/libraries/containers index ddf4e4a..924fafe 160000 --- a/libraries/containers +++ b/libraries/containers @@ -1 +1 @@ -Subproject commit ddf4e4a7abbfb81161251437a6a5bbe8167a7cde +Subproject commit 924fafe1030301ee1d62d7acd576e86b50251157 diff --git a/testsuite/tests/package/package01e.stderr b/testsuite/tests/package/package01e.stderr index 54f501c..5b169aa 100644 --- a/testsuite/tests/package/package01e.stderr +++ b/testsuite/tests/package/package01e.stderr @@ -1,10 +1,10 @@ package01e.hs:2:1: Failed to load interface for ?Data.Map? - It is a member of the hidden package ?containers-0.5.6.1?. + It is a member of the hidden package ?containers-0.5.6.2?. Use -v to see a list of the files searched for. package01e.hs:3:1: Failed to load interface for ?Data.IntMap? - It is a member of the hidden package ?containers-0.5.6.1?. + It is a member of the hidden package ?containers-0.5.6.2?. Use -v to see a list of the files searched for. From git at git.haskell.org Mon Dec 22 12:29:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 12:29:11 +0000 (UTC) Subject: [commit: ghc] wip/T9900: Support pattern synonyms in GHCi (fixes #9900) (b01aaea) Message-ID: <20141222122911.13BAB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9900 Link : http://ghc.haskell.org/trac/ghc/changeset/b01aaea0c2cc4d9805130861ee1ad677346ff1e0/ghc >--------------------------------------------------------------- commit b01aaea0c2cc4d9805130861ee1ad677346ff1e0 Author: Dr. ERDI Gergo Date: Sun Dec 21 15:01:15 2014 +0800 Support pattern synonyms in GHCi (fixes #9900) This involves recognizing lines starting with `"pattern "` as declarations, keeping non-exported pattern synonyms in `deSugar`, and including pattern synonyms in the result of `hscDeclsWithLocation`. >--------------------------------------------------------------- b01aaea0c2cc4d9805130861ee1ad677346ff1e0 compiler/deSugar/Desugar.hs | 2 +- compiler/main/HscMain.hs | 6 ++++-- compiler/main/HscTypes.hs | 5 +++-- ghc/InteractiveUI.hs | 1 + testsuite/tests/patsyn/should_run/all.T | 5 +++++ testsuite/tests/patsyn/should_run/ghci.script | 8 ++++++++ testsuite/tests/patsyn/should_run/ghci.stderr | 2 ++ testsuite/tests/patsyn/should_run/ghci.stdout | 3 +++ 8 files changed, 27 insertions(+), 5 deletions(-) diff --git a/compiler/deSugar/Desugar.hs b/compiler/deSugar/Desugar.hs index ac35464..4695543 100644 --- a/compiler/deSugar/Desugar.hs +++ b/compiler/deSugar/Desugar.hs @@ -184,7 +184,7 @@ deSugar hsc_env mg_fam_insts = fam_insts, mg_inst_env = inst_env, mg_fam_inst_env = fam_inst_env, - mg_patsyns = filter ((`elemNameSet` export_set) . patSynName) patsyns, + mg_patsyns = patsyns, mg_rules = ds_rules_for_imps, mg_binds = ds_binds, mg_foreign = ds_fords, diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index c5cb9a1..5af28cb 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -128,6 +128,7 @@ import CostCentre import ProfInit import TyCon import Name +import ConLike import SimplStg ( stg2stg ) import Cmm import CmmParse ( parseCmmFile ) @@ -1505,6 +1506,7 @@ hscDeclsWithLocation hsc_env0 str source linenumber = liftIO $ linkDecls hsc_env src_span cbc let tcs = filterOut isImplicitTyCon (mg_tcs simpl_mg) + patsyns = mg_patsyns simpl_mg ext_ids = [ id | id <- bindersOfBinds core_binds , isExternalName (idName id) @@ -1515,11 +1517,11 @@ hscDeclsWithLocation hsc_env0 str source linenumber = -- The DFunIds are in 'cls_insts' (see Note [ic_tythings] in HscTypes -- Implicit Ids are implicit in tcs - tythings = map AnId ext_ids ++ map ATyCon tcs + tythings = map AnId ext_ids ++ map ATyCon tcs ++ map (AConLike . PatSynCon) patsyns let icontext = hsc_IC hsc_env ictxt = extendInteractiveContext icontext ext_ids tcs - cls_insts fam_insts defaults + cls_insts fam_insts defaults patsyns return (tythings, ictxt) hscImport :: HscEnv -> String -> IO (ImportDecl RdrName) diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs index 909004e..29ee78c 100644 --- a/compiler/main/HscTypes.hs +++ b/compiler/main/HscTypes.hs @@ -1403,8 +1403,9 @@ extendInteractiveContext :: InteractiveContext -> [Id] -> [TyCon] -> [ClsInst] -> [FamInst] -> Maybe [Type] + -> [PatSyn] -> InteractiveContext -extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults +extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults new_patsyns = ictxt { ic_mod_index = ic_mod_index ictxt + 1 -- Always bump this; even instances should create -- a new mod_index (Trac #9426) @@ -1413,7 +1414,7 @@ extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults , ic_instances = (new_cls_insts ++ old_cls_insts, new_fam_insts ++ old_fam_insts) , ic_default = defaults } where - new_tythings = map AnId ids ++ map ATyCon tcs + new_tythings = map AnId ids ++ map ATyCon tcs ++ map (AConLike . PatSynCon) new_patsyns old_tythings = filterOut (shadowed_by ids) (ic_tythings ictxt) -- Discard old instances that have been fully overrridden diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 7d6c9ba..d4855ac 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -887,6 +887,7 @@ declPrefixes dflags = keywords ++ concat opt_keywords opt_keywords = [ ["foreign " | xopt Opt_ForeignFunctionInterface dflags] , ["deriving " | xopt Opt_StandaloneDeriving dflags] + , ["pattern " | xopt Opt_PatternSynonyms dflags] ] -- | Entry point to execute some haskell code from user diff --git a/testsuite/tests/patsyn/should_run/all.T b/testsuite/tests/patsyn/should_run/all.T index 40ec3e3..2f496a6 100644 --- a/testsuite/tests/patsyn/should_run/all.T +++ b/testsuite/tests/patsyn/should_run/all.T @@ -1,3 +1,7 @@ +# We only want to run these tests with GHCi +def just_ghci( name, opts ): + opts.only_ways = ['ghci'] + test('eval', normal, compile_and_run, ['']) test('match', normal, compile_and_run, ['']) test('ex-prov-run', normal, compile_and_run, ['']) @@ -6,3 +10,4 @@ test('bidir-explicit-scope', normal, compile_and_run, ['']) test('T9783', normal, compile_and_run, ['']) test('match-unboxed', normal, compile_and_run, ['']) test('unboxed-wrapper', normal, compile_and_run, ['']) +test('ghci', just_ghci, ghci_script, ['ghci.script']) diff --git a/testsuite/tests/patsyn/should_run/ghci.script b/testsuite/tests/patsyn/should_run/ghci.script new file mode 100644 index 0000000..cd71e33 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/ghci.script @@ -0,0 +1,8 @@ +:set -XPatternSynonyms + +pattern Single x = [x] +:i Single +let foo (Single x) = Single (not x) +:t foo +foo [True] +foo [True, False] diff --git a/testsuite/tests/patsyn/should_run/ghci.stderr b/testsuite/tests/patsyn/should_run/ghci.stderr new file mode 100644 index 0000000..9593b15 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/ghci.stderr @@ -0,0 +1,2 @@ +*** Exception: :6:5-35: Non-exhaustive patterns in function foo + diff --git a/testsuite/tests/patsyn/should_run/ghci.stdout b/testsuite/tests/patsyn/should_run/ghci.stdout new file mode 100644 index 0000000..796aa72 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/ghci.stdout @@ -0,0 +1,3 @@ +pattern Single :: t -> [t] -- Defined at :4:9 +foo :: [Bool] -> [Bool] +[False] From git at git.haskell.org Mon Dec 22 12:29:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 12:29:13 +0000 (UTC) Subject: [commit: ghc] wip/T9900's head updated: Support pattern synonyms in GHCi (fixes #9900) (b01aaea) Message-ID: <20141222122913.520233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9900' now includes: 707fb3a Strip leading whitespace before checking if a statement looks like a declaration (fixes #9914) b01aaea Support pattern synonyms in GHCi (fixes #9900) From git at git.haskell.org Mon Dec 22 13:24:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 13:24:54 +0000 (UTC) Subject: [commit: ghc] master: For :info, return all matching Names, rather than complaining about ambiguity (cf0a55d) Message-ID: <20141222132454.36F6F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cf0a55d76cf945a97fc229b77d6e6177fb14125d/ghc >--------------------------------------------------------------- commit cf0a55d76cf945a97fc229b77d6e6177fb14125d Author: Simon Peyton Jones Date: Mon Dec 22 12:00:10 2014 +0000 For :info, return all matching Names, rather than complaining about ambiguity This fixes Trac #9881, and gives more helpful output in the case of ambiguity. Certainly more helpful than the positively-misleading error we get right now. >--------------------------------------------------------------- cf0a55d76cf945a97fc229b77d6e6177fb14125d compiler/rename/RnEnv.hs | 81 ++++++++++++++-------- compiler/typecheck/TcRnDriver.hs | 39 +++-------- .../tests/ghci.debugger/scripts/break019.stderr | 2 +- testsuite/tests/ghci/scripts/T9881.script | 3 + testsuite/tests/ghci/scripts/T9881.stdout | 32 +++++++++ testsuite/tests/ghci/scripts/all.T | 1 + 6 files changed, 100 insertions(+), 58 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc cf0a55d76cf945a97fc229b77d6e6177fb14125d From git at git.haskell.org Mon Dec 22 13:24:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 13:24:56 +0000 (UTC) Subject: [commit: ghc] master: Comments only (eb4d96e) Message-ID: <20141222132456.C9B453A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eb4d96e15991d8a03fcbf2385a14dc7e4cb64bcf/ghc >--------------------------------------------------------------- commit eb4d96e15991d8a03fcbf2385a14dc7e4cb64bcf Author: Simon Peyton Jones Date: Mon Dec 22 12:43:58 2014 +0000 Comments only >--------------------------------------------------------------- eb4d96e15991d8a03fcbf2385a14dc7e4cb64bcf ghc/InteractiveUI.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 7d6c9ba..d478336 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -876,7 +876,8 @@ enqueueCommands cmds = do setGHCiState st{ cmdqueue = cmds ++ cmdqueue st } -- | If we one of these strings prefixes a command, then we treat it as a decl --- rather than a stmt. +-- rather than a stmt. NB that the appropriate decl prefixes depends on the +-- flag settings (Trac #9915) declPrefixes :: DynFlags -> [String] declPrefixes dflags = keywords ++ concat opt_keywords where @@ -924,6 +925,9 @@ runStmt stmt step Just result -> afterRunStmt (const True) result s `looks_like` prefix = prefix `isPrefixOf` dropWhile isSpace s + -- Ignore leading spaces (see Trac #9914), so that + -- ghci> data T = T + -- (note leading spaces) works properly -- | Clean up the GHCi environment after a statement has run afterRunStmt :: (SrcSpan -> Bool) -> GHC.RunResult -> GHCi Bool From git at git.haskell.org Mon Dec 22 15:46:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 15:46:19 +0000 (UTC) Subject: [commit: ghc] branch 'ghc-7.10' created Message-ID: <20141222154619.5BC703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : ghc-7.10 Referencing: bb0603902568cd2442430ea9848d56f2498c854a From git at git.haskell.org Mon Dec 22 15:46:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 15:46:22 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Bump version to 7.10.0 (bb06039) Message-ID: <20141222154622.0FE1C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/bb0603902568cd2442430ea9848d56f2498c854a/ghc >--------------------------------------------------------------- commit bb0603902568cd2442430ea9848d56f2498c854a Author: Austin Seipp Date: Mon Dec 22 09:46:08 2014 -0600 Bump version to 7.10.0 Signed-off-by: Austin Seipp >--------------------------------------------------------------- bb0603902568cd2442430ea9848d56f2498c854a configure.ac | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index 97fdc2f..c98feb8 100644 --- a/configure.ac +++ b/configure.ac @@ -13,7 +13,7 @@ dnl # see what flags are available. (Better yet, read the documentation!) # -AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.9], [glasgow-haskell-bugs at haskell.org], [ghc]) +AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.10.0], [glasgow-haskell-bugs at haskell.org], [ghc]) # Set this to YES for a released version, otherwise NO : ${RELEASE=NO} From git at git.haskell.org Mon Dec 22 15:47:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 15:47:07 +0000 (UTC) Subject: [commit: ghc] master: Bump version to 7.11 (18bf6d5) Message-ID: <20141222154707.EE5B53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/18bf6d5de5c8eed68584921f46efca79d7d59d6a/ghc >--------------------------------------------------------------- commit 18bf6d5de5c8eed68584921f46efca79d7d59d6a Author: Austin Seipp Date: Mon Dec 22 09:48:13 2014 -0600 Bump version to 7.11 Signed-off-by: Austin Seipp >--------------------------------------------------------------- 18bf6d5de5c8eed68584921f46efca79d7d59d6a configure.ac | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index 97fdc2f..8fadf30 100644 --- a/configure.ac +++ b/configure.ac @@ -13,7 +13,7 @@ dnl # see what flags are available. (Better yet, read the documentation!) # -AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.9], [glasgow-haskell-bugs at haskell.org], [ghc]) +AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.11], [glasgow-haskell-bugs at haskell.org], [ghc]) # Set this to YES for a released version, otherwise NO : ${RELEASE=NO} From git at git.haskell.org Mon Dec 22 16:02:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 16:02:07 +0000 (UTC) Subject: [commit: ghc] master: Revert "Bump version to 7.11" (41e1cf1) Message-ID: <20141222160207.CC0FE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/41e1cf18f897f0f7446f03c8ba9c174cf3962de8/ghc >--------------------------------------------------------------- commit 41e1cf18f897f0f7446f03c8ba9c174cf3962de8 Author: Austin Seipp Date: Mon Dec 22 10:02:59 2014 -0600 Revert "Bump version to 7.11" This reverts commit 18bf6d5de5c8eed68584921f46efca79d7d59d6a. We forgot to tweak some of the submodule bounds. Fixes incoming soon. >--------------------------------------------------------------- 41e1cf18f897f0f7446f03c8ba9c174cf3962de8 configure.ac | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index 8fadf30..97fdc2f 100644 --- a/configure.ac +++ b/configure.ac @@ -13,7 +13,7 @@ dnl # see what flags are available. (Better yet, read the documentation!) # -AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.11], [glasgow-haskell-bugs at haskell.org], [ghc]) +AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.9], [glasgow-haskell-bugs at haskell.org], [ghc]) # Set this to YES for a released version, otherwise NO : ${RELEASE=NO} From git at git.haskell.org Mon Dec 22 16:36:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 16:36:09 +0000 (UTC) Subject: [commit: ghc] master: Fix typo in GLASGOW_HASKELL_PATCHLEVEL2 macro (3879bdf) Message-ID: <20141222163609.193223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3879bdf3afb00ff8569cba4648876652d1addadb/ghc >--------------------------------------------------------------- commit 3879bdf3afb00ff8569cba4648876652d1addadb Author: Herbert Valerio Riedel Date: Mon Dec 22 17:35:39 2014 +0100 Fix typo in GLASGOW_HASKELL_PATCHLEVEL2 macro This typo slipped in through 3549c952b535803270872adaf87262f2df0295a4 >--------------------------------------------------------------- 3879bdf3afb00ff8569cba4648876652d1addadb includes/ghc.mk | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/includes/ghc.mk b/includes/ghc.mk index f0bfbec..c7cec6c 100644 --- a/includes/ghc.mk +++ b/includes/ghc.mk @@ -68,7 +68,7 @@ $(includes_H_VERSION) : mk/project.mk | $$(dir $$@)/. echo "#define __GLASGOW_HASKELL_PATCHLEVEL1__ $(ProjectPatchLevel1)" >> $@; \ fi @if [ -n "$(ProjectPatchLevel2)" ]; then \ - echo "#define __GLASGOW_HASKELL_PATCHLEVEL1__ $(ProjectPatchLevel2)" >> $@; \ + echo "#define __GLASGOW_HASKELL_PATCHLEVEL2__ $(ProjectPatchLevel2)" >> $@; \ fi @echo >> $@ @echo '#define MIN_VERSION_GLASGOW_HASKELL(ma,mi,pl1,pl2) (\\' >> $@ From git at git.haskell.org Mon Dec 22 16:43:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 16:43:21 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix typo in GLASGOW_HASKELL_PATCHLEVEL2 macro (a8c556d) Message-ID: <20141222164321.222F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/a8c556dfca3eca5277615cc2bf9d6c8f1f143c9a/ghc >--------------------------------------------------------------- commit a8c556dfca3eca5277615cc2bf9d6c8f1f143c9a Author: Herbert Valerio Riedel Date: Mon Dec 22 17:35:39 2014 +0100 Fix typo in GLASGOW_HASKELL_PATCHLEVEL2 macro This typo slipped in through 3549c952b535803270872adaf87262f2df0295a4 (cherry picked from commit 3879bdf3afb00ff8569cba4648876652d1addadb) >--------------------------------------------------------------- a8c556dfca3eca5277615cc2bf9d6c8f1f143c9a includes/ghc.mk | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/includes/ghc.mk b/includes/ghc.mk index f0bfbec..c7cec6c 100644 --- a/includes/ghc.mk +++ b/includes/ghc.mk @@ -68,7 +68,7 @@ $(includes_H_VERSION) : mk/project.mk | $$(dir $$@)/. echo "#define __GLASGOW_HASKELL_PATCHLEVEL1__ $(ProjectPatchLevel1)" >> $@; \ fi @if [ -n "$(ProjectPatchLevel2)" ]; then \ - echo "#define __GLASGOW_HASKELL_PATCHLEVEL1__ $(ProjectPatchLevel2)" >> $@; \ + echo "#define __GLASGOW_HASKELL_PATCHLEVEL2__ $(ProjectPatchLevel2)" >> $@; \ fi @echo >> $@ @echo '#define MIN_VERSION_GLASGOW_HASKELL(ma,mi,pl1,pl2) (\\' >> $@ From git at git.haskell.org Mon Dec 22 17:11:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 17:11:53 +0000 (UTC) Subject: [commit: ghc] master: Bump GHC version from 7.9 to 7.11 (8a02c5e) Message-ID: <20141222171153.F07E43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8a02c5e65c73b4b10a10198190fa815213445b73/ghc >--------------------------------------------------------------- commit 8a02c5e65c73b4b10a10198190fa815213445b73 Author: Herbert Valerio Riedel Date: Mon Dec 22 17:21:49 2014 +0100 Bump GHC version from 7.9 to 7.11 This needs to update the Haddock submodule as well Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 8a02c5e65c73b4b10a10198190fa815213445b73 compiler/utils/ExtsCompat46.hs | 2 +- configure.ac | 2 +- utils/haddock | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/utils/ExtsCompat46.hs b/compiler/utils/ExtsCompat46.hs index a33fef5..14ffe72 100644 --- a/compiler/utils/ExtsCompat46.hs +++ b/compiler/utils/ExtsCompat46.hs @@ -90,7 +90,7 @@ import qualified GHC.Exts as E ( ) -- See #8330 -#if __GLASGOW_HASKELL__ > 710 +#if __GLASGOW_HASKELL__ > 711 #error What is minimal version of GHC required for bootstraping? If it's GHC 7.8 we should remove this module and use GHC.Exts instead. #endif diff --git a/configure.ac b/configure.ac index 97fdc2f..8fadf30 100644 --- a/configure.ac +++ b/configure.ac @@ -13,7 +13,7 @@ dnl # see what flags are available. (Better yet, read the documentation!) # -AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.9], [glasgow-haskell-bugs at haskell.org], [ghc]) +AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.11], [glasgow-haskell-bugs at haskell.org], [ghc]) # Set this to YES for a released version, otherwise NO : ${RELEASE=NO} diff --git a/utils/haddock b/utils/haddock index 7f23bd5..45acead 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 7f23bd526a6dd6ed0a2ddeeb30724606ea058ef5 +Subproject commit 45acead293f9fc18e984d2e83d137809359d506d From git at git.haskell.org Mon Dec 22 17:13:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 17:13:51 +0000 (UTC) Subject: [commit: ghc] tag 'ghc-7.11-start' created Message-ID: <20141222171351.1C0743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New tag : ghc-7.11-start Referencing: e5ffd7bb8a202c64e89b8378b87c23da550db9c3 From git at git.haskell.org Mon Dec 22 18:22:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 18:22:29 +0000 (UTC) Subject: [commit: ghc] master: Expand notes in TcFlatten (22bb78b) Message-ID: <20141222182229.EB8DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/22bb78bb02718e162130690dfb9a11d7b719cea1/ghc >--------------------------------------------------------------- commit 22bb78bb02718e162130690dfb9a11d7b719cea1 Author: Richard Eisenberg Date: Mon Dec 22 13:23:11 2014 -0500 Expand notes in TcFlatten >--------------------------------------------------------------- 22bb78bb02718e162130690dfb9a11d7b719cea1 compiler/typecheck/TcFlatten.hs | 24 ++++++++++++++++++++---- 1 file changed, 20 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcFlatten.hs b/compiler/typecheck/TcFlatten.hs index 2c72c93..2b11f99 100644 --- a/compiler/typecheck/TcFlatten.hs +++ b/compiler/typecheck/TcFlatten.hs @@ -983,10 +983,26 @@ also indicated that the early reduction should not use the flat-cache, but that the later reduction should. It's possible that with more examples, we might learn that these knobs should be set differently. -Once we've got a flat rhs, we extend the flatten-cache to record the -result. Doing so can save lots of work when the same redex shows up -more than once. Note that we record the link from the redex all the -way to its *final* value, not just the single step reduction. +An example of where the early reduction appears helpful: + + type family Last x where + Last '[x] = x + Last (h ': t) = Last t + + workitem: (x ~ Last '[1,2,3,4,5,6]) + +Flattening the argument never gets us anywhere, but trying to flatten +it at every step is quadratic in the length of the list. Reducing more +eagerly makes simplifying the right-hand type linear in its length. + +At the end, once we've got a flat rhs, we extend the flatten-cache to record +the result. Doing so can save lots of work when the same redex shows up more +than once. Note that we record the link from the redex all the way to its +*final* value, not just the single step reduction. Interestingly, using the +flat-cache for the first reduction resulted in an increase in allocations +of about 3% for the four T9872x tests. However, using the flat-cache in +the later reduction is a similar gain. I (Richard E) don't currently (Dec '14) +have any knowledge as to *why* these facts are true. ************************************************************************ * * From git at git.haskell.org Mon Dec 22 21:16:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 21:16:20 +0000 (UTC) Subject: [commit: ghc] master: Groom comments related to StaticPointers. (c72f61c) Message-ID: <20141222211620.B3A7C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c72f61c6d4dd779d61bd0ebc0b1211a84c5b9038/ghc >--------------------------------------------------------------- commit c72f61c6d4dd779d61bd0ebc0b1211a84c5b9038 Author: Facundo Dom?nguez Date: Mon Dec 22 19:15:36 2014 -0200 Groom comments related to StaticPointers. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D575 >--------------------------------------------------------------- c72f61c6d4dd779d61bd0ebc0b1211a84c5b9038 compiler/deSugar/StaticPtrTable.hs | 5 ++--- compiler/rename/RnExpr.hs | 2 +- docs/users_guide/glasgow_exts.xml | 6 ++---- includes/rts/StaticPtrTable.h | 3 +-- rts/Hash.c | 2 +- rts/Hash.h | 2 +- testsuite/tests/rts/GcStaticPointers.hs | 12 ++++++------ testsuite/tests/th/TH_StaticPointers02.hs | 4 +--- testsuite/tests/th/TH_StaticPointers02.stderr | 2 +- 9 files changed, 16 insertions(+), 22 deletions(-) diff --git a/compiler/deSugar/StaticPtrTable.hs b/compiler/deSugar/StaticPtrTable.hs index d4cad0e..858a0e8 100644 --- a/compiler/deSugar/StaticPtrTable.hs +++ b/compiler/deSugar/StaticPtrTable.hs @@ -24,8 +24,7 @@ -- > -- > } -- --- where constants are values of a fingerprint of the string --- ":.sptEntry:" +-- where the constants are fingerprints produced from the static forms. -- module StaticPtrTable (sptInitCode) where @@ -38,7 +37,7 @@ import GHC.Fingerprint -- | @sptInitCode module statics@ is a C stub to insert the static entries --- @statics@ of @module@ into the static pointer table +-- @statics@ of @module@ into the static pointer table. -- -- Each entry contains the fingerprint used to locate the entry and the -- top-level binding for the entry. diff --git a/compiler/rename/RnExpr.hs b/compiler/rename/RnExpr.hs index 4755547..cf5457e 100644 --- a/compiler/rename/RnExpr.hs +++ b/compiler/rename/RnExpr.hs @@ -313,7 +313,7 @@ rnExpr e@(ELazyPat {}) = patSynErr e For the static form we check that the free variables are all top-level value bindings. This is done by checking that the name is external or -wired-in. See the Note about the NameSorts in Name.lhs. +wired-in. See the Notes about the NameSorts in Name.hs. -} rnExpr e@(HsStatic expr) = do diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 86ceb06..83576ef 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -10470,9 +10470,6 @@ While the following definitions are rejected: ref6 = let x = 1 in static x ref7 y = static (let x = 1 in y) -Note that currently, the body e in static -e is restricted to a single identifier when at the GHCi -prompt. @@ -10502,13 +10499,14 @@ That being said, with the appropriate use of wrapper datatypes, the above limitations induce no loss of generality: {-# LANGUAGE ConstraintKinds #-} -{-# LANGUAGE DerivingDataTypeable #-} +{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE StaticPointers #-} import Control.Monad.ST +import Data.Typeable import GHC.StaticPtr data Dict c = c => Dict diff --git a/includes/rts/StaticPtrTable.h b/includes/rts/StaticPtrTable.h index 8b56510..87a905c 100644 --- a/includes/rts/StaticPtrTable.h +++ b/includes/rts/StaticPtrTable.h @@ -17,8 +17,7 @@ /** Inserts an entry in the Static Pointer Table. * * The key is a fingerprint computed from the StaticName of a static pointer - * and the spe_closure is a pointer to the closure defining the table entry - * (GHC.SptEntry). + * and the spe_closure is a pointer to the closure defining the table entry. * * A stable pointer to the closure is made to prevent it from being garbage * collected while the entry exists on the table. diff --git a/rts/Hash.c b/rts/Hash.c index 1881092..422c3d9 100644 --- a/rts/Hash.c +++ b/rts/Hash.c @@ -206,7 +206,7 @@ lookupHashTable(HashTable *table, StgWord key) return NULL; } -// Puts up to keys_sz keys of the hash table into the given array. Returns the +// Puts up to szKeys keys of the hash table into the given array. Returns the // actual amount of keys that have been retrieved. // // If the table is modified concurrently, the function behavior is undefined. diff --git a/rts/Hash.h b/rts/Hash.h index e802644..136f94a 100644 --- a/rts/Hash.h +++ b/rts/Hash.h @@ -21,7 +21,7 @@ void * removeHashTable ( HashTable *table, StgWord key, void *data ); int keyCountHashTable (HashTable *table); -// Puts up to keys_sz keys of the hash table into the given array. Returns the +// Puts up to szKeys keys of the hash table into the given array. Returns the // actual amount of keys that have been retrieved. // // If the table is modified concurrently, the function behavior is undefined. diff --git a/testsuite/tests/rts/GcStaticPointers.hs b/testsuite/tests/rts/GcStaticPointers.hs index 7c2fc2b..c498af5 100644 --- a/testsuite/tests/rts/GcStaticPointers.hs +++ b/testsuite/tests/rts/GcStaticPointers.hs @@ -14,9 +14,9 @@ import Unsafe.Coerce (unsafeCoerce) nats :: [Integer] nats = [0 .. ] --- Just a StaticPtr to some CAF so that we can deRef it. -nats_fp :: StaticKey -nats_fp = staticKey (static nats :: StaticPtr [Integer]) +-- The key of a 'StaticPtr' to some CAF. +nats_key :: StaticKey +nats_key = staticKey (static nats :: StaticPtr [Integer]) main = do let z = nats !! 400 @@ -26,8 +26,8 @@ main = do print z performGC threadDelay 1000000 - let Just p = unsafeLookupStaticPtr nats_fp + let Just p = unsafeLookupStaticPtr nats_key print (deRefStaticPtr (unsafeCoerce p) !! 800 :: Integer) - -- Uncommenting the next line keeps primes alive and would prevent a segfault - -- if nats were garbage collected. + -- Uncommenting the next line keeps 'nats' alive and would prevent a segfault + -- if 'nats' were garbage collected. -- print (nats !! 900) diff --git a/testsuite/tests/th/TH_StaticPointers02.hs b/testsuite/tests/th/TH_StaticPointers02.hs index 1f619a7..b381050 100644 --- a/testsuite/tests/th/TH_StaticPointers02.hs +++ b/testsuite/tests/th/TH_StaticPointers02.hs @@ -1,9 +1,7 @@ {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE StaticPointers #-} --- | A test to try the static form in splices. --- --- A static form is defined in a splice and then it is used in the program. +-- | A test to try the static form in splices, which should fail. -- module Main(main) where diff --git a/testsuite/tests/th/TH_StaticPointers02.stderr b/testsuite/tests/th/TH_StaticPointers02.stderr index cc6fa82..88da9d1 100644 --- a/testsuite/tests/th/TH_StaticPointers02.stderr +++ b/testsuite/tests/th/TH_StaticPointers02.stderr @@ -1,5 +1,5 @@ -TH_StaticPointers02.hs:13:34: +TH_StaticPointers02.hs:11:34: static forms cannot be used in splices: static 'a' In the splice: $(case staticKey (static 'a') of { From git at git.haskell.org Mon Dec 22 21:20:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Dec 2014 21:20:11 +0000 (UTC) Subject: [commit: ghc] master: fix spInfoSrcLoc field name (1da2c0f) Message-ID: <20141222212011.A5DAE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1da2c0fcd1f9f00e25bed8a8abcc81e3f5b1de04/ghc >--------------------------------------------------------------- commit 1da2c0fcd1f9f00e25bed8a8abcc81e3f5b1de04 Author: Facundo Dom?nguez Date: Mon Dec 22 19:20:11 2014 -0200 fix spInfoSrcLoc field name Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D574 >--------------------------------------------------------------- 1da2c0fcd1f9f00e25bed8a8abcc81e3f5b1de04 libraries/base/GHC/StaticPtr.hs | 4 ++-- testsuite/tests/deSugar/should_run/DsStaticPointers.stdout | 10 +++++----- 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/libraries/base/GHC/StaticPtr.hs b/libraries/base/GHC/StaticPtr.hs index b92b843..b58564e 100644 --- a/libraries/base/GHC/StaticPtr.hs +++ b/libraries/base/GHC/StaticPtr.hs @@ -24,7 +24,7 @@ -- -- To solve such concern, the references provided by this module offer a key -- that can be used to locate the values on each process. Each process maintains --- a global and inmutable table of references which can be looked up with a +-- a global and immutable table of references which can be looked up with a -- given key. This table is known as the Static Pointer Table. The reference can -- then be dereferenced to obtain the value. -- @@ -88,7 +88,7 @@ data StaticPtrInfo = StaticPtrInfo , spInfoName :: String -- | Source location of the definition of the static pointer as a -- @(Line, Column)@ pair. - , spIntoSrcLoc :: (Int, Int) + , spInfoSrcLoc :: (Int, Int) } deriving (Show, Typeable) diff --git a/testsuite/tests/deSugar/should_run/DsStaticPointers.stdout b/testsuite/tests/deSugar/should_run/DsStaticPointers.stdout index 55ec658..b9d683e 100644 --- a/testsuite/tests/deSugar/should_run/DsStaticPointers.stdout +++ b/testsuite/tests/deSugar/should_run/DsStaticPointers.stdout @@ -1,5 +1,5 @@ -StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:1", spIntoSrcLoc = (10,32)} -StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:2", spIntoSrcLoc = (11,33)} -StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:0", spIntoSrcLoc = (21,13)} -StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:3", spIntoSrcLoc = (13,33)} -StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:4", spIntoSrcLoc = (14,33)} +StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:1", spInfoSrcLoc = (10,32)} +StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:2", spInfoSrcLoc = (11,33)} +StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:0", spInfoSrcLoc = (21,13)} +StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:3", spInfoSrcLoc = (13,33)} +StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:4", spInfoSrcLoc = (14,33)} From git at git.haskell.org Tue Dec 23 12:24:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 12:24:25 +0000 (UTC) Subject: [commit: ghc] wip/T9900: Support pattern synonyms in GHCi (fixes #9900) (e6558f2) Message-ID: <20141223122425.C58BE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9900 Link : http://ghc.haskell.org/trac/ghc/changeset/e6558f2ddb003e241be8ceebfdbdf395d2a4922a/ghc >--------------------------------------------------------------- commit e6558f2ddb003e241be8ceebfdbdf395d2a4922a Author: Dr. ERDI Gergo Date: Sun Dec 21 15:01:15 2014 +0800 Support pattern synonyms in GHCi (fixes #9900) This involves recognizing lines starting with `"pattern "` as declarations, keeping non-exported pattern synonyms in `deSugar`, and including pattern synonyms in the result of `hscDeclsWithLocation`. >--------------------------------------------------------------- e6558f2ddb003e241be8ceebfdbdf395d2a4922a compiler/deSugar/Desugar.hs | 2 +- compiler/main/HscMain.hs | 6 ++++-- compiler/main/HscTypes.hs | 5 +++-- ghc/InteractiveUI.hs | 1 + testsuite/tests/patsyn/should_run/all.T | 5 +++++ testsuite/tests/patsyn/should_run/ghci.script | 8 ++++++++ testsuite/tests/patsyn/should_run/ghci.stderr | 2 ++ testsuite/tests/patsyn/should_run/ghci.stdout | 3 +++ 8 files changed, 27 insertions(+), 5 deletions(-) diff --git a/compiler/deSugar/Desugar.hs b/compiler/deSugar/Desugar.hs index ac35464..4695543 100644 --- a/compiler/deSugar/Desugar.hs +++ b/compiler/deSugar/Desugar.hs @@ -184,7 +184,7 @@ deSugar hsc_env mg_fam_insts = fam_insts, mg_inst_env = inst_env, mg_fam_inst_env = fam_inst_env, - mg_patsyns = filter ((`elemNameSet` export_set) . patSynName) patsyns, + mg_patsyns = patsyns, mg_rules = ds_rules_for_imps, mg_binds = ds_binds, mg_foreign = ds_fords, diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index c5cb9a1..5af28cb 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -128,6 +128,7 @@ import CostCentre import ProfInit import TyCon import Name +import ConLike import SimplStg ( stg2stg ) import Cmm import CmmParse ( parseCmmFile ) @@ -1505,6 +1506,7 @@ hscDeclsWithLocation hsc_env0 str source linenumber = liftIO $ linkDecls hsc_env src_span cbc let tcs = filterOut isImplicitTyCon (mg_tcs simpl_mg) + patsyns = mg_patsyns simpl_mg ext_ids = [ id | id <- bindersOfBinds core_binds , isExternalName (idName id) @@ -1515,11 +1517,11 @@ hscDeclsWithLocation hsc_env0 str source linenumber = -- The DFunIds are in 'cls_insts' (see Note [ic_tythings] in HscTypes -- Implicit Ids are implicit in tcs - tythings = map AnId ext_ids ++ map ATyCon tcs + tythings = map AnId ext_ids ++ map ATyCon tcs ++ map (AConLike . PatSynCon) patsyns let icontext = hsc_IC hsc_env ictxt = extendInteractiveContext icontext ext_ids tcs - cls_insts fam_insts defaults + cls_insts fam_insts defaults patsyns return (tythings, ictxt) hscImport :: HscEnv -> String -> IO (ImportDecl RdrName) diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs index 909004e..29ee78c 100644 --- a/compiler/main/HscTypes.hs +++ b/compiler/main/HscTypes.hs @@ -1403,8 +1403,9 @@ extendInteractiveContext :: InteractiveContext -> [Id] -> [TyCon] -> [ClsInst] -> [FamInst] -> Maybe [Type] + -> [PatSyn] -> InteractiveContext -extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults +extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults new_patsyns = ictxt { ic_mod_index = ic_mod_index ictxt + 1 -- Always bump this; even instances should create -- a new mod_index (Trac #9426) @@ -1413,7 +1414,7 @@ extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults , ic_instances = (new_cls_insts ++ old_cls_insts, new_fam_insts ++ old_fam_insts) , ic_default = defaults } where - new_tythings = map AnId ids ++ map ATyCon tcs + new_tythings = map AnId ids ++ map ATyCon tcs ++ map (AConLike . PatSynCon) new_patsyns old_tythings = filterOut (shadowed_by ids) (ic_tythings ictxt) -- Discard old instances that have been fully overrridden diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index d478336..b7c50f5 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -888,6 +888,7 @@ declPrefixes dflags = keywords ++ concat opt_keywords opt_keywords = [ ["foreign " | xopt Opt_ForeignFunctionInterface dflags] , ["deriving " | xopt Opt_StandaloneDeriving dflags] + , ["pattern " | xopt Opt_PatternSynonyms dflags] ] -- | Entry point to execute some haskell code from user diff --git a/testsuite/tests/patsyn/should_run/all.T b/testsuite/tests/patsyn/should_run/all.T index 40ec3e3..2f496a6 100644 --- a/testsuite/tests/patsyn/should_run/all.T +++ b/testsuite/tests/patsyn/should_run/all.T @@ -1,3 +1,7 @@ +# We only want to run these tests with GHCi +def just_ghci( name, opts ): + opts.only_ways = ['ghci'] + test('eval', normal, compile_and_run, ['']) test('match', normal, compile_and_run, ['']) test('ex-prov-run', normal, compile_and_run, ['']) @@ -6,3 +10,4 @@ test('bidir-explicit-scope', normal, compile_and_run, ['']) test('T9783', normal, compile_and_run, ['']) test('match-unboxed', normal, compile_and_run, ['']) test('unboxed-wrapper', normal, compile_and_run, ['']) +test('ghci', just_ghci, ghci_script, ['ghci.script']) diff --git a/testsuite/tests/patsyn/should_run/ghci.script b/testsuite/tests/patsyn/should_run/ghci.script new file mode 100644 index 0000000..cd71e33 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/ghci.script @@ -0,0 +1,8 @@ +:set -XPatternSynonyms + +pattern Single x = [x] +:i Single +let foo (Single x) = Single (not x) +:t foo +foo [True] +foo [True, False] diff --git a/testsuite/tests/patsyn/should_run/ghci.stderr b/testsuite/tests/patsyn/should_run/ghci.stderr new file mode 100644 index 0000000..9593b15 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/ghci.stderr @@ -0,0 +1,2 @@ +*** Exception: :6:5-35: Non-exhaustive patterns in function foo + diff --git a/testsuite/tests/patsyn/should_run/ghci.stdout b/testsuite/tests/patsyn/should_run/ghci.stdout new file mode 100644 index 0000000..796aa72 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/ghci.stdout @@ -0,0 +1,3 @@ +pattern Single :: t -> [t] -- Defined at :4:9 +foo :: [Bool] -> [Bool] +[False] From git at git.haskell.org Tue Dec 23 12:24:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 12:24:28 +0000 (UTC) Subject: [commit: ghc] wip/T9900's head updated: Support pattern synonyms in GHCi (fixes #9900) (e6558f2) Message-ID: <20141223122428.0E0073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T9900' now includes: 4f80084 Update pretty and random submodules 2ba36b6 Update containers submodule to 0.5.6.2 release cf0a55d For :info, return all matching Names, rather than complaining about ambiguity eb4d96e Comments only bb06039 Bump version to 7.10.0 a8c556d Fix typo in GLASGOW_HASKELL_PATCHLEVEL2 macro e6558f2 Support pattern synonyms in GHCi (fixes #9900) From git at git.haskell.org Tue Dec 23 12:26:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 12:26:04 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: fix spInfoSrcLoc field name (f10b79d) Message-ID: <20141223122604.A76103A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/f10b79dc0f68c8983af18892b7107692bc5917fb/ghc >--------------------------------------------------------------- commit f10b79dc0f68c8983af18892b7107692bc5917fb Author: Facundo Dom?nguez Date: Mon Dec 22 19:20:11 2014 -0200 fix spInfoSrcLoc field name (cherry picked from commit 1da2c0fcd1f9f00e25bed8a8abcc81e3f5b1de04) >--------------------------------------------------------------- f10b79dc0f68c8983af18892b7107692bc5917fb libraries/base/GHC/StaticPtr.hs | 4 ++-- testsuite/tests/deSugar/should_run/DsStaticPointers.stdout | 10 +++++----- 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/libraries/base/GHC/StaticPtr.hs b/libraries/base/GHC/StaticPtr.hs index b92b843..b58564e 100644 --- a/libraries/base/GHC/StaticPtr.hs +++ b/libraries/base/GHC/StaticPtr.hs @@ -24,7 +24,7 @@ -- -- To solve such concern, the references provided by this module offer a key -- that can be used to locate the values on each process. Each process maintains --- a global and inmutable table of references which can be looked up with a +-- a global and immutable table of references which can be looked up with a -- given key. This table is known as the Static Pointer Table. The reference can -- then be dereferenced to obtain the value. -- @@ -88,7 +88,7 @@ data StaticPtrInfo = StaticPtrInfo , spInfoName :: String -- | Source location of the definition of the static pointer as a -- @(Line, Column)@ pair. - , spIntoSrcLoc :: (Int, Int) + , spInfoSrcLoc :: (Int, Int) } deriving (Show, Typeable) diff --git a/testsuite/tests/deSugar/should_run/DsStaticPointers.stdout b/testsuite/tests/deSugar/should_run/DsStaticPointers.stdout index 55ec658..b9d683e 100644 --- a/testsuite/tests/deSugar/should_run/DsStaticPointers.stdout +++ b/testsuite/tests/deSugar/should_run/DsStaticPointers.stdout @@ -1,5 +1,5 @@ -StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:1", spIntoSrcLoc = (10,32)} -StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:2", spIntoSrcLoc = (11,33)} -StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:0", spIntoSrcLoc = (21,13)} -StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:3", spIntoSrcLoc = (13,33)} -StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:4", spIntoSrcLoc = (14,33)} +StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:1", spInfoSrcLoc = (10,32)} +StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:2", spInfoSrcLoc = (11,33)} +StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:0", spInfoSrcLoc = (21,13)} +StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:3", spInfoSrcLoc = (13,33)} +StaticPtrInfo {spInfoPackageId = "main", spInfoModuleName = "Main", spInfoName = "sptEntry:4", spInfoSrcLoc = (14,33)} From git at git.haskell.org Tue Dec 23 14:46:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 14:46:12 +0000 (UTC) Subject: [commit: ghc] master: docs: create 7.12.1 relnotes (e435a09) Message-ID: <20141223144612.AAFAA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e435a09419023debc9dff6711bfac16882a60766/ghc >--------------------------------------------------------------- commit e435a09419023debc9dff6711bfac16882a60766 Author: Austin Seipp Date: Tue Dec 23 08:46:59 2014 -0600 docs: create 7.12.1 relnotes Signed-off-by: Austin Seipp >--------------------------------------------------------------- e435a09419023debc9dff6711bfac16882a60766 docs/users_guide/7.10.1-notes.xml | 682 -------------------------------------- docs/users_guide/7.12.1-notes.xml | 385 +++++++++++++++++++++ docs/users_guide/ug-ent.xml.in | 2 +- 3 files changed, 386 insertions(+), 683 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e435a09419023debc9dff6711bfac16882a60766 From git at git.haskell.org Tue Dec 23 14:47:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 14:47:42 +0000 (UTC) Subject: [commit: ghc] master: Fix panic on :kind _ in GHCi (Trac #9879) (6eb86a5) Message-ID: <20141223144742.1043A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6eb86a56135a9274d2c958a2ccf4df510c9dab86/ghc >--------------------------------------------------------------- commit 6eb86a56135a9274d2c958a2ccf4df510c9dab86 Author: Thomas Winant Date: Tue Dec 23 08:48:15 2014 -0600 Fix panic on :kind _ in GHCi (Trac #9879) Summary: Running `:kind _` in GHCi produced a panic, fix it by extracting the wildcards. Now, `:kind _` produces `_ :: k0`. Unfortunately, a `0` is added after the kind is tidied and I haven't found a way to get rid of it... This does not fix the other panic involving TemplateHaskell mentioned in #9879. Test Plan: new test GHCiWildcardKind should pass Reviewers: austin, simonpj Reviewed By: austin Subscribers: simonpj, carter, thomie, monoidal Differential Revision: https://phabricator.haskell.org/D572 GHC Trac Issues: #9879 >--------------------------------------------------------------- 6eb86a56135a9274d2c958a2ccf4df510c9dab86 compiler/typecheck/TcRnDriver.hs | 8 ++++++-- testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.script | 3 +++ testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.stdout | 2 ++ .../should_compile => partial-sigs/should_run}/Makefile | 0 testsuite/tests/partial-sigs/should_run/all.T | 1 + 5 files changed, 12 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index b464400..f640039 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -1792,12 +1792,16 @@ tcRnType :: HscEnv tcRnType hsc_env normalise rdr_type = runTcInteractive hsc_env $ setXOptM Opt_PolyKinds $ -- See Note [Kind-generalise in tcRnType] - do { (rn_type, _fvs) <- rnLHsType GHCiCtx rdr_type + do { (wcs, rdr_type') <- extractWildcards rdr_type + ; (rn_type, wcs) <- bindLocatedLocalsRn wcs $ \wcs_new -> do { + ; (rn_type, _fvs) <- rnLHsType GHCiCtx rdr_type' ; failIfErrsM + ; return (rn_type, wcs_new) } -- Now kind-check the type -- It can have any rank or kind - ; ty <- tcHsSigType GhciCtxt rn_type ; + ; nwc_tvs <- mapM newWildcardVarMetaKind wcs + ; ty <- tcExtendTyVarEnv nwc_tvs $ tcHsSigType GhciCtxt rn_type ; ty' <- if normalise then do { fam_envs <- tcGetFamInstEnvs diff --git a/testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.script b/testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.script new file mode 100644 index 0000000..a3f9b35 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.script @@ -0,0 +1,3 @@ +:kind _ +:kind Maybe _ + diff --git a/testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.stdout b/testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.stdout new file mode 100644 index 0000000..e1b2bd3 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.stdout @@ -0,0 +1,2 @@ +_ :: k0 +Maybe _ :: * diff --git a/testsuite/tests/annotations/should_compile/Makefile b/testsuite/tests/partial-sigs/should_run/Makefile similarity index 100% copy from testsuite/tests/annotations/should_compile/Makefile copy to testsuite/tests/partial-sigs/should_run/Makefile diff --git a/testsuite/tests/partial-sigs/should_run/all.T b/testsuite/tests/partial-sigs/should_run/all.T new file mode 100644 index 0000000..0ca1b61 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_run/all.T @@ -0,0 +1 @@ +test('GHCiWildcardKind', normal, ghci_script, ['GHCiWildcardKind.script']) From git at git.haskell.org Tue Dec 23 14:47:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 14:47:44 +0000 (UTC) Subject: [commit: ghc] master: Rename NamedWildcards flag to NamedWildCards (089222c) Message-ID: <20141223144744.C3DC43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/089222c9d6798c79179264e5c77c31d5c460a880/ghc >--------------------------------------------------------------- commit 089222c9d6798c79179264e5c77c31d5c460a880 Author: Thomas Winant Date: Tue Dec 23 08:48:29 2014 -0600 Rename NamedWildcards flag to NamedWildCards Summary: Mind the capital C. As there is already a flag RecordWildCards with a capital C, we should at least try to be consistent in the spelling of WildCards. Test Plan: validate Reviewers: goldfire, simonpj, austin Reviewed By: simonpj, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D584 >--------------------------------------------------------------- 089222c9d6798c79179264e5c77c31d5c460a880 compiler/main/DynFlags.hs | 4 ++-- compiler/parser/Parser.y | 2 +- docs/users_guide/flags.xml | 4 ++-- docs/users_guide/glasgow_exts.xml | 6 +++--- testsuite/tests/driver/T4437.hs | 2 +- testsuite/tests/partial-sigs/should_compile/Either.hs | 2 +- testsuite/tests/partial-sigs/should_compile/EveryNamed.hs | 2 +- testsuite/tests/partial-sigs/should_compile/ExpressionSigNamed.hs | 2 +- testsuite/tests/partial-sigs/should_compile/GenNamed.hs | 2 +- testsuite/tests/partial-sigs/should_compile/Meltdown.hs | 2 +- testsuite/tests/partial-sigs/should_compile/NamedTyVar.hs | 2 +- testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcards.hs | 2 +- .../tests/partial-sigs/should_compile/ScopedNamedWildcardsGood.hs | 2 +- testsuite/tests/partial-sigs/should_compile/ShowNamed.hs | 2 +- testsuite/tests/partial-sigs/should_compile/SomethingShowable.hs | 2 +- testsuite/tests/partial-sigs/should_compile/UncurryNamed.hs | 2 +- .../partial-sigs/should_compile/WarningWildcardInstantiations.hs | 2 +- .../should_fail/InstantiatedNamedWildcardsInConstraints.hs | 2 +- .../tests/partial-sigs/should_fail/NamedExtraConstraintsWildcard.hs | 2 +- testsuite/tests/partial-sigs/should_fail/NamedWildcardsEnabled.hs | 2 +- .../tests/partial-sigs/should_fail/NamedWildcardsNotInMonotype.hs | 2 +- .../partial-sigs/should_fail/NestedNamedExtraConstraintsWildcard.hs | 2 +- testsuite/tests/partial-sigs/should_fail/ScopedNamedWildcardsBad.hs | 2 +- testsuite/tests/partial-sigs/should_fail/TidyClash2.hs | 2 +- testsuite/tests/partial-sigs/should_fail/WildcardInADTContext2.hs | 2 +- testsuite/tests/partial-sigs/should_fail/WildcardInstantiations.hs | 2 +- .../tests/partial-sigs/should_fail/WildcardsInPatternAndExprSig.hs | 2 +- 27 files changed, 31 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 089222c9d6798c79179264e5c77c31d5c460a880 From git at git.haskell.org Tue Dec 23 14:54:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 14:54:02 +0000 (UTC) Subject: [commit: ghc] master: dwarf: sync getIdFromTrivialExpr with exprIsTrivial (test break028 and others) (30fdf86) Message-ID: <20141223145402.14B153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/30fdf86eec34711be07c6771b02a6fc81ac99ee2/ghc >--------------------------------------------------------------- commit 30fdf86eec34711be07c6771b02a6fc81ac99ee2 Author: Sergei Trofimovich Date: Tue Dec 23 08:55:06 2014 -0600 dwarf: sync getIdFromTrivialExpr with exprIsTrivial (test break028 and others) Summary: The bug manifests when built with EXTRA_HC_OPTS += -g +++ ./ghci.debugger/scripts/break028.run.stderr 2014-12-19 23:08:46.199876621 +0000 @@ -0,0 +1,11 @@ +ghc-stage2: panic! (the 'impossible' happened) + (GHC version 7.9.20141219 for x86_64-unknown-linux): + getIdFromTrivialExpr x_alJ + +Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug + + +:3:1: Not in scope: ?g? + +:3:3: Not in scope: data constructor ?False? Signed-off-by: Sergei Trofimovich Reviewers: simonmar, austin, scpmw Reviewed By: scpmw Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D580 >--------------------------------------------------------------- 30fdf86eec34711be07c6771b02a6fc81ac99ee2 compiler/coreSyn/CoreUtils.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index c520029..913dda3 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -663,6 +663,7 @@ getIdFromTrivialExpr :: CoreExpr -> Id getIdFromTrivialExpr e = go e where go (Var v) = v go (App f t) | not (isRuntimeArg t) = go f + go (Tick t e) | not (tickishIsCode t) = go e go (Cast e _) = go e go (Lam b e) | not (isRuntimeVar b) = go e go e = pprPanic "getIdFromTrivialExpr" (ppr e) From git at git.haskell.org Tue Dec 23 14:56:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 14:56:10 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: dwarf: sync getIdFromTrivialExpr with exprIsTrivial (test break028 and others) (a79cfe5) Message-ID: <20141223145610.1528B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/a79cfe5124bede0ab6f59f3004584f9cdf96da32/ghc >--------------------------------------------------------------- commit a79cfe5124bede0ab6f59f3004584f9cdf96da32 Author: Sergei Trofimovich Date: Tue Dec 23 08:55:06 2014 -0600 dwarf: sync getIdFromTrivialExpr with exprIsTrivial (test break028 and others) Summary: The bug manifests when built with EXTRA_HC_OPTS += -g +++ ./ghci.debugger/scripts/break028.run.stderr 2014-12-19 23:08:46.199876621 +0000 @@ -0,0 +1,11 @@ +ghc-stage2: panic! (the 'impossible' happened) + (GHC version 7.9.20141219 for x86_64-unknown-linux): + getIdFromTrivialExpr x_alJ + +Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug + + +:3:1: Not in scope: ?g? + +:3:3: Not in scope: data constructor ?False? Signed-off-by: Sergei Trofimovich Reviewers: simonmar, austin, scpmw Reviewed By: scpmw Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D580 (cherry picked from commit 30fdf86eec34711be07c6771b02a6fc81ac99ee2) >--------------------------------------------------------------- a79cfe5124bede0ab6f59f3004584f9cdf96da32 compiler/coreSyn/CoreUtils.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index c520029..913dda3 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -663,6 +663,7 @@ getIdFromTrivialExpr :: CoreExpr -> Id getIdFromTrivialExpr e = go e where go (Var v) = v go (App f t) | not (isRuntimeArg t) = go f + go (Tick t e) | not (tickishIsCode t) = go e go (Cast e _) = go e go (Lam b e) | not (isRuntimeVar b) = go e go e = pprPanic "getIdFromTrivialExpr" (ppr e) From git at git.haskell.org Tue Dec 23 14:56:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 14:56:12 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Rename NamedWildcards flag to NamedWildCards (f748ccd) Message-ID: <20141223145612.C1AEB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/f748ccd3f8be3e62f7d1c2aebee9b8e66ce52088/ghc >--------------------------------------------------------------- commit f748ccd3f8be3e62f7d1c2aebee9b8e66ce52088 Author: Thomas Winant Date: Tue Dec 23 08:48:29 2014 -0600 Rename NamedWildcards flag to NamedWildCards Summary: Mind the capital C. As there is already a flag RecordWildCards with a capital C, we should at least try to be consistent in the spelling of WildCards. Test Plan: validate Reviewers: goldfire, simonpj, austin Reviewed By: simonpj, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D584 (cherry picked from commit 089222c9d6798c79179264e5c77c31d5c460a880) >--------------------------------------------------------------- f748ccd3f8be3e62f7d1c2aebee9b8e66ce52088 compiler/main/DynFlags.hs | 4 ++-- compiler/parser/Parser.y | 2 +- docs/users_guide/flags.xml | 4 ++-- docs/users_guide/glasgow_exts.xml | 6 +++--- testsuite/tests/driver/T4437.hs | 2 +- testsuite/tests/partial-sigs/should_compile/Either.hs | 2 +- testsuite/tests/partial-sigs/should_compile/EveryNamed.hs | 2 +- testsuite/tests/partial-sigs/should_compile/ExpressionSigNamed.hs | 2 +- testsuite/tests/partial-sigs/should_compile/GenNamed.hs | 2 +- testsuite/tests/partial-sigs/should_compile/Meltdown.hs | 2 +- testsuite/tests/partial-sigs/should_compile/NamedTyVar.hs | 2 +- testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcards.hs | 2 +- .../tests/partial-sigs/should_compile/ScopedNamedWildcardsGood.hs | 2 +- testsuite/tests/partial-sigs/should_compile/ShowNamed.hs | 2 +- testsuite/tests/partial-sigs/should_compile/SomethingShowable.hs | 2 +- testsuite/tests/partial-sigs/should_compile/UncurryNamed.hs | 2 +- .../partial-sigs/should_compile/WarningWildcardInstantiations.hs | 2 +- .../should_fail/InstantiatedNamedWildcardsInConstraints.hs | 2 +- .../tests/partial-sigs/should_fail/NamedExtraConstraintsWildcard.hs | 2 +- testsuite/tests/partial-sigs/should_fail/NamedWildcardsEnabled.hs | 2 +- .../tests/partial-sigs/should_fail/NamedWildcardsNotInMonotype.hs | 2 +- .../partial-sigs/should_fail/NestedNamedExtraConstraintsWildcard.hs | 2 +- testsuite/tests/partial-sigs/should_fail/ScopedNamedWildcardsBad.hs | 2 +- testsuite/tests/partial-sigs/should_fail/TidyClash2.hs | 2 +- testsuite/tests/partial-sigs/should_fail/WildcardInADTContext2.hs | 2 +- testsuite/tests/partial-sigs/should_fail/WildcardInstantiations.hs | 2 +- .../tests/partial-sigs/should_fail/WildcardsInPatternAndExprSig.hs | 2 +- 27 files changed, 31 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 f748ccd3f8be3e62f7d1c2aebee9b8e66ce52088 From git at git.haskell.org Tue Dec 23 14:56:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 14:56:15 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix panic on :kind _ in GHCi (Trac #9879) (c52565e) Message-ID: <20141223145615.BE2AC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/c52565e20ba6ff21e9c1b222cede9b1eb640491a/ghc >--------------------------------------------------------------- commit c52565e20ba6ff21e9c1b222cede9b1eb640491a Author: Thomas Winant Date: Tue Dec 23 08:48:15 2014 -0600 Fix panic on :kind _ in GHCi (Trac #9879) Summary: Running `:kind _` in GHCi produced a panic, fix it by extracting the wildcards. Now, `:kind _` produces `_ :: k0`. Unfortunately, a `0` is added after the kind is tidied and I haven't found a way to get rid of it... This does not fix the other panic involving TemplateHaskell mentioned in #9879. Test Plan: new test GHCiWildcardKind should pass Reviewers: austin, simonpj Reviewed By: austin Subscribers: simonpj, carter, thomie, monoidal Differential Revision: https://phabricator.haskell.org/D572 GHC Trac Issues: #9879 (cherry picked from commit 6eb86a56135a9274d2c958a2ccf4df510c9dab86) >--------------------------------------------------------------- c52565e20ba6ff21e9c1b222cede9b1eb640491a compiler/typecheck/TcRnDriver.hs | 8 ++++++-- testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.script | 3 +++ testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.stdout | 2 ++ .../should_compile => partial-sigs/should_run}/Makefile | 0 testsuite/tests/partial-sigs/should_run/all.T | 1 + 5 files changed, 12 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index b464400..f640039 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -1792,12 +1792,16 @@ tcRnType :: HscEnv tcRnType hsc_env normalise rdr_type = runTcInteractive hsc_env $ setXOptM Opt_PolyKinds $ -- See Note [Kind-generalise in tcRnType] - do { (rn_type, _fvs) <- rnLHsType GHCiCtx rdr_type + do { (wcs, rdr_type') <- extractWildcards rdr_type + ; (rn_type, wcs) <- bindLocatedLocalsRn wcs $ \wcs_new -> do { + ; (rn_type, _fvs) <- rnLHsType GHCiCtx rdr_type' ; failIfErrsM + ; return (rn_type, wcs_new) } -- Now kind-check the type -- It can have any rank or kind - ; ty <- tcHsSigType GhciCtxt rn_type ; + ; nwc_tvs <- mapM newWildcardVarMetaKind wcs + ; ty <- tcExtendTyVarEnv nwc_tvs $ tcHsSigType GhciCtxt rn_type ; ty' <- if normalise then do { fam_envs <- tcGetFamInstEnvs diff --git a/testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.script b/testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.script new file mode 100644 index 0000000..a3f9b35 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.script @@ -0,0 +1,3 @@ +:kind _ +:kind Maybe _ + diff --git a/testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.stdout b/testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.stdout new file mode 100644 index 0000000..e1b2bd3 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_run/GHCiWildcardKind.stdout @@ -0,0 +1,2 @@ +_ :: k0 +Maybe _ :: * diff --git a/testsuite/tests/annotations/should_compile/Makefile b/testsuite/tests/partial-sigs/should_run/Makefile similarity index 100% copy from testsuite/tests/annotations/should_compile/Makefile copy to testsuite/tests/partial-sigs/should_run/Makefile diff --git a/testsuite/tests/partial-sigs/should_run/all.T b/testsuite/tests/partial-sigs/should_run/all.T new file mode 100644 index 0000000..0ca1b61 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_run/all.T @@ -0,0 +1 @@ +test('GHCiWildcardKind', normal, ghci_script, ['GHCiWildcardKind.script']) From git at git.haskell.org Tue Dec 23 14:56:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 14:56:18 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Groom comments related to StaticPointers. (2accf97) Message-ID: <20141223145618.933543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/2accf975340fdd07c6074c9aaf20f607f7c2ae19/ghc >--------------------------------------------------------------- commit 2accf975340fdd07c6074c9aaf20f607f7c2ae19 Author: Facundo Dom?nguez Date: Mon Dec 22 19:15:36 2014 -0200 Groom comments related to StaticPointers. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D575 (cherry picked from commit c72f61c6d4dd779d61bd0ebc0b1211a84c5b9038) >--------------------------------------------------------------- 2accf975340fdd07c6074c9aaf20f607f7c2ae19 compiler/deSugar/StaticPtrTable.hs | 5 ++--- compiler/rename/RnExpr.hs | 2 +- docs/users_guide/glasgow_exts.xml | 6 ++---- includes/rts/StaticPtrTable.h | 3 +-- rts/Hash.c | 2 +- rts/Hash.h | 2 +- testsuite/tests/rts/GcStaticPointers.hs | 12 ++++++------ testsuite/tests/th/TH_StaticPointers02.hs | 4 +--- testsuite/tests/th/TH_StaticPointers02.stderr | 2 +- 9 files changed, 16 insertions(+), 22 deletions(-) diff --git a/compiler/deSugar/StaticPtrTable.hs b/compiler/deSugar/StaticPtrTable.hs index d4cad0e..858a0e8 100644 --- a/compiler/deSugar/StaticPtrTable.hs +++ b/compiler/deSugar/StaticPtrTable.hs @@ -24,8 +24,7 @@ -- > -- > } -- --- where constants are values of a fingerprint of the string --- ":.sptEntry:" +-- where the constants are fingerprints produced from the static forms. -- module StaticPtrTable (sptInitCode) where @@ -38,7 +37,7 @@ import GHC.Fingerprint -- | @sptInitCode module statics@ is a C stub to insert the static entries --- @statics@ of @module@ into the static pointer table +-- @statics@ of @module@ into the static pointer table. -- -- Each entry contains the fingerprint used to locate the entry and the -- top-level binding for the entry. diff --git a/compiler/rename/RnExpr.hs b/compiler/rename/RnExpr.hs index 4755547..cf5457e 100644 --- a/compiler/rename/RnExpr.hs +++ b/compiler/rename/RnExpr.hs @@ -313,7 +313,7 @@ rnExpr e@(ELazyPat {}) = patSynErr e For the static form we check that the free variables are all top-level value bindings. This is done by checking that the name is external or -wired-in. See the Note about the NameSorts in Name.lhs. +wired-in. See the Notes about the NameSorts in Name.hs. -} rnExpr e@(HsStatic expr) = do diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index a717b72..44577f9 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -10470,9 +10470,6 @@ While the following definitions are rejected: ref6 = let x = 1 in static x ref7 y = static (let x = 1 in y) -Note that currently, the body e in static -e is restricted to a single identifier when at the GHCi -prompt. @@ -10502,13 +10499,14 @@ That being said, with the appropriate use of wrapper datatypes, the above limitations induce no loss of generality: {-# LANGUAGE ConstraintKinds #-} -{-# LANGUAGE DerivingDataTypeable #-} +{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE StaticPointers #-} import Control.Monad.ST +import Data.Typeable import GHC.StaticPtr data Dict c = c => Dict diff --git a/includes/rts/StaticPtrTable.h b/includes/rts/StaticPtrTable.h index 8b56510..87a905c 100644 --- a/includes/rts/StaticPtrTable.h +++ b/includes/rts/StaticPtrTable.h @@ -17,8 +17,7 @@ /** Inserts an entry in the Static Pointer Table. * * The key is a fingerprint computed from the StaticName of a static pointer - * and the spe_closure is a pointer to the closure defining the table entry - * (GHC.SptEntry). + * and the spe_closure is a pointer to the closure defining the table entry. * * A stable pointer to the closure is made to prevent it from being garbage * collected while the entry exists on the table. diff --git a/rts/Hash.c b/rts/Hash.c index 1881092..422c3d9 100644 --- a/rts/Hash.c +++ b/rts/Hash.c @@ -206,7 +206,7 @@ lookupHashTable(HashTable *table, StgWord key) return NULL; } -// Puts up to keys_sz keys of the hash table into the given array. Returns the +// Puts up to szKeys keys of the hash table into the given array. Returns the // actual amount of keys that have been retrieved. // // If the table is modified concurrently, the function behavior is undefined. diff --git a/rts/Hash.h b/rts/Hash.h index e802644..136f94a 100644 --- a/rts/Hash.h +++ b/rts/Hash.h @@ -21,7 +21,7 @@ void * removeHashTable ( HashTable *table, StgWord key, void *data ); int keyCountHashTable (HashTable *table); -// Puts up to keys_sz keys of the hash table into the given array. Returns the +// Puts up to szKeys keys of the hash table into the given array. Returns the // actual amount of keys that have been retrieved. // // If the table is modified concurrently, the function behavior is undefined. diff --git a/testsuite/tests/rts/GcStaticPointers.hs b/testsuite/tests/rts/GcStaticPointers.hs index 7c2fc2b..c498af5 100644 --- a/testsuite/tests/rts/GcStaticPointers.hs +++ b/testsuite/tests/rts/GcStaticPointers.hs @@ -14,9 +14,9 @@ import Unsafe.Coerce (unsafeCoerce) nats :: [Integer] nats = [0 .. ] --- Just a StaticPtr to some CAF so that we can deRef it. -nats_fp :: StaticKey -nats_fp = staticKey (static nats :: StaticPtr [Integer]) +-- The key of a 'StaticPtr' to some CAF. +nats_key :: StaticKey +nats_key = staticKey (static nats :: StaticPtr [Integer]) main = do let z = nats !! 400 @@ -26,8 +26,8 @@ main = do print z performGC threadDelay 1000000 - let Just p = unsafeLookupStaticPtr nats_fp + let Just p = unsafeLookupStaticPtr nats_key print (deRefStaticPtr (unsafeCoerce p) !! 800 :: Integer) - -- Uncommenting the next line keeps primes alive and would prevent a segfault - -- if nats were garbage collected. + -- Uncommenting the next line keeps 'nats' alive and would prevent a segfault + -- if 'nats' were garbage collected. -- print (nats !! 900) diff --git a/testsuite/tests/th/TH_StaticPointers02.hs b/testsuite/tests/th/TH_StaticPointers02.hs index 1f619a7..b381050 100644 --- a/testsuite/tests/th/TH_StaticPointers02.hs +++ b/testsuite/tests/th/TH_StaticPointers02.hs @@ -1,9 +1,7 @@ {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE StaticPointers #-} --- | A test to try the static form in splices. --- --- A static form is defined in a splice and then it is used in the program. +-- | A test to try the static form in splices, which should fail. -- module Main(main) where diff --git a/testsuite/tests/th/TH_StaticPointers02.stderr b/testsuite/tests/th/TH_StaticPointers02.stderr index cc6fa82..88da9d1 100644 --- a/testsuite/tests/th/TH_StaticPointers02.stderr +++ b/testsuite/tests/th/TH_StaticPointers02.stderr @@ -1,5 +1,5 @@ -TH_StaticPointers02.hs:13:34: +TH_StaticPointers02.hs:11:34: static forms cannot be used in splices: static 'a' In the splice: $(case staticKey (static 'a') of { From git at git.haskell.org Tue Dec 23 15:14:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 15:14:20 +0000 (UTC) Subject: [commit: ghc] master: always use 'mkdir -p' and fix missing dir (fixes #9876) (9fc3aeb) Message-ID: <20141223151420.92CE93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9fc3aebd0920561d9d3c747e6b78591d332bed08/ghc >--------------------------------------------------------------- commit 9fc3aebd0920561d9d3c747e6b78591d332bed08 Author: Joe Hillenbrand Date: Tue Dec 23 09:15:20 2014 -0600 always use 'mkdir -p' and fix missing dir (fixes #9876) Summary: Signed-off-by: Joe Hillenbrand Reviewers: thomie, austin Reviewed By: thomie, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D566 GHC Trac Issues: #9876 >--------------------------------------------------------------- 9fc3aebd0920561d9d3c747e6b78591d332bed08 ghc.mk | 24 ++++++++++++------------ 1 file changed, 12 insertions(+), 12 deletions(-) diff --git a/ghc.mk b/ghc.mk index 2c9c635..6c587bd 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1150,10 +1150,10 @@ EXTRA_PACKAGES=parallel stm random primitive vector dph sdist-ghc-prep : $(call removeTrees,$(SRC_DIST_GHC_ROOT)) $(call removeFiles,$(SRC_DIST_GHC_TARBALL)) - -mkdir $(SRC_DIST_ROOT) - mkdir $(SRC_DIST_GHC_ROOT) - mkdir $(SRC_DIST_GHC_DIR) - cd $(SRC_DIST_GHC_DIR) && for i in $(SRC_DIST_GHC_DIRS); do mkdir $$i; ( cd $$i && lndir $(TOP)/$$i ); done + mkdir -p $(SRC_DIST_ROOT) + mkdir -p $(SRC_DIST_GHC_ROOT) + mkdir -p $(SRC_DIST_GHC_DIR) + cd $(SRC_DIST_GHC_DIR) && for i in $(SRC_DIST_GHC_DIRS); do mkdir -p $$i; ( cd $$i && lndir $(TOP)/$$i ); done cd $(SRC_DIST_GHC_DIR) && for i in $(SRC_DIST_GHC_FILES); do $(LN_S) $(TOP)/$$i .; done cd $(SRC_DIST_GHC_DIR) && $(MAKE) distclean $(call removeTrees,$(SRC_DIST_GHC_DIR)/libraries/tarballs/) @@ -1174,10 +1174,10 @@ sdist-ghc-prep : sdist-windows-tarballs-prep : $(call removeTrees,$(SRC_DIST_WINDOWS_TARBALLS_ROOT)) $(call removeFiles,$(SRC_DIST_WINDOWS_TARBALLS_TARBALL)) - -mkdir $(SRC_DIST_ROOT) - mkdir $(SRC_DIST_WINDOWS_TARBALLS_ROOT) - mkdir $(SRC_DIST_WINDOWS_TARBALLS_DIR) - mkdir $(SRC_DIST_WINDOWS_TARBALLS_DIR)/ghc-tarballs + mkdir -p $(SRC_DIST_ROOT) + mkdir -p $(SRC_DIST_WINDOWS_TARBALLS_ROOT) + mkdir -p $(SRC_DIST_WINDOWS_TARBALLS_DIR) + mkdir -p $(SRC_DIST_WINDOWS_TARBALLS_DIR)/ghc-tarballs cd $(SRC_DIST_WINDOWS_TARBALLS_DIR)/ghc-tarballs && lndir $(TOP)/ghc-tarballs $(call removeTrees,$(SRC_DIST_WINDOWS_TARBALLS_DIR)/ghc-tarballs/.git) @@ -1185,10 +1185,10 @@ sdist-windows-tarballs-prep : sdist-testsuite-prep : $(call removeTrees,$(SRC_DIST_TESTSUITE_ROOT)) $(call removeFiles,$(SRC_DIST_TESTSUITE_TARBALL)) - -mkdir $(SRC_DIST_ROOT) - mkdir $(SRC_DIST_TESTSUITE_ROOT) - mkdir $(SRC_DIST_TESTSUITE_DIR) - mkdir $(SRC_DIST_TESTSUITE_DIR)/testsuite + mkdir -p $(SRC_DIST_ROOT) + mkdir -p $(SRC_DIST_TESTSUITE_ROOT) + mkdir -p $(SRC_DIST_TESTSUITE_DIR) + mkdir -p $(SRC_DIST_TESTSUITE_DIR)/testsuite cd $(SRC_DIST_TESTSUITE_DIR)/testsuite && lndir $(TOP)/testsuite .PHONY: sdist-ghc From git at git.haskell.org Tue Dec 23 15:14:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 15:14:50 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: always use 'mkdir -p' and fix missing dir (fixes #9876) (8869388) Message-ID: <20141223151450.588B63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/886938892b8c69b66b7fd9001355117675537c26/ghc >--------------------------------------------------------------- commit 886938892b8c69b66b7fd9001355117675537c26 Author: Joe Hillenbrand Date: Tue Dec 23 09:15:20 2014 -0600 always use 'mkdir -p' and fix missing dir (fixes #9876) Summary: Signed-off-by: Joe Hillenbrand Reviewers: thomie, austin Reviewed By: thomie, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D566 GHC Trac Issues: #9876 (cherry picked from commit 9fc3aebd0920561d9d3c747e6b78591d332bed08) >--------------------------------------------------------------- 886938892b8c69b66b7fd9001355117675537c26 ghc.mk | 24 ++++++++++++------------ 1 file changed, 12 insertions(+), 12 deletions(-) diff --git a/ghc.mk b/ghc.mk index 2c9c635..6c587bd 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1150,10 +1150,10 @@ EXTRA_PACKAGES=parallel stm random primitive vector dph sdist-ghc-prep : $(call removeTrees,$(SRC_DIST_GHC_ROOT)) $(call removeFiles,$(SRC_DIST_GHC_TARBALL)) - -mkdir $(SRC_DIST_ROOT) - mkdir $(SRC_DIST_GHC_ROOT) - mkdir $(SRC_DIST_GHC_DIR) - cd $(SRC_DIST_GHC_DIR) && for i in $(SRC_DIST_GHC_DIRS); do mkdir $$i; ( cd $$i && lndir $(TOP)/$$i ); done + mkdir -p $(SRC_DIST_ROOT) + mkdir -p $(SRC_DIST_GHC_ROOT) + mkdir -p $(SRC_DIST_GHC_DIR) + cd $(SRC_DIST_GHC_DIR) && for i in $(SRC_DIST_GHC_DIRS); do mkdir -p $$i; ( cd $$i && lndir $(TOP)/$$i ); done cd $(SRC_DIST_GHC_DIR) && for i in $(SRC_DIST_GHC_FILES); do $(LN_S) $(TOP)/$$i .; done cd $(SRC_DIST_GHC_DIR) && $(MAKE) distclean $(call removeTrees,$(SRC_DIST_GHC_DIR)/libraries/tarballs/) @@ -1174,10 +1174,10 @@ sdist-ghc-prep : sdist-windows-tarballs-prep : $(call removeTrees,$(SRC_DIST_WINDOWS_TARBALLS_ROOT)) $(call removeFiles,$(SRC_DIST_WINDOWS_TARBALLS_TARBALL)) - -mkdir $(SRC_DIST_ROOT) - mkdir $(SRC_DIST_WINDOWS_TARBALLS_ROOT) - mkdir $(SRC_DIST_WINDOWS_TARBALLS_DIR) - mkdir $(SRC_DIST_WINDOWS_TARBALLS_DIR)/ghc-tarballs + mkdir -p $(SRC_DIST_ROOT) + mkdir -p $(SRC_DIST_WINDOWS_TARBALLS_ROOT) + mkdir -p $(SRC_DIST_WINDOWS_TARBALLS_DIR) + mkdir -p $(SRC_DIST_WINDOWS_TARBALLS_DIR)/ghc-tarballs cd $(SRC_DIST_WINDOWS_TARBALLS_DIR)/ghc-tarballs && lndir $(TOP)/ghc-tarballs $(call removeTrees,$(SRC_DIST_WINDOWS_TARBALLS_DIR)/ghc-tarballs/.git) @@ -1185,10 +1185,10 @@ sdist-windows-tarballs-prep : sdist-testsuite-prep : $(call removeTrees,$(SRC_DIST_TESTSUITE_ROOT)) $(call removeFiles,$(SRC_DIST_TESTSUITE_TARBALL)) - -mkdir $(SRC_DIST_ROOT) - mkdir $(SRC_DIST_TESTSUITE_ROOT) - mkdir $(SRC_DIST_TESTSUITE_DIR) - mkdir $(SRC_DIST_TESTSUITE_DIR)/testsuite + mkdir -p $(SRC_DIST_ROOT) + mkdir -p $(SRC_DIST_TESTSUITE_ROOT) + mkdir -p $(SRC_DIST_TESTSUITE_DIR) + mkdir -p $(SRC_DIST_TESTSUITE_DIR)/testsuite cd $(SRC_DIST_TESTSUITE_DIR)/testsuite && lndir $(TOP)/testsuite .PHONY: sdist-ghc From git at git.haskell.org Tue Dec 23 16:29:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 16:29:29 +0000 (UTC) Subject: [commit: ghc] master: Add a small comment (625dd7b) Message-ID: <20141223162929.EF05F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/625dd7b646d37177731cad20abd4026f2725472f/ghc >--------------------------------------------------------------- commit 625dd7b646d37177731cad20abd4026f2725472f Author: Simon Peyton Jones Date: Mon Dec 22 14:35:24 2014 +0000 Add a small comment >--------------------------------------------------------------- 625dd7b646d37177731cad20abd4026f2725472f compiler/rename/RnSource.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index 95211cb..b94f73f 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -73,7 +73,7 @@ Checks the @(..)@ etc constraints in the export list. -- Brings the binders of the group into scope in the appropriate places; -- does NOT assume that anything is in scope already rnSrcDecls :: [Name] -> HsGroup RdrName -> RnM (TcGblEnv, HsGroup Name) --- Rename a HsGroup; used for normal source files *and* hs-boot files +-- Rename a top-level HsGroup; used for normal source files *and* hs-boot files rnSrcDecls extra_deps group@(HsGroup { hs_valds = val_decls, hs_splcds = splice_decls, hs_tyclds = tycl_decls, From git at git.haskell.org Tue Dec 23 16:29:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 16:29:32 +0000 (UTC) Subject: [commit: ghc] master: Eliminate so-called "silent superclass parameters" (a6f0f5a) Message-ID: <20141223162932.A04A93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a6f0f5ab45b2643b561e0a0a54a4f14745ab2152/ghc >--------------------------------------------------------------- commit a6f0f5ab45b2643b561e0a0a54a4f14745ab2152 Author: Simon Peyton Jones Date: Tue Dec 23 15:39:50 2014 +0000 Eliminate so-called "silent superclass parameters" The purpose of silent superclass parameters was to solve the awkward problem of superclass dictinaries being bound to bottom. See THE PROBLEM in Note [Recursive superclasses] in TcInstDcls Although the silent-superclass idea worked, * It had non-local consequences, and had effects even in Haddock, where we had to discard silent parameters before displaying instance declarations * It had unexpected peformance costs, shown up by Trac #3064 and its test case. In monad-transformer code, when constructing a Monad dictionary you had to pass an Applicative dictionary; and to construct that you neede a Functor dictionary. Yet these extra dictionaries were often never used. (All this got much worse when we added Applicative as a superclass of Monad.) Test T3064 compiled *far* faster after silent superclasses were eliminated. * It introduced new bugs. For example SilentParametersOverlapping, T5051, and T7862, all failed to compile because of instance overlap directly because of the silent-superclass trick. So this patch takes a new approach, which I worked out with Dimitrios in the closing hours before Christmas. It is described in detail in THE PROBLEM in Note [Recursive superclasses] in TcInstDcls. Seems to work great! Quite a bit of knock-on effect * The main implementation work is in tcSuperClasses in TcInstDcls Everything else is fall-out * IdInfo.DFunId no longer needs its n-silent argument * Ditto IDFunId in IfaceSyn * Hence interface file format changes * Now that DFunIds do not have silent superclass parameters, printing out instance declarations is simpler. There is tiny knock-on effect in Haddock, so that submodule is updated * I realised that when computing the "size of a dictionary type" in TcValidity.sizePred, we should be rather conservative about type functions, which can arbitrarily increase the size of a type. Hence the new datatype TypeSize, which has a TSBig constructor for "arbitrarily big". * instDFunType moves from TcSMonad to Inst * Interestingly, CmmNode and CmmExpr both now need a non-silent (Ord r) in a couple of instance declarations. These were previously silent but must now be explicit. * Quite a bit of wibbling in error messages >--------------------------------------------------------------- a6f0f5ab45b2643b561e0a0a54a4f14745ab2152 compiler/basicTypes/Id.hs | 7 +- compiler/basicTypes/IdInfo.hs | 13 +- compiler/basicTypes/MkId.hs | 20 +- compiler/basicTypes/OccName.hs | 7 +- compiler/cmm/CmmExpr.hs | 4 +- compiler/cmm/CmmNode.hs | 4 +- compiler/coreSyn/CoreUtils.hs | 2 +- compiler/deSugar/DsBinds.hs | 2 +- compiler/iface/IfaceSyn.hs | 8 +- compiler/iface/MkIface.hs | 2 +- compiler/iface/TcIface.hs | 4 +- compiler/typecheck/Inst.hs | 23 +- compiler/typecheck/TcInstDcls.hs | 282 +++++++++++++++++---- compiler/typecheck/TcInteract.hs | 14 +- compiler/typecheck/TcMType.hs | 2 +- compiler/typecheck/TcSMonad.hs | 30 +-- compiler/typecheck/TcSplice.hs | 5 +- compiler/typecheck/TcUnify.hs | 37 ++- compiler/typecheck/TcValidity.hs | 137 ++++++---- compiler/types/InstEnv.hs | 12 +- .../tests/deriving/should_fail/drvfail002.stderr | 2 +- .../should_compile/InstContextNorm.hs | 2 +- testsuite/tests/indexed-types/should_fail/T7862.hs | 5 +- .../tests/indexed-types/should_fail/T7862.stderr | 22 +- testsuite/tests/indexed-types/should_fail/all.T | 2 +- testsuite/tests/perf/compiler/all.T | 7 +- .../tests/simplCore/should_compile/Simpl020_A.hs | 3 +- .../tests/simplCore/should_compile/T8848.stderr | 45 +++- testsuite/tests/simplCore/should_compile/all.T | 2 +- .../tests/simplCore/should_compile/simpl020.stderr | 2 +- .../should_fail/SilentParametersOverlapping.stderr | 13 - testsuite/tests/typecheck/should_fail/T5051.hs | 2 + testsuite/tests/typecheck/should_fail/T5051.stderr | 14 +- testsuite/tests/typecheck/should_fail/T5691.stderr | 10 + testsuite/tests/typecheck/should_fail/T6161.hs | 19 ++ testsuite/tests/typecheck/should_fail/T6161.stderr | 8 +- testsuite/tests/typecheck/should_fail/T8603.stderr | 5 + testsuite/tests/typecheck/should_fail/all.T | 4 +- .../tests/typecheck/should_fail/tcfail017.stderr | 4 +- .../tests/typecheck/should_fail/tcfail019.stderr | 5 + .../tests/typecheck/should_fail/tcfail020.stderr | 4 +- .../tests/typecheck/should_fail/tcfail042.stderr | 15 ++ .../tests/typecheck/should_fail/tcfail106.stderr | 5 + utils/haddock | 2 +- 44 files changed, 542 insertions(+), 275 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a6f0f5ab45b2643b561e0a0a54a4f14745ab2152 From git at git.haskell.org Tue Dec 23 16:29:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 16:29:35 +0000 (UTC) Subject: [commit: ghc] master: Add a couple of missing cases to isTcReflCo and isTcReflCo_maybe (3e96d89) Message-ID: <20141223162935.3E28F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3e96d89b1d37a989b92a11587de29e347ef19328/ghc >--------------------------------------------------------------- commit 3e96d89b1d37a989b92a11587de29e347ef19328 Author: Simon Peyton Jones Date: Tue Dec 23 15:40:54 2014 +0000 Add a couple of missing cases to isTcReflCo and isTcReflCo_maybe >--------------------------------------------------------------- 3e96d89b1d37a989b92a11587de29e347ef19328 compiler/typecheck/TcEvidence.hs | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcEvidence.hs b/compiler/typecheck/TcEvidence.hs index 60ac889..552a403 100644 --- a/compiler/typecheck/TcEvidence.hs +++ b/compiler/typecheck/TcEvidence.hs @@ -157,12 +157,14 @@ isEqVar v = case tyConAppTyCon_maybe (varType v) of Nothing -> False isTcReflCo_maybe :: TcCoercion -> Maybe TcType -isTcReflCo_maybe (TcRefl _ ty) = Just ty -isTcReflCo_maybe _ = Nothing +isTcReflCo_maybe (TcRefl _ ty) = Just ty +isTcReflCo_maybe (TcCoercion co) = isReflCo_maybe co +isTcReflCo_maybe _ = Nothing isTcReflCo :: TcCoercion -> Bool -isTcReflCo (TcRefl {}) = True -isTcReflCo _ = False +isTcReflCo (TcRefl {}) = True +isTcReflCo (TcCoercion co) = isReflCo co +isTcReflCo _ = False getTcCoVar_maybe :: TcCoercion -> Maybe CoVar getTcCoVar_maybe (TcCoVarCo v) = Just v From git at git.haskell.org Tue Dec 23 16:29:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 16:29:37 +0000 (UTC) Subject: [commit: ghc] master: Comments only (c407b5a) Message-ID: <20141223162937.CB3A03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c407b5a6e206764a04d041dcb1894ce737d23cb0/ghc >--------------------------------------------------------------- commit c407b5a6e206764a04d041dcb1894ce737d23cb0 Author: Simon Peyton Jones Date: Tue Dec 23 15:41:59 2014 +0000 Comments only >--------------------------------------------------------------- c407b5a6e206764a04d041dcb1894ce737d23cb0 compiler/typecheck/TcFlatten.hs | 13 +++++++++---- 1 file changed, 9 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcFlatten.hs b/compiler/typecheck/TcFlatten.hs index 2b11f99..3e13a00 100644 --- a/compiler/typecheck/TcFlatten.hs +++ b/compiler/typecheck/TcFlatten.hs @@ -978,10 +978,7 @@ Examples that are helped are tests T9872, and T5321Fun. Performance testing indicates that it's best to try this *twice*, once before flattening arguments and once after flattening arguments. Adding the extra reduction attempt before flattening arguments cut -the allocation amounts for the T9872{a,b,c} tests by half. Testing -also indicated that the early reduction should not use the flat-cache, -but that the later reduction should. It's possible that with more -examples, we might learn that these knobs should be set differently. +the allocation amounts for the T9872{a,b,c} tests by half. An example of where the early reduction appears helpful: @@ -995,6 +992,14 @@ Flattening the argument never gets us anywhere, but trying to flatten it at every step is quadratic in the length of the list. Reducing more eagerly makes simplifying the right-hand type linear in its length. +Testing also indicated that the early reduction should *not* use the +flat-cache, but that the later reduction *should*. (Although the +effect was not large.) Hence the Bool argument to try_to_reduce. To +me (SLPJ) this seems odd; I get that eager reduction usually succeeds; +and if don't use the cache for eager reduction, we will miss most of +the opportunities for using it at all. More exploration would be good +here. + At the end, once we've got a flat rhs, we extend the flatten-cache to record the result. Doing so can save lots of work when the same redex shows up more than once. Note that we record the link from the redex all the way to its From git at git.haskell.org Tue Dec 23 16:29:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 16:29:40 +0000 (UTC) Subject: [commit: ghc] master: A bit of refactoring to TcErrors (679a661) Message-ID: <20141223162940.713CA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/679a661890c9e5a218d8328658cae2b71d367024/ghc >--------------------------------------------------------------- commit 679a661890c9e5a218d8328658cae2b71d367024 Author: Simon Peyton Jones Date: Tue Dec 23 15:44:00 2014 +0000 A bit of refactoring to TcErrors This replaces a bunch of boolean flags in ReportErrCtxt with an algebraic data type to say how to handle expression holes and type holes No change in functionality; I just found myself unable to understand the code easily, when thinking about something else. Result is quite nice, I think. >--------------------------------------------------------------- 679a661890c9e5a218d8328658cae2b71d367024 compiler/typecheck/TcErrors.hs | 126 ++++++++++++++++++++++------------------ compiler/typecheck/TcRnTypes.hs | 33 +++++++---- 2 files changed, 93 insertions(+), 66 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 679a661890c9e5a218d8328658cae2b71d367024 From git at git.haskell.org Tue Dec 23 16:29:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 16:29:43 +0000 (UTC) Subject: [commit: ghc] master: Attempt to improve cleaning (c3394e0) Message-ID: <20141223162943.0EF903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c3394e0d2cce4bbaa034dc77473add151781ef93/ghc >--------------------------------------------------------------- commit c3394e0d2cce4bbaa034dc77473add151781ef93 Author: Simon Peyton Jones Date: Tue Dec 23 15:45:09 2014 +0000 Attempt to improve cleaning I found several tests that failed when the interface file format changed, due to leftover .hi file droppings. I'm not sure I've done this right, but it should be a bit better >--------------------------------------------------------------- c3394e0d2cce4bbaa034dc77473add151781ef93 testsuite/tests/deriving/should_run/all.T | 2 +- testsuite/tests/driver/Makefile | 1 + testsuite/tests/generics/all.T | 9 ++++++--- 3 files changed, 8 insertions(+), 4 deletions(-) diff --git a/testsuite/tests/deriving/should_run/all.T b/testsuite/tests/deriving/should_run/all.T index 58b4903..13858a8 100644 --- a/testsuite/tests/deriving/should_run/all.T +++ b/testsuite/tests/deriving/should_run/all.T @@ -37,4 +37,4 @@ test('T5712', normal, compile_and_run, ['']) test('T7931', normal, compile_and_run, ['']) test('T8280', normal, compile_and_run, ['']) test('T9576', exit_code(1), compile_and_run, ['']) -test('T9830', normal, multimod_compile_and_run, ['T9830','-v0']) +test('T9830', extra_clean(['T9830a.hi', 'T9830a.o']), multimod_compile_and_run, ['T9830','-v0']) diff --git a/testsuite/tests/driver/Makefile b/testsuite/tests/driver/Makefile index 4670958..11724a5 100644 --- a/testsuite/tests/driver/Makefile +++ b/testsuite/tests/driver/Makefile @@ -571,6 +571,7 @@ T703: .PHONY: T2182 T2182: + $(RM) T2182_A.hi T2182.hi ! "$(TEST_HC)" $(TEST_HC_OPTS) --make T2182_A.hs T2182.hs -v0 ! "$(TEST_HC)" $(TEST_HC_OPTS) --make T2182.hs T2182_A.hs -v0 diff --git a/testsuite/tests/generics/all.T b/testsuite/tests/generics/all.T index d959d0c..b5050e4 100644 --- a/testsuite/tests/generics/all.T +++ b/testsuite/tests/generics/all.T @@ -19,9 +19,12 @@ test('GenCannotDoRep1_6', normal, compile_fail, ['']) test('GenCannotDoRep1_7', normal, compile_fail, ['']) test('GenCannotDoRep1_8', normal, compile_fail, ['']) -test('T5462Yes1', normal, multimod_compile_and_run, ['T5462Yes1', '-iGEq -iGEnum -iGFunctor -outputdir=out_T5462Yes1']) -test('T5462Yes2', normal, multimod_compile_and_run, ['T5462Yes2', '-iGFunctor -outputdir=out_T5462Yes2']) -test('T5462No1', normal, multimod_compile_fail, ['T5462No1', '-iGFunctor -outputdir=T5462No1']) +test('T5462Yes1', extra_clean(['T5462Yes1/GFunctor.hi']) + , multimod_compile_and_run, ['T5462Yes1', '-iGEq -iGEnum -iGFunctor -outputdir=out_T5462Yes1']) +test('T5462Yes2', extra_clean(['T5462Yes2/GFunctor.hi']) + , multimod_compile_and_run, ['T5462Yes2', '-iGFunctor -outputdir=out_T5462Yes2']) +test('T5462No1', extra_clean(['T5462No1/GFunctor.hi']) + , multimod_compile_fail, ['T5462No1', '-iGFunctor -outputdir=T5462No1']) test('T5884', normal, compile, ['']) test('GenNewtype', normal, compile_and_run, ['']) From git at git.haskell.org Tue Dec 23 16:29:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 16:29:46 +0000 (UTC) Subject: [commit: ghc] master: Test earlier for self-import (Trac #9032) (edd233a) Message-ID: <20141223162946.32D203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/edd233acc19d269385c1a870829e0916a3df8e88/ghc >--------------------------------------------------------------- commit edd233acc19d269385c1a870829e0916a3df8e88 Author: Simon Peyton Jones Date: Tue Dec 23 15:59:30 2014 +0000 Test earlier for self-import (Trac #9032) This patch makes the renamer check for self-import, especially when dependencies change, because the typechecker can fall over if that happens. I'm still uneasy about *indirect* self-import, but I'll leave that for another day >--------------------------------------------------------------- edd233acc19d269385c1a870829e0916a3df8e88 compiler/rename/RnNames.hs | 14 +++++++++++--- testsuite/tests/rename/should_fail/Makefile | 5 +++++ testsuite/tests/rename/should_fail/T9032.hs | 12 ++++++++++++ testsuite/tests/rename/should_fail/T9032.stderr | 3 +++ testsuite/tests/rename/should_fail/all.T | 5 +++++ 5 files changed, 36 insertions(+), 3 deletions(-) diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs index bff2ed0..145d6fc 100644 --- a/compiler/rename/RnNames.hs +++ b/compiler/rename/RnNames.hs @@ -181,6 +181,14 @@ rnImportDecl this_mod let imp_mod_name = unLoc loc_imp_mod_name doc = ppr imp_mod_name <+> ptext (sLit "is directly imported") + -- Check for self-import, which confuses the typechecker (Trac #9032) + -- ghc --make rejects self-import cycles already, but batch-mode may not + -- at least not until TcIface.tcHiBootIface, which is too late to avoid + -- typechecker crashes. ToDo: what about indirect self-import? + -- But 'import {-# SOURCE #-} M' is ok, even if a bit odd + when (not want_boot && imp_mod_name == moduleName this_mod) + (addErr (ptext (sLit "A module cannot import itself:") <+> ppr imp_mod_name)) + -- Check for a missing import list (Opt_WarnMissingImportList also -- checks for T(..) items but that is done in checkDodgyImport below) case imp_details of @@ -212,9 +220,9 @@ rnImportDecl this_mod warnIf (want_boot && any (not.mi_boot) ifaces && isOneShot (ghcMode dflags)) (warnRedundantSourceImport imp_mod_name) when (mod_safe && not (safeImportsOn dflags)) $ - addErrAt loc (ptext (sLit "safe import can't be used as Safe Haskell isn't on!") - $+$ ptext (sLit $ "please enable Safe Haskell through either " - ++ "Safe, Trustworthy or Unsafe")) + addErr (ptext (sLit "safe import can't be used as Safe Haskell isn't on!") + $+$ ptext (sLit $ "please enable Safe Haskell through either " + ++ "Safe, Trustworthy or Unsafe")) let qual_mod_name = as_mod `orElse` imp_mod_name diff --git a/testsuite/tests/rename/should_fail/Makefile b/testsuite/tests/rename/should_fail/Makefile index 9101fbd..037694c 100644 --- a/testsuite/tests/rename/should_fail/Makefile +++ b/testsuite/tests/rename/should_fail/Makefile @@ -1,3 +1,8 @@ TOP=../../.. include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/test.mk + +T9032: + '$(TEST_HC)' $(TEST_HC_OPTS) -c -fforce-recomp T9032.hs + '$(TEST_HC)' $(TEST_HC_OPTS) -c -fforce-recomp -DERR T9032.hs + diff --git a/testsuite/tests/rename/should_fail/T9032.hs b/testsuite/tests/rename/should_fail/T9032.hs new file mode 100644 index 0000000..0a00ba3 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T9032.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE CPP #-} + +module T9032 where + +#ifdef ERR +import T9032 +#endif + +f x = x + + + diff --git a/testsuite/tests/rename/should_fail/T9032.stderr b/testsuite/tests/rename/should_fail/T9032.stderr new file mode 100644 index 0000000..56b9158 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T9032.stderr @@ -0,0 +1,3 @@ + +T9032.hs:6:1: A module cannot import itself: T9032 +make[2]: *** [T9032] Error 1 diff --git a/testsuite/tests/rename/should_fail/all.T b/testsuite/tests/rename/should_fail/all.T index 2798fe9..8d60ef3 100644 --- a/testsuite/tests/rename/should_fail/all.T +++ b/testsuite/tests/rename/should_fail/all.T @@ -127,3 +127,8 @@ test('T9436', normal, compile_fail, ['']) test('T9437', normal, compile_fail, ['']) test('T9077', normal, compile_fail, ['']) test('T9815', normal, compile_fail, ['']) + +test('T9032', + exit_code(2), + run_command, + ['$MAKE -s --no-print-directory T9032']) From git at git.haskell.org Tue Dec 23 17:23:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 17:23:01 +0000 (UTC) Subject: [commit: ghc] master: Fixup edd233acc19d269385 (T9032 test) (7a2c9dd) Message-ID: <20141223172301.C1D023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7a2c9dde24b72fe53216881867d5543e5a6f756c/ghc >--------------------------------------------------------------- commit 7a2c9dde24b72fe53216881867d5543e5a6f756c Author: Herbert Valerio Riedel Date: Tue Dec 23 18:10:20 2014 +0100 Fixup edd233acc19d269385 (T9032 test) This is not a proper fix as the `x` in `make[x]: ...` changes depending on how the testsuite was called. So this probably only works when invoked via ./validate. >--------------------------------------------------------------- 7a2c9dde24b72fe53216881867d5543e5a6f756c testsuite/tests/rename/should_fail/T9032.stderr | 2 +- testsuite/tests/rename/should_fail/T9032.stdout | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/rename/should_fail/T9032.stderr b/testsuite/tests/rename/should_fail/T9032.stderr index 56b9158..c02dac8 100644 --- a/testsuite/tests/rename/should_fail/T9032.stderr +++ b/testsuite/tests/rename/should_fail/T9032.stderr @@ -1,3 +1,3 @@ T9032.hs:6:1: A module cannot import itself: T9032 -make[2]: *** [T9032] Error 1 +make[3]: *** [T9032] Error 1 diff --git a/testsuite/tests/rename/should_fail/T9032.stdout b/testsuite/tests/rename/should_fail/T9032.stdout new file mode 100644 index 0000000..82b486f --- /dev/null +++ b/testsuite/tests/rename/should_fail/T9032.stdout @@ -0,0 +1 @@ +Makefile:6: recipe for target 'T9032' failed From git at git.haskell.org Tue Dec 23 21:11:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 21:11:26 +0000 (UTC) Subject: [commit: ghc] master: Make ghc -e not exit on valid import commands (#9905) (878910e) Message-ID: <20141223211126.5E0093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/878910e1c4520732ab9d8372c1c81f00d484e48f/ghc >--------------------------------------------------------------- commit 878910e1c4520732ab9d8372c1c81f00d484e48f Author: Reid Barton Date: Tue Dec 23 15:22:01 2014 -0500 Make ghc -e not exit on valid import commands (#9905) Summary: Some Trues and Falses were mixed up due to Bool being used in different senses in different parts of GHCi. Test Plan: harbormaster; validate Reviewers: austin Reviewed By: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D581 GHC Trac Issues: #9905 Conflicts: ghc/InteractiveUI.hs >--------------------------------------------------------------- 878910e1c4520732ab9d8372c1c81f00d484e48f ghc/GhciMonad.hs | 1 + ghc/InteractiveUI.hs | 22 ++++++++++++++-------- testsuite/tests/ghc-e/should_fail/Makefile | 9 +++++++++ testsuite/tests/ghc-e/should_fail/all.T | 12 +++++++++++- testsuite/tests/ghc-e/should_run/Makefile | 6 ++++++ testsuite/tests/ghc-e/should_run/T9905.stdout | 1 + testsuite/tests/ghc-e/should_run/T9905b.stdout | 1 + testsuite/tests/ghc-e/should_run/all.T | 2 ++ 8 files changed, 45 insertions(+), 9 deletions(-) diff --git a/ghc/GhciMonad.hs b/ghc/GhciMonad.hs index 89c2028..f57fbba 100644 --- a/ghc/GhciMonad.hs +++ b/ghc/GhciMonad.hs @@ -63,6 +63,7 @@ import Control.Applicative (Applicative(..)) ----------------------------------------------------------------------------- -- GHCi monad +-- the Bool means: True = we should exit GHCi (:quit) type Command = (String, String -> InputT GHCi Bool, CompletionFunc GHCi) data GHCiState = GHCiState diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index d478336..ce73c48 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -729,7 +729,11 @@ runCommands' eh sourceErrorHandler gCmd = do when (not success) $ maybe (return ()) lift sourceErrorHandler runCommands' eh sourceErrorHandler gCmd --- | Evaluate a single line of user input (either : or Haskell code) +-- | Evaluate a single line of user input (either : or Haskell code). +-- A result of Nothing means there was no more input to process. +-- Otherwise the result is Just b where b is True if the command succeeded; +-- this is relevant only to ghc -e, which will exit with status 1 +-- if the commmand was unsuccessful. GHCi will continue in either case. runOneCommand :: (SomeException -> GHCi Bool) -> InputT GHCi (Maybe String) -> InputT GHCi (Maybe Bool) runOneCommand eh gCmd = do @@ -740,14 +744,14 @@ runOneCommand eh gCmd = do case mb_cmd1 of Nothing -> return Nothing Just c -> ghciHandle (\e -> lift $ eh e >>= return . Just) $ - handleSourceError printErrorAndKeepGoing + handleSourceError printErrorAndFail (doCommand c) -- source error's are handled by runStmt -- is the handler necessary here? where - printErrorAndKeepGoing err = do + printErrorAndFail err = do GHC.printException err - return $ Just True + return $ Just False -- Exit ghc -e, but not GHCi noSpace q = q >>= maybe (return Nothing) (\c -> case removeSpaces c of @@ -890,16 +894,18 @@ declPrefixes dflags = keywords ++ concat opt_keywords , ["deriving " | xopt Opt_StandaloneDeriving dflags] ] --- | Entry point to execute some haskell code from user +-- | Entry point to execute some haskell code from user. +-- The return value True indicates success, as in `runOneCommand`. runStmt :: String -> SingleStep -> GHCi Bool runStmt stmt step - -- empty + -- empty; this should be impossible anyways since we filtered out + -- whitespace-only input in runOneCommand's noSpace | null (filter (not.isSpace) stmt) - = return False + = return True -- import | stmt `looks_like` "import " - = do addImportToContext stmt; return False + = do addImportToContext stmt; return True | otherwise = do dflags <- getDynFlags diff --git a/testsuite/tests/ghc-e/should_fail/Makefile b/testsuite/tests/ghc-e/should_fail/Makefile index 5b0d753..7a02f7b 100644 --- a/testsuite/tests/ghc-e/should_fail/Makefile +++ b/testsuite/tests/ghc-e/should_fail/Makefile @@ -4,3 +4,12 @@ include $(TOP)/mk/test.mk T7962: '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "return (" + +T9905fail1: + '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "import This.Module.Does.Not.Exist" + +T9905fail2: + '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "import Data.List (bogusIdentifier)" + +T9905fail3: + '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "import Prelude (+)" # syntax error diff --git a/testsuite/tests/ghc-e/should_fail/all.T b/testsuite/tests/ghc-e/should_fail/all.T index 4c5ac5c..07dc614 100644 --- a/testsuite/tests/ghc-e/should_fail/all.T +++ b/testsuite/tests/ghc-e/should_fail/all.T @@ -1,3 +1,13 @@ setTestOpts(when(compiler_profiled(), skip)) -test('T7962', [exit_code(2), req_interp, ignore_output], run_command, ['$MAKE --no-print-directory -s T7962']) +test('T7962', [exit_code(2), req_interp, ignore_output], run_command, + ['$MAKE --no-print-directory -s T7962']) + +test('T9905fail1', [exit_code(2), req_interp, ignore_output], run_command, + ['$MAKE --no-print-directory -s T9905fail1']) + +test('T9905fail2', [exit_code(2), req_interp, ignore_output], run_command, + ['$MAKE --no-print-directory -s T9905fail2']) + +test('T9905fail3', [exit_code(2), req_interp, ignore_output], run_command, + ['$MAKE --no-print-directory -s T9905fail3']) diff --git a/testsuite/tests/ghc-e/should_run/Makefile b/testsuite/tests/ghc-e/should_run/Makefile index 5ed1ec2..aa7041b 100644 --- a/testsuite/tests/ghc-e/should_run/Makefile +++ b/testsuite/tests/ghc-e/should_run/Makefile @@ -32,3 +32,9 @@ T7299: T9086: '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e ":main" T9086.hs + +T9905: + '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "import Data.List" -e "sort [2,1]" + +T9905b: + '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "import qualified Data.List as L" -e "L.sort [2,1]" diff --git a/testsuite/tests/ghc-e/should_run/T9905.stdout b/testsuite/tests/ghc-e/should_run/T9905.stdout new file mode 100644 index 0000000..6ed63af --- /dev/null +++ b/testsuite/tests/ghc-e/should_run/T9905.stdout @@ -0,0 +1 @@ +[1,2] diff --git a/testsuite/tests/ghc-e/should_run/T9905b.stdout b/testsuite/tests/ghc-e/should_run/T9905b.stdout new file mode 100644 index 0000000..6ed63af --- /dev/null +++ b/testsuite/tests/ghc-e/should_run/T9905b.stdout @@ -0,0 +1 @@ +[1,2] diff --git a/testsuite/tests/ghc-e/should_run/all.T b/testsuite/tests/ghc-e/should_run/all.T index 9f64918..329ceea 100644 --- a/testsuite/tests/ghc-e/should_run/all.T +++ b/testsuite/tests/ghc-e/should_run/all.T @@ -15,3 +15,5 @@ test('T2636', req_interp, run_command, ['$MAKE --no-print-directory -s T2636']) test('T3890', req_interp, run_command, ['$MAKE --no-print-directory -s T3890']) test('T7299', req_interp, run_command, ['$MAKE --no-print-directory -s T7299']) test('T9086', req_interp, run_command, ['$MAKE --no-print-directory -s T9086']) +test('T9905', req_interp, run_command, ['$MAKE --no-print-directory -s T9905']) +test('T9905b', req_interp, run_command, ['$MAKE --no-print-directory -s T9905b']) From git at git.haskell.org Tue Dec 23 21:42:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Dec 2014 21:42:06 +0000 (UTC) Subject: [commit: ghc] master: Make ghc -e fail on invalid declarations (cc510b4) Message-ID: <20141223214206.A0C6B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cc510b46b4f6046115cd74acc2c8726c91823bcf/ghc >--------------------------------------------------------------- commit cc510b46b4f6046115cd74acc2c8726c91823bcf Author: Reid Barton Date: Tue Dec 23 16:16:29 2014 -0500 Make ghc -e fail on invalid declarations Summary: Note: This commit includes an API change to GhciMonad.runDecls to allow the caller to determine whether the declarations were run successfully or not. Test Plan: harbormaster Reviewers: austin Reviewed By: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D582 >--------------------------------------------------------------- cc510b46b4f6046115cd74acc2c8726c91823bcf ghc/GhciMonad.hs | 8 +++++--- ghc/InteractiveUI.hs | 6 ++++-- testsuite/tests/ghc-e/should_fail/Makefile | 6 ++++++ testsuite/tests/ghc-e/should_fail/all.T | 6 ++++++ testsuite/tests/ghc-e/should_run/Makefile | 3 +++ testsuite/tests/ghc-e/should_run/all.T | 1 + testsuite/tests/ghc-e/should_run/ghc-e006.stdout | 1 + 7 files changed, 26 insertions(+), 5 deletions(-) diff --git a/ghc/GhciMonad.hs b/ghc/GhciMonad.hs index f57fbba..19b9009 100644 --- a/ghc/GhciMonad.hs +++ b/ghc/GhciMonad.hs @@ -277,15 +277,17 @@ runStmt expr step = do r <- GHC.runStmtWithLocation (progname st) (line_number st) expr step return (Just r) -runDecls :: String -> GHCi [GHC.Name] +runDecls :: String -> GHCi (Maybe [GHC.Name]) runDecls decls = do st <- getGHCiState reifyGHCi $ \x -> withProgName (progname st) $ withArgs (args st) $ reflectGHCi x $ do - GHC.handleSourceError (\e -> do GHC.printException e; return []) $ do - GHC.runDeclsWithLocation (progname st) (line_number st) decls + GHC.handleSourceError (\e -> do GHC.printException e; + return Nothing) $ do + r <- GHC.runDeclsWithLocation (progname st) (line_number st) decls + return (Just r) resume :: (SrcSpan -> Bool) -> GHC.SingleStep -> GHCi GHC.RunResult resume canLogSpan step = do diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index ce73c48..7125f6d 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -915,8 +915,10 @@ runStmt stmt step where run_decl = do _ <- liftIO $ tryIO $ hFlushAll stdin - result <- GhciMonad.runDecls stmt - afterRunStmt (const True) (GHC.RunOk result) + m_result <- GhciMonad.runDecls stmt + case m_result of + Nothing -> return False + Just result -> afterRunStmt (const True) (GHC.RunOk result) run_stmt = do -- In the new IO library, read handles buffer data even if the Handle diff --git a/testsuite/tests/ghc-e/should_fail/Makefile b/testsuite/tests/ghc-e/should_fail/Makefile index 7a02f7b..c0cebcd 100644 --- a/testsuite/tests/ghc-e/should_fail/Makefile +++ b/testsuite/tests/ghc-e/should_fail/Makefile @@ -13,3 +13,9 @@ T9905fail2: T9905fail3: '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "import Prelude (+)" # syntax error + +ghc-e-fail1: + '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "class [" + +ghc-e-fail2: + '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "type A = A" diff --git a/testsuite/tests/ghc-e/should_fail/all.T b/testsuite/tests/ghc-e/should_fail/all.T index 07dc614..bfd4a8a 100644 --- a/testsuite/tests/ghc-e/should_fail/all.T +++ b/testsuite/tests/ghc-e/should_fail/all.T @@ -11,3 +11,9 @@ test('T9905fail2', [exit_code(2), req_interp, ignore_output], run_command, test('T9905fail3', [exit_code(2), req_interp, ignore_output], run_command, ['$MAKE --no-print-directory -s T9905fail3']) + +test('ghc-e-fail1', [exit_code(2), req_interp, ignore_output], run_command, + ['$MAKE --no-print-directory -s ghc-e-fail1']) + +test('ghc-e-fail2', [exit_code(2), req_interp, ignore_output], run_command, + ['$MAKE --no-print-directory -s ghc-e-fail2']) diff --git a/testsuite/tests/ghc-e/should_run/Makefile b/testsuite/tests/ghc-e/should_run/Makefile index aa7041b..54ce8a3 100644 --- a/testsuite/tests/ghc-e/should_run/Makefile +++ b/testsuite/tests/ghc-e/should_run/Makefile @@ -18,6 +18,9 @@ ghc-e004: ghc-e005: '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -main-is foo ghc-e005.hs -e ":set prog ghc-e005-prog" -e ":main [\"the\",\"args\"]"; echo $$? +ghc-e006: + '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "data X = X deriving Show" -e "X" + T2228: '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e ":main" T2228.hs diff --git a/testsuite/tests/ghc-e/should_run/all.T b/testsuite/tests/ghc-e/should_run/all.T index 329ceea..0e6f7f9 100644 --- a/testsuite/tests/ghc-e/should_run/all.T +++ b/testsuite/tests/ghc-e/should_run/all.T @@ -6,6 +6,7 @@ test('ghc-e002', req_interp, run_command, ['$MAKE --no-print-directory -s ghc-e0 test('ghc-e003', req_interp, run_command, ['$MAKE --no-print-directory -s ghc-e003']) test('ghc-e004', req_interp, run_command, ['$MAKE --no-print-directory -s ghc-e004']) test('ghc-e005', req_interp, run_command, ['$MAKE --no-print-directory -s ghc-e005']) +test('ghc-e006', req_interp, run_command, ['$MAKE --no-print-directory -s ghc-e006']) test('T2228', [req_interp, when(ghci_dynamic(), expect_broken(7298))], diff --git a/testsuite/tests/ghc-e/should_run/ghc-e006.stdout b/testsuite/tests/ghc-e/should_run/ghc-e006.stdout new file mode 100644 index 0000000..62d8fe9 --- /dev/null +++ b/testsuite/tests/ghc-e/should_run/ghc-e006.stdout @@ -0,0 +1 @@ +X From git at git.haskell.org Wed Dec 24 00:41:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 24 Dec 2014 00:41:12 +0000 (UTC) Subject: [commit: ghc] master: Fix linker interaction between Template Haskell and HPC (#9762) (3e3aa92) Message-ID: <20141224004112.475223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3e3aa9258b521d362d3a51cb48969df3eeab4981/ghc >--------------------------------------------------------------- commit 3e3aa9258b521d362d3a51cb48969df3eeab4981 Author: Reid Barton Date: Tue Dec 23 16:53:16 2014 -0500 Fix linker interaction between Template Haskell and HPC (#9762) Summary: I'm not really happy about perpetuating the hackish fix for #8696, but at least in the context of building with -fhpc, the performance cost should be negligible. I'm suspicious about PlainModuleInitLabel and the Windows stuff too, but I don't know what it does / can't test it (respectively) so I'll leave those alone for now. Hopefully out-of-process TH will save us from these hacks some day. The test is an adaptation of T8696. It's a bit more awkward since I couldn't think of a way to get cross-module tickbox references without optimizations (inlining), but ghci doesn't permit -O for some reason. Test Plan: harbormaster; validate Reviewers: austin Reviewed By: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D583 GHC Trac Issues: #9762 Conflicts: testsuite/tests/ghci/scripts/all.T >--------------------------------------------------------------- 3e3aa9258b521d362d3a51cb48969df3eeab4981 compiler/cmm/CLabel.hs | 2 +- testsuite/tests/ghci/scripts/Makefile | 3 +++ testsuite/tests/ghci/scripts/T9762.script | 3 +++ testsuite/tests/ghci/scripts/{T8696.stdout => T9762.stdout} | 0 testsuite/tests/ghci/scripts/T9762A.hs | 5 +++++ testsuite/tests/ghci/scripts/T9762B.hs | 4 ++++ testsuite/tests/ghci/scripts/all.T | 2 ++ 7 files changed, 18 insertions(+), 1 deletion(-) diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs index 603f213..ebf902f 100644 --- a/compiler/cmm/CLabel.hs +++ b/compiler/cmm/CLabel.hs @@ -897,7 +897,7 @@ labelDynamic dflags this_pkg this_mod lbl = PlainModuleInitLabel m -> not (gopt Opt_Static dflags) && this_pkg /= (modulePackageKey m) - HpcTicksLabel m -> not (gopt Opt_Static dflags) && this_pkg /= (modulePackageKey m) + HpcTicksLabel m -> not (gopt Opt_Static dflags) && this_mod /= m -- Note that DynamicLinkerLabels do NOT require dynamic linking themselves. _ -> False diff --git a/testsuite/tests/ghci/scripts/Makefile b/testsuite/tests/ghci/scripts/Makefile index 873de43..1ccd62f 100644 --- a/testsuite/tests/ghci/scripts/Makefile +++ b/testsuite/tests/ghci/scripts/Makefile @@ -44,3 +44,6 @@ 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 +.PHONY: T9762_prep +T9762_prep: + '$(TEST_HC)' $(TEST_HC_OPTS) -O -fhpc -dynamic T9762B.hs diff --git a/testsuite/tests/ghci/scripts/T9762.script b/testsuite/tests/ghci/scripts/T9762.script new file mode 100644 index 0000000..c41dbfd --- /dev/null +++ b/testsuite/tests/ghci/scripts/T9762.script @@ -0,0 +1,3 @@ +:load T9762A T9762B +T9762A.a +T9762B.b diff --git a/testsuite/tests/ghci/scripts/T8696.stdout b/testsuite/tests/ghci/scripts/T9762.stdout similarity index 100% copy from testsuite/tests/ghci/scripts/T8696.stdout copy to testsuite/tests/ghci/scripts/T9762.stdout diff --git a/testsuite/tests/ghci/scripts/T9762A.hs b/testsuite/tests/ghci/scripts/T9762A.hs new file mode 100644 index 0000000..cd386ed --- /dev/null +++ b/testsuite/tests/ghci/scripts/T9762A.hs @@ -0,0 +1,5 @@ +module T9762A (a) where +-- By marking a INLINE, we create a reference from B to A's tickboxes. +{-# INLINE a #-} +a :: Int +a = 3 diff --git a/testsuite/tests/ghci/scripts/T9762B.hs b/testsuite/tests/ghci/scripts/T9762B.hs new file mode 100644 index 0000000..387d0e2 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T9762B.hs @@ -0,0 +1,4 @@ +module T9762B (b) where +import T9762A (a) +b :: Int +b = a+1 diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index a78068a..c8462c1 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -193,4 +193,6 @@ test('T9086b', normal, ghci_script, ['T9086b.script']) test('T9140', combined_output, ghci_script, ['T9140.script']) test('T9658', normal, ghci_script, ['T9658.script']) test('T9293', normal, ghci_script_without_flag('-fno-warn-tabs'), ['T9293.script']) +test('T9762', [pre_cmd('$MAKE -s --no-print-directory T9762_prep')], + ghci_script, ['T9762.script']) test('T9881', normal, ghci_script, ['T9881.script']) From git at git.haskell.org Thu Dec 25 22:18:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 25 Dec 2014 22:18:34 +0000 (UTC) Subject: [commit: ghc] master: 2nd attempt to fix T9032 test-case (add6a30) Message-ID: <20141225221834.F37C83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/add6a30317ca7307a91563afbbf102c3771ee246/ghc >--------------------------------------------------------------- commit add6a30317ca7307a91563afbbf102c3771ee246 Author: Herbert Valerio Riedel Date: Thu Dec 25 23:16:28 2014 +0100 2nd attempt to fix T9032 test-case First attempt via 7a2c9dde24b72f wasn't working properly. This attempt should work better as it doesn't cause the makefile recipe to fail which causes `make` to emit additional varying output. >--------------------------------------------------------------- add6a30317ca7307a91563afbbf102c3771ee246 testsuite/tests/rename/should_fail/Makefile | 2 +- testsuite/tests/rename/should_fail/T9032.stderr | 1 - testsuite/tests/rename/should_fail/T9032.stdout | 1 - testsuite/tests/rename/should_fail/all.T | 2 +- 4 files changed, 2 insertions(+), 4 deletions(-) diff --git a/testsuite/tests/rename/should_fail/Makefile b/testsuite/tests/rename/should_fail/Makefile index 037694c..b2393f6 100644 --- a/testsuite/tests/rename/should_fail/Makefile +++ b/testsuite/tests/rename/should_fail/Makefile @@ -4,5 +4,5 @@ include $(TOP)/mk/test.mk T9032: '$(TEST_HC)' $(TEST_HC_OPTS) -c -fforce-recomp T9032.hs - '$(TEST_HC)' $(TEST_HC_OPTS) -c -fforce-recomp -DERR T9032.hs + -'$(TEST_HC)' $(TEST_HC_OPTS) -c -fforce-recomp -DERR T9032.hs diff --git a/testsuite/tests/rename/should_fail/T9032.stderr b/testsuite/tests/rename/should_fail/T9032.stderr index c02dac8..21af9ac 100644 --- a/testsuite/tests/rename/should_fail/T9032.stderr +++ b/testsuite/tests/rename/should_fail/T9032.stderr @@ -1,3 +1,2 @@ T9032.hs:6:1: A module cannot import itself: T9032 -make[3]: *** [T9032] Error 1 diff --git a/testsuite/tests/rename/should_fail/T9032.stdout b/testsuite/tests/rename/should_fail/T9032.stdout deleted file mode 100644 index 82b486f..0000000 --- a/testsuite/tests/rename/should_fail/T9032.stdout +++ /dev/null @@ -1 +0,0 @@ -Makefile:6: recipe for target 'T9032' failed diff --git a/testsuite/tests/rename/should_fail/all.T b/testsuite/tests/rename/should_fail/all.T index 8d60ef3..2aeee2f 100644 --- a/testsuite/tests/rename/should_fail/all.T +++ b/testsuite/tests/rename/should_fail/all.T @@ -129,6 +129,6 @@ test('T9077', normal, compile_fail, ['']) test('T9815', normal, compile_fail, ['']) test('T9032', - exit_code(2), + normal, run_command, ['$MAKE -s --no-print-directory T9032']) From git at git.haskell.org Sat Dec 27 08:12:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 08:12:09 +0000 (UTC) Subject: [commit: ghc] master: Copy GHC's config.guess/sub over libffi's versions (9ae78b0) Message-ID: <20141227081209.E96193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9ae78b0ac20199982b994122889a04c6124e01b2/ghc >--------------------------------------------------------------- commit 9ae78b0ac20199982b994122889a04c6124e01b2 Author: Herbert Valerio Riedel Date: Sat Dec 27 09:11:16 2014 +0100 Copy GHC's config.guess/sub over libffi's versions This should address #9924 as GHC's config.guess/sub versions need to be up to date anyway. >--------------------------------------------------------------- 9ae78b0ac20199982b994122889a04c6124e01b2 libffi/ghc.mk | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/libffi/ghc.mk b/libffi/ghc.mk index ec37f0c..abbe87f 100644 --- a/libffi/ghc.mk +++ b/libffi/ghc.mk @@ -58,6 +58,10 @@ $(libffi_STAMP_CONFIGURE): $(TOUCH_DEP) cat libffi-tarballs/libffi*.tar.gz | $(GZIP_CMD) -d | { cd libffi && $(TAR_CMD) -xf - ; } mv libffi/libffi-* libffi/build +# update config.guess/config.sub + $(CP) "$(TOP)/config.guess" libffi/build/config.guess + $(CP) "$(TOP)/config.sub" libffi/build/config.sub + # We have to fake a non-working ln for configure, so that the fallback # option (cp -p) gets used instead. Otherwise the libffi build system # will use cygwin symbolic links which cannot be read by mingw gcc. From git at git.haskell.org Sat Dec 27 12:12:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 12:12:07 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Test earlier for self-import (Trac #9032) (9e87d8c) Message-ID: <20141227121207.9B3583A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/9e87d8c9d5121db3492f7d8f26b2a7edbba7f03f/ghc >--------------------------------------------------------------- commit 9e87d8c9d5121db3492f7d8f26b2a7edbba7f03f Author: Simon Peyton Jones Date: Tue Dec 23 15:59:30 2014 +0000 Test earlier for self-import (Trac #9032) This patch makes the renamer check for self-import, especially when dependencies change, because the typechecker can fall over if that happens. I'm still uneasy about *indirect* self-import, but I'll leave that for another day (cherry picked from commit edd233acc19d269385c1a870829e0916a3df8e88, 7a2c9dde24b72fe53216881867d5543e5a6f756c, and add6a30317ca7307a91563afbbf102c3771ee246) >--------------------------------------------------------------- 9e87d8c9d5121db3492f7d8f26b2a7edbba7f03f compiler/rename/RnNames.hs | 14 +++++++++++--- testsuite/tests/rename/should_fail/Makefile | 5 +++++ testsuite/tests/rename/should_fail/T9032.hs | 12 ++++++++++++ testsuite/tests/rename/should_fail/T9032.stderr | 2 ++ testsuite/tests/rename/should_fail/all.T | 5 +++++ 5 files changed, 35 insertions(+), 3 deletions(-) diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs index bff2ed0..145d6fc 100644 --- a/compiler/rename/RnNames.hs +++ b/compiler/rename/RnNames.hs @@ -181,6 +181,14 @@ rnImportDecl this_mod let imp_mod_name = unLoc loc_imp_mod_name doc = ppr imp_mod_name <+> ptext (sLit "is directly imported") + -- Check for self-import, which confuses the typechecker (Trac #9032) + -- ghc --make rejects self-import cycles already, but batch-mode may not + -- at least not until TcIface.tcHiBootIface, which is too late to avoid + -- typechecker crashes. ToDo: what about indirect self-import? + -- But 'import {-# SOURCE #-} M' is ok, even if a bit odd + when (not want_boot && imp_mod_name == moduleName this_mod) + (addErr (ptext (sLit "A module cannot import itself:") <+> ppr imp_mod_name)) + -- Check for a missing import list (Opt_WarnMissingImportList also -- checks for T(..) items but that is done in checkDodgyImport below) case imp_details of @@ -212,9 +220,9 @@ rnImportDecl this_mod warnIf (want_boot && any (not.mi_boot) ifaces && isOneShot (ghcMode dflags)) (warnRedundantSourceImport imp_mod_name) when (mod_safe && not (safeImportsOn dflags)) $ - addErrAt loc (ptext (sLit "safe import can't be used as Safe Haskell isn't on!") - $+$ ptext (sLit $ "please enable Safe Haskell through either " - ++ "Safe, Trustworthy or Unsafe")) + addErr (ptext (sLit "safe import can't be used as Safe Haskell isn't on!") + $+$ ptext (sLit $ "please enable Safe Haskell through either " + ++ "Safe, Trustworthy or Unsafe")) let qual_mod_name = as_mod `orElse` imp_mod_name diff --git a/testsuite/tests/rename/should_fail/Makefile b/testsuite/tests/rename/should_fail/Makefile index 9101fbd..b2393f6 100644 --- a/testsuite/tests/rename/should_fail/Makefile +++ b/testsuite/tests/rename/should_fail/Makefile @@ -1,3 +1,8 @@ TOP=../../.. include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/test.mk + +T9032: + '$(TEST_HC)' $(TEST_HC_OPTS) -c -fforce-recomp T9032.hs + -'$(TEST_HC)' $(TEST_HC_OPTS) -c -fforce-recomp -DERR T9032.hs + diff --git a/testsuite/tests/rename/should_fail/T9032.hs b/testsuite/tests/rename/should_fail/T9032.hs new file mode 100644 index 0000000..0a00ba3 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T9032.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE CPP #-} + +module T9032 where + +#ifdef ERR +import T9032 +#endif + +f x = x + + + diff --git a/testsuite/tests/rename/should_fail/T9032.stderr b/testsuite/tests/rename/should_fail/T9032.stderr new file mode 100644 index 0000000..21af9ac --- /dev/null +++ b/testsuite/tests/rename/should_fail/T9032.stderr @@ -0,0 +1,2 @@ + +T9032.hs:6:1: A module cannot import itself: T9032 diff --git a/testsuite/tests/rename/should_fail/all.T b/testsuite/tests/rename/should_fail/all.T index 2798fe9..2aeee2f 100644 --- a/testsuite/tests/rename/should_fail/all.T +++ b/testsuite/tests/rename/should_fail/all.T @@ -127,3 +127,8 @@ test('T9436', normal, compile_fail, ['']) test('T9437', normal, compile_fail, ['']) test('T9077', normal, compile_fail, ['']) test('T9815', normal, compile_fail, ['']) + +test('T9032', + normal, + run_command, + ['$MAKE -s --no-print-directory T9032']) From git at git.haskell.org Sat Dec 27 12:12:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 12:12:10 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Copy GHC's config.guess/sub over libffi's versions (a643559) Message-ID: <20141227121210.425993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/a643559150fa6fe3842beaabc4b20f4edb42a18a/ghc >--------------------------------------------------------------- commit a643559150fa6fe3842beaabc4b20f4edb42a18a Author: Herbert Valerio Riedel Date: Sat Dec 27 09:11:16 2014 +0100 Copy GHC's config.guess/sub over libffi's versions This should address #9924 as GHC's config.guess/sub versions need to be up to date anyway. (cherry picked from commit 9ae78b0ac20199982b994122889a04c6124e01b2) >--------------------------------------------------------------- a643559150fa6fe3842beaabc4b20f4edb42a18a libffi/ghc.mk | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/libffi/ghc.mk b/libffi/ghc.mk index ec37f0c..abbe87f 100644 --- a/libffi/ghc.mk +++ b/libffi/ghc.mk @@ -58,6 +58,10 @@ $(libffi_STAMP_CONFIGURE): $(TOUCH_DEP) cat libffi-tarballs/libffi*.tar.gz | $(GZIP_CMD) -d | { cd libffi && $(TAR_CMD) -xf - ; } mv libffi/libffi-* libffi/build +# update config.guess/config.sub + $(CP) "$(TOP)/config.guess" libffi/build/config.guess + $(CP) "$(TOP)/config.sub" libffi/build/config.sub + # We have to fake a non-working ln for configure, so that the fallback # option (cp -p) gets used instead. Otherwise the libffi build system # will use cygwin symbolic links which cannot be read by mingw gcc. From git at git.haskell.org Sat Dec 27 12:12:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 12:12:12 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Make ghc -e not exit on valid import commands (#9905) (4566852) Message-ID: <20141227121212.EAE143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/45668525c0f100d4ac7f55eec744ca3ac00c304c/ghc >--------------------------------------------------------------- commit 45668525c0f100d4ac7f55eec744ca3ac00c304c Author: Reid Barton Date: Tue Dec 23 15:22:01 2014 -0500 Make ghc -e not exit on valid import commands (#9905) Some Trues and Falses were mixed up due to Bool being used in different senses in different parts of GHCi. (cherry picked from commit 878910e1c4520732ab9d8372c1c81f00d484e48f) >--------------------------------------------------------------- 45668525c0f100d4ac7f55eec744ca3ac00c304c ghc/GhciMonad.hs | 1 + ghc/InteractiveUI.hs | 22 ++++++++++++++-------- testsuite/tests/ghc-e/should_fail/Makefile | 9 +++++++++ testsuite/tests/ghc-e/should_fail/all.T | 12 +++++++++++- testsuite/tests/ghc-e/should_run/Makefile | 6 ++++++ testsuite/tests/ghc-e/should_run/T9905.stdout | 1 + testsuite/tests/ghc-e/should_run/T9905b.stdout | 1 + testsuite/tests/ghc-e/should_run/all.T | 2 ++ 8 files changed, 45 insertions(+), 9 deletions(-) diff --git a/ghc/GhciMonad.hs b/ghc/GhciMonad.hs index 89c2028..f57fbba 100644 --- a/ghc/GhciMonad.hs +++ b/ghc/GhciMonad.hs @@ -63,6 +63,7 @@ import Control.Applicative (Applicative(..)) ----------------------------------------------------------------------------- -- GHCi monad +-- the Bool means: True = we should exit GHCi (:quit) type Command = (String, String -> InputT GHCi Bool, CompletionFunc GHCi) data GHCiState = GHCiState diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index d478336..ce73c48 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -729,7 +729,11 @@ runCommands' eh sourceErrorHandler gCmd = do when (not success) $ maybe (return ()) lift sourceErrorHandler runCommands' eh sourceErrorHandler gCmd --- | Evaluate a single line of user input (either : or Haskell code) +-- | Evaluate a single line of user input (either : or Haskell code). +-- A result of Nothing means there was no more input to process. +-- Otherwise the result is Just b where b is True if the command succeeded; +-- this is relevant only to ghc -e, which will exit with status 1 +-- if the commmand was unsuccessful. GHCi will continue in either case. runOneCommand :: (SomeException -> GHCi Bool) -> InputT GHCi (Maybe String) -> InputT GHCi (Maybe Bool) runOneCommand eh gCmd = do @@ -740,14 +744,14 @@ runOneCommand eh gCmd = do case mb_cmd1 of Nothing -> return Nothing Just c -> ghciHandle (\e -> lift $ eh e >>= return . Just) $ - handleSourceError printErrorAndKeepGoing + handleSourceError printErrorAndFail (doCommand c) -- source error's are handled by runStmt -- is the handler necessary here? where - printErrorAndKeepGoing err = do + printErrorAndFail err = do GHC.printException err - return $ Just True + return $ Just False -- Exit ghc -e, but not GHCi noSpace q = q >>= maybe (return Nothing) (\c -> case removeSpaces c of @@ -890,16 +894,18 @@ declPrefixes dflags = keywords ++ concat opt_keywords , ["deriving " | xopt Opt_StandaloneDeriving dflags] ] --- | Entry point to execute some haskell code from user +-- | Entry point to execute some haskell code from user. +-- The return value True indicates success, as in `runOneCommand`. runStmt :: String -> SingleStep -> GHCi Bool runStmt stmt step - -- empty + -- empty; this should be impossible anyways since we filtered out + -- whitespace-only input in runOneCommand's noSpace | null (filter (not.isSpace) stmt) - = return False + = return True -- import | stmt `looks_like` "import " - = do addImportToContext stmt; return False + = do addImportToContext stmt; return True | otherwise = do dflags <- getDynFlags diff --git a/testsuite/tests/ghc-e/should_fail/Makefile b/testsuite/tests/ghc-e/should_fail/Makefile index 5b0d753..7a02f7b 100644 --- a/testsuite/tests/ghc-e/should_fail/Makefile +++ b/testsuite/tests/ghc-e/should_fail/Makefile @@ -4,3 +4,12 @@ include $(TOP)/mk/test.mk T7962: '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "return (" + +T9905fail1: + '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "import This.Module.Does.Not.Exist" + +T9905fail2: + '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "import Data.List (bogusIdentifier)" + +T9905fail3: + '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "import Prelude (+)" # syntax error diff --git a/testsuite/tests/ghc-e/should_fail/all.T b/testsuite/tests/ghc-e/should_fail/all.T index 4c5ac5c..07dc614 100644 --- a/testsuite/tests/ghc-e/should_fail/all.T +++ b/testsuite/tests/ghc-e/should_fail/all.T @@ -1,3 +1,13 @@ setTestOpts(when(compiler_profiled(), skip)) -test('T7962', [exit_code(2), req_interp, ignore_output], run_command, ['$MAKE --no-print-directory -s T7962']) +test('T7962', [exit_code(2), req_interp, ignore_output], run_command, + ['$MAKE --no-print-directory -s T7962']) + +test('T9905fail1', [exit_code(2), req_interp, ignore_output], run_command, + ['$MAKE --no-print-directory -s T9905fail1']) + +test('T9905fail2', [exit_code(2), req_interp, ignore_output], run_command, + ['$MAKE --no-print-directory -s T9905fail2']) + +test('T9905fail3', [exit_code(2), req_interp, ignore_output], run_command, + ['$MAKE --no-print-directory -s T9905fail3']) diff --git a/testsuite/tests/ghc-e/should_run/Makefile b/testsuite/tests/ghc-e/should_run/Makefile index 5ed1ec2..aa7041b 100644 --- a/testsuite/tests/ghc-e/should_run/Makefile +++ b/testsuite/tests/ghc-e/should_run/Makefile @@ -32,3 +32,9 @@ T7299: T9086: '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e ":main" T9086.hs + +T9905: + '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "import Data.List" -e "sort [2,1]" + +T9905b: + '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "import qualified Data.List as L" -e "L.sort [2,1]" diff --git a/testsuite/tests/ghc-e/should_run/T9905.stdout b/testsuite/tests/ghc-e/should_run/T9905.stdout new file mode 100644 index 0000000..6ed63af --- /dev/null +++ b/testsuite/tests/ghc-e/should_run/T9905.stdout @@ -0,0 +1 @@ +[1,2] diff --git a/testsuite/tests/ghc-e/should_run/T9905b.stdout b/testsuite/tests/ghc-e/should_run/T9905b.stdout new file mode 100644 index 0000000..6ed63af --- /dev/null +++ b/testsuite/tests/ghc-e/should_run/T9905b.stdout @@ -0,0 +1 @@ +[1,2] diff --git a/testsuite/tests/ghc-e/should_run/all.T b/testsuite/tests/ghc-e/should_run/all.T index 9f64918..329ceea 100644 --- a/testsuite/tests/ghc-e/should_run/all.T +++ b/testsuite/tests/ghc-e/should_run/all.T @@ -15,3 +15,5 @@ test('T2636', req_interp, run_command, ['$MAKE --no-print-directory -s T2636']) test('T3890', req_interp, run_command, ['$MAKE --no-print-directory -s T3890']) test('T7299', req_interp, run_command, ['$MAKE --no-print-directory -s T7299']) test('T9086', req_interp, run_command, ['$MAKE --no-print-directory -s T9086']) +test('T9905', req_interp, run_command, ['$MAKE --no-print-directory -s T9905']) +test('T9905b', req_interp, run_command, ['$MAKE --no-print-directory -s T9905b']) From git at git.haskell.org Sat Dec 27 12:12:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 12:12:16 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix linker interaction between Template Haskell and HPC (#9762) (3afe35d) Message-ID: <20141227121216.115973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/3afe35d13daa3c18fc8cc4d8bfd2294d1f6c7d8d/ghc >--------------------------------------------------------------- commit 3afe35d13daa3c18fc8cc4d8bfd2294d1f6c7d8d Author: Reid Barton Date: Tue Dec 23 16:53:16 2014 -0500 Fix linker interaction between Template Haskell and HPC (#9762) I'm not really happy about perpetuating the hackish fix for #8696, but at least in the context of building with -fhpc, the performance cost should be negligible. I'm suspicious about PlainModuleInitLabel and the Windows stuff too, but I don't know what it does / can't test it (respectively) so I'll leave those alone for now. Hopefully out-of-process TH will save us from these hacks some day. The test is an adaptation of T8696. It's a bit more awkward since I couldn't think of a way to get cross-module tickbox references without optimizations (inlining), but ghci doesn't permit -O for some reason. (cherry picked from commit 3e3aa9258b521d362d3a51cb48969df3eeab4981) >--------------------------------------------------------------- 3afe35d13daa3c18fc8cc4d8bfd2294d1f6c7d8d compiler/cmm/CLabel.hs | 2 +- testsuite/tests/ghci/scripts/Makefile | 3 +++ testsuite/tests/ghci/scripts/T9762.script | 3 +++ testsuite/tests/ghci/scripts/{T8696.stdout => T9762.stdout} | 0 testsuite/tests/ghci/scripts/T9762A.hs | 5 +++++ testsuite/tests/ghci/scripts/T9762B.hs | 4 ++++ testsuite/tests/ghci/scripts/all.T | 2 ++ 7 files changed, 18 insertions(+), 1 deletion(-) diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs index 603f213..ebf902f 100644 --- a/compiler/cmm/CLabel.hs +++ b/compiler/cmm/CLabel.hs @@ -897,7 +897,7 @@ labelDynamic dflags this_pkg this_mod lbl = PlainModuleInitLabel m -> not (gopt Opt_Static dflags) && this_pkg /= (modulePackageKey m) - HpcTicksLabel m -> not (gopt Opt_Static dflags) && this_pkg /= (modulePackageKey m) + HpcTicksLabel m -> not (gopt Opt_Static dflags) && this_mod /= m -- Note that DynamicLinkerLabels do NOT require dynamic linking themselves. _ -> False diff --git a/testsuite/tests/ghci/scripts/Makefile b/testsuite/tests/ghci/scripts/Makefile index 873de43..1ccd62f 100644 --- a/testsuite/tests/ghci/scripts/Makefile +++ b/testsuite/tests/ghci/scripts/Makefile @@ -44,3 +44,6 @@ 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 +.PHONY: T9762_prep +T9762_prep: + '$(TEST_HC)' $(TEST_HC_OPTS) -O -fhpc -dynamic T9762B.hs diff --git a/testsuite/tests/ghci/scripts/T9762.script b/testsuite/tests/ghci/scripts/T9762.script new file mode 100644 index 0000000..c41dbfd --- /dev/null +++ b/testsuite/tests/ghci/scripts/T9762.script @@ -0,0 +1,3 @@ +:load T9762A T9762B +T9762A.a +T9762B.b diff --git a/testsuite/tests/ghci/scripts/T8696.stdout b/testsuite/tests/ghci/scripts/T9762.stdout similarity index 100% copy from testsuite/tests/ghci/scripts/T8696.stdout copy to testsuite/tests/ghci/scripts/T9762.stdout diff --git a/testsuite/tests/ghci/scripts/T9762A.hs b/testsuite/tests/ghci/scripts/T9762A.hs new file mode 100644 index 0000000..cd386ed --- /dev/null +++ b/testsuite/tests/ghci/scripts/T9762A.hs @@ -0,0 +1,5 @@ +module T9762A (a) where +-- By marking a INLINE, we create a reference from B to A's tickboxes. +{-# INLINE a #-} +a :: Int +a = 3 diff --git a/testsuite/tests/ghci/scripts/T9762B.hs b/testsuite/tests/ghci/scripts/T9762B.hs new file mode 100644 index 0000000..387d0e2 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T9762B.hs @@ -0,0 +1,4 @@ +module T9762B (b) where +import T9762A (a) +b :: Int +b = a+1 diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index a78068a..c8462c1 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -193,4 +193,6 @@ test('T9086b', normal, ghci_script, ['T9086b.script']) test('T9140', combined_output, ghci_script, ['T9140.script']) test('T9658', normal, ghci_script, ['T9658.script']) test('T9293', normal, ghci_script_without_flag('-fno-warn-tabs'), ['T9293.script']) +test('T9762', [pre_cmd('$MAKE -s --no-print-directory T9762_prep')], + ghci_script, ['T9762.script']) test('T9881', normal, ghci_script, ['T9881.script']) From git at git.haskell.org Sat Dec 27 15:00:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 15:00:46 +0000 (UTC) Subject: [commit: ghc] master: Run T9762 only if dynamic libraries are available (1dcef98) Message-ID: <20141227150046.523063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1dcef98a77afa0f9dc73896b8d8cc7444e2e0039/ghc >--------------------------------------------------------------- commit 1dcef98a77afa0f9dc73896b8d8cc7444e2e0039 Author: Joachim Breitner Date: Sat Dec 27 16:01:54 2014 +0100 Run T9762 only if dynamic libraries are available >--------------------------------------------------------------- 1dcef98a77afa0f9dc73896b8d8cc7444e2e0039 testsuite/tests/ghci/scripts/all.T | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index c8462c1..3e2ea77 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -193,6 +193,9 @@ test('T9086b', normal, ghci_script, ['T9086b.script']) test('T9140', combined_output, ghci_script, ['T9140.script']) test('T9658', normal, ghci_script, ['T9658.script']) test('T9293', normal, ghci_script_without_flag('-fno-warn-tabs'), ['T9293.script']) -test('T9762', [pre_cmd('$MAKE -s --no-print-directory T9762_prep')], - ghci_script, ['T9762.script']) +test('T9762', + [ unless(have_dynamic(),skip) + , pre_cmd('$MAKE -s --no-print-directory T9762_prep') + ], + ghci_script, ['T9762.script']) test('T9881', normal, ghci_script, ['T9881.script']) From git at git.haskell.org Sat Dec 27 15:09:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 15:09:46 +0000 (UTC) Subject: [commit: ghc] master: We do emit a warning for stdcall now. (c0ab767) Message-ID: <20141227150946.31FA83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c0ab76744c6b3397ac56192b320ff63e5b029c54/ghc >--------------------------------------------------------------- commit c0ab76744c6b3397ac56192b320ff63e5b029c54 Author: Edward Z. Yang Date: Sat Dec 27 10:10:37 2014 -0500 We do emit a warning for stdcall now. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- c0ab76744c6b3397ac56192b320ff63e5b029c54 compiler/prelude/ForeignCall.hs | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/compiler/prelude/ForeignCall.hs b/compiler/prelude/ForeignCall.hs index 0a7a838..9afc249 100644 --- a/compiler/prelude/ForeignCall.hs +++ b/compiler/prelude/ForeignCall.hs @@ -138,11 +138,7 @@ ccall: Caller allocates parameters, *and* deallocates them. stdcall: Caller allocates parameters, callee deallocates. Function name has @N after it, where N is number of arg bytes - e.g. _Foo at 8 - -ToDo: The stdcall calling convention is x86 (win32) specific, -so perhaps we should emit a warning if it's being used on other -platforms. + e.g. _Foo at 8. This convention is x86 (win32) specific. See: http://www.programmersheaven.com/2/Calling-conventions -} From git at git.haskell.org Sat Dec 27 15:56:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 15:56:59 +0000 (UTC) Subject: [commit: ghc] master: Use directory-style database for bootstrapping database (0899caa) Message-ID: <20141227155659.280BE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0899caab400e7a095528ea769a7e93a33717ae72/ghc >--------------------------------------------------------------- commit 0899caab400e7a095528ea769a7e93a33717ae72 Author: Edward Z. Yang Date: Sat Dec 27 10:57:30 2014 -0500 Use directory-style database for bootstrapping database Summary: This allows GHC HEAD to be bootstrapped using 7.10. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D589 GHC Trac Issues: #9652 >--------------------------------------------------------------- 0899caab400e7a095528ea769a7e93a33717ae72 ghc.mk | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.mk b/ghc.mk index 6c587bd..0322ba6 100644 --- a/ghc.mk +++ b/ghc.mk @@ -726,7 +726,7 @@ ifneq "$(BINDIST)" "YES" ifneq "$(BOOTSTRAPPING_CONF)" "" ifeq "$(wildcard $(BOOTSTRAPPING_CONF))" "" -$(shell echo "[]" >$(BOOTSTRAPPING_CONF)) +$(shell $(GHC_PKG) init $(BOOTSTRAPPING_CONF)) endif endif @@ -1233,7 +1233,6 @@ sdist_%: .PHONY: clean -CLEAN_FILES += libraries/bootstrapping.conf CLEAN_FILES += libraries/integer-gmp/cbits/GmpDerivedConstants.h CLEAN_FILES += libraries/integer-gmp/include/HsIntegerGmp.h CLEAN_FILES += libraries/integer-gmp2/include/HsIntegerGmp.h @@ -1262,6 +1261,7 @@ clean_files : $(call removeTrees,includes/dist-derivedconstants) $(call removeTrees,inplace/bin) $(call removeTrees,inplace/lib) + $(call removeTrees,libraries/bootstrapping.conf) .PHONY: clean_libraries clean_libraries: $(patsubst %,clean_libraries/%_dist-install,$(PACKAGES_STAGE1) $(PACKAGES_STAGE2)) From git at git.haskell.org Sat Dec 27 16:01:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 16:01:57 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Use directory-style database for bootstrapping database (a96eb1c) Message-ID: <20141227160157.859893A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/a96eb1c80a772ea11e2d1def129e5766e7bb7c98/ghc >--------------------------------------------------------------- commit a96eb1c80a772ea11e2d1def129e5766e7bb7c98 Author: Edward Z. Yang Date: Sat Dec 27 10:57:30 2014 -0500 Use directory-style database for bootstrapping database This allows GHC HEAD to be bootstrapped using 7.10. Addresses #9652 Signed-off-by: Edward Z. Yang (cherry picked from commit 0899caab400e7a095528ea769a7e93a33717ae72) >--------------------------------------------------------------- a96eb1c80a772ea11e2d1def129e5766e7bb7c98 ghc.mk | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.mk b/ghc.mk index 6c587bd..0322ba6 100644 --- a/ghc.mk +++ b/ghc.mk @@ -726,7 +726,7 @@ ifneq "$(BINDIST)" "YES" ifneq "$(BOOTSTRAPPING_CONF)" "" ifeq "$(wildcard $(BOOTSTRAPPING_CONF))" "" -$(shell echo "[]" >$(BOOTSTRAPPING_CONF)) +$(shell $(GHC_PKG) init $(BOOTSTRAPPING_CONF)) endif endif @@ -1233,7 +1233,6 @@ sdist_%: .PHONY: clean -CLEAN_FILES += libraries/bootstrapping.conf CLEAN_FILES += libraries/integer-gmp/cbits/GmpDerivedConstants.h CLEAN_FILES += libraries/integer-gmp/include/HsIntegerGmp.h CLEAN_FILES += libraries/integer-gmp2/include/HsIntegerGmp.h @@ -1262,6 +1261,7 @@ clean_files : $(call removeTrees,includes/dist-derivedconstants) $(call removeTrees,inplace/bin) $(call removeTrees,inplace/lib) + $(call removeTrees,libraries/bootstrapping.conf) .PHONY: clean_libraries clean_libraries: $(patsubst %,clean_libraries/%_dist-install,$(PACKAGES_STAGE1) $(PACKAGES_STAGE2)) From git at git.haskell.org Sat Dec 27 18:12:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 18:12:28 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Run T9762 only if dynamic libraries are available (62a6d14) Message-ID: <20141227181228.A34433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/62a6d14be0076da0adb3524e5ef70352beb4ee13/ghc >--------------------------------------------------------------- commit 62a6d14be0076da0adb3524e5ef70352beb4ee13 Author: Joachim Breitner Date: Sat Dec 27 16:01:54 2014 +0100 Run T9762 only if dynamic libraries are available (cherry picked from commit 1dcef98a77afa0f9dc73896b8d8cc7444e2e0039) >--------------------------------------------------------------- 62a6d14be0076da0adb3524e5ef70352beb4ee13 testsuite/tests/ghci/scripts/all.T | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index c8462c1..3e2ea77 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -193,6 +193,9 @@ test('T9086b', normal, ghci_script, ['T9086b.script']) test('T9140', combined_output, ghci_script, ['T9140.script']) test('T9658', normal, ghci_script, ['T9658.script']) test('T9293', normal, ghci_script_without_flag('-fno-warn-tabs'), ['T9293.script']) -test('T9762', [pre_cmd('$MAKE -s --no-print-directory T9762_prep')], - ghci_script, ['T9762.script']) +test('T9762', + [ unless(have_dynamic(),skip) + , pre_cmd('$MAKE -s --no-print-directory T9762_prep') + ], + ghci_script, ['T9762.script']) test('T9881', normal, ghci_script, ['T9881.script']) From git at git.haskell.org Sat Dec 27 22:24:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 22:24:13 +0000 (UTC) Subject: [commit: hsc2hs] master: M-x untabify & M-x delete-trailing-whitespace (7fa9c38) Message-ID: <20141227222413.CA1663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hsc2hs On branch : master Link : http://git.haskell.org/hsc2hs.git/commitdiff/7fa9c384bbc3546315bf5af45590b64ca550b7ce >--------------------------------------------------------------- commit 7fa9c384bbc3546315bf5af45590b64ca550b7ce Author: Herbert Valerio Riedel Date: Sat Dec 27 23:21:44 2014 +0100 M-x untabify & M-x delete-trailing-whitespace >--------------------------------------------------------------- 7fa9c384bbc3546315bf5af45590b64ca550b7ce C.hs | 25 ++++++++++++------------- Common.hs | 1 - DirectCodegen.hs | 3 +-- 3 files changed, 13 insertions(+), 16 deletions(-) diff --git a/C.hs b/C.hs index 11d31f2..c6a7e5e 100644 --- a/C.hs +++ b/C.hs @@ -152,18 +152,18 @@ outTokenC (pos, key, arg) = 's':'t':'r':'u':'c':'t':' ':_ -> "" 't':'y':'p':'e':'d':'e':'f':' ':_ -> "" 'i':'n':'l':'i':'n':'e':' ':arg' -> - case span (\c -> c /= '{' && c /= '=') arg' of - (header, body) -> - outCLine pos++ - "#ifndef __GNUC__\n" ++ - "extern inline\n" ++ - "#endif\n"++ - header++ - "\n#ifndef __GNUC__\n" ++ - ";\n" ++ - "#else\n"++ - body++ - "\n#endif\n" + case span (\c -> c /= '{' && c /= '=') arg' of + (header, body) -> + outCLine pos++ + "#ifndef __GNUC__\n" ++ + "extern inline\n" ++ + "#endif\n"++ + header++ + "\n#ifndef __GNUC__\n" ++ + ";\n" ++ + "#else\n"++ + body++ + "\n#endif\n" _ -> outCLine pos++arg++"\n" _ | conditional key -> outCLine pos++"#"++key++" "++arg++"\n" _ -> "" @@ -207,4 +207,3 @@ showCString = concatMap showCChar intToDigit (ord c `quot` 64), intToDigit (ord c `quot` 8 `mod` 8), intToDigit (ord c `mod` 8)] - diff --git a/Common.hs b/Common.hs index 7b33093..ae11241 100644 --- a/Common.hs +++ b/Common.hs @@ -66,4 +66,3 @@ catchIO = Exception.catch onlyOne :: String -> IO a onlyOne what = die ("Only one "++what++" may be specified\n") - diff --git a/DirectCodegen.hs b/DirectCodegen.hs index 42b31a5..c6f428d 100644 --- a/DirectCodegen.hs +++ b/DirectCodegen.hs @@ -31,7 +31,7 @@ outputDirect config outName outDir outBase name toks = do -- via GHC has changed a few times, so this seems to be the only way... :-P * * * ++ ".exe" #endif - outHFile = outBase++"_hsc.h" + outHFile = outBase++"_hsc.h" outHName = outDir++outHFile outCName = outDir++outBase++"_hsc.c" @@ -107,4 +107,3 @@ outputDirect config outName outDir outBase name toks = do concatMap outTokenC specials -- NB. outHFile not outHName; works better when processed -- by gcc or mkdependC. - From git at git.haskell.org Sat Dec 27 22:24:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 22:24:15 +0000 (UTC) Subject: [commit: hsc2hs] master: Update .cabal file and LANGUAGE pragmas (546438f) Message-ID: <20141227222415.CF4FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hsc2hs On branch : master Link : http://git.haskell.org/hsc2hs.git/commitdiff/546438f93f8eb11da6b9279374552cfd86499253 >--------------------------------------------------------------- commit 546438f93f8eb11da6b9279374552cfd86499253 Author: Herbert Valerio Riedel Date: Sat Dec 27 23:22:17 2014 +0100 Update .cabal file and LANGUAGE pragmas >--------------------------------------------------------------- 546438f93f8eb11da6b9279374552cfd86499253 C.hs | 1 - Common.hs | 1 - Main.hs | 3 +-- UtilsCodegen.hs | 1 - hsc2hs.cabal | 24 ++++++++++++------------ 5 files changed, 13 insertions(+), 17 deletions(-) diff --git a/C.hs b/C.hs index c6a7e5e..dd02f43 100644 --- a/C.hs +++ b/C.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} module C where {- diff --git a/Common.hs b/Common.hs index ae11241..fefc40c 100644 --- a/Common.hs +++ b/Common.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} module Common where import Control.Exception ( bracket_ ) diff --git a/Main.hs b/Main.hs index 30b3a2d..afa192e 100644 --- a/Main.hs +++ b/Main.hs @@ -1,5 +1,4 @@ -{-# OPTIONS -cpp #-} -{-# LANGUAGE CPP, ForeignFunctionInterface #-} +{-# LANGUAGE CPP #-} ------------------------------------------------------------------------ -- Program for converting .hsc files to .hs files, by converting the diff --git a/UtilsCodegen.hs b/UtilsCodegen.hs index 8844052..19befd2 100644 --- a/UtilsCodegen.hs +++ b/UtilsCodegen.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} module UtilsCodegen where {- diff --git a/hsc2hs.cabal b/hsc2hs.cabal index 2eee52a..6dfa7c4 100644 --- a/hsc2hs.cabal +++ b/hsc2hs.cabal @@ -1,7 +1,6 @@ Name: hsc2hs Version: 0.67 Copyright: 2000, Marcin Kowalczyk -Build-Depends: base, directory, process License: BSD3 License-File: LICENSE Author: Marcin Kowalczyk @@ -21,20 +20,21 @@ Description: Category: Development Data-Files: template-hsc.h build-type: Simple -cabal-version: >=1.2 +cabal-version: >=1.10 Executable hsc2hs + Default-Language: Haskell2010 Main-Is: Main.hs - Other-Modules: HSCParser, - DirectCodegen, - CrossCodegen, - UtilsCodegen, - Common, - C, - Flags - -- needed for ReadP (used by Data.Version) - Hugs-Options: -98 - Extensions: CPP, ForeignFunctionInterface + Other-Modules: + C + Common + CrossCodegen + DirectCodegen + Flags + HSCParser + UtilsCodegen + + Other-Extensions: CPP, NoMonomorphismRestriction Build-Depends: base >= 4 && < 5, containers >= 0.2 && < 0.6, From git at git.haskell.org Sat Dec 27 22:39:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 22:39:02 +0000 (UTC) Subject: [commit: ghc] master: Update hsc2hs submodule for de-tabbing (bd01af9) Message-ID: <20141227223902.9ACAB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bd01af9af1120731f38396ce61767b03e0983317/ghc >--------------------------------------------------------------- commit bd01af9af1120731f38396ce61767b03e0983317 Author: Herbert Valerio Riedel Date: Sat Dec 27 23:39:18 2014 +0100 Update hsc2hs submodule for de-tabbing >--------------------------------------------------------------- bd01af9af1120731f38396ce61767b03e0983317 mk/validate-settings.mk | 1 - utils/hsc2hs | 2 +- 2 files changed, 1 insertion(+), 2 deletions(-) diff --git a/mk/validate-settings.mk b/mk/validate-settings.mk index 351ea83..4b0e3a7 100644 --- a/mk/validate-settings.mk +++ b/mk/validate-settings.mk @@ -187,4 +187,3 @@ GhcBootLibHcOpts += -fno-warn-deprecated-flags # for details # GhcLibHcOpts += -fno-warn-tabs -utils/hsc2hs_dist-install_EXTRA_HC_OPTS += -fno-warn-tabs diff --git a/utils/hsc2hs b/utils/hsc2hs index 10696fe..546438f 160000 --- a/utils/hsc2hs +++ b/utils/hsc2hs @@ -1 +1 @@ -Subproject commit 10696fe17c9d2b4e3498684c6ffbd9f44eda53c4 +Subproject commit 546438f93f8eb11da6b9279374552cfd86499253 From git at git.haskell.org Sat Dec 27 22:44:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 22:44:01 +0000 (UTC) Subject: [commit: ghc] master: Avoid redundant-import warning (w/o CPP) (c55fefc) Message-ID: <20141227224401.52D183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c55fefc0f25ecd754db3f274cba3f972d603f117/ghc >--------------------------------------------------------------- commit c55fefc0f25ecd754db3f274cba3f972d603f117 Author: Herbert Valerio Riedel Date: Sat Dec 27 23:43:20 2014 +0100 Avoid redundant-import warning (w/o CPP) >--------------------------------------------------------------- c55fefc0f25ecd754db3f274cba3f972d603f117 utils/genprimopcode/ParserM.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/utils/genprimopcode/ParserM.hs b/utils/genprimopcode/ParserM.hs index 4dedfa3..190ec0e 100644 --- a/utils/genprimopcode/ParserM.hs +++ b/utils/genprimopcode/ParserM.hs @@ -16,7 +16,10 @@ module ParserM ( -- Other happyError ) where + import Control.Applicative +import Prelude + import Control.Monad (ap, liftM) import Data.Word (Word8) import Data.Char (ord) From git at git.haskell.org Sat Dec 27 22:45:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 22:45:54 +0000 (UTC) Subject: [commit: packages/hpc] master: M-x untabify & M-x delete-trailing-whitespace (a071321) Message-ID: <20141227224554.69CB03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : master Link : http://git.haskell.org/packages/hpc.git/commitdiff/a071321d33188fb958f42e36778464617c56cfb9 >--------------------------------------------------------------- commit a071321d33188fb958f42e36778464617c56cfb9 Author: Herbert Valerio Riedel Date: Sat Dec 27 23:46:22 2014 +0100 M-x untabify & M-x delete-trailing-whitespace >--------------------------------------------------------------- a071321d33188fb958f42e36778464617c56cfb9 Trace/Hpc/Reflect.hsc | 33 ++++++++++++++++----------------- 1 file changed, 16 insertions(+), 17 deletions(-) diff --git a/Trace/Hpc/Reflect.hsc b/Trace/Hpc/Reflect.hsc index 16b27ca..fe30624 100644 --- a/Trace/Hpc/Reflect.hsc +++ b/Trace/Hpc/Reflect.hsc @@ -39,25 +39,25 @@ moduleInfoList ptr tickCount <- (#peek HpcModuleInfo, tickCount) ptr hashNo <- (#peek HpcModuleInfo, hashNo) ptr tixArr <- (#peek HpcModuleInfo, tixArr) ptr - next <- (#peek HpcModuleInfo, next) ptr + next <- (#peek HpcModuleInfo, next) ptr rest <- moduleInfoList next return $ ModuleInfo modName tickCount (toHash (hashNo :: Int)) tixArr : rest clearTix :: IO () clearTix = do sequence_ [ pokeArray ptr $ take (fromIntegral count) $ repeat 0 - | ModuleInfo _mod count _hash ptr <- modInfo - ] + | ModuleInfo _mod count _hash ptr <- modInfo + ] return () examineTix :: IO Tix examineTix = do mods <- sequence [ do tixs <- peekArray (fromIntegral count) ptr - return $ TixModule mod' hash (fromIntegral count) - $ map fromIntegral tixs - | (ModuleInfo mod' count hash ptr) <- modInfo - ] + return $ TixModule mod' hash (fromIntegral count) + $ map fromIntegral tixs + | (ModuleInfo mod' count hash ptr) <- modInfo + ] return $ Tix mods -- requirement that the tix be of the same shape as the @@ -67,14 +67,13 @@ updateTix (Tix modTixes) | length modTixes /= length modInfo = error "updateTix failed" | otherwise = do sequence_ [ pokeArray ptr $ map fromIntegral tixs - | (ModuleInfo mod1 count1 hash1 ptr, - TixModule mod2 hash2 count2 tixs) <- zip modInfo modTixes - , if mod1 /= mod2 - || (fromIntegral count1) /= count2 - || hash1 /= hash2 - || length tixs /= count2 - then error "updateTix failed" - else True - ] + | (ModuleInfo mod1 count1 hash1 ptr, + TixModule mod2 hash2 count2 tixs) <- zip modInfo modTixes + , if mod1 /= mod2 + || (fromIntegral count1) /= count2 + || hash1 /= hash2 + || length tixs /= count2 + then error "updateTix failed" + else True + ] return () - From git at git.haskell.org Sat Dec 27 22:47:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 22:47:56 +0000 (UTC) Subject: [commit: packages/hoopl] master: avoid redundant import warnings (d39ddd9) Message-ID: <20141227224756.EB83B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hoopl On branch : master Link : http://git.haskell.org/packages/hoopl.git/commitdiff/d39ddd928e0d691ee571768a613fd10f6f951a40 >--------------------------------------------------------------- commit d39ddd928e0d691ee571768a613fd10f6f951a40 Author: Herbert Valerio Riedel Date: Sat Dec 27 23:48:29 2014 +0100 avoid redundant import warnings >--------------------------------------------------------------- d39ddd928e0d691ee571768a613fd10f6f951a40 src/Compiler/Hoopl/Fuel.hs | 2 ++ src/Compiler/Hoopl/Graph.hs | 2 ++ src/Compiler/Hoopl/Unique.hs | 2 ++ 3 files changed, 6 insertions(+) diff --git a/src/Compiler/Hoopl/Fuel.hs b/src/Compiler/Hoopl/Fuel.hs index 3811f32..d6b042e 100644 --- a/src/Compiler/Hoopl/Fuel.hs +++ b/src/Compiler/Hoopl/Fuel.hs @@ -21,7 +21,9 @@ where import Compiler.Hoopl.Checkpoint import Compiler.Hoopl.Unique +#if !MIN_VERSION_base(4,8,0) import Control.Applicative (Applicative(..)) +#endif import Control.Monad (ap,liftM) class Monad m => FuelMonad m where diff --git a/src/Compiler/Hoopl/Graph.hs b/src/Compiler/Hoopl/Graph.hs index b553648..79fbfbb 100644 --- a/src/Compiler/Hoopl/Graph.hs +++ b/src/Compiler/Hoopl/Graph.hs @@ -46,7 +46,9 @@ import Compiler.Hoopl.Collections import Compiler.Hoopl.Block import Compiler.Hoopl.Label +#if !MIN_VERSION_base(4,8,0) import Control.Applicative (Applicative(..)) +#endif import Control.Monad (ap,liftM,liftM2) -- ----------------------------------------------------------------------------- diff --git a/src/Compiler/Hoopl/Unique.hs b/src/Compiler/Hoopl/Unique.hs index 0e88fb4..42e2b23 100644 --- a/src/Compiler/Hoopl/Unique.hs +++ b/src/Compiler/Hoopl/Unique.hs @@ -24,7 +24,9 @@ import Compiler.Hoopl.Collections import qualified Data.IntMap as M import qualified Data.IntSet as S +#if !MIN_VERSION_base(4,8,0) import Control.Applicative +#endif import Control.Monad (ap,liftM) ----------------------------------------------------------------------------- From git at git.haskell.org Sat Dec 27 22:51:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Dec 2014 22:51:04 +0000 (UTC) Subject: [commit: ghc] master: Update hoopl and hpc submodules (6b9e958) Message-ID: <20141227225104.764C73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6b9e958c89f5f31bcb8520d657986a5983f5c34e/ghc >--------------------------------------------------------------- commit 6b9e958c89f5f31bcb8520d657986a5983f5c34e Author: Herbert Valerio Riedel Date: Sat Dec 27 23:50:21 2014 +0100 Update hoopl and hpc submodules This removes compile warnings triggered by those modules due to redundant imports and/or due to tabs >--------------------------------------------------------------- 6b9e958c89f5f31bcb8520d657986a5983f5c34e libraries/hoopl | 2 +- libraries/hpc | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/hoopl b/libraries/hoopl index c9185a2..d39ddd9 160000 --- a/libraries/hoopl +++ b/libraries/hoopl @@ -1 +1 @@ -Subproject commit c9185a27af3be3161644711a79164baeff4377b9 +Subproject commit d39ddd928e0d691ee571768a613fd10f6f951a40 diff --git a/libraries/hpc b/libraries/hpc index 60e7bbf..a071321 160000 --- a/libraries/hpc +++ b/libraries/hpc @@ -1 +1 @@ -Subproject commit 60e7bbfeea8ba54688b8f432f0f337b275f06c58 +Subproject commit a071321d33188fb958f42e36778464617c56cfb9 From git at git.haskell.org Sun Dec 28 01:52:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 28 Dec 2014 01:52:29 +0000 (UTC) Subject: [commit: ghc] master: Add export lists to some modules. (d6e7f5d) Message-ID: <20141228015229.0CB683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d6e7f5dc9db7e382ce34d649f85505176a451a04/ghc >--------------------------------------------------------------- commit d6e7f5dc9db7e382ce34d649f85505176a451a04 Author: David Feuer Date: Sat Dec 27 20:53:37 2014 -0500 Add export lists to some modules. Summary: This makes it easier to see what is exported, and allows us to add non-exported top-level names. Reviewers: hvr, austin, ezyang Reviewed By: ezyang Subscribers: ezyang, carter, thomie Projects: #ghc Differential Revision: https://phabricator.haskell.org/D551 GHC Trac Issues: #9852 >--------------------------------------------------------------- d6e7f5dc9db7e382ce34d649f85505176a451a04 libraries/base/Control/Category.hs | 2 +- libraries/base/Control/Monad/Zip.hs | 2 +- libraries/base/GHC/Base.hs | 33 +++++++++++++++++++++----------- libraries/base/GHC/Num.hs | 7 ++++++- libraries/base/GHC/Real.hs | 14 +++++++++++++- libraries/base/System/Posix/Internals.hs | 27 ++++++++++++++++++++++++-- libraries/ghc-prim/GHC/Classes.hs | 19 +++++++++++++++++- 7 files changed, 86 insertions(+), 18 deletions(-) diff --git a/libraries/base/Control/Category.hs b/libraries/base/Control/Category.hs index ab7740b..d21d4f9 100644 --- a/libraries/base/Control/Category.hs +++ b/libraries/base/Control/Category.hs @@ -15,7 +15,7 @@ -- http://ghc.haskell.org/trac/ghc/ticket/1773 -module Control.Category where +module Control.Category ((<<<), (>>>), Category(..)) where import qualified GHC.Base (id,(.)) import Data.Type.Coercion diff --git a/libraries/base/Control/Monad/Zip.hs b/libraries/base/Control/Monad/Zip.hs index df096b1..b994c47 100644 --- a/libraries/base/Control/Monad/Zip.hs +++ b/libraries/base/Control/Monad/Zip.hs @@ -15,7 +15,7 @@ -- ----------------------------------------------------------------------------- -module Control.Monad.Zip where +module Control.Monad.Zip (MonadZip(..)) where import Control.Monad (liftM) diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index 44085a2..e3d247e 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -93,17 +93,28 @@ Other Prelude modules are much easier with fewer complex dependencies. #include "MachDeps.h" module GHC.Base - ( - module GHC.Base, - module GHC.Classes, - module GHC.CString, - module GHC.Magic, - module GHC.Types, - module GHC.Prim, -- Re-export GHC.Prim and [boot] GHC.Err, - -- to avoid lots of people having to - module GHC.Err -- import it explicitly - ) - where + ( + module GHC.Classes, + module GHC.CString, + module GHC.Magic, + module GHC.Types, + module GHC.Prim, -- Re-export GHC.Prim and [boot] GHC.Err, + -- to avoid lots of people having to + module GHC.Err, -- import it explicitly + + + Alternative(..), Applicative(..), Functor(..), Maybe(..), Monad(..), + MonadPlus(..), Monoid(..), Opaque(..), String, + + + ($), ($!), (++), (.), (<**>), (=<<), ap, asTypeOf, assert, augment, + bindIO, breakpoint, breakpointCond, build, const, divInt, divModInt, + divModInt#, eqString, flip, foldr, getTag, iShiftL#, iShiftRA#, + iShiftRL#, id, join, liftA, liftA2, liftA3, liftM, liftM2, liftM3, + liftM4, liftM5, map, mapFB, mapM, maxInt, minInt, modInt, ord, + otherwise, quotInt, quotRemInt, remInt, returnIO, sequence, shiftL#, + shiftRL#, thenIO, unIO, unsafeChr, until, when + ) where import GHC.Types import GHC.Classes diff --git a/libraries/base/GHC/Num.hs b/libraries/base/GHC/Num.hs index 5d46dac..0b331fc 100644 --- a/libraries/base/GHC/Num.hs +++ b/libraries/base/GHC/Num.hs @@ -16,7 +16,12 @@ -- ----------------------------------------------------------------------------- -module GHC.Num (module GHC.Num, module GHC.Integer) where +module GHC.Num + ( + module GHC.Integer + , Num(..) + , subtract + ) where import GHC.Base import GHC.Integer diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs index c301325..656a22d 100644 --- a/libraries/base/GHC/Real.hs +++ b/libraries/base/GHC/Real.hs @@ -18,7 +18,19 @@ -- ----------------------------------------------------------------------------- -module GHC.Real where +module GHC.Real + ( + Fractional(..), Integral(..), Ratio(..), Real(..), RealFrac(..), + + Rational, + + (%), (^), (^%^), (^^), (^^%^^), denominator, divZeroError, even, + fromIntegral, gcd, gcdInt', gcdWord', infinity, integralEnumFrom, + integralEnumFromThen, integralEnumFromThenTo, integralEnumFromTo, lcm, + notANumber, numerator, numericEnumFrom, numericEnumFromThen, + numericEnumFromThenTo, numericEnumFromTo, odd, overflowError, ratioPrec, + ratioPrec1, ratioZeroDenominatorError, realToFrac, reduce, showSigned + ) where import GHC.Base import GHC.Num diff --git a/libraries/base/System/Posix/Internals.hs b/libraries/base/System/Posix/Internals.hs index c49e613..e2e32c3 100644 --- a/libraries/base/System/Posix/Internals.hs +++ b/libraries/base/System/Posix/Internals.hs @@ -20,7 +20,30 @@ -- ----------------------------------------------------------------------------- -module System.Posix.Internals where +module System.Posix.Internals + ( + CFLock, CFilePath, CGroup, CLconv, CPasswd, CSigaction, CSigset, CStat, + CTermios, CTm, CTms, CUtimbuf, CUtsname, FD, + + c_access, c_chmod, c_close, c_creat, c_dup, c_dup2, c_fcntl_lock, + c_fcntl_read, c_fcntl_write, c_fork, c_fstat, c_ftruncate, c_getpid, + c_isatty, c_lflag, c_link, c_lseek, c_mkfifo, c_open, c_pipe, c_read, + c_s_isblk, c_s_ischr, c_s_isdir, c_s_isfifo, c_s_isreg, c_s_issock, + c_safe_open, c_safe_read, c_safe_write, c_sigaddset, c_sigemptyset, + c_sigprocmask, c_stat, c_tcgetattr, c_tcsetattr, c_umask, c_unlink, + c_utime, c_waitpid, c_write, const_echo, const_f_getfl, const_f_setfd, + const_f_setfl, const_fd_cloexec, const_icanon, const_sig_block, + const_sig_setmask, const_sigttou, const_tcsanow, const_vmin, const_vtime, + dEFAULT_BUFFER_SIZE, fdFileSize, fdGetMode, fdStat, fdType, fileType, + getEcho, get_saved_termios, ioe_unknownfiletype, lstat, newFilePath, + o_APPEND, o_BINARY, o_CREAT, o_EXCL, o_NOCTTY, o_NONBLOCK, o_RDONLY, + o_RDWR, o_TRUNC, o_WRONLY, peekFilePath, peekFilePathLen, poke_c_lflag, + ptr_c_cc, puts, sEEK_CUR, sEEK_END, sEEK_SET, s_isblk, s_ischr, s_isdir, + s_isfifo, s_isreg, s_issock, setCloseOnExec, setCooked, setEcho, + setNonBlockingFD, set_saved_termios, sizeof_sigset_t, sizeof_stat, + sizeof_termios, st_dev, st_ino, st_mode, st_mtime, st_size, statGetType, + tcSetAttr, withFilePath + ) where #include "HsBaseConfig.h" @@ -42,7 +65,7 @@ import GHC.Real import GHC.IO import GHC.IO.IOMode import GHC.IO.Exception -import GHC.IO.Device +import GHC.IO.Device hiding (getEcho, setEcho) #ifndef mingw32_HOST_OS import {-# SOURCE #-} GHC.IO.Encoding (getFileSystemEncoding) import qualified GHC.Foreign as GHC diff --git a/libraries/ghc-prim/GHC/Classes.hs b/libraries/ghc-prim/GHC/Classes.hs index 9028f6e..3f09ff7 100644 --- a/libraries/ghc-prim/GHC/Classes.hs +++ b/libraries/ghc-prim/GHC/Classes.hs @@ -17,7 +17,24 @@ -- ----------------------------------------------------------------------------- -module GHC.Classes where +module GHC.Classes + ( + (&&) + , (||) + , compareInt + , compareInt# + , divInt# + , eqInt + , geInt + , gtInt + , leInt + , ltInt + , modInt# + , neInt + , not + , Eq(..) + , Ord(..) + ) where -- GHC.Magic is used in some derived instances import GHC.Magic () From git at git.haskell.org Sun Dec 28 10:56:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 28 Dec 2014 10:56:35 +0000 (UTC) Subject: [commit: ghc] master: Update parallel submodule to 3.2.0.6 release (1fefb59) Message-ID: <20141228105635.EE1CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1fefb590d8eba25a0d4f75cc778a7b8547d53a18/ghc >--------------------------------------------------------------- commit 1fefb590d8eba25a0d4f75cc778a7b8547d53a18 Author: Herbert Valerio Riedel Date: Sun Dec 28 11:14:50 2014 +0100 Update parallel submodule to 3.2.0.6 release >--------------------------------------------------------------- 1fefb590d8eba25a0d4f75cc778a7b8547d53a18 libraries/parallel | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/parallel b/libraries/parallel index c4863d9..5b86f00 160000 --- a/libraries/parallel +++ b/libraries/parallel @@ -1 +1 @@ -Subproject commit c4863d925c446ba5416aeed6a11012f2e978686e +Subproject commit 5b86f00553688195ea3496d9b7052ec1a9a9c2fe From git at git.haskell.org Sun Dec 28 10:56:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 28 Dec 2014 10:56:38 +0000 (UTC) Subject: [commit: ghc] master: Update validate-settings.mk (6c86635) Message-ID: <20141228105638.8474E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6c86635df2b0c02a1cff8c2ace7f114c1be699fc/ghc >--------------------------------------------------------------- commit 6c86635df2b0c02a1cff8c2ace7f114c1be699fc Author: Herbert Valerio Riedel Date: Sun Dec 28 11:54:44 2014 +0100 Update validate-settings.mk This drops a couple of `-fno-warn-*` which seem to have become obsolete by now. Moreover, with the cleaned up settings `./validate` passes with GHC 7.10.1 as bootstrap compiler. >--------------------------------------------------------------- 6c86635df2b0c02a1cff8c2ace7f114c1be699fc mk/validate-settings.mk | 39 ++++++++------------------------------- 1 file changed, 8 insertions(+), 31 deletions(-) diff --git a/mk/validate-settings.mk b/mk/validate-settings.mk index 4b0e3a7..46d269f 100644 --- a/mk/validate-settings.mk +++ b/mk/validate-settings.mk @@ -93,39 +93,22 @@ utils/ghc-cabal_dist_EXTRA_HC_OPTS += -w libraries/Cabal/Cabal_dist-boot_EXTRA_HC_OPTS += -w libraries/Cabal/Cabal_dist-install_EXTRA_HC_OPTS += -w -# Temporarily turn off incomplete-pattern warnings for containers -libraries/containers_dist-install_EXTRA_HC_OPTS += -fno-warn-incomplete-patterns - -# Temporarily turn off pointless-pragma warnings for containers -libraries/containers_dist-install_EXTRA_HC_OPTS += -fno-warn-pointless-pragmas - # Turn off import warnings for bad unused imports libraries/containers_dist-install_EXTRA_HC_OPTS += -fno-warn-unused-imports -libraries/hoopl_dist-install_EXTRA_HC_OPTS += -fno-warn-unused-imports libraries/bytestring_dist-install_EXTRA_HC_OPTS += -fno-warn-unused-imports utils/haddock_dist_EXTRA_HC_OPTS += -fno-warn-unused-imports -libraries/stm_dist-install_EXTRA_HC_OPTS += -fno-warn-unused-imports -libraries/parallel_dist-install_EXTRA_HC_OPTS += -fno-warn-unused-imports libraries/vector_dist-install_EXTRA_HC_OPTS += -fno-warn-unused-imports # haddock's attoparsec uses deprecated `inlinePerformIO` utils/haddock_dist_EXTRA_HC_OPTS += -fno-warn-deprecations -# bytestring has identities at the moment -libraries/bytestring_dist-install_EXTRA_HC_OPTS += -fno-warn-identities - -# bytestring uses bitSize at the moment -libraries/bytestring_dist-install_EXTRA_HC_OPTS += -fno-warn-deprecations - # containers uses bitSize at the moment libraries/containers_dist-install_EXTRA_HC_OPTS += -fno-warn-deprecations -# Temporarily turn off unused-do-bind warnings for the time package -libraries/time_dist-install_EXTRA_HC_OPTS += -fno-warn-unused-do-bind -# Temporary: mkTyCon is deprecated -libraries/time_dist-install_EXTRA_HC_OPTS += -fno-warn-deprecations # On Windows, there are also some unused import warnings +ifeq "$(HostOS_CPP)" "mingw32" libraries/time_dist-install_EXTRA_HC_OPTS += -fno-warn-unused-imports -fno-warn-identities +endif # haskeline has warnings about deprecated use of block/unblock libraries/haskeline_dist-install_EXTRA_HC_OPTS += -fno-warn-deprecations @@ -135,22 +118,16 @@ libraries/haskeline_dist-install_EXTRA_HC_OPTS += -fno-warn-unused-imports libraries/binary_dist-boot_EXTRA_HC_OPTS += -Wwarn libraries/binary_dist-install_EXTRA_HC_OPTS += -Wwarn -# temporarily turn off -Werror for mtl -libraries/mtl_dist-install_EXTRA_HC_OPTS += -Wwarn - # temporarily turn off unused-imports warnings for pretty libraries/pretty_dist-install_EXTRA_HC_OPTS += -fno-warn-unused-imports # primitive has a warning about deprecated use of GHC.IOBase -libraries/primitive_dist-install_EXTRA_HC_OPTS += -Wwarn +libraries/primitive_dist-install_EXTRA_HC_OPTS += -fno-warn-unused-imports # temporarily turn off unused-imports warnings for terminfo +libraries/terminfo_dist-boot_EXTRA_HC_OPTS += -fno-warn-unused-imports libraries/terminfo_dist-install_EXTRA_HC_OPTS += -fno-warn-unused-imports -# temporarily turn off -Werror for transformers -libraries/transformers_dist-boot_EXTRA_HC_OPTS += -Wwarn -libraries/transformers_dist-install_EXTRA_HC_OPTS += -Wwarn - # vector has some unused match warnings libraries/vector_dist-install_EXTRA_HC_OPTS += -Wwarn @@ -163,17 +140,16 @@ libraries/dph/dph-prim-seq_dist-install_EXTRA_HC_OPTS += -Wwarn libraries/dph/dph-prim-par_dist-install_EXTRA_HC_OPTS += -Wwarn libraries/dph/dph-lifted-common-install_EXTRA_HC_OPTS += -Wwarn -# We need to turn of deprecated warnings for SafeHaskell transition -libraries/array_dist-install_EXTRA_HC_OPTS += -fno-warn-warnings-deprecations +# transformers has unused function parameters warnings +libraries/transformers_dist-boot_EXTRA_HC_OPTS += -fno-warn-unused-matches -fno-warn-unused-imports +libraries/transformers_dist-install_EXTRA_HC_OPTS += -fno-warn-unused-matches -fno-warn-unused-imports # Turn of trustworthy-safe warning libraries/base_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe libraries/ghc-prim_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe -libraries/unix_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe libraries/Win32_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe # Temporarely disable inline rule shadowing warning -libraries/bytestring_dist-install_EXTRA_HC_OPTS += -fno-warn-inline-rule-shadowing libraries/template-haskell_dist-install_EXTRA_HC_OPTS += -fno-warn-inline-rule-shadowing # We need -fno-warn-deprecated-flags to avoid failure with -Werror @@ -187,3 +163,4 @@ GhcBootLibHcOpts += -fno-warn-deprecated-flags # for details # GhcLibHcOpts += -fno-warn-tabs +GhcBootLibHcOpts += -fno-warn-tabs From git at git.haskell.org Sun Dec 28 11:40:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 28 Dec 2014 11:40:01 +0000 (UTC) Subject: [commit: ghc] master: Support pattern synonyms in GHCi (fixes #9900) (0cc0cc8) Message-ID: <20141228114001.9BE8E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0cc0cc8688ddb53db65a73d7d562e9564cfad22b/ghc >--------------------------------------------------------------- commit 0cc0cc8688ddb53db65a73d7d562e9564cfad22b Author: Dr. ERDI Gergo Date: Sun Dec 28 11:51:00 2014 +0800 Support pattern synonyms in GHCi (fixes #9900) This involves recognizing lines starting with `"pattern "` as declarations, keeping non-exported pattern synonyms in `deSugar`, and including pattern synonyms in the result of `hscDeclsWithLocation`. >--------------------------------------------------------------- 0cc0cc8688ddb53db65a73d7d562e9564cfad22b compiler/deSugar/Desugar.hs | 3 +-- compiler/main/HscMain.hs | 6 ++++-- compiler/main/HscTypes.hs | 5 +++-- ghc/InteractiveUI.hs | 1 + testsuite/tests/patsyn/should_run/all.T | 5 +++++ testsuite/tests/patsyn/should_run/ghci.script | 8 ++++++++ testsuite/tests/patsyn/should_run/ghci.stderr | 2 ++ testsuite/tests/patsyn/should_run/ghci.stdout | 3 +++ 8 files changed, 27 insertions(+), 6 deletions(-) diff --git a/compiler/deSugar/Desugar.hs b/compiler/deSugar/Desugar.hs index ac35464..70fa88e 100644 --- a/compiler/deSugar/Desugar.hs +++ b/compiler/deSugar/Desugar.hs @@ -24,7 +24,6 @@ import Coercion import InstEnv import Class import Avail -import PatSyn import CoreSyn import CoreSubst import PprCore @@ -184,7 +183,7 @@ deSugar hsc_env mg_fam_insts = fam_insts, mg_inst_env = inst_env, mg_fam_inst_env = fam_inst_env, - mg_patsyns = filter ((`elemNameSet` export_set) . patSynName) patsyns, + mg_patsyns = patsyns, mg_rules = ds_rules_for_imps, mg_binds = ds_binds, mg_foreign = ds_fords, diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index c5cb9a1..4fe74c6 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -97,6 +97,7 @@ import CoreLint ( lintInteractiveExpr ) import DsMeta ( templateHaskellNames ) import VarEnv ( emptyTidyEnv ) import Panic +import ConLike import GHC.Exts #endif @@ -1505,6 +1506,7 @@ hscDeclsWithLocation hsc_env0 str source linenumber = liftIO $ linkDecls hsc_env src_span cbc let tcs = filterOut isImplicitTyCon (mg_tcs simpl_mg) + patsyns = mg_patsyns simpl_mg ext_ids = [ id | id <- bindersOfBinds core_binds , isExternalName (idName id) @@ -1515,11 +1517,11 @@ hscDeclsWithLocation hsc_env0 str source linenumber = -- The DFunIds are in 'cls_insts' (see Note [ic_tythings] in HscTypes -- Implicit Ids are implicit in tcs - tythings = map AnId ext_ids ++ map ATyCon tcs + tythings = map AnId ext_ids ++ map ATyCon tcs ++ map (AConLike . PatSynCon) patsyns let icontext = hsc_IC hsc_env ictxt = extendInteractiveContext icontext ext_ids tcs - cls_insts fam_insts defaults + cls_insts fam_insts defaults patsyns return (tythings, ictxt) hscImport :: HscEnv -> String -> IO (ImportDecl RdrName) diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs index 909004e..29ee78c 100644 --- a/compiler/main/HscTypes.hs +++ b/compiler/main/HscTypes.hs @@ -1403,8 +1403,9 @@ extendInteractiveContext :: InteractiveContext -> [Id] -> [TyCon] -> [ClsInst] -> [FamInst] -> Maybe [Type] + -> [PatSyn] -> InteractiveContext -extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults +extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults new_patsyns = ictxt { ic_mod_index = ic_mod_index ictxt + 1 -- Always bump this; even instances should create -- a new mod_index (Trac #9426) @@ -1413,7 +1414,7 @@ extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults , ic_instances = (new_cls_insts ++ old_cls_insts, new_fam_insts ++ old_fam_insts) , ic_default = defaults } where - new_tythings = map AnId ids ++ map ATyCon tcs + new_tythings = map AnId ids ++ map ATyCon tcs ++ map (AConLike . PatSynCon) new_patsyns old_tythings = filterOut (shadowed_by ids) (ic_tythings ictxt) -- Discard old instances that have been fully overrridden diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 7125f6d..9941a60 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -892,6 +892,7 @@ declPrefixes dflags = keywords ++ concat opt_keywords opt_keywords = [ ["foreign " | xopt Opt_ForeignFunctionInterface dflags] , ["deriving " | xopt Opt_StandaloneDeriving dflags] + , ["pattern " | xopt Opt_PatternSynonyms dflags] ] -- | Entry point to execute some haskell code from user. diff --git a/testsuite/tests/patsyn/should_run/all.T b/testsuite/tests/patsyn/should_run/all.T index 40ec3e3..2f496a6 100644 --- a/testsuite/tests/patsyn/should_run/all.T +++ b/testsuite/tests/patsyn/should_run/all.T @@ -1,3 +1,7 @@ +# We only want to run these tests with GHCi +def just_ghci( name, opts ): + opts.only_ways = ['ghci'] + test('eval', normal, compile_and_run, ['']) test('match', normal, compile_and_run, ['']) test('ex-prov-run', normal, compile_and_run, ['']) @@ -6,3 +10,4 @@ test('bidir-explicit-scope', normal, compile_and_run, ['']) test('T9783', normal, compile_and_run, ['']) test('match-unboxed', normal, compile_and_run, ['']) test('unboxed-wrapper', normal, compile_and_run, ['']) +test('ghci', just_ghci, ghci_script, ['ghci.script']) diff --git a/testsuite/tests/patsyn/should_run/ghci.script b/testsuite/tests/patsyn/should_run/ghci.script new file mode 100644 index 0000000..cd71e33 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/ghci.script @@ -0,0 +1,8 @@ +:set -XPatternSynonyms + +pattern Single x = [x] +:i Single +let foo (Single x) = Single (not x) +:t foo +foo [True] +foo [True, False] diff --git a/testsuite/tests/patsyn/should_run/ghci.stderr b/testsuite/tests/patsyn/should_run/ghci.stderr new file mode 100644 index 0000000..9593b15 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/ghci.stderr @@ -0,0 +1,2 @@ +*** Exception: :6:5-35: Non-exhaustive patterns in function foo + diff --git a/testsuite/tests/patsyn/should_run/ghci.stdout b/testsuite/tests/patsyn/should_run/ghci.stdout new file mode 100644 index 0000000..796aa72 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/ghci.stdout @@ -0,0 +1,3 @@ +pattern Single :: t -> [t] -- Defined at :4:9 +foo :: [Bool] -> [Bool] +[False] From git at git.haskell.org Mon Dec 29 00:23:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Dec 2014 00:23:11 +0000 (UTC) Subject: [commit: ghc] master: LlvmCodeGen cross-compiling fixes (#9895) (58ac9c8) Message-ID: <20141229002311.0F0603A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/58ac9c8f6e986bac817ad08d5a2fd11cd167f029/ghc >--------------------------------------------------------------- commit 58ac9c8f6e986bac817ad08d5a2fd11cd167f029 Author: Erik de Castro Lopo Date: Sat Dec 27 21:11:52 2014 +1100 LlvmCodeGen cross-compiling fixes (#9895) Summary: * Throw an error when cross-compiling without a target definition. When cross compiling via LLVM, a target 'datalayout' and 'triple' must be defined or LLVM will generate code for the compile host instead of the compile target. * Add aarch64-unknown-linux-gnu target. The datalayout and triple lines were found by using clang to compile a small C program and -emit-llvm to get the LLVM IR output. Signed-off-by: Erik de Castro Lopo Test Plan: validate Reviewers: rwbarton, carter, hvr, bgamari, austin Reviewed By: austin Subscribers: carter, thomie, garious Differential Revision: https://phabricator.haskell.org/D585 GHC Trac Issues: #9895 >--------------------------------------------------------------- 58ac9c8f6e986bac817ad08d5a2fd11cd167f029 compiler/llvmGen/LlvmCodeGen/Ppr.hs | 14 ++++++++++++-- compiler/main/SysTools.hs | 4 +++- compiler/utils/Platform.hs | 3 ++- settings.in | 1 + 4 files changed, 18 insertions(+), 4 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Ppr.hs b/compiler/llvmGen/LlvmCodeGen/Ppr.hs index ed21685..5dd27ab 100644 --- a/compiler/llvmGen/LlvmCodeGen/Ppr.hs +++ b/compiler/llvmGen/LlvmCodeGen/Ppr.hs @@ -68,9 +68,19 @@ moduleLayout = sdocWithPlatform $ \platform -> Platform { platformArch = ArchARM64, platformOS = OSiOS } -> text "target datalayout = \"e-p:64:64:64-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:64:64-f32:32:32-f64:64:64-v64:64:64-v128:128:128-a0:0:64-n32:64-S128\"" $+$ text "target triple = \"arm64-apple-ios7.0.0\"" + Platform { platformArch = ArchARM64, platformOS = OSLinux } -> + text "target datalayout = \"e-m:e-i64:64-i128:128-n32:64-S128\"" + $+$ text "target triple = \"aarch64-unknown-linux-gnu\"" _ -> - -- FIX: Other targets - empty + if platformIsCrossCompiling platform + then panic "LlvmCodeGen.Ppr: Cross compiling without valid target info." + else empty + -- If you see the above panic, GHC is missing the required target datalayout + -- and triple information. You can obtain this info by compiling a simple + -- 'hello world' C program with the clang C compiler eg: + -- clang hello.c -emit-llvm -o hello.ll + -- and the first two lines of hello.ll should provide the 'target datalayout' + -- and 'target triple' lines required. -- | Pretty print LLVM data code diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs index 7b6c82f..e4520e1 100644 --- a/compiler/main/SysTools.hs +++ b/compiler/main/SysTools.hs @@ -221,6 +221,7 @@ initSysTools mbMinusB Just v -> return v Nothing -> pgmError ("Failed to read " ++ show key ++ " value " ++ show xs) Nothing -> pgmError ("No entry for " ++ show key ++ " in " ++ show settingsFile) + crossCompiling <- getBooleanSetting "cross compiling" targetArch <- readSetting "target arch" targetOS <- readSetting "target os" targetWordSize <- readSetting "target word size" @@ -309,7 +310,8 @@ initSysTools mbMinusB platformUnregisterised = targetUnregisterised, platformHasGnuNonexecStack = targetHasGnuNonexecStack, platformHasIdentDirective = targetHasIdentDirective, - platformHasSubsectionsViaSymbols = targetHasSubsectionsViaSymbols + platformHasSubsectionsViaSymbols = targetHasSubsectionsViaSymbols, + platformIsCrossCompiling = crossCompiling } return $ Settings { diff --git a/compiler/utils/Platform.hs b/compiler/utils/Platform.hs index 39903ea..8f9a8de 100644 --- a/compiler/utils/Platform.hs +++ b/compiler/utils/Platform.hs @@ -31,7 +31,8 @@ data Platform platformUnregisterised :: Bool, platformHasGnuNonexecStack :: Bool, platformHasIdentDirective :: Bool, - platformHasSubsectionsViaSymbols :: Bool + platformHasSubsectionsViaSymbols :: Bool, + platformIsCrossCompiling :: Bool } deriving (Read, Show, Eq) diff --git a/settings.in b/settings.in index 1bcb4ae..e8cdad3 100644 --- a/settings.in +++ b/settings.in @@ -18,6 +18,7 @@ ("windres command", "@SettingsWindresCommand@"), ("libtool command", "@SettingsLibtoolCommand@"), ("perl command", "@SettingsPerlCommand@"), + ("cross compiling", "@CrossCompiling@"), ("target os", "@HaskellTargetOs@"), ("target arch", "@HaskellTargetArch@"), ("target word size", "@WordSize@"), From git at git.haskell.org Mon Dec 29 08:14:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Dec 2014 08:14:36 +0000 (UTC) Subject: [commit: ghc] master: Fix `heapSizeSuggesionAuto` typo (#9934) (40561cd) Message-ID: <20141229081436.2A0843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/40561cd235f07d41904d2604ff7f0c942af4d35e/ghc >--------------------------------------------------------------- commit 40561cd235f07d41904d2604ff7f0c942af4d35e Author: Herbert Valerio Riedel Date: Mon Dec 29 09:14:05 2014 +0100 Fix `heapSizeSuggesionAuto` typo (#9934) This was introduced in 1617a10a (re #5364) >--------------------------------------------------------------- 40561cd235f07d41904d2604ff7f0c942af4d35e libraries/base/GHC/RTS/Flags.hsc | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/GHC/RTS/Flags.hsc b/libraries/base/GHC/RTS/Flags.hsc index ff1bf69..16764e5 100644 --- a/libraries/base/GHC/RTS/Flags.hsc +++ b/libraries/base/GHC/RTS/Flags.hsc @@ -86,7 +86,7 @@ data GCFlags = GCFlags , minAllocAreaSize :: Nat , minOldGenSize :: Nat , heapSizeSuggestion :: Nat - , heapSizeSuggesionAuto :: Bool + , heapSizeSuggestionAuto :: Bool , oldGenFactor :: Double , pcFreeHeap :: Double , generations :: Nat From git at git.haskell.org Mon Dec 29 16:32:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Dec 2014 16:32:19 +0000 (UTC) Subject: [commit: ghc] master: Fix system linker on Mac OS X (b32c227) Message-ID: <20141229163219.B7D643A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b32c22760687a6a1a2e88fdba8de32f6951b5029/ghc >--------------------------------------------------------------- commit b32c22760687a6a1a2e88fdba8de32f6951b5029 Author: Peter Trommler Date: Mon Dec 29 11:33:24 2014 -0500 Fix system linker on Mac OS X Summary: Flag `-l:` is GNU ld specific and not supported by the Mac OS X link editor. So we create a temporary file name lib. and link with the standard -l option on Linux and OS X. Fixes #9875 Test Plan: validate on Mac OS X Reviewers: austin, hvr, ezyang Reviewed By: ezyang Subscribers: carter, thomie, ezyang Differential Revision: https://phabricator.haskell.org/D579 GHC Trac Issues: #9875 >--------------------------------------------------------------- b32c22760687a6a1a2e88fdba8de32f6951b5029 compiler/ghci/Linker.hs | 11 +++++------ compiler/main/SysTools.hs | 20 +++++++++++++++++++- 2 files changed, 24 insertions(+), 7 deletions(-) diff --git a/compiler/ghci/Linker.hs b/compiler/ghci/Linker.hs index 3a91fc1..91706da 100644 --- a/compiler/ghci/Linker.hs +++ b/compiler/ghci/Linker.hs @@ -120,7 +120,7 @@ data PersistentLinkerState -- we need to remember the name of the last temporary DLL/.so -- so we can link it - last_temp_so :: !(Maybe FilePath) } + last_temp_so :: !(Maybe (FilePath, String)) } emptyPLS :: DynFlags -> PersistentLinkerState @@ -818,7 +818,7 @@ dynLoadObjs :: DynFlags -> PersistentLinkerState -> [FilePath] dynLoadObjs _ pls [] = return pls dynLoadObjs dflags pls objs = do let platform = targetPlatform dflags - soFile <- newTempName dflags (soExt platform) + (soFile, libPath , libName) <- newTempLibName dflags (soExt platform) let -- When running TH for a non-dynamic way, we still need to make -- -l flags to link against the dynamic libraries, so we turn -- Opt_Static off @@ -833,12 +833,11 @@ dynLoadObjs dflags pls objs = do ldInputs = case last_temp_so pls of Nothing -> [] - Just so -> - let (lp, l) = splitFileName so in + Just (lp, l) -> [ Option ("-L" ++ lp) , Option ("-Wl,-rpath") , Option ("-Wl," ++ lp) - , Option ("-l:" ++ l) + , Option ("-l" ++ l) ], -- Even if we're e.g. profiling, we still want -- the vanilla dynamic libraries, so we set the @@ -851,7 +850,7 @@ dynLoadObjs dflags pls objs = do consIORef (filesToNotIntermediateClean dflags) soFile m <- loadDLL soFile case m of - Nothing -> return pls { last_temp_so = Just soFile } + Nothing -> return pls { last_temp_so = Just (libPath, libName) } Just err -> panic ("Loading temp shared object failed: " ++ err) rmDupLinkables :: [Linkable] -- Already loaded diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs index e4520e1..a1209c7 100644 --- a/compiler/main/SysTools.hs +++ b/compiler/main/SysTools.hs @@ -40,7 +40,7 @@ module SysTools ( -- Temporary-file management setTmpDir, - newTempName, + newTempName, newTempLibName, cleanTempDirs, cleanTempFiles, cleanTempFilesExcept, addFilesToClean, @@ -1077,6 +1077,24 @@ newTempName dflags extn consIORef (filesToClean dflags) filename return filename +newTempLibName :: DynFlags -> Suffix -> IO (FilePath, FilePath, String) +newTempLibName dflags extn + = do d <- getTempDir dflags + x <- getProcessID + findTempName d ("ghc" ++ show x ++ "_") + where + findTempName :: FilePath -> String -> IO (FilePath, FilePath, String) + findTempName dir prefix + = do n <- newTempSuffix dflags + let libname = prefix ++ show n + filename = dir "lib" ++ libname <.> extn + b <- doesFileExist filename + if b then findTempName dir prefix + else do -- clean it up later + consIORef (filesToClean dflags) filename + return (filename, dir, libname) + + -- Return our temporary directory within tmp_dir, creating one if we -- don't have one yet. getTempDir :: DynFlags -> IO FilePath From git at git.haskell.org Mon Dec 29 16:35:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Dec 2014 16:35:27 +0000 (UTC) Subject: [commit: ghc] master: Skip T2276_ghci on Darwin, since stdcall is not supported. (4e1e776) Message-ID: <20141229163527.A92743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4e1e776a4cc54f117c2cbbdba1d4ed9be453b550/ghc >--------------------------------------------------------------- commit 4e1e776a4cc54f117c2cbbdba1d4ed9be453b550 Author: Edward Z. Yang Date: Mon Dec 29 11:36:21 2014 -0500 Skip T2276_ghci on Darwin, since stdcall is not supported. Summary: Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin, erikd Reviewed By: erikd Subscribers: erikd, carter, thomie Differential Revision: https://phabricator.haskell.org/D588 >--------------------------------------------------------------- 4e1e776a4cc54f117c2cbbdba1d4ed9be453b550 testsuite/tests/ffi/should_run/all.T | 1 + 1 file changed, 1 insertion(+) diff --git a/testsuite/tests/ffi/should_run/all.T b/testsuite/tests/ffi/should_run/all.T index 0352f31..cf785f1 100644 --- a/testsuite/tests/ffi/should_run/all.T +++ b/testsuite/tests/ffi/should_run/all.T @@ -115,6 +115,7 @@ test('T2276', [ omit_ways(['ghci']), extra_clean(['T2276_c.o']) ], compile_and_run, ['T2276_c.c']) test('T2276_ghci', [ only_ways(['ghci']), + when(opsys('darwin'), skip), # stdcall not supported on OS X pre_cmd('$MAKE -s --no-print-directory T2276_ghci_setup'), extra_clean(['T2276_ghci_c.o']) ], compile_and_run, ['-fobject-code T2276_ghci_c.o']) From mail at joachim-breitner.de Mon Dec 29 17:40:56 2014 From: mail at joachim-breitner.de (Joachim Breitner) Date: Mon, 29 Dec 2014 18:40:56 +0100 Subject: [commit: ghc] master: Eliminate so-called "silent superclass parameters" (a6f0f5a) In-Reply-To: <20141223162932.A04A93A300@ghc.haskell.org> References: <20141223162932.A04A93A300@ghc.haskell.org> Message-ID: <1419874856.13967.7.camel@joachim-breitner.de> Hi devs, Am Dienstag, den 23.12.2014, 16:29 +0000 schrieb git at git.haskell.org: > commit a6f0f5ab45b2643b561e0a0a54a4f14745ab2152 > Author: Simon Peyton Jones > Date: Tue Dec 23 15:39:50 2014 +0000 > > Eliminate so-called "silent superclass parameters" you may or may not have noticed that ghcspeed stopped producing results since this commits. The reason is that running nofib fails: ==nofib== cryptarithm2: size of Main.o follows... text data bss dec hex filename 25423 1304 0 26727 6867 Main.o ==nofib== cryptarithm2: time to link cryptarithm2 follows... Main.o: In Funktion `c79k_info': (.text+0x1a5b): Nicht definierter Verweis auf `transzuH9c1w14lEUN3zzdWCTsn8jG_ControlziMonadziTransziStateziLazzy_zdwzdcp0Alternative_info' Main.o: In Funktion `c7cP_info': (.text+0x2283): Nicht definierter Verweis auf `transzuH9c1w14lEUN3zzdWCTsn8jG_ControlziMonadziTransziStateziLazzy_zdwzdcp0Alternative_info' Main.o: In Funktion `c7ll_info': (.text+0x2f53): Nicht definierter Verweis auf `transzuH9c1w14lEUN3zzdWCTsn8jG_ControlziMonadziTransziStateziLazzy_zdwzdcp0Alternative_info' Main.o: In Funktion `c7p2_info': (.text+0x37cb): Nicht definierter Verweis auf `transzuH9c1w14lEUN3zzdWCTsn8jG_ControlziMonadziTransziStateziLazzy_zdwzdcp0Alternative_info' collect2: error: ld returned 1 exit status <> make[2]: *** [cryptarithm2] Fehler 1 Failed making all in cryptarithm2: 1 make[1]: *** [all] Fehler 1 Failed making all in spectral: 1 make: *** [all] Fehler 1 make: Verlasse Verzeichnis '/data1/ghc-builder/logs/ghc-tmp-REV/nofib' (sorry for the German, but its a missing link reference) Can this really be caused by this commit? Alternative is a type class, so maybe... (Building a new tree now to see if I can reproduce it locally.) Greetings, Joachim -- Joachim ?nomeata? Breitner mail at joachim-breitner.de ? http://www.joachim-breitner.de/ Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0xF0FBF51F Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: This is a digitally signed message part URL: From git at git.haskell.org Mon Dec 29 18:38:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Dec 2014 18:38:06 +0000 (UTC) Subject: [commit: ghc] master: Test case for #9938 (65e3e0b) Message-ID: <20141229183806.B9FAD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/65e3e0b2ce125b906efca129c92673fc40cf79f6/ghc >--------------------------------------------------------------- commit 65e3e0b2ce125b906efca129c92673fc40cf79f6 Author: Joachim Breitner Date: Mon Dec 29 19:37:19 2014 +0100 Test case for #9938 Marked as known_broken >--------------------------------------------------------------- 65e3e0b2ce125b906efca129c92673fc40cf79f6 testsuite/tests/driver/Makefile | 6 ++++++ testsuite/tests/driver/T9938.hs | 13 +++++++++++++ testsuite/tests/driver/all.T | 4 ++++ 3 files changed, 23 insertions(+) diff --git a/testsuite/tests/driver/Makefile b/testsuite/tests/driver/Makefile index 11724a5..2acedfc 100644 --- a/testsuite/tests/driver/Makefile +++ b/testsuite/tests/driver/Makefile @@ -586,3 +586,9 @@ write_interface_make: $(RM) -rf write_interface_make/A011.hi "$(TEST_HC)" $(TEST_HC_OPTS) -hidir write_interface_make -fno-code -fwrite-interface --make A011.hs test -f write_interface_make/A011.hi + +.PHONY: T9938 +T9938: + $(RM) -rf T9938.o T9938.hi T9938 + "$(TEST_HC)" -c T9938.hs + "$(TEST_HC)" T9938.o -o T9938 diff --git a/testsuite/tests/driver/T9938.hs b/testsuite/tests/driver/T9938.hs new file mode 100644 index 0000000..f9bb131 --- /dev/null +++ b/testsuite/tests/driver/T9938.hs @@ -0,0 +1,13 @@ +module Main where + +import Control.Monad +import Control.Monad.Trans.State + +solve :: Int -> StateT () [] () +solve carry | carry > 0 = + do guard (0 == carry) + solve (carry -1) +solve 0 = mzero + +main :: IO () +main = return () diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T index ed4d924..cd38ceb 100644 --- a/testsuite/tests/driver/all.T +++ b/testsuite/tests/driver/all.T @@ -410,3 +410,7 @@ test('write_interface_make', normal, run_command, ['$MAKE -s --no-print-director test('T9776', normal, compile_fail, ['-frule-check']) +test('T9938', + [ extra_clean(['T9938.hi', 'T9938.o', 'T9938']), expect_broken(9938)], + run_command, + ['$MAKE -s --no-print-directory T9938']) From git at git.haskell.org Tue Dec 30 10:39:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 Dec 2014 10:39:31 +0000 (UTC) Subject: [commit: ghc] master: Refine test case for #9938 (9521a58) Message-ID: <20141230103931.EEBF83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9521a58a5f3ca38a0bde8b67be00a74e5fc3ccea/ghc >--------------------------------------------------------------- commit 9521a58a5f3ca38a0bde8b67be00a74e5fc3ccea Author: Joachim Breitner Date: Tue Dec 30 11:38:25 2014 +0100 Refine test case for #9938 By passing -O2, the bug appears depending on the order of clauses in "solve", hence adding T9938B as the other variant. Currently, T9938 is marked as broken, but maybe the bug is actually in T9938B, where something (possibly inlining, as suggested by rwbarton) affected the requirement to link against transformers. >--------------------------------------------------------------- 9521a58a5f3ca38a0bde8b67be00a74e5fc3ccea testsuite/tests/driver/Makefile | 10 ++++++++-- testsuite/tests/driver/{T9938.hs => T9938B.hs} | 2 +- testsuite/tests/driver/all.T | 5 +++++ 3 files changed, 14 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/driver/Makefile b/testsuite/tests/driver/Makefile index 2acedfc..3bec5b7 100644 --- a/testsuite/tests/driver/Makefile +++ b/testsuite/tests/driver/Makefile @@ -590,5 +590,11 @@ write_interface_make: .PHONY: T9938 T9938: $(RM) -rf T9938.o T9938.hi T9938 - "$(TEST_HC)" -c T9938.hs - "$(TEST_HC)" T9938.o -o T9938 + "$(TEST_HC)" $(TEST_HC_OPTS) -O2 -c T9938.hs + "$(TEST_HC)" $(TEST_HC_OPTS) -O2 T9938.o -o T9938 + +.PHONY: T9938B +T9938B: + $(RM) -rf T9938B.o T9938B.hi T9938B + "$(TEST_HC)" $(TEST_HC_OPTS) -O2 -c T9938B.hs + "$(TEST_HC)" $(TEST_HC_OPTS) -O2 T9938B.o -o T9938B diff --git a/testsuite/tests/driver/T9938.hs b/testsuite/tests/driver/T9938B.hs similarity index 100% copy from testsuite/tests/driver/T9938.hs copy to testsuite/tests/driver/T9938B.hs index f9bb131..8b92369 100644 --- a/testsuite/tests/driver/T9938.hs +++ b/testsuite/tests/driver/T9938B.hs @@ -4,10 +4,10 @@ import Control.Monad import Control.Monad.Trans.State solve :: Int -> StateT () [] () +solve 0 = mzero solve carry | carry > 0 = do guard (0 == carry) solve (carry -1) -solve 0 = mzero main :: IO () main = return () diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T index cd38ceb..fbacf2e 100644 --- a/testsuite/tests/driver/all.T +++ b/testsuite/tests/driver/all.T @@ -414,3 +414,8 @@ test('T9938', [ extra_clean(['T9938.hi', 'T9938.o', 'T9938']), expect_broken(9938)], run_command, ['$MAKE -s --no-print-directory T9938']) + +test('T9938B', + [ extra_clean(['T9938B.hi', 'T9938B.o', 'T9938B']) ], + run_command, + ['$MAKE -s --no-print-directory T9938B']) From git at git.haskell.org Tue Dec 30 11:47:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 Dec 2014 11:47:22 +0000 (UTC) Subject: [commit: nofib] branch 'HEAD' created Message-ID: <20141230114722.B64743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib New branch : HEAD Referencing: c9c20d477088a8a7d5747f16afdf0652fba6dadf From git at git.haskell.org Tue Dec 30 11:47:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 Dec 2014 11:47:37 +0000 (UTC) Subject: [commit: nofib] master: Unbreak cryptarithm2: Pass -package transformers (818d889) Message-ID: <20141230114737.403693A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/818d8895242e888e1346b33a90ed9bb45295bf0c/nofib >--------------------------------------------------------------- commit 818d8895242e888e1346b33a90ed9bb45295bf0c Author: Joachim Breitner Date: Tue Dec 30 12:48:29 2014 +0100 Unbreak cryptarithm2: Pass -package transformers >--------------------------------------------------------------- 818d8895242e888e1346b33a90ed9bb45295bf0c spectral/cryptarithm2/Makefile | 1 + 1 file changed, 1 insertion(+) diff --git a/spectral/cryptarithm2/Makefile b/spectral/cryptarithm2/Makefile index b0ddca4..dcb62e4 100644 --- a/spectral/cryptarithm2/Makefile +++ b/spectral/cryptarithm2/Makefile @@ -3,3 +3,4 @@ include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/target.mk +SRC_HC_OPTS += -package transformers From git at git.haskell.org Tue Dec 30 11:48:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 Dec 2014 11:48:28 +0000 (UTC) Subject: [commit: ghc] master: Update nofib submodule, unbreak cryptarithm2 (8d62f92) Message-ID: <20141230114828.7692B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8d62f92cba09e9a9dbb046850e7942ab21f56035/ghc >--------------------------------------------------------------- commit 8d62f92cba09e9a9dbb046850e7942ab21f56035 Author: Joachim Breitner Date: Tue Dec 30 12:49:40 2014 +0100 Update nofib submodule, unbreak cryptarithm2 >--------------------------------------------------------------- 8d62f92cba09e9a9dbb046850e7942ab21f56035 nofib | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/nofib b/nofib index 69bae89..818d889 160000 --- a/nofib +++ b/nofib @@ -1 +1 @@ -Subproject commit 69bae89103aca6e498b811d562f387830fbcb959 +Subproject commit 818d8895242e888e1346b33a90ed9bb45295bf0c From git at git.haskell.org Tue Dec 30 12:55:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 Dec 2014 12:55:42 +0000 (UTC) Subject: [commit: nofib] branch 'HEAD' deleted Message-ID: <20141230125542.720B63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib Deleted branch: HEAD From git at git.haskell.org Tue Dec 30 13:55:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 Dec 2014 13:55:13 +0000 (UTC) Subject: [commit: ghc] master: Improve documentation of -XFlexibleInstances (a3d6eb7) Message-ID: <20141230135513.C2D783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a3d6eb7768deb8bc8107c8497fd7714bc2e06710/ghc >--------------------------------------------------------------- commit a3d6eb7768deb8bc8107c8497fd7714bc2e06710 Author: Simon Peyton Jones Date: Tue Dec 30 10:58:15 2014 +0000 Improve documentation of -XFlexibleInstances I ended up introducing a new sub-section on instance termination. >--------------------------------------------------------------- a3d6eb7768deb8bc8107c8497fd7714bc2e06710 docs/users_guide/glasgow_exts.xml | 74 ++++++++++++++++++++++++++------------- 1 file changed, 50 insertions(+), 24 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 44577f9..424064e 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -4898,28 +4898,54 @@ The flag implies