From git at git.haskell.org Mon Mar 2 09:54:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 09:54:03 +0000 (UTC) Subject: [commit: ghc] master: Extend the docs for Data.List.transpose (c5977c2) Message-ID: <20150302095403.E3F8E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c5977c2e2951e9e346a8f4990d5a6bbdbf9cee0b/ghc >--------------------------------------------------------------- commit c5977c2e2951e9e346a8f4990d5a6bbdbf9cee0b Author: Joachim Breitner Date: Mon Mar 2 10:55:22 2015 +0100 Extend the docs for Data.List.transpose by giving a sufficient general example to explain what happens when the rows are not of the same lengths. Thanks to Doug McIlroy for the suggestoin. Fixes #10128. >--------------------------------------------------------------- c5977c2e2951e9e346a8f4990d5a6bbdbf9cee0b libraries/base/Data/OldList.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index 137ce42..7e79c34 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -468,6 +468,10 @@ intercalate xs xss = concat (intersperse xs xss) -- For example, -- -- > transpose [[1,2,3],[4,5,6]] == [[1,4],[2,5],[3,6]] +-- +-- If some of the rows are shorter than the following rows, their elements are skipped: +-- +-- > transpose [[10,11],[20],[],[30,31,32]] == [[10,20,30],[11,31],[32]] transpose :: [[a]] -> [[a]] transpose [] = [] From git at git.haskell.org Mon Mar 2 16:39:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 16:39:36 +0000 (UTC) Subject: [commit: ghc] master: Comments only (7727371) Message-ID: <20150302163936.DF7373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/772737195823ac399203ac4cc4b051d8028eee1d/ghc >--------------------------------------------------------------- commit 772737195823ac399203ac4cc4b051d8028eee1d Author: Simon Peyton Jones Date: Thu Feb 26 16:41:12 2015 +0000 Comments only >--------------------------------------------------------------- 772737195823ac399203ac4cc4b051d8028eee1d compiler/typecheck/TcTyClsDecls.hs | 19 ++++++++++--------- 1 file changed, 10 insertions(+), 9 deletions(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 034ff6f..f6d4085 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -221,12 +221,6 @@ Kind checking is done thus: 3. Kind check the data type and class decls -Synonyms are treated differently to data type and classes, -because a type synonym can be an unboxed type - type Foo = Int# -and a kind variable can't unify with UnboxedTypeKind -So we infer their kinds in dependency order - We need to kind check all types in the mutually recursive group before we know the kind of the type variables. For example: @@ -245,9 +239,16 @@ just involve (->) and *: type R = Int# -- Kind # type S a = Array# a -- Kind * -> # type T a b = (# a,b #) -- Kind * -> * -> (# a,b #) -So we must infer their kinds from their right-hand sides *first* and then -use them, whereas for the mutually recursive data types D we bring into -scope kind bindings D -> k, where k is a kind variable, and do inference. +and a kind variable can't unify with UnboxedTypeKind. + +So we must infer the kinds of type synonyms from their right-hand +sides *first* and then use them, whereas for the mutually recursive +data types D we bring into scope kind bindings D -> k, where k is a +kind variable, and do inference. + +NB: synonyms can be mutually recursive with data type declarations though! + type T = D -> D + data D = MkD Int T Open type families ~~~~~~~~~~~~~~~~~~ From git at git.haskell.org Mon Mar 2 16:39:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 16:39:39 +0000 (UTC) Subject: [commit: ghc] master: Improve comments on coreView/tcView, and combine coreExpandTyCon/tcExpandTyCon (9b3239f) Message-ID: <20150302163939.9C7B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9b3239f81261f05ee3285c1b9dcbe113635145ef/ghc >--------------------------------------------------------------- commit 9b3239f81261f05ee3285c1b9dcbe113635145ef Author: Simon Peyton Jones Date: Thu Feb 26 17:26:56 2015 +0000 Improve comments on coreView/tcView, and combine coreExpandTyCon/tcExpandTyCon This is minor stuff triggered by Trac #10103. * Fix outdated comments on tcView/coreView (we should really combine them with a new name, but I'll leave that slightly-disruptive change for now) * Combine tcExpandTyCon_maybe and coreExpandTyCon_maybe (which were identical) into expandSynTyCon_maybe * A few more comment fixups >--------------------------------------------------------------- 9b3239f81261f05ee3285c1b9dcbe113635145ef compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcFlatten.hs | 2 +- compiler/typecheck/TcTyDecls.hs | 2 +- compiler/types/Coercion.hs | 2 +- compiler/types/FamInstEnv.hs | 2 +- compiler/types/TyCon.hs | 44 +++++++++++------------------------------ compiler/types/Type.hs | 20 ++++++++----------- 7 files changed, 24 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9b3239f81261f05ee3285c1b9dcbe113635145ef From git at git.haskell.org Mon Mar 2 16:39:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 16:39:42 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #10112 (104c0ad) Message-ID: <20150302163942.D183B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/104c0ad53d4d5b6ea5ee67e04eb7943f5f0d4899/ghc >--------------------------------------------------------------- commit 104c0ad53d4d5b6ea5ee67e04eb7943f5f0d4899 Author: Simon Peyton Jones Date: Thu Feb 26 17:27:15 2015 +0000 Test Trac #10112 >--------------------------------------------------------------- 104c0ad53d4d5b6ea5ee67e04eb7943f5f0d4899 testsuite/tests/rebindable/T10112.hs | 16 ++++++++++++++++ testsuite/tests/rebindable/all.T | 1 + 2 files changed, 17 insertions(+) diff --git a/testsuite/tests/rebindable/T10112.hs b/testsuite/tests/rebindable/T10112.hs new file mode 100644 index 0000000..1cfe49e --- /dev/null +++ b/testsuite/tests/rebindable/T10112.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE RankNTypes, RebindableSyntax #-} +module T10112 where + +import qualified Prelude as P + +(>>=) :: a -> ((forall b . b) -> c) -> c +a >>= f = f P.undefined +return a = a +fail s = P.undefined + +t1 = 'd' >>= (\_ -> 'k') + +t2 = do { _ <- 'd' + ; 'k' } + +foo = P.putStrLn [t1, t2] diff --git a/testsuite/tests/rebindable/all.T b/testsuite/tests/rebindable/all.T index 70628fa..6d7283e 100644 --- a/testsuite/tests/rebindable/all.T +++ b/testsuite/tests/rebindable/all.T @@ -31,3 +31,4 @@ test('T5038', normal, compile_and_run, ['']) test('T4851', normal, compile, ['']) test('T5908', normal, compile, ['']) +test('T10112', normal, compile, ['']) From git at git.haskell.org Mon Mar 2 16:39:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 16:39:45 +0000 (UTC) Subject: [commit: ghc] master: Comments only (52dfa61) Message-ID: <20150302163945.7BDEA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/52dfa616028f3ac9ffdcbe4b6342c17cf69a364f/ghc >--------------------------------------------------------------- commit 52dfa616028f3ac9ffdcbe4b6342c17cf69a364f Author: Simon Peyton Jones Date: Thu Feb 26 17:43:31 2015 +0000 Comments only >--------------------------------------------------------------- 52dfa616028f3ac9ffdcbe4b6342c17cf69a364f compiler/typecheck/TcGenDeriv.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcGenDeriv.hs b/compiler/typecheck/TcGenDeriv.hs index 1df57d1..188d2b6 100644 --- a/compiler/typecheck/TcGenDeriv.hs +++ b/compiler/typecheck/TcGenDeriv.hs @@ -1187,7 +1187,7 @@ gen_Show_binds get_fixity loc tycon show_arg :: RdrName -> Type -> LHsExpr RdrName show_arg b arg_ty | isUnLiftedType arg_ty - -- See Note [Deriving and unboxed types]. + -- See Note [Deriving and unboxed types] in TcDeriv = nlHsApps compose_RDR [mk_shows_app boxed_arg, mk_showString_app postfixMod] | otherwise @@ -2113,7 +2113,7 @@ box :: String -- The class involved -> LHsExpr RdrName -- The argument -> Type -- The argument type -> LHsExpr RdrName -- Boxed version of the arg --- See Note [Deriving and unboxed types] +-- See Note [Deriving and unboxed types] in TcDeriv box cls_str tycon arg arg_ty = nlHsApp (nlHsVar box_con) arg where box_con = assoc_ty_id cls_str tycon boxConTbl arg_ty @@ -2123,7 +2123,7 @@ primOrdOps :: String -- The class involved -> TyCon -- The tycon involved -> Type -- The type -> (RdrName, RdrName, RdrName, RdrName, RdrName) -- (lt,le,eq,ge,gt) --- See Note [Deriving and unboxed types] +-- See Note [Deriving and unboxed types] in TcDeriv primOrdOps str tycon ty = assoc_ty_id str tycon ordOpTbl ty ordOpTbl :: [(Type, (RdrName, RdrName, RdrName, RdrName, RdrName))] From git at git.haskell.org Mon Mar 2 16:39:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 16:39:48 +0000 (UTC) Subject: [commit: ghc] master: Two kind-polymorphism fixes (Trac #10122) (cabe174) Message-ID: <20150302163948.C3B723A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cabe174877d0c31535e224d69bd78434b2d28651/ghc >--------------------------------------------------------------- commit cabe174877d0c31535e224d69bd78434b2d28651 Author: Simon Peyton Jones Date: Mon Mar 2 16:29:39 2015 +0000 Two kind-polymorphism fixes (Trac #10122) * The original fix was to improve the documentation, in line with the suggestions on Trac #10122 * But in doing so I realised that the kind generalisation in TcRnDriver.tcRnType was completely wrong. So I fixed that and updated Note [Kind-generalise in tcRnType] to explain. >--------------------------------------------------------------- cabe174877d0c31535e224d69bd78434b2d28651 compiler/typecheck/TcRnDriver.hs | 44 +++++++++++----- compiler/types/TypeRep.hs | 2 +- docs/users_guide/glasgow_exts.xml | 59 +++++++++++++++++----- testsuite/tests/ghci/scripts/T10122.script | 5 ++ testsuite/tests/ghci/scripts/T10122.stdout | 2 + testsuite/tests/ghci/scripts/all.T | 1 + .../should_run/GHCiWildcardKind.stdout | 2 +- 7 files changed, 86 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 cabe174877d0c31535e224d69bd78434b2d28651 From git at git.haskell.org Mon Mar 2 16:39:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 16:39:51 +0000 (UTC) Subject: [commit: ghc] master: Improve documentation of infinite inlining bug (d2e6a3b) Message-ID: <20150302163951.73B933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d2e6a3b5edd687f2a384cd6671a519e222f664b8/ghc >--------------------------------------------------------------- commit d2e6a3b5edd687f2a384cd6671a519e222f664b8 Author: Simon Peyton Jones Date: Mon Mar 2 16:30:36 2015 +0000 Improve documentation of infinite inlining bug This fixes the documentation suggestion in Trac #10105 >--------------------------------------------------------------- d2e6a3b5edd687f2a384cd6671a519e222f664b8 docs/users_guide/bugs.xml | 16 +++++++++++++--- 1 file changed, 13 insertions(+), 3 deletions(-) diff --git a/docs/users_guide/bugs.xml b/docs/users_guide/bugs.xml index a23c75c..1e948e6 100644 --- a/docs/users_guide/bugs.xml +++ b/docs/users_guide/bugs.xml @@ -503,7 +503,7 @@ checking for duplicates. The reason for this is efficiency, pure and simple. GHC's inliner can be persuaded into non-termination - using the standard way to encode recursion via a data type: + using the standard way to encode recursion via a data type: data U = MkU (U -> Bool) @@ -513,8 +513,18 @@ checking for duplicates. The reason for this is efficiency, pure and simple. x :: Bool x = russel (MkU russel) - - We have never found another class of programs, other + The non-termination is reported like this: + +ghc: panic! (the 'impossible' happened) + (GHC version 7.10.1 for x86_64-unknown-linux): + Simplifier ticks exhausted + When trying UnfoldingDone x_alB + To increase the limit, use -fsimpl-tick-factor=N (default 100) + + with the panic being reported no matter how high a -fsimpl-tick-factor you supply. + + + We have never found another class of programs, other than this contrived one, that makes GHC diverge, and fixing the problem would impose an extra overhead on every compilation. So the bug remains un-fixed. There is more From git at git.haskell.org Mon Mar 2 17:15:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 17:15:59 +0000 (UTC) Subject: [commit: ghc] master: Show record construction/update without parens (5692643) Message-ID: <20150302171559.6883E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5692643c9d17e746327588cd6157a923642b7975/ghc >--------------------------------------------------------------- commit 5692643c9d17e746327588cd6157a923642b7975 Author: Thomas Miedema Date: Mon Mar 2 11:07:58 2015 -0600 Show record construction/update without parens Summary: The 2010 report mentions: "The result of `show` is a syntactically correct Haskell expression ... Parenthesis are only added where needed, //ignoring associativity//". Reviewers: austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D669 GHC Trac Issues: #2530 >--------------------------------------------------------------- 5692643c9d17e746327588cd6157a923642b7975 compiler/hsSyn/HsExpr.hs | 4 +++- compiler/typecheck/TcGenDeriv.hs | 2 ++ testsuite/tests/codeGen/should_run/T7953.stdout | 4 ++-- testsuite/tests/deriving/should_run/drvrun020.stdout | 2 +- testsuite/tests/ghc-api/annotations-literals/literals.stdout | 6 +++--- 5 files changed, 11 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 5692643c9d17e746327588cd6157a923642b7975 From git at git.haskell.org Mon Mar 2 17:16:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 17:16:02 +0000 (UTC) Subject: [commit: ghc] master: fix typos in coreSyn (6cdccb4) Message-ID: <20150302171602.3E5EC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6cdccb4656c22aaf809e93f8ce5886153f83096e/ghc >--------------------------------------------------------------- commit 6cdccb4656c22aaf809e93f8ce5886153f83096e Author: Javran Cheng Date: Mon Mar 2 11:09:23 2015 -0600 fix typos in coreSyn Summary: fixed few typos in coreSyn, no trac number Test Plan: validate Reviewers: austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D682 >--------------------------------------------------------------- 6cdccb4656c22aaf809e93f8ce5886153f83096e compiler/coreSyn/CoreArity.hs | 2 +- compiler/coreSyn/CoreSyn.hs | 2 +- compiler/coreSyn/CoreTidy.hs | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/coreSyn/CoreArity.hs b/compiler/coreSyn/CoreArity.hs index 5e50642..47c8085 100644 --- a/compiler/coreSyn/CoreArity.hs +++ b/compiler/coreSyn/CoreArity.hs @@ -437,7 +437,7 @@ ArityType 'at', then * If at = ATop as, and n=length as, then expanding 'f' to (\x1..xn. f x1 .. xn) loses no sharing, - assuming the calls of f respect the one-shot-ness of of + assuming the calls of f respect the one-shot-ness of its definition. NB 'f' is an arbitary expression, eg (f = g e1 e2). This 'f' diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index 83b3600..32ebd8a 100644 --- a/compiler/coreSyn/CoreSyn.hs +++ b/compiler/coreSyn/CoreSyn.hs @@ -340,7 +340,7 @@ See #letrec_invariant# Note [CoreSyn let/app invariant] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The let/app invariant - the right hand side of of a non-recursive 'Let', and + the right hand side of a non-recursive 'Let', and the argument of an 'App', /may/ be of unlifted type, but only if the expression is ok-for-speculation. diff --git a/compiler/coreSyn/CoreTidy.hs b/compiler/coreSyn/CoreTidy.hs index 7f09c68..325950c 100644 --- a/compiler/coreSyn/CoreTidy.hs +++ b/compiler/coreSyn/CoreTidy.hs @@ -261,7 +261,7 @@ Note [Preserve OneShotInfo] We keep the OneShotInfo because we want it to propagate into the interface. Not all OneShotInfo is determined by a compiler analysis; some is added by a -call of GHC.Exts.oneShot, which is then discarded before the end of of the +call of GHC.Exts.oneShot, which is then discarded before the end of the optimisation pipeline, leaving only the OneShotInfo on the lambda. Hence we must preserve this info in inlinings. From git at git.haskell.org Mon Mar 2 17:16:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 17:16:04 +0000 (UTC) Subject: [commit: ghc] master: Fix detection of llvm-x.x (1dfab7a) Message-ID: <20150302171604.EDFF63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1dfab7a8ace5f09f00f8fb695932b4324e88b822/ghc >--------------------------------------------------------------- commit 1dfab7a8ace5f09f00f8fb695932b4324e88b822 Author: Thomas Miedema Date: Mon Mar 2 11:09:33 2015 -0600 Fix detection of llvm-x.x Summary: Four bug fixes and a little refactoring. * `find -perm \mode` should be `find -perm /mode` (#9697) * `find -regex '$3' should be `find -regex "$3"` (#7661) From `man sh` on my system (Ubuntu 14.04): "Enclosing characters in single quotes preserves the literal meaning of all the characters ..." * LlcCmd and OptCmd should be passed to ghc, using `-pgmlo` and `-pgmlc`, for detection of #9439. * -pgmlo and -pgmlc were undocumented because of an xml tag misplacement. Test Plan: The aclocal.m4 macro has seen about 10 iterations since its inception. Without a testsuite, I can't guarantee this version is bug free either. It's all pretty frustrating. Reviewers: bgamari, austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D683 GHC Trac Issues: #9697, #7661, #9439 >--------------------------------------------------------------- 1dfab7a8ace5f09f00f8fb695932b4324e88b822 aclocal.m4 | 20 +++++++++++++++----- configure.ac | 4 ++-- docs/users_guide/flags.xml | 2 +- 3 files changed, 18 insertions(+), 8 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 73b8890..a4944c1 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2095,21 +2095,31 @@ AC_DEFUN([XCODE_VERSION],[ AC_DEFUN([FIND_LLVM_PROG],[ FP_ARG_WITH_PATH_GNU_PROG_OPTIONAL_NOTARGET([$1], [$2], [$3]) if test "$$1" = ""; then + echo -n "checking for $3-x.x... " save_IFS=$IFS IFS=":;" + if test "$windows" = YES; then + PERM= + MODE= + else + # Search for executables. + PERM="-perm" + MODE="/+x" + fi for p in ${PATH}; do if test -d "${p}"; then - if test "$windows" = YES; then - $1=`${FindCmd} "${p}" -type f -maxdepth 1 -regex '.*/$3-[[0-9]]\.[[0-9]]' -or -type l -maxdepth 1 -regex '.*/$3-[[0-9]]\.[[0-9]]' | ${SortCmd} -n | tail -1` - else - $1=`${FindCmd} "${p}" -type f -perm \111 -maxdepth 1 -regex '.*/$3-[[0-9]]\.[[0-9]]' -or -type l -perm \111 -maxdepth 1 -regex '.*/$3-[[0-9]]\.[[0-9]]' | ${SortCmd} -n | tail -1` - fi + $1=`${FindCmd} "${p}" -maxdepth 1 \( -type f -o -type l \) ${PERM} ${MODE} -regex ".*/$3-[[0-9]]\.[[0-9]]" | ${SortCmd} -n | tail -1` if test -n "$$1"; then break fi fi done IFS=$save_IFS + if test -n "$$1"; then + echo "$$1" + else + echo "no" + fi fi ]) diff --git a/configure.ac b/configure.ac index f65d133..c64af90 100644 --- a/configure.ac +++ b/configure.ac @@ -508,7 +508,7 @@ then echo "main = putStrLn \"%function\"" > conftestghc.hs # Check whether LLVM backend is default for this platform - "${WithGhc}" conftestghc.hs 2>&1 >/dev/null + "${WithGhc}" -pgmlc="${LlcCmd}" -pgmlo="${OptCmd}" conftestghc.hs 2>&1 >/dev/null res=`./conftestghc` if test "x$res" = "x%object" then @@ -525,7 +525,7 @@ then # -fllvm is not the default, but set a flag so the Makefile can check # -for it in the build flags later on - "${WithGhc}" -fforce-recomp -fllvm conftestghc.hs 2>&1 >/dev/null + "${WithGhc}" -fforce-recomp -pgmlc="${LlcCmd}" -pgmlo="${OptCmd}" -fllvm conftestghc.hs 2>&1 >/dev/null if test $? = 0 then res=`./conftestghc` diff --git a/docs/users_guide/flags.xml b/docs/users_guide/flags.xml index 3d90479..4bf78b6 100644 --- a/docs/users_guide/flags.xml +++ b/docs/users_guide/flags.xml @@ -2731,6 +2731,7 @@ Use cmd as the C compiler dynamic - + cmd Use cmd as the LLVM optimiser @@ -2743,7 +2744,6 @@ dynamic - - cmd Use cmd as the splitter From git at git.haskell.org Mon Mar 2 17:16:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 17:16:07 +0000 (UTC) Subject: [commit: ghc] master: Fix typecheck tests (--slow) (ca478ac) Message-ID: <20150302171607.BD0BA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ca478acc3825852320abc45ed6bc8efa4e869ff3/ghc >--------------------------------------------------------------- commit ca478acc3825852320abc45ed6bc8efa4e869ff3 Author: Thomas Miedema Date: Mon Mar 2 11:09:50 2015 -0600 Fix typecheck tests (--slow) Summary: Fallout from AMP, recent addition of -fwarn-redundant-constraints and others. Some of these tests need `mtl` or `syb` to run. Reviewers: austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D684 >--------------------------------------------------------------- ca478acc3825852320abc45ed6bc8efa4e869ff3 testsuite/tests/typecheck/should_compile/T4355.hs | 1 + testsuite/tests/typecheck/should_compile/T4355.stderr | 4 ++-- testsuite/tests/typecheck/should_compile/tc223.hs | 1 + testsuite/tests/typecheck/should_compile/tc232.hs | 8 ++++++++ testsuite/tests/typecheck/should_fail/tcfail126.hs | 1 + testsuite/tests/typecheck/should_run/T4809_IdentityT.hs | 4 ++++ testsuite/tests/typecheck/should_run/T4809_XMLGenerator.hs | 8 ++++++++ testsuite/tests/typecheck/should_run/T9497a-run.stderr | 1 + testsuite/tests/typecheck/should_run/T9497b-run.stderr | 1 + testsuite/tests/typecheck/should_run/T9497c-run.stderr | 1 + testsuite/tests/typecheck/should_run/tcrun045.stderr | 2 +- 11 files changed, 29 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/typecheck/should_compile/T4355.hs b/testsuite/tests/typecheck/should_compile/T4355.hs index 712430d..7aecd2a 100644 --- a/testsuite/tests/typecheck/should_compile/T4355.hs +++ b/testsuite/tests/typecheck/should_compile/T4355.hs @@ -1,3 +1,4 @@ +{-# OPTIONS_GHC -fno-warn-redundant-constraints -fno-warn-missing-methods #-} {-# LANGUAGE DeriveDataTypeable, ExistentialQuantification, RankNTypes, MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, FlexibleContexts, PatternGuards, DatatypeContexts #-} module T4355 where diff --git a/testsuite/tests/typecheck/should_compile/T4355.stderr b/testsuite/tests/typecheck/should_compile/T4355.stderr index af072e6..a977ce0 100644 --- a/testsuite/tests/typecheck/should_compile/T4355.stderr +++ b/testsuite/tests/typecheck/should_compile/T4355.stderr @@ -1,3 +1,3 @@ -T4355.hs:1:172: - Warning: -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language. +T4355.hs:2:172: Warning: + -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language. diff --git a/testsuite/tests/typecheck/should_compile/tc223.hs b/testsuite/tests/typecheck/should_compile/tc223.hs index bf04ba3..fc8a9d1 100644 --- a/testsuite/tests/typecheck/should_compile/tc223.hs +++ b/testsuite/tests/typecheck/should_compile/tc223.hs @@ -1,3 +1,4 @@ +{-# OPTIONS_GHC -fno-warn-deprecations #-} {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-} module Foo where diff --git a/testsuite/tests/typecheck/should_compile/tc232.hs b/testsuite/tests/typecheck/should_compile/tc232.hs index c9f23d4..0e6450b 100644 --- a/testsuite/tests/typecheck/should_compile/tc232.hs +++ b/testsuite/tests/typecheck/should_compile/tc232.hs @@ -1,3 +1,4 @@ +{-# OPTIONS_GHC -fno-warn-redundant-constraints #-} -- This one foxed the constraint solver (Lint error) -- See Trac #1494 @@ -8,6 +9,13 @@ import Control.Monad.State newtype L m r = L (StateT Int m r) +instance Functor (L m) where + fmap = undefined + +instance Applicative (L m) where + pure = undefined + (<*>) = undefined + instance Monad m => Monad (L m) where (>>=) = undefined return = undefined diff --git a/testsuite/tests/typecheck/should_fail/tcfail126.hs b/testsuite/tests/typecheck/should_fail/tcfail126.hs index 1ef2b48..20b0f55 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail126.hs +++ b/testsuite/tests/typecheck/should_fail/tcfail126.hs @@ -1,3 +1,4 @@ +{-# OPTIONS_GHC -fno-warn-redundant-constraints #-} {-# LANGUAGE RankNTypes, ExistentialQuantification #-} -- An interesting interaction of universals and existentials, prompted by diff --git a/testsuite/tests/typecheck/should_run/T4809_IdentityT.hs b/testsuite/tests/typecheck/should_run/T4809_IdentityT.hs index 879dada..0289dec 100644 --- a/testsuite/tests/typecheck/should_run/T4809_IdentityT.hs +++ b/testsuite/tests/typecheck/should_run/T4809_IdentityT.hs @@ -6,6 +6,7 @@ module T4809_IdentityT , XML(..) ) where +import Control.Applicative import Control.Monad (MonadPlus) import Control.Monad.Trans (MonadTrans(lift), MonadIO(liftIO)) import T4809_XMLGenerator (XMLGenT(..), EmbedAsChild(..), Name) @@ -20,6 +21,9 @@ data XML newtype IdentityT m a = IdentityT { runIdentityT :: m a } deriving (Functor, Monad, MonadIO, MonadPlus) +instance Monad m => Applicative (IdentityT m) where +instance Monad m => Alternative (IdentityT m) where + instance MonadTrans IdentityT where lift = IdentityT diff --git a/testsuite/tests/typecheck/should_run/T4809_XMLGenerator.hs b/testsuite/tests/typecheck/should_run/T4809_XMLGenerator.hs index 9ee37e8..1b5cbfe 100644 --- a/testsuite/tests/typecheck/should_run/T4809_XMLGenerator.hs +++ b/testsuite/tests/typecheck/should_run/T4809_XMLGenerator.hs @@ -18,6 +18,8 @@ ----------------------------------------------------------------------------- module T4809_XMLGenerator where +import Control.Applicative +import Control.Monad import Control.Monad.Trans import Control.Monad.Cont (MonadCont) import Control.Monad.Error (MonadError) @@ -35,6 +37,12 @@ newtype XMLGenT m a = XMLGenT (m a) deriving (Monad, Functor, MonadIO, MonadPlus, MonadWriter w, MonadReader r, MonadState s, MonadRWS r w s, MonadCont, MonadError e) +instance Monad m => Applicative (XMLGenT m) where + pure = return + (<*>) = ap + +instance Monad m => Alternative (XMLGenT m) where + -- | un-lift. unXMLGenT :: XMLGenT m a -> m a unXMLGenT (XMLGenT ma) = ma diff --git a/testsuite/tests/typecheck/should_run/T9497a-run.stderr b/testsuite/tests/typecheck/should_run/T9497a-run.stderr index aae24cf..192f78f 100644 --- a/testsuite/tests/typecheck/should_run/T9497a-run.stderr +++ b/testsuite/tests/typecheck/should_run/T9497a-run.stderr @@ -1,5 +1,6 @@ T9497a-run: T9497a-run.hs:2:8: Found hole ?_main? with type: IO () + Or perhaps ?_main? is mis-spelled, or not in scope Relevant bindings include main :: IO () (bound at T9497a-run.hs:2:1) In the expression: _main diff --git a/testsuite/tests/typecheck/should_run/T9497b-run.stderr b/testsuite/tests/typecheck/should_run/T9497b-run.stderr index 62d858f..a53262e 100644 --- a/testsuite/tests/typecheck/should_run/T9497b-run.stderr +++ b/testsuite/tests/typecheck/should_run/T9497b-run.stderr @@ -1,5 +1,6 @@ T9497b-run: T9497b-run.hs:2:8: Found hole ?_main? with type: IO () + Or perhaps ?_main? is mis-spelled, or not in scope Relevant bindings include main :: IO () (bound at T9497b-run.hs:2:1) In the expression: _main diff --git a/testsuite/tests/typecheck/should_run/T9497c-run.stderr b/testsuite/tests/typecheck/should_run/T9497c-run.stderr index be5d947..f991cd6 100644 --- a/testsuite/tests/typecheck/should_run/T9497c-run.stderr +++ b/testsuite/tests/typecheck/should_run/T9497c-run.stderr @@ -1,5 +1,6 @@ T9497c-run: T9497c-run.hs:2:8: Found hole ?_main? with type: IO () + Or perhaps ?_main? is mis-spelled, or not in scope Relevant bindings include main :: IO () (bound at T9497c-run.hs:2:1) In the expression: _main diff --git a/testsuite/tests/typecheck/should_run/tcrun045.stderr b/testsuite/tests/typecheck/should_run/tcrun045.stderr index 4017279..c7a6616 100644 --- a/testsuite/tests/typecheck/should_run/tcrun045.stderr +++ b/testsuite/tests/typecheck/should_run/tcrun045.stderr @@ -1,6 +1,6 @@ tcrun045.hs:24:1: Illegal implicit parameter ??imp::Int? - In the context: (?imp::Int) + In the context: ?imp::Int While checking the super-classes of class ?D? In the class declaration for ?D? From git at git.haskell.org Mon Mar 2 17:16:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 17:16:10 +0000 (UTC) Subject: [commit: ghc] master: `make test` in root directory now runs fulltest (31d4f2e) Message-ID: <20150302171610.993393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/31d4f2e9c89e22a91f98b4a4aa0f80af6b07b60f/ghc >--------------------------------------------------------------- commit 31d4f2e9c89e22a91f98b4a4aa0f80af6b07b60f Author: Thomas Miedema Date: Mon Mar 2 11:10:09 2015 -0600 `make test` in root directory now runs fulltest Summary: Currently, running `make test` in: / runs fast testsuite /testsuite doesn't work /testsuite/tests runs slow testsuite This commit: * changes `make test` in the ghc root directory to run the slow testsuite, just like it already does in `testsuite/tests` * adds some simple targets to `/testsuite`, that all delegate to `/testsuite/tests` * adds a new target `fasttest` to the toplevel Makefile, with a shorthand name `fast` (for consistency with /testsuite and /testsuite/tests) * declares some more targets PHONY for safety Wiki pages that need updating: * Building/StandardTargets * Buliding/RunningTests Reviewers: austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D685 >--------------------------------------------------------------- 31d4f2e9c89e22a91f98b4a4aa0f80af6b07b60f Makefile | 14 +++++++------- testsuite/Makefile | 14 ++++++++++++++ testsuite/mk/test.mk | 2 +- validate | 4 ++-- 4 files changed, 24 insertions(+), 10 deletions(-) diff --git a/Makefile b/Makefile index 2cc62b5..60853bc 100644 --- a/Makefile +++ b/Makefile @@ -25,6 +25,7 @@ install show: else +.PHONY: default default : all @: @@ -52,7 +53,7 @@ endif endif # No need to update makefiles for these targets: -REALGOALS=$(filter-out binary-dist binary-dist-prep bootstrapping-files framework-pkg clean clean_% distclean maintainer-clean show echo help test fulltest,$(MAKECMDGOALS)) +REALGOALS=$(filter-out binary-dist binary-dist-prep bootstrapping-files framework-pkg clean clean_% distclean maintainer-clean show echo help test fulltest fast fasttest,$(MAKECMDGOALS)) # configure touches certain files even if they haven't changed. This # can mean a lot of unnecessary recompilation after a re-configure, so @@ -65,7 +66,7 @@ REALGOALS=$(filter-out binary-dist binary-dist-prep bootstrapping-files framewor # NB. not the same as saying '%: ...', which doesn't do the right thing: # it does nothing if we specify a target that already exists. -.PHONY: $(REALGOALS) +.PHONY: $(REALGOALS) all $(REALGOALS) all: mk/config.mk.old mk/project.mk.old compiler/ghc.cabal.old ifneq "$(OMIT_PHASE_0)" "YES" @echo "===--- building phase 0" @@ -111,11 +112,10 @@ endif endif -.PHONY: test -test: +.PHONY: fasttest fast +fasttest fast: $(MAKE) -C testsuite/tests CLEANUP=1 OUTPUT_SUMMARY=../../testsuite_summary.txt fast -.PHONY: fulltest -fulltest: +.PHONY: fulltest test +fulltest test: $(MAKE) -C testsuite/tests CLEANUP=1 OUTPUT_SUMMARY=../../testsuite_summary.txt - diff --git a/testsuite/Makefile b/testsuite/Makefile index 401e30a..6ad3439 100644 --- a/testsuite/Makefile +++ b/testsuite/Makefile @@ -11,15 +11,29 @@ ifneq "$(MAKECMDGOALS)" "maintainer-clean" include $(TOP)/mk/boilerplate.mk +.PHONY: all boot test verbose accept fast list_broken + boot: $(MAKE) -C $(TOP)/timeout all all: $(MAKE) -C $(TOP)/tests all +test: + $(MAKE) -C $(TOP)/tests test + +verbose: + $(MAKE) -C $(TOP)/tests verbose + +accept: + $(MAKE) -C $(TOP)/tests accept + fast: $(MAKE) -C $(TOP)/tests fast +list_broken: + $(MAKE) -C $(TOP)/tests list_broken + endif endif endif diff --git a/testsuite/mk/test.mk b/testsuite/mk/test.mk index 0229cfd..42022cd 100644 --- a/testsuite/mk/test.mk +++ b/testsuite/mk/test.mk @@ -241,7 +241,7 @@ TESTS = TEST = WAY = -.PHONY: all boot test verbose accept fast +.PHONY: all boot test verbose accept fast list_broken all: test diff --git a/validate b/validate index 5954e96..109d521 100755 --- a/validate +++ b/validate @@ -229,11 +229,11 @@ SLOW) BINDIST="BINDIST=YES" ;; NORMAL) - MAKE_TEST_TARGET=test + MAKE_TEST_TARGET=fasttest BINDIST="BINDIST=YES" ;; FAST) - MAKE_TEST_TARGET=test + MAKE_TEST_TARGET=fasttest BINDIST="BINDIST=NO" ;; esac From git at git.haskell.org Mon Mar 2 17:16:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 17:16:13 +0000 (UTC) Subject: [commit: ghc] master: Removed unused constrained which causes build to fail with -Werror (efbd3eb) Message-ID: <20150302171613.6EE2D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/efbd3eb10a2741d45b0e25c98674c8da57dac5ab/ghc >--------------------------------------------------------------- commit efbd3eb10a2741d45b0e25c98674c8da57dac5ab Author: Tamar Christina Date: Mon Mar 2 11:10:37 2015 -0600 Removed unused constrained which causes build to fail with -Werror Summary: Unused Show constraint is cauzing validate build failures because of -Werror. Removing constraint solves the problem Test Plan: validate Reviewers: austin, hvr Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D690 >--------------------------------------------------------------- efbd3eb10a2741d45b0e25c98674c8da57dac5ab libraries/base/GHC/IO/Encoding/CodePage/API.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/GHC/IO/Encoding/CodePage/API.hs b/libraries/base/GHC/IO/Encoding/CodePage/API.hs index 966a690..7fd22cb 100644 --- a/libraries/base/GHC/IO/Encoding/CodePage/API.hs +++ b/libraries/base/GHC/IO/Encoding/CodePage/API.hs @@ -373,7 +373,7 @@ bSearch msg code ibuf mbuf target_to_elems = go go' mn mx | mn <= mx = go mn (mn + ((mx - mn) `div` 2)) mx | otherwise = error $ "bSearch(" ++ msg ++ "): search crossed! " ++ show (summaryBuffer ibuf, summaryBuffer mbuf, target_to_elems, mn, mx) -cpRecode :: forall from to. (Show from, Storable from) +cpRecode :: forall from to. Storable from => (Ptr from -> Int -> Ptr to -> Int -> IO (Either Bool Int)) -> (from -> IO Bool) -> Int -- ^ Maximum length of a complete translatable sequence in the input (e.g. 2 if the input is UTF-16, 1 if the input is a SBCS, 2 is the input is a DBCS). Must be at least 1. From git at git.haskell.org Mon Mar 2 18:27:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 18:27:22 +0000 (UTC) Subject: [commit: ghc] master: Typos in non-code (3197018) Message-ID: <20150302182722.BDE603A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3197018d4efbf7407577300b88897cef26f7f4c6/ghc >--------------------------------------------------------------- commit 3197018d4efbf7407577300b88897cef26f7f4c6 Author: Gabor Greif Date: Mon Mar 2 19:28:36 2015 +0100 Typos in non-code >--------------------------------------------------------------- 3197018d4efbf7407577300b88897cef26f7f4c6 compiler/typecheck/TcInstDcls.hs | 2 +- docs/users_guide/glasgow_exts.xml | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 9b07554..5ee6479 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -973,7 +973,7 @@ Notice that This is a bit of a hack, but works very nicely in practice. - * Note that if a method has a locally-polymorhic binding, there will + * Note that if a method has a locally-polymorphic binding, there will be yet another implication for that, generated by tcPolyCheck in tcMethodBody. E.g. class C a where diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 7bb2f68..edfdc84 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -6679,8 +6679,8 @@ level of the signature for f1. But in the case of of f2 we give a kind annotation in the forall (a:k) binding, and GHC therefore puts the kind forall right there too. This design decision makes default case (f1) -as polymorphic as possible; remember that a more polymorhic argument type (as in f2 -makes the overall function less polymorphic, because there are fewer accepable arguments. +as polymorphic as possible; remember that a more polymorphic argument type (as in f2 +makes the overall function less polymorphic, because there are fewer acceptable arguments. From git at git.haskell.org Mon Mar 2 22:05:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 22:05:11 +0000 (UTC) Subject: [commit: ghc] ghc-july: Give full-precision time for BEGIN_SAMPLE/END_SAMPLE. (807cb0c) Message-ID: <20150302220511.DF3E63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-july Link : http://ghc.haskell.org/trac/ghc/changeset/807cb0c4437d3e78cb29c4ba820aa74a7bc7c9c9/ghc >--------------------------------------------------------------- commit 807cb0c4437d3e78cb29c4ba820aa74a7bc7c9c9 Author: Edward Z. Yang Date: Mon Feb 23 20:02:25 2015 -0800 Give full-precision time for BEGIN_SAMPLE/END_SAMPLE. Summary: Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonmar, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D679 >--------------------------------------------------------------- 807cb0c4437d3e78cb29c4ba820aa74a7bc7c9c9 rts/ProfHeap.c | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/rts/ProfHeap.c b/rts/ProfHeap.c index 06b677c..8d3f408 100644 --- a/rts/ProfHeap.c +++ b/rts/ProfHeap.c @@ -356,11 +356,9 @@ void endProfiling( void ) static void printSample(rtsBool beginSample, StgDouble sampleValue) { - StgDouble fractionalPart, integralPart; - fractionalPart = modf(sampleValue, &integralPart); - fprintf(hp_file, "%s %" FMT_Word64 ".%02" FMT_Word64 "\n", + fprintf(hp_file, "%s %f\n", (beginSample ? "BEGIN_SAMPLE" : "END_SAMPLE"), - (StgWord64)integralPart, (StgWord64)(fractionalPart * 100)); + sampleValue); if (!beginSample) { fflush(hp_file); } From git at git.haskell.org Mon Mar 2 22:05:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 22:05:14 +0000 (UTC) Subject: [commit: ghc] ghc-july's head updated: Give full-precision time for BEGIN_SAMPLE/END_SAMPLE. (807cb0c) Message-ID: <20150302220514.AB2593A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'ghc-july' now includes: cecf036 Fix #10031 by inverting a critical test in kick_out. cf3e340 update submodule 276da79 Improve error message on typed holes, and user manual (Tradc #10040) 07ee96f Use strict atomicModifyIORef' (added in GHC 7.6). 92c9354 Fix #10017 daed18c Fix a profiling bug 78216e2 fix _FILE_OFFSET_BITS redefined warning on Solaris/i386 platform c88e112 Bring Match m_fun_id_infix through the renamer. d4f25cb GRHS with empty wherebinds gets wrong SrcSpan ae39c5c Add packageName to GHC.Generics.Datatype 7cf87fc Eta-expand argument to foldr in mapM_ for [] 73f976c Make -ddump-splices output to stdout (fixes #8796) 2f13cd8 Comments only da78af3 Comments only 111e587 Put parens around (ty :: kind) when pretty-printing TH syntax dda6528 Fix the nullary-type-class case for associated types 0f75a3f Test Trac #10041 43636e1 Fix Trac #10004: head [] exception when using recursive mdo 9bc13c0 Remove the *o pattern in testsuite/.gitignore a741e69 Provide default implementation of `Monad(return)` 83efb98 Replace .lhs with .hs in compiler comments e22282e Remove deprecated libraries/base/include/Typeable.h de9a836 Clarify the documentation for 'evaluate' a1db53c Add a workaround to allow older cabal-install to use ghc-7.10 d5a80db Add Uniquable instances for InstalledPackageId/SourcePackageId/PackageName 5d5abdc llvmGen: move to LLVM 3.6 exclusively 78833ca Don't overwrite input file by default f46360e Refactor the handling of quasi-quotes 1e651b9 Comments only 12698ff More comments and white space 1e58ed8 Add a couple of tcTraces around reify 1d982ba Do not complain about missing fields in Trac #10047 3568bf3 Do not share T9878.hs between test T9878 and T9878b 6ff3db9 nameIsLocalOrFrom should include interactive modules befe2d7 Fix #10079 by recurring after flattening exposes a TyConApp. d5cd94d Fix egregious typo in checkTauTvUpdate. 849e25c Propagate ReturnTvs in matchExpectedFunTys b45309f Comments and white space; plus structurally avoiding the previously "egregious bug" 6be91dd Tiny refactoring; no change in behaviour b96db75 Refactor decideQuantification 7fdded4 Improve documentation of 'trace' 36f2ad5 Comments only 5ab7518 Improve typechecking of RULEs, to account for type wildcard holes 6fa285d Move comments about evaluating the message to the top of the module 49d99eb Fix typo in error message 555eef1 Remove RAWCPP_FLAGS (Task #9094) 310b636 Add missing va_end to va_start a82364c Don't truncate traceEvents to 512 bytes (#8309) e7fab33 Improve outdated ghc-pkg cache warning (#9606) 08102b3 Delete vestigial external core code (#9402) 1b82619 Add configurable verbosity level to hpc 91d9530 Revert "Eta-expand argument to foldr in mapM_ for []" 9caf71a Do not clobber CPPFLAGS nor LDFLAGS, fixes #10093 6d17125 runghc: be explicit about ghc version (#9054) 32d1a8a Cleanup ghc-pkg 35d464b Typo in function name e9d72ce Fix #10045 ef391f8 Comments only 3f30912 fix T7600 run on bigendian platform 10fab31 Don't report instance constraints with fundeps as redundant 9c78d09 Add a bizarre corner-case to cgExpr (Trac #9964) f3e5c30 Comments only 5f675e5 Comments only 5094719 Comments only 547c40a [ci skip] comment typo d4b6453 Unbreak travis by installing llvm-3.6 1f60d63 {Data,Generic(1),MonadZip} instances for Identity b2be772 fix bus errors on SPARC caused by unalignment access to alloc_limit (fixes #10043) 0fa2072 Error out on `Main` without `main` in GHCi (#7765) bbb57a6 Make top-level "configure" accept and propagate --with-curses-{includes,libraries} to libraries fd581a7 Fix for ticket #10078: ensure that tcPluginStop is called even in case of type errors 30dc59e Always ignore user-package-db when running tests a0ef626 Declare some Makefile targets to be PHONY a293925 rts/linker: ignore unknown PE sections 47175e0 Show '#' on unboxed literals 9a1c8d9 docs: add INSTALL.md to root dir (#9926) c3f9eb4 docs: Flatten MAKEHELP/SUBMAKEHELP 266fa70 base: fix broken link (#10088) 9004f0d Fix build bogons due to missing separator 4f467b2 base: Fix (**) implementation for Data.Complex a5a4c25 Provide a faster implementation for the Read Integer instance d1d02e8 testsuite: update .gitignore bb3b71a System.IO.Error: Fix a documentation link to Control.Exception.Exception 26a85bd Comment typo aead019 driver: split -fwarn-unused-binds into 3 flags (fixes #17) 5be8ed4 Emulate GMP 5+ operations for GMP 4.x compat 00c971e Update submodule to Cabal 1.22.1.0 release 7a3d7c0 Fix comments, and a little reformatting ea3b4cf Axe ModFinderCache, folding it into a generalized FinderCache. b7f7889 AllocationLimitExceeded should be a child of SomeAsyncException 1def53f Update process submodule to 1.2.3.0 snapshot c5977c2 Extend the docs for Data.List.transpose 7727371 Comments only 9b3239f Improve comments on coreView/tcView, and combine coreExpandTyCon/tcExpandTyCon 104c0ad Test Trac #10112 52dfa61 Comments only cabe174 Two kind-polymorphism fixes (Trac #10122) d2e6a3b Improve documentation of infinite inlining bug 5692643 Show record construction/update without parens 6cdccb4 fix typos in coreSyn 1dfab7a Fix detection of llvm-x.x ca478ac Fix typecheck tests (--slow) 31d4f2e `make test` in root directory now runs fulltest efbd3eb Removed unused constrained which causes build to fail with -Werror 3197018 Typos in non-code 807cb0c Give full-precision time for BEGIN_SAMPLE/END_SAMPLE. From git at git.haskell.org Mon Mar 2 22:11:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 22:11:06 +0000 (UTC) Subject: [commit: ghc] master: Small emitCmmSwitch/emitCmmLitSwitch refactoring (5bdfb9b) Message-ID: <20150302221106.89A243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5bdfb9beb28206a014d817ddf15f1c6c36d79a69/ghc >--------------------------------------------------------------- commit 5bdfb9beb28206a014d817ddf15f1c6c36d79a69 Author: Joachim Breitner Date: Mon Mar 2 21:35:05 2015 +0100 Small emitCmmSwitch/emitCmmLitSwitch refactoring both use the same logic to divide, so put it in divideBranches :: Ord a => [(a,b)] -> ([(a,b)], a, [(a,b)]) >--------------------------------------------------------------- 5bdfb9beb28206a014d817ddf15f1c6c36d79a69 compiler/codeGen/StgCmmUtils.hs | 23 +++++++++++------------ 1 file changed, 11 insertions(+), 12 deletions(-) diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index 763177f..98295c9 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -626,14 +626,18 @@ mk_switch tag_expr branches mb_deflt lo_tag hi_tag via_C -- lo_tag <= mid_tag < hi_tag -- lo_branches have tags < mid_tag -- hi_branches have tags >= mid_tag + (lo_branches, mid_tag, hi_branches) = divideBranches branches - (mid_tag,_) = branches !! (n_branches `div` 2) - -- 2 branches => n_branches `div` 2 = 1 - -- => branches !! 1 give the *second* tag - -- There are always at least 2 branches here +divideBranches :: Ord a => [(a,b)] -> ([(a,b)], a, [(a,b)]) +divideBranches branches = (lo_branches, mid, hi_branches) + where + -- 2 branches => n_branches `div` 2 = 1 + -- => branches !! 1 give the *second* tag + -- There are always at least 2 branches here + (mid,_) = branches !! (length branches `div` 2) (lo_branches, hi_branches) = span is_lo branches - is_lo (t,_) = t < mid_tag + is_lo (t,_) = t < mid -------------- emitCmmLitSwitch :: CmmExpr -- Tag to switch on @@ -681,7 +685,7 @@ mk_lit_switch scrut deflt bounds [(lit,blk)] where -- If the bounds already imply scrut == lit, then we can skip the final check (#10129) l `onlyWithinBounds'` (Just lo, Just hi) = l `onlyWithinBounds` (lo, hi) - l `onlyWithinBounds'` _ = False + _ `onlyWithinBounds'` _ = False mk_lit_switch scrut deflt_blk_id (lo_bound, hi_bound) branches = do dflags <- getDynFlags @@ -689,12 +693,7 @@ mk_lit_switch scrut deflt_blk_id (lo_bound, hi_bound) branches hi_blk <- mk_lit_switch scrut deflt_blk_id bounds_hi hi_branches mkCmmIfThenElse (cond dflags) lo_blk hi_blk where - n_branches = length branches - (mid_lit,_) = branches !! (n_branches `div` 2) - -- See notes above re mid_tag - - (lo_branches, hi_branches) = span is_lo branches - is_lo (t,_) = t < mid_lit + (lo_branches, mid_lit, hi_branches) = divideBranches branches bounds_lo = (lo_bound, Just mid_lit) bounds_hi = (Just mid_lit, hi_bound) From git at git.haskell.org Mon Mar 2 22:11:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 22:11:09 +0000 (UTC) Subject: [commit: ghc] master: Improve if-then-else tree for cases on literal values (c3eee14) Message-ID: <20150302221109.590873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c3eee14d31585445d4a7eff5b6c69a815b911059/ghc >--------------------------------------------------------------- commit c3eee14d31585445d4a7eff5b6c69a815b911059 Author: Joachim Breitner Date: Mon Mar 2 21:20:24 2015 +0100 Improve if-then-else tree for cases on literal values Previously, in the branch of the if-then-else tree, it would emit a final check if the scrut matches the alternative, even if earlier comparisons alread imply this equality. By keeping track of the bounds we can skip this check. Of course this is only sound for integer types. This closes #10129. Differential Revision: https://phabricator.haskell.org/D693 >--------------------------------------------------------------- c3eee14d31585445d4a7eff5b6c69a815b911059 compiler/basicTypes/Literal.hs | 11 +++++++++++ compiler/codeGen/StgCmmUtils.hs | 29 +++++++++++++++++++++++------ 2 files changed, 34 insertions(+), 6 deletions(-) diff --git a/compiler/basicTypes/Literal.hs b/compiler/basicTypes/Literal.hs index cb0be03..8198f81 100644 --- a/compiler/basicTypes/Literal.hs +++ b/compiler/basicTypes/Literal.hs @@ -30,6 +30,7 @@ module Literal , inIntRange, inWordRange, tARGET_MAX_INT, inCharRange , isZeroLit , litFitsInChar + , onlyWithinBounds -- ** Coercions , word2IntLit, int2WordLit @@ -359,6 +360,16 @@ litIsLifted :: Literal -> Bool litIsLifted (LitInteger {}) = True litIsLifted _ = False +-- | x `onlyWithinBounds` (l,h) is true if l <= y < h ==> x = y +onlyWithinBounds :: Literal -> (Literal, Literal) -> Bool +onlyWithinBounds (MachChar x) (MachChar l, MachChar h) = x == l && succ x == h +onlyWithinBounds (MachInt x) (MachInt l, MachInt h) = x == l && succ x == h +onlyWithinBounds (MachWord x) (MachWord l, MachWord h) = x == l && succ x == h +onlyWithinBounds (MachInt64 x) (MachInt64 l, MachInt64 h) = x == l && succ x == h +onlyWithinBounds (MachWord64 x) (MachWord64 l, MachWord64 h) = x == l && succ x == h +onlyWithinBounds _ _ = False + + {- Types ~~~~~ diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index 5e8944d..763177f 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -652,14 +652,21 @@ emitCmmLitSwitch scrut branches deflt = do join_lbl <- newLabelC deflt_lbl <- label_code join_lbl deflt branches_lbls <- label_branches join_lbl branches - emit =<< mk_lit_switch scrut' deflt_lbl + emit =<< mk_lit_switch scrut' deflt_lbl noBound (sortBy (comparing fst) branches_lbls) emitLabel join_lbl +-- | lower bound (inclusive), upper bound (exclusive) +type LitBound = (Maybe Literal, Maybe Literal) + +noBound :: LitBound +noBound = (Nothing, Nothing) + mk_lit_switch :: CmmExpr -> BlockId + -> LitBound -> [(Literal,BlockId)] -> FCode CmmAGraph -mk_lit_switch scrut deflt [(lit,blk)] +mk_lit_switch scrut deflt bounds [(lit,blk)] = do dflags <- getDynFlags let @@ -667,12 +674,19 @@ mk_lit_switch scrut deflt [(lit,blk)] cmm_ty = cmmLitType dflags cmm_lit rep = typeWidth cmm_ty ne = if isFloatType cmm_ty then MO_F_Ne rep else MO_Ne rep - return (mkCbranch (CmmMachOp ne [scrut, CmmLit cmm_lit]) deflt blk) -mk_lit_switch scrut deflt_blk_id branches + return $ if lit `onlyWithinBounds'` bounds + then mkBranch blk + else mkCbranch (CmmMachOp ne [scrut, CmmLit cmm_lit]) deflt blk + where + -- If the bounds already imply scrut == lit, then we can skip the final check (#10129) + l `onlyWithinBounds'` (Just lo, Just hi) = l `onlyWithinBounds` (lo, hi) + l `onlyWithinBounds'` _ = False + +mk_lit_switch scrut deflt_blk_id (lo_bound, hi_bound) branches = do dflags <- getDynFlags - lo_blk <- mk_lit_switch scrut deflt_blk_id lo_branches - hi_blk <- mk_lit_switch scrut deflt_blk_id hi_branches + lo_blk <- mk_lit_switch scrut deflt_blk_id bounds_lo lo_branches + hi_blk <- mk_lit_switch scrut deflt_blk_id bounds_hi hi_branches mkCmmIfThenElse (cond dflags) lo_blk hi_blk where n_branches = length branches @@ -682,6 +696,9 @@ mk_lit_switch scrut deflt_blk_id branches (lo_branches, hi_branches) = span is_lo branches is_lo (t,_) = t < mid_lit + bounds_lo = (lo_bound, Just mid_lit) + bounds_hi = (Just mid_lit, hi_bound) + cond dflags = CmmMachOp (mkLtOp dflags mid_lit) [scrut, CmmLit (mkSimpleLit dflags mid_lit)] From git at git.haskell.org Mon Mar 2 22:11:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 22:11:36 +0000 (UTC) Subject: [commit: ghc] master: Give full-precision time for BEGIN_SAMPLE/END_SAMPLE. (1da3bbd) Message-ID: <20150302221136.4EC0C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1da3bbd2bd82ea11f8a1d760385df84708bbea63/ghc >--------------------------------------------------------------- commit 1da3bbd2bd82ea11f8a1d760385df84708bbea63 Author: Edward Z. Yang Date: Mon Feb 23 20:02:25 2015 -0800 Give full-precision time for BEGIN_SAMPLE/END_SAMPLE. Summary: Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonmar, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D679 >--------------------------------------------------------------- 1da3bbd2bd82ea11f8a1d760385df84708bbea63 rts/ProfHeap.c | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/rts/ProfHeap.c b/rts/ProfHeap.c index 06b677c..8d3f408 100644 --- a/rts/ProfHeap.c +++ b/rts/ProfHeap.c @@ -356,11 +356,9 @@ void endProfiling( void ) static void printSample(rtsBool beginSample, StgDouble sampleValue) { - StgDouble fractionalPart, integralPart; - fractionalPart = modf(sampleValue, &integralPart); - fprintf(hp_file, "%s %" FMT_Word64 ".%02" FMT_Word64 "\n", + fprintf(hp_file, "%s %f\n", (beginSample ? "BEGIN_SAMPLE" : "END_SAMPLE"), - (StgWord64)integralPart, (StgWord64)(fractionalPart * 100)); + sampleValue); if (!beginSample) { fflush(hp_file); } From git at git.haskell.org Mon Mar 2 22:15:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 22:15:23 +0000 (UTC) Subject: [commit: ghc] branch 'wip/D694' created Message-ID: <20150302221523.2E8C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/D694 Referencing: d2625192e56dbee1f320172c593c9f0653f72bb0 From git at git.haskell.org Mon Mar 2 22:15:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 22:15:26 +0000 (UTC) Subject: [commit: ghc] wip/D694: Use 64bit relocations (d262519) Message-ID: <20150302221526.08FD23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/D694 Link : http://ghc.haskell.org/trac/ghc/changeset/d2625192e56dbee1f320172c593c9f0653f72bb0/ghc >--------------------------------------------------------------- commit d2625192e56dbee1f320172c593c9f0653f72bb0 Author: Joachim Breitner Date: Mon Mar 2 22:24:36 2015 +0100 Use 64bit relocations Summary: according to the comments, this was not possible with ancient (pre 2006) versions of binutils. Even Debian stable has newer versions since a whilte. Please have a close look if you know something about this; I basically removed code by looking at the code around it, but do not necessarily know what I am doing here. Test Plan: Run validate on Harbormaster Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D694 >--------------------------------------------------------------- d2625192e56dbee1f320172c593c9f0653f72bb0 compiler/nativeGen/X86/CodeGen.hs | 11 +---------- compiler/nativeGen/X86/Ppr.hs | 24 +----------------------- includes/rts/storage/InfoTables.h | 14 -------------- 3 files changed, 2 insertions(+), 47 deletions(-) diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs index 531213d..d797b80 100644 --- a/compiler/nativeGen/X86/CodeGen.hs +++ b/compiler/nativeGen/X86/CodeGen.hs @@ -2616,17 +2616,8 @@ genSwitch dflags expr ids JMP_TBL (OpReg tableReg) ids Text lbl ] _ -> - -- HACK: On x86_64 binutils<2.17 is only able - -- to generate PC32 relocations, hence we only - -- get 32-bit offsets in the jump table. As - -- these offsets are always negative we need - -- to properly sign extend them to 64-bit. - -- This hack should be removed in conjunction - -- with the hack in PprMach.hs/pprDataItem - -- once binutils 2.17 is standard. e_code `appOL` t_code `appOL` toOL [ - MOVSxL II32 op (OpReg reg), - ADD (intSize (wordWidth dflags)) (OpReg reg) (OpReg tableReg), + ADD (intSize (wordWidth dflags)) op (OpReg tableReg), JMP_TBL (OpReg tableReg) ids ReadOnlyData lbl ] | otherwise diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs index 7022e59..9d290f2 100644 --- a/compiler/nativeGen/X86/Ppr.hs +++ b/compiler/nativeGen/X86/Ppr.hs @@ -470,29 +470,7 @@ pprDataItem' dflags lit <> int (fromIntegral (fromIntegral (x `shiftR` 32) :: Word32))] _ -> panic "X86.Ppr.ppr_item: no match for II64" - | otherwise -> - [ptext (sLit "\t.quad\t") <> pprImm imm] - _ - | target32Bit platform -> - [ptext (sLit "\t.quad\t") <> pprImm imm] - | otherwise -> - -- x86_64: binutils can't handle the R_X86_64_PC64 - -- relocation type, which means we can't do - -- pc-relative 64-bit addresses. Fortunately we're - -- assuming the small memory model, in which all such - -- offsets will fit into 32 bits, so we have to stick - -- to 32-bit offset fields and modify the RTS - -- appropriately - -- - -- See Note [x86-64-relative] in includes/rts/storage/InfoTables.h - -- - case lit of - -- A relative relocation: - CmmLabelDiffOff _ _ _ -> - [ptext (sLit "\t.long\t") <> pprImm imm, - ptext (sLit "\t.long\t0")] - _ -> - [ptext (sLit "\t.quad\t") <> pprImm imm] + _ -> [ptext (sLit "\t.quad\t") <> pprImm imm] ppr_item _ _ = panic "X86.Ppr.ppr_item: no match" diff --git a/includes/rts/storage/InfoTables.h b/includes/rts/storage/InfoTables.h index 3890d49..250f7c7 100644 --- a/includes/rts/storage/InfoTables.h +++ b/includes/rts/storage/InfoTables.h @@ -16,23 +16,9 @@ relative to the info pointer, so that we can generate position-independent code. - Note [x86-64-relative] - There is a complication on the x86_64 platform, where pointeres are - 64 bits, but the tools don't support 64-bit relative relocations. - However, the default memory model (small) ensures that all symbols - have values in the lower 2Gb of the address space, so offsets all - fit in 32 bits. Hence we can use 32-bit offset fields. - - Somewhere between binutils-2.16.1 and binutils-2.16.91.0.6, - support for 64-bit PC-relative relocations was added, so maybe this - hackery can go away sometime. ------------------------------------------------------------------------- */ -#if x86_64_TARGET_ARCH -#define OFFSET_FIELD(n) StgHalfInt n; StgHalfWord __pad_##n -#else #define OFFSET_FIELD(n) StgInt n -#endif /* ----------------------------------------------------------------------------- Profiling info From git at git.haskell.org Mon Mar 2 22:52:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Mar 2015 22:52:23 +0000 (UTC) Subject: [commit: ghc] master: Cite the TrieMap idea [skip-ci] (f6609b0) Message-ID: <20150302225223.1BC503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f6609b0ed031135b8402fd179b3370958698ecb2/ghc >--------------------------------------------------------------- commit f6609b0ed031135b8402fd179b3370958698ecb2 Author: Edward Z. Yang Date: Mon Mar 2 14:54:30 2015 -0800 Cite the TrieMap idea [skip-ci] Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- f6609b0ed031135b8402fd179b3370958698ecb2 compiler/coreSyn/TrieMap.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/compiler/coreSyn/TrieMap.hs b/compiler/coreSyn/TrieMap.hs index 96db166..dad00e1 100644 --- a/compiler/coreSyn/TrieMap.hs +++ b/compiler/coreSyn/TrieMap.hs @@ -47,6 +47,12 @@ The code is very regular and boilerplate-like, but there is some neat handling of *binders*. In effect they are deBruijn numbered on the fly. +The regular pattern for handling TrieMaps on data structures was first +described (to my knowledge) in Connelly and Morris's 1995 paper "A +generalization of the Trie Data Structure"; there is also an accessible +description of the idea in Okasaki's book "Purely Functional Data +Structures", Section 10.3.2 + ************************************************************************ * * The TrieMap class From git at git.haskell.org Tue Mar 3 13:00:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Mar 2015 13:00:11 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Emulate GMP 5+ operations for GMP 4.x compat (8827ade) Message-ID: <20150303130011.294E33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/8827ade65eee66c42ff6aa11dff20f9b7bece3e2/ghc >--------------------------------------------------------------- commit 8827ade65eee66c42ff6aa11dff20f9b7bece3e2 Author: Herbert Valerio Riedel Date: Sun Feb 22 17:50:07 2015 +0100 Emulate GMP 5+ operations for GMP 4.x compat The following operations are only (officially) available starting with GMP 5.0: - `mpn_and_n` - `mpn_andn_n` - `mpn_ior_n` - `mpn_xor_n` In order to properly support GMP 4.x, we simply emulate those operation in terms of `mpz_*` operations available in GMP 4.x (unless GMP>=5.x available, obviously) while incurring some overhead. Ideally, GMP 4.x environments will reach their EOL in the foreseeable future... This fixes #10003 Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D675 (cherry picked from commit 5be8ed4da1963ed2d45a65fb61d761c977707cce) >--------------------------------------------------------------- 8827ade65eee66c42ff6aa11dff20f9b7bece3e2 libraries/integer-gmp2/cbits/wrappers.c | 80 ++++++++++++++++++++++++++ libraries/integer-gmp2/src/GHC/Integer/Type.hs | 8 +-- 2 files changed, 84 insertions(+), 4 deletions(-) diff --git a/libraries/integer-gmp2/cbits/wrappers.c b/libraries/integer-gmp2/cbits/wrappers.c index 4b710dc..1736efd 100644 --- a/libraries/integer-gmp2/cbits/wrappers.c +++ b/libraries/integer-gmp2/cbits/wrappers.c @@ -750,3 +750,83 @@ integer_gmp_invert_word(const mp_limb_t x0, const mp_limb_t m0) return r0; } + + +/* Wrappers for GMP 4.x compat + * + * In GMP 5.0 the following operations were added: + * + * mpn_sqr, mpn_and_n, mpn_ior_n, mpn_xor_n, mpn_nand_n, mpn_nior_n, + * mpn_xnor_n, mpn_andn_n, mpn_iorn_n, mpn_com, mpn_neg, mpn_copyi, + * mpn_copyd, mpn_zero + * + * We use some of those, but for GMP 4.x compatibility we need to + * emulate those (while incurring some overhead). + */ +#if __GNU_MP_VERSION < 5 + +#define MPN_LOGIC_OP_WRAPPER(MPN_WRAPPER, MPZ_OP) \ +void \ +MPN_WRAPPER(mp_limb_t *rp, const mp_limb_t *s1p, \ + const mp_limb_t *s2p, mp_size_t n) \ +{ \ + assert(n > 0); \ + \ + const mpz_t s1 = CONST_MPZ_INIT(s1p, n); \ + const mpz_t s2 = CONST_MPZ_INIT(s2p, n); \ + \ + mpz_t r; \ + mpz_init (r); \ + MPZ_OP (r, s1, s2); \ + \ + const mp_size_t rn = r[0]._mp_size; \ + memset (rp, 0, n*sizeof(mp_limb_t)); \ + memcpy (rp, r[0]._mp_d, mp_size_minabs(rn,n)*sizeof(mp_limb_t)); \ + \ + mpz_clear (r); \ +} + +static void +__mpz_andn(mpz_t r, const mpz_t s1, const mpz_t s2) +{ + mpz_t s2c; + mpz_init (s2c); + mpz_com (s2c, s2); + mpz_and (r, s1, s2c); + mpz_clear (s2c); +} + +MPN_LOGIC_OP_WRAPPER(integer_gmp_mpn_and_n, mpz_and) +MPN_LOGIC_OP_WRAPPER(integer_gmp_mpn_andn_n, __mpz_andn) +MPN_LOGIC_OP_WRAPPER(integer_gmp_mpn_ior_n, mpz_ior) +MPN_LOGIC_OP_WRAPPER(integer_gmp_mpn_xor_n, mpz_xor) + +#else /* __GNU_MP_VERSION >= 5 */ +void +integer_gmp_mpn_and_n(mp_limb_t *rp, const mp_limb_t *s1p, + const mp_limb_t *s2p, mp_size_t n) +{ + mpn_and_n(rp, s1p, s2p, n); +} + +void +integer_gmp_mpn_andn_n(mp_limb_t *rp, const mp_limb_t *s1p, + const mp_limb_t *s2p, mp_size_t n) +{ + mpn_andn_n(rp, s1p, s2p, n); +} + +void +integer_gmp_mpn_ior_n(mp_limb_t *rp, const mp_limb_t *s1p, + const mp_limb_t *s2p, mp_size_t n) +{ + mpn_ior_n(rp, s1p, s2p, n); +} + +void +integer_gmp_mpn_xor_n(mp_limb_t *rp, const mp_limb_t *s1p, + const mp_limb_t *s2p, mp_size_t n) +{ + mpn_xor_n(rp, s1p, s2p, n); +} +#endif diff --git a/libraries/integer-gmp2/src/GHC/Integer/Type.hs b/libraries/integer-gmp2/src/GHC/Integer/Type.hs index e202855..5670bb4 100644 --- a/libraries/integer-gmp2/src/GHC/Integer/Type.hs +++ b/libraries/integer-gmp2/src/GHC/Integer/Type.hs @@ -1575,25 +1575,25 @@ foreign import ccall unsafe "integer_gmp_mpn_lshift" -- void mpn_and_n (mp_limb_t *rp, const mp_limb_t *s1p, const mp_limb_t *s2p, -- mp_size_t n) -foreign import ccall unsafe "gmp.h __gmpn_and_n" +foreign import ccall unsafe "integer_gmp_mpn_and_n" c_mpn_and_n :: MutableByteArray# s -> ByteArray# -> ByteArray# -> GmpSize# -> IO () -- void mpn_andn_n (mp_limb_t *rp, const mp_limb_t *s1p, const mp_limb_t *s2p, -- mp_size_t n) -foreign import ccall unsafe "gmp.h __gmpn_andn_n" +foreign import ccall unsafe "integer_gmp_mpn_andn_n" c_mpn_andn_n :: MutableByteArray# s -> ByteArray# -> ByteArray# -> GmpSize# -> IO () -- void mpn_ior_n (mp_limb_t *rp, const mp_limb_t *s1p, const mp_limb_t *s2p, -- mp_size_t n) -foreign import ccall unsafe "gmp.h __gmpn_ior_n" +foreign import ccall unsafe "integer_gmp_mpn_ior_n" c_mpn_ior_n :: MutableByteArray# s -> ByteArray# -> ByteArray# -> GmpSize# -> IO () -- void mpn_xor_n (mp_limb_t *rp, const mp_limb_t *s1p, const mp_limb_t *s2p, -- mp_size_t n) -foreign import ccall unsafe "gmp.h __gmpn_xor_n" +foreign import ccall unsafe "integer_gmp_mpn_xor_n" c_mpn_xor_n :: MutableByteArray# s -> ByteArray# -> ByteArray# -> GmpSize# -> IO () From git at git.haskell.org Tue Mar 3 13:25:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Mar 2015 13:25:49 +0000 (UTC) Subject: [commit: ghc] master: Replaced SEH handles with VEH handlers which should work uniformly across x86 and x64 (5200bde) Message-ID: <20150303132549.7F3DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5200bdeb26c5ec98739b14b10fc8907296bceeb9/ghc >--------------------------------------------------------------- commit 5200bdeb26c5ec98739b14b10fc8907296bceeb9 Author: Tamar Christina Date: Tue Mar 3 07:20:55 2015 -0600 Replaced SEH handles with VEH handlers which should work uniformly across x86 and x64 Summary: On Windows, the default action for things like division by zero and segfaults is to pop up a Dr. Watson error reporting dialog if the exception is unhandled by the user code. This is a pain when we are SSHed into a Windows machine, or when we want to debug a problem with gdb (gdb will get a first and second chance to handle the exception, but if it doesn't the pop-up will show). veh_excn provides two macros, `BEGIN_CATCH` and `END_CATCH`, which will catch such exceptions in the entire process and die by printing a message and calling `stg_exit(1)`. Previously this code was handled using SEH (Structured Exception Handlers) however each compiler and platform have different ways of dealing with SEH. `MSVC` compilers have the keywords `__try`, `__catch` and `__except` to have the compiler generate the appropriate SEH handler code for you. `MinGW` compilers have no such keywords and require you to manually set the SEH Handlers, however because SEH is implemented differently in x86 and x64 the methods to use them in GCC differs. `x86`: SEH is based on the stack, the SEH handlers are available at `FS[0]`. On startup one would only need to add a new handler there. This has a number of issues such as hard to share handlers and it can be exploited. `x64`: In order to fix the issues with the way SEH worked in x86, on x64 SEH handlers are statically compiled and added to the .pdata section by the compiler. Instead of being thread global they can now be Image global since you have to specify the `RVA` of the region of code that the handlers govern. You can on x64 Dynamically allocate SEH handlers, but it seems that (based on experimentation and it's very under-documented) that the dynamic calls cannot override static SEH handlers in the .pdata section. Because of this and because GHC no longer needs to support < windows XP, the better alternative for handling errors would be using the in XP introduced VEH. The bonus is because VEH (Vectored Exception Handler) are a runtime construct the API is the same for both x86 and x64 (note that the Context object does contain CPU specific structures) and the calls are the same cross compilers. Which means this file can be simplified quite a bit. Using VEH also means we don't have to worry about the dynamic code generated by GHCi. Test Plan: Prior to this diff the tests for `derefnull` and `divbyzero` seem to have been disabled for windows. To reproduce the issue on x64: 1) open ghci 2) import GHC.Base 3) run: 1 `divInt` 0 which should lead to ghci crashing an a watson error box displaying. After applying the patch, run: make TEST="derefnull divbyzero" on both x64 and x86 builds of ghc to verify fix. Reviewers: simonmar, austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D691 GHC Trac Issues: #6079 >--------------------------------------------------------------- 5200bdeb26c5ec98739b14b10fc8907296bceeb9 rts/Excn.h | 34 ++++++ rts/RtsMain.c | 123 +++++++++------------ rts/ghc.mk | 14 +-- rts/win32/OSMem.c | 2 - rts/win32/OSThreads.c | 2 - rts/win32/Ticker.c | 1 - rts/win32/seh_excn.c | 45 -------- rts/win32/seh_excn.h | 92 --------------- rts/win32/veh_excn.c | 100 +++++++++++++++++ rts/win32/veh_excn.h | 73 ++++++++++++ testsuite/tests/rts/all.T | 18 ++- ...w32 => derefnull.stdout-x86_64-unknown-mingw32} | 0 ...w32 => divbyzero.stdout-x86_64-unknown-mingw32} | 0 13 files changed, 276 insertions(+), 228 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5200bdeb26c5ec98739b14b10fc8907296bceeb9 From git at git.haskell.org Tue Mar 3 13:25:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Mar 2015 13:25:53 +0000 (UTC) Subject: [commit: ghc] master: Pretty-print # on unboxed literals in core (89458eb) Message-ID: <20150303132553.C1D9E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/89458eba5721de1b6b3378415f26e110bab8cc0f/ghc >--------------------------------------------------------------- commit 89458eba5721de1b6b3378415f26e110bab8cc0f Author: Thomas Miedema Date: Tue Mar 3 07:21:32 2015 -0600 Pretty-print # on unboxed literals in core Summary: Ticket #10104 dealt with showing the '#'s on types with unboxed fields. This commit pretty prints the '#'s on unboxed literals in core output. Test Plan: simplCore/should_compile/T8274 Reviewers: jstolarek, simonpj, austin Reviewed By: simonpj, austin Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D678 GHC Trac Issues: #8274 >--------------------------------------------------------------- 89458eba5721de1b6b3378415f26e110bab8cc0f compiler/basicTypes/Literal.hs | 67 ++++++++++++++++------ compiler/hsSyn/HsLit.hs | 17 +++--- compiler/prelude/PrelRules.hs | 10 ++-- compiler/utils/Outputable.hs | 27 ++++++++- .../tests/deriving/should_run/drvrun017.stdout | 2 +- testsuite/tests/simplCore/should_compile/Makefile | 8 ++- .../tests/simplCore/should_compile/T3055.stdout | 2 +- .../tests/simplCore/should_compile/T3717.stderr | 4 +- .../tests/simplCore/should_compile/T3772.stdout | 7 ++- .../tests/simplCore/should_compile/T4908.stderr | 12 ++-- .../tests/simplCore/should_compile/T4918.stdout | 4 +- .../tests/simplCore/should_compile/T4930.stderr | 10 ++-- .../tests/simplCore/should_compile/T7360.stderr | 6 +- testsuite/tests/simplCore/should_compile/T8274.hs | 10 ++++ .../tests/simplCore/should_compile/T8274.stdout | 2 + .../tests/simplCore/should_compile/T8832.stdout | 20 +++---- .../simplCore/should_compile/T8832.stdout-ws-32 | 16 +++--- testsuite/tests/simplCore/should_compile/all.T | 3 +- .../simplCore/should_compile/spec-inline.stderr | 34 +++++------ 19 files changed, 169 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 89458eba5721de1b6b3378415f26e110bab8cc0f From git at git.haskell.org Tue Mar 3 13:25:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Mar 2015 13:25:57 +0000 (UTC) Subject: [commit: ghc] master: Add various instances to newtypes in Data.Monoid (4e6bcc2) Message-ID: <20150303132557.043B83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4e6bcc2c8134f9c1ba7d715b3206130f23c529fb/ghc >--------------------------------------------------------------- commit 4e6bcc2c8134f9c1ba7d715b3206130f23c529fb Author: Oleg Grenrus Date: Tue Mar 3 07:21:43 2015 -0600 Add various instances to newtypes in Data.Monoid Summary: Add Functor instances for Dual, Sum and Product Add Foldable instances for Dual, Sum and Product Add Traversable instances for Dual, Sum and Product Add Foldable and Traversable instances for First and Last Add Applicative, Monad instances to Dual, Sum, Product Add MonadFix to Data.Monoid wrappers Derive Data for Identity Add Data instances to Data.Monoid wrappers Add Data (Alt f a) instance Reviewers: ekmett, dfeuer, hvr, austin Reviewed By: dfeuer, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D673 GHC Trac Issues: #10107 >--------------------------------------------------------------- 4e6bcc2c8134f9c1ba7d715b3206130f23c529fb libraries/base/Control/Monad/Fix.hs | 18 ++++ libraries/base/Data/Data.hs | 113 ++++++++++++++++++++- libraries/base/Data/Foldable.hs | 60 +++++++++++ libraries/base/Data/Monoid.hs | 33 ++++++ libraries/base/Data/Traversable.hs | 16 +++ .../tests/annotations/should_fail/annfail10.stderr | 25 +++-- .../tests/ghci.debugger/scripts/break006.stderr | 22 ++-- testsuite/tests/typecheck/should_fail/T5095.stderr | 15 +++ 8 files changed, 281 insertions(+), 21 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4e6bcc2c8134f9c1ba7d715b3206130f23c529fb From git at git.haskell.org Tue Mar 3 18:43:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Mar 2015 18:43:20 +0000 (UTC) Subject: [commit: ghc] master: Don't use deriveUnique *twice* in flattenTys. (a0cea7b) Message-ID: <20150303184320.213A23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a0cea7ba9f14a193f31f057371d104c2dc0b7d80/ghc >--------------------------------------------------------------- commit a0cea7ba9f14a193f31f057371d104c2dc0b7d80 Author: Richard Eisenberg Date: Tue Mar 3 12:55:54 2015 -0500 Don't use deriveUnique *twice* in flattenTys. Previously, we used deriveUnique and then uniqAway. This worked doubly hard to avoid clashes. Doing just uniqAway is enough. This commit also includes clarifying comments. >--------------------------------------------------------------- a0cea7ba9f14a193f31f057371d104c2dc0b7d80 compiler/types/FamInstEnv.hs | 27 +++++++++++++++++++++++---- 1 file changed, 23 insertions(+), 4 deletions(-) diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs index b121c73..690cab2 100644 --- a/compiler/types/FamInstEnv.hs +++ b/compiler/types/FamInstEnv.hs @@ -986,6 +986,24 @@ means replacing all top-level uses of type functions with fresh variables, taking care to preserve sharing. That is, the type (Either (F a b) (F a b)) should flatten to (Either c c), never (Either c d). +Here is a nice example of why it's all necessary: + + type family F a b where + F Int Bool = Char + F a b = Double + type family G a -- open, no instances + +How do we reduce (F (G Float) (G Float))? The first equation clearly doesn't match, +while the second equation does. But, before reducing, we must make sure that the +target can never become (F Int Bool). Well, no matter what G Float becomes, it +certainly won't become *both* Int and Bool, so indeed we're safe reducing +(F (G Float) (G Float)) to Double. + +This is necessary not only to get more reductions, but for substitutivity. If +we have (F x x), we can see that (F x x) can reduce to Double. So, it had better +be the case that (F blah blah) can reduce to Double, no matter what (blah) is! +Flattening as done below ensures this. + Defined here because of module dependencies. -} @@ -1044,10 +1062,11 @@ coreFlattenTyFamApp in_scope m fam_tc fam_args = case lookupTypeMap m fam_ty of Just tv -> (m, tv) -- we need fresh variables here, but this is called far from - -- any good source of uniques. So, we generate one from thin - -- air, using the arbitrary prime number 71 as a seed - Nothing -> let tyvar_unique = deriveUnique (getUnique fam_tc) 71 - tyvar_name = mkSysTvName tyvar_unique (fsLit "fl") + -- any good source of uniques. So, we just use the fam_tc's unique + -- and trust uniqAway to avoid clashes. Recall that the in_scope set + -- contains *all* tyvars, even locally bound ones elsewhere in the + -- overall type, so this really is fresh. + Nothing -> let tyvar_name = mkSysTvName (getUnique fam_tc) (fsLit "fl") tv = uniqAway in_scope $ mkTyVar tyvar_name (typeKind fam_ty) m' = extendTypeMap m fam_ty tv in (m', tv) From git at git.haskell.org Tue Mar 3 21:03:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Mar 2015 21:03:10 +0000 (UTC) Subject: [commit: ghc] master: Clarify some comments in Packages.hs [skip-ci] (6e77d45) Message-ID: <20150303210310.1425C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6e77d45b2b4dcf189b71621009e80b96a3c5155a/ghc >--------------------------------------------------------------- commit 6e77d45b2b4dcf189b71621009e80b96a3c5155a Author: Edward Z. Yang Date: Tue Mar 3 13:05:03 2015 -0800 Clarify some comments in Packages.hs [skip-ci] Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 6e77d45b2b4dcf189b71621009e80b96a3c5155a compiler/main/Packages.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index db48d99..42aa0a1 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -233,9 +233,10 @@ type ModuleToPkgConfAll = data PackageState = PackageState { -- | A mapping of 'PackageKey' to 'PackageConfig'. This list is adjusted - -- so that only valid packages are here. Currently, we also flip the - -- exposed/trusted bits based on package flags; however, the hope is to - -- stop doing that. + -- so that only valid packages are here. 'PackageConfig' reflects + -- what was stored *on disk*, except for the 'trusted' flag, which + -- is adjusted at runtime. (In particular, some packages in this map + -- may have the 'exposed' flag be 'False'.) pkgIdMap :: PackageConfigMap, -- | The packages we're going to link in eagerly. This list @@ -287,7 +288,9 @@ getPackageDetails dflags pid = expectJust "getPackageDetails" (lookupPackage dflags pid) -- | Get a list of entries from the package database. NB: be careful with --- this function, it may not do what you expect it to. +-- this function, although all packages in this map are "visible", this +-- does not imply that the exposed-modules of the package are available +-- (they may have been thinned or renamed). listPackageConfigMap :: DynFlags -> [PackageConfig] listPackageConfigMap dflags = eltsUFM (pkgIdMap (pkgState dflags)) From git at git.haskell.org Wed Mar 4 00:32:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 00:32:06 +0000 (UTC) Subject: [commit: hsc2hs] master: Fix cross-compiling from Linux to Windows (Closes: #9524). (e32b4fa) Message-ID: <20150304003206.568C73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hsc2hs On branch : master Link : http://git.haskell.org/hsc2hs.git/commitdiff/e32b4faf97833f92708a8f3f8bbb015f5d1dbcc7 >--------------------------------------------------------------- commit e32b4faf97833f92708a8f3f8bbb015f5d1dbcc7 Author: Erik de Castro Lopo Date: Sun Feb 8 12:59:54 2015 +1100 Fix cross-compiling from Linux to Windows (Closes: #9524). Remove include of "../../includes/ghcconfig.h" which should really only be a GHC-build-time include, not an include for building external tools like this. >--------------------------------------------------------------- e32b4faf97833f92708a8f3f8bbb015f5d1dbcc7 Main.hs | 4 ---- 1 file changed, 4 deletions(-) diff --git a/Main.hs b/Main.hs index afa192e..40e52dc 100644 --- a/Main.hs +++ b/Main.hs @@ -9,10 +9,6 @@ -- -- See the documentation in the Users' Guide for more details. -#if defined(__GLASGOW_HASKELL__) && !defined(BUILD_NHC) -#include "../../includes/ghcconfig.h" -#endif - import Control.Monad ( liftM, forM_ ) import Data.List ( isSuffixOf ) import System.Console.GetOpt From git at git.haskell.org Wed Mar 4 01:39:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 01:39:42 +0000 (UTC) Subject: [commit: ghc] master: Fix -Werror build failure in RtsMain (e673b84) Message-ID: <20150304013942.1AD143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e673b8408d84f9149f88964c3318059984eb7788/ghc >--------------------------------------------------------------- commit e673b8408d84f9149f88964c3318059984eb7788 Author: Tamar Christina Date: Tue Mar 3 19:41:43 2015 -0600 Fix -Werror build failure in RtsMain Summary: Something in Excn.h's include chain is loading _mingw.h which is defining a macro that PosixSource.h is going to define. _mingw.h's version properly checks if it has already been defined and skips it, so fixing the warning can be done by just including Excn.h later (moved it to before last include). Test Plan: ./validate Reviewers: austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D698 >--------------------------------------------------------------- e673b8408d84f9149f88964c3318059984eb7788 rts/RtsMain.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/RtsMain.c b/rts/RtsMain.c index 667c9e4..154eafa 100644 --- a/rts/RtsMain.c +++ b/rts/RtsMain.c @@ -8,7 +8,6 @@ #define COMPILING_RTS_MAIN -#include "Excn.h" #include "PosixSource.h" #include "Rts.h" #include "RtsAPI.h" @@ -16,6 +15,7 @@ #include "RtsUtils.h" #include "Prelude.h" #include "Task.h" +#include "Excn.h" #ifdef DEBUG # include "Printer.h" /* for printing */ From git at git.haskell.org Wed Mar 4 11:38:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 11:38:59 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Cleanup 1: Remove redundant debugging prints (8364107) Message-ID: <20150304113859.52D893A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/836410748b31ed382ca07758220b78df02528f46/ghc >--------------------------------------------------------------- commit 836410748b31ed382ca07758220b78df02528f46 Author: George Karachalias Date: Sat Feb 28 17:53:03 2015 +0100 Cleanup 1: Remove redundant debugging prints >--------------------------------------------------------------- 836410748b31ed382ca07758220b78df02528f46 compiler/basicTypes/Var.hs | 3 +- compiler/deSugar/Check.hs | 64 ++---------------------------------------- compiler/typecheck/TcSMonad.hs | 4 --- 3 files changed, 3 insertions(+), 68 deletions(-) diff --git a/compiler/basicTypes/Var.hs b/compiler/basicTypes/Var.hs index 3971b84..4cac5d5 100644 --- a/compiler/basicTypes/Var.hs +++ b/compiler/basicTypes/Var.hs @@ -205,8 +205,7 @@ After CoreTidy, top-level LocalIds are turned into GlobalIds -} instance Outputable Var where - -- ppr var = ppr (varName var) <> getPprStyle (ppr_debug var) - ppr var = parens $ ppr (varName var) <> ptext (sLit "_") <> ppr (varUnique var) <> getPprStyle (ppr_debug var) <+> dcolon <+> ppr (varType var) + ppr var = ppr (varName var) <> getPprStyle (ppr_debug var) ppr_debug :: Var -> PprStyle -> SDoc ppr_debug (TyVar {}) sty diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 83016b2..2235d66 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -138,8 +138,6 @@ checkpm tys eq_info | null eq_info = return (Just ([],[],[])) -- If we have an empty match, do not reason at all | otherwise = do loc <- getSrcSpanDs - pprInTcRnIf (ptext (sLit "Checking match at") <+> ppr loc <+> - ptext (sLit "with signature:") <+> sep (punctuate comma (map pprTyWithKind tys))) uncovered0 <- initial_uncovered tys let allvanilla = all isVanillaEqn eq_info -- Need to pass this to process_vector, so that tc can be avoided @@ -541,45 +539,6 @@ isSatisfiable evs Just sat -> return sat Nothing -> pprPanic "isSatisfiable" (vcat $ pprErrMsgBagWithLoc errs) } -{- --- ----------------------------------------------------------------------- --- | Infer types --- INVARIANTS: --- 1) ALL PmLit and PmLitCon have the EXACT type (inherit it carefully while checking uncovered). --- 2) ALL PmVarPat have fresh type, with the correct super kind -inferTyPmPat :: PmPat Id -> PmM (Type, Bag EvVar) -- infer a type and a set of constraints -inferTyPmPat (PmGuardPat _) = panic "inferTyPmPat: PmGuardPat" -inferTyPmPat (PmVarPat ty _) = return (ty, emptyBag) -- instTypePmM ty >>= \ty' -> return (ty', emptyBag) -inferTyPmPat (PmLitPat ty _) = return (ty, emptyBag) -inferTyPmPat (PmLitCon ty _) = return (ty, emptyBag) -inferTyPmPat (PmConPat con args) = do - -- ---------------------------------------------------------------- - -- pprInTcRnIf (ptext (sLit "For pattern:") <+> ppr (PmConPat con args)) - -- pprInTcRnIf (ptext (sLit "dataConUserType =") <+> ppr (dataConUserType con)) - -- pprInTcRnIf (ptext (sLit "dataConSig =") <+> ppr (dataConSig con)) - -- ---------------------------------------------------------------- - (tys, cs) <- inferTyPmPats args -- Infer argument types and respective constraints (Just like the paper) - - let (tvs, thetas', arg_tys', res_ty') = dataConSig con -- take apart the constructor - (subst, _tvs) <- -- create the substitution for both as and bs - getSrcSpanDs >>= \loc -> genInstSkolTyVars loc tvs - let res_ty = substTy subst res_ty' -- result type - arg_tys = substTys subst arg_tys' - thetas <- mapM (nameType "varcon") $ substTheta subst thetas' - - arg_thetas <- foldM (\acc (ty1, ty2) -> do - eq_theta <- newEqPmM ty1 ty2 - return (eq_theta `consBag` acc)) - cs (tys `zip` arg_tys) -- All thetas from the argument patterns and tau_i ~ t_i for all arguments - return (res_ty, listToBag thetas `unionBags` arg_thetas) - -inferTyPmPats :: [PmPat Id] -> PmM ([Type], Bag EvVar) -inferTyPmPats pats = do - tys_cs <- mapM inferTyPmPat pats - let (tys, cs) = unzip tys_cs - return (tys, unionManyBags cs) --} - checkTyPmPat :: PmPat Id -> Type -> PmM (Bag EvVar) -- check a type and a set of constraints checkTyPmPat (PmGuardPat _) _ = panic "checkTyPmPat: PmGuardPat" checkTyPmPat (PmVarPat {}) _ = return emptyBag @@ -600,15 +559,12 @@ checkTyPmPat pat@(PmConPat con args) res_ty = do | otherwise -> ASSERT( res_tc == data_tc ) Just res_tc_tys - pprInTcRnIf (text "checkTyPmPat con" <+> vcat [ ppr con, ppr univ_tvs, ppr dc_res_ty, ppr res_ty, ppr mb_tc_args ]) loc <- getSrcSpanDs (subst, res_eq) <- case mb_tc_args of Nothing -> -- The context type doesn't have a type constructor at the head. -- so generate an equality. But this doesn't really work if there -- are kind variables involved - do when (any isKindVar univ_tvs) - (pprInTcRnIf (text "checkTyPmPat: Danger! Kind variables" <+> ppr pat)) - (subst, _) <- genInstSkolTyVars loc univ_tvs + do (subst, _) <- genInstSkolTyVars loc univ_tvs res_eq <- newEqPmM (substTy subst dc_res_ty) res_ty return (subst, unitBag res_eq) Just tys -> return (zipTopTvSubst univ_tvs tys, emptyBag) @@ -637,26 +593,10 @@ genInstSkolTyVars loc tvs = genInstSkolTyVarsX loc emptyTvSubst tvs wt :: [Type] -> OutVec -> PmM Bool wt sig (_, vec) | length sig == length vec = do --- (tys, cs) <- inferTyPmPats vec --- cs' <- zipWithM newEqPmM (map expandTypeSynonyms sig) tys -- The vector should match the signature type cs <- checkTyPmPats vec sig env_cs <- getDictsDs loc <- getSrcSpanDs - -- pprInTcRnIf (ptext (sLit "Checking in location:") <+> ppr loc) - -- pprInTcRnIf (ptext (sLit "Checking vector") <+> ppr vec <+> ptext (sLit "with inferred type:") <+> - -- sep (punctuate comma (map pprTyWithKind tys))) - pprInTcRnIf (ptext (sLit "With given signature:") <+> sep (punctuate comma (map pprTyWithKind sig))) - pprInTcRnIf (ppr loc <+> ptext (sLit "vector:") <+> ppr vec) --- pprInTcRnIf (ptext (sLit "with type:") <+> sep (punctuate comma (map pprTyWithKind ys))) - let constraints = cs `unionBags` env_cs - pprInTcRnIf (ptext (sLit "And constraints:") - <+> vcat [ text "cs:" <+> ppr (mapBag varType cs) - , text "env_cs:" <+> ppr (mapBag varType env_cs) ]) - - is_sat <- isSatisfiable constraints - pprInTcRnIf (ptext (sLit "Satisfiable:") <+> ppr is_sat) - return is_sat - + isSatisfiable (cs `unionBags` env_cs) | otherwise = pprPanic "wt: length mismatch:" (ppr sig $$ ppr vec) {- diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index 3721f92..5b98482 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -962,10 +962,6 @@ checkInsoluble :: TcS Bool -- True if there are any insoluble constraints checkInsoluble = do { icans <- getInertCans - ; let insols = inert_insols icans - ; if isEmptyBag insols - then return () - else wrapTcS $ pprInTcRnIf (ptext (sLit "insolubles:") $$ ppr insols) -- just to see ; return (not (isEmptyBag (inert_insols icans))) } lookupFlatCache :: TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcType, CtFlavour)) From git at git.haskell.org Wed Mar 4 11:39:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 11:39:01 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Removed typing from all places it shouldn't be (cd2695f) Message-ID: <20150304113901.F254A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/cd2695f1581838ce22cbd02100b84833c8f6996d/ghc >--------------------------------------------------------------- commit cd2695f1581838ce22cbd02100b84833c8f6996d Author: George Karachalias Date: Sun Mar 1 13:25:45 2015 +0100 Removed typing from all places it shouldn't be >--------------------------------------------------------------- cd2695f1581838ce22cbd02100b84833c8f6996d compiler/deSugar/Check.hs | 173 +++++++++++++--------------------------------- compiler/deSugar/Match.hs | 7 -- 2 files changed, 48 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 cd2695f1581838ce22cbd02100b84833c8f6996d From git at git.haskell.org Wed Mar 4 11:58:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 11:58:12 +0000 (UTC) Subject: [commit: ghc] master: Tidy up and improve comments about one-shot info (ee56dc5) Message-ID: <20150304115812.E76163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ee56dc56a4a0f556894c4d2bd04c3d4ca73e95a1/ghc >--------------------------------------------------------------- commit ee56dc56a4a0f556894c4d2bd04c3d4ca73e95a1 Author: Simon Peyton Jones Date: Tue Mar 3 21:52:28 2015 +0000 Tidy up and improve comments about one-shot info (Triggered by investigating Trac #10102 etc.) >--------------------------------------------------------------- ee56dc56a4a0f556894c4d2bd04c3d4ca73e95a1 compiler/basicTypes/BasicTypes.hs | 2 +- compiler/basicTypes/Demand.hs | 5 ++--- compiler/basicTypes/MkId.hs | 9 +++++---- compiler/coreSyn/CoreTidy.hs | 3 +-- compiler/iface/IfaceType.hs | 4 ++-- 5 files changed, 11 insertions(+), 12 deletions(-) diff --git a/compiler/basicTypes/BasicTypes.hs b/compiler/basicTypes/BasicTypes.hs index 04353bf..973666d 100644 --- a/compiler/basicTypes/BasicTypes.hs +++ b/compiler/basicTypes/BasicTypes.hs @@ -163,7 +163,7 @@ type Alignment = Int -- align to next N-byte boundary (N must be a power of 2). data OneShotInfo = NoOneShotInfo -- ^ No information | ProbOneShot -- ^ The lambda is probably applied at most once - -- See Note [Computing one-shot info, and ProbOneShot] in OccurAnl + -- See Note [Computing one-shot info, and ProbOneShot] in Demand | OneShotLam -- ^ The lambda is applied at most once. deriving (Eq) diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index ecf22bc..3ca7c2d 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -1618,9 +1618,8 @@ argOneShots one_shot_info (JD { absd = usg }) go (UCall Many u) = NoOneShotInfo : go u go _ = [] -{- -Note [Computing one-shot info, and ProbOneShot] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +{- Note [Computing one-shot info, and ProbOneShot] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider a call f (\pqr. e1) (\xyz. e2) e3 where f has usage signature diff --git a/compiler/basicTypes/MkId.hs b/compiler/basicTypes/MkId.hs index 0b22a64..c4222be 100644 --- a/compiler/basicTypes/MkId.hs +++ b/compiler/basicTypes/MkId.hs @@ -1250,7 +1250,6 @@ appears un-applied, we'll end up just calling it. Note [The oneShot function] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ - In the context of making left-folds fuse somewhat okish (see ticket #7994 and Note [Left folds via right fold]) it was determined that it would be useful if library authors could explicitly tell the compiler that a certain lambda is @@ -1270,9 +1269,11 @@ after unfolding the definition `oneShot = \f \x[oneshot]. f x` we get --> \x[oneshot] e[x/y] which is what we want. -It is only effective if this bits survives as long as possible and makes it into -the interface in unfoldings (See Note [Preserve OneShotInfo]). Also see -https://ghc.haskell.org/trac/ghc/wiki/OneShot. +It is only effective if the one-shot info survives as long as possible; in +particular it must make it into the interface in unfoldings. See Note [Preserve +OneShotInfo] in CoreTidy. + +Also see https://ghc.haskell.org/trac/ghc/wiki/OneShot. Note [magicDictId magic] diff --git a/compiler/coreSyn/CoreTidy.hs b/compiler/coreSyn/CoreTidy.hs index 325950c..4ee867a 100644 --- a/compiler/coreSyn/CoreTidy.hs +++ b/compiler/coreSyn/CoreTidy.hs @@ -258,12 +258,11 @@ but that seems more indirect and surprising.) Note [Preserve OneShotInfo] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ - We keep the OneShotInfo because we want it to propagate into the interface. Not all OneShotInfo is determined by a compiler analysis; some is added by a call of GHC.Exts.oneShot, which is then discarded before the end of the optimisation pipeline, leaving only the OneShotInfo on the lambda. Hence we -must preserve this info in inlinings. +must preserve this info in inlinings. See Note [The oneShot function] in MkId. This applies to lambda binders only, hence it is stored in IfaceLamBndr. -} diff --git a/compiler/iface/IfaceType.hs b/compiler/iface/IfaceType.hs index fed3ffc..e83c25e 100644 --- a/compiler/iface/IfaceType.hs +++ b/compiler/iface/IfaceType.hs @@ -87,8 +87,8 @@ type IfaceIdBndr = (IfLclName, IfaceType) type IfaceTvBndr = (IfLclName, IfaceKind) -data IfaceOneShot -- see Note [Preserve OneShotInfo] - = IfaceNoOneShot +data IfaceOneShot -- See Note [Preserve OneShotInfo] in CoreTicy + = IfaceNoOneShot -- and Note [The oneShot function] in MkId | IfaceOneShot type IfaceLamBndr From git at git.haskell.org Wed Mar 4 11:58:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 11:58:15 +0000 (UTC) Subject: [commit: ghc] master: Some minor refactoring in TcHsType (d058bc9) Message-ID: <20150304115815.896863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d058bc9ce04e8397c8fd0a32a8654b83f3ef4af1/ghc >--------------------------------------------------------------- commit d058bc9ce04e8397c8fd0a32a8654b83f3ef4af1 Author: Simon Peyton Jones Date: Tue Mar 3 21:54:58 2015 +0000 Some minor refactoring in TcHsType >--------------------------------------------------------------- d058bc9ce04e8397c8fd0a32a8654b83f3ef4af1 compiler/typecheck/TcHsType.hs | 37 ++++++++++++++++++++----------------- 1 file changed, 20 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 0cb128e..fbd21b2 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -8,7 +8,7 @@ {-# LANGUAGE CPP #-} module TcHsType ( - tcHsSigType, tcHsSigTypeNC, tcHsDeriv, tcHsVectInst, + tcHsSigType, tcHsDeriv, tcHsVectInst, tcHsInstHead, UserTypeCtxt(..), @@ -21,7 +21,7 @@ module TcHsType ( -- No kind generalisation, no checkValidType kcHsTyVarBndrs, tcHsTyVarBndrs, tcHsLiftedType, tcHsOpenType, - tcLHsType, tcCheckLHsType, + tcLHsType, tcCheckLHsType, tcCheckLHsTypeAndGen, tcHsContext, tcInferApps, tcHsArgTys, kindGeneralize, checkKind, @@ -155,17 +155,13 @@ the TyCon being defined. ************************************************************************ -} -tcHsSigType, tcHsSigTypeNC :: UserTypeCtxt -> LHsType Name -> TcM Type +tcHsSigType :: UserTypeCtxt -> LHsType Name -> TcM Type -- NB: it's important that the foralls that come from the top-level -- HsForAllTy in hs_ty occur *first* in the returned type. -- See Note [Scoped] with TcSigInfo -tcHsSigType ctxt hs_ty - = addErrCtxt (pprSigCtxt ctxt empty (ppr hs_ty)) $ - tcHsSigTypeNC ctxt hs_ty - -tcHsSigTypeNC ctxt (L loc hs_ty) - = setSrcSpan loc $ -- The "In the type..." context - -- comes from the caller; hence "NC" +tcHsSigType ctxt (L loc hs_ty) + = setSrcSpan loc $ + addErrCtxt (pprSigCtxt ctxt empty (ppr hs_ty)) $ do { kind <- case expectedKindInCtxt ctxt of Nothing -> newMetaKindVar Just k -> return k @@ -182,7 +178,7 @@ tcHsSigTypeNC ctxt (L loc hs_ty) ----------------- tcHsInstHead :: UserTypeCtxt -> LHsType Name -> TcM ([TyVar], ThetaType, Class, [Type]) --- Like tcHsSigTypeNC, but for an instance head. +-- Like tcHsSigType, but for an instance head. tcHsInstHead user_ctxt lhs_ty@(L loc hs_ty) = setSrcSpan loc $ -- The "In the type..." context comes from the caller do { inst_ty <- tc_inst_head hs_ty @@ -203,7 +199,7 @@ tc_inst_head hs_ty ----------------- tcHsDeriv :: HsType Name -> TcM ([TyVar], Class, [Type], Kind) --- Like tcHsSigTypeNC, but for the ...deriving( C t1 ty2 ) clause +-- Like tcHsSigType, but for the ...deriving( C t1 ty2 ) clause -- Returns the C, [ty1, ty2, and the kind of C's *next* argument -- E.g. class C (a::*) (b::k->k) -- data T a b = ... deriving( C Int ) @@ -247,9 +243,8 @@ tcHsVectInst ty -} tcClassSigType :: LHsType Name -> TcM Type -tcClassSigType lhs_ty@(L _ hs_ty) - = addTypeCtxt lhs_ty $ - do { ty <- tcCheckHsTypeAndGen hs_ty liftedTypeKind +tcClassSigType lhs_ty + = do { ty <- tcCheckLHsTypeAndGen lhs_ty liftedTypeKind ; zonkSigType ty } tcHsConArgType :: NewOrData -> LHsType Name -> TcM Type @@ -294,10 +289,18 @@ tcLHsType :: LHsType Name -> TcM (TcType, TcKind) tcLHsType ty = addTypeCtxt ty (tc_infer_lhs_type ty) --------------------------- -tcCheckHsTypeAndGen :: HsType Name -> Kind -> TcM Type --- Input type is HsType, not LhsType; the caller adds the context +tcCheckLHsTypeAndGen :: LHsType Name -> Kind -> TcM Type -- Typecheck a type signature, and kind-generalise it -- The result is not necessarily zonked, and has not been checked for validity +tcCheckLHsTypeAndGen lhs_ty kind + = do { ty <- tcCheckLHsType lhs_ty kind + ; kvs <- zonkTcTypeAndFV ty + ; kvs <- kindGeneralize kvs + ; return (mkForAllTys kvs ty) } + +tcCheckHsTypeAndGen :: HsType Name -> Kind -> TcM Type +-- Input type is HsType, not LHsType; the caller adds the context +-- Otherwise same as tcCheckLHsTypeAndGen tcCheckHsTypeAndGen hs_ty kind = do { ty <- tc_hs_type hs_ty (EK kind expectedKindMsg) ; traceTc "tcCheckHsTypeAndGen" (ppr hs_ty) From git at git.haskell.org Wed Mar 4 11:58:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 11:58:18 +0000 (UTC) Subject: [commit: ghc] master: A raft of small changes associated with -XConstrainedClassMethods (f66e0e6) Message-ID: <20150304115818.C44CA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f66e0e695b0377c469fbe877d4850fc0ebca2010/ghc >--------------------------------------------------------------- commit f66e0e695b0377c469fbe877d4850fc0ebca2010 Author: Simon Peyton Jones Date: Wed Mar 4 11:59:47 2015 +0000 A raft of small changes associated with -XConstrainedClassMethods See Trac #7854. Specifically: * Major clean up and simplification of check_op in checkValidClass; specifically - use checkValidType on the entire method-selector type to detect ambiguity - put a specific test for -XConstrainedClassMethods * Make -XConstrainedClassMethods be implied by -XMultiParamTypeClasses (a bit ad-hoc but see #7854), and document in the user manual. * Do the checkAmbiguity test just once in TcValidity.checkValidType, rather than repeatedly at every level. See Note [When to call checkAmbiguity] * Add -XAllowAmbiguousTypes in GHC.IP, since 'ip' really is ambiguous. (It's a rather magic function.) * Improve location info for check_op in checkValidClass * Update quite a few tests, which had genuinely-ambiguous class method signatures. Some I fixed by making them unambiguous; some by adding -XAllowAmbiguousTypes >--------------------------------------------------------------- f66e0e695b0377c469fbe877d4850fc0ebca2010 compiler/main/DynFlags.hs | 1 + compiler/typecheck/TcTyClsDecls.hs | 75 ++++--- compiler/typecheck/TcValidity.hs | 219 +++++++++++---------- docs/users_guide/glasgow_exts.xml | 11 +- libraries/base/GHC/IP.hs | 2 + .../tests/indexed-types/should_compile/T2715.hs | 7 +- .../tests/indexed-types/should_compile/T4160.hs | 3 + .../tests/indexed-types/should_compile/T4200.hs | 4 +- .../tests/indexed-types/should_compile/T9582.hs | 6 +- .../tests/indexed-types/should_fail/T1900.stderr | 15 +- testsuite/tests/indexed-types/should_fail/T2544.hs | 2 + .../tests/indexed-types/should_fail/T2544.stderr | 4 +- testsuite/tests/module/all.T | 2 +- testsuite/tests/module/mod39.stderr | 7 + testsuite/tests/polykinds/T8566.hs | 1 + testsuite/tests/polykinds/T8566.stderr | 8 +- testsuite/tests/polykinds/T9200.hs | 3 +- testsuite/tests/roles/should_compile/Roles3.hs | 1 + testsuite/tests/th/TH_tf2.hs | 1 + testsuite/tests/typecheck/should_compile/tc165.hs | 1 + testsuite/tests/typecheck/should_compile/tc199.hs | 3 +- testsuite/tests/typecheck/should_compile/tc200.hs | 1 + testsuite/tests/typecheck/should_compile/tc235.hs | 2 + testsuite/tests/typecheck/should_compile/tc259.hs | 3 + testsuite/tests/typecheck/should_compile/tc260.hs | 3 + testsuite/tests/typecheck/should_fail/all.T | 2 +- .../tests/typecheck/should_fail/tcfail116.stderr | 14 +- testsuite/tests/typecheck/should_fail/tcfail149.hs | 2 + .../tests/typecheck/should_fail/tcfail150.stderr | 8 + testsuite/tests/typecheck/should_fail/tcfail151.hs | 2 +- 30 files changed, 238 insertions(+), 175 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f66e0e695b0377c469fbe877d4850fc0ebca2010 From git at git.haskell.org Wed Mar 4 13:45:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 13:45:47 +0000 (UTC) Subject: [commit: ghc] master: Comments only (ef2c7a7) Message-ID: <20150304134547.AFE7C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ef2c7a7345a3c39c5290894e16edf187b97d3a96/ghc >--------------------------------------------------------------- commit ef2c7a7345a3c39c5290894e16edf187b97d3a96 Author: Simon Peyton Jones Date: Wed Mar 4 12:01:12 2015 +0000 Comments only >--------------------------------------------------------------- ef2c7a7345a3c39c5290894e16edf187b97d3a96 compiler/types/FamInstEnv.hs | 25 ++++++++++++++----------- 1 file changed, 14 insertions(+), 11 deletions(-) diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs index 690cab2..72e6490 100644 --- a/compiler/types/FamInstEnv.hs +++ b/compiler/types/FamInstEnv.hs @@ -859,6 +859,7 @@ findBranch (CoAxBranch { cab_tvs = tpl_tvs, cab_lhs = tpl_lhs, cab_incomps = inc where isSurelyApart SurelyApart = True isSurelyApart _ = False + -- See Note [Flattening] below flattened_target = flattenTys in_scope target_tys in_scope = mkInScopeSet (unionVarSets $ map (tyVarsOfTypes . coAxBranchLHS) incomps) @@ -978,13 +979,14 @@ normaliseType _ role ty@(TyVarTy _) Note [Flattening] ~~~~~~~~~~~~~~~~~ - -As described in +As described in "Closed type families with overlapping equations" http://research.microsoft.com/en-us/um/people/simonpj/papers/ext-f/axioms-extended.pdf -we sometimes need to flatten core types before unifying them. Flattening -means replacing all top-level uses of type functions with fresh variables, -taking care to preserve sharing. That is, the type (Either (F a b) (F a b)) should -flatten to (Either c c), never (Either c d). +we need to flatten core types before unifying them, when checking for "surely-apart" +against earlier equations of a closed type family. +Flattening means replacing all top-level uses of type functions with +fresh variables, *taking care to preserve sharing*. That is, the type +(Either (F a b) (F a b)) should flatten to (Either c c), never (Either +c d). Here is a nice example of why it's all necessary: @@ -999,12 +1001,13 @@ target can never become (F Int Bool). Well, no matter what G Float becomes, it certainly won't become *both* Int and Bool, so indeed we're safe reducing (F (G Float) (G Float)) to Double. -This is necessary not only to get more reductions, but for substitutivity. If -we have (F x x), we can see that (F x x) can reduce to Double. So, it had better -be the case that (F blah blah) can reduce to Double, no matter what (blah) is! -Flattening as done below ensures this. +This is necessary not only to get more reductions (which we might be +willing to give up on), but for substitutivity. If we have (F x x), we +can see that (F x x) can reduce to Double. So, it had better be the +case that (F blah blah) can reduce to Double, no matter what (blah) +is! Flattening as done below ensures this. -Defined here because of module dependencies. +flattenTys is defined here because of module dependencies. -} type FlattenMap = TypeMap TyVar From git at git.haskell.org Wed Mar 4 13:45:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 13:45:50 +0000 (UTC) Subject: [commit: ghc] master: Check for equality before deferring (3aa2519) Message-ID: <20150304134550.781693A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3aa2519ec29156f57a862a033bc7a902b742a2e0/ghc >--------------------------------------------------------------- commit 3aa2519ec29156f57a862a033bc7a902b742a2e0 Author: Simon Peyton Jones Date: Wed Mar 4 13:18:57 2015 +0000 Check for equality before deferring This one was a bit of a surprise. In fixing Trac #7854, I moved the checkAmbiguity tests to checkValidType. That meant it happened even for monotypes, and that turned out to be very expensive in T9872a, for reasons described in this (new) Note in TcUnify: Note [Check for equality before deferring] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Particularly in ambiguity checks we can get equalities like (ty ~ ty). If ty involves a type function we may defer, which isn't very sensible. An egregious example of this was in test T9872a, which has a type signature Proxy :: Proxy (Solutions Cubes) Doing the ambiguity check on this signature generates the equality Solutions Cubes ~ Solutions Cubes and currently the constraint solver normalises both sides at vast cost. This little short-cut in 'defer' helps quite a bit. I fixed the problem with a quick equality test, but it feels like an ad-hoc solution; I think we might want to do something in the constraint solver too. (The problem was there all along, just more hidden.) >--------------------------------------------------------------- 3aa2519ec29156f57a862a033bc7a902b742a2e0 compiler/typecheck/TcUnify.hs | 26 +++++++++++++++++++++----- compiler/typecheck/TcValidity.hs | 2 ++ 2 files changed, 23 insertions(+), 5 deletions(-) diff --git a/compiler/typecheck/TcUnify.hs b/compiler/typecheck/TcUnify.hs index 32a04de..f732515 100644 --- a/compiler/typecheck/TcUnify.hs +++ b/compiler/typecheck/TcUnify.hs @@ -738,14 +738,15 @@ uType origin orig_ty1 orig_ty2 -- Always defer if a type synonym family (type function) -- is involved. (Data families behave rigidly.) go ty1@(TyConApp tc1 _) ty2 - | isTypeFamilyTyCon tc1 = uType_defer origin ty1 ty2 + | isTypeFamilyTyCon tc1 = defer ty1 ty2 go ty1 ty2@(TyConApp tc2 _) - | isTypeFamilyTyCon tc2 = uType_defer origin ty1 ty2 + | isTypeFamilyTyCon tc2 = defer ty1 ty2 go (TyConApp tc1 tys1) (TyConApp tc2 tys2) -- See Note [Mismatched type lists and application decomposition] | tc1 == tc2, length tys1 == length tys2 - = do { cos <- zipWithM (uType origin) tys1 tys2 + = ASSERT( isDecomposableTyCon tc1 ) + do { cos <- zipWithM (uType origin) tys1 tys2 ; return $ mkTcTyConAppCo Nominal tc1 cos } go (LitTy m) ty@(LitTy n) @@ -770,7 +771,12 @@ uType origin orig_ty1 orig_ty2 -- Anything else fails -- E.g. unifying for-all types, which is relative unusual - go ty1 ty2 = uType_defer origin ty1 ty2 -- failWithMisMatch origin + go ty1 ty2 = defer ty1 ty2 + + ------------------ + defer ty1 ty2 -- See Note [Check for equality before deferring] + | ty1 `tcEqType` ty2 = return (mkTcNomReflCo ty1) + | otherwise = uType_defer origin ty1 ty2 ------------------ go_app s1 t1 s2 t2 @@ -778,7 +784,17 @@ uType origin orig_ty1 orig_ty2 ; co_t <- uType origin t1 t2 ; return $ mkTcAppCo co_s co_t } -{- +{- Note [Check for equality before deferring] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Particularly in ambiguity checks we can get equalities like (ty ~ ty). +If ty involves a type function we may defer, which isn't very sensible. +An egregious example of this was in test T9872a, which has a type signature + Proxy :: Proxy (Solutions Cubes) +Doing the ambiguity check on this signature generates the equality + Solutions Cubes ~ Solutions Cubes +and currently the constraint solver normalises both sides at vast cost. +This little short-cut in 'defer' helps quite a bit. + Note [Care with type applications] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Note: type applications need a bit of care! diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index 3988af4..3d01f50 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -296,6 +296,8 @@ checkValidType ctxt ty ; check_kind ctxt ty -- Check for ambiguous types. See Note [When to call checkAmbiguity] + -- NB: this will happen even for monotypes, but that should be cheap; + -- and there may be nested foralls for the subtype test to examine ; checkAmbiguity ctxt ty ; traceTc "checkValidType done" (ppr ty <+> text "::" <+> ppr (typeKind ty)) } From git at git.haskell.org Wed Mar 4 13:45:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 13:45:53 +0000 (UTC) Subject: [commit: ghc] master: Three other test updates following the fix to Trac #7854 (9dc0d63) Message-ID: <20150304134553.45CD13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9dc0d63cd7231392320e4afcfe78102801126d34/ghc >--------------------------------------------------------------- commit 9dc0d63cd7231392320e4afcfe78102801126d34 Author: Simon Peyton Jones Date: Wed Mar 4 13:20:28 2015 +0000 Three other test updates following the fix to Trac #7854 >--------------------------------------------------------------- 9dc0d63cd7231392320e4afcfe78102801126d34 testsuite/tests/deriving/should_fail/T8851.hs | 2 +- testsuite/tests/ghci/prog008/A.hs | 1 + testsuite/tests/ghci/scripts/ghci025.hs | 1 + 3 files changed, 3 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/deriving/should_fail/T8851.hs b/testsuite/tests/deriving/should_fail/T8851.hs index 84f0ad4..8b5c0e5 100644 --- a/testsuite/tests/deriving/should_fail/T8851.hs +++ b/testsuite/tests/deriving/should_fail/T8851.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving, ConstrainedClassMethods #-} module T8851 where diff --git a/testsuite/tests/ghci/prog008/A.hs b/testsuite/tests/ghci/prog008/A.hs index 6a85ca7..d724bd2 100644 --- a/testsuite/tests/ghci/prog008/A.hs +++ b/testsuite/tests/ghci/prog008/A.hs @@ -1,4 +1,5 @@ {-# LANGUAGE RankNTypes, MultiParamTypeClasses #-} +{-# LANGUAGE AllowAmbiguousTypes #-} -- c3 is ambiguous! -- Tests a bug spotted by Claus in which the type -- of c3 was wrongly displayed in GHCi as diff --git a/testsuite/tests/ghci/scripts/ghci025.hs b/testsuite/tests/ghci/scripts/ghci025.hs index d5e2673..b556509 100644 --- a/testsuite/tests/ghci/scripts/ghci025.hs +++ b/testsuite/tests/ghci/scripts/ghci025.hs @@ -1,4 +1,5 @@ {-# LANGUAGE RankNTypes, MultiParamTypeClasses #-} +{-# LANGUAGE AllowAmbiguousTypes #-} -- c3 is ambiguous! module T where From git at git.haskell.org Wed Mar 4 16:35:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 16:35:04 +0000 (UTC) Subject: [commit: ghc] branch 'wip/travis' created Message-ID: <20150304163504.ABE933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/travis Referencing: d1f079b8fa19d0211c2ea1806045525cda3595ff From git at git.haskell.org Wed Mar 4 16:35:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 16:35:07 +0000 (UTC) Subject: [commit: ghc] wip/travis: travis: Get libstdc++ from a more sensible location (d1f079b) Message-ID: <20150304163507.58D5A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/travis Link : http://ghc.haskell.org/trac/ghc/changeset/d1f079b8fa19d0211c2ea1806045525cda3595ff/ghc >--------------------------------------------------------------- commit d1f079b8fa19d0211c2ea1806045525cda3595ff Author: Joachim Breitner Date: Wed Mar 4 17:37:09 2015 +0100 travis: Get libstdc++ from a more sensible location >--------------------------------------------------------------- d1f079b8fa19d0211c2ea1806045525cda3595ff .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 91c3baf..179b854 100644 --- a/.travis.yml +++ b/.travis.yml @@ -12,7 +12,7 @@ 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:ubuntu-toolchain-r/test - travis_retry sudo sh -c "echo 'deb http://llvm.org/apt/precise/ llvm-toolchain-precise-3.6-binaries main' >> /etc/apt/sources.list" - wget -O - http://llvm.org/apt/llvm-snapshot.gpg.key | sudo apt-key add - - travis_retry sudo apt-get update From git at git.haskell.org Wed Mar 4 16:37:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 16:37:25 +0000 (UTC) Subject: [commit: ghc] wip/travis: travis: Get libstdc++ from a more sensible location (e73c0de) Message-ID: <20150304163725.1762D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/travis Link : http://ghc.haskell.org/trac/ghc/changeset/e73c0dea836fc4636bb9b7997486888ce97c4b32/ghc >--------------------------------------------------------------- commit e73c0dea836fc4636bb9b7997486888ce97c4b32 Author: Joachim Breitner Date: Wed Mar 4 17:37:09 2015 +0100 travis: Get libstdc++ from a more sensible location >--------------------------------------------------------------- e73c0dea836fc4636bb9b7997486888ce97c4b32 .travis.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 91c3baf..fe48552 100644 --- a/.travis.yml +++ b/.travis.yml @@ -12,8 +12,8 @@ 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 sh -c "echo 'deb http://llvm.org/apt/precise/ llvm-toolchain-precise-3.6-binaries main' >> /etc/apt/sources.list" + - travis_retry sudo add-apt-repository -y ppa:ubuntu-toolchain-r/test + - travis_retry sudo sh -c "echo 'deb http://llvm.org/apt/precise/ llvm-toolchain-precise-3.6 main' >> /etc/apt/sources.list" - wget -O - http://llvm.org/apt/llvm-snapshot.gpg.key | sudo apt-key add - - 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 From git at git.haskell.org Wed Mar 4 16:54:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 16:54:36 +0000 (UTC) Subject: [commit: ghc] branch 'wip/travis' deleted Message-ID: <20150304165436.E34E93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/travis From git at git.haskell.org Wed Mar 4 16:54:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 16:54:39 +0000 (UTC) Subject: [commit: ghc] master's head updated: travis: Get libstdc++ from a more sensible location (e73c0de) Message-ID: <20150304165439.191E63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: e73c0de travis: Get libstdc++ from a more sensible location From git at git.haskell.org Wed Mar 4 18:53:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 18:53:04 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T10137' created Message-ID: <20150304185304.ACF583A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T10137 Referencing: 62cfcaf57f91a91ee7a79c948712916452c0a216 From git at git.haskell.org Wed Mar 4 18:53:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 18:53:07 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Refactor CmmSwitch: Use a Map (62cfcaf) Message-ID: <20150304185307.A09CD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/62cfcaf57f91a91ee7a79c948712916452c0a216/ghc >--------------------------------------------------------------- commit 62cfcaf57f91a91ee7a79c948712916452c0a216 Author: Joachim Breitner Date: Wed Mar 4 19:54:17 2015 +0100 Refactor CmmSwitch: Use a Map this is in preparation for #10137, where we want to be able to express sparse switch statements in Cmm. >--------------------------------------------------------------- 62cfcaf57f91a91ee7a79c948712916452c0a216 compiler/cmm/CmmCommonBlockElim.hs | 10 +++-- compiler/cmm/CmmContFlowOpt.hs | 2 +- compiler/cmm/CmmLint.hs | 5 ++- compiler/cmm/CmmNode.hs | 76 ++++++++++++++++++++++++++++----- compiler/cmm/CmmParse.y | 20 +++------ compiler/cmm/CmmProcPoint.hs | 4 +- compiler/cmm/MkGraph.hs | 4 +- compiler/cmm/PprC.hs | 24 ++++------- compiler/cmm/PprCmm.hs | 30 +++++++------ compiler/codeGen/StgCmmUtils.hs | 17 ++++---- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 10 +++-- compiler/nativeGen/PPC/CodeGen.hs | 9 ++-- compiler/nativeGen/SPARC/CodeGen.hs | 9 ++-- compiler/nativeGen/X86/CodeGen.hs | 9 ++-- 14 files changed, 141 insertions(+), 88 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 62cfcaf57f91a91ee7a79c948712916452c0a216 From git at git.haskell.org Wed Mar 4 19:44:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 19:44:15 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Refactor CmmSwitch: Use a Map (667379b) Message-ID: <20150304194415.EA18D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/667379ba3000afa13346cffb9cf660e6daa3693c/ghc >--------------------------------------------------------------- commit 667379ba3000afa13346cffb9cf660e6daa3693c Author: Joachim Breitner Date: Wed Mar 4 19:54:17 2015 +0100 Refactor CmmSwitch: Use a Map this is in preparation for #10137, where we want to be able to express sparse switch statements in Cmm. >--------------------------------------------------------------- 667379ba3000afa13346cffb9cf660e6daa3693c compiler/cmm/CmmCommonBlockElim.hs | 10 +++-- compiler/cmm/CmmContFlowOpt.hs | 2 +- compiler/cmm/CmmLint.hs | 5 +-- compiler/cmm/CmmNode.hs | 76 ++++++++++++++++++++++++++++----- compiler/cmm/CmmParse.y | 20 +++------ compiler/cmm/CmmProcPoint.hs | 4 +- compiler/cmm/MkGraph.hs | 4 +- compiler/cmm/PprC.hs | 24 ++++------- compiler/cmm/PprCmm.hs | 30 +++++++------ compiler/codeGen/StgCmmUtils.hs | 17 ++++---- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 10 +++-- compiler/nativeGen/PPC/CodeGen.hs | 9 ++-- compiler/nativeGen/SPARC/CodeGen.hs | 9 ++-- compiler/nativeGen/X86/CodeGen.hs | 9 ++-- 14 files changed, 140 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 667379ba3000afa13346cffb9cf660e6daa3693c From git at git.haskell.org Wed Mar 4 19:59:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 19:59:18 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Refactor CmmSwitch: Use a Map (11a51f5) Message-ID: <20150304195918.1190F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/11a51f50da18956fa61930905c05a43ae95e3031/ghc >--------------------------------------------------------------- commit 11a51f50da18956fa61930905c05a43ae95e3031 Author: Joachim Breitner Date: Wed Mar 4 19:54:17 2015 +0100 Refactor CmmSwitch: Use a Map this is in preparation for #10137, where we want to be able to express sparse switch statements in Cmm. >--------------------------------------------------------------- 11a51f50da18956fa61930905c05a43ae95e3031 compiler/cmm/CmmCommonBlockElim.hs | 10 +++-- compiler/cmm/CmmContFlowOpt.hs | 2 +- compiler/cmm/CmmLint.hs | 5 +-- compiler/cmm/CmmNode.hs | 76 ++++++++++++++++++++++++++++----- compiler/cmm/CmmParse.y | 20 +++------ compiler/cmm/CmmProcPoint.hs | 4 +- compiler/cmm/MkGraph.hs | 4 +- compiler/cmm/PprC.hs | 24 ++++------- compiler/cmm/PprCmm.hs | 30 +++++++------ compiler/codeGen/StgCmmUtils.hs | 17 ++++---- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 10 +++-- compiler/nativeGen/PPC/CodeGen.hs | 9 ++-- compiler/nativeGen/SPARC/CodeGen.hs | 9 ++-- compiler/nativeGen/X86/CodeGen.hs | 9 ++-- 14 files changed, 140 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 11a51f50da18956fa61930905c05a43ae95e3031 From git at git.haskell.org Wed Mar 4 20:31:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 20:31:11 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Make SwitchTargets type abstract (82ca17b) Message-ID: <20150304203111.CD2223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/82ca17bb3679963903f8633a0b3a43141b85172b/ghc >--------------------------------------------------------------- commit 82ca17bb3679963903f8633a0b3a43141b85172b Author: Joachim Breitner Date: Wed Mar 4 21:32:52 2015 +0100 Make SwitchTargets type abstract so that less code has to be touched when it is changed. >--------------------------------------------------------------- 82ca17bb3679963903f8633a0b3a43141b85172b compiler/cmm/CmmCommonBlockElim.hs | 9 ++------ compiler/cmm/CmmNode.hs | 37 ++++++++++++++++++++++++++------- compiler/codeGen/StgCmmUtils.hs | 4 +++- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 14 +++++-------- 4 files changed, 39 insertions(+), 25 deletions(-) diff --git a/compiler/cmm/CmmCommonBlockElim.hs b/compiler/cmm/CmmCommonBlockElim.hs index 234b729..6174929 100644 --- a/compiler/cmm/CmmCommonBlockElim.hs +++ b/compiler/cmm/CmmCommonBlockElim.hs @@ -203,15 +203,10 @@ eqLastWith eqBid (CmmCondBranch c1 t1 f1) (CmmCondBranch c2 t2 f2) = c1 == c2 && eqBid t1 t2 && eqBid f1 f2 eqLastWith eqBid (CmmCall t1 c1 g1 a1 r1 u1) (CmmCall t2 c2 g2 a2 r2 u2) = t1 == t2 && eqMaybeWith eqBid c1 c2 && a1 == a2 && r1 == r2 && u1 == u2 && g1 == g2 -eqLastWith eqBid (CmmSwitch e1 (mbdef1, bs1)) (CmmSwitch e2 (mbdef2, bs2)) = - e1 == e2 && eqMaybeWith eqBid mbdef1 mbdef2 && eqMapWith eqBid bs1 bs2 +eqLastWith eqBid (CmmSwitch e1 ids1) (CmmSwitch e2 ids2) = + e1 == e2 && eqSwitchTargetWith eqBid ids1 ids2 eqLastWith _ _ _ = False -eqMapWith :: Eq k => (a -> b -> Bool) -> M.Map k a -> M.Map k b -> Bool -eqMapWith eltEq m1 m2 = - all (\((k1,v1), (k2,v2)) -> k1 == k2 && v1 `eltEq` v2) $ - List.zip (M.toList m1) (M.toList m2) - eqMaybeWith :: (a -> b -> Bool) -> Maybe a -> Maybe b -> Bool eqMaybeWith eltEq (Just e) (Just e') = eltEq e e' eqMaybeWith _ Nothing Nothing = True diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index e6daa18..a3edc3f 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -22,8 +22,9 @@ module CmmNode ( -- * Switch SwitchTargets, + mkSwitchTargets, switchTargetsCases, switchTargetsDefault, mapSwitchTargets, switchTargetsToTable, switchTargetsFallThrough, - switchTargetsToList, + switchTargetsToList, eqSwitchTargetWith, ) where import CodeGen.Platform @@ -696,13 +697,25 @@ combineTickScopes s1 s2 -- See Note [Switch Table] -type SwitchTargets = (Maybe Label, M.Map Integer Label) +data SwitchTargets = + SwitchTargets (Maybe Label) (M.Map Integer Label) + deriving Eq + +mkSwitchTargets :: Maybe Label -> M.Map Integer Label -> SwitchTargets +mkSwitchTargets = SwitchTargets mapSwitchTargets :: (Label -> Label) -> SwitchTargets -> SwitchTargets -mapSwitchTargets f (mbdef, branches) = (fmap f mbdef, fmap f branches) +mapSwitchTargets f (SwitchTargets mbdef branches) + = SwitchTargets (fmap f mbdef) (fmap f branches) + +switchTargetsCases :: SwitchTargets -> [(Integer, Label)] +switchTargetsCases (SwitchTargets _ branches) = M.toList branches + +switchTargetsDefault :: SwitchTargets -> Maybe Label +switchTargetsDefault (SwitchTargets mbdef _) = mbdef switchTargetsToTable :: SwitchTargets -> [Maybe Label] -switchTargetsToTable (mbdef, branches) +switchTargetsToTable (SwitchTargets mbdef branches) | min < 0 = pprPanic "mapSwitchTargets" empty | otherwise = [ labelFor i | i <- [0..max] ] where @@ -712,19 +725,27 @@ switchTargetsToTable (mbdef, branches) Nothing -> mbdef switchTargetsToList :: SwitchTargets -> [Label] -switchTargetsToList (mbdef, branches) = maybeToList mbdef ++ M.elems branches +switchTargetsToList (SwitchTargets mbdef branches) = maybeToList mbdef ++ M.elems branches -- | Groups cases with equal targets, suitable for pretty-printing to a -- c-like switch statement with fall-through semantics. switchTargetsFallThrough :: SwitchTargets -> ([([Integer], Label)], Maybe Label) -switchTargetsFallThrough (mbdef, branches) = (groups, mbdef) +switchTargetsFallThrough (SwitchTargets mbdef branches) = (groups, mbdef) where groups = map (\xs -> (map fst xs, snd (head xs))) $ groupBy ((==) `on` snd) $ M.toList branches - - +eqSwitchTargetWith :: (Label -> Label -> Bool) -> SwitchTargets -> SwitchTargets -> Bool +eqSwitchTargetWith eq (SwitchTargets mbdef1 ids1) (SwitchTargets mbdef2 ids2) = + goMB mbdef1 mbdef2 && goList (M.toList ids1) (M.toList ids2) + where + goMB Nothing Nothing = True + goMB (Just l1) (Just l2) = l1 `eq` l2 + goMB _ _ = False + goList [] [] = True + goList ((i1,l1):ls1) ((i2,l2):ls2) = i1 == i2 && l1 `eq` l2 && goList ls1 ls2 + goList _ _ = False -- Note [SwitchTargets]: -- ~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index 2ad794e..4935c7f 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -550,7 +550,9 @@ mk_switch tag_expr branches mb_deflt lo_tag hi_tag via_C , i <= real_hi_tag ] dflags <- getDynFlags - return (mkSwitch (cmmOffset dflags tag_expr (- real_lo_tag)) (Nothing, arms)) + return $ mkSwitch + (cmmOffset dflags tag_expr (- real_lo_tag)) + (mkSwitchTargets Nothing arms) -- if we can knock off a bunch of default cases with one if, then do so | Just deflt <- mb_deflt, (lowest_branch - lo_tag) >= n_branches diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 230c64f..9049214 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -32,7 +32,6 @@ import Unique import Data.List ( nub ) import Data.Maybe ( catMaybes ) -import qualified Data.Map as M type Atomic = Bool type LlvmStatements = OrdList LlvmStatement @@ -825,19 +824,16 @@ For a real example of this, see ./rts/StgStdThunks.cmm -- | Switch branch --- --- N.B. We remove Nothing's from the list of branches, as they are 'undefined'. --- However, they may be defined one day, so we better document this behaviour. genSwitch :: CmmExpr -> SwitchTargets -> LlvmM StmtData -genSwitch cond (mbdef, ids) = do +genSwitch cond ids = do (vc, stmts, top) <- exprToVar cond let ty = getVarType vc - let pairs = M.toList ids - let labels = map (\(ix, b) -> (mkIntLit ty ix, blockIdToLlvm b)) pairs + let labels = [ (mkIntLit ty ix, blockIdToLlvm b) + | (ix, b) <- switchTargetsCases ids ] -- out of range is undefined, so let's just branch to first label - let defLbl | Just l <- mbdef = blockIdToLlvm l - | otherwise = snd (head labels) + let defLbl | Just l <- switchTargetsDefault ids = blockIdToLlvm l + | otherwise = snd (head labels) let s1 = Switch vc defLbl labels return $ (stmts `snocOL` s1, top) From git at git.haskell.org Wed Mar 4 20:35:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 20:35:08 +0000 (UTC) Subject: [commit: ghc] master: Remove unused/undocumented flag `-fhpc-no-auto` (8a5d320) Message-ID: <20150304203508.1A4173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8a5d32057fb899810d5fb614e57a319b4a951afc/ghc >--------------------------------------------------------------- commit 8a5d32057fb899810d5fb614e57a319b4a951afc Author: Thomas Miedema Date: Wed Mar 4 21:26:31 2015 +0100 Remove unused/undocumented flag `-fhpc-no-auto` Added in 53a5d0b01. Perhaps accidentally? It didn't do anything back then either. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D700 >--------------------------------------------------------------- 8a5d32057fb899810d5fb614e57a319b4a951afc compiler/main/DynFlags.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index ef9b4e6..8d6d429 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -388,7 +388,6 @@ data GeneralFlag | Opt_PrintBindResult | Opt_Haddock | Opt_HaddockOptions - | Opt_Hpc_No_Auto | Opt_BreakOnException | Opt_BreakOnError | Opt_PrintEvldWithShow @@ -2954,7 +2953,6 @@ fFlags = [ flagSpec "ghci-sandbox" Opt_GhciSandbox, flagSpec "helpful-errors" Opt_HelpfulErrors, flagSpec "hpc" Opt_Hpc, - flagSpec "hpc-no-auto" Opt_Hpc_No_Auto, flagSpec "ignore-asserts" Opt_IgnoreAsserts, flagSpec "ignore-interface-pragmas" Opt_IgnoreInterfacePragmas, flagGhciSpec "implicit-import-qualified" Opt_ImplicitImportQualified, From git at git.haskell.org Wed Mar 4 21:02:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 21:02:29 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Make SwitchTargets type abstract (f83791f) Message-ID: <20150304210229.069343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/f83791f8f3ca05b970f45ad84194c76de0a1407d/ghc >--------------------------------------------------------------- commit f83791f8f3ca05b970f45ad84194c76de0a1407d Author: Joachim Breitner Date: Wed Mar 4 21:32:52 2015 +0100 Make SwitchTargets type abstract so that less code has to be touched when it is changed. >--------------------------------------------------------------- f83791f8f3ca05b970f45ad84194c76de0a1407d compiler/cmm/CmmCommonBlockElim.hs | 9 ++------ compiler/cmm/CmmNode.hs | 37 ++++++++++++++++++++++++++------- compiler/cmm/CmmParse.y | 2 +- compiler/codeGen/StgCmmUtils.hs | 4 +++- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 14 +++++-------- 5 files changed, 40 insertions(+), 26 deletions(-) diff --git a/compiler/cmm/CmmCommonBlockElim.hs b/compiler/cmm/CmmCommonBlockElim.hs index 234b729..6174929 100644 --- a/compiler/cmm/CmmCommonBlockElim.hs +++ b/compiler/cmm/CmmCommonBlockElim.hs @@ -203,15 +203,10 @@ eqLastWith eqBid (CmmCondBranch c1 t1 f1) (CmmCondBranch c2 t2 f2) = c1 == c2 && eqBid t1 t2 && eqBid f1 f2 eqLastWith eqBid (CmmCall t1 c1 g1 a1 r1 u1) (CmmCall t2 c2 g2 a2 r2 u2) = t1 == t2 && eqMaybeWith eqBid c1 c2 && a1 == a2 && r1 == r2 && u1 == u2 && g1 == g2 -eqLastWith eqBid (CmmSwitch e1 (mbdef1, bs1)) (CmmSwitch e2 (mbdef2, bs2)) = - e1 == e2 && eqMaybeWith eqBid mbdef1 mbdef2 && eqMapWith eqBid bs1 bs2 +eqLastWith eqBid (CmmSwitch e1 ids1) (CmmSwitch e2 ids2) = + e1 == e2 && eqSwitchTargetWith eqBid ids1 ids2 eqLastWith _ _ _ = False -eqMapWith :: Eq k => (a -> b -> Bool) -> M.Map k a -> M.Map k b -> Bool -eqMapWith eltEq m1 m2 = - all (\((k1,v1), (k2,v2)) -> k1 == k2 && v1 `eltEq` v2) $ - List.zip (M.toList m1) (M.toList m2) - eqMaybeWith :: (a -> b -> Bool) -> Maybe a -> Maybe b -> Bool eqMaybeWith eltEq (Just e) (Just e') = eltEq e e' eqMaybeWith _ Nothing Nothing = True diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index e6daa18..a3edc3f 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -22,8 +22,9 @@ module CmmNode ( -- * Switch SwitchTargets, + mkSwitchTargets, switchTargetsCases, switchTargetsDefault, mapSwitchTargets, switchTargetsToTable, switchTargetsFallThrough, - switchTargetsToList, + switchTargetsToList, eqSwitchTargetWith, ) where import CodeGen.Platform @@ -696,13 +697,25 @@ combineTickScopes s1 s2 -- See Note [Switch Table] -type SwitchTargets = (Maybe Label, M.Map Integer Label) +data SwitchTargets = + SwitchTargets (Maybe Label) (M.Map Integer Label) + deriving Eq + +mkSwitchTargets :: Maybe Label -> M.Map Integer Label -> SwitchTargets +mkSwitchTargets = SwitchTargets mapSwitchTargets :: (Label -> Label) -> SwitchTargets -> SwitchTargets -mapSwitchTargets f (mbdef, branches) = (fmap f mbdef, fmap f branches) +mapSwitchTargets f (SwitchTargets mbdef branches) + = SwitchTargets (fmap f mbdef) (fmap f branches) + +switchTargetsCases :: SwitchTargets -> [(Integer, Label)] +switchTargetsCases (SwitchTargets _ branches) = M.toList branches + +switchTargetsDefault :: SwitchTargets -> Maybe Label +switchTargetsDefault (SwitchTargets mbdef _) = mbdef switchTargetsToTable :: SwitchTargets -> [Maybe Label] -switchTargetsToTable (mbdef, branches) +switchTargetsToTable (SwitchTargets mbdef branches) | min < 0 = pprPanic "mapSwitchTargets" empty | otherwise = [ labelFor i | i <- [0..max] ] where @@ -712,19 +725,27 @@ switchTargetsToTable (mbdef, branches) Nothing -> mbdef switchTargetsToList :: SwitchTargets -> [Label] -switchTargetsToList (mbdef, branches) = maybeToList mbdef ++ M.elems branches +switchTargetsToList (SwitchTargets mbdef branches) = maybeToList mbdef ++ M.elems branches -- | Groups cases with equal targets, suitable for pretty-printing to a -- c-like switch statement with fall-through semantics. switchTargetsFallThrough :: SwitchTargets -> ([([Integer], Label)], Maybe Label) -switchTargetsFallThrough (mbdef, branches) = (groups, mbdef) +switchTargetsFallThrough (SwitchTargets mbdef branches) = (groups, mbdef) where groups = map (\xs -> (map fst xs, snd (head xs))) $ groupBy ((==) `on` snd) $ M.toList branches - - +eqSwitchTargetWith :: (Label -> Label -> Bool) -> SwitchTargets -> SwitchTargets -> Bool +eqSwitchTargetWith eq (SwitchTargets mbdef1 ids1) (SwitchTargets mbdef2 ids2) = + goMB mbdef1 mbdef2 && goList (M.toList ids1) (M.toList ids2) + where + goMB Nothing Nothing = True + goMB (Just l1) (Just l2) = l1 `eq` l2 + goMB _ _ = False + goList [] [] = True + goList ((i1,l1):ls1) ((i2,l2):ls2) = i1 == i2 && l1 `eq` l2 && goList ls1 ls2 + goList _ _ = False -- Note [SwitchTargets]: -- ~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 84b297a..4f286f5 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -1326,7 +1326,7 @@ doSwitch mb_range scrut arms deflt expr <- scrut -- ToDo: check for out of range and jump to default if necessary - emit $ mkSwitch expr (dflt_entry, table) + emit $ mkSwitch expr (mkSwitchTargets dflt_entry table) where emitArm :: ([Int],Either BlockId (CmmParse ())) -> CmmParse [(Integer,BlockId)] emitArm (ints,Left blockid) = return [ (fromIntegral i,blockid) | i <- ints ] diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index 2ad794e..4935c7f 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -550,7 +550,9 @@ mk_switch tag_expr branches mb_deflt lo_tag hi_tag via_C , i <= real_hi_tag ] dflags <- getDynFlags - return (mkSwitch (cmmOffset dflags tag_expr (- real_lo_tag)) (Nothing, arms)) + return $ mkSwitch + (cmmOffset dflags tag_expr (- real_lo_tag)) + (mkSwitchTargets Nothing arms) -- if we can knock off a bunch of default cases with one if, then do so | Just deflt <- mb_deflt, (lowest_branch - lo_tag) >= n_branches diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 230c64f..9049214 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -32,7 +32,6 @@ import Unique import Data.List ( nub ) import Data.Maybe ( catMaybes ) -import qualified Data.Map as M type Atomic = Bool type LlvmStatements = OrdList LlvmStatement @@ -825,19 +824,16 @@ For a real example of this, see ./rts/StgStdThunks.cmm -- | Switch branch --- --- N.B. We remove Nothing's from the list of branches, as they are 'undefined'. --- However, they may be defined one day, so we better document this behaviour. genSwitch :: CmmExpr -> SwitchTargets -> LlvmM StmtData -genSwitch cond (mbdef, ids) = do +genSwitch cond ids = do (vc, stmts, top) <- exprToVar cond let ty = getVarType vc - let pairs = M.toList ids - let labels = map (\(ix, b) -> (mkIntLit ty ix, blockIdToLlvm b)) pairs + let labels = [ (mkIntLit ty ix, blockIdToLlvm b) + | (ix, b) <- switchTargetsCases ids ] -- out of range is undefined, so let's just branch to first label - let defLbl | Just l <- mbdef = blockIdToLlvm l - | otherwise = snd (head labels) + let defLbl | Just l <- switchTargetsDefault ids = blockIdToLlvm l + | otherwise = snd (head labels) let s1 = Switch vc defLbl labels return $ (stmts `snocOL` s1, top) From git at git.haskell.org Wed Mar 4 21:17:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 21:17:16 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Add an (optional) range field to the SwitchTargets data type (27f91c3) Message-ID: <20150304211716.CB5483A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/27f91c3b3ae34aa46ae624f8024f7c9df8c559e9/ghc >--------------------------------------------------------------- commit 27f91c3b3ae34aa46ae624f8024f7c9df8c559e9 Author: Joachim Breitner Date: Wed Mar 4 22:16:44 2015 +0100 Add an (optional) range field to the SwitchTargets data type As there is one in the Cmm syntax, and we might be able to exploit that during code generation. >--------------------------------------------------------------- 27f91c3b3ae34aa46ae624f8024f7c9df8c559e9 compiler/cmm/CmmNode.hs | 36 +++++++++++++++++++++++------------- compiler/cmm/CmmParse.y | 26 ++++++++++++++------------ compiler/codeGen/StgCmmUtils.hs | 2 +- 3 files changed, 38 insertions(+), 26 deletions(-) diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index a3edc3f..4b3dfd2 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -698,25 +698,34 @@ combineTickScopes s1 s2 -- See Note [Switch Table] data SwitchTargets = - SwitchTargets (Maybe Label) (M.Map Integer Label) + SwitchTargets (Maybe (Integer, Integer)) (Maybe Label) (M.Map Integer Label) deriving Eq -mkSwitchTargets :: Maybe Label -> M.Map Integer Label -> SwitchTargets -mkSwitchTargets = SwitchTargets +-- mkSwitchTargets normalises the map a bit: +mkSwitchTargets :: Maybe (Integer, Integer) -> Maybe Label -> M.Map Integer Label -> SwitchTargets +mkSwitchTargets mbrange mbdef ids + = SwitchTargets mbrange mbdef $ dropDefault $ restrict ids + where + -- It drops entries outside the range, if there is a range + restrict | Just (lo,hi) <- mbrange = M.filterWithKey (\x _ -> lo <= x && x <= hi) + | otherwise = id + -- It entries that equal the default, if there is a default + dropDefault | Just l <- mbdef = M.filter (/= l) + | otherwise = id mapSwitchTargets :: (Label -> Label) -> SwitchTargets -> SwitchTargets -mapSwitchTargets f (SwitchTargets mbdef branches) - = SwitchTargets (fmap f mbdef) (fmap f branches) +mapSwitchTargets f (SwitchTargets range mbdef branches) + = SwitchTargets range (fmap f mbdef) (fmap f branches) switchTargetsCases :: SwitchTargets -> [(Integer, Label)] -switchTargetsCases (SwitchTargets _ branches) = M.toList branches +switchTargetsCases (SwitchTargets _ _ branches) = M.toList branches switchTargetsDefault :: SwitchTargets -> Maybe Label -switchTargetsDefault (SwitchTargets mbdef _) = mbdef +switchTargetsDefault (SwitchTargets _ mbdef _) = mbdef switchTargetsToTable :: SwitchTargets -> [Maybe Label] -switchTargetsToTable (SwitchTargets mbdef branches) - | min < 0 = pprPanic "mapSwitchTargets" empty +switchTargetsToTable (SwitchTargets _ mbdef branches) + | min < 0 = pprPanic "mapSwitchTargets" empty | otherwise = [ labelFor i | i <- [0..max] ] where min = fst (M.findMin branches) @@ -725,20 +734,21 @@ switchTargetsToTable (SwitchTargets mbdef branches) Nothing -> mbdef switchTargetsToList :: SwitchTargets -> [Label] -switchTargetsToList (SwitchTargets mbdef branches) = maybeToList mbdef ++ M.elems branches +switchTargetsToList (SwitchTargets _ mbdef branches) + = maybeToList mbdef ++ M.elems branches -- | Groups cases with equal targets, suitable for pretty-printing to a -- c-like switch statement with fall-through semantics. switchTargetsFallThrough :: SwitchTargets -> ([([Integer], Label)], Maybe Label) -switchTargetsFallThrough (SwitchTargets mbdef branches) = (groups, mbdef) +switchTargetsFallThrough (SwitchTargets _ mbdef branches) = (groups, mbdef) where groups = map (\xs -> (map fst xs, snd (head xs))) $ groupBy ((==) `on` snd) $ M.toList branches eqSwitchTargetWith :: (Label -> Label -> Bool) -> SwitchTargets -> SwitchTargets -> Bool -eqSwitchTargetWith eq (SwitchTargets mbdef1 ids1) (SwitchTargets mbdef2 ids2) = - goMB mbdef1 mbdef2 && goList (M.toList ids1) (M.toList ids2) +eqSwitchTargetWith eq (SwitchTargets range1 mbdef1 ids1) (SwitchTargets range2 mbdef2 ids2) = + range1 == range2 && goMB mbdef1 mbdef2 && goList (M.toList ids1) (M.toList ids2) where goMB Nothing Nothing = True goMB (Just l1) (Just l2) = l1 `eq` l2 diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 4f286f5..7ec1e4a 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -677,24 +677,24 @@ globals :: { [GlobalReg] } : GLOBALREG { [$1] } | GLOBALREG ',' globals { $1 : $3 } -maybe_range :: { Maybe (Int,Int) } - : '[' INT '..' INT ']' { Just (fromIntegral $2, fromIntegral $4) } +maybe_range :: { Maybe (Integer,Integer) } + : '[' INT '..' INT ']' { Just ($2, $4) } | {- empty -} { Nothing } -arms :: { [CmmParse ([Int],Either BlockId (CmmParse ()))] } +arms :: { [CmmParse ([Integer],Either BlockId (CmmParse ()))] } : {- empty -} { [] } | arm arms { $1 : $2 } -arm :: { CmmParse ([Int],Either BlockId (CmmParse ())) } +arm :: { CmmParse ([Integer],Either BlockId (CmmParse ())) } : 'case' ints ':' arm_body { do b <- $4; return ($2, b) } arm_body :: { CmmParse (Either BlockId (CmmParse ())) } : '{' body '}' { return (Right (withSourceNote $1 $3 $2)) } | 'goto' NAME ';' { do l <- lookupLabel $2; return (Left l) } -ints :: { [Int] } - : INT { [ fromIntegral $1 ] } - | INT ',' ints { fromIntegral $1 : $3 } +ints :: { [Integer] } + : INT { [ $1 ] } + | INT ',' ints { $1 : $3 } default :: { Maybe (CmmParse ()) } : 'default' ':' '{' body '}' { Just (withSourceNote $3 $5 $4) } @@ -1308,7 +1308,9 @@ withSourceNote a b parse = do -- optional range on the switch (eg. switch [0..7] {...}), or by -- the minimum/maximum values from the branches. -doSwitch :: Maybe (Int,Int) -> CmmParse CmmExpr -> [([Int],Either BlockId (CmmParse ()))] +doSwitch :: Maybe (Integer,Integer) + -> CmmParse CmmExpr + -> [([Integer],Either BlockId (CmmParse ()))] -> Maybe (CmmParse ()) -> CmmParse () doSwitch mb_range scrut arms deflt = do @@ -1326,13 +1328,13 @@ doSwitch mb_range scrut arms deflt expr <- scrut -- ToDo: check for out of range and jump to default if necessary - emit $ mkSwitch expr (mkSwitchTargets dflt_entry table) + emit $ mkSwitch expr (mkSwitchTargets mb_range dflt_entry table) where - emitArm :: ([Int],Either BlockId (CmmParse ())) -> CmmParse [(Integer,BlockId)] - emitArm (ints,Left blockid) = return [ (fromIntegral i,blockid) | i <- ints ] + emitArm :: ([Integer],Either BlockId (CmmParse ())) -> CmmParse [(Integer,BlockId)] + emitArm (ints,Left blockid) = return [ (i,blockid) | i <- ints ] emitArm (ints,Right code) = do blockid <- forkLabelledCode code - return [ (fromIntegral i,blockid) | i <- ints ] + return [ (i,blockid) | i <- ints ] forkLabelledCode :: CmmParse () -> CmmParse BlockId forkLabelledCode p = do diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index 4935c7f..7e2279b 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -552,7 +552,7 @@ mk_switch tag_expr branches mb_deflt lo_tag hi_tag via_C dflags <- getDynFlags return $ mkSwitch (cmmOffset dflags tag_expr (- real_lo_tag)) - (mkSwitchTargets Nothing arms) + (mkSwitchTargets (Just (0, fromIntegral (real_hi_tag-real_lo_tag))) Nothing arms) -- if we can knock off a bunch of default cases with one if, then do so | Just deflt <- mb_deflt, (lowest_branch - lo_tag) >= n_branches From git at git.haskell.org Wed Mar 4 22:14:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 22:14:23 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Move table offset to code generation phase (55f2096) Message-ID: <20150304221423.848613A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/55f20969acf76266b164d27773096e0a08512d57/ghc >--------------------------------------------------------------- commit 55f20969acf76266b164d27773096e0a08512d57 Author: Joachim Breitner Date: Wed Mar 4 23:13:28 2015 +0100 CmmSwitch: Move table offset to code generation phase Previously, if a switch statement would not start with 0, the Stg ? Cmm phase would offset the scrutinee to make the table zero-based. In order to have CmmSwitch a bit higher level, this step is moved to the Cmm ? Assembly phase. This also means that in the llvm backend, more is left to the LLVM compiler. >--------------------------------------------------------------- 55f20969acf76266b164d27773096e0a08512d57 compiler/cmm/CmmNode.hs | 18 ++++++++++++------ compiler/codeGen/StgCmmUtils.hs | 10 ++++++---- compiler/nativeGen/PPC/CodeGen.hs | 6 +++--- compiler/nativeGen/SPARC/CodeGen.hs | 4 ++-- compiler/nativeGen/X86/CodeGen.hs | 6 +++--- 5 files changed, 26 insertions(+), 18 deletions(-) diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index 4b3dfd2..90d1b77 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -723,13 +723,19 @@ switchTargetsCases (SwitchTargets _ _ branches) = M.toList branches switchTargetsDefault :: SwitchTargets -> Maybe Label switchTargetsDefault (SwitchTargets _ mbdef _) = mbdef -switchTargetsToTable :: SwitchTargets -> [Maybe Label] -switchTargetsToTable (SwitchTargets _ mbdef branches) - | min < 0 = pprPanic "mapSwitchTargets" empty - | otherwise = [ labelFor i | i <- [0..max] ] +-- switchTargetsToTable creates a dense jump table, usable for code generation. +-- This is not possible if there is no explicit range, so before code generation +-- all switch statements need to be transformed to one with an explicit range. +-- +-- Returns an offset to add to the value; the list is 0-based on the result +-- +-- TODO: Is the conversion from Integral to Int fishy? +switchTargetsToTable :: SwitchTargets -> (Int, [Maybe Label]) +switchTargetsToTable (SwitchTargets Nothing _mbdef _branches) + = pprPanic "switchTargetsToTable" empty +switchTargetsToTable (SwitchTargets (Just (lo,hi)) mbdef branches) + = (fromIntegral (-lo), [ labelFor i | i <- [lo..hi] ]) where - min = fst (M.findMin branches) - max = fst (M.findMax branches) labelFor i = case M.lookup i branches of Just l -> Just l Nothing -> mbdef diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index 7e2279b..d1a9cf8 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -544,15 +544,17 @@ mk_switch tag_expr branches mb_deflt lo_tag hi_tag via_C -- either end of the range (see below), so the first -- tag of a real branch is real_lo_tag (not lo_tag). arms :: M.Map Integer BlockId - arms = M.fromList [ (fromIntegral (i - real_lo_tag), l) + arms = M.fromList [ (fromIntegral i, l) | (i,l) <- branches , real_lo_tag <= i , i <= real_hi_tag ] - dflags <- getDynFlags + range = (fromIntegral real_lo_tag, fromIntegral real_hi_tag) + return $ mkSwitch - (cmmOffset dflags tag_expr (- real_lo_tag)) - (mkSwitchTargets (Just (0, fromIntegral (real_hi_tag-real_lo_tag))) Nothing arms) + -- (cmmOffset dflags tag_expr (- real_lo_tag)) + tag_expr + (mkSwitchTargets (Just range) Nothing arms) -- if we can knock off a bunch of default cases with one if, then do so | Just deflt <- mb_deflt, (lowest_branch - lo_tag) >= n_branches diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs index 552d9ac..fb42c07 100644 --- a/compiler/nativeGen/PPC/CodeGen.hs +++ b/compiler/nativeGen/PPC/CodeGen.hs @@ -1205,7 +1205,7 @@ genSwitch :: DynFlags -> CmmExpr -> SwitchTargets -> NatM InstrBlock genSwitch dflags expr targets | gopt Opt_PIC dflags = do - (reg,e_code) <- getSomeReg expr + (reg,e_code) <- getSomeReg (cmmOffset dflags expr offset) tmp <- getNewRegNat II32 lbl <- getNewLabelNat dflags <- getDynFlags @@ -1221,7 +1221,7 @@ genSwitch dflags expr targets return code | otherwise = do - (reg,e_code) <- getSomeReg expr + (reg,e_code) <- getSomeReg (cmmOffset dflags expr offset) tmp <- getNewRegNat II32 lbl <- getNewLabelNat let code = e_code `appOL` toOL [ @@ -1232,7 +1232,7 @@ genSwitch dflags expr targets BCTR ids (Just lbl) ] return code - where ids = switchTargetsToTable targets + where (offset, ids) = switchTargetsToTable targets generateJumpTableForInstr :: DynFlags -> Instr -> Maybe (NatCmmDecl CmmStatics Instr) diff --git a/compiler/nativeGen/SPARC/CodeGen.hs b/compiler/nativeGen/SPARC/CodeGen.hs index 8631ab8..3f49afe 100644 --- a/compiler/nativeGen/SPARC/CodeGen.hs +++ b/compiler/nativeGen/SPARC/CodeGen.hs @@ -314,7 +314,7 @@ genSwitch dflags expr targets = error "MachCodeGen: sparc genSwitch PIC not finished\n" | otherwise - = do (e_reg, e_code) <- getSomeReg expr + = do (e_reg, e_code) <- getSomeReg (cmmOffset dflags expr offset) base_reg <- getNewRegNat II32 offset_reg <- getNewRegNat II32 @@ -335,7 +335,7 @@ genSwitch dflags expr targets , LD II32 (AddrRegReg base_reg offset_reg) dst , JMP_TBL (AddrRegImm dst (ImmInt 0)) ids label , NOP ] - where ids = switchTargetsToTable targets + where (offset, ids) = switchTargetsToTable targets generateJumpTableForInstr :: DynFlags -> Instr -> Maybe (NatCmmDecl CmmStatics Instr) diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs index 6e0e8ad..a826531 100644 --- a/compiler/nativeGen/X86/CodeGen.hs +++ b/compiler/nativeGen/X86/CodeGen.hs @@ -2589,7 +2589,7 @@ genSwitch :: DynFlags -> CmmExpr -> SwitchTargets -> NatM InstrBlock genSwitch dflags expr targets | gopt Opt_PIC dflags = do - (reg,e_code) <- getSomeReg expr + (reg,e_code) <- getSomeReg (cmmOffset dflags expr offset) lbl <- getNewLabelNat dflags <- getDynFlags dynRef <- cmmMakeDynamicReference dflags DataReference lbl @@ -2631,14 +2631,14 @@ genSwitch dflags expr targets ] | otherwise = do - (reg,e_code) <- getSomeReg expr + (reg,e_code) <- getSomeReg (cmmOffset dflags expr offset) lbl <- getNewLabelNat let op = OpAddr (AddrBaseIndex EABaseNone (EAIndex reg (wORD_SIZE dflags)) (ImmCLbl lbl)) code = e_code `appOL` toOL [ JMP_TBL op ids ReadOnlyData lbl ] return code - where ids = switchTargetsToTable targets + where (offset, ids) = switchTargetsToTable targets generateJumpTableForInstr :: DynFlags -> Instr -> Maybe (NatCmmDecl (Alignment, CmmStatics) Instr) generateJumpTableForInstr dflags (JMP_TBL _ ids section lbl) From git at git.haskell.org Wed Mar 4 22:21:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 22:21:39 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Add an (optional) range field to the SwitchTargets data type (86db745) Message-ID: <20150304222139.30E153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/86db7454880dbcfeec5f529492b68ef1cc71277f/ghc >--------------------------------------------------------------- commit 86db7454880dbcfeec5f529492b68ef1cc71277f Author: Joachim Breitner Date: Wed Mar 4 22:16:44 2015 +0100 Add an (optional) range field to the SwitchTargets data type As there is one in the Cmm syntax, and we might be able to exploit that during code generation. >--------------------------------------------------------------- 86db7454880dbcfeec5f529492b68ef1cc71277f compiler/cmm/CmmNode.hs | 36 +++++++++++++++++++++++------------- compiler/cmm/CmmParse.y | 26 ++++++++++++++------------ compiler/codeGen/StgCmmUtils.hs | 9 +++------ 3 files changed, 40 insertions(+), 31 deletions(-) diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index a3edc3f..4b3dfd2 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -698,25 +698,34 @@ combineTickScopes s1 s2 -- See Note [Switch Table] data SwitchTargets = - SwitchTargets (Maybe Label) (M.Map Integer Label) + SwitchTargets (Maybe (Integer, Integer)) (Maybe Label) (M.Map Integer Label) deriving Eq -mkSwitchTargets :: Maybe Label -> M.Map Integer Label -> SwitchTargets -mkSwitchTargets = SwitchTargets +-- mkSwitchTargets normalises the map a bit: +mkSwitchTargets :: Maybe (Integer, Integer) -> Maybe Label -> M.Map Integer Label -> SwitchTargets +mkSwitchTargets mbrange mbdef ids + = SwitchTargets mbrange mbdef $ dropDefault $ restrict ids + where + -- It drops entries outside the range, if there is a range + restrict | Just (lo,hi) <- mbrange = M.filterWithKey (\x _ -> lo <= x && x <= hi) + | otherwise = id + -- It entries that equal the default, if there is a default + dropDefault | Just l <- mbdef = M.filter (/= l) + | otherwise = id mapSwitchTargets :: (Label -> Label) -> SwitchTargets -> SwitchTargets -mapSwitchTargets f (SwitchTargets mbdef branches) - = SwitchTargets (fmap f mbdef) (fmap f branches) +mapSwitchTargets f (SwitchTargets range mbdef branches) + = SwitchTargets range (fmap f mbdef) (fmap f branches) switchTargetsCases :: SwitchTargets -> [(Integer, Label)] -switchTargetsCases (SwitchTargets _ branches) = M.toList branches +switchTargetsCases (SwitchTargets _ _ branches) = M.toList branches switchTargetsDefault :: SwitchTargets -> Maybe Label -switchTargetsDefault (SwitchTargets mbdef _) = mbdef +switchTargetsDefault (SwitchTargets _ mbdef _) = mbdef switchTargetsToTable :: SwitchTargets -> [Maybe Label] -switchTargetsToTable (SwitchTargets mbdef branches) - | min < 0 = pprPanic "mapSwitchTargets" empty +switchTargetsToTable (SwitchTargets _ mbdef branches) + | min < 0 = pprPanic "mapSwitchTargets" empty | otherwise = [ labelFor i | i <- [0..max] ] where min = fst (M.findMin branches) @@ -725,20 +734,21 @@ switchTargetsToTable (SwitchTargets mbdef branches) Nothing -> mbdef switchTargetsToList :: SwitchTargets -> [Label] -switchTargetsToList (SwitchTargets mbdef branches) = maybeToList mbdef ++ M.elems branches +switchTargetsToList (SwitchTargets _ mbdef branches) + = maybeToList mbdef ++ M.elems branches -- | Groups cases with equal targets, suitable for pretty-printing to a -- c-like switch statement with fall-through semantics. switchTargetsFallThrough :: SwitchTargets -> ([([Integer], Label)], Maybe Label) -switchTargetsFallThrough (SwitchTargets mbdef branches) = (groups, mbdef) +switchTargetsFallThrough (SwitchTargets _ mbdef branches) = (groups, mbdef) where groups = map (\xs -> (map fst xs, snd (head xs))) $ groupBy ((==) `on` snd) $ M.toList branches eqSwitchTargetWith :: (Label -> Label -> Bool) -> SwitchTargets -> SwitchTargets -> Bool -eqSwitchTargetWith eq (SwitchTargets mbdef1 ids1) (SwitchTargets mbdef2 ids2) = - goMB mbdef1 mbdef2 && goList (M.toList ids1) (M.toList ids2) +eqSwitchTargetWith eq (SwitchTargets range1 mbdef1 ids1) (SwitchTargets range2 mbdef2 ids2) = + range1 == range2 && goMB mbdef1 mbdef2 && goList (M.toList ids1) (M.toList ids2) where goMB Nothing Nothing = True goMB (Just l1) (Just l2) = l1 `eq` l2 diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 4f286f5..7ec1e4a 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -677,24 +677,24 @@ globals :: { [GlobalReg] } : GLOBALREG { [$1] } | GLOBALREG ',' globals { $1 : $3 } -maybe_range :: { Maybe (Int,Int) } - : '[' INT '..' INT ']' { Just (fromIntegral $2, fromIntegral $4) } +maybe_range :: { Maybe (Integer,Integer) } + : '[' INT '..' INT ']' { Just ($2, $4) } | {- empty -} { Nothing } -arms :: { [CmmParse ([Int],Either BlockId (CmmParse ()))] } +arms :: { [CmmParse ([Integer],Either BlockId (CmmParse ()))] } : {- empty -} { [] } | arm arms { $1 : $2 } -arm :: { CmmParse ([Int],Either BlockId (CmmParse ())) } +arm :: { CmmParse ([Integer],Either BlockId (CmmParse ())) } : 'case' ints ':' arm_body { do b <- $4; return ($2, b) } arm_body :: { CmmParse (Either BlockId (CmmParse ())) } : '{' body '}' { return (Right (withSourceNote $1 $3 $2)) } | 'goto' NAME ';' { do l <- lookupLabel $2; return (Left l) } -ints :: { [Int] } - : INT { [ fromIntegral $1 ] } - | INT ',' ints { fromIntegral $1 : $3 } +ints :: { [Integer] } + : INT { [ $1 ] } + | INT ',' ints { $1 : $3 } default :: { Maybe (CmmParse ()) } : 'default' ':' '{' body '}' { Just (withSourceNote $3 $5 $4) } @@ -1308,7 +1308,9 @@ withSourceNote a b parse = do -- optional range on the switch (eg. switch [0..7] {...}), or by -- the minimum/maximum values from the branches. -doSwitch :: Maybe (Int,Int) -> CmmParse CmmExpr -> [([Int],Either BlockId (CmmParse ()))] +doSwitch :: Maybe (Integer,Integer) + -> CmmParse CmmExpr + -> [([Integer],Either BlockId (CmmParse ()))] -> Maybe (CmmParse ()) -> CmmParse () doSwitch mb_range scrut arms deflt = do @@ -1326,13 +1328,13 @@ doSwitch mb_range scrut arms deflt expr <- scrut -- ToDo: check for out of range and jump to default if necessary - emit $ mkSwitch expr (mkSwitchTargets dflt_entry table) + emit $ mkSwitch expr (mkSwitchTargets mb_range dflt_entry table) where - emitArm :: ([Int],Either BlockId (CmmParse ())) -> CmmParse [(Integer,BlockId)] - emitArm (ints,Left blockid) = return [ (fromIntegral i,blockid) | i <- ints ] + emitArm :: ([Integer],Either BlockId (CmmParse ())) -> CmmParse [(Integer,BlockId)] + emitArm (ints,Left blockid) = return [ (i,blockid) | i <- ints ] emitArm (ints,Right code) = do blockid <- forkLabelledCode code - return [ (fromIntegral i,blockid) | i <- ints ] + return [ (i,blockid) | i <- ints ] forkLabelledCode :: CmmParse () -> CmmParse BlockId forkLabelledCode p = do diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index 4935c7f..df913d1 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -544,15 +544,12 @@ mk_switch tag_expr branches mb_deflt lo_tag hi_tag via_C -- either end of the range (see below), so the first -- tag of a real branch is real_lo_tag (not lo_tag). arms :: M.Map Integer BlockId - arms = M.fromList [ (fromIntegral (i - real_lo_tag), l) - | (i,l) <- branches - , real_lo_tag <= i - , i <= real_hi_tag - ] + arms = M.fromList [ (fromIntegral i, l) | (i,l) <- branches ] + dflags <- getDynFlags return $ mkSwitch (cmmOffset dflags tag_expr (- real_lo_tag)) - (mkSwitchTargets Nothing arms) + (mkSwitchTargets (Just (0, fromIntegral (real_hi_tag-real_lo_tag))) Nothing arms) -- if we can knock off a bunch of default cases with one if, then do so | Just deflt <- mb_deflt, (lowest_branch - lo_tag) >= n_branches From git at git.haskell.org Wed Mar 4 22:21:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Mar 2015 22:21:41 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Move table offset to code generation phase (8f5d606) Message-ID: <20150304222141.E593B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/8f5d60622b107d1bbf306abbc6fefb56c040c35e/ghc >--------------------------------------------------------------- commit 8f5d60622b107d1bbf306abbc6fefb56c040c35e Author: Joachim Breitner Date: Wed Mar 4 23:13:28 2015 +0100 CmmSwitch: Move table offset to code generation phase Previously, if a switch statement would not start with 0, the Stg ? Cmm phase would offset the scrutinee to make the table zero-based. In order to have CmmSwitch a bit higher level, this step is moved to the Cmm ? Assembly phase. This also means that in the llvm backend, more is more logic left to the LLVM compiler (which hopefully knows best how to compile a switch statement). >--------------------------------------------------------------- 8f5d60622b107d1bbf306abbc6fefb56c040c35e compiler/cmm/CmmNode.hs | 18 ++++++++++++------ compiler/codeGen/StgCmmUtils.hs | 6 +++--- compiler/nativeGen/PPC/CodeGen.hs | 6 +++--- compiler/nativeGen/SPARC/CodeGen.hs | 4 ++-- compiler/nativeGen/X86/CodeGen.hs | 6 +++--- 5 files changed, 23 insertions(+), 17 deletions(-) diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index 4b3dfd2..90d1b77 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -723,13 +723,19 @@ switchTargetsCases (SwitchTargets _ _ branches) = M.toList branches switchTargetsDefault :: SwitchTargets -> Maybe Label switchTargetsDefault (SwitchTargets _ mbdef _) = mbdef -switchTargetsToTable :: SwitchTargets -> [Maybe Label] -switchTargetsToTable (SwitchTargets _ mbdef branches) - | min < 0 = pprPanic "mapSwitchTargets" empty - | otherwise = [ labelFor i | i <- [0..max] ] +-- switchTargetsToTable creates a dense jump table, usable for code generation. +-- This is not possible if there is no explicit range, so before code generation +-- all switch statements need to be transformed to one with an explicit range. +-- +-- Returns an offset to add to the value; the list is 0-based on the result +-- +-- TODO: Is the conversion from Integral to Int fishy? +switchTargetsToTable :: SwitchTargets -> (Int, [Maybe Label]) +switchTargetsToTable (SwitchTargets Nothing _mbdef _branches) + = pprPanic "switchTargetsToTable" empty +switchTargetsToTable (SwitchTargets (Just (lo,hi)) mbdef branches) + = (fromIntegral (-lo), [ labelFor i | i <- [lo..hi] ]) where - min = fst (M.findMin branches) - max = fst (M.findMax branches) labelFor i = case M.lookup i branches of Just l -> Just l Nothing -> mbdef diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index df913d1..0f2d4b2 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -546,10 +546,10 @@ mk_switch tag_expr branches mb_deflt lo_tag hi_tag via_C arms :: M.Map Integer BlockId arms = M.fromList [ (fromIntegral i, l) | (i,l) <- branches ] - dflags <- getDynFlags + range = (fromIntegral real_lo_tag, fromIntegral real_hi_tag) return $ mkSwitch - (cmmOffset dflags tag_expr (- real_lo_tag)) - (mkSwitchTargets (Just (0, fromIntegral (real_hi_tag-real_lo_tag))) Nothing arms) + tag_expr + (mkSwitchTargets (Just range) Nothing arms) -- if we can knock off a bunch of default cases with one if, then do so | Just deflt <- mb_deflt, (lowest_branch - lo_tag) >= n_branches diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs index 552d9ac..fb42c07 100644 --- a/compiler/nativeGen/PPC/CodeGen.hs +++ b/compiler/nativeGen/PPC/CodeGen.hs @@ -1205,7 +1205,7 @@ genSwitch :: DynFlags -> CmmExpr -> SwitchTargets -> NatM InstrBlock genSwitch dflags expr targets | gopt Opt_PIC dflags = do - (reg,e_code) <- getSomeReg expr + (reg,e_code) <- getSomeReg (cmmOffset dflags expr offset) tmp <- getNewRegNat II32 lbl <- getNewLabelNat dflags <- getDynFlags @@ -1221,7 +1221,7 @@ genSwitch dflags expr targets return code | otherwise = do - (reg,e_code) <- getSomeReg expr + (reg,e_code) <- getSomeReg (cmmOffset dflags expr offset) tmp <- getNewRegNat II32 lbl <- getNewLabelNat let code = e_code `appOL` toOL [ @@ -1232,7 +1232,7 @@ genSwitch dflags expr targets BCTR ids (Just lbl) ] return code - where ids = switchTargetsToTable targets + where (offset, ids) = switchTargetsToTable targets generateJumpTableForInstr :: DynFlags -> Instr -> Maybe (NatCmmDecl CmmStatics Instr) diff --git a/compiler/nativeGen/SPARC/CodeGen.hs b/compiler/nativeGen/SPARC/CodeGen.hs index 8631ab8..3f49afe 100644 --- a/compiler/nativeGen/SPARC/CodeGen.hs +++ b/compiler/nativeGen/SPARC/CodeGen.hs @@ -314,7 +314,7 @@ genSwitch dflags expr targets = error "MachCodeGen: sparc genSwitch PIC not finished\n" | otherwise - = do (e_reg, e_code) <- getSomeReg expr + = do (e_reg, e_code) <- getSomeReg (cmmOffset dflags expr offset) base_reg <- getNewRegNat II32 offset_reg <- getNewRegNat II32 @@ -335,7 +335,7 @@ genSwitch dflags expr targets , LD II32 (AddrRegReg base_reg offset_reg) dst , JMP_TBL (AddrRegImm dst (ImmInt 0)) ids label , NOP ] - where ids = switchTargetsToTable targets + where (offset, ids) = switchTargetsToTable targets generateJumpTableForInstr :: DynFlags -> Instr -> Maybe (NatCmmDecl CmmStatics Instr) diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs index 6e0e8ad..a826531 100644 --- a/compiler/nativeGen/X86/CodeGen.hs +++ b/compiler/nativeGen/X86/CodeGen.hs @@ -2589,7 +2589,7 @@ genSwitch :: DynFlags -> CmmExpr -> SwitchTargets -> NatM InstrBlock genSwitch dflags expr targets | gopt Opt_PIC dflags = do - (reg,e_code) <- getSomeReg expr + (reg,e_code) <- getSomeReg (cmmOffset dflags expr offset) lbl <- getNewLabelNat dflags <- getDynFlags dynRef <- cmmMakeDynamicReference dflags DataReference lbl @@ -2631,14 +2631,14 @@ genSwitch dflags expr targets ] | otherwise = do - (reg,e_code) <- getSomeReg expr + (reg,e_code) <- getSomeReg (cmmOffset dflags expr offset) lbl <- getNewLabelNat let op = OpAddr (AddrBaseIndex EABaseNone (EAIndex reg (wORD_SIZE dflags)) (ImmCLbl lbl)) code = e_code `appOL` toOL [ JMP_TBL op ids ReadOnlyData lbl ] return code - where ids = switchTargetsToTable targets + where (offset, ids) = switchTargetsToTable targets generateJumpTableForInstr :: DynFlags -> Instr -> Maybe (NatCmmDecl (Alignment, CmmStatics) Instr) generateJumpTableForInstr dflags (JMP_TBL _ ids section lbl) From git at git.haskell.org Thu Mar 5 17:40:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Mar 2015 17:40:18 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T10137-travis' created Message-ID: <20150305174018.A2DFA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T10137-travis Referencing: 11a51f50da18956fa61930905c05a43ae95e3031 From git at git.haskell.org Thu Mar 5 17:47:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Mar 2015 17:47:04 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Refactor CmmSwitch: Use a Map (a2a6c70) Message-ID: <20150305174704.C32BA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/a2a6c70126df4d1448f615cec585cdeae4f9bb07/ghc >--------------------------------------------------------------- commit a2a6c70126df4d1448f615cec585cdeae4f9bb07 Author: Joachim Breitner Date: Wed Mar 4 19:54:17 2015 +0100 Refactor CmmSwitch: Use a Map this is in preparation for #10137, where we want to be able to express sparse switch statements in Cmm. >--------------------------------------------------------------- a2a6c70126df4d1448f615cec585cdeae4f9bb07 compiler/cmm/CmmCommonBlockElim.hs | 10 +++-- compiler/cmm/CmmContFlowOpt.hs | 2 +- compiler/cmm/CmmLint.hs | 5 +-- compiler/cmm/CmmNode.hs | 76 ++++++++++++++++++++++++++++----- compiler/cmm/CmmParse.y | 20 +++------ compiler/cmm/CmmProcPoint.hs | 4 +- compiler/cmm/MkGraph.hs | 4 +- compiler/cmm/PprC.hs | 24 ++++------- compiler/cmm/PprCmm.hs | 30 +++++++------ compiler/codeGen/StgCmmUtils.hs | 17 ++++---- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 10 +++-- compiler/nativeGen/PPC/CodeGen.hs | 9 ++-- compiler/nativeGen/SPARC/CodeGen.hs | 9 ++-- compiler/nativeGen/X86/CodeGen.hs | 9 ++-- 14 files changed, 140 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 a2a6c70126df4d1448f615cec585cdeae4f9bb07 From git at git.haskell.org Thu Mar 5 17:47:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Mar 2015 17:47:07 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Make SwitchTargets type abstract (33b1c4a) Message-ID: <20150305174707.B02673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/33b1c4a091497d6f0047fd01e05f14e50c8d55a5/ghc >--------------------------------------------------------------- commit 33b1c4a091497d6f0047fd01e05f14e50c8d55a5 Author: Joachim Breitner Date: Wed Mar 4 21:32:52 2015 +0100 Make SwitchTargets type abstract so that less code has to be touched when it is changed. >--------------------------------------------------------------- 33b1c4a091497d6f0047fd01e05f14e50c8d55a5 compiler/cmm/CmmCommonBlockElim.hs | 9 ++------ compiler/cmm/CmmNode.hs | 37 ++++++++++++++++++++++++++------- compiler/cmm/CmmParse.y | 2 +- compiler/codeGen/StgCmmUtils.hs | 4 +++- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 14 +++++-------- 5 files changed, 40 insertions(+), 26 deletions(-) diff --git a/compiler/cmm/CmmCommonBlockElim.hs b/compiler/cmm/CmmCommonBlockElim.hs index 234b729..6174929 100644 --- a/compiler/cmm/CmmCommonBlockElim.hs +++ b/compiler/cmm/CmmCommonBlockElim.hs @@ -203,15 +203,10 @@ eqLastWith eqBid (CmmCondBranch c1 t1 f1) (CmmCondBranch c2 t2 f2) = c1 == c2 && eqBid t1 t2 && eqBid f1 f2 eqLastWith eqBid (CmmCall t1 c1 g1 a1 r1 u1) (CmmCall t2 c2 g2 a2 r2 u2) = t1 == t2 && eqMaybeWith eqBid c1 c2 && a1 == a2 && r1 == r2 && u1 == u2 && g1 == g2 -eqLastWith eqBid (CmmSwitch e1 (mbdef1, bs1)) (CmmSwitch e2 (mbdef2, bs2)) = - e1 == e2 && eqMaybeWith eqBid mbdef1 mbdef2 && eqMapWith eqBid bs1 bs2 +eqLastWith eqBid (CmmSwitch e1 ids1) (CmmSwitch e2 ids2) = + e1 == e2 && eqSwitchTargetWith eqBid ids1 ids2 eqLastWith _ _ _ = False -eqMapWith :: Eq k => (a -> b -> Bool) -> M.Map k a -> M.Map k b -> Bool -eqMapWith eltEq m1 m2 = - all (\((k1,v1), (k2,v2)) -> k1 == k2 && v1 `eltEq` v2) $ - List.zip (M.toList m1) (M.toList m2) - eqMaybeWith :: (a -> b -> Bool) -> Maybe a -> Maybe b -> Bool eqMaybeWith eltEq (Just e) (Just e') = eltEq e e' eqMaybeWith _ Nothing Nothing = True diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index e6daa18..a3edc3f 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -22,8 +22,9 @@ module CmmNode ( -- * Switch SwitchTargets, + mkSwitchTargets, switchTargetsCases, switchTargetsDefault, mapSwitchTargets, switchTargetsToTable, switchTargetsFallThrough, - switchTargetsToList, + switchTargetsToList, eqSwitchTargetWith, ) where import CodeGen.Platform @@ -696,13 +697,25 @@ combineTickScopes s1 s2 -- See Note [Switch Table] -type SwitchTargets = (Maybe Label, M.Map Integer Label) +data SwitchTargets = + SwitchTargets (Maybe Label) (M.Map Integer Label) + deriving Eq + +mkSwitchTargets :: Maybe Label -> M.Map Integer Label -> SwitchTargets +mkSwitchTargets = SwitchTargets mapSwitchTargets :: (Label -> Label) -> SwitchTargets -> SwitchTargets -mapSwitchTargets f (mbdef, branches) = (fmap f mbdef, fmap f branches) +mapSwitchTargets f (SwitchTargets mbdef branches) + = SwitchTargets (fmap f mbdef) (fmap f branches) + +switchTargetsCases :: SwitchTargets -> [(Integer, Label)] +switchTargetsCases (SwitchTargets _ branches) = M.toList branches + +switchTargetsDefault :: SwitchTargets -> Maybe Label +switchTargetsDefault (SwitchTargets mbdef _) = mbdef switchTargetsToTable :: SwitchTargets -> [Maybe Label] -switchTargetsToTable (mbdef, branches) +switchTargetsToTable (SwitchTargets mbdef branches) | min < 0 = pprPanic "mapSwitchTargets" empty | otherwise = [ labelFor i | i <- [0..max] ] where @@ -712,19 +725,27 @@ switchTargetsToTable (mbdef, branches) Nothing -> mbdef switchTargetsToList :: SwitchTargets -> [Label] -switchTargetsToList (mbdef, branches) = maybeToList mbdef ++ M.elems branches +switchTargetsToList (SwitchTargets mbdef branches) = maybeToList mbdef ++ M.elems branches -- | Groups cases with equal targets, suitable for pretty-printing to a -- c-like switch statement with fall-through semantics. switchTargetsFallThrough :: SwitchTargets -> ([([Integer], Label)], Maybe Label) -switchTargetsFallThrough (mbdef, branches) = (groups, mbdef) +switchTargetsFallThrough (SwitchTargets mbdef branches) = (groups, mbdef) where groups = map (\xs -> (map fst xs, snd (head xs))) $ groupBy ((==) `on` snd) $ M.toList branches - - +eqSwitchTargetWith :: (Label -> Label -> Bool) -> SwitchTargets -> SwitchTargets -> Bool +eqSwitchTargetWith eq (SwitchTargets mbdef1 ids1) (SwitchTargets mbdef2 ids2) = + goMB mbdef1 mbdef2 && goList (M.toList ids1) (M.toList ids2) + where + goMB Nothing Nothing = True + goMB (Just l1) (Just l2) = l1 `eq` l2 + goMB _ _ = False + goList [] [] = True + goList ((i1,l1):ls1) ((i2,l2):ls2) = i1 == i2 && l1 `eq` l2 && goList ls1 ls2 + goList _ _ = False -- Note [SwitchTargets]: -- ~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 84b297a..4f286f5 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -1326,7 +1326,7 @@ doSwitch mb_range scrut arms deflt expr <- scrut -- ToDo: check for out of range and jump to default if necessary - emit $ mkSwitch expr (dflt_entry, table) + emit $ mkSwitch expr (mkSwitchTargets dflt_entry table) where emitArm :: ([Int],Either BlockId (CmmParse ())) -> CmmParse [(Integer,BlockId)] emitArm (ints,Left blockid) = return [ (fromIntegral i,blockid) | i <- ints ] diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index f90bc4b..df62df0 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -550,7 +550,9 @@ mk_switch tag_expr branches mb_deflt lo_tag hi_tag via_C , i <= real_hi_tag ] dflags <- getDynFlags - return (mkSwitch (cmmOffset dflags tag_expr (- real_lo_tag)) (mb_deflt, arms)) + return $ mkSwitch + (cmmOffset dflags tag_expr (- real_lo_tag)) + (mkSwitchTargets mb_deflt arms) -- if we can knock off a bunch of default cases with one if, then do so | Just deflt <- mb_deflt, (lowest_branch - lo_tag) >= n_branches diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 230c64f..9049214 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -32,7 +32,6 @@ import Unique import Data.List ( nub ) import Data.Maybe ( catMaybes ) -import qualified Data.Map as M type Atomic = Bool type LlvmStatements = OrdList LlvmStatement @@ -825,19 +824,16 @@ For a real example of this, see ./rts/StgStdThunks.cmm -- | Switch branch --- --- N.B. We remove Nothing's from the list of branches, as they are 'undefined'. --- However, they may be defined one day, so we better document this behaviour. genSwitch :: CmmExpr -> SwitchTargets -> LlvmM StmtData -genSwitch cond (mbdef, ids) = do +genSwitch cond ids = do (vc, stmts, top) <- exprToVar cond let ty = getVarType vc - let pairs = M.toList ids - let labels = map (\(ix, b) -> (mkIntLit ty ix, blockIdToLlvm b)) pairs + let labels = [ (mkIntLit ty ix, blockIdToLlvm b) + | (ix, b) <- switchTargetsCases ids ] -- out of range is undefined, so let's just branch to first label - let defLbl | Just l <- mbdef = blockIdToLlvm l - | otherwise = snd (head labels) + let defLbl | Just l <- switchTargetsDefault ids = blockIdToLlvm l + | otherwise = snd (head labels) let s1 = Switch vc defLbl labels return $ (stmts `snocOL` s1, top) From git at git.haskell.org Thu Mar 5 17:47:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Mar 2015 17:47:10 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Add an (optional) range field to the SwitchTargets data type (fe3e28d) Message-ID: <20150305174710.7C8E13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/fe3e28dccaeb3b26bebb7ef607cb4c8fb47d1666/ghc >--------------------------------------------------------------- commit fe3e28dccaeb3b26bebb7ef607cb4c8fb47d1666 Author: Joachim Breitner Date: Wed Mar 4 22:16:44 2015 +0100 Add an (optional) range field to the SwitchTargets data type As there is one in the Cmm syntax, and we might be able to exploit that during code generation. >--------------------------------------------------------------- fe3e28dccaeb3b26bebb7ef607cb4c8fb47d1666 compiler/cmm/CmmNode.hs | 36 +++++++++++++++++++++++------------- compiler/cmm/CmmParse.y | 26 ++++++++++++++------------ compiler/codeGen/StgCmmUtils.hs | 9 +++------ 3 files changed, 40 insertions(+), 31 deletions(-) diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index a3edc3f..4b3dfd2 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -698,25 +698,34 @@ combineTickScopes s1 s2 -- See Note [Switch Table] data SwitchTargets = - SwitchTargets (Maybe Label) (M.Map Integer Label) + SwitchTargets (Maybe (Integer, Integer)) (Maybe Label) (M.Map Integer Label) deriving Eq -mkSwitchTargets :: Maybe Label -> M.Map Integer Label -> SwitchTargets -mkSwitchTargets = SwitchTargets +-- mkSwitchTargets normalises the map a bit: +mkSwitchTargets :: Maybe (Integer, Integer) -> Maybe Label -> M.Map Integer Label -> SwitchTargets +mkSwitchTargets mbrange mbdef ids + = SwitchTargets mbrange mbdef $ dropDefault $ restrict ids + where + -- It drops entries outside the range, if there is a range + restrict | Just (lo,hi) <- mbrange = M.filterWithKey (\x _ -> lo <= x && x <= hi) + | otherwise = id + -- It entries that equal the default, if there is a default + dropDefault | Just l <- mbdef = M.filter (/= l) + | otherwise = id mapSwitchTargets :: (Label -> Label) -> SwitchTargets -> SwitchTargets -mapSwitchTargets f (SwitchTargets mbdef branches) - = SwitchTargets (fmap f mbdef) (fmap f branches) +mapSwitchTargets f (SwitchTargets range mbdef branches) + = SwitchTargets range (fmap f mbdef) (fmap f branches) switchTargetsCases :: SwitchTargets -> [(Integer, Label)] -switchTargetsCases (SwitchTargets _ branches) = M.toList branches +switchTargetsCases (SwitchTargets _ _ branches) = M.toList branches switchTargetsDefault :: SwitchTargets -> Maybe Label -switchTargetsDefault (SwitchTargets mbdef _) = mbdef +switchTargetsDefault (SwitchTargets _ mbdef _) = mbdef switchTargetsToTable :: SwitchTargets -> [Maybe Label] -switchTargetsToTable (SwitchTargets mbdef branches) - | min < 0 = pprPanic "mapSwitchTargets" empty +switchTargetsToTable (SwitchTargets _ mbdef branches) + | min < 0 = pprPanic "mapSwitchTargets" empty | otherwise = [ labelFor i | i <- [0..max] ] where min = fst (M.findMin branches) @@ -725,20 +734,21 @@ switchTargetsToTable (SwitchTargets mbdef branches) Nothing -> mbdef switchTargetsToList :: SwitchTargets -> [Label] -switchTargetsToList (SwitchTargets mbdef branches) = maybeToList mbdef ++ M.elems branches +switchTargetsToList (SwitchTargets _ mbdef branches) + = maybeToList mbdef ++ M.elems branches -- | Groups cases with equal targets, suitable for pretty-printing to a -- c-like switch statement with fall-through semantics. switchTargetsFallThrough :: SwitchTargets -> ([([Integer], Label)], Maybe Label) -switchTargetsFallThrough (SwitchTargets mbdef branches) = (groups, mbdef) +switchTargetsFallThrough (SwitchTargets _ mbdef branches) = (groups, mbdef) where groups = map (\xs -> (map fst xs, snd (head xs))) $ groupBy ((==) `on` snd) $ M.toList branches eqSwitchTargetWith :: (Label -> Label -> Bool) -> SwitchTargets -> SwitchTargets -> Bool -eqSwitchTargetWith eq (SwitchTargets mbdef1 ids1) (SwitchTargets mbdef2 ids2) = - goMB mbdef1 mbdef2 && goList (M.toList ids1) (M.toList ids2) +eqSwitchTargetWith eq (SwitchTargets range1 mbdef1 ids1) (SwitchTargets range2 mbdef2 ids2) = + range1 == range2 && goMB mbdef1 mbdef2 && goList (M.toList ids1) (M.toList ids2) where goMB Nothing Nothing = True goMB (Just l1) (Just l2) = l1 `eq` l2 diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 4f286f5..7ec1e4a 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -677,24 +677,24 @@ globals :: { [GlobalReg] } : GLOBALREG { [$1] } | GLOBALREG ',' globals { $1 : $3 } -maybe_range :: { Maybe (Int,Int) } - : '[' INT '..' INT ']' { Just (fromIntegral $2, fromIntegral $4) } +maybe_range :: { Maybe (Integer,Integer) } + : '[' INT '..' INT ']' { Just ($2, $4) } | {- empty -} { Nothing } -arms :: { [CmmParse ([Int],Either BlockId (CmmParse ()))] } +arms :: { [CmmParse ([Integer],Either BlockId (CmmParse ()))] } : {- empty -} { [] } | arm arms { $1 : $2 } -arm :: { CmmParse ([Int],Either BlockId (CmmParse ())) } +arm :: { CmmParse ([Integer],Either BlockId (CmmParse ())) } : 'case' ints ':' arm_body { do b <- $4; return ($2, b) } arm_body :: { CmmParse (Either BlockId (CmmParse ())) } : '{' body '}' { return (Right (withSourceNote $1 $3 $2)) } | 'goto' NAME ';' { do l <- lookupLabel $2; return (Left l) } -ints :: { [Int] } - : INT { [ fromIntegral $1 ] } - | INT ',' ints { fromIntegral $1 : $3 } +ints :: { [Integer] } + : INT { [ $1 ] } + | INT ',' ints { $1 : $3 } default :: { Maybe (CmmParse ()) } : 'default' ':' '{' body '}' { Just (withSourceNote $3 $5 $4) } @@ -1308,7 +1308,9 @@ withSourceNote a b parse = do -- optional range on the switch (eg. switch [0..7] {...}), or by -- the minimum/maximum values from the branches. -doSwitch :: Maybe (Int,Int) -> CmmParse CmmExpr -> [([Int],Either BlockId (CmmParse ()))] +doSwitch :: Maybe (Integer,Integer) + -> CmmParse CmmExpr + -> [([Integer],Either BlockId (CmmParse ()))] -> Maybe (CmmParse ()) -> CmmParse () doSwitch mb_range scrut arms deflt = do @@ -1326,13 +1328,13 @@ doSwitch mb_range scrut arms deflt expr <- scrut -- ToDo: check for out of range and jump to default if necessary - emit $ mkSwitch expr (mkSwitchTargets dflt_entry table) + emit $ mkSwitch expr (mkSwitchTargets mb_range dflt_entry table) where - emitArm :: ([Int],Either BlockId (CmmParse ())) -> CmmParse [(Integer,BlockId)] - emitArm (ints,Left blockid) = return [ (fromIntegral i,blockid) | i <- ints ] + emitArm :: ([Integer],Either BlockId (CmmParse ())) -> CmmParse [(Integer,BlockId)] + emitArm (ints,Left blockid) = return [ (i,blockid) | i <- ints ] emitArm (ints,Right code) = do blockid <- forkLabelledCode code - return [ (fromIntegral i,blockid) | i <- ints ] + return [ (i,blockid) | i <- ints ] forkLabelledCode :: CmmParse () -> CmmParse BlockId forkLabelledCode p = do diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index df62df0..11864d7 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -544,15 +544,12 @@ mk_switch tag_expr branches mb_deflt lo_tag hi_tag via_C -- either end of the range (see below), so the first -- tag of a real branch is real_lo_tag (not lo_tag). arms :: M.Map Integer BlockId - arms = M.fromList [ (fromIntegral (i - real_lo_tag), l) - | (i,l) <- branches - , real_lo_tag <= i - , i <= real_hi_tag - ] + arms = M.fromList [ (fromIntegral i, l) | (i,l) <- branches ] + dflags <- getDynFlags return $ mkSwitch (cmmOffset dflags tag_expr (- real_lo_tag)) - (mkSwitchTargets mb_deflt arms) + (mkSwitchTargets (Just (0, fromIntegral (real_hi_tag-real_lo_tag))) mb_deflt arms) -- if we can knock off a bunch of default cases with one if, then do so | Just deflt <- mb_deflt, (lowest_branch - lo_tag) >= n_branches From git at git.haskell.org Thu Mar 5 17:47:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Mar 2015 17:47:13 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Move table offset to code generation phase (1ec5c8a) Message-ID: <20150305174713.532663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/1ec5c8a1b3db46026d159f54f9dad0d77a6f9b33/ghc >--------------------------------------------------------------- commit 1ec5c8a1b3db46026d159f54f9dad0d77a6f9b33 Author: Joachim Breitner Date: Wed Mar 4 23:13:28 2015 +0100 CmmSwitch: Move table offset to code generation phase Previously, if a switch statement would not start with 0, the Stg ? Cmm phase would offset the scrutinee to make the table zero-based. In order to have CmmSwitch a bit higher level, this step is moved to the Cmm ? Assembly phase. This also means that in the llvm backend, more is more logic left to the LLVM compiler (which hopefully knows best how to compile a switch statement). >--------------------------------------------------------------- 1ec5c8a1b3db46026d159f54f9dad0d77a6f9b33 compiler/cmm/CmmNode.hs | 18 ++++++++++++------ compiler/codeGen/StgCmmUtils.hs | 6 +++--- compiler/nativeGen/PPC/CodeGen.hs | 6 +++--- compiler/nativeGen/SPARC/CodeGen.hs | 4 ++-- compiler/nativeGen/X86/CodeGen.hs | 6 +++--- 5 files changed, 23 insertions(+), 17 deletions(-) diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index 4b3dfd2..90d1b77 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -723,13 +723,19 @@ switchTargetsCases (SwitchTargets _ _ branches) = M.toList branches switchTargetsDefault :: SwitchTargets -> Maybe Label switchTargetsDefault (SwitchTargets _ mbdef _) = mbdef -switchTargetsToTable :: SwitchTargets -> [Maybe Label] -switchTargetsToTable (SwitchTargets _ mbdef branches) - | min < 0 = pprPanic "mapSwitchTargets" empty - | otherwise = [ labelFor i | i <- [0..max] ] +-- switchTargetsToTable creates a dense jump table, usable for code generation. +-- This is not possible if there is no explicit range, so before code generation +-- all switch statements need to be transformed to one with an explicit range. +-- +-- Returns an offset to add to the value; the list is 0-based on the result +-- +-- TODO: Is the conversion from Integral to Int fishy? +switchTargetsToTable :: SwitchTargets -> (Int, [Maybe Label]) +switchTargetsToTable (SwitchTargets Nothing _mbdef _branches) + = pprPanic "switchTargetsToTable" empty +switchTargetsToTable (SwitchTargets (Just (lo,hi)) mbdef branches) + = (fromIntegral (-lo), [ labelFor i | i <- [lo..hi] ]) where - min = fst (M.findMin branches) - max = fst (M.findMax branches) labelFor i = case M.lookup i branches of Just l -> Just l Nothing -> mbdef diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index 11864d7..a4b28fa 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -546,10 +546,10 @@ mk_switch tag_expr branches mb_deflt lo_tag hi_tag via_C arms :: M.Map Integer BlockId arms = M.fromList [ (fromIntegral i, l) | (i,l) <- branches ] - dflags <- getDynFlags + range = (fromIntegral real_lo_tag, fromIntegral real_hi_tag) return $ mkSwitch - (cmmOffset dflags tag_expr (- real_lo_tag)) - (mkSwitchTargets (Just (0, fromIntegral (real_hi_tag-real_lo_tag))) mb_deflt arms) + tag_expr + (mkSwitchTargets (Just range) mb_deflt arms) -- if we can knock off a bunch of default cases with one if, then do so | Just deflt <- mb_deflt, (lowest_branch - lo_tag) >= n_branches diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs index 552d9ac..fb42c07 100644 --- a/compiler/nativeGen/PPC/CodeGen.hs +++ b/compiler/nativeGen/PPC/CodeGen.hs @@ -1205,7 +1205,7 @@ genSwitch :: DynFlags -> CmmExpr -> SwitchTargets -> NatM InstrBlock genSwitch dflags expr targets | gopt Opt_PIC dflags = do - (reg,e_code) <- getSomeReg expr + (reg,e_code) <- getSomeReg (cmmOffset dflags expr offset) tmp <- getNewRegNat II32 lbl <- getNewLabelNat dflags <- getDynFlags @@ -1221,7 +1221,7 @@ genSwitch dflags expr targets return code | otherwise = do - (reg,e_code) <- getSomeReg expr + (reg,e_code) <- getSomeReg (cmmOffset dflags expr offset) tmp <- getNewRegNat II32 lbl <- getNewLabelNat let code = e_code `appOL` toOL [ @@ -1232,7 +1232,7 @@ genSwitch dflags expr targets BCTR ids (Just lbl) ] return code - where ids = switchTargetsToTable targets + where (offset, ids) = switchTargetsToTable targets generateJumpTableForInstr :: DynFlags -> Instr -> Maybe (NatCmmDecl CmmStatics Instr) diff --git a/compiler/nativeGen/SPARC/CodeGen.hs b/compiler/nativeGen/SPARC/CodeGen.hs index 8631ab8..3f49afe 100644 --- a/compiler/nativeGen/SPARC/CodeGen.hs +++ b/compiler/nativeGen/SPARC/CodeGen.hs @@ -314,7 +314,7 @@ genSwitch dflags expr targets = error "MachCodeGen: sparc genSwitch PIC not finished\n" | otherwise - = do (e_reg, e_code) <- getSomeReg expr + = do (e_reg, e_code) <- getSomeReg (cmmOffset dflags expr offset) base_reg <- getNewRegNat II32 offset_reg <- getNewRegNat II32 @@ -335,7 +335,7 @@ genSwitch dflags expr targets , LD II32 (AddrRegReg base_reg offset_reg) dst , JMP_TBL (AddrRegImm dst (ImmInt 0)) ids label , NOP ] - where ids = switchTargetsToTable targets + where (offset, ids) = switchTargetsToTable targets generateJumpTableForInstr :: DynFlags -> Instr -> Maybe (NatCmmDecl CmmStatics Instr) diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs index 6e0e8ad..a826531 100644 --- a/compiler/nativeGen/X86/CodeGen.hs +++ b/compiler/nativeGen/X86/CodeGen.hs @@ -2589,7 +2589,7 @@ genSwitch :: DynFlags -> CmmExpr -> SwitchTargets -> NatM InstrBlock genSwitch dflags expr targets | gopt Opt_PIC dflags = do - (reg,e_code) <- getSomeReg expr + (reg,e_code) <- getSomeReg (cmmOffset dflags expr offset) lbl <- getNewLabelNat dflags <- getDynFlags dynRef <- cmmMakeDynamicReference dflags DataReference lbl @@ -2631,14 +2631,14 @@ genSwitch dflags expr targets ] | otherwise = do - (reg,e_code) <- getSomeReg expr + (reg,e_code) <- getSomeReg (cmmOffset dflags expr offset) lbl <- getNewLabelNat let op = OpAddr (AddrBaseIndex EABaseNone (EAIndex reg (wORD_SIZE dflags)) (ImmCLbl lbl)) code = e_code `appOL` toOL [ JMP_TBL op ids ReadOnlyData lbl ] return code - where ids = switchTargetsToTable targets + where (offset, ids) = switchTargetsToTable targets generateJumpTableForInstr :: DynFlags -> Instr -> Maybe (NatCmmDecl (Alignment, CmmStatics) Instr) generateJumpTableForInstr dflags (JMP_TBL _ ids section lbl) From git at git.haskell.org Thu Mar 5 17:47:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Mar 2015 17:47:24 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T10137-travis' deleted Message-ID: <20150305174724.44CD43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T10137-travis From git at git.haskell.org Thu Mar 5 17:54:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Mar 2015 17:54:12 +0000 (UTC) Subject: [commit: ghc] master: Add public rnf/hash operations to TypeRep/TyCon (56e0ac9) Message-ID: <20150305175412.19C2D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/56e0ac98c3a439b8757a2e886db259270bdc85f0/ghc >--------------------------------------------------------------- commit 56e0ac98c3a439b8757a2e886db259270bdc85f0 Author: Herbert Valerio Riedel Date: Thu Mar 5 11:56:03 2015 -0600 Add public rnf/hash operations to TypeRep/TyCon Summary: `TyCon` and `TypeRep` are supposed to be abstract, by providing these additional few public operations the need to import `Data.Typeable.Internal` is reduced, and future changes to the internal structure of `TypeRep`/`TyCon` shouldn't require changes in packages such as `deepseq` or `hashable` anymore (hopefully). Reviewers: ekmett, simonpj, tibbe, austin Reviewed By: ekmett, simonpj, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D699 >--------------------------------------------------------------- 56e0ac98c3a439b8757a2e886db259270bdc85f0 libraries/base/Data/Typeable.hs | 4 ++++ libraries/base/Data/Typeable/Internal.hs | 29 ++++++++++++++++++++++++++++- libraries/base/changelog.md | 3 +++ 3 files changed, 35 insertions(+), 1 deletion(-) diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs index 168600f..7e501a5 100644 --- a/libraries/base/Data/Typeable.hs +++ b/libraries/base/Data/Typeable.hs @@ -61,13 +61,17 @@ module Data.Typeable -- * Type representations TypeRep, -- abstract, instance of: Eq, Show, Typeable + typeRepHash, + rnfTypeRep, showsTypeRep, TyCon, -- abstract, instance of: Eq, Show, Typeable + tyConHash, tyConString, tyConPackage, tyConModule, tyConName, + rnfTyCon, -- * Construction of type representations -- mkTyCon, -- :: String -> TyCon diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 647697a..8917833 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -42,8 +42,11 @@ module Data.Typeable.Internal ( splitTyConApp, funResultTy, typeRepArgs, + typeRepHash, + rnfTypeRep, showsTypeRep, tyConString, + rnfTyCon, listTc, funTc ) where @@ -93,7 +96,7 @@ instance Ord TypeRep where -- | An abstract representation of a type constructor. 'TyCon' objects can -- be built using 'mkTyCon'. data TyCon = TyCon { - tyConHash :: {-# UNPACK #-} !Fingerprint, + tyConHash :: {-# UNPACK #-} !Fingerprint, -- ^ @since 4.8.0.0 tyConPackage :: String, -- ^ @since 4.5.0.0 tyConModule :: String, -- ^ @since 4.5.0.0 tyConName :: String -- ^ @since 4.5.0.0 @@ -191,6 +194,12 @@ typeRepArgs (TypeRep _ _ args) = args tyConString :: TyCon -> String tyConString = tyConName +-- | Observe the 'Fingerprint' of a type representation +-- +-- @since 4.8.0.0 +typeRepHash :: TypeRep -> Fingerprint +typeRepHash (TypeRep fpr _ _) = fpr + ------------------------------------------------------------- -- -- The Typeable class and friends @@ -301,6 +310,24 @@ isTupleTyCon :: TyCon -> Bool isTupleTyCon (TyCon _ _ _ ('(':',':_)) = True isTupleTyCon _ = False +-- | Helper to fully evaluate 'TypeRep' for use as @NFData(rnf)@ implementation +-- +-- @since 4.8.0.0 +rnfTypeRep :: TypeRep -> () +rnfTypeRep (TypeRep _ tyc tyrs) = rnfTyCon tyc `seq` go tyrs + where + go [] = () + go (x:xs) = rnfTypeRep x `seq` go xs + +-- | Helper to fully evaluate 'TyCon' for use as @NFData(rnf)@ implementation +-- +-- @since 4.8.0.0 +rnfTyCon :: TyCon -> () +rnfTyCon (TyCon _ tcp tcm tcn) = go tcp `seq` go tcm `seq` go tcn + where + go [] = () + go (x:xs) = x `seq` go xs + -- Some (Show.TypeRep) helpers: showArgs :: Show a => ShowS -> [a] -> ShowS diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 89caf01..5635918 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -138,6 +138,9 @@ * Restore invariant in `Data (Ratio a)` instance (#10011) + * Add/expose `rnfTypeRep`, `rnfTyCon`, `TypeRepHash`, and + `TyConHash` helpers to `Data.Typeable`. + ## 4.7.0.2 *Dec 2014* * Bundled with GHC 7.8.4 From git at git.haskell.org Thu Mar 5 18:38:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Mar 2015 18:38:00 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Print range of a switch in PprCmm (de24b27) Message-ID: <20150305183800.788183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/de24b276ffa5b21addcaa1a14d5b4c31e9d5ea2f/ghc >--------------------------------------------------------------- commit de24b276ffa5b21addcaa1a14d5b4c31e9d5ea2f Author: Joachim Breitner Date: Thu Mar 5 19:40:11 2015 +0100 Print range of a switch in PprCmm >--------------------------------------------------------------- de24b276ffa5b21addcaa1a14d5b4c31e9d5ea2f compiler/cmm/CmmNode.hs | 24 ++++++++++++++++++++---- compiler/cmm/PprCmm.hs | 10 ++++++++-- 2 files changed, 28 insertions(+), 6 deletions(-) diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index 90d1b77..42e5fca 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -22,7 +22,8 @@ module CmmNode ( -- * Switch SwitchTargets, - mkSwitchTargets, switchTargetsCases, switchTargetsDefault, + mkSwitchTargets, + switchTargetsCases, switchTargetsDefault, switchTargetsRange, mapSwitchTargets, switchTargetsToTable, switchTargetsFallThrough, switchTargetsToList, eqSwitchTargetWith, ) where @@ -696,23 +697,35 @@ combineTickScopes s1 s2 | otherwise = CombinedScope s1 s2 --- See Note [Switch Table] +-- See Note [SwitchTargets] data SwitchTargets = SwitchTargets (Maybe (Integer, Integer)) (Maybe Label) (M.Map Integer Label) deriving Eq -- mkSwitchTargets normalises the map a bit: +-- * No entries outside the range +-- * No entries equal to the default +-- * No default if there is a range, and all elements have explicit values mkSwitchTargets :: Maybe (Integer, Integer) -> Maybe Label -> M.Map Integer Label -> SwitchTargets mkSwitchTargets mbrange mbdef ids - = SwitchTargets mbrange mbdef $ dropDefault $ restrict ids + = SwitchTargets mbrange mbdef' ids' where + ids' = dropDefault $ restrict ids + mbdef' | defaultNeeded = mbdef + | otherwise = Nothing + -- It drops entries outside the range, if there is a range restrict | Just (lo,hi) <- mbrange = M.filterWithKey (\x _ -> lo <= x && x <= hi) | otherwise = id - -- It entries that equal the default, if there is a default + + -- It drops entries that equal the default, if there is a default dropDefault | Just l <- mbdef = M.filter (/= l) | otherwise = id + defaultNeeded | Just (lo,hi) <- mbrange = fromIntegral (M.size ids') /= hi-lo+1 + | otherwise = True + + mapSwitchTargets :: (Label -> Label) -> SwitchTargets -> SwitchTargets mapSwitchTargets f (SwitchTargets range mbdef branches) = SwitchTargets range (fmap f mbdef) (fmap f branches) @@ -723,6 +736,9 @@ switchTargetsCases (SwitchTargets _ _ branches) = M.toList branches switchTargetsDefault :: SwitchTargets -> Maybe Label switchTargetsDefault (SwitchTargets _ mbdef _) = mbdef +switchTargetsRange :: SwitchTargets -> Maybe (Integer, Integer) +switchTargetsRange (SwitchTargets mbrange _ _) = mbrange + -- switchTargetsToTable creates a dense jump table, usable for code generation. -- This is not possible if there is no explicit range, so before code generation -- all switch statements need to be transformed to one with an explicit range. diff --git a/compiler/cmm/PprCmm.hs b/compiler/cmm/PprCmm.hs index 8948c90..dac6c46 100644 --- a/compiler/cmm/PprCmm.hs +++ b/compiler/cmm/PprCmm.hs @@ -229,11 +229,12 @@ pprNode node = pp_node <+> pp_debug ] CmmSwitch expr ids -> - hang (hcat [ ptext (sLit "switch ") + hang (hsep [ ptext (sLit "switch") + , range , if isTrivialCmmExpr expr then ppr expr else parens (ppr expr) - , ptext (sLit " {") + , ptext (sLit "{") ]) 4 (vcat (map ppCase cases) $$ def) $$ rbrace where @@ -250,6 +251,11 @@ pprNode node = pp_node <+> pp_debug ] | otherwise = empty + range | Just (lo,hi) <- switchTargetsRange ids + = brackets $ hsep [integer lo, ptext (sLit ".."), integer hi] + | otherwise + = empty + CmmCall tgt k regs out res updfr_off -> hcat [ ptext (sLit "call"), space , pprFun tgt, parens (interpp'SP regs), space From git at git.haskell.org Thu Mar 5 19:29:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Mar 2015 19:29:46 +0000 (UTC) Subject: [commit: ghc] master: libraries: update deepseq submodule (44b6bbd) Message-ID: <20150305192946.304033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/44b6bbda7009bd6ea588960c0e77a28e2cec0a85/ghc >--------------------------------------------------------------- commit 44b6bbda7009bd6ea588960c0e77a28e2cec0a85 Author: Austin Seipp Date: Thu Mar 5 13:31:28 2015 -0600 libraries: update deepseq submodule Signed-off-by: Austin Seipp >--------------------------------------------------------------- 44b6bbda7009bd6ea588960c0e77a28e2cec0a85 libraries/deepseq | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/deepseq b/libraries/deepseq index de1bc89..5cbc7d1 160000 --- a/libraries/deepseq +++ b/libraries/deepseq @@ -1 +1 @@ -Subproject commit de1bc894de1ffdd34e6eb8be4fb9e057198060c6 +Subproject commit 5cbc7d1c1d51838b5a147b3fb2d4b6f87b0eda09 From git at git.haskell.org Thu Mar 5 21:02:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Mar 2015 21:02:19 +0000 (UTC) Subject: [commit: packages/hpc] branch 'wip/T9619' created Message-ID: <20150305210219.9FD7B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc New branch : wip/T9619 Referencing: ed803439c303cc27632a0d47f52aab71d15c1121 From git at git.haskell.org Thu Mar 5 21:02:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Mar 2015 21:02:21 +0000 (UTC) Subject: [commit: packages/hpc] wip/T9619: Update maintainer (53afc8c) Message-ID: <20150305210221.A7A073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/T9619 Link : http://git.haskell.org/packages/hpc.git/commitdiff/53afc8c34d78b0d765be4e48d9d08c32cfa4dd77 >--------------------------------------------------------------- commit 53afc8c34d78b0d765be4e48d9d08c32cfa4dd77 Author: Thomas Miedema Date: Mon Sep 29 10:38:48 2014 +0200 Update maintainer >--------------------------------------------------------------- 53afc8c34d78b0d765be4e48d9d08c32cfa4dd77 hpc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hpc.cabal b/hpc.cabal index ccf7738..857faba 100644 --- a/hpc.cabal +++ b/hpc.cabal @@ -4,7 +4,7 @@ version: 0.6.0.2 license: BSD3 license-file: LICENSE author: Andy Gill -maintainer: libraries at haskell.org +maintainer: ghc-devs at haskell.org bug-reports: http://ghc.haskell.org/trac/ghc/newticket?component=Code%20Coverage category: Control synopsis: Code Coverage Library for Haskell From git at git.haskell.org Thu Mar 5 21:02:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Mar 2015 21:02:23 +0000 (UTC) Subject: [commit: packages/hpc] wip/T9619: Use System.FilePath functions instead of (++) (949a781) Message-ID: <20150305210223.AD82C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/T9619 Link : http://git.haskell.org/packages/hpc.git/commitdiff/949a7811795140381e2d52a401bd05dc2280257f >--------------------------------------------------------------- commit 949a7811795140381e2d52a401bd05dc2280257f Author: Thomas Miedema Date: Thu Mar 5 21:36:07 2015 +0100 Use System.FilePath functions instead of (++) >--------------------------------------------------------------- 949a7811795140381e2d52a401bd05dc2280257f Trace/Hpc/Mix.hs | 4 +++- Trace/Hpc/Tix.hs | 13 +++---------- hpc.cabal | 1 + 3 files changed, 7 insertions(+), 11 deletions(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index 28050ad..4a7fc74 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -27,6 +27,8 @@ import Data.Time (UTCTime) import Data.Tree import Data.Char +import System.FilePath + -- a module index records the attributes of each tick-box that has -- been introduced in that module, accessed by tick-number position -- in the list @@ -107,7 +109,7 @@ readMix dirNames mod' = do _ -> error $ "can not find " ++ modName ++ " in " ++ show dirNames mixName :: FilePath -> String -> String -mixName dirName name = dirName ++ "/" ++ name ++ ".mix" +mixName dirName name = dirName name <.> "mix" ------------------------------------------------------------------------------ diff --git a/Trace/Hpc/Tix.hs b/Trace/Hpc/Tix.hs index 2b03e0a..36c3cb8 100644 --- a/Trace/Hpc/Tix.hs +++ b/Trace/Hpc/Tix.hs @@ -12,7 +12,8 @@ module Trace.Hpc.Tix(Tix(..), TixModule(..), tixModuleName, tixModuleHash, tixModuleTixs, readTix, writeTix, getTixFileName) where -import Data.List (isSuffixOf) +import System.FilePath (replaceExtension) + import Trace.Hpc.Util (Hash, catchIO) -- | 'Tix' is the storage format for our dynamic information about @@ -52,15 +53,7 @@ writeTix :: String writeTix name tix = writeFile name (show tix) -{- -tixName :: String -> String -tixName name = name ++ ".tix" --} - -- | 'getTixFullName' takes a binary or @.tix at -file name, -- and normalizes it into a @.tix at -file name. getTixFileName :: String -> String -getTixFileName str | ".tix" `isSuffixOf` str - = str - | otherwise - = str ++ ".tix" +getTixFileName str = replaceExtension str "tix" diff --git a/hpc.cabal b/hpc.cabal index 857faba..33e62cd 100644 --- a/hpc.cabal +++ b/hpc.cabal @@ -38,5 +38,6 @@ Library base >= 4.4.1 && < 4.9, containers >= 0.4.1 && < 0.6, directory >= 1.1 && < 1.3, + filepath >= 1 && < 2, time >= 1.2 && < 1.6 ghc-options: -Wall From git at git.haskell.org Thu Mar 5 21:02:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Mar 2015 21:02:25 +0000 (UTC) Subject: [commit: packages/hpc] wip/T9619: Allow same `Mix` file in different dirs (#9619) (ed80343) Message-ID: <20150305210225.B7E0D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/T9619 Link : http://git.haskell.org/packages/hpc.git/commitdiff/ed803439c303cc27632a0d47f52aab71d15c1121 >--------------------------------------------------------------- commit ed803439c303cc27632a0d47f52aab71d15c1121 Author: Thomas Miedema Date: Thu Mar 5 21:43:36 2015 +0100 Allow same `Mix` file in different dirs (#9619) >--------------------------------------------------------------- ed803439c303cc27632a0d47f52aab71d15c1121 Trace/Hpc/Mix.hs | 10 +++++++--- tests/T9619.hs | 1 + tests/all.T | 16 ++++++++++++++++ 3 files changed, 24 insertions(+), 3 deletions(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index 4a7fc74..340a800 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -22,6 +22,7 @@ module Trace.Hpc.Mix ) where +import Data.List (nub) import Data.Maybe (catMaybes) import Data.Time (UTCTime) import Data.Tree @@ -49,7 +50,7 @@ data Mix = Mix Hash -- hash of mix entry + timestamp Int -- tab stop value. [MixEntry] -- entries - deriving (Show,Read) + deriving (Show,Read,Eq) type MixEntry = (HpcPos, BoxLabel) @@ -103,9 +104,12 @@ readMix dirNames mod' = do _ -> return $ Nothing) `catchIO` (\ _ -> return $ Nothing) | dirName <- dirNames ] - case catMaybes res of + -- `nub` allows identical `Mix` files in different directories (#9619). + case nub (catMaybes res) of [r] -> return r - xs@(_:_) -> error $ "found " ++ show(length xs) ++ " instances of " ++ modName ++ " in " ++ show dirNames + xs@(_:_) -> error $ "found " ++ show(length xs) ++ + " different instances of " ++ modName ++ + " in " ++ show dirNames _ -> error $ "can not find " ++ modName ++ " in " ++ show dirNames mixName :: FilePath -> String -> String diff --git a/tests/T9619.hs b/tests/T9619.hs new file mode 100644 index 0000000..b3549c2 --- /dev/null +++ b/tests/T9619.hs @@ -0,0 +1 @@ +main = return () diff --git a/tests/all.T b/tests/all.T new file mode 100644 index 0000000..da94fbb --- /dev/null +++ b/tests/all.T @@ -0,0 +1,16 @@ +# Do not explicitly specify '-fhpc' in extra_hc_opts, without also setting +# '-hpcdir' to a different value for each test. Only the `hpc` way does this +# automatically. This way the tests in this directory can be run concurrently +# (Main.mix might overlap otherwise). + +setTestOpts([only_compiler_types(['ghc']), + only_ways(['hpc']), + ]) + +def T9619(cmd): + # Having the same mix file in two different hpcdirs should work (exit code 0). + return(cmd + " && cp -R .hpc.T9619 .hpc.T9619b && " + + "{hpc} report T9619.tix --hpcdir=.hpc.T9619 --hpcdir=.hpc.T9619b") +test('T9619', [cmd_wrapper(T9619), ignore_output], + extra_clean(['.hpc.T9619b/Main.mix', '.hpc.T9619b'])], + compile_and_run, ['']) From git at git.haskell.org Thu Mar 5 22:30:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Mar 2015 22:30:51 +0000 (UTC) Subject: [commit: ghc] master: User manual section to document the principles of kind inference (b833bc2) Message-ID: <20150305223051.615EE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b833bc2767d7a8c42093cf2994453f70df206c8d/ghc >--------------------------------------------------------------- commit b833bc2767d7a8c42093cf2994453f70df206c8d Author: Simon Peyton Jones Date: Thu Mar 5 22:32:44 2015 +0000 User manual section to document the principles of kind inference This just documents the conclusions of Trac #10132 >--------------------------------------------------------------- b833bc2767d7a8c42093cf2994453f70df206c8d docs/users_guide/glasgow_exts.xml | 60 +++++++++++++++++++++++++++++++++++++++ 1 file changed, 60 insertions(+) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 8a1c9ec..118b629 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -6692,6 +6692,66 @@ very convenient, and it is not clear what the syntax for explicit quantification + Principles of kind inference + + +Generally speaking, when is on, GHC tries to infer the most +general kind for a declaration. For example: + +data T f a = MkT (f a) -- GHC infers: + -- T :: forall k. (k->*) -> k -> * + +In this case the definition has a right-hand side to inform kind inference. +But that is not always the case. Consider + +type family F a + +Type family declararations have no right-hand side, but GHC must still infer a kind +for F. Since there are no constraints, it could infer +F :: forall k1 k2. k1 -> k2, but that seems too +polymorphic. So GHC defaults those entirely-unconstrained kind variables to * and +we get F :: * -> *. You can still declare F to be +kind-polymorphic using kind signatures: + +type family F1 a -- F1 :: * -> * +type family F2 (a :: k) -- F2 :: forall k. k -> * +type family F3 a :: k -- F3 :: forall k. * -> k +type family F4 (a :: k1) :: k -- F4 :: forall k1 k2. k1 -> k2 + + + +The general principle is this: + + +When there is a right-hand side, GHC +infers the most polymorphic kind consistent with the right-hand side. +Examples: ordinary data type and GADT declarations, class declarations. +In the case of a class declaration the role of "right hand side" is played +by the class moethod signatures. + + +When there is no right hand side, GHC defaults argument and result kinds to *, +except when directed otherwise by a kind signature. +Examples: data and type family declarations. + + +This rule has occasionally-surprising consequences +(see Trac 10132). + +class C a where -- Class declarations are generalised + -- so C :: forall k. k -> Constraint + data D1 a -- No right hand side for these two family + type F1 a -- declarations, but the class forces (a :: k) + -- so D1, F1 :: D1 :: forall k. k -> * + +data D2 a -- No right-hand side so D2 :: * -> * +type F2 a -- No right-hand side so F2 :: * -> * + +The kind-polymorphism from the class declaration makes D1 +kind-polymorphic, but not so D2; and similarly F1, F1. + + + Polymorphic kind recursion and complete kind signatures From git at git.haskell.org Fri Mar 6 01:54:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Mar 2015 01:54:30 +0000 (UTC) Subject: [commit: ghc] master: testsuite: accept updated output (7b486a6) Message-ID: <20150306015430.579613A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7b486a6344e891ec04ffcfbdd0e4347aed02f923/ghc >--------------------------------------------------------------- commit 7b486a6344e891ec04ffcfbdd0e4347aed02f923 Author: Austin Seipp Date: Thu Mar 5 19:56:34 2015 -0600 testsuite: accept updated output Signed-off-by: Austin Seipp >--------------------------------------------------------------- 7b486a6344e891ec04ffcfbdd0e4347aed02f923 testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout | 16 ++++++++-------- testsuite/tests/th/TH_Roles2.stderr | 2 +- 2 files changed, 9 insertions(+), 9 deletions(-) diff --git a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout index 1567b60..16be65e 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout +++ b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout @@ -4,42 +4,42 @@ pdb.safePkg01/local.db: trusted: False M_SafePkg -package dependencies: base-4.8.0.0* ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: base-4.8.0.0* ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 trusted: safe require own pkg trusted: False M_SafePkg2 -package dependencies: base-4.8.0.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: base-4.8.0.0 ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 trusted: trustworthy require own pkg trusted: False M_SafePkg3 -package dependencies: base-4.8.0.0* ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: base-4.8.0.0* ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 trusted: safe require own pkg trusted: True M_SafePkg4 -package dependencies: base-4.8.0.0* ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: base-4.8.0.0* ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 trusted: safe require own pkg trusted: True M_SafePkg5 -package dependencies: base-4.8.0.0* ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: base-4.8.0.0* ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 trusted: safe require own pkg trusted: True M_SafePkg6 -package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.5.0* deepseq-1.4.0.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.6.0* deepseq-1.4.1.0 ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 trusted: trustworthy require own pkg trusted: False M_SafePkg7 -package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.5.0* deepseq-1.4.0.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.6.0* deepseq-1.4.1.0 ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 trusted: safe require own pkg trusted: False M_SafePkg8 -package dependencies: array-0.5.0.1 base-4.8.0.0 bytestring-0.10.5.0* deepseq-1.4.0.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: array-0.5.0.1 base-4.8.0.0 bytestring-0.10.6.0* deepseq-1.4.1.0 ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 trusted: trustworthy require own pkg trusted: False diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index ccfe2f5..83d3ac2 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -4,7 +4,7 @@ TYPE CONSTRUCTORS data T (a :: k) COERCION AXIOMS Dependent modules: [] -Dependent packages: [array-0.5.0.1, base-4.8.0.0, deepseq-1.4.0.0, +Dependent packages: [array-0.5.0.1, base-4.8.0.0, deepseq-1.4.1.0, ghc-prim-0.3.1.0, integer-gmp-1.0.0.0, pretty-1.1.2.0, template-haskell-2.10.0.0] From git at git.haskell.org Fri Mar 6 13:44:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Mar 2015 13:44:44 +0000 (UTC) Subject: [commit: ghc] master: Typos in docs [ci skip] (48f32a8) Message-ID: <20150306134444.3BA4F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/48f32a84f1a8ae08feac80441667a5b38860f0f7/ghc >--------------------------------------------------------------- commit 48f32a84f1a8ae08feac80441667a5b38860f0f7 Author: Gabor Greif Date: Fri Mar 6 14:12:25 2015 +0100 Typos in docs [ci skip] >--------------------------------------------------------------- 48f32a84f1a8ae08feac80441667a5b38860f0f7 docs/users_guide/glasgow_exts.xml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 118b629..d98445e 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -6727,7 +6727,7 @@ The general principle is this: infers the most polymorphic kind consistent with the right-hand side. Examples: ordinary data type and GADT declarations, class declarations. In the case of a class declaration the role of "right hand side" is played -by the class moethod signatures. +by the class method signatures. When there is no right hand side, GHC defaults argument and result kinds to *, @@ -6742,7 +6742,7 @@ class C a where -- Class declarations are generalised -- so C :: forall k. k -> Constraint data D1 a -- No right hand side for these two family type F1 a -- declarations, but the class forces (a :: k) - -- so D1, F1 :: D1 :: forall k. k -> * + -- so D1, F1 :: forall k. k -> * data D2 a -- No right-hand side so D2 :: * -> * type F2 a -- No right-hand side so F2 :: * -> * From git at git.haskell.org Fri Mar 6 16:59:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Mar 2015 16:59:31 +0000 (UTC) Subject: [commit: packages/hpc] wip/T9619: Use System.FilePath functions instead of (++) (23426d6) Message-ID: <20150306165931.236E93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/T9619 Link : http://git.haskell.org/packages/hpc.git/commitdiff/23426d6778a94bd0675830da77532d0f413f9486 >--------------------------------------------------------------- commit 23426d6778a94bd0675830da77532d0f413f9486 Author: Thomas Miedema Date: Thu Mar 5 21:36:07 2015 +0100 Use System.FilePath functions instead of (++) >--------------------------------------------------------------- 23426d6778a94bd0675830da77532d0f413f9486 Trace/Hpc/Mix.hs | 4 +++- Trace/Hpc/Tix.hs | 19 ++++++++----------- hpc.cabal | 1 + 3 files changed, 12 insertions(+), 12 deletions(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index 28050ad..4a7fc74 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -27,6 +27,8 @@ import Data.Time (UTCTime) import Data.Tree import Data.Char +import System.FilePath + -- a module index records the attributes of each tick-box that has -- been introduced in that module, accessed by tick-number position -- in the list @@ -107,7 +109,7 @@ readMix dirNames mod' = do _ -> error $ "can not find " ++ modName ++ " in " ++ show dirNames mixName :: FilePath -> String -> String -mixName dirName name = dirName ++ "/" ++ name ++ ".mix" +mixName dirName name = dirName name <.> "mix" ------------------------------------------------------------------------------ diff --git a/Trace/Hpc/Tix.hs b/Trace/Hpc/Tix.hs index 2b03e0a..fa95dbf 100644 --- a/Trace/Hpc/Tix.hs +++ b/Trace/Hpc/Tix.hs @@ -1,6 +1,10 @@ {-# LANGUAGE CPP #-} -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 704 {-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 702 +-- System.FilePath in filepath version 1.2.0.1 isn't marked or implied Safe, +-- as shipped with GHC 7.2. +{-# LANGUAGE Trustworthy #-} #endif ------------------------------------------------------------ -- Andy Gill and Colin Runciman, June 2006 @@ -12,7 +16,8 @@ module Trace.Hpc.Tix(Tix(..), TixModule(..), tixModuleName, tixModuleHash, tixModuleTixs, readTix, writeTix, getTixFileName) where -import Data.List (isSuffixOf) +import System.FilePath (replaceExtension) + import Trace.Hpc.Util (Hash, catchIO) -- | 'Tix' is the storage format for our dynamic information about @@ -52,15 +57,7 @@ writeTix :: String writeTix name tix = writeFile name (show tix) -{- -tixName :: String -> String -tixName name = name ++ ".tix" --} - -- | 'getTixFullName' takes a binary or @.tix at -file name, -- and normalizes it into a @.tix at -file name. getTixFileName :: String -> String -getTixFileName str | ".tix" `isSuffixOf` str - = str - | otherwise - = str ++ ".tix" +getTixFileName str = replaceExtension str "tix" diff --git a/hpc.cabal b/hpc.cabal index 857faba..32d1d42 100644 --- a/hpc.cabal +++ b/hpc.cabal @@ -38,5 +38,6 @@ Library base >= 4.4.1 && < 4.9, containers >= 0.4.1 && < 0.6, directory >= 1.1 && < 1.3, + filepath >= 1 && < 1.4, time >= 1.2 && < 1.6 ghc-options: -Wall From git at git.haskell.org Fri Mar 6 16:59:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Mar 2015 16:59:33 +0000 (UTC) Subject: [commit: packages/hpc] wip/T9619: Allow same `Mix` file in different dirs (#9619) (6b36dc6) Message-ID: <20150306165933.2C6133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/T9619 Link : http://git.haskell.org/packages/hpc.git/commitdiff/6b36dc61fda02a994f9ea3ae7166dfffbee2c594 >--------------------------------------------------------------- commit 6b36dc61fda02a994f9ea3ae7166dfffbee2c594 Author: Thomas Miedema Date: Thu Mar 5 21:43:36 2015 +0100 Allow same `Mix` file in different dirs (#9619) >--------------------------------------------------------------- 6b36dc61fda02a994f9ea3ae7166dfffbee2c594 Trace/Hpc/Mix.hs | 10 +++++++--- tests/T9619.hs | 1 + tests/all.T | 16 ++++++++++++++++ 3 files changed, 24 insertions(+), 3 deletions(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index 4a7fc74..340a800 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -22,6 +22,7 @@ module Trace.Hpc.Mix ) where +import Data.List (nub) import Data.Maybe (catMaybes) import Data.Time (UTCTime) import Data.Tree @@ -49,7 +50,7 @@ data Mix = Mix Hash -- hash of mix entry + timestamp Int -- tab stop value. [MixEntry] -- entries - deriving (Show,Read) + deriving (Show,Read,Eq) type MixEntry = (HpcPos, BoxLabel) @@ -103,9 +104,12 @@ readMix dirNames mod' = do _ -> return $ Nothing) `catchIO` (\ _ -> return $ Nothing) | dirName <- dirNames ] - case catMaybes res of + -- `nub` allows identical `Mix` files in different directories (#9619). + case nub (catMaybes res) of [r] -> return r - xs@(_:_) -> error $ "found " ++ show(length xs) ++ " instances of " ++ modName ++ " in " ++ show dirNames + xs@(_:_) -> error $ "found " ++ show(length xs) ++ + " different instances of " ++ modName ++ + " in " ++ show dirNames _ -> error $ "can not find " ++ modName ++ " in " ++ show dirNames mixName :: FilePath -> String -> String diff --git a/tests/T9619.hs b/tests/T9619.hs new file mode 100644 index 0000000..b3549c2 --- /dev/null +++ b/tests/T9619.hs @@ -0,0 +1 @@ +main = return () diff --git a/tests/all.T b/tests/all.T new file mode 100644 index 0000000..da94fbb --- /dev/null +++ b/tests/all.T @@ -0,0 +1,16 @@ +# Do not explicitly specify '-fhpc' in extra_hc_opts, without also setting +# '-hpcdir' to a different value for each test. Only the `hpc` way does this +# automatically. This way the tests in this directory can be run concurrently +# (Main.mix might overlap otherwise). + +setTestOpts([only_compiler_types(['ghc']), + only_ways(['hpc']), + ]) + +def T9619(cmd): + # Having the same mix file in two different hpcdirs should work (exit code 0). + return(cmd + " && cp -R .hpc.T9619 .hpc.T9619b && " + + "{hpc} report T9619.tix --hpcdir=.hpc.T9619 --hpcdir=.hpc.T9619b") +test('T9619', [cmd_wrapper(T9619), ignore_output], + extra_clean(['.hpc.T9619b/Main.mix', '.hpc.T9619b'])], + compile_and_run, ['']) From git at git.haskell.org Fri Mar 6 18:06:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Mar 2015 18:06:50 +0000 (UTC) Subject: [commit: packages/hpc] wip/T9619: Allow same `Mix` file in different dirs (#9619) (aec093e) Message-ID: <20150306180650.8152C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/T9619 Link : http://git.haskell.org/packages/hpc.git/commitdiff/aec093ee0fb4530f22abbffd2fbccd059eb9b5e3 >--------------------------------------------------------------- commit aec093ee0fb4530f22abbffd2fbccd059eb9b5e3 Author: Thomas Miedema Date: Thu Mar 5 21:43:36 2015 +0100 Allow same `Mix` file in different dirs (#9619) >--------------------------------------------------------------- aec093ee0fb4530f22abbffd2fbccd059eb9b5e3 Trace/Hpc/Mix.hs | 10 +++++++--- tests/T9619.hs | 1 + tests/all.T | 16 ++++++++++++++++ 3 files changed, 24 insertions(+), 3 deletions(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index 4a7fc74..340a800 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -22,6 +22,7 @@ module Trace.Hpc.Mix ) where +import Data.List (nub) import Data.Maybe (catMaybes) import Data.Time (UTCTime) import Data.Tree @@ -49,7 +50,7 @@ data Mix = Mix Hash -- hash of mix entry + timestamp Int -- tab stop value. [MixEntry] -- entries - deriving (Show,Read) + deriving (Show,Read,Eq) type MixEntry = (HpcPos, BoxLabel) @@ -103,9 +104,12 @@ readMix dirNames mod' = do _ -> return $ Nothing) `catchIO` (\ _ -> return $ Nothing) | dirName <- dirNames ] - case catMaybes res of + -- `nub` allows identical `Mix` files in different directories (#9619). + case nub (catMaybes res) of [r] -> return r - xs@(_:_) -> error $ "found " ++ show(length xs) ++ " instances of " ++ modName ++ " in " ++ show dirNames + xs@(_:_) -> error $ "found " ++ show(length xs) ++ + " different instances of " ++ modName ++ + " in " ++ show dirNames _ -> error $ "can not find " ++ modName ++ " in " ++ show dirNames mixName :: FilePath -> String -> String diff --git a/tests/T9619.hs b/tests/T9619.hs new file mode 100644 index 0000000..b3549c2 --- /dev/null +++ b/tests/T9619.hs @@ -0,0 +1 @@ +main = return () diff --git a/tests/all.T b/tests/all.T new file mode 100644 index 0000000..b0bb743 --- /dev/null +++ b/tests/all.T @@ -0,0 +1,16 @@ +# Do not explicitly specify '-fhpc' in extra_hc_opts, without also setting +# '-hpcdir' to a different value for each test. Only the `hpc` way does this +# automatically. This way the tests in this directory can be run concurrently +# (Main.mix might overlap otherwise). + +setTestOpts([only_compiler_types(['ghc']), + only_ways(['hpc']), + ]) + +def T9619(cmd): + # Having the same mix file in two different hpcdirs should work (exit code 0). + return(cmd + " && cp -R .hpc.T9619 .hpc.T9619b && " + + "{hpc} report T9619.tix --hpcdir=.hpc.T9619 --hpcdir=.hpc.T9619b") +test('T9619', [cmd_wrapper(T9619), ignore_output, + extra_clean(['.hpc.T9619b/Main.mix', '.hpc.T9619b'])], + compile_and_run, ['']) From git at git.haskell.org Fri Mar 6 18:54:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Mar 2015 18:54:12 +0000 (UTC) Subject: [commit: ghc] master: Update shift/reduce commentary in Parser.y (41df51d) Message-ID: <20150306185412.0AA8A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/41df51d5a2b3dca9cc172e0b128a9f576fd4be05/ghc >--------------------------------------------------------------- commit 41df51d5a2b3dca9cc172e0b128a9f576fd4be05 Author: Edward Z. Yang Date: Tue Mar 3 16:05:45 2015 -0800 Update shift/reduce commentary in Parser.y Summary: Signed-off-by: Edward Z. Yang Test Plan: none Reviewers: austin, simonpj, simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D697 >--------------------------------------------------------------- 41df51d5a2b3dca9cc172e0b128a9f576fd4be05 compiler/parser/Parser.y | 383 +++++++++++++++++++++++++++++++++-------------- 1 file changed, 272 insertions(+), 111 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 41df51d5a2b3dca9cc172e0b128a9f576fd4be05 From git at git.haskell.org Fri Mar 6 19:20:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Mar 2015 19:20:26 +0000 (UTC) Subject: [commit: ghc] master: testsuite: format commands using config dict (91c11fe) Message-ID: <20150306192026.D44373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/91c11feacc4c66a7ebcf8a88ab1cb851ce48142a/ghc >--------------------------------------------------------------- commit 91c11feacc4c66a7ebcf8a88ab1cb851ce48142a Author: Thomas Miedema Date: Fri Mar 6 20:17:41 2015 +0100 testsuite: format commands using config dict Summary: Allow `cmd_wrapper` to return a format string that can refer to config values. Very useful! This allows for many tests to be defined in pure Python, instead of in an additional script or Makefile. Example: def Thpc(cmd): return(cmd + ' && {hpc} report Thpc.tix') test('Thpc', [cmd_wrapper(Thpc), only_ways['hpc']), compile_and_run, ['']) The `{hpc}` is replaced by the value of `config.hpc`. The result is that the module `Thpc` first gets compiled, then the binary `Thpc` is run, and then the `hpc report` command is run. The output of all of this is redirected (and later appended) to Thpc.run.stdout/stderr as normally. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D706 >--------------------------------------------------------------- 91c11feacc4c66a7ebcf8a88ab1cb851ce48142a testsuite/driver/testlib.py | 24 +++++++++++++++++------- 1 file changed, 17 insertions(+), 7 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index ac6d97c..a4e7d96 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1314,11 +1314,11 @@ def simple_run( name, way, prog, args ): stdin_comes_from = ' <' + use_stdin if opts.combined_output: - redirection = ' >' + run_stdout \ - + ' 2>&1' + redirection = ' > {} 2>&1'.format(run_stdout) + redirection_append = ' >> {} 2>&1'.format(run_stdout) else: - redirection = ' >' + run_stdout \ - + ' 2>' + run_stderr + redirection = ' > {} 2> {}'.format(run_stdout, run_stderr) + redirection_append = ' >> {} 2>> {}'.format(run_stdout, run_stderr) cmd = prog + ' ' + args + ' ' \ + my_rts_flags + ' ' \ @@ -1326,7 +1326,7 @@ def simple_run( name, way, prog, args ): + redirection if opts.cmd_wrapper != None: - cmd = opts.cmd_wrapper(cmd); + cmd = opts.cmd_wrapper(cmd) + redirection_append cmd = 'cd ' + opts.testdir + ' && ' + cmd @@ -1426,16 +1426,23 @@ def interpreter_run( name, way, extra_hc_opts, compile_only, top_mod ): if getTestOpts().outputdir != None: flags.extend(["-outputdir", getTestOpts().outputdir]) + if getTestOpts().combined_output: + redirection = ' > {} 2>&1'.format(outname) + redirection_append = ' >> {} 2>&1'.format(outname) + else: + redirection = ' > {} 2> {}'.format(outname, errname) + redirection_append = ' >> {} 2>> {}'.format(outname, errname) + cmd = "'" + config.compiler + "' " \ + ' '.join(flags) + ' ' \ + srcname + ' ' \ + ' '.join(config.way_flags(name)[way]) + ' ' \ + extra_hc_opts + ' ' \ + getTestOpts().extra_hc_opts + ' ' \ - + '<' + scriptname + ' 1>' + outname + ' 2>' + errname + + '<' + scriptname + redirection if getTestOpts().cmd_wrapper != None: - cmd = getTestOpts().cmd_wrapper(cmd); + cmd = getTestOpts().cmd_wrapper(cmd) + redirection_append; cmd = 'cd ' + getTestOpts().testdir + " && " + cmd @@ -1830,6 +1837,9 @@ def runCmd( cmd ): return r << 8 def runCmdFor( name, cmd, timeout_multiplier=1.0 ): + # Format cmd using config. Example: cmd='{hpc} report A.tix' + cmd = cmd.format(**config.__dict__) + if_verbose( 3, cmd ) r = 0 if config.os == 'mingw32': From git at git.haskell.org Fri Mar 6 19:33:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Mar 2015 19:33:37 +0000 (UTC) Subject: [commit: ghc] typeable-with-kinds: Always use a fresh wanted variable, as otherwise we could get into loops. (e63a277) Message-ID: <20150306193337.C18693A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/e63a277d2b1bfd01e5a53566f8f72a13ad7c0f86/ghc >--------------------------------------------------------------- commit e63a277d2b1bfd01e5a53566f8f72a13ad7c0f86 Author: Iavor S. Diatchki Date: Fri Mar 6 11:33:31 2015 -0800 Always use a fresh wanted variable, as otherwise we could get into loops. >--------------------------------------------------------------- e63a277d2b1bfd01e5a53566f8f72a13ad7c0f86 compiler/typecheck/TcInteract.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 53ef0e6..11c917d 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1836,7 +1836,7 @@ matchTypeableClass clas k t loc -- Emit a `Typeable` constraint for the given type. subGoal ty = do let goal = mkClassPred clas [ typeKind ty, ty ] - (ev,_) <- newWantedEvVar loc goal + ev <- newWantedEvVarNC loc goal return ev From git at git.haskell.org Fri Mar 6 19:50:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Mar 2015 19:50:46 +0000 (UTC) Subject: [commit: packages/hpc] wip/T9619: Allow same `Mix` file in different dirs (#9619) (361a019) Message-ID: <20150306195046.26F343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/T9619 Link : http://git.haskell.org/packages/hpc.git/commitdiff/361a0196569d5a013ad73fb607ec50ca896af2a2 >--------------------------------------------------------------- commit 361a0196569d5a013ad73fb607ec50ca896af2a2 Author: Thomas Miedema Date: Thu Mar 5 21:43:36 2015 +0100 Allow same `Mix` file in different dirs (#9619) >--------------------------------------------------------------- 361a0196569d5a013ad73fb607ec50ca896af2a2 Trace/Hpc/Mix.hs | 12 ++++++++---- tests/T9619.hs | 1 + tests/all.T | 16 ++++++++++++++++ 3 files changed, 25 insertions(+), 4 deletions(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index 4a7fc74..f4025d9 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -49,7 +49,7 @@ data Mix = Mix Hash -- hash of mix entry + timestamp Int -- tab stop value. [MixEntry] -- entries - deriving (Show,Read) + deriving (Show,Read,Eq) type MixEntry = (HpcPos, BoxLabel) @@ -104,9 +104,13 @@ readMix dirNames mod' = do | dirName <- dirNames ] case catMaybes res of - [r] -> return r - xs@(_:_) -> error $ "found " ++ show(length xs) ++ " instances of " ++ modName ++ " in " ++ show dirNames - _ -> error $ "can not find " ++ modName ++ " in " ++ show dirNames + xs@(x:_:_) | any (/= x) (tail xs) -> + -- Only complain if multiple *different* `Mix` files with the + -- same name are found (#9619). + error $ "found " ++ show(length xs) ++ " different instances of " + ++ modName ++ " in " ++ show dirNames + (x:_) -> return x + _ -> error $ "can not find " ++ modName ++ " in " ++ show dirNames mixName :: FilePath -> String -> String mixName dirName name = dirName name <.> "mix" diff --git a/tests/T9619.hs b/tests/T9619.hs new file mode 100644 index 0000000..b3549c2 --- /dev/null +++ b/tests/T9619.hs @@ -0,0 +1 @@ +main = return () diff --git a/tests/all.T b/tests/all.T new file mode 100644 index 0000000..b0bb743 --- /dev/null +++ b/tests/all.T @@ -0,0 +1,16 @@ +# Do not explicitly specify '-fhpc' in extra_hc_opts, without also setting +# '-hpcdir' to a different value for each test. Only the `hpc` way does this +# automatically. This way the tests in this directory can be run concurrently +# (Main.mix might overlap otherwise). + +setTestOpts([only_compiler_types(['ghc']), + only_ways(['hpc']), + ]) + +def T9619(cmd): + # Having the same mix file in two different hpcdirs should work (exit code 0). + return(cmd + " && cp -R .hpc.T9619 .hpc.T9619b && " + + "{hpc} report T9619.tix --hpcdir=.hpc.T9619 --hpcdir=.hpc.T9619b") +test('T9619', [cmd_wrapper(T9619), ignore_output, + extra_clean(['.hpc.T9619b/Main.mix', '.hpc.T9619b'])], + compile_and_run, ['']) From git at git.haskell.org Sat Mar 7 10:09:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 10:09:22 +0000 (UTC) Subject: [commit: ghc] master: Drop redundant LANGUAGE pragmas (1965202) Message-ID: <20150307100922.6A9633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1965202febe27949a027dea90c0f0040fd9236e7/ghc >--------------------------------------------------------------- commit 1965202febe27949a027dea90c0f0040fd9236e7 Author: Herbert Valerio Riedel Date: Sat Mar 7 11:08:01 2015 +0100 Drop redundant LANGUAGE pragmas Due to refactoring & cleanups those pragmas have become redundant by now >--------------------------------------------------------------- 1965202febe27949a027dea90c0f0040fd9236e7 libraries/base/Prelude.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/Prelude.hs b/libraries/base/Prelude.hs index fd439b5..d1dc1a4 100644 --- a/libraries/base/Prelude.hs +++ b/libraries/base/Prelude.hs @@ -1,5 +1,5 @@ {-# LANGUAGE Trustworthy #-} -{-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns #-} +{-# LANGUAGE NoImplicitPrelude #-} ----------------------------------------------------------------------------- -- | From git at git.haskell.org Sat Mar 7 10:36:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 10:36:03 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Drop redundant LANGUAGE pragmas (e341dcc) Message-ID: <20150307103603.DB4D23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/e341dccf354e03dadbb5bf39814241ea90168c05/ghc >--------------------------------------------------------------- commit e341dccf354e03dadbb5bf39814241ea90168c05 Author: Herbert Valerio Riedel Date: Sat Mar 7 11:08:01 2015 +0100 Drop redundant LANGUAGE pragmas Due to refactoring & cleanups those pragmas have become redundant by now (cherry picked from commit 1965202febe27949a027dea90c0f0040fd9236e7) >--------------------------------------------------------------- e341dccf354e03dadbb5bf39814241ea90168c05 libraries/base/Prelude.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/Prelude.hs b/libraries/base/Prelude.hs index fd439b5..d1dc1a4 100644 --- a/libraries/base/Prelude.hs +++ b/libraries/base/Prelude.hs @@ -1,5 +1,5 @@ {-# LANGUAGE Trustworthy #-} -{-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns #-} +{-# LANGUAGE NoImplicitPrelude #-} ----------------------------------------------------------------------------- -- | From git at git.haskell.org Sat Mar 7 10:36:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 10:36:20 +0000 (UTC) Subject: [commit: ghc] master: Re-export `<$>` from Prelude (#10113) (eb3661f) Message-ID: <20150307103620.A66B33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eb3661f2b9f8472f3714774126ebe1183484dd85/ghc >--------------------------------------------------------------- commit eb3661f2b9f8472f3714774126ebe1183484dd85 Author: Herbert Valerio Riedel Date: Sat Mar 7 11:10:34 2015 +0100 Re-export `<$>` from Prelude (#10113) Whether to re-export the `<$>` non-method operator from `Prelude` wasn't explicitly covered in the original AMP proposal[1], but it turns out that not doing so forces most code that makes use of applicatives to import `Data.Functor` or `Control.Applicative` just to get that operator into scope. To this end, it was proposed to add `<$>` to Prelude as well[2]. The down-side is that this increases the amount of redundant-import warnings triggered, as well as the relatively minor issue of stealing the `<$>` operator from the default namespace for good (although at this point `<$>` is supposed to be ubiquitous anyway due to `Applicative` being implicitly required into the next Haskell Report) [1]: https://wiki.haskell.org/Functor-Applicative-Monad_Proposal [2]: http://thread.gmane.org/gmane.comp.lang.haskell.libraries/24161 Reviewed By: austin, ekmett Differential Revision: https://phabricator.haskell.org/D680 >--------------------------------------------------------------- eb3661f2b9f8472f3714774126ebe1183484dd85 compiler/hsSyn/HsBinds.hs | 2 -- compiler/parser/RdrHsSyn.hs | 2 ++ compiler/typecheck/TcEvidence.hs | 2 +- compiler/typecheck/TcGenDeriv.hs | 2 ++ compiler/types/Coercion.hs | 2 +- compiler/utils/MonadUtils.hs | 1 + compiler/utils/Pair.hs | 2 +- compiler/vectorise/Vectorise/Convert.hs | 2 +- compiler/vectorise/Vectorise/Exp.hs | 2 ++ compiler/vectorise/Vectorise/Type/Type.hs | 2 +- compiler/vectorise/Vectorise/Utils/Hoisting.hs | 2 +- compiler/vectorise/Vectorise/Var.hs | 2 +- libraries/base/Prelude.hs | 3 ++- testsuite/tests/parser/should_compile/T7476/T7476.hs | 2 +- testsuite/tests/parser/should_compile/T7476/T7476.stdout | 2 +- testsuite/tests/rename/should_fail/T2993.hs | 2 +- testsuite/tests/rename/should_fail/T2993.stderr | 2 +- testsuite/tests/th/T10019.stdout | 2 +- 18 files changed, 21 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 eb3661f2b9f8472f3714774126ebe1183484dd85 From git at git.haskell.org Sat Mar 7 10:36:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 10:36:59 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Re-export `<$>` from Prelude (#10113) (dc73705) Message-ID: <20150307103659.EC7753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/dc737056fd66f6033cf6b7089a8508b62ab2eeb1/ghc >--------------------------------------------------------------- commit dc737056fd66f6033cf6b7089a8508b62ab2eeb1 Author: Herbert Valerio Riedel Date: Sat Mar 7 11:10:34 2015 +0100 Re-export `<$>` from Prelude (#10113) Whether to re-export the `<$>` non-method operator from `Prelude` wasn't explicitly covered in the original AMP proposal[1], but it turns out that not doing so forces most code that makes use of applicatives to import `Data.Functor` or `Control.Applicative` just to get that operator into scope. To this end, it was proposed to add `<$>` to Prelude as well[2]. The down-side is that this increases the amount of redundant-import warnings triggered, as well as the relatively minor issue of stealing the `<$>` operator from the default namespace for good (although at this point `<$>` is supposed to be ubiquitous anyway due to `Applicative` being implicitly required into the next Haskell Report) [1]: https://wiki.haskell.org/Functor-Applicative-Monad_Proposal [2]: http://thread.gmane.org/gmane.comp.lang.haskell.libraries/24161 (cherry picked from commit eb3661f2b9f8472f3714774126ebe1183484dd85) >--------------------------------------------------------------- dc737056fd66f6033cf6b7089a8508b62ab2eeb1 compiler/hsSyn/HsBinds.hs | 2 -- compiler/parser/RdrHsSyn.hs | 2 ++ compiler/typecheck/TcEvidence.hs | 2 +- compiler/typecheck/TcGenDeriv.hs | 2 ++ compiler/types/Coercion.hs | 2 +- compiler/utils/MonadUtils.hs | 1 + compiler/utils/Pair.hs | 2 +- compiler/vectorise/Vectorise/Convert.hs | 2 +- compiler/vectorise/Vectorise/Exp.hs | 2 ++ compiler/vectorise/Vectorise/Type/Type.hs | 2 +- compiler/vectorise/Vectorise/Utils/Hoisting.hs | 2 +- compiler/vectorise/Vectorise/Var.hs | 2 +- libraries/base/Prelude.hs | 3 ++- testsuite/tests/parser/should_compile/T7476/T7476.hs | 2 +- testsuite/tests/parser/should_compile/T7476/T7476.stdout | 2 +- testsuite/tests/rename/should_fail/T2993.hs | 2 +- testsuite/tests/rename/should_fail/T2993.stderr | 2 +- testsuite/tests/th/T10019.stdout | 2 +- 18 files changed, 21 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 dc737056fd66f6033cf6b7089a8508b62ab2eeb1 From git at git.haskell.org Sat Mar 7 10:42:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 10:42:22 +0000 (UTC) Subject: [commit: ghc] master: Re-export `<$` from Prelude (#10113) (479523f) Message-ID: <20150307104222.6812D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/479523f3c37894d63352f1718e06696f3ed63143/ghc >--------------------------------------------------------------- commit 479523f3c37894d63352f1718e06696f3ed63143 Author: Herbert Valerio Riedel Date: Sat Mar 7 11:37:52 2015 +0100 Re-export `<$` from Prelude (#10113) This is a follow-up to eb3661f2b9f8472f3714774126ebe1183484dd85 re-exporting `<$` from `Prelude` as well. Reviewed By: austin, ekmett Differential Revision: https://phabricator.haskell.org/D681 >--------------------------------------------------------------- 479523f3c37894d63352f1718e06696f3ed63143 libraries/base/Prelude.hs | 2 +- testsuite/tests/indexed-types/should_compile/Simple15.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/base/Prelude.hs b/libraries/base/Prelude.hs index 8e275aa..fa070f3 100644 --- a/libraries/base/Prelude.hs +++ b/libraries/base/Prelude.hs @@ -70,7 +70,7 @@ module Prelude ( Monoid(mempty, mappend, mconcat), -- ** Monads and functors - Functor(fmap), (<$>), + Functor(fmap, (<$)), (<$>), Applicative(pure, (<*>), (*>), (<*)), Monad((>>=), (>>), return, fail), mapM_, sequence_, (=<<), diff --git a/testsuite/tests/indexed-types/should_compile/Simple15.hs b/testsuite/tests/indexed-types/should_compile/Simple15.hs index 8a28d27..31829d6 100644 --- a/testsuite/tests/indexed-types/should_compile/Simple15.hs +++ b/testsuite/tests/indexed-types/should_compile/Simple15.hs @@ -19,7 +19,7 @@ data FOO = FOO type instance Def FOO = EQU () () foo :: FOO -foo = equ_refl <$ def +foo = equ_refl Simple15.<$ def -- This works: -- foo = def $ equ_refl From git at git.haskell.org Sat Mar 7 10:47:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 10:47:06 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Re-export `<$` from Prelude (#10113) (8601c744) Message-ID: <20150307104706.029B03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/8601c74450a2a079ab1a8b67f18b503fae5b057b/ghc >--------------------------------------------------------------- commit 8601c74450a2a079ab1a8b67f18b503fae5b057b Author: Herbert Valerio Riedel Date: Sat Mar 7 11:37:52 2015 +0100 Re-export `<$` from Prelude (#10113) This is a follow-up to eb3661f2b9f8472f3714774126ebe1183484dd85 re-exporting `<$` from `Prelude` as well. (cherry picked from commit 479523f3c37894d63352f1718e06696f3ed63143) >--------------------------------------------------------------- 8601c74450a2a079ab1a8b67f18b503fae5b057b libraries/base/Prelude.hs | 2 +- testsuite/tests/indexed-types/should_compile/Simple15.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/base/Prelude.hs b/libraries/base/Prelude.hs index 8e275aa..fa070f3 100644 --- a/libraries/base/Prelude.hs +++ b/libraries/base/Prelude.hs @@ -70,7 +70,7 @@ module Prelude ( Monoid(mempty, mappend, mconcat), -- ** Monads and functors - Functor(fmap), (<$>), + Functor(fmap, (<$)), (<$>), Applicative(pure, (<*>), (*>), (<*)), Monad((>>=), (>>), return, fail), mapM_, sequence_, (=<<), diff --git a/testsuite/tests/indexed-types/should_compile/Simple15.hs b/testsuite/tests/indexed-types/should_compile/Simple15.hs index 8a28d27..31829d6 100644 --- a/testsuite/tests/indexed-types/should_compile/Simple15.hs +++ b/testsuite/tests/indexed-types/should_compile/Simple15.hs @@ -19,7 +19,7 @@ data FOO = FOO type instance Def FOO = EQU () () foo :: FOO -foo = equ_refl <$ def +foo = equ_refl Simple15.<$ def -- This works: -- foo = def $ equ_refl From git at git.haskell.org Sat Mar 7 16:08:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:08:54 +0000 (UTC) Subject: [commit: packages/hpc] branch 'wip/cleanup-tests' created Message-ID: <20150307160854.DB6803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc New branch : wip/cleanup-tests Referencing: 08afa91988b68315a035df4702b84b69ba8e125e From git at git.haskell.org Sat Mar 7 16:08:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:08:56 +0000 (UTC) Subject: [commit: packages/hpc] wip/cleanup-tests: Cleanup test.T files using PEP8 style guide (cb27dd9) Message-ID: <20150307160856.E50BC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/cleanup-tests Link : http://git.haskell.org/packages/hpc.git/commitdiff/cb27dd99f5411504887538f21279be89655028c7 >--------------------------------------------------------------- commit cb27dd99f5411504887538f21279be89655028c7 Author: Thomas Miedema Date: Sat Mar 7 12:45:57 2015 +0100 Cleanup test.T files using PEP8 style guide https://www.python.org/dev/peps/pep-0008 * 80 character max Use new config friendly formatting strings. >--------------------------------------------------------------- cb27dd99f5411504887538f21279be89655028c7 tests/fork/test.T | 2 +- tests/function/test.T | 2 +- tests/function2/test.T | 2 +- tests/raytrace/test.T | 2 +- tests/raytrace/tixs/test.T | 30 ++++++----- tests/simple/test.T | 2 +- tests/simple/tixs/test.T | 123 ++++++++++++++++++++++++--------------------- 7 files changed, 84 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 cb27dd99f5411504887538f21279be89655028c7 From git at git.haskell.org Sat Mar 7 16:08:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:08:58 +0000 (UTC) Subject: [commit: packages/hpc] wip/cleanup-tests: Update fulltest output (08afa91) Message-ID: <20150307160858.EBA353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/cleanup-tests Link : http://git.haskell.org/packages/hpc.git/commitdiff/08afa91988b68315a035df4702b84b69ba8e125e >--------------------------------------------------------------- commit 08afa91988b68315a035df4702b84b69ba8e125e Author: Thomas Miedema Date: Sat Mar 7 16:59:53 2015 +0100 Update fulltest output >--------------------------------------------------------------- 08afa91988b68315a035df4702b84b69ba8e125e tests/simple/tixs/hpc_help_draft.stdout | 2 ++ tests/simple/tixs/hpc_help_markup.stdout | 2 ++ tests/simple/tixs/hpc_help_overlay.stdout | 16 +++++++++------- tests/simple/tixs/hpc_help_report.stdout | 2 ++ tests/simple/tixs/hpc_help_show.stdout | 2 ++ tests/simple/tixs/hpc_markup_001.stdout | 5 ----- tests/simple/tixs/hpc_markup_002.stdout | 5 ----- tests/simple/tixs/hpc_markup_error_001.stdout | 2 ++ tests/simple/tixs/hpc_markup_error_002.stdout | 2 ++ tests/simple/tixs/hpc_report_error_001.stdout | 2 ++ tests/simple/tixs/hpc_report_error_002.stdout | 2 ++ tests/simple/tixs/hpc_show_error_001.stdout | 2 ++ tests/simple/tixs/hpc_show_error_002.stdout | 2 ++ 13 files changed, 29 insertions(+), 17 deletions(-) diff --git a/tests/simple/tixs/hpc_help_draft.stdout b/tests/simple/tixs/hpc_help_draft.stdout index d678a0b..fb663ff 100644 --- a/tests/simple/tixs/hpc_help_draft.stdout +++ b/tests/simple/tixs/hpc_help_draft.stdout @@ -13,4 +13,6 @@ Options: --reset-hpcdirs empty the list of hpcdir's [rarely used] --output=FILE output FILE + --verbosity=[0-2] verbosity level, 0-2 + default 1 diff --git a/tests/simple/tixs/hpc_help_markup.stdout b/tests/simple/tixs/hpc_help_markup.stdout index 5d39d50..947d18b 100644 --- a/tests/simple/tixs/hpc_help_markup.stdout +++ b/tests/simple/tixs/hpc_help_markup.stdout @@ -15,4 +15,6 @@ Options: --fun-entry-count show top-level function entry counts --highlight-covered highlight covered code, rather that code gaps --destdir=DIR path to write output to + --verbosity=[0-2] verbosity level, 0-2 + default 1 diff --git a/tests/simple/tixs/hpc_help_overlay.stdout b/tests/simple/tixs/hpc_help_overlay.stdout index facba2b..ea4859c 100644 --- a/tests/simple/tixs/hpc_help_overlay.stdout +++ b/tests/simple/tixs/hpc_help_overlay.stdout @@ -4,11 +4,13 @@ Generate a .tix file from an overlay file Options: - --srcdir=DIR path to source directory of .hs files - multi-use of srcdir possible - --hpcdir=DIR append sub-directory that contains .mix files - default .hpc [rarely used] - --reset-hpcdirs empty the list of hpcdir's - [rarely used] - --output=FILE output FILE + --srcdir=DIR path to source directory of .hs files + multi-use of srcdir possible + --hpcdir=DIR append sub-directory that contains .mix files + default .hpc [rarely used] + --reset-hpcdirs empty the list of hpcdir's + [rarely used] + --output=FILE output FILE + --verbosity=[0-2] verbosity level, 0-2 + default 1 diff --git a/tests/simple/tixs/hpc_help_report.stdout b/tests/simple/tixs/hpc_help_report.stdout index 4526705..5d73a49 100644 --- a/tests/simple/tixs/hpc_help_report.stdout +++ b/tests/simple/tixs/hpc_help_report.stdout @@ -15,4 +15,6 @@ Options: --reset-hpcdirs empty the list of hpcdir's [rarely used] --xml-output show output in XML + --verbosity=[0-2] verbosity level, 0-2 + default 1 diff --git a/tests/simple/tixs/hpc_help_show.stdout b/tests/simple/tixs/hpc_help_show.stdout index 85ec2d3..1302178 100644 --- a/tests/simple/tixs/hpc_help_show.stdout +++ b/tests/simple/tixs/hpc_help_show.stdout @@ -13,4 +13,6 @@ Options: --reset-hpcdirs empty the list of hpcdir's [rarely used] --output=FILE output FILE + --verbosity=[0-2] verbosity level, 0-2 + default 1 diff --git a/tests/simple/tixs/hpc_markup_001.stdout b/tests/simple/tixs/hpc_markup_001.stdout index 42da970..6f80922 100644 --- a/tests/simple/tixs/hpc_markup_001.stdout +++ b/tests/simple/tixs/hpc_markup_001.stdout @@ -1,8 +1,3 @@ -Writing: Main.hs.html -Writing: hpc_index.html -Writing: hpc_index_fun.html -Writing: hpc_index_alt.html -Writing: hpc_index_exp.html diff --git a/tests/simple/tixs/hpc_markup_002.stdout b/tests/simple/tixs/hpc_markup_002.stdout index 1225aea..ad7e017 100644 --- a/tests/simple/tixs/hpc_markup_002.stdout +++ b/tests/simple/tixs/hpc_markup_002.stdout @@ -1,8 +1,3 @@ -Writing: Main.hs.html -Writing: hpc_index.html -Writing: hpc_index_fun.html -Writing: hpc_index_alt.html -Writing: hpc_index_exp.html diff --git a/tests/simple/tixs/hpc_markup_error_001.stdout b/tests/simple/tixs/hpc_markup_error_001.stdout index 6373f65..a68a5dc 100644 --- a/tests/simple/tixs/hpc_markup_error_001.stdout +++ b/tests/simple/tixs/hpc_markup_error_001.stdout @@ -16,4 +16,6 @@ Options: --fun-entry-count show top-level function entry counts --highlight-covered highlight covered code, rather that code gaps --destdir=DIR path to write output to + --verbosity=[0-2] verbosity level, 0-2 + default 1 diff --git a/tests/simple/tixs/hpc_markup_error_002.stdout b/tests/simple/tixs/hpc_markup_error_002.stdout index b867b79..4374860 100644 --- a/tests/simple/tixs/hpc_markup_error_002.stdout +++ b/tests/simple/tixs/hpc_markup_error_002.stdout @@ -16,4 +16,6 @@ Options: --fun-entry-count show top-level function entry counts --highlight-covered highlight covered code, rather that code gaps --destdir=DIR path to write output to + --verbosity=[0-2] verbosity level, 0-2 + default 1 diff --git a/tests/simple/tixs/hpc_report_error_001.stdout b/tests/simple/tixs/hpc_report_error_001.stdout index c365d88..4878dd7 100644 --- a/tests/simple/tixs/hpc_report_error_001.stdout +++ b/tests/simple/tixs/hpc_report_error_001.stdout @@ -16,4 +16,6 @@ Options: --reset-hpcdirs empty the list of hpcdir's [rarely used] --xml-output show output in XML + --verbosity=[0-2] verbosity level, 0-2 + default 1 diff --git a/tests/simple/tixs/hpc_report_error_002.stdout b/tests/simple/tixs/hpc_report_error_002.stdout index 8592a3c..0c95a0a 100644 --- a/tests/simple/tixs/hpc_report_error_002.stdout +++ b/tests/simple/tixs/hpc_report_error_002.stdout @@ -16,4 +16,6 @@ Options: --reset-hpcdirs empty the list of hpcdir's [rarely used] --xml-output show output in XML + --verbosity=[0-2] verbosity level, 0-2 + default 1 diff --git a/tests/simple/tixs/hpc_show_error_001.stdout b/tests/simple/tixs/hpc_show_error_001.stdout index 93c2e4d..184957b 100644 --- a/tests/simple/tixs/hpc_show_error_001.stdout +++ b/tests/simple/tixs/hpc_show_error_001.stdout @@ -14,4 +14,6 @@ Options: --reset-hpcdirs empty the list of hpcdir's [rarely used] --output=FILE output FILE + --verbosity=[0-2] verbosity level, 0-2 + default 1 diff --git a/tests/simple/tixs/hpc_show_error_002.stdout b/tests/simple/tixs/hpc_show_error_002.stdout index 9c0f6c5..50f6a25 100644 --- a/tests/simple/tixs/hpc_show_error_002.stdout +++ b/tests/simple/tixs/hpc_show_error_002.stdout @@ -14,4 +14,6 @@ Options: --reset-hpcdirs empty the list of hpcdir's [rarely used] --output=FILE output FILE + --verbosity=[0-2] verbosity level, 0-2 + default 1 From git at git.haskell.org Sat Mar 7 16:38:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:38:49 +0000 (UTC) Subject: [commit: ghc] master: Custom `Typeable` solver, that keeps track of kinds. (b359c88) Message-ID: <20150307163849.27A143A302@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b359c886cd7578ed083bcedcea05d315ecaeeb54/ghc >--------------------------------------------------------------- commit b359c886cd7578ed083bcedcea05d315ecaeeb54 Author: Iavor S. Diatchki Date: Sat Mar 7 10:37:31 2015 -0600 Custom `Typeable` solver, that keeps track of kinds. Summary: This implements the new `Typeable` solver: when GHC sees `Typeable` constraints it solves them on the spot. The current implementation creates `TyCon` representations on the spot. Pro: No overhead at all in code that does not use `Typeable` Cons: Code that uses `Typeable` may create multipe `TyCon` represntations. We have discussed an implementation where representations of `TyCons` are computed once, in the module, where a datatype is declared. This would lead to more code being generated: for a promotable datatype we need to generate `2 + number_of_data_cons` type-constructro representations, and we have to do that for all programs, even ones that do not intend to use typeable. I added code to emit warning whenevar `deriving Typeable` is encountered--- the idea being that this is not needed anymore, and shold be fixed. Also, we allow `instance Typeable T` in .hs-boot files, but they result in a warning, and are ignored. This last one was to avoid breaking exisitng code, and should become an error, eventually. Test Plan: 1. GHC can compile itself. 2. I compiled a number of large libraries, including `lens`. - I had to make some small changes: `unordered-containers` uses internals of `TypeReps`, so I had to do a 1 line fix - `lens` needed one instance changed, due to a poly-kinded `Typeble` instance 3. I also run some code that uses `syb` to traverse a largish datastrucutre. I didn't notice any signifiant performance difference between the 7.8.3 version, and this implementation. Reviewers: simonpj, simonmar, austin, hvr Reviewed By: austin, hvr Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D652 GHC Trac Issues: #9858 >--------------------------------------------------------------- b359c886cd7578ed083bcedcea05d315ecaeeb54 compiler/basicTypes/MkId.hs | 1 + compiler/deSugar/DsBinds.hs | 128 +++++++++- compiler/main/DynFlags.hs | 2 + compiler/prelude/PrelNames.hs | 44 +++- compiler/typecheck/TcDeriv.hs | 230 +++++++----------- compiler/typecheck/TcEvidence.hs | 35 +++ compiler/typecheck/TcGenDeriv.hs | 52 ----- compiler/typecheck/TcHsSyn.hs | 14 ++ compiler/typecheck/TcInstDcls.hs | 47 ++-- compiler/typecheck/TcInteract.hs | 65 +++++- docs/users_guide/flags.xml | 19 +- docs/users_guide/glasgow_exts.xml | 53 +++-- libraries/base/Data/Data.hs | 2 +- libraries/base/Data/Typeable/Internal.hs | 260 ++++----------------- .../tests/annotations/should_fail/annfail10.stderr | 5 +- testsuite/tests/deriving/should_compile/all.T | 2 +- testsuite/tests/deriving/should_fail/T2604.hs | 9 - testsuite/tests/deriving/should_fail/T2604.stderr | 10 - testsuite/tests/deriving/should_fail/T5863a.hs | 12 - testsuite/tests/deriving/should_fail/T5863a.stderr | 10 - testsuite/tests/deriving/should_fail/T7800.hs | 7 - testsuite/tests/deriving/should_fail/T7800.stderr | 6 - testsuite/tests/deriving/should_fail/T7800a.hs | 4 - testsuite/tests/deriving/should_fail/T9687.stderr | 4 +- testsuite/tests/deriving/should_fail/all.T | 6 +- .../tests/ghci.debugger/scripts/print019.stderr | 12 +- testsuite/tests/polykinds/T8132.stderr | 4 +- testsuite/tests/typecheck/should_compile/T9999.hs | 13 -- testsuite/tests/typecheck/should_compile/all.T | 1 - .../should_fail/TcStaticPointersFail02.stderr | 2 +- testsuite/tests/typecheck/should_fail/all.T | 1 + 31 files changed, 499 insertions(+), 561 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b359c886cd7578ed083bcedcea05d315ecaeeb54 From git at git.haskell.org Sat Mar 7 16:40:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:40:48 +0000 (UTC) Subject: [commit: ghc] master: Add missed test (uuugh) (34ba68c) Message-ID: <20150307164048.561673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/34ba68c2aeb6fb2d1ea25a1a5e45c233ed7efc9c/ghc >--------------------------------------------------------------- commit 34ba68c2aeb6fb2d1ea25a1a5e45c233ed7efc9c Author: Austin Seipp Date: Sat Mar 7 10:40:18 2015 -0600 Add missed test (uuugh) Signed-off-by: Austin Seipp >--------------------------------------------------------------- 34ba68c2aeb6fb2d1ea25a1a5e45c233ed7efc9c testsuite/tests/typecheck/should_fail/T9999.hs | 13 +++++++++++++ testsuite/tests/typecheck/should_fail/T9999.stderr | 11 +++++++++++ 2 files changed, 24 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T9999.hs b/testsuite/tests/typecheck/should_fail/T9999.hs new file mode 100644 index 0000000..656e913 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9999.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE AutoDeriveTypeable, PolyKinds, TypeFamilies, StandaloneDeriving #-} + +module T9999 where + +import Data.Typeable + +data family F a + +class C a where + data F1 a + type F2 a + +main = typeRep (Proxy :: Proxy F) == typeRep (Proxy :: Proxy F1) diff --git a/testsuite/tests/typecheck/should_fail/T9999.stderr b/testsuite/tests/typecheck/should_fail/T9999.stderr new file mode 100644 index 0000000..ae7fa28 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9999.stderr @@ -0,0 +1,11 @@ + +T9999.hs:13:38: + No instance for (Typeable F1) + (maybe you haven't applied a function to enough arguments?) + arising from a use of ?typeRep? + In the second argument of ?(==)?, namely + ?typeRep (Proxy :: Proxy F1)? + In the expression: + typeRep (Proxy :: Proxy F) == typeRep (Proxy :: Proxy F1) + In an equation for ?main?: + main = typeRep (Proxy :: Proxy F) == typeRep (Proxy :: Proxy F1) From git at git.haskell.org Sat Mar 7 16:42:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:42:59 +0000 (UTC) Subject: [commit: ghc] branch 'wip/tc/typeable-with-kinds' created Message-ID: <20150307164259.278703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/tc/typeable-with-kinds Referencing: 2540a1f9d3728e815c4a491a109df7af5544bfc3 From git at git.haskell.org Sat Mar 7 16:43:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:01 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Checkpoint: generate explicit representations for all type constructors. (267d4d6) Message-ID: <20150307164301.D5A2D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/267d4d6e4a89b0e623a53e870260bd9fbbb1e3af/ghc >--------------------------------------------------------------- commit 267d4d6e4a89b0e623a53e870260bd9fbbb1e3af Author: Iavor S. Diatchki Date: Sun Feb 1 20:33:41 2015 -0800 Checkpoint: generate explicit representations for all type constructors. This is probably not quite right yet for the following reasons: - The call to generate tycons is called from withing the code that derives instances. This is incorrect, as nothing is generated when there is nothing to derive. - Currently, the representation of the tycon `Test`, its promoted version (i.e., kind) `Test`, and a promoted *data* constructor, also `Test`, end up having the same representation. Technically, this might not matter as these all have different kinds/sorts, however it is odd, and it seems safer to distinguish them. >--------------------------------------------------------------- 267d4d6e4a89b0e623a53e870260bd9fbbb1e3af compiler/basicTypes/OccName.hs | 6 ++++ compiler/prelude/PrelNames.hs | 3 +- compiler/typecheck/TcDeriv.hs | 74 ++++++++++++++++++++++++++++++++++++++-- compiler/typecheck/TcGenDeriv.hs | 38 +++++++++++++++++++++ 4 files changed, 118 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/OccName.hs b/compiler/basicTypes/OccName.hs index 989f814..320ae62 100644 --- a/compiler/basicTypes/OccName.hs +++ b/compiler/basicTypes/OccName.hs @@ -72,6 +72,8 @@ module OccName ( mkPReprTyConOcc, mkPADFunOcc, + mkTyConRepOcc, + -- ** Deconstruction occNameFS, occNameString, occNameSpace, @@ -607,6 +609,7 @@ mkDataConWrapperOcc, mkWorkerOcc, mkDataTOcc, mkDataCOcc, mkDataConWorkerOcc, mkNewTyCoOcc, mkInstTyCoOcc, mkEqPredCoOcc, mkClassOpAuxOcc, mkCon2TagOcc, mkTag2ConOcc, mkMaxTagOcc + :: OccName -> OccName -- These derived variables have a prefix that no Haskell value could have @@ -658,6 +661,9 @@ mkGenRCo = mk_simple_deriv tcName "CoRep_" mkDataTOcc = mk_simple_deriv varName "$t" mkDataCOcc = mk_simple_deriv varName "$c" +mkTyConRepOcc :: Maybe String -> OccName -> OccName +mkTyConRepOcc = mk_simple_deriv_with varName "$tcr" + -- Vectorisation mkVectOcc, mkVectTyConOcc, mkVectDataConOcc, mkVectIsoOcc, mkPADFunOcc, mkPReprTyConOcc, diff --git a/compiler/prelude/PrelNames.hs b/compiler/prelude/PrelNames.hs index a3d0099..69520eb 100644 --- a/compiler/prelude/PrelNames.hs +++ b/compiler/prelude/PrelNames.hs @@ -677,10 +677,11 @@ showString_RDR = varQual_RDR gHC_SHOW (fsLit "showString") showSpace_RDR = varQual_RDR gHC_SHOW (fsLit "showSpace") showParen_RDR = varQual_RDR gHC_SHOW (fsLit "showParen") -typeRep_RDR, mkTyCon_RDR, mkTyConApp_RDR :: RdrName +typeRep_RDR, mkTyCon_RDR, mkTyConApp_RDR, typeable_TyCon_RDR :: RdrName typeRep_RDR = varQual_RDR tYPEABLE_INTERNAL (fsLit "typeRep#") mkTyCon_RDR = varQual_RDR tYPEABLE_INTERNAL (fsLit "mkTyCon") mkTyConApp_RDR = varQual_RDR tYPEABLE_INTERNAL (fsLit "mkTyConApp") +typeable_TyCon_RDR = tcQual_RDR tYPEABLE_INTERNAL (fsLit "TyCon") undefined_RDR :: RdrName undefined_RDR = varQual_RDR gHC_ERR (fsLit "undefined") diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 04023b5..799ca53 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -382,10 +382,14 @@ tcDeriving tycl_decls inst_decls deriv_decls ; let (binds, newTyCons, famInsts, extraInstances) = genAuxBinds loc (unionManyBags (auxDerivStuff : deriv_stuff)) + ; dflags <- getDynFlags + ; tcRepBinds <- genTypeableTyConReps dflags + tycl_decls inst_decls + ; (inst_info, rn_binds, rn_dus) <- - renameDeriv is_boot (inst_infos ++ (bagToList extraInstances)) binds + renameDeriv is_boot (inst_infos ++ (bagToList extraInstances)) + (unionBags tcRepBinds binds) - ; dflags <- getDynFlags ; unless (isEmptyBag inst_info) $ liftIO (dumpIfSet_dyn dflags Opt_D_dump_deriv "Derived instances" (ddump_deriving inst_info rn_binds newTyCons famInsts)) @@ -414,6 +418,72 @@ tcDeriving tycl_decls inst_decls deriv_decls hangP s x = text "" $$ hang (ptext (sLit s)) 2 x +genTypeableTyConReps :: DynFlags -> + [LTyClDecl Name] -> + [LInstDecl Name] -> + TcM (Bag (LHsBind RdrName, LSig RdrName)) +genTypeableTyConReps dflags decls insts = + do tcs1 <- mapM tyConsFromDecl decls + tcs2 <- mapM tyConsFromInst insts + return $ listToBag [ genTypeableTyConRep dflags loc tc + | (loc,tc) <- concat (tcs1 ++ tcs2) ] + where + + tyConFromDataCon (L l n) = do dc <- tcLookupDataCon n + return (do tc <- promoteDataCon_maybe dc + return (l,tc)) + + -- Promoted data constructors from a data declaration, or + -- a data-family instance. + tyConsFromDataRHS = fmap catMaybes + . mapM tyConFromDataCon + . concatMap (con_names . unLoc) + . dd_cons + + -- Tycons from a data-family declaration; not promotable. + tyConFromDataFamDecl FamilyDecl { fdLName = L loc name } = + do tc <- tcLookupTyCon name + return (loc,tc) + + + -- tycons from a type-level declaration + tyConsFromDecl (L _ d) + + -- data or newtype declaration: promoted tycon, tycon, promoted ctrs. + | isDataDecl d = + do let L loc name = tcdLName d + tc <- tcLookupTyCon name + promotedCtrs <- tyConsFromDataRHS (tcdDataDefn d) + let tyCons = (loc,tc) : promotedCtrs + + return (case promotableTyCon_maybe tc of + Nothing -> tyCons + Just kc -> (loc,kc) : tyCons) + + -- data family: just the type constructor; these are not promotable. + | isDataFamilyDecl d = + do res <- tyConFromDataFamDecl (tcdFam d) + return [res] + + -- class: the type constructors of associated data families + | isClassDecl d = + let isData FamilyDecl { fdInfo = DataFamily } = True + isData _ = False + + in mapM tyConFromDataFamDecl (filter isData (map unLoc (tcdATs d))) + + | otherwise = return [] + + + tyConsFromInst (L _ d) = + case d of + ClsInstD ci -> fmap concat + $ mapM (tyConsFromDataRHS . dfid_defn . unLoc) + $ cid_datafam_insts ci + DataFamInstD dfi -> tyConsFromDataRHS (dfid_defn dfi) + TyFamInstD {} -> return [] + + -- Prints the representable type family instance pprRepTy :: FamInst -> SDoc pprRepTy fi@(FamInst { fi_tys = lhs }) diff --git a/compiler/typecheck/TcGenDeriv.hs b/compiler/typecheck/TcGenDeriv.hs index 57718b0..2db507c 100644 --- a/compiler/typecheck/TcGenDeriv.hs +++ b/compiler/typecheck/TcGenDeriv.hs @@ -20,6 +20,7 @@ module TcGenDeriv ( canDeriveAnyClass, genDerivedBinds, + genTypeableTyConRep, FFoldType(..), functorLikeTraverse, deepSubtypesContaining, foldDataConArgs, mkCoerceClassMethEqn, @@ -1298,6 +1299,43 @@ gen_Typeable_binds dflags loc tycon | wORD_SIZE dflags == 4 = HsWord64Prim "" . fromIntegral | otherwise = HsWordPrim "" . fromIntegral +genTypeableTyConRep :: DynFlags -> SrcSpan -> TyCon -> + (LHsBind RdrName, LSig RdrName) +genTypeableTyConRep dflags loc tycon = + ( mk_easy_FunBind loc rep_name [] tycon_rep + , L loc (TypeSig [L loc rep_name] sig_ty PlaceHolder) + ) + where + rep_name = mk_tc_deriv_name tycon (mkTyConRepOcc suf) + suf = if isPromotedTyCon tycon then Just "k" else + if isPromotedDataCon tycon then Just "c" else Nothing + + sig_ty = nlHsTyVar typeable_TyCon_RDR + + tycon_name = tyConName tycon + modl = nameModule tycon_name + pkg = modulePackageKey modl + + modl_fs = moduleNameFS (moduleName modl) + pkg_fs = packageKeyFS pkg + name_fs = occNameFS (nameOccName tycon_name) + + tycon_rep = nlHsApps mkTyCon_RDR + (map nlHsLit [int64 high, + int64 low, + HsString "" pkg_fs, + HsString "" modl_fs, + HsString "" name_fs]) + + hashThis = unwords $ map unpackFS [pkg_fs, modl_fs, name_fs] + Fingerprint high low = fingerprintString hashThis + + int64 + | wORD_SIZE dflags == 4 = HsWord64Prim "" . fromIntegral + | otherwise = HsWordPrim "" . fromIntegral + + + {- ************************************************************************ * * From git at git.haskell.org Sat Mar 7 16:43:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:04 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Use the kind itself in the evidence for `Typeable` (65dc366) Message-ID: <20150307164304.84EF43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/65dc366b0d0d6c6cf0e03c89aed6682349d0727c/ghc >--------------------------------------------------------------- commit 65dc366b0d0d6c6cf0e03c89aed6682349d0727c Author: Iavor S. Diatchki Date: Tue Feb 10 10:10:59 2015 -0800 Use the kind itself in the evidence for `Typeable` >--------------------------------------------------------------- 65dc366b0d0d6c6cf0e03c89aed6682349d0727c compiler/deSugar/DsBinds.hs | 4 +--- compiler/typecheck/TcEvidence.hs | 15 ++------------- compiler/typecheck/TcInteract.hs | 8 +++++--- 3 files changed, 8 insertions(+), 19 deletions(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index 3c50d1e..3fb42bf 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -889,7 +889,7 @@ dsEvTypeable ev = (rep,ty) <- case ev of EvTypeableTyCon tc ks ts -> - do let ty = mkTyConApp tc (map toKind ks ++ map snd ts) + do let ty = mkTyConApp tc (ks ++ map snd ts) kReps <- mapM kindRep ks tReps <- mapM (getRep tyCl) ts return (tyConRep tc kReps tReps, ty) @@ -928,8 +928,6 @@ dsEvTypeable ev = (getTypeableCo tc ty) where proxyT = mkProxyPrimTy (typeKind ty) ty - toKind (EvTypeableKind kc ks) = mkTyConApp kc (map toKind ks) - kindRep k = undefined tyConRep tc kReps tReps = undefined tyAppRep t1 t2 = undefined diff --git a/compiler/typecheck/TcEvidence.hs b/compiler/typecheck/TcEvidence.hs index fdd90da..3eb5a31 100644 --- a/compiler/typecheck/TcEvidence.hs +++ b/compiler/typecheck/TcEvidence.hs @@ -17,7 +17,7 @@ module TcEvidence ( EvTerm(..), mkEvCast, evVarsOfTerm, EvLit(..), evTermCoercion, EvCallStack(..), - EvTypeable(..), EvTypeableKind(..), + EvTypeable(..), -- TcCoercion TcCoercion(..), LeftOrRight(..), pickLR, @@ -735,7 +735,7 @@ data EvTerm -- | Instructions on how to make a 'Typeable' dictionary. data EvTypeable - = EvTypeableTyCon TyCon [EvTypeableKind] [(EvTerm, Type)] + = EvTypeableTyCon TyCon [Kind] [(EvTerm, Type)] -- ^ Dicitionary for concrete type constructors. | EvTypeableTyApp (EvTerm,Type) (EvTerm,Type) @@ -747,11 +747,6 @@ data EvTypeable deriving ( Data.Data, Data.Typeable ) --- | Instructions on how to make evidence for the typeable representation --- of a kind. -data EvTypeableKind = EvTypeableKind TyCon [EvTypeableKind] - deriving ( Data.Data, Data.Typeable ) - data EvLit = EvNum Integer | EvStr FastString @@ -1112,12 +1107,6 @@ instance Outputable EvTypeable where EvTypeableTyApp t1 t2 -> parens (ppr (fst t1) <+> ppr (fst t2)) EvTypeableTyLit x -> ppr x -instance Outputable EvTypeableKind where - ppr (EvTypeableKind kc ks) = - case ks of - [] -> ppr kc - _ -> parens (ppr kc <+> sep (map ppr ks)) - ---------------------------------------------------------------------- -- Helper functions for dealing with IP newtype-dictionaries diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 7ba92a8..3e6424b 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1876,10 +1876,12 @@ matchTypeableClass clas k t loc mkEv [ct1,ct2] (EvTypeableTyApp (ctEvTerm ct1,f) (ctEvTerm ct2,tk)) - -- Representation for concrete kinds. + -- Representation for concrete kinds. We just use the kind itself, + -- but first check to make sure that it is "simple" (i.e., made entirely + -- out of kind constructors). kindRep ki = do (kc,ks) <- splitTyConApp_maybe ki - kReps <- mapM kindRep ks - return (EvTypeableKind kc kReps) + mapM_ kindRep ks + return ki -- Emit a `Typeable` constraint for the given type. From git at git.haskell.org Sat Mar 7 16:43:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:07 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Put it all together. (d1f89c6) Message-ID: <20150307164307.3C8BA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/d1f89c622766b055871f504d54e8a1eb0e2ac4b3/ghc >--------------------------------------------------------------- commit d1f89c622766b055871f504d54e8a1eb0e2ac4b3 Author: Iavor S. Diatchki Date: Tue Feb 10 11:50:22 2015 -0800 Put it all together. >--------------------------------------------------------------- d1f89c622766b055871f504d54e8a1eb0e2ac4b3 compiler/deSugar/DsBinds.hs | 40 +++++++++++++++++++++++++++++++++++++--- compiler/typecheck/TcInteract.hs | 5 +++++ 2 files changed, 42 insertions(+), 3 deletions(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index 11bd4b8..707a963 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -40,7 +40,8 @@ import Digraph import PrelNames import TysPrim ( mkProxyPrimTy ) -import TyCon ( isTupleTyCon, tyConDataCons_maybe ) +import TyCon ( isTupleTyCon, tyConDataCons_maybe + , tyConName, isPromotedTyCon, isPromotedDataCon ) import TcEvidence import TcType import Type @@ -73,6 +74,7 @@ import Util import Control.Monad( when ) import MonadUtils import Control.Monad(liftM) +import Fingerprint(Fingerprint(..), fingerprintString) {- ************************************************************************ @@ -888,9 +890,12 @@ dsEvTypeable ev = do tyCl <- dsLookupTyCon typeableClassName (ty, rep) <- case ev of + EvTypeableTyCon tc ks ts -> do ctr <- dsLookupGlobalId mkPolyTyConAppName + mkTyCon <- dsLookupGlobalId mkTyConName typeRepTc <- dsLookupTyCon typeRepTyConName + dflags <- getDynFlags let tyRepType = mkTyConApp typeRepTc [] mkRep cRep kReps tReps = mkApps (Var ctr) [ cRep @@ -903,11 +908,11 @@ dsEvTypeable ev = case splitTyConApp_maybe k of Nothing -> panic "dsEvTypeable: not a kind constructor" Just (kc,ks) -> - do kcRep <- undefined kc + do kcRep <- tyConRep dflags mkTyCon kc reps <- mapM kindRep ks return (mkRep kcRep [] reps) - tcRep <- undefined tc + tcRep <- tyConRep dflags mkTyCon tc kReps <- mapM kindRep ks tReps <- mapM (getRep tyCl) ts @@ -957,6 +962,35 @@ dsEvTypeable ev = (getTypeableCo tc ty) where proxyT = mkProxyPrimTy (typeKind ty) ty + -- This part could be cached + tyConRep dflags mkTyCon tc = + do pkgStr <- mkStringExprFS pkg_fs + modStr <- mkStringExprFS modl_fs + nameStr <- mkStringExprFS name_fs + return (mkApps (Var mkTyCon) [ int64 high, int64 low + , pkgStr, modStr, nameStr + ]) + where + tycon_name = tyConName tc + modl = nameModule tycon_name + pkg = modulePackageKey modl + + modl_fs = moduleNameFS (moduleName modl) + pkg_fs = packageKeyFS pkg + name_fs = occNameFS (nameOccName tycon_name) + hash_name_fs + | isPromotedTyCon tc = appendFS (mkFastString "$k") name_fs + | isPromotedDataCon tc = appendFS (mkFastString "$c") name_fs + | otherwise = name_fs + + hashThis = unwords $ map unpackFS [pkg_fs, modl_fs, hash_name_fs] + Fingerprint high low = fingerprintString hashThis + + int64 + | wORD_SIZE dflags == 4 = mkWord64LitWord64 + | otherwise = mkWordLit dflags . fromIntegral + + diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 3e6424b..5191277 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1692,6 +1692,11 @@ matchClassInst _ clas [ ty ] _ = panicTcS (text "Unexpected evidence for" <+> ppr (className clas) $$ vcat (map (ppr . idType) (classMethods clas))) + + +matchClassInst inerts clas [k,t] loc + | className clas == typeableClassName = matchTypeableClass clas k t loc + matchClassInst inerts clas tys loc = do { dflags <- getDynFlags ; tclvl <- getTcLevel From git at git.haskell.org Sat Mar 7 16:43:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:09 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Bug-fix: the coercion was the wrong way around. (c95620a) Message-ID: <20150307164309.EA3233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/c95620a82cc98788d49a23a65c897cc0070426db/ghc >--------------------------------------------------------------- commit c95620a82cc98788d49a23a65c897cc0070426db Author: Iavor S. Diatchki Date: Tue Feb 10 14:37:47 2015 -0800 Bug-fix: the coercion was the wrong way around. >--------------------------------------------------------------- c95620a82cc98788d49a23a65c897cc0070426db compiler/deSugar/DsBinds.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index 6db3cae..eebf298 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -945,7 +945,7 @@ dsEvTypeable ev = $ mkLams [mkWildValBinder proxyT] (Var repName) -- package up the method as `Typeable` dictionary - return (mkCast method (getTypeableCo tyCl ty)) + return $ mkCast method $ mkSymCo $ getTypeableCo tyCl ty where -- co: method -> Typeable k t @@ -958,7 +958,7 @@ dsEvTypeable ev = getRep tc (ev,t) = do typeableExpr <- dsEvTerm ev let co = getTypeableCo tc t - method = mkCast typeableExpr (mkSymCo co) + method = mkCast typeableExpr co proxy = mkTyApps (Var proxyHashId) [t] return (mkApps method [proxy]) From git at git.haskell.org Sat Mar 7 16:43:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:12 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Add wire-in names for the `Typeable` dictionary constructors. (6cb9e85) Message-ID: <20150307164312.929BB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/6cb9e85e202ccf2ff1515512728c5506ae2d338d/ghc >--------------------------------------------------------------- commit 6cb9e85e202ccf2ff1515512728c5506ae2d338d Author: Iavor S. Diatchki Date: Tue Feb 10 10:37:23 2015 -0800 Add wire-in names for the `Typeable` dictionary constructors. >--------------------------------------------------------------- 6cb9e85e202ccf2ff1515512728c5506ae2d338d compiler/prelude/PrelNames.hs | 37 +++++++++++++++++++++++++++++++++---- 1 file changed, 33 insertions(+), 4 deletions(-) diff --git a/compiler/prelude/PrelNames.hs b/compiler/prelude/PrelNames.hs index 69520eb..f23d77e 100644 --- a/compiler/prelude/PrelNames.hs +++ b/compiler/prelude/PrelNames.hs @@ -213,7 +213,14 @@ basicKnownKeyNames alternativeClassName, foldableClassName, traversableClassName, - typeableClassName, -- derivable + + -- Typeable + typeableClassName, + mkTyConName, + mkPolyTyConAppName, + mkAppTyName, + typeLitTypeRepName, + -- Numeric stuff negateName, minusName, geName, eqName, @@ -1033,9 +1040,19 @@ rationalToDoubleName = varQual gHC_FLOAT (fsLit "rationalToDouble") rationalToDo ixClassName :: Name ixClassName = clsQual gHC_ARR (fsLit "Ix") ixClassKey --- Class Typeable -typeableClassName :: Name -typeableClassName = clsQual tYPEABLE_INTERNAL (fsLit "Typeable") typeableClassKey +-- Class Typeable, and functions for constructing `Typeable` dictionaries +typeableClassName + , mkTyConName + , mkPolyTyConAppName + , mkAppTyName + , typeLitTypeRepName + :: Name +typeableClassName = clsQual tYPEABLE_INTERNAL (fsLit "Typeable") typeableClassKey +mkTyConName = varQual tYPEABLE_INTERNAL (fsLit "mkTyCon") mkTyConKey +mkPolyTyConAppName = varQual tYPEABLE_INTERNAL (fsLit "mkPolyTyConApp") mkPolyTyConAppKey +mkAppTyName = varQual tYPEABLE_INTERNAL (fsLit "mkAppTy") mkAppTyKey +typeLitTypeRepName = varQual tYPEABLE_INTERNAL (fsLit "typeLitTypeRep") typeLitTypeRepKey + -- Class Data @@ -1873,6 +1890,18 @@ proxyHashKey = mkPreludeMiscIdUnique 502 -- USES IdUniques 200-499 ----------------------------------------------------- +-- Used to make `Typeable` dictionaries +mkTyConKey + , mkPolyTyConAppKey + , mkAppTyKey + , typeLitTypeRepKey + :: Unique +mkTyConKey = mkPreludeMiscIdUnique 503 +mkPolyTyConAppKey = mkPreludeMiscIdUnique 504 +mkAppTyKey = mkPreludeMiscIdUnique 505 +typeLitTypeRepKey = mkPreludeMiscIdUnique 506 + + {- ************************************************************************ * * From git at git.haskell.org Sat Mar 7 16:43:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:15 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: All reps, except the ones for type/kind constructors. (4a97d56) Message-ID: <20150307164315.3AA5F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/4a97d56c28a02d94929ee164cdf239bd473e6e6e/ghc >--------------------------------------------------------------- commit 4a97d56c28a02d94929ee164cdf239bd473e6e6e Author: Iavor S. Diatchki Date: Tue Feb 10 11:13:47 2015 -0800 All reps, except the ones for type/kind constructors. >--------------------------------------------------------------- 4a97d56c28a02d94929ee164cdf239bd473e6e6e compiler/deSugar/DsBinds.hs | 43 +++++++++++++++++++++++++++++-------------- 1 file changed, 29 insertions(+), 14 deletions(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index 92d2e7f..11bd4b8 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -889,25 +889,41 @@ dsEvTypeable ev = (ty, rep) <- case ev of EvTypeableTyCon tc ks ts -> - do let ty = mkTyConApp tc (ks ++ map snd ts) - tcRep <- undefined - kReps <- mapM kindRep ks - tReps <- mapM (getRep tyCl) ts - ctr <- dsLookupGlobalId mkPolyTyConAppName + do ctr <- dsLookupGlobalId mkPolyTyConAppName typeRepTc <- dsLookupTyCon typeRepTyConName let tyRepType = mkTyConApp typeRepTc [] - return (ty, mkApps (Var ctr) - [ tcRep - , mkListExpr tyRepType kReps - , mkListExpr tyRepType tReps - ]) + mkRep cRep kReps tReps = mkApps (Var ctr) + [ cRep + , mkListExpr tyRepType kReps + , mkListExpr tyRepType tReps + ] + + + let kindRep k = + case splitTyConApp_maybe k of + Nothing -> panic "dsEvTypeable: not a kind constructor" + Just (kc,ks) -> + do kcRep <- undefined kc + reps <- mapM kindRep ks + return (mkRep kcRep [] reps) + + tcRep <- undefined tc + + kReps <- mapM kindRep ks + tReps <- mapM (getRep tyCl) ts + + return ( mkTyConApp tc (ks ++ map snd ts) + , mkRep tcRep kReps tReps + ) EvTypeableTyApp t1 t2 -> - do let ty = mkAppTy (snd t1) (snd t2) - e1 <- getRep tyCl t1 + do e1 <- getRep tyCl t1 e2 <- getRep tyCl t2 ctr <- dsLookupGlobalId mkAppTyName - return (ty, mkApps (Var ctr) [ e1, e2 ]) + + return ( mkAppTy (snd t1) (snd t2) + , mkApps (Var ctr) [ e1, e2 ] + ) EvTypeableTyLit ty -> do str <- case (isNumLitTy ty, isStrLitTy ty) of @@ -941,7 +957,6 @@ dsEvTypeable ev = (getTypeableCo tc ty) where proxyT = mkProxyPrimTy (typeKind ty) ty - kindRep k = undefined From git at git.haskell.org Sat Mar 7 16:43:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:18 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Most of the custom solver for typeable. What's missing: (b050a98) Message-ID: <20150307164318.0B5693A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/b050a98cbabfb256c693d8b83e6cfdaa74183e70/ghc >--------------------------------------------------------------- commit b050a98cbabfb256c693d8b83e6cfdaa74183e70 Author: Iavor S. Diatchki Date: Mon Feb 9 17:09:39 2015 -0800 Most of the custom solver for typeable. What's missing: * All the scaffolding is there, but solver is not connected in TcInteract * The final step of the dsugaring---where we actually make the expressions for the TypeReps---is not written yet. This changes the deepseq submodule because the representation of TypeReps now has an extra field. >--------------------------------------------------------------- b050a98cbabfb256c693d8b83e6cfdaa74183e70 compiler/basicTypes/MkId.hs | 1 + compiler/deSugar/DsBinds.hs | 58 +++++++++++++++++++++++++ compiler/typecheck/TcDeriv.hs | 5 ++- compiler/typecheck/TcEvidence.hs | 46 ++++++++++++++++++++ compiler/typecheck/TcHsSyn.hs | 14 ++++++ compiler/typecheck/TcInteract.hs | 60 +++++++++++++++++++++++++- libraries/base/Data/Typeable/Internal.hs | 74 ++++++++++++++++++++++++-------- 7 files changed, 236 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 b050a98cbabfb256c693d8b83e6cfdaa74183e70 From git at git.haskell.org Sat Mar 7 16:43:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:20 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Construct basic dictionary shapes. (908b9f0) Message-ID: <20150307164320.CE4B43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/908b9f08099195cabc681377df76ff1f4b29b27c/ghc >--------------------------------------------------------------- commit 908b9f08099195cabc681377df76ff1f4b29b27c Author: Iavor S. Diatchki Date: Tue Feb 10 11:05:25 2015 -0800 Construct basic dictionary shapes. >--------------------------------------------------------------- 908b9f08099195cabc681377df76ff1f4b29b27c compiler/deSugar/DsBinds.hs | 40 +++++++++++++++++++++++++--------------- compiler/prelude/PrelNames.hs | 7 +++++++ 2 files changed, 32 insertions(+), 15 deletions(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index 3fb42bf..92d2e7f 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -885,26 +885,39 @@ dsEvTerm (EvTypeable ev) = dsEvTypeable ev dsEvTypeable :: EvTypeable -> DsM CoreExpr dsEvTypeable ev = - do tyCl <- dsLookupTyCon typeableClassName - (rep,ty) <- + do tyCl <- dsLookupTyCon typeableClassName + (ty, rep) <- case ev of EvTypeableTyCon tc ks ts -> do let ty = mkTyConApp tc (ks ++ map snd ts) - kReps <- mapM kindRep ks - tReps <- mapM (getRep tyCl) ts - return (tyConRep tc kReps tReps, ty) + tcRep <- undefined + kReps <- mapM kindRep ks + tReps <- mapM (getRep tyCl) ts + ctr <- dsLookupGlobalId mkPolyTyConAppName + typeRepTc <- dsLookupTyCon typeRepTyConName + let tyRepType = mkTyConApp typeRepTc [] + return (ty, mkApps (Var ctr) + [ tcRep + , mkListExpr tyRepType kReps + , mkListExpr tyRepType tReps + ]) EvTypeableTyApp t1 t2 -> do let ty = mkAppTy (snd t1) (snd t2) - e1 <- getRep tyCl t1 - e2 <- getRep tyCl t2 - return (tyAppRep e1 e2, ty) + e1 <- getRep tyCl t1 + e2 <- getRep tyCl t2 + ctr <- dsLookupGlobalId mkAppTyName + return (ty, mkApps (Var ctr) [ e1, e2 ]) EvTypeableTyLit ty -> - case (isNumLitTy ty, isStrLitTy ty) of - (Just n, _) -> return (litRep (show n), ty) - (_, Just n) -> return (litRep (show n), ty) - _ -> panic "dsEvTypeable: malformed TyLit evidence" + do str <- case (isNumLitTy ty, isStrLitTy ty) of + (Just n, _) -> return (show n) + (_, Just n) -> return (show n) + _ -> panic "dsEvTypeable: malformed TyLit evidence" + ctr <- dsLookupGlobalId typeLitTypeRepName + tag <- mkStringExpr str + return (ty, mkApps (Var ctr) [ tag ]) + return (mkDict tyCl ty rep) @@ -929,9 +942,6 @@ dsEvTypeable ev = where proxyT = mkProxyPrimTy (typeKind ty) ty kindRep k = undefined - tyConRep tc kReps tReps = undefined - tyAppRep t1 t2 = undefined - litRep str = undefined diff --git a/compiler/prelude/PrelNames.hs b/compiler/prelude/PrelNames.hs index f23d77e..cac4ec7 100644 --- a/compiler/prelude/PrelNames.hs +++ b/compiler/prelude/PrelNames.hs @@ -216,6 +216,7 @@ basicKnownKeyNames -- Typeable typeableClassName, + typeRepTyConName, mkTyConName, mkPolyTyConAppName, mkAppTyName, @@ -1042,12 +1043,14 @@ ixClassName = clsQual gHC_ARR (fsLit "Ix") ixClassKey -- Class Typeable, and functions for constructing `Typeable` dictionaries typeableClassName + , typeRepTyConName , mkTyConName , mkPolyTyConAppName , mkAppTyName , typeLitTypeRepName :: Name typeableClassName = clsQual tYPEABLE_INTERNAL (fsLit "Typeable") typeableClassKey +typeRepTyConName = tcQual tYPEABLE_INTERNAL (fsLit "TypeRep") typeRepTyConKey mkTyConName = varQual tYPEABLE_INTERNAL (fsLit "mkTyCon") mkTyConKey mkPolyTyConAppName = varQual tYPEABLE_INTERNAL (fsLit "mkPolyTyConApp") mkPolyTyConAppKey mkAppTyName = varQual tYPEABLE_INTERNAL (fsLit "mkAppTy") mkAppTyKey @@ -1559,6 +1562,10 @@ staticPtrInfoTyConKey = mkPreludeTyConUnique 181 callStackTyConKey :: Unique callStackTyConKey = mkPreludeTyConUnique 182 +-- Typeables +typeRepTyConKey :: Unique +typeRepTyConKey = mkPreludeTyConUnique 183 + ---------------- Template Haskell ------------------- -- USES TyConUniques 200-299 ----------------------------------------------------- From git at git.haskell.org Sat Mar 7 16:43:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:23 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Cache representation outside lambda, the way it was in manual instances. (f8ff9f4) Message-ID: <20150307164323.8AD683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/f8ff9f4bd877138fffce1e87527837b4e6016078/ghc >--------------------------------------------------------------- commit f8ff9f4bd877138fffce1e87527837b4e6016078 Author: Iavor S. Diatchki Date: Tue Feb 10 14:28:19 2015 -0800 Cache representation outside lambda, the way it was in manual instances. >--------------------------------------------------------------- f8ff9f4bd877138fffce1e87527837b4e6016078 compiler/deSugar/DsBinds.hs | 39 +++++++++++++++++++++++++-------------- 1 file changed, 25 insertions(+), 14 deletions(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index 707a963..6db3cae 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -888,21 +888,19 @@ dsEvTerm (EvTypeable ev) = dsEvTypeable ev dsEvTypeable :: EvTypeable -> DsM CoreExpr dsEvTypeable ev = do tyCl <- dsLookupTyCon typeableClassName + typeRepTc <- dsLookupTyCon typeRepTyConName + let tyRepType = mkTyConApp typeRepTc [] + (ty, rep) <- case ev of EvTypeableTyCon tc ks ts -> do ctr <- dsLookupGlobalId mkPolyTyConAppName mkTyCon <- dsLookupGlobalId mkTyConName - typeRepTc <- dsLookupTyCon typeRepTyConName dflags <- getDynFlags - let tyRepType = mkTyConApp typeRepTc [] - mkRep cRep kReps tReps = mkApps (Var ctr) - [ cRep - , mkListExpr tyRepType kReps - , mkListExpr tyRepType tReps - ] - + let mkRep cRep kReps tReps = + mkApps (Var ctr) [ cRep, mkListExpr tyRepType kReps + , mkListExpr tyRepType tReps ] let kindRep k = case splitTyConApp_maybe k of @@ -939,8 +937,15 @@ dsEvTypeable ev = tag <- mkStringExpr str return (ty, mkApps (Var ctr) [ tag ]) + -- TyRep -> Typeable t + -- see also: Note [Memoising typeOf] + repName <- newSysLocalDs tyRepType + let proxyT = mkProxyPrimTy (typeKind ty) ty + method = bindNonRec repName rep + $ mkLams [mkWildValBinder proxyT] (Var repName) - return (mkDict tyCl ty rep) + -- package up the method as `Typeable` dictionary + return (mkCast method (getTypeableCo tyCl ty)) where -- co: method -> Typeable k t @@ -957,11 +962,6 @@ dsEvTypeable ev = proxy = mkTyApps (Var proxyHashId) [t] return (mkApps method [proxy]) - -- TyRep -> Typeable t - mkDict tc ty rep = mkCast (mkLams [mkWildValBinder proxyT] rep) - (getTypeableCo tc ty) - where proxyT = mkProxyPrimTy (typeKind ty) ty - -- This part could be cached tyConRep dflags mkTyCon tc = do pkgStr <- mkStringExprFS pkg_fs @@ -992,6 +992,17 @@ dsEvTypeable ev = +{- Note [Memoising typeOf] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +See #3245, #9203 + +IMPORTANT: we don't want to recalculate the TypeRep once per call with +the proxy argument. This is what went wrong in #3245 and #9203. So we +help GHC by manually keeping the 'rep' *outside* the lambda. +-} + + + dsEvCallStack :: EvCallStack -> DsM CoreExpr From git at git.haskell.org Sat Mar 7 16:43:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:26 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Custom treatment of `Typeable` in super-classes. (379d627) Message-ID: <20150307164326.440D83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/379d6273717157c3ec1ce3daea621d8243103438/ghc >--------------------------------------------------------------- commit 379d6273717157c3ec1ce3daea621d8243103438 Author: Iavor S. Diatchki Date: Tue Feb 10 17:35:01 2015 -0800 Custom treatment of `Typeable` in super-classes. It would appear that GHC "short-cuts" the solver when it encounters super-class constraints that look like classes. This means that the custom solvers in TcInteract do not work! This does not seem quite right, but until we fix it, we have an explicit check to pass on `Typeable` to the constraint solver. >--------------------------------------------------------------- 379d6273717157c3ec1ce3daea621d8243103438 compiler/typecheck/TcInstDcls.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 5ee6479..fb3b466 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -1068,6 +1068,7 @@ tcSuperClasses dfun_id cls tyvars dfun_evs inst_tys dfun_ev_binds fam_envs sc_th | (sc_co, norm_sc_pred) <- normaliseType fam_envs Nominal sc_pred -- sc_co :: sc_pred ~ norm_sc_pred , ClassPred cls tys <- classifyPredType norm_sc_pred + , className cls /= typeableClassName = do { sc_ev_tm <- emit_sc_cls_pred norm_sc_pred cls tys ; sc_ev_id <- newEvVar sc_pred ; let tc_co = TcCoercion (mkSubCo (mkSymCo sc_co)) From git at git.haskell.org Sat Mar 7 16:43:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:28 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: We still need `DataTypeable` when deriving `Data` (was removed accidentally) (7518644) Message-ID: <20150307164328.E11D13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/7518644147b2fa23668bb8433b78475113990a15/ghc >--------------------------------------------------------------- commit 7518644147b2fa23668bb8433b78475113990a15 Author: Iavor S. Diatchki Date: Wed Feb 11 13:58:16 2015 -0800 We still need `DataTypeable` when deriving `Data` (was removed accidentally) >--------------------------------------------------------------- 7518644147b2fa23668bb8433b78475113990a15 compiler/typecheck/TcDeriv.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 72e3b89..c237269 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -1191,7 +1191,8 @@ sideConditions mtheta cls | cls_key == enumClassKey = Just (cond_std `andCond` cond_isEnumeration) | cls_key == ixClassKey = Just (cond_std `andCond` cond_enumOrProduct cls) | cls_key == boundedClassKey = Just (cond_std `andCond` cond_enumOrProduct cls) - | cls_key == dataClassKey = Just (cond_std `andCond` + | cls_key == dataClassKey = Just (checkFlag Opt_DeriveDataTypeable `andCond` + cond_std `andCond` cond_args cls) | cls_key == functorClassKey = Just (checkFlag Opt_DeriveFunctor `andCond` cond_vanilla `andCond` From git at git.haskell.org Sat Mar 7 16:43:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:31 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Allow `Typeable` instances in interfaces, but warn, and ignore them. (350bda4) Message-ID: <20150307164331.90E373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/350bda4cb23b99c75977fd960e6b1bc6b67f5f24/ghc >--------------------------------------------------------------- commit 350bda4cb23b99c75977fd960e6b1bc6b67f5f24 Author: Iavor S. Diatchki Date: Wed Feb 11 10:21:42 2015 -0800 Allow `Typeable` instances in interfaces, but warn, and ignore them. >--------------------------------------------------------------- 350bda4cb23b99c75977fd960e6b1bc6b67f5f24 compiler/typecheck/TcInstDcls.hs | 19 +++++++++++++++---- 1 file changed, 15 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 5eb8e5c..b7f2623 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -49,6 +49,7 @@ import BasicTypes import DynFlags import ErrUtils import FastString +import HscTypes ( isHsBootOrSig ) import Id import MkId import Name @@ -424,6 +425,7 @@ tcInstDecls1 tycl_decls inst_decls deriv_decls bad_typeable_instance i = typeableClassName == is_cls_nm (iSpec i) + overlapCheck ty = case overlapMode (is_flag $ iSpec ty) of NoOverlap _ -> False _ -> True @@ -433,10 +435,19 @@ tcInstDecls1 tycl_decls inst_decls deriv_decls ptext (sLit "Replace the following instance:")) 2 (pprInstanceHdr (iSpec i)) - typeable_err i - = setSrcSpan (getSrcSpan (iSpec i)) $ - addErrTc $ ptext - (sLit "Class `Typeable` does not support user-specified instances.") + -- Report an error or a warning for a `Typeable` instances. + -- If we are workikng on an .hs-boot file, we just report a warning, + -- and ignore the instance. We do this, to give users a chance to fix + -- their code. + typeable_err i = + setSrcSpan (getSrcSpan (iSpec i)) $ + do env <- getGblEnv + if isHsBootOrSig (tcg_src env) + then addWarnTc $ vcat + [ ptext (sLit "`Typeable` instances in .hs-boot files are ignored.") + , ptext (sLit "This warning will become an error in future versions of the compiler.") + ] + else addErrTc $ ptext (sLit "Class `Typeable` does not support user-specified instances.") addClsInsts :: [InstInfo Name] -> TcM a -> TcM a addClsInsts infos thing_inside From git at git.haskell.org Sat Mar 7 16:43:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:34 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Remove warnings (e0e0303) Message-ID: <20150307164334.476A43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/e0e03036017d4db7c20ef3d6ea0fab207e391cd7/ghc >--------------------------------------------------------------- commit e0e03036017d4db7c20ef3d6ea0fab207e391cd7 Author: Iavor S. Diatchki Date: Tue Feb 10 17:33:06 2015 -0800 Remove warnings >--------------------------------------------------------------- e0e03036017d4db7c20ef3d6ea0fab207e391cd7 compiler/typecheck/TcInteract.hs | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 5191277..716a8c1 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1692,9 +1692,7 @@ matchClassInst _ clas [ ty ] _ = panicTcS (text "Unexpected evidence for" <+> ppr (className clas) $$ vcat (map (ppr . idType) (classMethods clas))) - - -matchClassInst inerts clas [k,t] loc +matchClassInst _ clas [k,t] loc | className clas == typeableClassName = matchTypeableClass clas k t loc matchClassInst inerts clas tys loc @@ -1849,8 +1847,8 @@ matchTypeableClass clas k t loc | isForAllTy k = return NoInstance | Just (tc, ks_tys) <- splitTyConApp_maybe t = doTyConApp tc ks_tys | Just (f,kt) <- splitAppTy_maybe t = doTyApp f kt - | Just n <- isNumLitTy t = mkEv [] (EvTypeableTyLit t) - | Just s <- isStrLitTy t = mkEv [] (EvTypeableTyLit t) + | Just _ <- isNumLitTy t = mkEv [] (EvTypeableTyLit t) + | Just _ <- isStrLitTy t = mkEv [] (EvTypeableTyLit t) | otherwise = return NoInstance where @@ -1884,7 +1882,7 @@ matchTypeableClass clas k t loc -- Representation for concrete kinds. We just use the kind itself, -- but first check to make sure that it is "simple" (i.e., made entirely -- out of kind constructors). - kindRep ki = do (kc,ks) <- splitTyConApp_maybe ki + kindRep ki = do (_,ks) <- splitTyConApp_maybe ki mapM_ kindRep ks return ki From git at git.haskell.org Sat Mar 7 16:43:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:36 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Delete commented out code. (af2b2d6) Message-ID: <20150307164336.EA6CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/af2b2d6f31b1fa724bec73041abd38cd9df5ff1e/ghc >--------------------------------------------------------------- commit af2b2d6f31b1fa724bec73041abd38cd9df5ff1e Author: Iavor S. Diatchki Date: Wed Feb 11 14:54:39 2015 -0800 Delete commented out code. >--------------------------------------------------------------- af2b2d6f31b1fa724bec73041abd38cd9df5ff1e compiler/typecheck/TcGenDeriv.hs | 38 -------------------------------------- 1 file changed, 38 deletions(-) diff --git a/compiler/typecheck/TcGenDeriv.hs b/compiler/typecheck/TcGenDeriv.hs index c6296d6..7802a22 100644 --- a/compiler/typecheck/TcGenDeriv.hs +++ b/compiler/typecheck/TcGenDeriv.hs @@ -1246,44 +1246,6 @@ getPrecedence get_fixity nm -- into account for either Read or Show; hence we -- ignore associativity here -{- XXX -genTypeableTyConRep :: DynFlags -> SrcSpan -> TyCon -> - (LHsBind RdrName, LSig RdrName) -genTypeableTyConRep dflags loc tycon = - ( mk_easy_FunBind loc rep_name [] tycon_rep - , L loc (TypeSig [L loc rep_name] sig_ty PlaceHolder) - ) - where - rep_name = mk_tc_deriv_name tycon (mkTyConRepOcc suf) - suf = if isPromotedTyCon tycon then Just "k" else - if isPromotedDataCon tycon then Just "c" else Nothing - - sig_ty = nlHsTyVar typeable_TyCon_RDR - - tycon_name = tyConName tycon - modl = nameModule tycon_name - pkg = modulePackageKey modl - - modl_fs = moduleNameFS (moduleName modl) - pkg_fs = packageKeyFS pkg - name_fs = occNameFS (nameOccName tycon_name) - - tycon_rep = nlHsApps mkTyCon_RDR - (map nlHsLit [int64 high, - int64 low, - HsString "" pkg_fs, - HsString "" modl_fs, - HsString "" name_fs]) - - hashThis = unwords $ map unpackFS [pkg_fs, modl_fs, name_fs] - Fingerprint high low = fingerprintString hashThis - - int64 - | wORD_SIZE dflags == 4 = HsWord64Prim "" . fromIntegral - | otherwise = HsWordPrim "" . fromIntegral --} - - {- ************************************************************************ * * From git at git.haskell.org Sat Mar 7 16:43:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:39 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Mostly disable the old-style Deriving. (c042f3b) Message-ID: <20150307164339.AB3103A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/c042f3b9d3b932a1c47e30246c633b7e05eb094d/ghc >--------------------------------------------------------------- commit c042f3b9d3b932a1c47e30246c633b7e05eb094d Author: Iavor S. Diatchki Date: Tue Feb 10 18:16:10 2015 -0800 Mostly disable the old-style Deriving. For some reason, "deriving" declarations are being processed twice?? >--------------------------------------------------------------- c042f3b9d3b932a1c47e30246c633b7e05eb094d compiler/typecheck/TcDeriv.hs | 161 +++----------------------- compiler/typecheck/TcGenDeriv.hs | 7 +- libraries/base/Data/Typeable/Internal.hs | 188 ------------------------------- 3 files changed, 19 insertions(+), 337 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c042f3b9d3b932a1c47e30246c633b7e05eb094d From git at git.haskell.org Sat Mar 7 16:43:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:42 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Remove more unused code. (684bfc3) Message-ID: <20150307164342.61E553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/684bfc35054952791c568f303a08b0810dc703b8/ghc >--------------------------------------------------------------- commit 684bfc35054952791c568f303a08b0810dc703b8 Author: Iavor S. Diatchki Date: Wed Feb 11 15:47:07 2015 -0800 Remove more unused code. >--------------------------------------------------------------- 684bfc35054952791c568f303a08b0810dc703b8 compiler/basicTypes/OccName.hs | 6 ------ compiler/prelude/PrelNames.hs | 3 +-- 2 files changed, 1 insertion(+), 8 deletions(-) diff --git a/compiler/basicTypes/OccName.hs b/compiler/basicTypes/OccName.hs index 320ae62..989f814 100644 --- a/compiler/basicTypes/OccName.hs +++ b/compiler/basicTypes/OccName.hs @@ -72,8 +72,6 @@ module OccName ( mkPReprTyConOcc, mkPADFunOcc, - mkTyConRepOcc, - -- ** Deconstruction occNameFS, occNameString, occNameSpace, @@ -609,7 +607,6 @@ mkDataConWrapperOcc, mkWorkerOcc, mkDataTOcc, mkDataCOcc, mkDataConWorkerOcc, mkNewTyCoOcc, mkInstTyCoOcc, mkEqPredCoOcc, mkClassOpAuxOcc, mkCon2TagOcc, mkTag2ConOcc, mkMaxTagOcc - :: OccName -> OccName -- These derived variables have a prefix that no Haskell value could have @@ -661,9 +658,6 @@ mkGenRCo = mk_simple_deriv tcName "CoRep_" mkDataTOcc = mk_simple_deriv varName "$t" mkDataCOcc = mk_simple_deriv varName "$c" -mkTyConRepOcc :: Maybe String -> OccName -> OccName -mkTyConRepOcc = mk_simple_deriv_with varName "$tcr" - -- Vectorisation mkVectOcc, mkVectTyConOcc, mkVectDataConOcc, mkVectIsoOcc, mkPADFunOcc, mkPReprTyConOcc, diff --git a/compiler/prelude/PrelNames.hs b/compiler/prelude/PrelNames.hs index cac4ec7..5e13227 100644 --- a/compiler/prelude/PrelNames.hs +++ b/compiler/prelude/PrelNames.hs @@ -685,11 +685,10 @@ showString_RDR = varQual_RDR gHC_SHOW (fsLit "showString") showSpace_RDR = varQual_RDR gHC_SHOW (fsLit "showSpace") showParen_RDR = varQual_RDR gHC_SHOW (fsLit "showParen") -typeRep_RDR, mkTyCon_RDR, mkTyConApp_RDR, typeable_TyCon_RDR :: RdrName +typeRep_RDR, mkTyCon_RDR, mkTyConApp_RDR :: RdrName typeRep_RDR = varQual_RDR tYPEABLE_INTERNAL (fsLit "typeRep#") mkTyCon_RDR = varQual_RDR tYPEABLE_INTERNAL (fsLit "mkTyCon") mkTyConApp_RDR = varQual_RDR tYPEABLE_INTERNAL (fsLit "mkTyConApp") -typeable_TyCon_RDR = tcQual_RDR tYPEABLE_INTERNAL (fsLit "TyCon") undefined_RDR :: RdrName undefined_RDR = varQual_RDR gHC_ERR (fsLit "undefined") From git at git.haskell.org Sat Mar 7 16:43:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:45 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Remove some more code for deriving `Typeable` (1f99e8b) Message-ID: <20150307164345.1CA043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/1f99e8b7513fdb5e4fb197f8f3c7dc5ca3aa049e/ghc >--------------------------------------------------------------- commit 1f99e8b7513fdb5e4fb197f8f3c7dc5ca3aa049e Author: Iavor S. Diatchki Date: Wed Feb 11 09:53:11 2015 -0800 Remove some more code for deriving `Typeable` >--------------------------------------------------------------- 1f99e8b7513fdb5e4fb197f8f3c7dc5ca3aa049e compiler/typecheck/TcDeriv.hs | 4 +-- compiler/typecheck/TcGenDeriv.hs | 57 +--------------------------------------- compiler/typecheck/TcInstDcls.hs | 33 +++++++---------------- 3 files changed, 12 insertions(+), 82 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1f99e8b7513fdb5e4fb197f8f3c7dc5ca3aa049e From git at git.haskell.org Sat Mar 7 16:43:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:47 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Disable `Ignoring derive Typeable` warnings. (4350fba) Message-ID: <20150307164347.CD8703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/4350fbaacf929900f9ecfdb0aabda904ea3e912b/ghc >--------------------------------------------------------------- commit 4350fbaacf929900f9ecfdb0aabda904ea3e912b Author: Iavor S. Diatchki Date: Wed Feb 11 17:13:17 2015 -0800 Disable `Ignoring derive Typeable` warnings. Very many things in base derive Typeable, so we'll need a huge commit to remove these warning. For the time being, I am jsut commenting out the warning. Perhaps, it'd be better to control the behavior with a flag. >--------------------------------------------------------------- 4350fbaacf929900f9ecfdb0aabda904ea3e912b compiler/typecheck/TcDeriv.hs | 4 ++-- compiler/typecheck/TcInstDcls.hs | 6 ++++-- 2 files changed, 6 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index c237269..2cc8902 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -685,7 +685,7 @@ deriveStandalone (L loc (DerivDecl deriv_ty overlap_mode)) ; case tcSplitTyConApp_maybe inst_ty of Just (tc, tc_args) | className cls == typeableClassName - -> do addWarnTc (text "Standalone deriving `Typeable` has no effect.") + -> do -- addWarnTc (text "Standalone deriving `Typeable` has no effect.") return [] | isAlgTyCon tc -- All other classes @@ -720,7 +720,7 @@ deriveTyData tvs tc tc_args (L loc deriv_pred) -- so the argument kind 'k' is not decomposable by splitKindFunTys -- as is the case for all other derivable type classes ; if className cls == typeableClassName - then do addWarnTc (text "Deriving `Typeable` has no effect.") + then do -- addWarnTc (text "Deriving `Typeable` has no effect.") return [] else diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index b7f2623..f2bb494 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -443,10 +443,12 @@ tcInstDecls1 tycl_decls inst_decls deriv_decls setSrcSpan (getSrcSpan (iSpec i)) $ do env <- getGblEnv if isHsBootOrSig (tcg_src env) - then addWarnTc $ vcat + then return () + {- + addWarnTc $ vcat [ ptext (sLit "`Typeable` instances in .hs-boot files are ignored.") , ptext (sLit "This warning will become an error in future versions of the compiler.") - ] + ] -} else addErrTc $ ptext (sLit "Class `Typeable` does not support user-specified instances.") addClsInsts :: [InstInfo Name] -> TcM a -> TcM a From git at git.haskell.org Sat Mar 7 16:43:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:50 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Fix fallout from TypeRep changes (6b0508c) Message-ID: <20150307164350.857A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/6b0508cd6afc675db8c9f83c0e68e695d6a26725/ghc >--------------------------------------------------------------- commit 6b0508cd6afc675db8c9f83c0e68e695d6a26725 Author: Austin Seipp Date: Thu Mar 5 20:30:47 2015 -0600 Fix fallout from TypeRep changes Signed-off-by: Austin Seipp >--------------------------------------------------------------- 6b0508cd6afc675db8c9f83c0e68e695d6a26725 libraries/base/Data/Typeable/Internal.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 9341ca9..4cdc57d 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -198,7 +198,7 @@ tyConString = tyConName -- -- @since 4.8.0.0 typeRepHash :: TypeRep -> Fingerprint -typeRepHash (TypeRep fpr _ _) = fpr +typeRepHash (TypeRep fpr _ _ _) = fpr ------------------------------------------------------------- -- @@ -298,7 +298,7 @@ isTupleTyCon _ = False -- -- @since 4.8.0.0 rnfTypeRep :: TypeRep -> () -rnfTypeRep (TypeRep _ tyc tyrs) = rnfTyCon tyc `seq` go tyrs +rnfTypeRep (TypeRep _ tyc krs tyrs) = rnfTyCon tyc `seq` go krs `seq` go tyrs where go [] = () go (x:xs) = rnfTypeRep x `seq` go xs From git at git.haskell.org Sat Mar 7 16:43:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:53 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: testsuite: fix/update fallout from Typeable changes (bcb49ae) Message-ID: <20150307164353.428A73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/bcb49ae326d626e884f83ac4d65b2004a215cca8/ghc >--------------------------------------------------------------- commit bcb49ae326d626e884f83ac4d65b2004a215cca8 Author: Austin Seipp Date: Thu Mar 5 20:01:36 2015 -0600 testsuite: fix/update fallout from Typeable changes Signed-off-by: Austin Seipp >--------------------------------------------------------------- bcb49ae326d626e884f83ac4d65b2004a215cca8 testsuite/tests/deriving/should_compile/all.T | 2 +- testsuite/tests/deriving/should_fail/T2604.hs | 9 --------- testsuite/tests/deriving/should_fail/T2604.stderr | 10 ---------- testsuite/tests/deriving/should_fail/T5863a.hs | 12 ------------ testsuite/tests/deriving/should_fail/T5863a.stderr | 10 ---------- testsuite/tests/deriving/should_fail/T7800.hs | 7 ------- testsuite/tests/deriving/should_fail/T7800.stderr | 6 ------ testsuite/tests/deriving/should_fail/T7800a.hs | 4 ---- testsuite/tests/deriving/should_fail/T9687.stderr | 4 +--- testsuite/tests/deriving/should_fail/all.T | 6 +++--- testsuite/tests/polykinds/T8132.stderr | 4 +--- .../typecheck/should_fail/TcStaticPointersFail02.stderr | 2 +- 12 files changed, 7 insertions(+), 69 deletions(-) diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index 8d90236..b56baed 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -46,7 +46,7 @@ test('T8758', extra_clean(['T8758a.o', 'T8758a.hi']), multimod_compile, ['T8758a test('T8678', normal, compile, ['']) test('T8865', normal, compile, ['']) test('T8893', normal, compile, ['']) -test('T8950', expect_broken(8950), compile, ['']) +test('T8950', normal, compile, ['']) test('T8963', normal, compile, ['']) test('T7269', normal, compile, ['']) test('T9069', normal, compile, ['']) diff --git a/testsuite/tests/deriving/should_fail/T2604.hs b/testsuite/tests/deriving/should_fail/T2604.hs deleted file mode 100644 index 0f830d9..0000000 --- a/testsuite/tests/deriving/should_fail/T2604.hs +++ /dev/null @@ -1,9 +0,0 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} - -module Test where - -import Data.Typeable - -data DList a = DList [a] deriving(Typeable) - -newtype NList a = NList [a] deriving(Typeable) diff --git a/testsuite/tests/deriving/should_fail/T2604.stderr b/testsuite/tests/deriving/should_fail/T2604.stderr deleted file mode 100644 index 3000b50..0000000 --- a/testsuite/tests/deriving/should_fail/T2604.stderr +++ /dev/null @@ -1,10 +0,0 @@ - -T2604.hs:7:35: - Can't make a Typeable instance of ?DList? - You need DeriveDataTypeable to derive Typeable instances - In the data declaration for ?DList? - -T2604.hs:9:38: - Can't make a Typeable instance of ?NList? - You need DeriveDataTypeable to derive Typeable instances - In the newtype declaration for ?NList? diff --git a/testsuite/tests/deriving/should_fail/T5863a.hs b/testsuite/tests/deriving/should_fail/T5863a.hs deleted file mode 100644 index 3506dcc..0000000 --- a/testsuite/tests/deriving/should_fail/T5863a.hs +++ /dev/null @@ -1,12 +0,0 @@ -{-# LANGUAGE DeriveDataTypeable, TypeFamilies #-} - -import Data.Typeable - -class C a where - data T a :: * - -instance C Int where - data T Int = A1 deriving (Typeable) - -instance C Bool where - data T Bool = A2 deriving (Typeable) diff --git a/testsuite/tests/deriving/should_fail/T5863a.stderr b/testsuite/tests/deriving/should_fail/T5863a.stderr deleted file mode 100644 index d64f1b2..0000000 --- a/testsuite/tests/deriving/should_fail/T5863a.stderr +++ /dev/null @@ -1,10 +0,0 @@ - -T5863a.hs:9:31: - Deriving Typeable is not allowed for family instances; - derive Typeable for ?T? alone - In the data instance declaration for ?T? - -T5863a.hs:12:32: - Deriving Typeable is not allowed for family instances; - derive Typeable for ?T? alone - In the data instance declaration for ?T? diff --git a/testsuite/tests/deriving/should_fail/T7800.hs b/testsuite/tests/deriving/should_fail/T7800.hs deleted file mode 100644 index 9f190cf..0000000 --- a/testsuite/tests/deriving/should_fail/T7800.hs +++ /dev/null @@ -1,7 +0,0 @@ -{-# LANGUAGE StandaloneDeriving, DeriveDataTypeable #-} -module T7800 where - -import T7800a -import Data.Typeable - -deriving instance Typeable A diff --git a/testsuite/tests/deriving/should_fail/T7800.stderr b/testsuite/tests/deriving/should_fail/T7800.stderr deleted file mode 100644 index 8cd8533..0000000 --- a/testsuite/tests/deriving/should_fail/T7800.stderr +++ /dev/null @@ -1,6 +0,0 @@ -[1 of 2] Compiling T7800a ( T7800a.hs, T7800a.o ) -[2 of 2] Compiling T7800 ( T7800.hs, T7800.o ) - -T7800.hs:7:1: - To make a Typeable instance of poly-kinded ?A?, use XPolyKinds - In the stand-alone deriving instance for ?Typeable A? diff --git a/testsuite/tests/deriving/should_fail/T7800a.hs b/testsuite/tests/deriving/should_fail/T7800a.hs deleted file mode 100644 index 22f1305..0000000 --- a/testsuite/tests/deriving/should_fail/T7800a.hs +++ /dev/null @@ -1,4 +0,0 @@ -{-# LANGUAGE PolyKinds #-} -module T7800a where - -data A a \ No newline at end of file diff --git a/testsuite/tests/deriving/should_fail/T9687.stderr b/testsuite/tests/deriving/should_fail/T9687.stderr index 10619a6..ad95393 100644 --- a/testsuite/tests/deriving/should_fail/T9687.stderr +++ b/testsuite/tests/deriving/should_fail/T9687.stderr @@ -1,5 +1,3 @@ T9687.hs:4:10: - Typeable instances can only be derived - Try ?deriving instance Typeable (,,,,,,,)? - (requires StandaloneDeriving) + Class `Typeable` does not support user-specified instances. diff --git a/testsuite/tests/deriving/should_fail/all.T b/testsuite/tests/deriving/should_fail/all.T index df7957d..60a4b7b 100644 --- a/testsuite/tests/deriving/should_fail/all.T +++ b/testsuite/tests/deriving/should_fail/all.T @@ -17,7 +17,7 @@ test('drvfail016', run_command, ['$MAKE --no-print-directory -s drvfail016']) test('T2394', normal, compile_fail, ['']) -test('T2604', normal, compile_fail, ['']) +# T2604 was removed as it was out of date re: fixing #9858 test('T2701', normal, compile_fail, ['']) test('T2851', normal, compile_fail, ['']) test('T2721', normal, compile_fail, ['']) @@ -38,14 +38,14 @@ test('T1133A', extra_clean(['T1133A.o-boot', 'T1133A.hi-boot']), run_command, ['$MAKE --no-print-directory -s T1133A']) -test('T5863a', normal, compile_fail, ['']) +# 5863a was removed as it was out of date re: fixing #9858 test('T7959', normal, compile_fail, ['']) test('T1496', normal, compile_fail, ['']) test('T4846', normal, compile_fail, ['']) test('T7148', normal, compile_fail, ['']) test('T7148a', normal, compile_fail, ['']) -test('T7800', normal, multimod_compile_fail, ['T7800','']) +# T7800 was removed as it was out of date re: fixing #9858 test('T5498', normal, compile_fail, ['']) test('T6147', normal, compile_fail, ['']) test('T8851', normal, compile_fail, ['']) diff --git a/testsuite/tests/polykinds/T8132.stderr b/testsuite/tests/polykinds/T8132.stderr index 6c567de..e4c4659 100644 --- a/testsuite/tests/polykinds/T8132.stderr +++ b/testsuite/tests/polykinds/T8132.stderr @@ -1,5 +1,3 @@ T8132.hs:6:10: - Typeable instances can only be derived - Try ?deriving instance Typeable K? - (requires StandaloneDeriving) + Class `Typeable` does not support user-specified instances. diff --git a/testsuite/tests/typecheck/should_fail/TcStaticPointersFail02.stderr b/testsuite/tests/typecheck/should_fail/TcStaticPointersFail02.stderr index ead183c..3989ea4 100644 --- a/testsuite/tests/typecheck/should_fail/TcStaticPointersFail02.stderr +++ b/testsuite/tests/typecheck/should_fail/TcStaticPointersFail02.stderr @@ -7,7 +7,7 @@ TcStaticPointersFail02.hs:9:6: f1 = static (undefined :: (forall a. a -> a) -> b) TcStaticPointersFail02.hs:12:6: - No instance for (Data.Typeable.Internal.Typeable Monad) + No instance for (Data.Typeable.Internal.Typeable m) (maybe you haven't applied a function to enough arguments?) arising from a static form In the expression: static return From git at git.haskell.org Sat Mar 7 16:43:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:56 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Add flag to warn when deriving typeable, and update user manual (735d968) Message-ID: <20150307164356.272E63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/735d96891a0f861e4130c67e35c24c8eafefda2c/ghc >--------------------------------------------------------------- commit 735d96891a0f861e4130c67e35c24c8eafefda2c Author: Iavor S. Diatchki Date: Thu Feb 12 17:05:51 2015 -0800 Add flag to warn when deriving typeable, and update user manual >--------------------------------------------------------------- 735d96891a0f861e4130c67e35c24c8eafefda2c compiler/main/DynFlags.hs | 2 ++ compiler/typecheck/TcDeriv.hs | 11 +++++--- compiler/typecheck/TcInstDcls.hs | 12 ++++----- docs/users_guide/flags.xml | 19 ++++++++++++-- docs/users_guide/glasgow_exts.xml | 53 +++++++++++++++++++++------------------ 5 files changed, 62 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 735d96891a0f861e4130c67e35c24c8eafefda2c From git at git.haskell.org Sat Mar 7 16:43:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:43:58 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Remove unused imports to prevent warning, which leads to validation failure. (09d522f) Message-ID: <20150307164358.DC4CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/09d522f67f4c68e64e25a9f2e51da05f251bbcc5/ghc >--------------------------------------------------------------- commit 09d522f67f4c68e64e25a9f2e51da05f251bbcc5 Author: Iavor S. Diatchki Date: Wed Feb 11 17:13:42 2015 -0800 Remove unused imports to prevent warning, which leads to validation failure. >--------------------------------------------------------------- 09d522f67f4c68e64e25a9f2e51da05f251bbcc5 libraries/base/Data/Typeable/Internal.hs | 24 +++--------------------- 1 file changed, 3 insertions(+), 21 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index dbc76be..9341ca9 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -50,33 +50,15 @@ module Data.Typeable.Internal ( showsTypeRep, tyConString, rnfTyCon, - listTc, funTc + listTc, funTc, + typeRepKinds, + typeLitTypeRep ) where import GHC.Base import GHC.Word import GHC.Show -import GHC.Read ( Read ) import Data.Proxy -import GHC.Num -import GHC.Real --- import GHC.IORef --- import GHC.IOArray --- import GHC.MVar -import GHC.ST ( ST, STret ) -import GHC.STRef ( STRef ) -import GHC.Ptr ( Ptr, FunPtr ) --- import GHC.Stable -import GHC.Arr ( Array, STArray, Ix ) -import GHC.TypeLits ( Nat, Symbol, KnownNat, KnownSymbol, natVal', symbolVal' ) -import Data.Type.Coercion -import Data.Type.Equality -import Text.ParserCombinators.ReadP ( ReadP ) -import Text.Read.Lex ( Lexeme, Number ) -import Text.ParserCombinators.ReadPrec ( ReadPrec ) -import GHC.Float ( FFFormat, RealFloat, Floating ) -import Data.Bits ( Bits, FiniteBits ) -import GHC.Enum ( Bounded, Enum ) import GHC.Fingerprint.Type import {-# SOURCE #-} GHC.Fingerprint From git at git.haskell.org Sat Mar 7 16:44:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:44:01 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Bugfix: proxy# needs a kind, as well as a type. (079c8a3) Message-ID: <20150307164401.8DC403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/079c8a3eeefa8425902454997b46e78d72c36bf4/ghc >--------------------------------------------------------------- commit 079c8a3eeefa8425902454997b46e78d72c36bf4 Author: Iavor S. Diatchki Date: Wed Feb 11 16:17:17 2015 -0800 Bugfix: proxy# needs a kind, as well as a type. >--------------------------------------------------------------- 079c8a3eeefa8425902454997b46e78d72c36bf4 compiler/deSugar/DsBinds.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index eebf298..079cfbf 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -959,7 +959,7 @@ dsEvTypeable ev = do typeableExpr <- dsEvTerm ev let co = getTypeableCo tc t method = mkCast typeableExpr co - proxy = mkTyApps (Var proxyHashId) [t] + proxy = mkTyApps (Var proxyHashId) [typeKind t, t] return (mkApps method [proxy]) -- This part could be cached From git at git.haskell.org Sat Mar 7 16:44:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:44:04 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: testsuite: fix/update fallout from Typeable changes (3c32dc7) Message-ID: <20150307164404.42AC13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/3c32dc79dde531fd876f51bb6a3d629fd64cef8d/ghc >--------------------------------------------------------------- commit 3c32dc79dde531fd876f51bb6a3d629fd64cef8d Author: Austin Seipp Date: Fri Mar 6 11:33:43 2015 -0600 testsuite: fix/update fallout from Typeable changes Signed-off-by: Austin Seipp >--------------------------------------------------------------- 3c32dc79dde531fd876f51bb6a3d629fd64cef8d testsuite/tests/ghci.debugger/scripts/print019.stderr | 12 ++++-------- 1 file changed, 4 insertions(+), 8 deletions(-) diff --git a/testsuite/tests/ghci.debugger/scripts/print019.stderr b/testsuite/tests/ghci.debugger/scripts/print019.stderr index 139ce8d..0c92dba 100644 --- a/testsuite/tests/ghci.debugger/scripts/print019.stderr +++ b/testsuite/tests/ghci.debugger/scripts/print019.stderr @@ -5,12 +5,8 @@ Use :print or :force to determine these types Relevant bindings include it :: a1 (bound at :11:1) Note: there are several potential instances: - instance forall (k :: BOX) (s :: k). Show (Proxy s) - -- Defined in ?Data.Proxy? - instance forall (k :: BOX) (a :: k) (b :: k). - Show (Data.Type.Coercion.Coercion a b) - -- Defined in ?Data.Type.Coercion? - instance forall (k :: BOX) (a :: k) (b :: k). Show (a :~: b) - -- Defined in ?Data.Type.Equality? - ...plus 47 others + instance Show TyCon -- Defined in ?Data.Typeable.Internal? + instance Show TypeRep -- Defined in ?Data.Typeable.Internal? + instance Show a => Show (Maybe a) -- Defined in ?GHC.Show? + ...plus 30 others In a stmt of an interactive GHCi command: print it From git at git.haskell.org Sat Mar 7 16:44:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:44:07 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: More testsuite fixes. (d2cffe2) Message-ID: <20150307164407.78F0D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/d2cffe244d6408625384de67e383a5fd7a606c28/ghc >--------------------------------------------------------------- commit d2cffe244d6408625384de67e383a5fd7a606c28 Author: Austin Seipp Date: Fri Mar 6 18:16:23 2015 -0600 More testsuite fixes. Signed-off-by: Austin Seipp >--------------------------------------------------------------- d2cffe244d6408625384de67e383a5fd7a606c28 testsuite/tests/typecheck/should_compile/all.T | 1 - .../tests/typecheck/{should_compile => should_fail}/T9999.hs | 0 testsuite/tests/typecheck/should_fail/T9999.stderr | 11 +++++++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 4 files changed, 12 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index c1ed579..7b3fb9f 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -440,7 +440,6 @@ test('T9892', normal, compile, ['']) test('T9939', normal, compile, ['']) test('T9973', normal, compile, ['']) test('T9971', normal, compile, ['']) -test('T9999', normal, compile, ['']) test('T10031', normal, compile, ['']) test('T10072', normal, compile_fail, ['']) test('T10100', normal, compile, ['']) diff --git a/testsuite/tests/typecheck/should_compile/T9999.hs b/testsuite/tests/typecheck/should_fail/T9999.hs similarity index 100% rename from testsuite/tests/typecheck/should_compile/T9999.hs rename to testsuite/tests/typecheck/should_fail/T9999.hs diff --git a/testsuite/tests/typecheck/should_fail/T9999.stderr b/testsuite/tests/typecheck/should_fail/T9999.stderr new file mode 100644 index 0000000..ae7fa28 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9999.stderr @@ -0,0 +1,11 @@ + +T9999.hs:13:38: + No instance for (Typeable F1) + (maybe you haven't applied a function to enough arguments?) + arising from a use of ?typeRep? + In the second argument of ?(==)?, namely + ?typeRep (Proxy :: Proxy F1)? + In the expression: + typeRep (Proxy :: Proxy F) == typeRep (Proxy :: Proxy F1) + In an equation for ?main?: + main = typeRep (Proxy :: Proxy F) == typeRep (Proxy :: Proxy F1) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 20eede0..1ebb0a7 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -353,3 +353,4 @@ test('T9497d', normal, compile_fail, ['-fdefer-type-errors -fno-defer-typed-hole test('T8044', normal, compile_fail, ['']) test('T4921', normal, compile_fail, ['']) test('T9605', normal, compile_fail, ['']) +test('T9999', normal, compile_fail, ['']) From git at git.haskell.org Sat Mar 7 16:44:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:44:10 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Always use a fresh wanted variable, as otherwise we could get into loops. (968ebd4) Message-ID: <20150307164410.3B8283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/968ebd4936121e139978d106b809b9f58df3d234/ghc >--------------------------------------------------------------- commit 968ebd4936121e139978d106b809b9f58df3d234 Author: Iavor S. Diatchki Date: Fri Mar 6 11:33:31 2015 -0800 Always use a fresh wanted variable, as otherwise we could get into loops. >--------------------------------------------------------------- 968ebd4936121e139978d106b809b9f58df3d234 compiler/typecheck/TcInteract.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 716a8c1..8f85dd3 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1889,7 +1889,7 @@ matchTypeableClass clas k t loc -- Emit a `Typeable` constraint for the given type. subGoal ty = do let goal = mkClassPred clas [ typeKind ty, ty ] - (ev,_) <- newWantedEvVar loc goal + ev <- newWantedEvVarNC loc goal return ev From git at git.haskell.org Sat Mar 7 16:44:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 16:44:12 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Fix type checking fallout in Data.hs (2540a1f) Message-ID: <20150307164412.EF2F63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/2540a1f9d3728e815c4a491a109df7af5544bfc3/ghc >--------------------------------------------------------------- commit 2540a1f9d3728e815c4a491a109df7af5544bfc3 Author: Austin Seipp Date: Sat Mar 7 09:49:05 2015 -0600 Fix type checking fallout in Data.hs Signed-off-by: Austin Seipp >--------------------------------------------------------------- 2540a1f9d3728e815c4a491a109df7af5544bfc3 libraries/base/Data/Data.hs | 2 +- testsuite/tests/annotations/should_fail/annfail10.stderr | 5 ++--- 2 files changed, 3 insertions(+), 4 deletions(-) diff --git a/libraries/base/Data/Data.hs b/libraries/base/Data/Data.hs index 34c2350..7fe9c4d 100644 --- a/libraries/base/Data/Data.hs +++ b/libraries/base/Data/Data.hs @@ -1504,7 +1504,7 @@ altConstr = mkConstr altDataType "Alt" ["getAlt"] Prefix altDataType :: DataType altDataType = mkDataType "Alt" [altConstr] -instance (Data (f a), Typeable f, Typeable a) => Data (Alt f a) where +instance (Data (f a), Data a, Typeable f) => Data (Alt f a) where gfoldl f z (Alt x) = (z Alt `f` x) gunfold k z _ = k (z Alt) toConstr (Alt _) = altConstr diff --git a/testsuite/tests/annotations/should_fail/annfail10.stderr b/testsuite/tests/annotations/should_fail/annfail10.stderr index 262677b..5b42bd3 100644 --- a/testsuite/tests/annotations/should_fail/annfail10.stderr +++ b/testsuite/tests/annotations/should_fail/annfail10.stderr @@ -7,9 +7,8 @@ annfail10.hs:9:1: Data.Data.Data (Either a b) -- Defined in ?Data.Data? instance Data.Data.Data Data.Monoid.All -- Defined in ?Data.Data? - instance forall (k :: BOX) (f :: k -> *) (a :: k). - (Data.Data.Data (f a), Data.Typeable.Internal.Typeable f, - Data.Typeable.Internal.Typeable a) => + instance (Data.Data.Data (f a), Data.Data.Data a, + Data.Typeable.Internal.Typeable f) => Data.Data.Data (Data.Monoid.Alt f a) -- Defined in ?Data.Data? ...plus 39 others From git at git.haskell.org Sat Mar 7 17:15:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 17:15:26 +0000 (UTC) Subject: [commit: ghc] master: Don't assume tools are in same directory as ghc in some cases (504d8a4) Message-ID: <20150307171526.28AEA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/504d8a4b183670830093a81d3c7a6d78416aed20/ghc >--------------------------------------------------------------- commit 504d8a4b183670830093a81d3c7a6d78416aed20 Author: Phil Ruffwind Date: Sat Mar 7 11:04:00 2015 -0600 Don't assume tools are in same directory as ghc in some cases Summary: Tools such as `ghc-pkg` and `runghc` are no longer required to be in the same directory as `ghc` when running tests, provided that `TEST_HC` is not explicitly set and an in-tree compiler is not used. Fixes #10126. Reviewers: thomie, austin Reviewed By: thomie, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D705 GHC Trac Issues: #10126 >--------------------------------------------------------------- 504d8a4b183670830093a81d3c7a6d78416aed20 testsuite/mk/boilerplate.mk | 23 ++++++++++++++++++----- 1 file changed, 18 insertions(+), 5 deletions(-) diff --git a/testsuite/mk/boilerplate.mk b/testsuite/mk/boilerplate.mk index 1765d78..3292d3d 100644 --- a/testsuite/mk/boilerplate.mk +++ b/testsuite/mk/boilerplate.mk @@ -43,6 +43,7 @@ STAGE3_GHC := $(abspath $(TOP)/../inplace/bin/ghc-stage3) ifneq "$(wildcard $(STAGE1_GHC) $(STAGE1_GHC).exe)" "" +IMPLICIT_COMPILER = NO IN_TREE_COMPILER = YES ifeq "$(BINDIST)" "YES" TEST_HC := $(abspath $(TOP)/../)/bindisttest/install dir/bin/ghc @@ -56,11 +57,17 @@ TEST_HC := $(STAGE2_GHC) endif else +IMPLICIT_COMPILER = YES IN_TREE_COMPILER = NO TEST_HC := $(shell which ghc) endif else +ifeq "$(TEST_HC)" "ghc" +IMPLICIT_COMPILER = YES +else +IMPLICIT_COMPILER = NO +endif IN_TREE_COMPILER = NO # We want to support both "ghc" and "/usr/bin/ghc" as values of TEST_HC # passed in by the user, but @@ -87,24 +94,30 @@ endif # containing spaces BIN_ROOT = $(shell dirname '$(TEST_HC)') +ifeq "$(IMPLICIT_COMPILER)" "YES" +find_tool = $(shell which $(1)) +else +find_tool = $(BIN_ROOT)/$(1) +endif + ifeq "$(GHC_PKG)" "" -GHC_PKG := $(BIN_ROOT)/ghc-pkg +GHC_PKG := $(call find_tool,ghc-pkg) endif ifeq "$(RUNGHC)" "" -RUNGHC := $(BIN_ROOT)/runghc +RUNGHC := $(call find_tool,runghc) endif ifeq "$(HSC2HS)" "" -HSC2HS := $(BIN_ROOT)/hsc2hs +HSC2HS := $(call find_tool,hsc2hs) endif ifeq "$(HP2PS_ABS)" "" -HP2PS_ABS := $(BIN_ROOT)/hp2ps +HP2PS_ABS := $(call find_tool,hp2ps) endif ifeq "$(HPC)" "" -HPC := $(BIN_ROOT)/hpc +HPC := $(call find_tool,hpc) endif $(eval $(call canonicaliseExecutable,TEST_HC)) From git at git.haskell.org Sat Mar 7 17:15:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 17:15:29 +0000 (UTC) Subject: [commit: ghc] master: Improve core linter so it catches unsafeCoerce problems (T9122) (76b1e11) Message-ID: <20150307171529.10DE93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/76b1e11943d794da61d342c072a783862a9e2a1a/ghc >--------------------------------------------------------------- commit 76b1e11943d794da61d342c072a783862a9e2a1a Author: Alexander Vershilov Date: Sat Mar 7 11:13:12 2015 -0600 Improve core linter so it catches unsafeCoerce problems (T9122) Summary: This is a draft of the patch that is sent for review. In this patch required changes in linter were introduced and actual check: - new helper function: primRepSizeB - primRep check for floating - Add access to dynamic flags in linter. - Implement additional lint rules. Reviewers: austin, goldfire, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D637 GHC Trac Issues: #9122 >--------------------------------------------------------------- 76b1e11943d794da61d342c072a783862a9e2a1a compiler/coreSyn/CoreLint.hs | 98 +++++++++++++++++++---- compiler/iface/TcIface.hs | 3 +- compiler/types/TyCon.hs | 9 +++ docs/core-spec/CoreLint.ott | 8 +- docs/core-spec/CoreSyn.ott | 2 + docs/core-spec/core-spec.mng | 12 +++ docs/core-spec/core-spec.pdf | Bin 339243 -> 340768 bytes testsuite/tests/callarity/unittest/CallArity1.hs | 2 +- 8 files changed, 113 insertions(+), 21 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 76b1e11943d794da61d342c072a783862a9e2a1a From git at git.haskell.org Sat Mar 7 17:15:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 17:15:31 +0000 (UTC) Subject: [commit: ghc] master: Dynamically link all loaded packages in new object (0fcc454) Message-ID: <20150307171531.CC5AC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0fcc454329c4e3e0dc4474412bff599d0e9bdfcd/ghc >--------------------------------------------------------------- commit 0fcc454329c4e3e0dc4474412bff599d0e9bdfcd Author: Peter Trommler Date: Sat Mar 7 11:13:37 2015 -0600 Dynamically link all loaded packages in new object Summary: As a result of fixing #8935 we needed to open shared libraries with RTLD_LOCAL and so symbols from packages loaded earlier cannot be found anymore. We need to include in the link all packages loaded so far. This fixes #10058 Test Plan: validate Reviewers: hvr, simonmar, austin Reviewed By: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D676 GHC Trac Issues: #10058 >--------------------------------------------------------------- 0fcc454329c4e3e0dc4474412bff599d0e9bdfcd compiler/ghci/Linker.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/compiler/ghci/Linker.hs b/compiler/ghci/Linker.hs index 0e36cd9..a2e694e 100644 --- a/compiler/ghci/Linker.hs +++ b/compiler/ghci/Linker.hs @@ -846,7 +846,10 @@ dynLoadObjs dflags pls objs = do buildTag = mkBuildTag [WayDyn], outputFile = Just soFile } - linkDynLib dflags2 objs [] + -- link all "loaded packages" so symbols in those can be resolved + -- Note: We are loading packages with local scope, so to see the + -- symbols in this link we must link all loaded packages again. + linkDynLib dflags2 objs (pkgs_loaded pls) consIORef (filesToNotIntermediateClean dflags) soFile m <- loadDLL soFile case m of From git at git.haskell.org Sat Mar 7 17:19:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 17:19:06 +0000 (UTC) Subject: [commit: ghc] master: build: fix 'make help' (e642de6) Message-ID: <20150307171906.ADFD43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e642de625651c4af0e42932d447d1f53b218aebf/ghc >--------------------------------------------------------------- commit e642de625651c4af0e42932d447d1f53b218aebf Author: Austin Seipp Date: Sat Mar 7 11:18:44 2015 -0600 build: fix 'make help' Summary: This fixes the usage of `make help` in the top-level and subdirectories. Signed-off-by: Austin Seipp Test Plan: It worked now and didn't before. Reviewers: hvr Reviewed By: hvr Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D692 >--------------------------------------------------------------- e642de625651c4af0e42932d447d1f53b218aebf Makefile | 2 +- mk/sub-makefile.mk | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/Makefile b/Makefile index 60853bc..83ef07c 100644 --- a/Makefile +++ b/Makefile @@ -32,7 +32,7 @@ default : all # For help, type 'make help' .PHONY: help help: - @cat MAKEHELP + @cat MAKEHELP.md ifneq "$(filter maintainer-clean distclean clean help,$(MAKECMDGOALS))" "" -include mk/config.mk diff --git a/mk/sub-makefile.mk b/mk/sub-makefile.mk index fdaf830..0ed85c8 100644 --- a/mk/sub-makefile.mk +++ b/mk/sub-makefile.mk @@ -59,4 +59,4 @@ help : sub-help sub-help : @echo "You are in subdirectory \"$(dir)\"." @echo "Useful targets in this directory:" - @cat $(TOP)/SUBMAKEHELP + @sed '1,/Using `make` in subdirectories/d' $(TOP)/MAKEHELP.md From git at git.haskell.org Sat Mar 7 19:30:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 19:30:51 +0000 (UTC) Subject: [commit: ghc] master: Store renamings as (ModuleName, ModuleName) pairs. (68d4f47) Message-ID: <20150307193051.188513A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/68d4f47212633d101c5f4963dbfccf0fb9a8580f/ghc >--------------------------------------------------------------- commit 68d4f47212633d101c5f4963dbfccf0fb9a8580f Author: Edward Z. Yang Date: Fri Mar 6 20:01:12 2015 -0800 Store renamings as (ModuleName, ModuleName) pairs. Summary: Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin, simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D710 >--------------------------------------------------------------- 68d4f47212633d101c5f4963dbfccf0fb9a8580f compiler/main/DynFlags.hs | 15 ++++++++------- compiler/main/Packages.hs | 8 +++----- 2 files changed, 11 insertions(+), 12 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 04445c8..74e0ce6 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -1109,8 +1109,8 @@ data PackageArg = PackageArg String | PackageKeyArg String deriving (Eq, Show) -data ModRenaming = ModRenaming Bool [(String, String)] - deriving (Eq, Show) +data ModRenaming = ModRenaming Bool [(ModuleName, ModuleName)] + deriving (Eq) data PackageFlag = ExposePackage PackageArg ModRenaming @@ -1118,7 +1118,7 @@ data PackageFlag | IgnorePackage String | TrustPackage String | DistrustPackage String - deriving (Eq, Show) + deriving (Eq) defaultHscTarget :: Platform -> HscTarget defaultHscTarget = defaultObjectTarget @@ -1928,12 +1928,12 @@ parseSigOf str = case filter ((=="").snd) (readP_to_S parse str) of -- ToDo: deprecate this 'is' syntax? tok $ ((string "is" >> return ()) +++ (R.char '=' >> return ())) m <- tok $ parseModule - return (mkModuleName n, m) + return (n, m) parseModule = do pk <- munch1 (\c -> isAlphaNum c || c `elem` "-_") _ <- R.char ':' m <- parseModuleName - return (mkModule (stringToPackageKey pk) (mkModuleName m)) + return (mkModule (stringToPackageKey pk) m) tok m = skipSpaces >> m setSigOf :: String -> DynFlags -> DynFlags @@ -3683,8 +3683,9 @@ removeGlobalPkgConf = upd $ \s -> s { extraPkgConfs = filter isNotGlobal . extra clearPkgConf :: DynP () clearPkgConf = upd $ \s -> s { extraPkgConfs = const [] } -parseModuleName :: ReadP String -parseModuleName = munch1 (\c -> isAlphaNum c || c `elem` ".") +parseModuleName :: ReadP ModuleName +parseModuleName = fmap mkModuleName + $ munch1 (\c -> isAlphaNum c || c `elem` ".") parsePackageFlag :: (String -> PackageArg) -- type of argument -> String -- string to parse diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index 42aa0a1..e36221b 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -502,10 +502,8 @@ applyPackageFlag dflags unusable (pkgs, vm) flag = Right (p:_,_) -> return (pkgs, vm') where n = fsPackageName p - vm' = addToUFM_C edit vm_cleared (packageConfigId p) - (b, map convRn rns, n) + vm' = addToUFM_C edit vm_cleared (packageConfigId p) (b, rns, n) edit (b, rns, n) (b', rns', _) = (b || b', rns ++ rns', n) - convRn (a,b) = (mkModuleName a, mkModuleName b) -- ToDo: ATM, -hide-all-packages implicitly triggers change in -- behavior, maybe eventually make it toggleable with a separate -- flag @@ -611,8 +609,8 @@ pprFlag flag = case flag of ppr_rns (ModRenaming b rns) = if b then text "with" else Outputable.empty <+> char '(' <> hsep (punctuate comma (map ppr_rn rns)) <> char ')' - ppr_rn (orig, new) | orig == new = text orig - | otherwise = text orig <+> text "as" <+> text new + ppr_rn (orig, new) | orig == new = ppr orig + | otherwise = ppr orig <+> text "as" <+> ppr new -- ----------------------------------------------------------------------------- -- Wired-in packages From git at git.haskell.org Sat Mar 7 19:45:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 19:45:54 +0000 (UTC) Subject: [commit: ghc] master: base: drop redundant Typeable derivings (47b5b5c) Message-ID: <20150307194554.908E43A302@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/47b5b5c2b2c92ba091313c36489588edadceaa9d/ghc >--------------------------------------------------------------- commit 47b5b5c2b2c92ba091313c36489588edadceaa9d Author: Herbert Valerio Riedel Date: Sat Mar 7 20:42:21 2015 +0100 base: drop redundant Typeable derivings Thanks to #9858 `Typeable` doesn't need to be explicitly derived anymore. This also makes `AutoDeriveTypeable` redundant, as well as some imports of `Typeable` (removal of whose may be beneficial to #9707). This commit removes several such now redundant use-sites in `base`. Reviewed By: austin, ekmett Differential Revision: https://phabricator.haskell.org/D712 >--------------------------------------------------------------- 47b5b5c2b2c92ba091313c36489588edadceaa9d libraries/base/Control/Applicative.hs | 1 - libraries/base/Control/Concurrent/Chan.hs | 5 ++--- libraries/base/Control/Concurrent/QSem.hs | 2 +- libraries/base/Control/Concurrent/QSemN.hs | 4 +--- libraries/base/Control/Exception/Base.hs | 17 ++++++++--------- libraries/base/Data/Complex.hs | 5 ++--- libraries/base/Data/Data.hs | 2 +- libraries/base/Data/Dynamic.hs | 3 +-- libraries/base/Data/Either.hs | 5 ++--- libraries/base/Data/Fixed.hs | 1 - libraries/base/Data/Functor/Identity.hs | 2 +- libraries/base/Data/Monoid.hs | 1 - libraries/base/Data/Typeable/Internal.hs | 1 - libraries/base/Data/Unique.hs | 5 ++--- libraries/base/Data/Version.hs | 4 +--- libraries/base/Data/Void.hs | 1 - libraries/base/Foreign/C/Types.hs | 3 +-- libraries/base/Foreign/Ptr.hs | 3 +-- libraries/base/GHC/Conc/Sync.hs | 9 +-------- libraries/base/GHC/Conc/Windows.hs | 5 ++--- libraries/base/GHC/Exception.hs | 6 ++---- libraries/base/GHC/Exts.hs | 4 ++-- libraries/base/GHC/ForeignPtr.hs | 4 +--- libraries/base/GHC/IO/Exception.hs | 17 +++++------------ libraries/base/GHC/IO/FD.hs | 3 --- libraries/base/GHC/IO/Handle/Types.hs | 4 ---- libraries/base/GHC/IOArray.hs | 5 ++--- libraries/base/GHC/IORef.hs | 5 ++--- libraries/base/GHC/Int.hs | 14 ++++++-------- libraries/base/GHC/MVar.hs | 5 ++--- libraries/base/GHC/Natural.hs | 1 - libraries/base/GHC/Stable.hs | 3 --- libraries/base/GHC/StaticPtr.hs | 5 +---- libraries/base/GHC/Weak.hs | 4 +--- libraries/base/System/Mem/StableName.hs | 5 +---- libraries/base/System/Posix/Types.hs | 3 +-- libraries/base/System/Timeout.hs | 5 ++--- libraries/base/base.cabal | 1 - libraries/base/include/CTypes.h | 2 +- libraries/base/tests/IO/T4144.hs | 1 - libraries/base/tests/foldableArray.hs | 2 +- 41 files changed, 57 insertions(+), 121 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 47b5b5c2b2c92ba091313c36489588edadceaa9d From git at git.haskell.org Sat Mar 7 22:15:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 22:15:35 +0000 (UTC) Subject: [commit: ghc] master: Define proper `MINIMAL` pragma for `class Ix` (7a2d65a) Message-ID: <20150307221535.03DBD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7a2d65a4d93273c89fbb1d19e282d5933c67c7ca/ghc >--------------------------------------------------------------- commit 7a2d65a4d93273c89fbb1d19e282d5933c67c7ca Author: Herbert Valerio Riedel Date: Sat Mar 7 23:15:07 2015 +0100 Define proper `MINIMAL` pragma for `class Ix` Summary: This addresses #10142 Reviewers: goldfire, austin, ekmett Reviewed By: austin, ekmett Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D709 GHC Trac Issues: #10142 >--------------------------------------------------------------- 7a2d65a4d93273c89fbb1d19e282d5933c67c7ca libraries/base/GHC/Arr.hs | 4 ++-- libraries/base/changelog.md | 2 ++ 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/libraries/base/GHC/Arr.hs b/libraries/base/GHC/Arr.hs index ee666eb..6b3a923 100644 --- a/libraries/base/GHC/Arr.hs +++ b/libraries/base/GHC/Arr.hs @@ -71,9 +71,9 @@ default () -- -- * @'rangeSize' (l,u) == 'length' ('range' (l,u))@ @ @ -- --- Minimal complete instance: 'range', 'index' and 'inRange'. --- class (Ord a) => Ix a where + {-# MINIMAL range, (index | unsafeIndex), inRange #-} + -- | The list of values in the subrange defined by a bounding pair. range :: (a,a) -> [a] -- | The position of a subscript in the subrange. diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 5635918..670fa11 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -141,6 +141,8 @@ * Add/expose `rnfTypeRep`, `rnfTyCon`, `TypeRepHash`, and `TyConHash` helpers to `Data.Typeable`. + * Define proper `MINIMAL` pragma for `class Ix`. (#10142) + ## 4.7.0.2 *Dec 2014* * Bundled with GHC 7.8.4 From git at git.haskell.org Sat Mar 7 22:19:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 22:19:05 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Add public rnf/hash operations to TypeRep/TyCon (b2b1c8d) Message-ID: <20150307221905.1E4AA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/b2b1c8d4623db6f8fe38afbe59a8adcf0815056d/ghc >--------------------------------------------------------------- commit b2b1c8d4623db6f8fe38afbe59a8adcf0815056d Author: Herbert Valerio Riedel Date: Thu Mar 5 11:56:03 2015 -0600 Add public rnf/hash operations to TypeRep/TyCon `TyCon` and `TypeRep` are supposed to be abstract, by providing these additional few public operations the need to import `Data.Typeable.Internal` is reduced, and future changes to the internal structure of `TypeRep`/`TyCon` shouldn't require changes in packages such as `deepseq` or `hashable` anymore (hopefully). (cherry picked from commit 56e0ac98c3a439b8757a2e886db259270bdc85f0) >--------------------------------------------------------------- b2b1c8d4623db6f8fe38afbe59a8adcf0815056d libraries/base/Data/Typeable.hs | 4 ++++ libraries/base/Data/Typeable/Internal.hs | 29 ++++++++++++++++++++++++++++- libraries/base/changelog.md | 3 +++ 3 files changed, 35 insertions(+), 1 deletion(-) diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs index 168600f..7e501a5 100644 --- a/libraries/base/Data/Typeable.hs +++ b/libraries/base/Data/Typeable.hs @@ -61,13 +61,17 @@ module Data.Typeable -- * Type representations TypeRep, -- abstract, instance of: Eq, Show, Typeable + typeRepHash, + rnfTypeRep, showsTypeRep, TyCon, -- abstract, instance of: Eq, Show, Typeable + tyConHash, tyConString, tyConPackage, tyConModule, tyConName, + rnfTyCon, -- * Construction of type representations -- mkTyCon, -- :: String -> TyCon diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 647697a..8917833 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -42,8 +42,11 @@ module Data.Typeable.Internal ( splitTyConApp, funResultTy, typeRepArgs, + typeRepHash, + rnfTypeRep, showsTypeRep, tyConString, + rnfTyCon, listTc, funTc ) where @@ -93,7 +96,7 @@ instance Ord TypeRep where -- | An abstract representation of a type constructor. 'TyCon' objects can -- be built using 'mkTyCon'. data TyCon = TyCon { - tyConHash :: {-# UNPACK #-} !Fingerprint, + tyConHash :: {-# UNPACK #-} !Fingerprint, -- ^ @since 4.8.0.0 tyConPackage :: String, -- ^ @since 4.5.0.0 tyConModule :: String, -- ^ @since 4.5.0.0 tyConName :: String -- ^ @since 4.5.0.0 @@ -191,6 +194,12 @@ typeRepArgs (TypeRep _ _ args) = args tyConString :: TyCon -> String tyConString = tyConName +-- | Observe the 'Fingerprint' of a type representation +-- +-- @since 4.8.0.0 +typeRepHash :: TypeRep -> Fingerprint +typeRepHash (TypeRep fpr _ _) = fpr + ------------------------------------------------------------- -- -- The Typeable class and friends @@ -301,6 +310,24 @@ isTupleTyCon :: TyCon -> Bool isTupleTyCon (TyCon _ _ _ ('(':',':_)) = True isTupleTyCon _ = False +-- | Helper to fully evaluate 'TypeRep' for use as @NFData(rnf)@ implementation +-- +-- @since 4.8.0.0 +rnfTypeRep :: TypeRep -> () +rnfTypeRep (TypeRep _ tyc tyrs) = rnfTyCon tyc `seq` go tyrs + where + go [] = () + go (x:xs) = rnfTypeRep x `seq` go xs + +-- | Helper to fully evaluate 'TyCon' for use as @NFData(rnf)@ implementation +-- +-- @since 4.8.0.0 +rnfTyCon :: TyCon -> () +rnfTyCon (TyCon _ tcp tcm tcn) = go tcp `seq` go tcm `seq` go tcn + where + go [] = () + go (x:xs) = x `seq` go xs + -- Some (Show.TypeRep) helpers: showArgs :: Show a => ShowS -> [a] -> ShowS diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 89caf01..5635918 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -138,6 +138,9 @@ * Restore invariant in `Data (Ratio a)` instance (#10011) + * Add/expose `rnfTypeRep`, `rnfTyCon`, `TypeRepHash`, and + `TyConHash` helpers to `Data.Typeable`. + ## 4.7.0.2 *Dec 2014* * Bundled with GHC 7.8.4 From git at git.haskell.org Sat Mar 7 22:19:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 22:19:07 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Define proper `MINIMAL` pragma for `class Ix` (0d58613) Message-ID: <20150307221907.C87743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/0d586136ce995f725bcaae064c98298d391ba178/ghc >--------------------------------------------------------------- commit 0d586136ce995f725bcaae064c98298d391ba178 Author: Herbert Valerio Riedel Date: Sat Mar 7 23:15:07 2015 +0100 Define proper `MINIMAL` pragma for `class Ix` This addresses #10142 (cherry picked from commit 7a2d65a4d93273c89fbb1d19e282d5933c67c7ca) >--------------------------------------------------------------- 0d586136ce995f725bcaae064c98298d391ba178 libraries/base/GHC/Arr.hs | 4 ++-- libraries/base/changelog.md | 2 ++ 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/libraries/base/GHC/Arr.hs b/libraries/base/GHC/Arr.hs index cefef97..537382e 100644 --- a/libraries/base/GHC/Arr.hs +++ b/libraries/base/GHC/Arr.hs @@ -71,9 +71,9 @@ default () -- -- * @'rangeSize' (l,u) == 'length' ('range' (l,u))@ @ @ -- --- Minimal complete instance: 'range', 'index' and 'inRange'. --- class (Ord a) => Ix a where + {-# MINIMAL range, (index | unsafeIndex), inRange #-} + -- | The list of values in the subrange defined by a bounding pair. range :: (a,a) -> [a] -- | The position of a subscript in the subrange. diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 5635918..670fa11 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -141,6 +141,8 @@ * Add/expose `rnfTypeRep`, `rnfTyCon`, `TypeRepHash`, and `TyConHash` helpers to `Data.Typeable`. + * Define proper `MINIMAL` pragma for `class Ix`. (#10142) + ## 4.7.0.2 *Dec 2014* * Bundled with GHC 7.8.4 From git at git.haskell.org Sat Mar 7 22:36:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 22:36:56 +0000 (UTC) Subject: [commit: ghc] master: Add `GHC.OldList` legacy module (e76f866) Message-ID: <20150307223656.B54B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e76f86646229b3f8bcdc6ad71d464104c639f431/ghc >--------------------------------------------------------------- commit e76f86646229b3f8bcdc6ad71d464104c639f431 Author: Herbert Valerio Riedel Date: Sat Mar 7 23:31:27 2015 +0100 Add `GHC.OldList` legacy module This module provides access the list-specialised versions for legacy purposes (such as implementing Haskell2010-ish preludes). This module basically re-exports the hidden `Data.OldList` module (but in the less controversial `GHC.*` namespace, which signals less committment to keep this module around). This is legacy module is mostly for GHC 7.10's sake. What becomes long-term of `GHC.OldList` can be decided unhurriedly during the GHC 7.12 development cycle. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D689 >--------------------------------------------------------------- e76f86646229b3f8bcdc6ad71d464104c639f431 libraries/base/GHC/OldList.hs | 29 +++++++++++++++++++++++++++++ libraries/base/base.cabal | 1 + libraries/base/changelog.md | 4 ++++ 3 files changed, 34 insertions(+) diff --git a/libraries/base/GHC/OldList.hs b/libraries/base/GHC/OldList.hs new file mode 100644 index 0000000..cfb7314 --- /dev/null +++ b/libraries/base/GHC/OldList.hs @@ -0,0 +1,29 @@ +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE Safe #-} + +----------------------------------------------------------------------------- +-- | +-- Module : GHC.OldList +-- Copyright : (c) The University of Glasgow 2001 +-- License : BSD-style (see the file libraries/base/LICENSE) +-- +-- Maintainer : libraries at haskell.org +-- Stability : experimental +-- Portability : portable +-- +-- This legacy module provides access to the list-specialised operations +-- of "Data.List". This module may go away again in future GHC versions and +-- is provided as transitional tool to access some of the list-specialised +-- operations that had to be generalised due to the implementation of the +-- . +-- +-- If the operations needed are available in "GHC.List", it's +-- recommended to avoid importing this module and use "GHC.List" +-- instead for now. +-- +-- @since 4.8.0.0 +----------------------------------------------------------------------------- + +module GHC.OldList (module Data.OldList) where + +import Data.OldList diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal index 3d6021f..2993692 100644 --- a/libraries/base/base.cabal +++ b/libraries/base/base.cabal @@ -246,6 +246,7 @@ Library GHC.MVar GHC.Natural GHC.Num + GHC.OldList GHC.PArr GHC.Pack GHC.Profiling diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 670fa11..e99c1b1 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -60,6 +60,10 @@ and `Data.Foldable`/`Data.Traversable` no longer lead to conflicting definitions. (#9586) + * New (unofficial) module `GHC.OldList` containing only list-specialised + versions of the functions from `Data.List` (in other words, `GHC.OldList` + corresponds to `base-4.7.0.2`'s `Data.List`) + * Replace the `Control.Monad`-exported functions ``` From git at git.haskell.org Sat Mar 7 22:37:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 7 Mar 2015 22:37:32 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Add `GHC.OldList` legacy module (11441db) Message-ID: <20150307223732.4EE753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/11441db9a00223a7e96678f3d621ac14fda634f8/ghc >--------------------------------------------------------------- commit 11441db9a00223a7e96678f3d621ac14fda634f8 Author: Herbert Valerio Riedel Date: Sat Mar 7 23:31:27 2015 +0100 Add `GHC.OldList` legacy module This module provides access the list-specialised versions for legacy purposes (such as implementing Haskell2010-ish preludes). This module basically re-exports the hidden `Data.OldList` module (but in the less controversial `GHC.*` namespace, which signals less committment to keep this module around). This is legacy module is mostly for GHC 7.10's sake. What becomes long-term of `GHC.OldList` can be decided unhurriedly during the GHC 7.12 development cycle. (cherry picked from commit e76f86646229b3f8bcdc6ad71d464104c639f431) >--------------------------------------------------------------- 11441db9a00223a7e96678f3d621ac14fda634f8 libraries/base/GHC/OldList.hs | 29 +++++++++++++++++++++++++++++ libraries/base/base.cabal | 1 + libraries/base/changelog.md | 4 ++++ 3 files changed, 34 insertions(+) diff --git a/libraries/base/GHC/OldList.hs b/libraries/base/GHC/OldList.hs new file mode 100644 index 0000000..cfb7314 --- /dev/null +++ b/libraries/base/GHC/OldList.hs @@ -0,0 +1,29 @@ +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE Safe #-} + +----------------------------------------------------------------------------- +-- | +-- Module : GHC.OldList +-- Copyright : (c) The University of Glasgow 2001 +-- License : BSD-style (see the file libraries/base/LICENSE) +-- +-- Maintainer : libraries at haskell.org +-- Stability : experimental +-- Portability : portable +-- +-- This legacy module provides access to the list-specialised operations +-- of "Data.List". This module may go away again in future GHC versions and +-- is provided as transitional tool to access some of the list-specialised +-- operations that had to be generalised due to the implementation of the +-- . +-- +-- If the operations needed are available in "GHC.List", it's +-- recommended to avoid importing this module and use "GHC.List" +-- instead for now. +-- +-- @since 4.8.0.0 +----------------------------------------------------------------------------- + +module GHC.OldList (module Data.OldList) where + +import Data.OldList diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal index c5c4a15..f83b441 100644 --- a/libraries/base/base.cabal +++ b/libraries/base/base.cabal @@ -247,6 +247,7 @@ Library GHC.MVar GHC.Natural GHC.Num + GHC.OldList GHC.PArr GHC.Pack GHC.Profiling diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 670fa11..e99c1b1 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -60,6 +60,10 @@ and `Data.Foldable`/`Data.Traversable` no longer lead to conflicting definitions. (#9586) + * New (unofficial) module `GHC.OldList` containing only list-specialised + versions of the functions from `Data.List` (in other words, `GHC.OldList` + corresponds to `base-4.7.0.2`'s `Data.List`) + * Replace the `Control.Monad`-exported functions ``` From git at git.haskell.org Sun Mar 8 16:12:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 8 Mar 2015 16:12:10 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Refactor code generation for switch expression (3698409) Message-ID: <20150308161210.660AA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/369840962a79ad71f8aa5d1fea59660cd558d3a7/ghc >--------------------------------------------------------------- commit 369840962a79ad71f8aa5d1fea59660cd558d3a7 Author: Joachim Breitner Date: Sun Mar 8 17:09:46 2015 +0100 Refactor code generation for switch expression This (work-in-progress, Notes-lacking) commit: * Moves the planning of a switch statement from the Stg ? Cmm transformation to a separate Cmm ? Cmm phase. * Separates the algorithm that does the planning from the code that that implements it on Cmm Graphs. * Is already smarter, i.e. will not break the range in the middle of a dense (and hence jump-table-suitable) part. >--------------------------------------------------------------- 369840962a79ad71f8aa5d1fea59660cd558d3a7 compiler/cmm/CmmCreateSwitchPlans.hs | 75 ++++++++++++++++++++ compiler/cmm/CmmNode.hs | 109 ++-------------------------- compiler/cmm/CmmPipeline.hs | 6 ++ compiler/codeGen/StgCmmUtils.hs | 129 +++------------------------------- compiler/ghc.cabal.in | 2 + compiler/ghc.mk | 1 + testsuite/tests/driver/recomp013/B.hs | 2 +- 7 files changed, 101 insertions(+), 223 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 369840962a79ad71f8aa5d1fea59660cd558d3a7 From git at git.haskell.org Sun Mar 8 16:23:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 8 Mar 2015 16:23:46 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Refactor code generation for switch expression (26734a7) Message-ID: <20150308162346.5913B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/26734a76fc8583ecbd6da4163d812e2e7a303289/ghc >--------------------------------------------------------------- commit 26734a76fc8583ecbd6da4163d812e2e7a303289 Author: Joachim Breitner Date: Sun Mar 8 17:09:46 2015 +0100 Refactor code generation for switch expression This (work-in-progress, Notes-lacking) commit: * Moves the planning of a switch statement from the Stg ? Cmm transformation to a separate Cmm ? Cmm phase. * Separates the algorithm that does the planning from the code that that implements it on Cmm Graphs. * Is already smarter, i.e. will not break the range in the middle of a dense (and hence jump-table-suitable) part. >--------------------------------------------------------------- 26734a76fc8583ecbd6da4163d812e2e7a303289 compiler/cmm/CmmCreateSwitchPlans.hs | 75 ++++++++++ compiler/cmm/CmmNode.hs | 109 +------------- compiler/cmm/CmmPipeline.hs | 6 + compiler/cmm/CmmSwitch.hs | 267 ++++++++++++++++++++++++++++++++++ compiler/codeGen/StgCmmUtils.hs | 129 ++-------------- compiler/ghc.cabal.in | 2 + compiler/ghc.mk | 1 + testsuite/tests/driver/recomp013/B.hs | 2 +- 8 files changed, 368 insertions(+), 223 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 26734a76fc8583ecbd6da4163d812e2e7a303289 From git at git.haskell.org Sun Mar 8 19:30:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 8 Mar 2015 19:30:24 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Refactor code generation for switch expression (4be8983) Message-ID: <20150308193024.0554B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/4be8983d6a54605b4c6242f475203c441d94e9e2/ghc >--------------------------------------------------------------- commit 4be8983d6a54605b4c6242f475203c441d94e9e2 Author: Joachim Breitner Date: Sun Mar 8 17:09:46 2015 +0100 Refactor code generation for switch expression This (work-in-progress, Notes-lacking) commit: * Moves the planning of a switch statement from the Stg ? Cmm transformation to a separate Cmm ? Cmm phase. * Separates the algorithm that does the planning from the code that that implements it on Cmm Graphs. * Is already smarter, i.e. will not break the range in the middle of a dense (and hence jump-table-suitable) part. >--------------------------------------------------------------- 4be8983d6a54605b4c6242f475203c441d94e9e2 compiler/cmm/CmmCreateSwitchPlans.hs | 75 ++++++++++ compiler/cmm/CmmNode.hs | 109 +------------- compiler/cmm/CmmPipeline.hs | 6 + compiler/cmm/CmmSwitch.hs | 267 +++++++++++++++++++++++++++++++++++ compiler/codeGen/StgCmmUtils.hs | 129 ++--------------- compiler/ghc.cabal.in | 2 + compiler/ghc.mk | 1 + 7 files changed, 367 insertions(+), 222 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4be8983d6a54605b4c6242f475203c441d94e9e2 From git at git.haskell.org Sun Mar 8 19:30:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 8 Mar 2015 19:30:26 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Apply findSingleValues after adding the off-range elements (1be0041) Message-ID: <20150308193026.CAD853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/1be0041bf81c0d7fcebf423097ff35b512f54e56/ghc >--------------------------------------------------------------- commit 1be0041bf81c0d7fcebf423097ff35b512f54e56 Author: Joachim Breitner Date: Sun Mar 8 20:00:31 2015 +0100 Apply findSingleValues after adding the off-range elements >--------------------------------------------------------------- 1be0041bf81c0d7fcebf423097ff35b512f54e56 compiler/cmm/CmmSwitch.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index 12c392b..4bd905e 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -134,8 +134,8 @@ createSwitchPlan ids = where (range, m, wrap) = addRange ids pieces = concatMap breakTooSmall $ splitAtHoles 10 m - flatPlan = findSingleValues $ mkFlatSwitchPlan (switchTargetsDefault ids) range pieces - plan = buildTree $ wrap flatPlan + flatPlan = findSingleValues $ wrap $ mkFlatSwitchPlan (switchTargetsDefault ids) range pieces + plan = buildTree $ flatPlan type SeparatedList b a = (a, [(b,a)]) From git at git.haskell.org Sun Mar 8 19:30:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 8 Mar 2015 19:30:29 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Fix two off-by-one errors (21d975a) Message-ID: <20150308193029.AC31A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/21d975a7d095b1a0c074396055ce9d23afd458bf/ghc >--------------------------------------------------------------- commit 21d975a7d095b1a0c074396055ce9d23afd458bf Author: Joachim Breitner Date: Sun Mar 8 20:00:55 2015 +0100 Fix two off-by-one errors >--------------------------------------------------------------- 21d975a7d095b1a0c074396055ce9d23afd458bf compiler/cmm/CmmSwitch.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index 4bd905e..bbc1199 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -167,7 +167,7 @@ mkFlatSwitchPlan Nothing _ (m:ms) mkFlatSwitchPlan (Just l) r ms = let ((_,p1):ps) = go r ms in (p1, ps) where go (lo,hi) [] - | lo >= hi = [] + | lo > hi = [] | otherwise = [(lo, Unconditionally l)] go (lo,hi) (m:ms) | lo < min @@ -223,12 +223,11 @@ addRange (SwitchTargets Nothing Nothing m) = ((lo,hi), m, id) where (lo,_) = M.findMin m (hi,_) = M.findMax m --- No range, but a default. Make set the range, but also return the necessary --- branching +-- No range, but a default. Create a range, but also emit SwitchPlans for outside the range addRange (SwitchTargets Nothing (Just l) m) = ( (lo,hi) , m - , \plan -> (Unconditionally l, lo) `consSL` plan `snocSL` (hi, Unconditionally l) + , \plan -> (Unconditionally l, lo) `consSL` plan `snocSL` (hi+1, Unconditionally l) ) where (lo,_) = M.findMin m (hi,_) = M.findMax m From git at git.haskell.org Sun Mar 8 19:30:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 8 Mar 2015 19:30:32 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Handle the two-branch-case in StgCmmUtils already (165dbd9) Message-ID: <20150308193032.721363A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/165dbd92febd638a48b30797316c23b1723508db/ghc >--------------------------------------------------------------- commit 165dbd92febd638a48b30797316c23b1723508db Author: Joachim Breitner Date: Sun Mar 8 20:20:23 2015 +0100 Handle the two-branch-case in StgCmmUtils already >--------------------------------------------------------------- 165dbd92febd638a48b30797316c23b1723508db compiler/codeGen/StgCmmUtils.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index e21b52d..b3cafc6 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -506,6 +506,12 @@ mk_switch tag_expr [(tag,lbl)] (Just deflt) _ _ -- so there must be a default return (mkCbranch cond deflt lbl) +-- TWO BRANCHES, NO DEFAULT: simply do it here +mk_switch tag_expr [(tag1,lbl1), (_tag2,lbl2)] Nothing _ _ + = do dflags <- getDynFlags + let cond = cmmNeWord dflags tag_expr (mkIntExpr dflags tag1) + return (mkCbranch cond lbl2 lbl1) + -- SOMETHING MORE COMPLICATED: defer to CmmCreateSwitchPlans mk_switch tag_expr branches mb_deflt lo_tag hi_tag = do let From git at git.haskell.org Sun Mar 8 21:26:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 8 Mar 2015 21:26:24 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Fix module imports, make validate happier (cd21093) Message-ID: <20150308212624.36CAB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/cd21093b5e4cfba19bafe7269d9f3d33e6c75ce1/ghc >--------------------------------------------------------------- commit cd21093b5e4cfba19bafe7269d9f3d33e6c75ce1 Author: Joachim Breitner Date: Sun Mar 8 22:25:54 2015 +0100 Fix module imports, make validate happier >--------------------------------------------------------------- cd21093b5e4cfba19bafe7269d9f3d33e6c75ce1 compiler/cmm/CmmCommonBlockElim.hs | 1 + compiler/cmm/CmmContFlowOpt.hs | 1 + compiler/cmm/CmmCreateSwitchPlans.hs | 32 ++++++++++++++++---------------- compiler/cmm/CmmLint.hs | 1 + compiler/cmm/CmmNode.hs | 10 ---------- compiler/cmm/CmmProcPoint.hs | 1 + compiler/cmm/CmmSwitch.hs | 2 +- compiler/cmm/MkGraph.hs | 1 + compiler/cmm/PprC.hs | 1 + compiler/cmm/PprCmm.hs | 1 + compiler/codeGen/StgCmmUtils.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, 29 insertions(+), 27 deletions(-) diff --git a/compiler/cmm/CmmCommonBlockElim.hs b/compiler/cmm/CmmCommonBlockElim.hs index 6174929..8f2b07e 100644 --- a/compiler/cmm/CmmCommonBlockElim.hs +++ b/compiler/cmm/CmmCommonBlockElim.hs @@ -8,6 +8,7 @@ where import BlockId import Cmm import CmmUtils +import CmmSwitch import CmmContFlowOpt import Prelude hiding (iterate, succ, unzip, zip) diff --git a/compiler/cmm/CmmContFlowOpt.hs b/compiler/cmm/CmmContFlowOpt.hs index 87b84c9..6842687 100644 --- a/compiler/cmm/CmmContFlowOpt.hs +++ b/compiler/cmm/CmmContFlowOpt.hs @@ -12,6 +12,7 @@ import Hoopl import BlockId import Cmm import CmmUtils +import CmmSwitch import Maybes import Panic diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmCreateSwitchPlans.hs index e7dba4d..570ed6e 100644 --- a/compiler/cmm/CmmCreateSwitchPlans.hs +++ b/compiler/cmm/CmmCreateSwitchPlans.hs @@ -19,6 +19,22 @@ cmmCreateSwitchPlans dflags g = do blocks' <- concat <$> mapM (visitSwitches dflags) (toBlockList g) return $ ofBlockList (g_entry g) blocks' +visitSwitches :: DynFlags -> CmmBlock -> UniqSM [CmmBlock] +visitSwitches dflags block + | (CmmEntry l s, middle, CmmSwitch expr ids) <- blockSplit block + = do + let plan = createSwitchPlan ids + + (newTail, newBlocks) <- implementSwitchPlan dflags expr plan + + let block' = CmmEntry l s `blockJoinHead` middle `blockAppend` newTail + + return $ block' : newBlocks + + | otherwise + = return [block] + + -- Implementing a switch plan (returning a tail block) implementSwitchPlan :: DynFlags -> CmmExpr -> SwitchPlan -> UniqSM (Block CmmNode O C, [CmmBlock]) implementSwitchPlan _ _ (Unconditionally l) @@ -57,19 +73,3 @@ implementSwitchPlan' dflags expr p return (bid, block: newBlocks) -visitSwitches :: DynFlags -> CmmBlock -> UniqSM [CmmBlock] -visitSwitches dflags block - | (CmmEntry l s, middle, CmmSwitch expr ids) <- blockSplit block - = do - let plan = createSwitchPlan ids - - (newTail, newBlocks) <- implementSwitchPlan dflags expr plan - - let block' = CmmEntry l s `blockJoinHead` middle `blockAppend` newTail - - return $ block' : newBlocks - - | otherwise - = return [block] - - diff --git a/compiler/cmm/CmmLint.hs b/compiler/cmm/CmmLint.hs index 89de56d..d1e80fd 100644 --- a/compiler/cmm/CmmLint.hs +++ b/compiler/cmm/CmmLint.hs @@ -14,6 +14,7 @@ import Hoopl import Cmm import CmmUtils import CmmLive +import CmmSwitch import PprCmm () import BlockId import FastString diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index 1d7211a..1899a00 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -19,16 +19,6 @@ module CmmNode ( -- * Tick scopes CmmTickScope(..), isTickSubScope, combineTickScopes, - - -- * Switch - SwitchTargets, - mkSwitchTargets, - switchTargetsCases, switchTargetsDefault, switchTargetsRange, - mapSwitchTargets, switchTargetsToTable, switchTargetsFallThrough, - switchTargetsToList, eqSwitchTargetWith, - - SwitchPlan(..), - createSwitchPlan, ) where import CodeGen.Platform diff --git a/compiler/cmm/CmmProcPoint.hs b/compiler/cmm/CmmProcPoint.hs index 147afe5..a310482 100644 --- a/compiler/cmm/CmmProcPoint.hs +++ b/compiler/cmm/CmmProcPoint.hs @@ -18,6 +18,7 @@ import PprCmm () import CmmUtils import CmmInfo import CmmLive (cmmGlobalLiveness) +import CmmSwitch import Data.List (sortBy) import Maybes import Control.Monad diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index bbc1199..c5c328a 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -129,7 +129,7 @@ data SwitchPlan createSwitchPlan :: SwitchTargets -> SwitchPlan createSwitchPlan ids = - pprTrace "createSwitchPlan" (text (show ids) $$ text (show (range,m)) $$ text (show pieces) $$ text (show flatPlan) $$ text (show plan)) $ + -- pprTrace "createSwitchPlan" (text (show ids) $$ text (show (range,m)) $$ text (show pieces) $$ text (show flatPlan) $$ text (show plan)) $ plan where (range, m, wrap) = addRange ids diff --git a/compiler/cmm/MkGraph.hs b/compiler/cmm/MkGraph.hs index f6b9225..6a7ee01 100644 --- a/compiler/cmm/MkGraph.hs +++ b/compiler/cmm/MkGraph.hs @@ -22,6 +22,7 @@ where import BlockId import Cmm import CmmCallConv +import CmmSwitch import Compiler.Hoopl hiding (Unique, (<*>), mkFirst, mkMiddle, mkLast, mkLabel, mkBranch, Shape(..)) import DynFlags diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs index 5608828..92c8182 100644 --- a/compiler/cmm/PprC.hs +++ b/compiler/cmm/PprC.hs @@ -33,6 +33,7 @@ import Cmm hiding (pprBBlock) import PprCmm () import Hoopl import CmmUtils +import CmmSwitch -- Utils import CPrim diff --git a/compiler/cmm/PprCmm.hs b/compiler/cmm/PprCmm.hs index dac6c46..e623a49 100644 --- a/compiler/cmm/PprCmm.hs +++ b/compiler/cmm/PprCmm.hs @@ -43,6 +43,7 @@ import BlockId () import CLabel import Cmm import CmmUtils +import CmmSwitch import DynFlags import FastString import Outputable diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index b3cafc6..fd4afbc 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -51,6 +51,7 @@ import MkGraph import CodeGen.Platform import CLabel import CmmUtils +import CmmSwitch import ForeignCall import IdInfo diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 9049214..4f864b6 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -18,6 +18,7 @@ import Cmm import CPrim import PprCmm import CmmUtils +import CmmSwitch import Hoopl import DynFlags diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs index fb42c07..a115980 100644 --- a/compiler/nativeGen/PPC/CodeGen.hs +++ b/compiler/nativeGen/PPC/CodeGen.hs @@ -45,6 +45,7 @@ import BlockId import PprCmm ( pprExpr ) import Cmm import CmmUtils +import CmmSwitch import CLabel import Hoopl diff --git a/compiler/nativeGen/SPARC/CodeGen.hs b/compiler/nativeGen/SPARC/CodeGen.hs index 3f49afe..a9d8619 100644 --- a/compiler/nativeGen/SPARC/CodeGen.hs +++ b/compiler/nativeGen/SPARC/CodeGen.hs @@ -43,6 +43,7 @@ import NCGMonad import BlockId import Cmm import CmmUtils +import CmmSwitch import Hoopl import PIC import Reg diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs index a826531..7b7cc54 100644 --- a/compiler/nativeGen/X86/CodeGen.hs +++ b/compiler/nativeGen/X86/CodeGen.hs @@ -45,6 +45,7 @@ import BlockId import Module ( primPackageKey ) import PprCmm () import CmmUtils +import CmmSwitch import Cmm import Hoopl import CLabel From git at git.haskell.org Sun Mar 8 21:41:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 8 Mar 2015 21:41:23 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Fix module imports, make validate happier (e2c1b53) Message-ID: <20150308214123.138CA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/e2c1b53261a90d97bffa47b7aa324fc54133d69d/ghc >--------------------------------------------------------------- commit e2c1b53261a90d97bffa47b7aa324fc54133d69d Author: Joachim Breitner Date: Sun Mar 8 22:25:54 2015 +0100 Fix module imports, make validate happier >--------------------------------------------------------------- e2c1b53261a90d97bffa47b7aa324fc54133d69d compiler/cmm/CmmCommonBlockElim.hs | 1 + compiler/cmm/CmmContFlowOpt.hs | 1 + compiler/cmm/CmmCreateSwitchPlans.hs | 32 ++++++++++++++++---------------- compiler/cmm/CmmLint.hs | 1 + compiler/cmm/CmmNode.hs | 10 ---------- compiler/cmm/CmmParse.y | 1 + compiler/cmm/CmmProcPoint.hs | 1 + compiler/cmm/CmmSwitch.hs | 2 +- compiler/cmm/MkGraph.hs | 1 + compiler/cmm/PprC.hs | 1 + compiler/cmm/PprCmm.hs | 1 + compiler/codeGen/StgCmmUtils.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 + 16 files changed, 30 insertions(+), 27 deletions(-) diff --git a/compiler/cmm/CmmCommonBlockElim.hs b/compiler/cmm/CmmCommonBlockElim.hs index 6174929..8f2b07e 100644 --- a/compiler/cmm/CmmCommonBlockElim.hs +++ b/compiler/cmm/CmmCommonBlockElim.hs @@ -8,6 +8,7 @@ where import BlockId import Cmm import CmmUtils +import CmmSwitch import CmmContFlowOpt import Prelude hiding (iterate, succ, unzip, zip) diff --git a/compiler/cmm/CmmContFlowOpt.hs b/compiler/cmm/CmmContFlowOpt.hs index 87b84c9..6842687 100644 --- a/compiler/cmm/CmmContFlowOpt.hs +++ b/compiler/cmm/CmmContFlowOpt.hs @@ -12,6 +12,7 @@ import Hoopl import BlockId import Cmm import CmmUtils +import CmmSwitch import Maybes import Panic diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmCreateSwitchPlans.hs index e7dba4d..570ed6e 100644 --- a/compiler/cmm/CmmCreateSwitchPlans.hs +++ b/compiler/cmm/CmmCreateSwitchPlans.hs @@ -19,6 +19,22 @@ cmmCreateSwitchPlans dflags g = do blocks' <- concat <$> mapM (visitSwitches dflags) (toBlockList g) return $ ofBlockList (g_entry g) blocks' +visitSwitches :: DynFlags -> CmmBlock -> UniqSM [CmmBlock] +visitSwitches dflags block + | (CmmEntry l s, middle, CmmSwitch expr ids) <- blockSplit block + = do + let plan = createSwitchPlan ids + + (newTail, newBlocks) <- implementSwitchPlan dflags expr plan + + let block' = CmmEntry l s `blockJoinHead` middle `blockAppend` newTail + + return $ block' : newBlocks + + | otherwise + = return [block] + + -- Implementing a switch plan (returning a tail block) implementSwitchPlan :: DynFlags -> CmmExpr -> SwitchPlan -> UniqSM (Block CmmNode O C, [CmmBlock]) implementSwitchPlan _ _ (Unconditionally l) @@ -57,19 +73,3 @@ implementSwitchPlan' dflags expr p return (bid, block: newBlocks) -visitSwitches :: DynFlags -> CmmBlock -> UniqSM [CmmBlock] -visitSwitches dflags block - | (CmmEntry l s, middle, CmmSwitch expr ids) <- blockSplit block - = do - let plan = createSwitchPlan ids - - (newTail, newBlocks) <- implementSwitchPlan dflags expr plan - - let block' = CmmEntry l s `blockJoinHead` middle `blockAppend` newTail - - return $ block' : newBlocks - - | otherwise - = return [block] - - diff --git a/compiler/cmm/CmmLint.hs b/compiler/cmm/CmmLint.hs index 89de56d..d1e80fd 100644 --- a/compiler/cmm/CmmLint.hs +++ b/compiler/cmm/CmmLint.hs @@ -14,6 +14,7 @@ import Hoopl import Cmm import CmmUtils import CmmLive +import CmmSwitch import PprCmm () import BlockId import FastString diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index 1d7211a..1899a00 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -19,16 +19,6 @@ module CmmNode ( -- * Tick scopes CmmTickScope(..), isTickSubScope, combineTickScopes, - - -- * Switch - SwitchTargets, - mkSwitchTargets, - switchTargetsCases, switchTargetsDefault, switchTargetsRange, - mapSwitchTargets, switchTargetsToTable, switchTargetsFallThrough, - switchTargetsToList, eqSwitchTargetWith, - - SwitchPlan(..), - createSwitchPlan, ) where import CodeGen.Platform diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 7ec1e4a..0322927 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -226,6 +226,7 @@ import CmmOpt import MkGraph import Cmm import CmmUtils +import CmmSwitch import CmmInfo import BlockId import CmmLex diff --git a/compiler/cmm/CmmProcPoint.hs b/compiler/cmm/CmmProcPoint.hs index 147afe5..a310482 100644 --- a/compiler/cmm/CmmProcPoint.hs +++ b/compiler/cmm/CmmProcPoint.hs @@ -18,6 +18,7 @@ import PprCmm () import CmmUtils import CmmInfo import CmmLive (cmmGlobalLiveness) +import CmmSwitch import Data.List (sortBy) import Maybes import Control.Monad diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index bbc1199..c5c328a 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -129,7 +129,7 @@ data SwitchPlan createSwitchPlan :: SwitchTargets -> SwitchPlan createSwitchPlan ids = - pprTrace "createSwitchPlan" (text (show ids) $$ text (show (range,m)) $$ text (show pieces) $$ text (show flatPlan) $$ text (show plan)) $ + -- pprTrace "createSwitchPlan" (text (show ids) $$ text (show (range,m)) $$ text (show pieces) $$ text (show flatPlan) $$ text (show plan)) $ plan where (range, m, wrap) = addRange ids diff --git a/compiler/cmm/MkGraph.hs b/compiler/cmm/MkGraph.hs index f6b9225..6a7ee01 100644 --- a/compiler/cmm/MkGraph.hs +++ b/compiler/cmm/MkGraph.hs @@ -22,6 +22,7 @@ where import BlockId import Cmm import CmmCallConv +import CmmSwitch import Compiler.Hoopl hiding (Unique, (<*>), mkFirst, mkMiddle, mkLast, mkLabel, mkBranch, Shape(..)) import DynFlags diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs index 5608828..92c8182 100644 --- a/compiler/cmm/PprC.hs +++ b/compiler/cmm/PprC.hs @@ -33,6 +33,7 @@ import Cmm hiding (pprBBlock) import PprCmm () import Hoopl import CmmUtils +import CmmSwitch -- Utils import CPrim diff --git a/compiler/cmm/PprCmm.hs b/compiler/cmm/PprCmm.hs index dac6c46..e623a49 100644 --- a/compiler/cmm/PprCmm.hs +++ b/compiler/cmm/PprCmm.hs @@ -43,6 +43,7 @@ import BlockId () import CLabel import Cmm import CmmUtils +import CmmSwitch import DynFlags import FastString import Outputable diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index b3cafc6..fd4afbc 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -51,6 +51,7 @@ import MkGraph import CodeGen.Platform import CLabel import CmmUtils +import CmmSwitch import ForeignCall import IdInfo diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 9049214..4f864b6 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -18,6 +18,7 @@ import Cmm import CPrim import PprCmm import CmmUtils +import CmmSwitch import Hoopl import DynFlags diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs index fb42c07..a115980 100644 --- a/compiler/nativeGen/PPC/CodeGen.hs +++ b/compiler/nativeGen/PPC/CodeGen.hs @@ -45,6 +45,7 @@ import BlockId import PprCmm ( pprExpr ) import Cmm import CmmUtils +import CmmSwitch import CLabel import Hoopl diff --git a/compiler/nativeGen/SPARC/CodeGen.hs b/compiler/nativeGen/SPARC/CodeGen.hs index 3f49afe..a9d8619 100644 --- a/compiler/nativeGen/SPARC/CodeGen.hs +++ b/compiler/nativeGen/SPARC/CodeGen.hs @@ -43,6 +43,7 @@ import NCGMonad import BlockId import Cmm import CmmUtils +import CmmSwitch import Hoopl import PIC import Reg diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs index a826531..7b7cc54 100644 --- a/compiler/nativeGen/X86/CodeGen.hs +++ b/compiler/nativeGen/X86/CodeGen.hs @@ -45,6 +45,7 @@ import BlockId import Module ( primPackageKey ) import PprCmm () import CmmUtils +import CmmSwitch import Cmm import Hoopl import CLabel From git at git.haskell.org Mon Mar 9 13:17:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 13:17:27 +0000 (UTC) Subject: [commit: ghc] master: Update process submodule (8b7534b) Message-ID: <20150309131727.960143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8b7534b39052c9cb44411bea0ca311a751564d6c/ghc >--------------------------------------------------------------- commit 8b7534b39052c9cb44411bea0ca311a751564d6c Author: Thomas Miedema Date: Sun Mar 8 15:39:16 2015 +0100 Update process submodule Summary: Rename `SysTools.readCreateProcess`. Functions `readCreateProcess` and `readCreateProcessWithExitCode` were added to `System.Process`, the former of which conflicts with `SysTools.readCreateProcess`. Reviewed by: austin Differential Revision: https://phabricator.haskell.org/D713 >--------------------------------------------------------------- 8b7534b39052c9cb44411bea0ca311a751564d6c compiler/main/SysTools.hs | 9 +++++---- libraries/process | 2 +- 2 files changed, 6 insertions(+), 5 deletions(-) diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs index 56eba69..aba4a1b 100644 --- a/compiler/main/SysTools.hs +++ b/compiler/main/SysTools.hs @@ -469,13 +469,14 @@ askCc dflags args = do args2 = args0 ++ args1 ++ args mb_env <- getGccEnv args2 runSomethingWith dflags "gcc" p args2 $ \real_args -> - readCreateProcess (proc p real_args){ env = mb_env } + readCreateProcessWithExitCode' (proc p real_args){ env = mb_env } --- Version of System.Process.readProcessWithExitCode that takes an environment -readCreateProcess +-- Similar to System.Process.readCreateProcessWithExitCode, but stderr is +-- inherited from the parent process, and output to stderr is not captured. +readCreateProcessWithExitCode' :: CreateProcess -> IO (ExitCode, String) -- ^ stdout -readCreateProcess proc = do +readCreateProcessWithExitCode' proc = do (_, Just outh, _, pid) <- createProcess proc{ std_out = CreatePipe } diff --git a/libraries/process b/libraries/process index 160bdd1..ae10a33 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 160bdd16722d85c2644bd2353121d8eb5e1597e4 +Subproject commit ae10a33cd16d9ac9238a193e5355c5c2e05ef0a2 From git at git.haskell.org Mon Mar 9 15:59:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 15:59:51 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Use import lists in simple cases (fd51a9b) Message-ID: <20150309155951.190133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/fd51a9b344ee823353e7d1922e8cfaaf7f5363a1/ghc >--------------------------------------------------------------- commit fd51a9b344ee823353e7d1922e8cfaaf7f5363a1 Author: Joachim Breitner Date: Mon Mar 9 16:07:20 2015 +0100 Use import lists in simple cases >--------------------------------------------------------------- fd51a9b344ee823353e7d1922e8cfaaf7f5363a1 compiler/cmm/CmmCommonBlockElim.hs | 2 +- compiler/cmm/CmmContFlowOpt.hs | 2 +- compiler/cmm/CmmLint.hs | 2 +- compiler/cmm/CmmNode.hs | 2 +- compiler/cmm/CmmParse.y | 2 +- compiler/cmm/MkGraph.hs | 4 ++-- 6 files changed, 7 insertions(+), 7 deletions(-) diff --git a/compiler/cmm/CmmCommonBlockElim.hs b/compiler/cmm/CmmCommonBlockElim.hs index 8f2b07e..0912410 100644 --- a/compiler/cmm/CmmCommonBlockElim.hs +++ b/compiler/cmm/CmmCommonBlockElim.hs @@ -8,7 +8,7 @@ where import BlockId import Cmm import CmmUtils -import CmmSwitch +import CmmSwitch (eqSwitchTargetWith) import CmmContFlowOpt import Prelude hiding (iterate, succ, unzip, zip) diff --git a/compiler/cmm/CmmContFlowOpt.hs b/compiler/cmm/CmmContFlowOpt.hs index 6842687..95c1950 100644 --- a/compiler/cmm/CmmContFlowOpt.hs +++ b/compiler/cmm/CmmContFlowOpt.hs @@ -12,7 +12,7 @@ import Hoopl import BlockId import Cmm import CmmUtils -import CmmSwitch +import CmmSwitch (mapSwitchTargets) import Maybes import Panic diff --git a/compiler/cmm/CmmLint.hs b/compiler/cmm/CmmLint.hs index d1e80fd..edce2e9 100644 --- a/compiler/cmm/CmmLint.hs +++ b/compiler/cmm/CmmLint.hs @@ -14,7 +14,7 @@ import Hoopl import Cmm import CmmUtils import CmmLive -import CmmSwitch +import CmmSwitch (switchTargetsToList) import PprCmm () import BlockId import FastString diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index 1899a00..3bdc70f 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -494,7 +494,7 @@ mapExpM f (CmmAssign r e) = CmmAssign r `fmap` f e mapExpM f (CmmStore addr e) = (\[addr', e'] -> CmmStore addr' e') `fmap` mapListM f [addr, e] mapExpM _ (CmmBranch _) = Nothing mapExpM f (CmmCondBranch e ti fi) = (\x -> CmmCondBranch x ti fi) `fmap` f e -mapExpM f (CmmSwitch e ids) = (\x -> CmmSwitch x ids) `fmap` f e +mapExpM f (CmmSwitch e tbl) = (\x -> CmmSwitch x tbl) `fmap` f e mapExpM f (CmmCall tgt mb_id r o i s) = (\x -> CmmCall x mb_id r o i s) `fmap` f tgt mapExpM f (CmmUnsafeForeignCall tgt fs as) = case mapForeignTargetM f tgt of diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 0322927..8ce5c1d 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -226,7 +226,7 @@ import CmmOpt import MkGraph import Cmm import CmmUtils -import CmmSwitch +import CmmSwitch ( mkSwitchTargets ) import CmmInfo import BlockId import CmmLex diff --git a/compiler/cmm/MkGraph.hs b/compiler/cmm/MkGraph.hs index 6a7ee01..d2aa4aa 100644 --- a/compiler/cmm/MkGraph.hs +++ b/compiler/cmm/MkGraph.hs @@ -22,7 +22,7 @@ where import BlockId import Cmm import CmmCallConv -import CmmSwitch +import CmmSwitch (SwitchTargets) import Compiler.Hoopl hiding (Unique, (<*>), mkFirst, mkMiddle, mkLast, mkLabel, mkBranch, Shape(..)) import DynFlags @@ -225,7 +225,7 @@ mkCbranch :: CmmExpr -> BlockId -> BlockId -> CmmAGraph mkCbranch pred ifso ifnot = mkLast (CmmCondBranch pred ifso ifnot) mkSwitch :: CmmExpr -> SwitchTargets -> CmmAGraph -mkSwitch e ids = mkLast $ CmmSwitch e ids +mkSwitch e tbl = mkLast $ CmmSwitch e tbl mkReturn :: DynFlags -> CmmExpr -> [CmmActual] -> UpdFrameOffset -> CmmAGraph From git at git.haskell.org Mon Mar 9 15:59:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 15:59:54 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Add a few notes, and reorder code in CmmSwitch (0c8dd27) Message-ID: <20150309155954.0EB853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/0c8dd275e1dfd79d15ec7fadb2a34e66bc5815b6/ghc >--------------------------------------------------------------- commit 0c8dd275e1dfd79d15ec7fadb2a34e66bc5815b6 Author: Joachim Breitner Date: Mon Mar 9 16:40:04 2015 +0100 Add a few notes, and reorder code in CmmSwitch >--------------------------------------------------------------- 0c8dd275e1dfd79d15ec7fadb2a34e66bc5815b6 compiler/cmm/CmmSwitch.hs | 224 ++++++++++++++++++++++++++++------------ compiler/codeGen/StgCmmUtils.hs | 1 + 2 files changed, 160 insertions(+), 65 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0c8dd275e1dfd79d15ec7fadb2a34e66bc5815b6 From git at git.haskell.org Mon Mar 9 17:15:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 17:15:57 +0000 (UTC) Subject: [commit: ghc] wip/tc/typeable-with-kinds: Switch back to `newWatnedEvVar`, so we don't keep resolving the same constraint. (ecd6149) Message-ID: <20150309171557.4638F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tc/typeable-with-kinds Link : http://ghc.haskell.org/trac/ghc/changeset/ecd6149ca770ea88f8ac968b33683e5ccc9d17d6/ghc >--------------------------------------------------------------- commit ecd6149ca770ea88f8ac968b33683e5ccc9d17d6 Author: Iavor S. Diatchki Date: Mon Mar 9 10:15:56 2015 -0700 Switch back to `newWatnedEvVar`, so we don't keep resolving the same constraint. >--------------------------------------------------------------- ecd6149ca770ea88f8ac968b33683e5ccc9d17d6 compiler/typecheck/TcInteract.hs | 11 +++++------ 1 file changed, 5 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 8f85dd3..5e514f4 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1858,7 +1858,7 @@ matchTypeableClass clas k t loc Nothing -> return NoInstance -- Not concrete kinds Just kReps -> do tCts <- mapM subGoal ts - mkEv tCts (EvTypeableTyCon tc kReps (map ctEvTerm tCts `zip` ts)) + mkEv tCts (EvTypeableTyCon tc kReps (map getEv tCts `zip` ts)) where (ks,ts) = span isKind ks_ts @@ -1876,7 +1876,7 @@ matchTypeableClass clas k t loc | otherwise = do ct1 <- subGoal f ct2 <- subGoal tk - mkEv [ct1,ct2] (EvTypeableTyApp (ctEvTerm ct1,f) (ctEvTerm ct2,tk)) + mkEv [ct1,ct2] (EvTypeableTyApp (getEv ct1,f) (getEv ct2,tk)) -- Representation for concrete kinds. We just use the kind itself, @@ -1886,13 +1886,12 @@ matchTypeableClass clas k t loc mapM_ kindRep ks return ki + getEv (ct,_fresh) = ctEvTerm ct -- Emit a `Typeable` constraint for the given type. subGoal ty = do let goal = mkClassPred clas [ typeKind ty, ty ] - ev <- newWantedEvVarNC loc goal - return ev + newWantedEvVar loc goal - - mkEv subs ev = return (GenInst subs (EvTypeable ev)) + mkEv subs ev = return (GenInst [ c | (c,Fresh) <- subs ] (EvTypeable ev)) From git at git.haskell.org Mon Mar 9 18:52:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 18:52:44 +0000 (UTC) Subject: [commit: ghc] master: hsc2hs: update submodule (2aef320) Message-ID: <20150309185244.21B013A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2aef3205115b88be8c068739c136eadc8c07e886/ghc >--------------------------------------------------------------- commit 2aef3205115b88be8c068739c136eadc8c07e886 Author: Austin Seipp Date: Mon Mar 9 13:52:14 2015 -0500 hsc2hs: update submodule This includes the fix for #9524. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 2aef3205115b88be8c068739c136eadc8c07e886 utils/hsc2hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/hsc2hs b/utils/hsc2hs index 546438f..e32b4fa 160000 --- a/utils/hsc2hs +++ b/utils/hsc2hs @@ -1 +1 @@ -Subproject commit 546438f93f8eb11da6b9279374552cfd86499253 +Subproject commit e32b4faf97833f92708a8f3f8bbb015f5d1dbcc7 From git at git.haskell.org Mon Mar 9 18:54:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 18:54:43 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: AllocationLimitExceeded should be a child of SomeAsyncException (aec39c9) Message-ID: <20150309185443.C32FD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/aec39c95e482f475f39f65f787d903b166d15f5b/ghc >--------------------------------------------------------------- commit aec39c95e482f475f39f65f787d903b166d15f5b Author: Simon Marlow Date: Wed Feb 25 09:31:18 2015 +0000 AllocationLimitExceeded should be a child of SomeAsyncException (cherry picked from commit b7f7889fc28460e3e8be3ea8e29f98ff473fd934) >--------------------------------------------------------------- aec39c95e482f475f39f65f787d903b166d15f5b libraries/base/GHC/IO/Exception.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/libraries/base/GHC/IO/Exception.hs b/libraries/base/GHC/IO/Exception.hs index 6701fdf..0ed504c 100644 --- a/libraries/base/GHC/IO/Exception.hs +++ b/libraries/base/GHC/IO/Exception.hs @@ -107,7 +107,9 @@ instance Show Deadlock where data AllocationLimitExceeded = AllocationLimitExceeded deriving Typeable -instance Exception AllocationLimitExceeded +instance Exception AllocationLimitExceeded where + toException = asyncExceptionToException + fromException = asyncExceptionFromException instance Show AllocationLimitExceeded where showsPrec _ AllocationLimitExceeded = From git at git.haskell.org Mon Mar 9 18:54:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 18:54:46 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Extend the docs for Data.List.transpose (bbc36b3) Message-ID: <20150309185446.84A703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/bbc36b3e05c6d3078be7a8737c317d2d609317f7/ghc >--------------------------------------------------------------- commit bbc36b3e05c6d3078be7a8737c317d2d609317f7 Author: Joachim Breitner Date: Mon Mar 2 10:55:22 2015 +0100 Extend the docs for Data.List.transpose by giving a sufficient general example to explain what happens when the rows are not of the same lengths. Thanks to Doug McIlroy for the suggestoin. Fixes #10128. (cherry picked from commit c5977c2e2951e9e346a8f4990d5a6bbdbf9cee0b) >--------------------------------------------------------------- bbc36b3e05c6d3078be7a8737c317d2d609317f7 libraries/base/Data/OldList.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index 137ce42..7e79c34 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -468,6 +468,10 @@ intercalate xs xss = concat (intersperse xs xss) -- For example, -- -- > transpose [[1,2,3],[4,5,6]] == [[1,4],[2,5],[3,6]] +-- +-- If some of the rows are shorter than the following rows, their elements are skipped: +-- +-- > transpose [[10,11],[20],[],[30,31,32]] == [[10,20,30],[11,31],[32]] transpose :: [[a]] -> [[a]] transpose [] = [] From git at git.haskell.org Mon Mar 9 18:54:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 18:54:49 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Dynamically link all loaded packages in new object (2e2d540) Message-ID: <20150309185449.593AE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/2e2d5401e76cdc0db58617662c529b7a5c593461/ghc >--------------------------------------------------------------- commit 2e2d5401e76cdc0db58617662c529b7a5c593461 Author: Peter Trommler Date: Sat Mar 7 11:13:37 2015 -0600 Dynamically link all loaded packages in new object Summary: As a result of fixing #8935 we needed to open shared libraries with RTLD_LOCAL and so symbols from packages loaded earlier cannot be found anymore. We need to include in the link all packages loaded so far. This fixes #10058 Test Plan: validate Reviewers: hvr, simonmar, austin Reviewed By: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D676 GHC Trac Issues: #10058 (cherry picked from commit 0fcc454329c4e3e0dc4474412bff599d0e9bdfcd) >--------------------------------------------------------------- 2e2d5401e76cdc0db58617662c529b7a5c593461 compiler/ghci/Linker.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/compiler/ghci/Linker.hs b/compiler/ghci/Linker.hs index 91706da..f9467e1 100644 --- a/compiler/ghci/Linker.hs +++ b/compiler/ghci/Linker.hs @@ -846,7 +846,10 @@ dynLoadObjs dflags pls objs = do buildTag = mkBuildTag [WayDyn], outputFile = Just soFile } - linkDynLib dflags2 objs [] + -- link all "loaded packages" so symbols in those can be resolved + -- Note: We are loading packages with local scope, so to see the + -- symbols in this link we must link all loaded packages again. + linkDynLib dflags2 objs (pkgs_loaded pls) consIORef (filesToNotIntermediateClean dflags) soFile m <- loadDLL soFile case m of From git at git.haskell.org Mon Mar 9 18:58:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 18:58:45 +0000 (UTC) Subject: [commit: ghc] master: Refactor Digraph to use Data.Graph when possible (c439af5) Message-ID: <20150309185845.1431E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c439af5f5baa2c8af3434652554135230edbf5c3/ghc >--------------------------------------------------------------- commit c439af5f5baa2c8af3434652554135230edbf5c3 Author: Edward Z. Yang Date: Fri Mar 6 13:43:31 2015 -0800 Refactor Digraph to use Data.Graph when possible Summary: This just rewrites the IntGraph data type. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D708 >--------------------------------------------------------------- c439af5f5baa2c8af3434652554135230edbf5c3 compiler/utils/Digraph.hs | 300 ++++++------------------------------------- compiler/utils/Outputable.hs | 5 + 2 files changed, 41 insertions(+), 264 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c439af5f5baa2c8af3434652554135230edbf5c3 From git at git.haskell.org Mon Mar 9 19:07:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 19:07:41 +0000 (UTC) Subject: [commit: packages/hpc] wip/T9619: Update maintainer (cf88706) Message-ID: <20150309190741.B68753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/T9619 Link : http://git.haskell.org/packages/hpc.git/commitdiff/cf88706056abafcbeee68fa853a2939c6c6c2100 >--------------------------------------------------------------- commit cf88706056abafcbeee68fa853a2939c6c6c2100 Author: Thomas Miedema Date: Mon Sep 29 10:38:48 2014 +0200 Update maintainer >--------------------------------------------------------------- cf88706056abafcbeee68fa853a2939c6c6c2100 hpc.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hpc.cabal b/hpc.cabal index ccf7738..857faba 100644 --- a/hpc.cabal +++ b/hpc.cabal @@ -4,7 +4,7 @@ version: 0.6.0.2 license: BSD3 license-file: LICENSE author: Andy Gill -maintainer: libraries at haskell.org +maintainer: ghc-devs at haskell.org bug-reports: http://ghc.haskell.org/trac/ghc/newticket?component=Code%20Coverage category: Control synopsis: Code Coverage Library for Haskell From git at git.haskell.org Mon Mar 9 19:07:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 19:07:43 +0000 (UTC) Subject: [commit: packages/hpc] wip/T9619: Use System.FilePath functions instead of (++) (79ec938) Message-ID: <20150309190743.BCCAA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/T9619 Link : http://git.haskell.org/packages/hpc.git/commitdiff/79ec938d1565dca249c6b90c6f4ec30d009966c8 >--------------------------------------------------------------- commit 79ec938d1565dca249c6b90c6f4ec30d009966c8 Author: Thomas Miedema Date: Thu Mar 5 21:36:07 2015 +0100 Use System.FilePath functions instead of (++) >--------------------------------------------------------------- 79ec938d1565dca249c6b90c6f4ec30d009966c8 Trace/Hpc/Mix.hs | 4 +++- Trace/Hpc/Tix.hs | 19 ++++++++----------- hpc.cabal | 1 + 3 files changed, 12 insertions(+), 12 deletions(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index 28050ad..4a7fc74 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -27,6 +27,8 @@ import Data.Time (UTCTime) import Data.Tree import Data.Char +import System.FilePath + -- a module index records the attributes of each tick-box that has -- been introduced in that module, accessed by tick-number position -- in the list @@ -107,7 +109,7 @@ readMix dirNames mod' = do _ -> error $ "can not find " ++ modName ++ " in " ++ show dirNames mixName :: FilePath -> String -> String -mixName dirName name = dirName ++ "/" ++ name ++ ".mix" +mixName dirName name = dirName name <.> "mix" ------------------------------------------------------------------------------ diff --git a/Trace/Hpc/Tix.hs b/Trace/Hpc/Tix.hs index 2b03e0a..fa95dbf 100644 --- a/Trace/Hpc/Tix.hs +++ b/Trace/Hpc/Tix.hs @@ -1,6 +1,10 @@ {-# LANGUAGE CPP #-} -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 704 {-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 702 +-- System.FilePath in filepath version 1.2.0.1 isn't marked or implied Safe, +-- as shipped with GHC 7.2. +{-# LANGUAGE Trustworthy #-} #endif ------------------------------------------------------------ -- Andy Gill and Colin Runciman, June 2006 @@ -12,7 +16,8 @@ module Trace.Hpc.Tix(Tix(..), TixModule(..), tixModuleName, tixModuleHash, tixModuleTixs, readTix, writeTix, getTixFileName) where -import Data.List (isSuffixOf) +import System.FilePath (replaceExtension) + import Trace.Hpc.Util (Hash, catchIO) -- | 'Tix' is the storage format for our dynamic information about @@ -52,15 +57,7 @@ writeTix :: String writeTix name tix = writeFile name (show tix) -{- -tixName :: String -> String -tixName name = name ++ ".tix" --} - -- | 'getTixFullName' takes a binary or @.tix at -file name, -- and normalizes it into a @.tix at -file name. getTixFileName :: String -> String -getTixFileName str | ".tix" `isSuffixOf` str - = str - | otherwise - = str ++ ".tix" +getTixFileName str = replaceExtension str "tix" diff --git a/hpc.cabal b/hpc.cabal index 857faba..32d1d42 100644 --- a/hpc.cabal +++ b/hpc.cabal @@ -38,5 +38,6 @@ Library base >= 4.4.1 && < 4.9, containers >= 0.4.1 && < 0.6, directory >= 1.1 && < 1.3, + filepath >= 1 && < 1.4, time >= 1.2 && < 1.6 ghc-options: -Wall From git at git.haskell.org Mon Mar 9 19:07:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 19:07:45 +0000 (UTC) Subject: [commit: packages/hpc] wip/T9619: Allow same `Mix` file in different dirs (#9619) (6857115) Message-ID: <20150309190745.C21733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/T9619 Link : http://git.haskell.org/packages/hpc.git/commitdiff/6857115fb24862cb5ac11615fe14849dc869f42f >--------------------------------------------------------------- commit 6857115fb24862cb5ac11615fe14849dc869f42f Author: Thomas Miedema Date: Thu Mar 5 21:43:36 2015 +0100 Allow same `Mix` file in different dirs (#9619) >--------------------------------------------------------------- 6857115fb24862cb5ac11615fe14849dc869f42f Trace/Hpc/Mix.hs | 12 ++++++++---- tests/simple/tixs/{.hpc => .hpc.copy}/Main.mix | 0 tests/simple/tixs/test.T | 4 ++++ 3 files changed, 12 insertions(+), 4 deletions(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index 4a7fc74..f4025d9 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -49,7 +49,7 @@ data Mix = Mix Hash -- hash of mix entry + timestamp Int -- tab stop value. [MixEntry] -- entries - deriving (Show,Read) + deriving (Show,Read,Eq) type MixEntry = (HpcPos, BoxLabel) @@ -104,9 +104,13 @@ readMix dirNames mod' = do | dirName <- dirNames ] case catMaybes res of - [r] -> return r - xs@(_:_) -> error $ "found " ++ show(length xs) ++ " instances of " ++ modName ++ " in " ++ show dirNames - _ -> error $ "can not find " ++ modName ++ " in " ++ show dirNames + xs@(x:_:_) | any (/= x) (tail xs) -> + -- Only complain if multiple *different* `Mix` files with the + -- same name are found (#9619). + error $ "found " ++ show(length xs) ++ " different instances of " + ++ modName ++ " in " ++ show dirNames + (x:_) -> return x + _ -> error $ "can not find " ++ modName ++ " in " ++ show dirNames mixName :: FilePath -> String -> String mixName dirName name = dirName name <.> "mix" diff --git a/tests/simple/tixs/.hpc/Main.mix b/tests/simple/tixs/.hpc.copy/Main.mix similarity index 100% copy from tests/simple/tixs/.hpc/Main.mix copy to tests/simple/tixs/.hpc.copy/Main.mix diff --git a/tests/simple/tixs/test.T b/tests/simple/tixs/test.T index 48ca67f..8e98d0e 100644 --- a/tests/simple/tixs/test.T +++ b/tests/simple/tixs/test.T @@ -67,3 +67,7 @@ test('hpc_hand_overlay', "{hpc} report total3.tix"]) test('hpc_bad_001', exit_code(1), run_command, ["{hpc} bad arguments"]) + +test('T9619', ignore_output, run_command, + # Having the same mix file in two different hpcdirs should work. + ["{hpc} report hpc_sample.tix --hpcdir=.hpc --hpcdir=.hpc.copy"]) From git at git.haskell.org Mon Mar 9 19:07:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 19:07:47 +0000 (UTC) Subject: [commit: packages/hpc] wip/T9619's head updated: Allow same `Mix` file in different dirs (#9619) (6857115) Message-ID: <20150309190747.CAF333A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc Branch 'wip/T9619' now includes: cb27dd9 Cleanup test.T files using PEP8 style guide 08afa91 Update fulltest output cf88706 Update maintainer 79ec938 Use System.FilePath functions instead of (++) 6857115 Allow same `Mix` file in different dirs (#9619) From git at git.haskell.org Mon Mar 9 19:22:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 19:22:26 +0000 (UTC) Subject: [commit: ghc] master: Remove obsolete comment in cmmOffset (d01844f) Message-ID: <20150309192226.1DE493A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d01844f145263a038235684900bc7228a799ca6d/ghc >--------------------------------------------------------------- commit d01844f145263a038235684900bc7228a799ca6d Author: Joachim Breitner Date: Mon Mar 9 16:04:42 2015 +0100 Remove obsolete comment in cmmOffset Summary: as obviously, the code does _not_ adhere to the comment, and yet the compiler does _not_ go into an infinite loop. Test Plan: Run validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D719 >--------------------------------------------------------------- d01844f145263a038235684900bc7228a799ca6d compiler/cmm/CmmUtils.hs | 7 ------- 1 file changed, 7 deletions(-) diff --git a/compiler/cmm/CmmUtils.hs b/compiler/cmm/CmmUtils.hs index 65d633e..3ddb9ec 100644 --- a/compiler/cmm/CmmUtils.hs +++ b/compiler/cmm/CmmUtils.hs @@ -205,13 +205,6 @@ cmmOffsetExpr :: DynFlags -> CmmExpr -> CmmExpr -> CmmExpr cmmOffsetExpr dflags e (CmmLit (CmmInt n _)) = cmmOffset dflags e (fromInteger n) cmmOffsetExpr dflags e byte_off = CmmMachOp (MO_Add (cmmExprWidth dflags e)) [e, byte_off] --- NB. Do *not* inspect the value of the offset in these smart constructors!!! --- because the offset is sometimes involved in a loop in the code generator --- (we don't know the real Hp offset until we've generated code for the entire --- basic block, for example). So we cannot eliminate zero offsets at this --- stage; they're eliminated later instead (either during printing or --- a later optimisation step on Cmm). --- cmmOffset :: DynFlags -> CmmExpr -> Int -> CmmExpr cmmOffset _ e 0 = e cmmOffset _ (CmmReg reg) byte_off = cmmRegOff reg byte_off From git at git.haskell.org Mon Mar 9 19:43:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 19:43:42 +0000 (UTC) Subject: [commit: ghc] master: Fix `ghc --make -fhpc` with imported lhs modules (f9344f3) Message-ID: <20150309194342.69E453A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f9344f3646156a9efff2dcfb90e1d5d67fd4f5a1/ghc >--------------------------------------------------------------- commit f9344f3646156a9efff2dcfb90e1d5d67fd4f5a1 Author: Thomas Miedema Date: Tue Mar 3 23:03:44 2015 +0100 Fix `ghc --make -fhpc` with imported lhs modules See Note [Don't normalise input filenames] in `compiler/main/DriverPipeline.hs`. Fixes #2991. Reviewers: austin Differential Revision: https://phabricator.haskell.org/D701 >--------------------------------------------------------------- f9344f3646156a9efff2dcfb90e1d5d67fd4f5a1 compiler/main/DriverPipeline.hs | 68 ++++++++++++++++++++++++++- testsuite/tests/{annotations => hpc}/Makefile | 0 testsuite/tests/hpc/T2991.hs | 5 ++ testsuite/tests/hpc/T2991LiterateModule.lhs | 4 ++ testsuite/tests/hpc/all.T | 17 +++++++ 5 files changed, 92 insertions(+), 2 deletions(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 2d7ee46..24df3a2 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -809,7 +809,8 @@ runPhase (RealPhase (Unlit sf)) input_fn dflags let flags = [ -- The -h option passes the file name for unlit to -- put in a #line directive SysTools.Option "-h" - , SysTools.Option $ escape $ normalise input_fn + -- See Note [Don't normalise input filenames]. + , SysTools.Option $ escape input_fn , SysTools.FileOption "" input_fn , SysTools.FileOption "" output_fn ] @@ -821,7 +822,7 @@ runPhase (RealPhase (Unlit sf)) input_fn dflags -- escape the characters \, ", and ', but don't try to escape -- Unicode or anything else (so we don't use Util.charToC -- here). If we get this wrong, then in - -- Coverage.addTicksToBinds where we check that the filename in + -- Coverage.isGoodTickSrcSpan where we check that the filename in -- a SrcLoc is the same as the source filenaame, the two will -- look bogusly different. See test: -- libraries/hpc/tests/function/subdir/tough2.hs @@ -2327,3 +2328,66 @@ getGhcVersionPathName dflags = do -- 3c: 2f 00 00 00 sethi %hi(0), %l7 -- - 3c: R_SPARC_PC22 _GLOBAL_OFFSET_TABLE_-0x8 -- + 3c: R_SPARC_HI22 _GLOBAL_OFFSET_TABLE_-0x8 + +{- Note [Don't normalise input filenames] + +Summary + We used to normalise input filenames when starting the unlit phase. This + broke hpc in `--make` mode with imported literate modules (#2991). + +Introduction + 1) --main + When compiling a module with --main, GHC scans its imports to find out which + other modules it needs to compile too. It turns out that there is a small + difference between saying `ghc --make A.hs`, when `A` imports `B`, and + specifying both modules on the command line with `ghc --make A.hs B.hs`. In + the former case, the filename for B is inferred to be './B.hs' instead of + 'B.hs'. + + 2) unlit + When GHC compiles a literate haskell file, the source code first needs to go + through unlit, which turns it into normal Haskell source code. At the start + of the unlit phase, in `Driver.Pipeline.runPhase`, we call unlit with the + option `-h` and the name of the original file. We used to normalise this + filename using System.FilePath.normalise, which among other things removes + an initial './'. unlit then uses that filename in #line directives that it + inserts in the transformed source code. + + 3) SrcSpan + A SrcSpan represents a portion of a source code file. It has fields + linenumber, start column, end column, and also a reference to the file it + originated from. The SrcSpans for a literate haskell file refer to the + filename that was passed to unlit -h. + + 4) -fhpc + At some point during compilation with -fhpc, in the function + `deSugar.Coverage.isGoodTickSrcSpan`, we compare the filename that a + `SrcSpan` refers to with the name of the file we are currently compiling. + For some reason I don't yet understand, they can sometimes legitimally be + different, and then hpc ignores that SrcSpan. + +Problem + When running `ghc --make -fhpc A.hs`, where `A.hs` imports the literate + module `B.lhs`, `B` is inferred to be in the file `./B.lhs` (1). At the + start of the unlit phase, the name `./B.lhs` is normalised to `B.lhs` (2). + Therefore the SrcSpans of `B` refer to the file `B.lhs` (3), but we are + still compiling `./B.lhs`. Hpc thinks these two filenames are different (4), + doesn't include ticks for B, and we have unhappy customers (#2991). + +Solution + Do not normalise `input_fn` when starting the unlit phase. + +Alternative solution + Another option would be to not compare the two filenames on equality, but to + use System.FilePath.equalFilePath. That function first normalises its + arguments. The problem is that by the time we need to do the comparison, the + filenames have been turned into FastStrings, probably for performance + reasons, so System.FilePath.equalFilePath can not be used directly. + +Archeology + The call to `normalise` was added in a commit called "Fix slash + direction on Windows with the new filePath code" (c9b6b5e8). The problem + that commit was addressing has since been solved in a different manner, in a + commit called "Fix the filename passed to unlit" (1eedbc6b). So the + `normalise` is no longer necessary. +-} diff --git a/testsuite/tests/annotations/Makefile b/testsuite/tests/hpc/Makefile similarity index 100% copy from testsuite/tests/annotations/Makefile copy to testsuite/tests/hpc/Makefile diff --git a/testsuite/tests/hpc/T2991.hs b/testsuite/tests/hpc/T2991.hs new file mode 100644 index 0000000..451e1eb --- /dev/null +++ b/testsuite/tests/hpc/T2991.hs @@ -0,0 +1,5 @@ +module Main where +-- Test that there are actually entries in the .mix file for an imported +-- literate module generated with --make. +import T2991LiterateModule +main = return () diff --git a/testsuite/tests/hpc/T2991LiterateModule.lhs b/testsuite/tests/hpc/T2991LiterateModule.lhs new file mode 100644 index 0000000..55fc31c --- /dev/null +++ b/testsuite/tests/hpc/T2991LiterateModule.lhs @@ -0,0 +1,4 @@ +\begin{code} +module T2991LiterateModule where +cover_me = 1 +\end{code} diff --git a/testsuite/tests/hpc/all.T b/testsuite/tests/hpc/all.T new file mode 100644 index 0000000..d279018 --- /dev/null +++ b/testsuite/tests/hpc/all.T @@ -0,0 +1,17 @@ +# Do not explicitly specify '-fhpc' in extra_hc_opts, unless also setting +# '-hpcdir' to a different value for each test. Only the `hpc` way does this +# automatically. This way the tests in this directory can be run concurrently +# (Main.mix might overlap otherwise). + +setTestOpts([only_compiler_types(['ghc']), + only_ways(['hpc']), + ]) + +def T2991(cmd): + # The .mix file for the literate module should have non-zero entries. + # The `grep` should exit with exit code 0. + return(cmd + " && grep -q cover_me .hpc.T2991/T2991LiterateModule.mix") +test('T2991', [cmd_wrapper(T2991), extra_clean(['T2991LiterateModule.hi', + 'T2991LiterateModule.o'])], + # Run with 'ghc --main'. Do not list other modules explicitly. + multimod_compile_and_run, ['T2991', '']) From git at git.haskell.org Mon Mar 9 20:15:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 20:15:26 +0000 (UTC) Subject: [commit: ghc] master: Revert "Refactor Digraph to use Data.Graph when possible" (fe3cf4d) Message-ID: <20150309201526.183983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fe3cf4d277b55f99feb9e143705d414f8ca7133b/ghc >--------------------------------------------------------------- commit fe3cf4d277b55f99feb9e143705d414f8ca7133b Author: Edward Z. Yang Date: Mon Mar 9 13:14:13 2015 -0700 Revert "Refactor Digraph to use Data.Graph when possible" This breaks the build with GHC 7.6 bootstrapping, since the Functor SCC instance is not available. This reverts commit c439af5f5baa2c8af3434652554135230edbf5c3. >--------------------------------------------------------------- fe3cf4d277b55f99feb9e143705d414f8ca7133b compiler/utils/Digraph.hs | 300 +++++++++++++++++++++++++++++++++++++------ compiler/utils/Outputable.hs | 5 - 2 files changed, 264 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fe3cf4d277b55f99feb9e143705d414f8ca7133b From git at git.haskell.org Mon Mar 9 21:49:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 21:49:25 +0000 (UTC) Subject: [commit: ghc] master: Refactor Digraph to use Data.Graph when possible (6188d0a) Message-ID: <20150309214925.813523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6188d0ab4f5eaa85b5e5c743939b71f95ade688c/ghc >--------------------------------------------------------------- commit 6188d0ab4f5eaa85b5e5c743939b71f95ade688c Author: Edward Z. Yang Date: Fri Mar 6 13:43:31 2015 -0800 Refactor Digraph to use Data.Graph when possible Summary: This just rewrites the IntGraph data type. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D708 >--------------------------------------------------------------- 6188d0ab4f5eaa85b5e5c743939b71f95ade688c compiler/utils/Digraph.hs | 308 +++++++------------------------------------ compiler/utils/Outputable.hs | 5 + 2 files changed, 50 insertions(+), 263 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6188d0ab4f5eaa85b5e5c743939b71f95ade688c From git at git.haskell.org Mon Mar 9 22:28:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 22:28:18 +0000 (UTC) Subject: [commit: ghc] master: RTS/IOManager: fix trac issue #9722. (74625d6) Message-ID: <20150309222818.230B53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/74625d6847e970e8bdc6991c327515b3e10b231b/ghc >--------------------------------------------------------------- commit 74625d6847e970e8bdc6991c327515b3e10b231b Author: Andreas Voellmy Date: Mon Mar 9 18:27:41 2015 -0400 RTS/IOManager: fix trac issue #9722. Summary: Whenever the RTS has been inactive for idleGCDelayTime, the idle timer fires and calls wakeUpRts(), which in turn calls ioManagerWakeup(), which in turn writes a byte (or a few) to a file descriptor (stored in the io_manager_wakeup_fd variable) registered by the TimerManager and on which the TimerManager will wait. (Note that the write will only occur if the file descriptor is non-negative.) When the RTS shuts down, it shuts down the TimerManager, and in this process the file descriptor stored in io_manager_wakeup_fd is closed. In the error case, the idle timer fires after the close of the file occurs, and then the write() call in ioManagerWakeup() fails and the aforementioned error message gets printed. This patch solves the problem by (1) having the TimerManager (via Control) write -1 to io_manager_wakeup_fd just before closing the file descriptor written in io_manager_wakeup_fd, and (2) having ioManagerWakeup() ignore an error returned by write() in the case that the write returned -1 and the io_manager_wakeup_fd is -1. Reviewers: austin, simonmar, hvr, thomie Reviewed By: thomie Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D722 GHC Trac Issues: #9722 >--------------------------------------------------------------- 74625d6847e970e8bdc6991c327515b3e10b231b libraries/base/GHC/Event/Control.hs | 7 +++++++ rts/posix/Signals.c | 17 +++++++++++++++-- 2 files changed, 22 insertions(+), 2 deletions(-) diff --git a/libraries/base/GHC/Event/Control.hs b/libraries/base/GHC/Event/Control.hs index 747a416..5dcc66e 100644 --- a/libraries/base/GHC/Event/Control.hs +++ b/libraries/base/GHC/Event/Control.hs @@ -68,6 +68,7 @@ data Control = W { , wakeupReadFd :: {-# UNPACK #-} !Fd , wakeupWriteFd :: {-# UNPACK #-} !Fd #endif + , didRegisterWakeupFd :: !Bool } deriving (Show) #if defined(HAVE_EVENTFD) @@ -108,13 +109,19 @@ newControl shouldRegister = allocaArray 2 $ \fds -> do , wakeupReadFd = fromIntegral wake_rd , wakeupWriteFd = fromIntegral wake_wr #endif + , didRegisterWakeupFd = shouldRegister } -- | Close the control structure used by the IO manager thread. +-- N.B. If this Control is the Control whose wakeup file was registered with +-- the RTS, then *BEFORE* the wakeup file is closed, we must call +-- c_setIOManagerWakeupFd (-1), so that the RTS does not try to use the wakeup +-- file after it has been closed. closeControl :: Control -> IO () closeControl w = do _ <- c_close . fromIntegral . controlReadFd $ w _ <- c_close . fromIntegral . controlWriteFd $ w + when (didRegisterWakeupFd w) $ c_setIOManagerWakeupFd (-1) #if defined(HAVE_EVENTFD) _ <- c_close . fromIntegral . controlEventFd $ w #else diff --git a/rts/posix/Signals.c b/rts/posix/Signals.c index 5fbb917..a2fa07f 100644 --- a/rts/posix/Signals.c +++ b/rts/posix/Signals.c @@ -126,7 +126,7 @@ more_handlers(int sig) } // Here's the pipe into which we will send our signals -static int io_manager_wakeup_fd = -1; +static volatile int io_manager_wakeup_fd = -1; static int timer_manager_control_wr_fd = -1; #define IO_MANAGER_WAKEUP 0xff @@ -161,7 +161,20 @@ ioManagerWakeup (void) StgWord8 byte = (StgWord8)IO_MANAGER_WAKEUP; r = write(io_manager_wakeup_fd, &byte, 1); #endif - if (r == -1) { sysErrorBelch("ioManagerWakeup: write"); } + /* N.B. If the TimerManager is shutting down as we run this + * then there is a possiblity that our first read of + * io_manager_wakeup_fd is non-negative, but before we get to the + * write the file is closed. If this occurs, io_manager_wakeup_fd + * will be written into with -1 (GHC.Event.Control does this prior + * to closing), so checking this allows us to distinguish this case. + * To ensure we observe the correct ordering, we declare the + * io_manager_wakeup_fd as volatile. + * Since this is not an error condition, we do not print the error + * message in this case. + */ + if (r == -1 && io_manager_wakeup_fd >= 0) { + sysErrorBelch("ioManagerWakeup: write"); + } } } From git at git.haskell.org Mon Mar 9 22:28:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Mar 2015 22:28:22 +0000 (UTC) Subject: [commit: ghc] master: Merge branch 'master' of git://git.haskell.org/ghc (c4ac3c9) Message-ID: <20150309222822.29CBF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c4ac3c9d981e23a0bc1aa990414213f2049173c8/ghc >--------------------------------------------------------------- commit c4ac3c9d981e23a0bc1aa990414213f2049173c8 Merge: 74625d6 6188d0a Author: Andreas Voellmy Date: Mon Mar 9 18:27:54 2015 -0400 Merge branch 'master' of git://git.haskell.org/ghc >--------------------------------------------------------------- c4ac3c9d981e23a0bc1aa990414213f2049173c8 compiler/cmm/CmmUtils.hs | 7 - compiler/main/DriverPipeline.hs | 68 +++++- compiler/main/SysTools.hs | 9 +- compiler/utils/Digraph.hs | 308 ++++---------------------- compiler/utils/Outputable.hs | 5 + libraries/process | 2 +- testsuite/tests/{annotations => hpc}/Makefile | 0 testsuite/tests/hpc/T2991.hs | 5 + testsuite/tests/hpc/T2991LiterateModule.lhs | 4 + testsuite/tests/hpc/all.T | 17 ++ utils/hsc2hs | 2 +- 11 files changed, 149 insertions(+), 278 deletions(-) From git at git.haskell.org Tue Mar 10 03:56:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 03:56:40 +0000 (UTC) Subject: [commit: ghc] master: Changes to Safe Haskell documentation from feedback (#10140). (c1db477) Message-ID: <20150310035640.1D64D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c1db477151c2c1a330081fd0b4aab29bd85b636f/ghc >--------------------------------------------------------------- commit c1db477151c2c1a330081fd0b4aab29bd85b636f Author: David Terei Date: Mon Mar 9 20:55:52 2015 -0700 Changes to Safe Haskell documentation from feedback (#10140). >--------------------------------------------------------------- c1db477151c2c1a330081fd0b4aab29bd85b636f docs/users_guide/safe_haskell.xml | 230 ++++++++++++++++++++++---------------- 1 file changed, 133 insertions(+), 97 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c1db477151c2c1a330081fd0b4aab29bd85b636f From git at git.haskell.org Tue Mar 10 07:11:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 07:11:18 +0000 (UTC) Subject: [commit: ghc] master: ghc-prim : Hide 64 bit primops when the word size is 32 bits (fixes #9886). (19440ae) Message-ID: <20150310071118.CA0F33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/19440ae2bb256f75934949ae57934caee3831a80/ghc >--------------------------------------------------------------- commit 19440ae2bb256f75934949ae57934caee3831a80 Author: Erik de Castro Lopo Date: Thu Mar 5 19:39:16 2015 +1100 ghc-prim : Hide 64 bit primops when the word size is 32 bits (fixes #9886). Summary: These primops were failing to compile on PowerPC (32 bit). There is also currently no way to call into these primops from Haskell code. Currently, the *only* way to call any of these C hs_atomic_* functions is via the fetch*IntArray primops which are only defined for Int values and Int is always the native word size. When these functions can be called (and tested) from Haskell code, then it will be worth while implementing them. Test Plan: Compile and run on x86, x86_64, powerpc and arm: testsuite/tests/concurrent/should_run/AtomicPrimops.hs Reviewers: tibbe, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D702 GHC Trac Issues: #9886 >--------------------------------------------------------------- 19440ae2bb256f75934949ae57934caee3831a80 libraries/ghc-prim/cbits/atomic.c | 14 ++++++++++++++ 1 file changed, 14 insertions(+) diff --git a/libraries/ghc-prim/cbits/atomic.c b/libraries/ghc-prim/cbits/atomic.c index e3d6cc1..01cc458 100644 --- a/libraries/ghc-prim/cbits/atomic.c +++ b/libraries/ghc-prim/cbits/atomic.c @@ -32,12 +32,14 @@ hs_atomic_add32(volatile StgWord32 *x, StgWord val) return __sync_fetch_and_add(x, (StgWord32) val); } +#if WORD_SIZE_IN_BITS == 64 extern StgWord64 hs_atomic_add64(volatile StgWord64 *x, StgWord64 val); StgWord64 hs_atomic_add64(volatile StgWord64 *x, StgWord64 val) { return __sync_fetch_and_add(x, val); } +#endif // FetchSubByteArrayOp_Int @@ -62,12 +64,14 @@ hs_atomic_sub32(volatile StgWord32 *x, StgWord val) return __sync_fetch_and_sub(x, (StgWord32) val); } +#if WORD_SIZE_IN_BITS == 64 extern StgWord64 hs_atomic_sub64(volatile StgWord64 *x, StgWord64 val); StgWord64 hs_atomic_sub64(volatile StgWord64 *x, StgWord64 val) { return __sync_fetch_and_sub(x, val); } +#endif // FetchAndByteArrayOp_Int @@ -92,12 +96,14 @@ hs_atomic_and32(volatile StgWord32 *x, StgWord val) return __sync_fetch_and_and(x, (StgWord32) val); } +#if WORD_SIZE_IN_BITS == 64 extern StgWord64 hs_atomic_and64(volatile StgWord64 *x, StgWord64 val); StgWord64 hs_atomic_and64(volatile StgWord64 *x, StgWord64 val) { return __sync_fetch_and_and(x, val); } +#endif // FetchNandByteArrayOp_Int @@ -144,6 +150,7 @@ hs_atomic_nand32(volatile StgWord32 *x, StgWord val) #endif } +#if WORD_SIZE_IN_BITS == 64 extern StgWord64 hs_atomic_nand64(volatile StgWord64 *x, StgWord64 val); StgWord64 hs_atomic_nand64(volatile StgWord64 *x, StgWord64 val) @@ -154,6 +161,7 @@ hs_atomic_nand64(volatile StgWord64 *x, StgWord64 val) return __sync_fetch_and_nand(x, val); #endif } +#endif // FetchOrByteArrayOp_Int @@ -178,12 +186,14 @@ hs_atomic_or32(volatile StgWord32 *x, StgWord val) return __sync_fetch_and_or(x, (StgWord32) val); } +#if WORD_SIZE_IN_BITS == 64 extern StgWord64 hs_atomic_or64(volatile StgWord64 *x, StgWord64 val); StgWord64 hs_atomic_or64(volatile StgWord64 *x, StgWord64 val) { return __sync_fetch_and_or(x, val); } +#endif // FetchXorByteArrayOp_Int @@ -208,12 +218,14 @@ hs_atomic_xor32(volatile StgWord32 *x, StgWord val) return __sync_fetch_and_xor(x, (StgWord32) val); } +#if WORD_SIZE_IN_BITS == 64 extern StgWord64 hs_atomic_xor64(volatile StgWord64 *x, StgWord64 val); StgWord64 hs_atomic_xor64(volatile StgWord64 *x, StgWord64 val) { return __sync_fetch_and_xor(x, val); } +#endif // CasByteArrayOp_Int @@ -238,12 +250,14 @@ hs_cmpxchg32(volatile StgWord32 *x, StgWord old, StgWord new) return __sync_val_compare_and_swap(x, (StgWord32) old, (StgWord32) new); } +#if WORD_SIZE_IN_BITS == 64 extern StgWord hs_cmpxchg64(volatile StgWord64 *x, StgWord64 old, StgWord64 new); StgWord hs_cmpxchg64(volatile StgWord64 *x, StgWord64 old, StgWord64 new) { return __sync_val_compare_and_swap(x, old, new); } +#endif // AtomicReadByteArrayOp_Int From git at git.haskell.org Tue Mar 10 08:05:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 08:05:07 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Add a overview comment to CmmCreateSwitchPlan (8257cbe) Message-ID: <20150310080507.7D40B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/8257cbe459ef40ec08338e622de2d82236305e08/ghc >--------------------------------------------------------------- commit 8257cbe459ef40ec08338e622de2d82236305e08 Author: Joachim Breitner Date: Tue Mar 10 09:04:31 2015 +0100 Add a overview comment to CmmCreateSwitchPlan that explains its purpose and the division between CmmCreateSwitchPlan and CmmSwitch. >--------------------------------------------------------------- 8257cbe459ef40ec08338e622de2d82236305e08 compiler/cmm/CmmCreateSwitchPlans.hs | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmCreateSwitchPlans.hs index 570ed6e..1b3ecb4 100644 --- a/compiler/cmm/CmmCreateSwitchPlans.hs +++ b/compiler/cmm/CmmCreateSwitchPlans.hs @@ -14,6 +14,21 @@ import CmmSwitch import UniqSupply import DynFlags + +-- +-- This module replaces Switch statements as generated by the Stg -> Cmm +-- transformation, which might be huge and sparse and hence unsuitable for +-- assembly code, by proper constructs (if-then-else trees, dense jump tables). +-- +-- The actual, abstract strategy is determined by createSwitchPlan in +-- CmmSwitch and returned as a SwitchPlan; here is just the implementation in +-- terms of Cmm code. See Note [Cmm Switches, the general plan] in CmmSwitch. +-- +-- This division into different modules is both to clearly separte concerns, +-- but also because createSwitchPlan needs access to the constructors of +-- SwitchTargets, a data type exported abstractly by CmmSwitch. +-- + cmmCreateSwitchPlans :: DynFlags -> CmmGraph -> UniqSM CmmGraph cmmCreateSwitchPlans dflags g = do blocks' <- concat <$> mapM (visitSwitches dflags) (toBlockList g) From git at git.haskell.org Tue Mar 10 08:13:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 08:13:11 +0000 (UTC) Subject: [commit: ghc] master: Update submodule to Cabal 1.22.1.1 release (fdb7283) Message-ID: <20150310081311.BDF893A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fdb72839fbefc439ac729e01fcb98fa6bd6511cc/ghc >--------------------------------------------------------------- commit fdb72839fbefc439ac729e01fcb98fa6bd6511cc Author: Herbert Valerio Riedel Date: Tue Mar 10 09:11:45 2015 +0100 Update submodule to Cabal 1.22.1.1 release >--------------------------------------------------------------- fdb72839fbefc439ac729e01fcb98fa6bd6511cc libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 9225192..a8dfc6f 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 9225192b7afc2b96062fb991cc3d16cccb9de1b0 +Subproject commit a8dfc6f4cb9cd280299385a50fefc0a4f8103ef1 From git at git.haskell.org Tue Mar 10 08:49:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 08:49:17 +0000 (UTC) Subject: [commit: packages/array] master: Bump minor version to 0.5.1.0 (c585b1f) Message-ID: <20150310084917.CBAC13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array On branch : master Link : http://git.haskell.org/packages/array.git/commitdiff/c585b1f1ef2a65327a6b8d56150c1f951ef375fb >--------------------------------------------------------------- commit c585b1f1ef2a65327a6b8d56150c1f951ef375fb Author: Herbert Valerio Riedel Date: Tue Mar 10 09:32:56 2015 +0100 Bump minor version to 0.5.1.0 This way the type-role addition in 4baaf0b6d1e7498f529e41eaa3a065cfa84b078c becomes be detectable via `MIN_VERSION_array()` >--------------------------------------------------------------- c585b1f1ef2a65327a6b8d56150c1f951ef375fb array.cabal | 2 +- changelog.md | 3 ++- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/array.cabal b/array.cabal index c6b732d..cd9215e 100644 --- a/array.cabal +++ b/array.cabal @@ -1,5 +1,5 @@ name: array -version: 0.5.0.1 +version: 0.5.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE diff --git a/changelog.md b/changelog.md index 5a04388..1134a32 100644 --- a/changelog.md +++ b/changelog.md @@ -1,8 +1,9 @@ # Changelog for [`array` package](http://hackage.haskell.org/package/array) -## 0.5.0.1 *TBA* +## 0.5.1.0 *Mar 2015* * Bundled with GHC 7.10.1 + * Add role annotations for GHC >= 7.8 (#9220) ## 0.5.0.0 *Nov 2013* From git at git.haskell.org Tue Mar 10 08:49:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 08:49:19 +0000 (UTC) Subject: [commit: packages/array] master: Restore compatibility with GHC 7.10 (3b750b3) Message-ID: <20150310084919.D27E63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array On branch : master Link : http://git.haskell.org/packages/array.git/commitdiff/3b750b3eeb02051520f1b149f0171baba951f544 >--------------------------------------------------------------- commit 3b750b3eeb02051520f1b149f0171baba951f544 Author: Herbert Valerio Riedel Date: Tue Mar 10 09:34:10 2015 +0100 Restore compatibility with GHC 7.10 This adds CPP guards around the changes in c9f207182d4c0a4fcfaaabffb5ed759b99913bb5 >--------------------------------------------------------------- 3b750b3eeb02051520f1b149f0171baba951f544 Data/Array/Base.hs | 28 ++++++++++++++++++++++++++++ Data/Array/IO/Internals.hs | 19 +++++++++++++++++++ Data/Array/ST.hs | 15 +++++++++++---- 3 files changed, 58 insertions(+), 4 deletions(-) diff --git a/Data/Array/Base.hs b/Data/Array/Base.hs index d632e10..ab41c0b 100644 --- a/Data/Array/Base.hs +++ b/Data/Array/Base.hs @@ -1390,7 +1390,11 @@ freeze marr = do -- use the safe array creation function here. return (listArray (l,u) es) +#if __GLASGOW_HASKELL__ >= 711 freezeSTUArray :: STUArray s i e -> ST s (UArray i e) +#else +freezeSTUArray :: Ix i => STUArray s i e -> ST s (UArray i e) +#endif freezeSTUArray (STUArray l u n marr#) = ST $ \s1# -> case sizeofMutableByteArray# marr# of { n# -> case newByteArray# n# s1# of { (# s2#, marr'# #) -> @@ -1465,7 +1469,11 @@ thaw arr = case bounds arr of | i <- [0 .. n - 1]] return marr +#if __GLASGOW_HASKELL__ >= 711 thawSTUArray :: UArray i e -> ST s (STUArray s i e) +#else +thawSTUArray :: Ix i => UArray i e -> ST s (STUArray s i e) +#endif thawSTUArray (UArray l u n arr#) = ST $ \s1# -> case sizeofByteArray# arr# of { n# -> case newByteArray# n# s1# of { (# s2#, marr# #) -> @@ -1525,7 +1533,11 @@ unsafeThaw :: (Ix i, IArray a e, MArray b e m) => a i e -> m (b i e) unsafeThaw = thaw {-# INLINE unsafeThawSTUArray #-} +#if __GLASGOW_HASKELL__ >= 711 unsafeThawSTUArray :: UArray i e -> ST s (STUArray s i e) +#else +unsafeThawSTUArray :: Ix i => UArray i e -> ST s (STUArray s i e) +#endif unsafeThawSTUArray (UArray l u n marr#) = return (STUArray l u n (unsafeCoerce# marr#)) @@ -1535,7 +1547,11 @@ unsafeThawSTUArray (UArray l u n marr#) = #-} {-# INLINE unsafeThawIOArray #-} +#if __GLASGOW_HASKELL__ >= 711 unsafeThawIOArray :: Arr.Array ix e -> IO (IOArray ix e) +#else +unsafeThawIOArray :: Ix ix => Arr.Array ix e -> IO (IOArray ix e) +#endif unsafeThawIOArray arr = stToIO $ do marr <- ArrST.unsafeThawSTArray arr return (IOArray marr) @@ -1544,7 +1560,11 @@ unsafeThawIOArray arr = stToIO $ do "unsafeThaw/IOArray" unsafeThaw = unsafeThawIOArray #-} +#if __GLASGOW_HASKELL__ >= 711 thawIOArray :: Arr.Array ix e -> IO (IOArray ix e) +#else +thawIOArray :: Ix ix => Arr.Array ix e -> IO (IOArray ix e) +#endif thawIOArray arr = stToIO $ do marr <- ArrST.thawSTArray arr return (IOArray marr) @@ -1553,7 +1573,11 @@ thawIOArray arr = stToIO $ do "thaw/IOArray" thaw = thawIOArray #-} +#if __GLASGOW_HASKELL__ >= 711 freezeIOArray :: IOArray ix e -> IO (Arr.Array ix e) +#else +freezeIOArray :: Ix ix => IOArray ix e -> IO (Arr.Array ix e) +#endif freezeIOArray (IOArray marr) = stToIO (ArrST.freezeSTArray marr) {-# RULES @@ -1561,7 +1585,11 @@ freezeIOArray (IOArray marr) = stToIO (ArrST.freezeSTArray marr) #-} {-# INLINE unsafeFreezeIOArray #-} +#if __GLASGOW_HASKELL__ >= 711 unsafeFreezeIOArray :: IOArray ix e -> IO (Arr.Array ix e) +#else +unsafeFreezeIOArray :: Ix ix => IOArray ix e -> IO (Arr.Array ix e) +#endif unsafeFreezeIOArray (IOArray marr) = stToIO (ArrST.unsafeFreezeSTArray marr) {-# RULES diff --git a/Data/Array/IO/Internals.hs b/Data/Array/IO/Internals.hs index a7883f3..c934cc5 100644 --- a/Data/Array/IO/Internals.hs +++ b/Data/Array/IO/Internals.hs @@ -34,6 +34,9 @@ import Control.Monad.ST ( RealWorld, stToIO ) import Foreign.Ptr ( Ptr, FunPtr ) import Foreign.StablePtr ( StablePtr ) +#if __GLASGOW_HASKELL__ < 711 +import Data.Ix +#endif import Data.Array.Base import GHC.IOArray (IOArray(..)) @@ -374,7 +377,11 @@ castIOUArray (IOUArray marr) = stToIO $ do return (IOUArray marr') {-# INLINE unsafeThawIOUArray #-} +#if __GLASGOW_HASKELL__ >= 711 unsafeThawIOUArray :: UArray ix e -> IO (IOUArray ix e) +#else +unsafeThawIOUArray :: Ix ix => UArray ix e -> IO (IOUArray ix e) +#endif unsafeThawIOUArray arr = stToIO $ do marr <- unsafeThawSTUArray arr return (IOUArray marr) @@ -383,7 +390,11 @@ unsafeThawIOUArray arr = stToIO $ do "unsafeThaw/IOUArray" unsafeThaw = unsafeThawIOUArray #-} +#if __GLASGOW_HASKELL__ >= 711 thawIOUArray :: UArray ix e -> IO (IOUArray ix e) +#else +thawIOUArray :: Ix ix => UArray ix e -> IO (IOUArray ix e) +#endif thawIOUArray arr = stToIO $ do marr <- thawSTUArray arr return (IOUArray marr) @@ -393,14 +404,22 @@ thawIOUArray arr = stToIO $ do #-} {-# INLINE unsafeFreezeIOUArray #-} +#if __GLASGOW_HASKELL__ >= 711 unsafeFreezeIOUArray :: IOUArray ix e -> IO (UArray ix e) +#else +unsafeFreezeIOUArray :: Ix ix => IOUArray ix e -> IO (UArray ix e) +#endif unsafeFreezeIOUArray (IOUArray marr) = stToIO (unsafeFreezeSTUArray marr) {-# RULES "unsafeFreeze/IOUArray" unsafeFreeze = unsafeFreezeIOUArray #-} +#if __GLASGOW_HASKELL__ >= 711 freezeIOUArray :: IOUArray ix e -> IO (UArray ix e) +#else +freezeIOUArray :: Ix ix => IOUArray ix e -> IO (UArray ix e) +#endif freezeIOUArray (IOUArray marr) = stToIO (freezeSTUArray marr) {-# RULES diff --git a/Data/Array/ST.hs b/Data/Array/ST.hs index 31e1ed0..0a8ff0d 100644 --- a/Data/Array/ST.hs +++ b/Data/Array/ST.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-} {-# LANGUAGE RankNTypes #-} ----------------------------------------------------------------------------- -- | @@ -37,8 +38,11 @@ import GHC.Arr ( STArray, Array, unsafeFreezeSTArray ) -- the array before returning it - it uses 'unsafeFreeze' internally, but -- this wrapper is a safe interface to that function. -- -runSTArray :: (forall s . ST s (STArray s i e)) - -> Array i e +#if __GLASGOW_HASKELL__ >= 711 +runSTArray :: (forall s . ST s (STArray s i e)) -> Array i e +#else +runSTArray :: Ix i => (forall s . ST s (STArray s i e)) -> Array i e +#endif runSTArray st = runST (st >>= unsafeFreezeSTArray) -- | A safe way to create and work with an unboxed mutable array before @@ -47,8 +51,11 @@ runSTArray st = runST (st >>= unsafeFreezeSTArray) -- 'unsafeFreeze' internally, but this wrapper is a safe interface to -- that function. -- -runSTUArray :: (forall s . ST s (STUArray s i e)) - -> UArray i e +#if __GLASGOW_HASKELL__ >= 711 +runSTUArray :: (forall s . ST s (STUArray s i e)) -> UArray i e +#else +runSTUArray :: Ix i => (forall s . ST s (STUArray s i e)) -> UArray i e +#endif runSTUArray st = runST (st >>= unsafeFreezeSTUArray) From git at git.haskell.org Tue Mar 10 09:07:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 09:07:37 +0000 (UTC) Subject: [commit: ghc] master: Update array submodule (min ver bump to 0.5.1.0) (0281c98) Message-ID: <20150310090737.BD2A93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0281c9872501de2b7caa91949457728b5eb7a939/ghc >--------------------------------------------------------------- commit 0281c9872501de2b7caa91949457728b5eb7a939 Author: Herbert Valerio Riedel Date: Tue Mar 10 10:07:07 2015 +0100 Update array submodule (min ver bump to 0.5.1.0) >--------------------------------------------------------------- 0281c9872501de2b7caa91949457728b5eb7a939 libraries/array | 2 +- testsuite/tests/th/TH_Roles2.stderr | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/array b/libraries/array index e69fab7..3b750b3 160000 --- a/libraries/array +++ b/libraries/array @@ -1 +1 @@ -Subproject commit e69fab76b5b15d7e7f413edb936faab30d05b8a0 +Subproject commit 3b750b3eeb02051520f1b149f0171baba951f544 diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index 83d3ac2..489064c 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -4,7 +4,7 @@ TYPE CONSTRUCTORS data T (a :: k) COERCION AXIOMS Dependent modules: [] -Dependent packages: [array-0.5.0.1, base-4.8.0.0, deepseq-1.4.1.0, +Dependent packages: [array-0.5.1.0, base-4.8.0.0, deepseq-1.4.1.0, ghc-prim-0.3.1.0, integer-gmp-1.0.0.0, pretty-1.1.2.0, template-haskell-2.10.0.0] From git at git.haskell.org Tue Mar 10 09:36:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 09:36:47 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update submodule to Cabal 1.22.1.1 release (6de430d) Message-ID: <20150310093647.632153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/6de430d7e4f982b22b9c96b59c8b7440a6236893/ghc >--------------------------------------------------------------- commit 6de430d7e4f982b22b9c96b59c8b7440a6236893 Author: Herbert Valerio Riedel Date: Tue Mar 10 09:11:45 2015 +0100 Update submodule to Cabal 1.22.1.1 release (cherry picked from commit fdb72839fbefc439ac729e01fcb98fa6bd6511cc) >--------------------------------------------------------------- 6de430d7e4f982b22b9c96b59c8b7440a6236893 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 9225192..a8dfc6f 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 9225192b7afc2b96062fb991cc3d16cccb9de1b0 +Subproject commit a8dfc6f4cb9cd280299385a50fefc0a4f8103ef1 From git at git.haskell.org Tue Mar 10 09:36:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 09:36:50 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update deepseq submodule to 1.4.1.0 snapshot (2fb9015) Message-ID: <20150310093650.243813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/2fb901550b8ce8faf194c347cb6f20c55f7688f3/ghc >--------------------------------------------------------------- commit 2fb901550b8ce8faf194c347cb6f20c55f7688f3 Author: Herbert Valerio Riedel Date: Tue Mar 10 10:27:25 2015 +0100 Update deepseq submodule to 1.4.1.0 snapshot >--------------------------------------------------------------- 2fb901550b8ce8faf194c347cb6f20c55f7688f3 libraries/deepseq | 2 +- testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout | 6 +++--- testsuite/tests/th/TH_Roles2.stderr | 2 +- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/libraries/deepseq b/libraries/deepseq index a79bee5..56809c3 160000 --- a/libraries/deepseq +++ b/libraries/deepseq @@ -1 +1 @@ -Subproject commit a79bee5f5da25353b88759cf5ed8d0df2b59946c +Subproject commit 56809c3e45c3a266564672b968817ca8b6d496c1 diff --git a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout index 1567b60..134ad6f 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout +++ b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout @@ -29,17 +29,17 @@ trusted: safe require own pkg trusted: True M_SafePkg6 -package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.5.0* deepseq-1.4.0.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.5.0* deepseq-1.4.1.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 trusted: trustworthy require own pkg trusted: False M_SafePkg7 -package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.5.0* deepseq-1.4.0.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.5.0* deepseq-1.4.1.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 trusted: safe require own pkg trusted: False M_SafePkg8 -package dependencies: array-0.5.0.1 base-4.8.0.0 bytestring-0.10.5.0* deepseq-1.4.0.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: array-0.5.0.1 base-4.8.0.0 bytestring-0.10.5.0* deepseq-1.4.1.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 trusted: trustworthy require own pkg trusted: False diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index ccfe2f5..83d3ac2 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -4,7 +4,7 @@ TYPE CONSTRUCTORS data T (a :: k) COERCION AXIOMS Dependent modules: [] -Dependent packages: [array-0.5.0.1, base-4.8.0.0, deepseq-1.4.0.0, +Dependent packages: [array-0.5.0.1, base-4.8.0.0, deepseq-1.4.1.0, ghc-prim-0.3.1.0, integer-gmp-1.0.0.0, pretty-1.1.2.0, template-haskell-2.10.0.0] From git at git.haskell.org Tue Mar 10 09:36:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 09:36:52 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update array submodule (min ver bump to 0.5.1.0) (8f6ee69) Message-ID: <20150310093652.C63253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/8f6ee6971676613e911bf29a4fa13b3740a39b85/ghc >--------------------------------------------------------------- commit 8f6ee6971676613e911bf29a4fa13b3740a39b85 Author: Herbert Valerio Riedel Date: Tue Mar 10 10:07:07 2015 +0100 Update array submodule (min ver bump to 0.5.1.0) (cherry picked from commit 0281c9872501de2b7caa91949457728b5eb7a939) >--------------------------------------------------------------- 8f6ee6971676613e911bf29a4fa13b3740a39b85 libraries/array | 2 +- testsuite/tests/th/TH_Roles2.stderr | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/array b/libraries/array index 4baaf0b..3b750b3 160000 --- a/libraries/array +++ b/libraries/array @@ -1 +1 @@ -Subproject commit 4baaf0b6d1e7498f529e41eaa3a065cfa84b078c +Subproject commit 3b750b3eeb02051520f1b149f0171baba951f544 diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index 83d3ac2..489064c 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -4,7 +4,7 @@ TYPE CONSTRUCTORS data T (a :: k) COERCION AXIOMS Dependent modules: [] -Dependent packages: [array-0.5.0.1, base-4.8.0.0, deepseq-1.4.1.0, +Dependent packages: [array-0.5.1.0, base-4.8.0.0, deepseq-1.4.1.0, ghc-prim-0.3.1.0, integer-gmp-1.0.0.0, pretty-1.1.2.0, template-haskell-2.10.0.0] From git at git.haskell.org Tue Mar 10 09:43:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 09:43:24 +0000 (UTC) Subject: [commit: ghc] master: Sync up terminfo/haskeline submodule with ghc-7.10 (d2a5ea1) Message-ID: <20150310094324.560013A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d2a5ea11559e3446cb40848e52328bebca00cbf7/ghc >--------------------------------------------------------------- commit d2a5ea11559e3446cb40848e52328bebca00cbf7 Author: Herbert Valerio Riedel Date: Tue Mar 10 10:42:22 2015 +0100 Sync up terminfo/haskeline submodule with ghc-7.10 The GHC 7.10 tree was pointing to slightly newer commits >--------------------------------------------------------------- d2a5ea11559e3446cb40848e52328bebca00cbf7 libraries/haskeline | 2 +- libraries/terminfo | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/haskeline b/libraries/haskeline index 9d032a3..87a01d2 160000 --- a/libraries/haskeline +++ b/libraries/haskeline @@ -1 +1 @@ -Subproject commit 9d032a3ad4e652357212dda1e02c4baa3579f111 +Subproject commit 87a01d222ef13f89a68204602e3fe9273eeed3ca diff --git a/libraries/terminfo b/libraries/terminfo index 83cb515..1b5ab01 160000 --- a/libraries/terminfo +++ b/libraries/terminfo @@ -1 +1 @@ -Subproject commit 83cb51568234910c66a1ec6fd69ba127f6177194 +Subproject commit 1b5ab01452eaa6c21de7174ad4312a017a13d0ab From git at git.haskell.org Tue Mar 10 13:40:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 13:40:22 +0000 (UTC) Subject: [commit: ghc] wip/T10137: mk_switch can be pure (3d682ce) Message-ID: <20150310134022.6D6683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/3d682ce57bc8d4a2df3f0fea6e0e172f11bbd241/ghc >--------------------------------------------------------------- commit 3d682ce57bc8d4a2df3f0fea6e0e172f11bbd241 Author: Joachim Breitner Date: Tue Mar 10 12:56:36 2015 +0100 mk_switch can be pure >--------------------------------------------------------------- 3d682ce57bc8d4a2df3f0fea6e0e172f11bbd241 compiler/codeGen/StgCmmUtils.hs | 43 ++++++++++------------------------------- 1 file changed, 10 insertions(+), 33 deletions(-) diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index f14abd7..7b01536 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -472,61 +472,38 @@ emitSwitch tag_expr branches mb_deflt lo_tag hi_tag = do branches_lbls <- label_branches join_lbl branches tag_expr' <- assignTemp' tag_expr - emit =<< mk_switch tag_expr' (sortBy (comparing fst) branches_lbls) - mb_deflt_lbl lo_tag hi_tag + -- Sort the branches before calling mk_switch + let branches_lbls' = [ (fromIntegral i, l) | (i,l) <- sortBy (comparing fst) branches_lbls ] - -- Sort the branches before calling mk_switch + emit $ mk_switch tag_expr' branches_lbls' + mb_deflt_lbl (fromIntegral lo_tag) (fromIntegral hi_tag) emitLabel join_lbl -mk_switch :: CmmExpr -> [(ConTagZ, BlockId)] +mk_switch :: CmmExpr -> [(Integer, BlockId)] -> Maybe BlockId - -> ConTagZ -> ConTagZ - -> FCode CmmAGraph + -> Integer -> Integer + -> CmmAGraph -- SINGLETON TAG RANGE: no case analysis to do mk_switch _tag_expr [(tag, lbl)] _ lo_tag hi_tag | lo_tag == hi_tag = ASSERT( tag == lo_tag ) - return (mkBranch lbl) + mkBranch lbl -- SINGLETON BRANCH, NO DEFAULT: no case analysis to do mk_switch _tag_expr [(_tag,lbl)] Nothing _ _ - = return (mkBranch lbl) + = mkBranch lbl -- The simplifier might have eliminated a case -- so we may have e.g. case xs of -- [] -> e -- In that situation we can be sure the (:) case -- can't happen, so no need to test --- SINGLETON BRANCH: one equality check to do -mk_switch tag_expr [(tag,lbl)] (Just deflt) _ _ - = do dflags <- getDynFlags - let cond = cmmNeWord dflags tag_expr (mkIntExpr dflags tag) - -- We have lo_tag < hi_tag, but there's only one branch, - -- so there must be a default - return (mkCbranch cond deflt lbl) - --- TWO BRANCHES, NO DEFAULT: simply do it here -mk_switch tag_expr [(tag1,lbl1), (_tag2,lbl2)] Nothing _ _ - = do dflags <- getDynFlags - let cond = cmmNeWord dflags tag_expr (mkIntExpr dflags tag1) - return (mkCbranch cond lbl2 lbl1) - -- SOMETHING MORE COMPLICATED: defer to CmmCreateSwitchPlans -- See Note [Cmm Switches, the general plan] in CmmSwitch mk_switch tag_expr branches mb_deflt lo_tag hi_tag - = do let - -- NB. we have eliminated impossible branches at - -- either end of the range (see below), so the first - -- tag of a real branch is real_lo_tag (not lo_tag). - arms :: M.Map Integer BlockId - arms = M.fromList [ (fromIntegral i, l) | (i,l) <- branches ] - - range = (fromIntegral lo_tag, fromIntegral hi_tag) - return $ mkSwitch - tag_expr - (mkSwitchTargets (Just range) mb_deflt arms) + = mkSwitch tag_expr $ mkSwitchTargets (Just (lo_tag, hi_tag)) mb_deflt (M.fromList branches) divideBranches :: Ord a => [(a,b)] -> ([(a,b)], a, [(a,b)]) divideBranches branches = (lo_branches, mid, hi_branches) From git at git.haskell.org Tue Mar 10 13:40:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 13:40:25 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Remember if we have are dealing with signed values or not (ea6291e) Message-ID: <20150310134025.760113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/ea6291ef4e109f56803b772bc32de2f2ab98e7cc/ghc >--------------------------------------------------------------- commit ea6291ef4e109f56803b772bc32de2f2ab98e7cc Author: Joachim Breitner Date: Tue Mar 10 14:10:24 2015 +0100 CmmSwitch: Remember if we have are dealing with signed values or not >--------------------------------------------------------------- ea6291ef4e109f56803b772bc32de2f2ab98e7cc compiler/cmm/CmmCommonBlockElim.hs | 6 +-- compiler/cmm/CmmContFlowOpt.hs | 2 +- compiler/cmm/CmmCreateSwitchPlans.hs | 75 +++++++++++++++++---------------- compiler/cmm/CmmLint.hs | 2 +- compiler/cmm/CmmNode.hs | 15 ++++--- compiler/cmm/CmmProcPoint.hs | 4 +- compiler/cmm/MkGraph.hs | 6 +-- compiler/cmm/PprC.hs | 4 +- compiler/cmm/PprCmm.hs | 2 +- compiler/codeGen/StgCmmUtils.hs | 17 +++++--- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 2 +- compiler/nativeGen/AsmCodeGen.hs | 4 +- compiler/nativeGen/PPC/CodeGen.hs | 4 +- compiler/nativeGen/SPARC/CodeGen.hs | 4 +- compiler/nativeGen/X86/CodeGen.hs | 4 +- 15 files changed, 78 insertions(+), 73 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ea6291ef4e109f56803b772bc32de2f2ab98e7cc From git at git.haskell.org Tue Mar 10 13:40:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 13:40:28 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Implement discrete literal cases also via the new machinery (01a0809) Message-ID: <20150310134028.62FE63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/01a0809004532ef0d7a94da628c17a8923bd18dd/ghc >--------------------------------------------------------------- commit 01a0809004532ef0d7a94da628c17a8923bd18dd Author: Joachim Breitner Date: Tue Mar 10 13:52:42 2015 +0100 Implement discrete literal cases also via the new machinery (In this form broken for signed literals, fix coming up next.) >--------------------------------------------------------------- 01a0809004532ef0d7a94da628c17a8923bd18dd compiler/basicTypes/Literal.hs | 10 +++++ compiler/codeGen/StgCmmUtils.hs | 87 +++++++++++++++++++---------------------- 2 files changed, 50 insertions(+), 47 deletions(-) diff --git a/compiler/basicTypes/Literal.hs b/compiler/basicTypes/Literal.hs index 2c71be4..8be78a2 100644 --- a/compiler/basicTypes/Literal.hs +++ b/compiler/basicTypes/Literal.hs @@ -31,6 +31,7 @@ module Literal , isZeroLit , litFitsInChar , onlyWithinBounds + , litValue -- ** Coercions , word2IntLit, int2WordLit @@ -271,6 +272,15 @@ isZeroLit (MachFloat 0) = True isZeroLit (MachDouble 0) = True isZeroLit _ = False +litValue :: Literal -> Integer +litValue (MachChar c) = toInteger $ ord c +litValue (MachInt i) = i +litValue (MachInt64 i) = i +litValue (MachWord i) = i +litValue (MachWord64 i) = i +litValue (LitInteger i _) = i +litValue l = pprPanic "litValue" (ppr l) + {- Coercions ~~~~~~~~~ diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index 7b01536..0b36868 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -87,14 +87,6 @@ cgLit (MachStr s) = newByteStringCLit (BS.unpack s) cgLit other_lit = do dflags <- getDynFlags return (mkSimpleLit dflags other_lit) -mkLtOp :: DynFlags -> Literal -> MachOp --- On signed literals we must do a signed comparison -mkLtOp dflags (MachInt _) = MO_S_Lt (wordWidth dflags) -mkLtOp _ (MachFloat _) = MO_F_Lt W32 -mkLtOp _ (MachDouble _) = MO_F_Lt W64 -mkLtOp dflags lit = MO_U_Lt (typeWidth (cmmLitType dflags (mkSimpleLit dflags lit))) - -- ToDo: seems terribly indirect! - mkSimpleLit :: DynFlags -> Literal -> CmmLit mkSimpleLit dflags (MachChar c) = CmmInt (fromIntegral (ord c)) (wordWidth dflags) mkSimpleLit dflags MachNullAddr = zeroCLit dflags @@ -472,27 +464,27 @@ emitSwitch tag_expr branches mb_deflt lo_tag hi_tag = do branches_lbls <- label_branches join_lbl branches tag_expr' <- assignTemp' tag_expr - -- Sort the branches before calling mk_switch + -- Sort the branches before calling mk_discrete_switch let branches_lbls' = [ (fromIntegral i, l) | (i,l) <- sortBy (comparing fst) branches_lbls ] - emit $ mk_switch tag_expr' branches_lbls' - mb_deflt_lbl (fromIntegral lo_tag) (fromIntegral hi_tag) + emit $ mk_discrete_switch tag_expr' branches_lbls' + mb_deflt_lbl (Just (fromIntegral lo_tag, fromIntegral hi_tag)) emitLabel join_lbl -mk_switch :: CmmExpr -> [(Integer, BlockId)] +mk_discrete_switch :: CmmExpr -> [(Integer, BlockId)] -> Maybe BlockId - -> Integer -> Integer + -> Maybe (Integer, Integer) -> CmmAGraph -- SINGLETON TAG RANGE: no case analysis to do -mk_switch _tag_expr [(tag, lbl)] _ lo_tag hi_tag +mk_discrete_switch _tag_expr [(tag, lbl)] _ (Just (lo_tag, hi_tag)) | lo_tag == hi_tag = ASSERT( tag == lo_tag ) mkBranch lbl -- SINGLETON BRANCH, NO DEFAULT: no case analysis to do -mk_switch _tag_expr [(_tag,lbl)] Nothing _ _ +mk_discrete_switch _tag_expr [(_tag,lbl)] Nothing _ = mkBranch lbl -- The simplifier might have eliminated a case -- so we may have e.g. case xs of @@ -502,8 +494,8 @@ mk_switch _tag_expr [(_tag,lbl)] Nothing _ _ -- SOMETHING MORE COMPLICATED: defer to CmmCreateSwitchPlans -- See Note [Cmm Switches, the general plan] in CmmSwitch -mk_switch tag_expr branches mb_deflt lo_tag hi_tag - = mkSwitch tag_expr $ mkSwitchTargets (Just (lo_tag, hi_tag)) mb_deflt (M.fromList branches) +mk_discrete_switch tag_expr branches mb_deflt range + = mkSwitch tag_expr $ mkSwitchTargets range mb_deflt (M.fromList branches) divideBranches :: Ord a => [(a,b)] -> ([(a,b)], a, [(a,b)]) divideBranches branches = (lo_branches, mid, hi_branches) @@ -520,20 +512,23 @@ emitCmmLitSwitch :: CmmExpr -- Tag to switch on -> [(Literal, CmmAGraphScoped)] -- Tagged branches -> CmmAGraphScoped -- Default branch (always) -> FCode () -- Emit the code --- Used for general literals, whose size might not be a word, --- where there is always a default case, and where we don't know --- the range of values for certain. For simplicity we always generate a tree. --- --- ToDo: for integers we could do better here, perhaps by generalising --- mk_switch and using that. --SDM 15/09/2004 emitCmmLitSwitch _scrut [] deflt = emit $ fst deflt emitCmmLitSwitch scrut branches deflt = do scrut' <- assignTemp' scrut join_lbl <- newLabelC deflt_lbl <- label_code join_lbl deflt branches_lbls <- label_branches join_lbl branches - emit =<< mk_lit_switch scrut' deflt_lbl noBound - (sortBy (comparing fst) branches_lbls) + + dflags <- getDynFlags + let cmm_ty = cmmExprType dflags scrut + + if isFloatType cmm_ty + then emit =<< mk_float_switch scrut' deflt_lbl noBound branches_lbls + else emit $ mk_discrete_switch -- TODO Remember signedness + scrut' + [(litValue lit,l) | (lit,l) <- branches_lbls] + (Just deflt_lbl) + Nothing emitLabel join_lbl -- | lower bound (inclusive), upper bound (exclusive) @@ -542,31 +537,25 @@ type LitBound = (Maybe Literal, Maybe Literal) noBound :: LitBound noBound = (Nothing, Nothing) -mk_lit_switch :: CmmExpr -> BlockId +mk_float_switch :: CmmExpr -> BlockId -> LitBound -> [(Literal,BlockId)] -> FCode CmmAGraph -mk_lit_switch scrut deflt bounds [(lit,blk)] - = do - dflags <- getDynFlags - let - cmm_lit = mkSimpleLit dflags lit - cmm_ty = cmmLitType dflags cmm_lit - rep = typeWidth cmm_ty - ne = if isFloatType cmm_ty then MO_F_Ne rep else MO_Ne rep - - return $ if lit `onlyWithinBounds'` bounds - then mkBranch blk - else mkCbranch (CmmMachOp ne [scrut, CmmLit cmm_lit]) deflt blk +mk_float_switch scrut deflt _bounds [(lit,blk)] + = do dflags <- getDynFlags + return $ mkCbranch (cond dflags) deflt blk where - -- If the bounds already imply scrut == lit, then we can skip the final check (#10129) - l `onlyWithinBounds'` (Just lo, Just hi) = l `onlyWithinBounds` (lo, hi) - _ `onlyWithinBounds'` _ = False - -mk_lit_switch scrut deflt_blk_id (lo_bound, hi_bound) branches + cond dflags = CmmMachOp ne [scrut, CmmLit cmm_lit] + where + cmm_lit = mkSimpleLit dflags lit + cmm_ty = cmmLitType dflags cmm_lit + rep = typeWidth cmm_ty + ne = MO_F_Ne rep + +mk_float_switch scrut deflt_blk_id (lo_bound, hi_bound) branches = do dflags <- getDynFlags - lo_blk <- mk_lit_switch scrut deflt_blk_id bounds_lo lo_branches - hi_blk <- mk_lit_switch scrut deflt_blk_id bounds_hi hi_branches + lo_blk <- mk_float_switch scrut deflt_blk_id bounds_lo lo_branches + hi_blk <- mk_float_switch scrut deflt_blk_id bounds_hi hi_branches mkCmmIfThenElse (cond dflags) lo_blk hi_blk where (lo_branches, mid_lit, hi_branches) = divideBranches branches @@ -574,8 +563,12 @@ mk_lit_switch scrut deflt_blk_id (lo_bound, hi_bound) branches bounds_lo = (lo_bound, Just mid_lit) bounds_hi = (Just mid_lit, hi_bound) - cond dflags = CmmMachOp (mkLtOp dflags mid_lit) - [scrut, CmmLit (mkSimpleLit dflags mid_lit)] + cond dflags = CmmMachOp lt [scrut, CmmLit cmm_lit] + where + cmm_lit = mkSimpleLit dflags mid_lit + cmm_ty = cmmLitType dflags cmm_lit + rep = typeWidth cmm_ty + lt = MO_F_Lt rep -------------- From git at git.haskell.org Tue Mar 10 13:40:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 13:40:31 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Detect if alternatives are signed (22e2a5e) Message-ID: <20150310134031.36DC43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/22e2a5e6b2e91c8c5de9d172454232d9ef219350/ghc >--------------------------------------------------------------- commit 22e2a5e6b2e91c8c5de9d172454232d9ef219350 Author: Joachim Breitner Date: Tue Mar 10 14:21:12 2015 +0100 CmmSwitch: Detect if alternatives are signed and use appropriate comparison operator when creating if-then-else branches. >--------------------------------------------------------------- 22e2a5e6b2e91c8c5de9d172454232d9ef219350 compiler/cmm/CmmCreateSwitchPlans.hs | 4 +++- compiler/cmm/CmmUtils.hs | 17 +++++++++++------ compiler/codeGen/StgCmmUtils.hs | 8 +++++++- 3 files changed, 21 insertions(+), 8 deletions(-) diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmCreateSwitchPlans.hs index 6016409..df935fc 100644 --- a/compiler/cmm/CmmCreateSwitchPlans.hs +++ b/compiler/cmm/CmmCreateSwitchPlans.hs @@ -64,7 +64,9 @@ implementSwitchPlan dflags signed expr = go (bid2, newBlocks2) <- go' ids2 -- TODO: Is this cast safe? - let scrut = cmmULtWord dflags expr (mkIntExpr dflags (fromIntegral i)) + let lt | signed = cmmSLtWord + | otherwise = cmmULtWord + scrut = lt dflags expr $ CmmLit $ mkWordCLit dflags i lastNode = CmmCondBranch scrut bid1 bid2 lastBlock = emptyBlock `blockJoinTail` lastNode return (lastBlock, newBlocks1++newBlocks2) diff --git a/compiler/cmm/CmmUtils.hs b/compiler/cmm/CmmUtils.hs index 65d633e..be1b1fe 100644 --- a/compiler/cmm/CmmUtils.hs +++ b/compiler/cmm/CmmUtils.hs @@ -28,9 +28,11 @@ module CmmUtils( cmmRegOffW, cmmOffsetW, cmmLabelOffW, cmmOffsetLitW, cmmOffsetExprW, cmmIndex, cmmIndexExpr, cmmLoadIndex, cmmLoadIndexW, cmmNegate, - cmmULtWord, cmmUGeWord, cmmUGtWord, cmmSubWord, - cmmNeWord, cmmEqWord, cmmOrWord, cmmAndWord, - cmmUShrWord, cmmAddWord, cmmMulWord, cmmQuotWord, + cmmULtWord, cmmUGeWord, cmmUGtWord, cmmUShrWord, + cmmSLtWord, + cmmNeWord, cmmEqWord, + cmmOrWord, cmmAndWord, + cmmSubWord, cmmAddWord, cmmMulWord, cmmQuotWord, cmmToWord, isTrivialCmmExpr, hasNoGlobalRegs, @@ -311,9 +313,11 @@ cmmLoadIndexW :: DynFlags -> CmmExpr -> Int -> CmmType -> CmmExpr cmmLoadIndexW dflags base off ty = CmmLoad (cmmOffsetW dflags base off) ty ----------------------- -cmmULtWord, cmmUGeWord, cmmUGtWord, cmmSubWord, - cmmNeWord, cmmEqWord, cmmOrWord, cmmAndWord, - cmmUShrWord, cmmAddWord, cmmMulWord, cmmQuotWord +cmmULtWord, cmmUGeWord, cmmUGtWord, cmmUShrWord, + cmmSLtWord, + cmmNeWord, cmmEqWord, + cmmOrWord, cmmAndWord, + cmmSubWord, cmmAddWord, cmmMulWord, cmmQuotWord :: DynFlags -> CmmExpr -> CmmExpr -> CmmExpr cmmOrWord dflags e1 e2 = CmmMachOp (mo_wordOr dflags) [e1, e2] cmmAndWord dflags e1 e2 = CmmMachOp (mo_wordAnd dflags) [e1, e2] @@ -323,6 +327,7 @@ cmmULtWord dflags e1 e2 = CmmMachOp (mo_wordULt dflags) [e1, e2] cmmUGeWord dflags e1 e2 = CmmMachOp (mo_wordUGe dflags) [e1, e2] cmmUGtWord dflags e1 e2 = CmmMachOp (mo_wordUGt dflags) [e1, e2] --cmmShlWord dflags e1 e2 = CmmMachOp (mo_wordShl dflags) [e1, e2] +cmmSLtWord dflags e1 e2 = CmmMachOp (mo_wordSLt dflags) [e1, e2] cmmUShrWord dflags e1 e2 = CmmMachOp (mo_wordUShr dflags) [e1, e2] cmmAddWord dflags e1 e2 = CmmMachOp (mo_wordAdd dflags) [e1, e2] cmmSubWord dflags e1 e2 = CmmMachOp (mo_wordSub dflags) [e1, e2] diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index d443879..06b3f9a 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -524,10 +524,16 @@ emitCmmLitSwitch scrut branches deflt = do dflags <- getDynFlags let cmm_ty = cmmExprType dflags scrut + -- We find the necessary type information in the literals in the branches + let signed = case head branches of + (MachInt _, _) -> True + (MachInt64 _, _) -> True + _ -> False + if isFloatType cmm_ty then emit =<< mk_float_switch scrut' deflt_lbl noBound branches_lbls else emit $ mk_discrete_switch - False -- TODO Remember signedness + signed scrut' [(litValue lit,l) | (lit,l) <- branches_lbls] (Just deflt_lbl) From git at git.haskell.org Tue Mar 10 13:56:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 13:56:44 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Use mkWordCLit (d4b8168) Message-ID: <20150310135644.619733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/d4b8168428d4e6bba9a2b6a828135beced7024eb/ghc >--------------------------------------------------------------- commit d4b8168428d4e6bba9a2b6a828135beced7024eb Author: Joachim Breitner Date: Tue Mar 10 14:56:41 2015 +0100 CmmSwitch: Use mkWordCLit >--------------------------------------------------------------- d4b8168428d4e6bba9a2b6a828135beced7024eb compiler/cmm/CmmCreateSwitchPlans.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmCreateSwitchPlans.hs index df935fc..7784fcf 100644 --- a/compiler/cmm/CmmCreateSwitchPlans.hs +++ b/compiler/cmm/CmmCreateSwitchPlans.hs @@ -63,7 +63,6 @@ implementSwitchPlan dflags signed expr = go (bid1, newBlocks1) <- go' ids1 (bid2, newBlocks2) <- go' ids2 - -- TODO: Is this cast safe? let lt | signed = cmmSLtWord | otherwise = cmmULtWord scrut = lt dflags expr $ CmmLit $ mkWordCLit dflags i @@ -74,8 +73,7 @@ implementSwitchPlan dflags signed expr = go = do (bid2, newBlocks2) <- go' ids2 - -- TODO: Is this cast safe? - let scrut = cmmNeWord dflags expr (mkIntExpr dflags (fromIntegral i)) + let scrut = cmmNeWord dflags expr $ CmmLit $ mkWordCLit dflags i lastNode = CmmCondBranch scrut bid2 l lastBlock = emptyBlock `blockJoinTail` lastNode return (lastBlock, newBlocks2) From git at git.haskell.org Tue Mar 10 14:00:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 14:00:07 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Fix compilation error in CmmParse.y, not CmmParse.hs (f6f7b4e) Message-ID: <20150310140007.04A5B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/f6f7b4ef48eacbbdaa0009118437beccc9514d99/ghc >--------------------------------------------------------------- commit f6f7b4ef48eacbbdaa0009118437beccc9514d99 Author: Joachim Breitner Date: Tue Mar 10 15:00:04 2015 +0100 Fix compilation error in CmmParse.y, not CmmParse.hs >--------------------------------------------------------------- f6f7b4ef48eacbbdaa0009118437beccc9514d99 compiler/cmm/CmmParse.y | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 8ce5c1d..adf0500 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -1329,7 +1329,7 @@ doSwitch mb_range scrut arms deflt expr <- scrut -- ToDo: check for out of range and jump to default if necessary - emit $ mkSwitch expr (mkSwitchTargets mb_range dflt_entry table) + emit $ mkSwitch expr False (mkSwitchTargets mb_range dflt_entry table) where emitArm :: ([Integer],Either BlockId (CmmParse ())) -> CmmParse [(Integer,BlockId)] emitArm (ints,Left blockid) = return [ (i,blockid) | i <- ints ] From git at git.haskell.org Tue Mar 10 14:28:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 14:28:08 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: fixup T10019 output yet again (9f19723) Message-ID: <20150310142809.017243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/9f19723668b5ef012841012406d1ea42b618fb69/ghc >--------------------------------------------------------------- commit 9f19723668b5ef012841012406d1ea42b618fb69 Author: Herbert Valerio Riedel Date: Tue Mar 10 15:25:59 2015 +0100 fixup T10019 output yet again >--------------------------------------------------------------- 9f19723668b5ef012841012406d1ea42b618fb69 testsuite/tests/th/T10019.stdout | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/th/T10019.stdout b/testsuite/tests/th/T10019.stdout index 350338c..6345930 100644 --- a/testsuite/tests/th/T10019.stdout +++ b/testsuite/tests/th/T10019.stdout @@ -1 +1 @@ -"DataConI Ghci1.Some (ForallT [KindedTV a_1627391549 StarT] [] (AppT (AppT ArrowT (VarT a_1627391549)) (AppT (ConT Ghci1.Option) (VarT a_1627391549)))) Ghci1.Option (Fixity 9 InfixL)" +"DataConI Ghci1.Some (ForallT [KindedTV a_1627391544 StarT] [] (AppT (AppT ArrowT (VarT a_1627391544)) (AppT (ConT Ghci1.Option) (VarT a_1627391544)))) Ghci1.Option (Fixity 9 InfixL)" From git at git.haskell.org Tue Mar 10 14:56:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 14:56:29 +0000 (UTC) Subject: [commit: ghc] master: Update directory submodule to latest 1.2.2 snapshot (b03479d) Message-ID: <20150310145629.0E4663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b03479dccf3eaddb56db0f48c666c946c4d0f275/ghc >--------------------------------------------------------------- commit b03479dccf3eaddb56db0f48c666c946c4d0f275 Author: Herbert Valerio Riedel Date: Tue Mar 10 15:54:40 2015 +0100 Update directory submodule to latest 1.2.2 snapshot >--------------------------------------------------------------- b03479dccf3eaddb56db0f48c666c946c4d0f275 libraries/directory | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/directory b/libraries/directory index b78c422..e04430d 160000 --- a/libraries/directory +++ b/libraries/directory @@ -1 +1 @@ -Subproject commit b78c422d9433141334d072a85f530dbacdadd1f7 +Subproject commit e04430d2e65baa28ab4fd8c0c044b5819d63006a From git at git.haskell.org Tue Mar 10 16:02:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 16:02:13 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Make the code FTP-warning-free (1ae2afb) Message-ID: <20150310160213.C3AA53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/1ae2afbc724f882db9566317ae849c8b5ef5f021/ghc >--------------------------------------------------------------- commit 1ae2afbc724f882db9566317ae849c8b5ef5f021 Author: Joachim Breitner Date: Tue Mar 10 17:01:28 2015 +0100 Make the code FTP-warning-free >--------------------------------------------------------------- 1ae2afbc724f882db9566317ae849c8b5ef5f021 compiler/cmm/CmmCreateSwitchPlans.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmCreateSwitchPlans.hs index 7784fcf..f51ef07 100644 --- a/compiler/cmm/CmmCreateSwitchPlans.hs +++ b/compiler/cmm/CmmCreateSwitchPlans.hs @@ -13,6 +13,7 @@ import CmmUtils import CmmSwitch import UniqSupply import DynFlags +import Prelude -- From git at git.haskell.org Tue Mar 10 16:23:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 16:23:05 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Set CmmTickScope correctly (971f0b5) Message-ID: <20150310162305.953C43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/971f0b58ee4b66c008355cbc1f126801162f7801/ghc >--------------------------------------------------------------- commit 971f0b58ee4b66c008355cbc1f126801162f7801 Author: Joachim Breitner Date: Tue Mar 10 17:07:27 2015 +0100 Set CmmTickScope correctly >--------------------------------------------------------------- 971f0b58ee4b66c008355cbc1f126801162f7801 compiler/cmm/CmmCreateSwitchPlans.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmCreateSwitchPlans.hs index f51ef07..d89a0f4 100644 --- a/compiler/cmm/CmmCreateSwitchPlans.hs +++ b/compiler/cmm/CmmCreateSwitchPlans.hs @@ -37,13 +37,13 @@ cmmCreateSwitchPlans dflags g = do visitSwitches :: DynFlags -> CmmBlock -> UniqSM [CmmBlock] visitSwitches dflags block - | (CmmEntry l s, middle, CmmSwitch expr signed ids) <- blockSplit block + | (entry@(CmmEntry l scope), middle, CmmSwitch expr signed ids) <- blockSplit block = do let plan = createSwitchPlan ids - (newTail, newBlocks) <- implementSwitchPlan dflags signed expr plan + (newTail, newBlocks) <- implementSwitchPlan dflags signed scope expr plan - let block' = CmmEntry l s `blockJoinHead` middle `blockAppend` newTail + let block' = entry `blockJoinHead` middle `blockAppend` newTail return $ block' : newBlocks @@ -52,8 +52,8 @@ visitSwitches dflags block -- Implementing a switch plan (returning a tail block) -implementSwitchPlan :: DynFlags -> Bool -> CmmExpr -> SwitchPlan -> UniqSM (Block CmmNode O C, [CmmBlock]) -implementSwitchPlan dflags signed expr = go +implementSwitchPlan :: DynFlags -> Bool -> CmmTickScope -> CmmExpr -> SwitchPlan -> UniqSM (Block CmmNode O C, [CmmBlock]) +implementSwitchPlan dflags signed scope expr = go where go (Unconditionally l) = return (emptyBlock `blockJoinTail` CmmBranch l, []) @@ -86,7 +86,7 @@ implementSwitchPlan dflags signed expr = go = do bid <- mkBlockId <$> getUniqueM (last, newBlocks) <- go p - let block = CmmEntry bid GlobalScope `blockJoinHead` last + let block = CmmEntry bid scope `blockJoinHead` last return (bid, block: newBlocks) From git at git.haskell.org Tue Mar 10 16:23:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 16:23:08 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Put the "signed" flag into SwitchTargets, which is abstract (d0f0b72) Message-ID: <20150310162308.903A93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/d0f0b72f7c9e86736573b321cab86cd2e7ceb3e0/ghc >--------------------------------------------------------------- commit d0f0b72f7c9e86736573b321cab86cd2e7ceb3e0 Author: Joachim Breitner Date: Tue Mar 10 17:22:09 2015 +0100 Put the "signed" flag into SwitchTargets, which is abstract So less code needs to be touched. Partly reverts "CmmSwitch: Remember if we have are dealing with signed values or not" (ea6291ef4e109f56803b772bc32de2f2ab98e7cc) >--------------------------------------------------------------- d0f0b72f7c9e86736573b321cab86cd2e7ceb3e0 compiler/cmm/CmmCommonBlockElim.hs | 6 +-- compiler/cmm/CmmContFlowOpt.hs | 2 +- compiler/cmm/CmmCreateSwitchPlans.hs | 14 +++--- compiler/cmm/CmmLint.hs | 2 +- compiler/cmm/CmmNode.hs | 15 +++---- compiler/cmm/CmmParse.y | 2 +- compiler/cmm/CmmProcPoint.hs | 4 +- compiler/cmm/CmmSwitch.hs | 76 ++++++++++++++++++--------------- compiler/cmm/MkGraph.hs | 6 +-- compiler/cmm/PprC.hs | 4 +- compiler/cmm/PprCmm.hs | 2 +- compiler/codeGen/StgCmmUtils.hs | 4 +- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 2 +- compiler/nativeGen/AsmCodeGen.hs | 4 +- compiler/nativeGen/PPC/CodeGen.hs | 4 +- compiler/nativeGen/SPARC/CodeGen.hs | 4 +- compiler/nativeGen/X86/CodeGen.hs | 4 +- 17 files changed, 80 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 d0f0b72f7c9e86736573b321cab86cd2e7ceb3e0 From git at git.haskell.org Tue Mar 10 18:22:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 18:22:59 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Rename `SysTools.readCreateProcess`. (4be3722) Message-ID: <20150310182259.48D033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/4be3722325d9c684ef3113b54adac17a46512cff/ghc >--------------------------------------------------------------- commit 4be3722325d9c684ef3113b54adac17a46512cff Author: Thomas Miedema Date: Sun Mar 8 15:39:16 2015 +0100 Rename `SysTools.readCreateProcess`. Functions `readCreateProcess` and `readCreateProcessWithExitCode` were added to `System.Process`, the former of which conflicts with `SysTools.readCreateProcess`. (cherry picked from commit 8b7534b39052c9cb44411bea0ca311a751564d6c) >--------------------------------------------------------------- 4be3722325d9c684ef3113b54adac17a46512cff compiler/main/SysTools.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs index af80051..bef8d0c 100644 --- a/compiler/main/SysTools.hs +++ b/compiler/main/SysTools.hs @@ -467,13 +467,14 @@ askCc dflags args = do args2 = args0 ++ args1 ++ args mb_env <- getGccEnv args2 runSomethingWith dflags "gcc" p args2 $ \real_args -> - readCreateProcess (proc p real_args){ env = mb_env } + readCreateProcessWithExitCode' (proc p real_args){ env = mb_env } --- Version of System.Process.readProcessWithExitCode that takes an environment -readCreateProcess +-- Similar to System.Process.readCreateProcessWithExitCode, but stderr is +-- inherited from the parent process, and output to stderr is not captured. +readCreateProcessWithExitCode' :: CreateProcess -> IO (ExitCode, String) -- ^ stdout -readCreateProcess proc = do +readCreateProcessWithExitCode' proc = do (_, Just outh, _, pid) <- createProcess proc{ std_out = CreatePipe } From git at git.haskell.org Tue Mar 10 18:23:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 18:23:02 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update directory submodule to latest 1.2.2 snapshot (0259b5f) Message-ID: <20150310182302.30F4B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/0259b5f685b08d9516b7b1b9549a036a730ddf8a/ghc >--------------------------------------------------------------- commit 0259b5f685b08d9516b7b1b9549a036a730ddf8a Author: Herbert Valerio Riedel Date: Tue Mar 10 15:54:40 2015 +0100 Update directory submodule to latest 1.2.2 snapshot (cherry picked from commit b03479dccf3eaddb56db0f48c666c946c4d0f275) >--------------------------------------------------------------- 0259b5f685b08d9516b7b1b9549a036a730ddf8a libraries/directory | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/directory b/libraries/directory index b78c422..e04430d 160000 --- a/libraries/directory +++ b/libraries/directory @@ -1 +1 @@ -Subproject commit b78c422d9433141334d072a85f530dbacdadd1f7 +Subproject commit e04430d2e65baa28ab4fd8c0c044b5819d63006a From git at git.haskell.org Tue Mar 10 21:32:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 21:32:18 +0000 (UTC) Subject: [commit: ghc] master: Documentation for PackageArg/ModRenaming/PackageFlag (8a91079) Message-ID: <20150310213218.AEA943A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8a91079b5895c1505717b5d401617269720ad8ab/ghc >--------------------------------------------------------------- commit 8a91079b5895c1505717b5d401617269720ad8ab Author: Edward Z. Yang Date: Mon Mar 9 13:52:40 2015 -0700 Documentation for PackageArg/ModRenaming/PackageFlag Summary: [skip-ci] Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D723 >--------------------------------------------------------------- 8a91079b5895c1505717b5d401617269720ad8ab compiler/main/DynFlags.hs | 42 +++++++++++++++++++++++++++++++----------- 1 file changed, 31 insertions(+), 11 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 74e0ce6..aa6b7f9 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -1104,20 +1104,40 @@ isNoLink :: GhcLink -> Bool isNoLink NoLink = True isNoLink _ = False -data PackageArg = PackageArg String - | PackageIdArg String - | PackageKeyArg String +-- | We accept flags which make packages visible, but how they select +-- the package varies; this data type reflects what selection criterion +-- is used. +data PackageArg = + PackageArg String -- ^ @-package@, by 'PackageName' + | PackageIdArg String -- ^ @-package-id@, by 'SourcePackageId' + | PackageKeyArg String -- ^ @-package-key@, by 'InstalledPackageId' deriving (Eq, Show) -data ModRenaming = ModRenaming Bool [(ModuleName, ModuleName)] - deriving (Eq) - +-- | Represents the renaming that may be associated with an exposed +-- package, e.g. the @rns@ part of @-package "foo (rns)"@. +-- +-- Here are some example parsings of the package flags (where +-- a string literal is punned to be a 'ModuleName': +-- +-- * @-package foo@ is @ModRenaming True []@ +-- * @-package foo ()@ is @ModRenaming False []@ +-- * @-package foo (A)@ is @ModRenaming False [("A", "A")]@ +-- * @-package foo (A as B)@ is @ModRenaming False [("A", "B")]@ +-- * @-package foo with (A as B)@ is @ModRenaming True [("A", "B")]@ +data ModRenaming = ModRenaming { + modRenamingWithImplicit :: Bool, -- ^ Bring all exposed modules into scope? + modRenamings :: [(ModuleName, ModuleName)] -- ^ Bring module @m@ into scope + -- under name @n at . + } deriving (Eq) + +-- | Flags for manipulating packages. data PackageFlag - = ExposePackage PackageArg ModRenaming - | HidePackage String - | IgnorePackage String - | TrustPackage String - | DistrustPackage String + = ExposePackage PackageArg ModRenaming -- ^ @-package@, @-package-id@ + -- and @-package-key@ + | HidePackage String -- ^ @-hide-package@ + | IgnorePackage String -- ^ @-ignore-package@ + | TrustPackage String -- ^ @-trust-package@ + | DistrustPackage String -- ^ @-distrust-package@ deriving (Eq) defaultHscTarget :: Platform -> HscTarget From git at git.haskell.org Tue Mar 10 21:50:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 21:50:20 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Make it validate-clean (0e65b8f) Message-ID: <20150310215020.444843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/0e65b8f399d1c7f27cdb2891add8f8fa31c82787/ghc >--------------------------------------------------------------- commit 0e65b8f399d1c7f27cdb2891add8f8fa31c82787 Author: Joachim Breitner Date: Tue Mar 10 22:50:02 2015 +0100 Make it validate-clean >--------------------------------------------------------------- 0e65b8f399d1c7f27cdb2891add8f8fa31c82787 compiler/cmm/CmmCreateSwitchPlans.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmCreateSwitchPlans.hs index 836de40..9b0f589 100644 --- a/compiler/cmm/CmmCreateSwitchPlans.hs +++ b/compiler/cmm/CmmCreateSwitchPlans.hs @@ -37,7 +37,7 @@ cmmCreateSwitchPlans dflags g = do visitSwitches :: DynFlags -> CmmBlock -> UniqSM [CmmBlock] visitSwitches dflags block - | (entry@(CmmEntry l scope), middle, CmmSwitch expr ids) <- blockSplit block + | (entry@(CmmEntry _ scope), middle, CmmSwitch expr ids) <- blockSplit block = do let plan = createSwitchPlan ids From git at git.haskell.org Tue Mar 10 22:20:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 22:20:59 +0000 (UTC) Subject: [commit: ghc] master: Refactor testsuite with normalise_version() (8cbd7f5) Message-ID: <20150310222059.4D3453A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8cbd7f5d97cdc0f4cd6b8baaa999f990533dc801/ghc >--------------------------------------------------------------- commit 8cbd7f5d97cdc0f4cd6b8baaa999f990533dc801 Author: Edward Z. Yang Date: Tue Mar 10 14:10:26 2015 -0700 Refactor testsuite with normalise_version() Summary: This function generalizes the normaliseBytestringPackage and other similar one-off functions into normalise_version() with takes a package name to normalize against. This JUST manages package versions; we also could use a normalize for keys. In the process, I modified all the normalization functions to be accumulative; I don't think this makes a difference for current test cases but I think it makes things nicer. Signed-off-by: Edward Z. Yang Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D725 >--------------------------------------------------------------- 8cbd7f5d97cdc0f4cd6b8baaa999f990533dc801 testsuite/driver/testlib.py | 20 ++++++++++++++++---- testsuite/tests/package/all.T | 9 +++------ testsuite/tests/safeHaskell/check/all.T | 5 +---- testsuite/tests/safeHaskell/check/pkg01/all.T | 21 +++++---------------- testsuite/tests/safeHaskell/ghci/all.T | 15 ++++----------- testsuite/tests/th/all.T | 4 +++- 6 files changed, 32 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 8cbd7f5d97cdc0f4cd6b8baaa999f990533dc801 From git at git.haskell.org Tue Mar 10 22:51:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Mar 2015 22:51:21 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Avoid Data.Functor (ca3b167) Message-ID: <20150310225121.9FF363A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/ca3b167807cf2dfc63aed024431336a77e3b6869/ghc >--------------------------------------------------------------- commit ca3b167807cf2dfc63aed024431336a77e3b6869 Author: Joachim Breitner Date: Tue Mar 10 23:50:56 2015 +0100 Avoid Data.Functor as I did not manage to make it compile with -Wall >--------------------------------------------------------------- ca3b167807cf2dfc63aed024431336a77e3b6869 compiler/cmm/CmmCreateSwitchPlans.hs | 8 ++------ 1 file changed, 2 insertions(+), 6 deletions(-) diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmCreateSwitchPlans.hs index 9b0f589..089839d 100644 --- a/compiler/cmm/CmmCreateSwitchPlans.hs +++ b/compiler/cmm/CmmCreateSwitchPlans.hs @@ -4,8 +4,6 @@ module CmmCreateSwitchPlans ) where -import Data.Functor ((<$>)) - import Hoopl import BlockId import Cmm @@ -13,8 +11,6 @@ import CmmUtils import CmmSwitch import UniqSupply import DynFlags -import Prelude - -- -- This module replaces Switch statements as generated by the Stg -> Cmm @@ -32,7 +28,7 @@ import Prelude cmmCreateSwitchPlans :: DynFlags -> CmmGraph -> UniqSM CmmGraph cmmCreateSwitchPlans dflags g = do - blocks' <- concat <$> mapM (visitSwitches dflags) (toBlockList g) + blocks' <- concat `fmap` mapM (visitSwitches dflags) (toBlockList g) return $ ofBlockList (g_entry g) blocks' visitSwitches :: DynFlags -> CmmBlock -> UniqSM [CmmBlock] @@ -84,7 +80,7 @@ implementSwitchPlan dflags scope expr = go = return (l, []) go' p = do - bid <- mkBlockId <$> getUniqueM + bid <- mkBlockId `fmap` getUniqueM (last, newBlocks) <- go p let block = CmmEntry bid scope `blockJoinHead` last return (bid, block: newBlocks) From git at git.haskell.org Wed Mar 11 08:45:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 08:45:58 +0000 (UTC) Subject: [commit: hsc2hs] master: Allow new filepath-1.4 (c16032d) Message-ID: <20150311084558.473033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hsc2hs On branch : master Link : http://git.haskell.org/hsc2hs.git/commitdiff/c16032d83c8ce7ac3e11b99f8e80bfdfc77f0d1f >--------------------------------------------------------------- commit c16032d83c8ce7ac3e11b99f8e80bfdfc77f0d1f Author: Herbert Valerio Riedel Date: Wed Mar 11 09:45:00 2015 +0100 Allow new filepath-1.4 See haskell/filepath at d039d5ae7c070452a443219fdb7df65508567338 >--------------------------------------------------------------- c16032d83c8ce7ac3e11b99f8e80bfdfc77f0d1f hsc2hs.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hsc2hs.cabal b/hsc2hs.cabal index 6dfa7c4..0d5e3b2 100644 --- a/hsc2hs.cabal +++ b/hsc2hs.cabal @@ -39,6 +39,6 @@ Executable hsc2hs Build-Depends: base >= 4 && < 5, containers >= 0.2 && < 0.6, directory >= 1 && < 1.3, - filepath >= 1 && < 1.4, + filepath >= 1 && < 1.5, process >= 1 && < 1.3 From git at git.haskell.org Wed Mar 11 13:19:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 13:19:55 +0000 (UTC) Subject: [commit: packages/haskeline] master: Allow new filepath-1.4 (6d046de) Message-ID: <20150311131955.24D093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/6d046de06d9f2ee550b697dfcfdafd6547c57501 >--------------------------------------------------------------- commit 6d046de06d9f2ee550b697dfcfdafd6547c57501 Author: Herbert Valerio Riedel Date: Wed Mar 11 09:19:25 2015 +0100 Allow new filepath-1.4 See haskell/filepath at d039d5ae7c070452a443219fdb7df65508567338 >--------------------------------------------------------------- 6d046de06d9f2ee550b697dfcfdafd6547c57501 haskeline.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/haskeline.cabal b/haskeline.cabal index d1fe65a..c37129c 100644 --- a/haskeline.cabal +++ b/haskeline.cabal @@ -52,7 +52,7 @@ flag legacy-encoding Library Build-depends: base >=4.3 && < 4.9, containers>=0.4 && < 0.6, directory>=1.1 && < 1.3, bytestring>=0.9 && < 0.11, - filepath >= 1.2 && < 1.4, transformers >= 0.2 && < 0.5 + filepath >= 1.2 && < 1.5, transformers >= 0.2 && < 0.5 Default-Language: Haskell98 Default-Extensions: ForeignFunctionInterface, Rank2Types, FlexibleInstances, From git at git.haskell.org Wed Mar 11 13:19:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 13:19:57 +0000 (UTC) Subject: [commit: packages/haskeline] master: Merge pull request #19 from hvr/pr-filepath-1.4 (06679b7) Message-ID: <20150311131957.2AF123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/06679b723fc07ca805d0dc6b328a5762255e93ee >--------------------------------------------------------------- commit 06679b723fc07ca805d0dc6b328a5762255e93ee Merge: 87a01d2 6d046de Author: Judah Jacobson Date: Wed Mar 11 06:07:00 2015 -0700 Merge pull request #19 from hvr/pr-filepath-1.4 Allow new filepath-1.4 for GHC 7.10.1RC3 >--------------------------------------------------------------- 06679b723fc07ca805d0dc6b328a5762255e93ee haskeline.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Wed Mar 11 14:18:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 14:18:21 +0000 (UTC) Subject: [commit: ghc] master: Update Cabal submodule to latest 1.22 snapshot (838d804) Message-ID: <20150311141821.8FA633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/838d8044896b6544d8c80c2ab5de63d97220f06c/ghc >--------------------------------------------------------------- commit 838d8044896b6544d8c80c2ab5de63d97220f06c Author: Edward Z. Yang Date: Wed Mar 11 14:53:17 2015 +0100 Update Cabal submodule to latest 1.22 snapshot This changes the library file name format NOTE: This patch originally updated to Cabal HEAD, but was reduced to update to Cabal 1.22 HEAD by hvr as this is needed in order to update the filepath submodule to version 1.4.0, and subsequently to be cherry-picked into the ghc-7.10 branch Signed-off-by: Edward Z. Yang Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D707 >--------------------------------------------------------------- 838d8044896b6544d8c80c2ab5de63d97220f06c compiler/ghc.mk | 1 + libraries/Cabal | 2 +- rules/build-package-way.mk | 6 +++--- utils/ghc-cabal/Main.hs | 3 +++ 4 files changed, 8 insertions(+), 4 deletions(-) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index 07f5ec5..b692891 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -445,6 +445,7 @@ compiler_stage1_MUNGED_VERSION = $(subst .$(ProjectPatchLevel),,$(ProjectVersion define compiler_PACKAGE_MAGIC compiler_stage1_VERSION = $(compiler_stage1_MUNGED_VERSION) compiler_stage1_PACKAGE_KEY = $(subst .$(ProjectPatchLevel),,$(compiler_stage1_PACKAGE_KEY)) +compiler_stage1_LIB_NAME = $(subst .$(ProjectPatchLevel),,$(compiler_stage1_LIB_NAME)) endef # NB: the PACKAGE_KEY munging has no effect for new-style package keys diff --git a/libraries/Cabal b/libraries/Cabal index a8dfc6f..a9958fe 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit a8dfc6f4cb9cd280299385a50fefc0a4f8103ef1 +Subproject commit a9958fefc737b223b75babc68ecd3122b9697cd9 diff --git a/rules/build-package-way.mk b/rules/build-package-way.mk index 3efe501..27da099 100644 --- a/rules/build-package-way.mk +++ b/rules/build-package-way.mk @@ -23,13 +23,13 @@ $(call hs-objs,$1,$2,$3) # The .a/.so library file, indexed by two different sets of vars: # the first is indexed by the dir, distdir and way # the second is indexed by the package id, distdir and way -$1_$2_$3_LIB_NAME = libHS$$($1_$2_PACKAGE_KEY)$$($3_libsuf) +$1_$2_$3_LIB_NAME = libHS$$($1_$2_LIB_NAME)$$($3_libsuf) $1_$2_$3_LIB = $1/$2/build/$$($1_$2_$3_LIB_NAME) $$($1_$2_PACKAGE_KEY)_$2_$3_LIB = $$($1_$2_$3_LIB) ifeq "$$(HostOS_CPP)" "mingw32" ifneq "$$($1_$2_dll0_HS_OBJS)" "" -$1_$2_$3_LIB0_ROOT = HS$$($1_$2_PACKAGE_KEY)-0$$($3_libsuf) +$1_$2_$3_LIB0_ROOT = HS$$($1_$2_LIB_NAME)-0$$($3_libsuf) $1_$2_$3_LIB0_NAME = lib$$($1_$2_$3_LIB0_ROOT) $1_$2_$3_LIB0 = $1/$2/build/$$($1_$2_$3_LIB0_NAME) endif @@ -136,7 +136,7 @@ ifeq "$$(DYNAMIC_GHC_PROGRAMS)" "YES" $1_$2_GHCI_LIB = $$($1_$2_dyn_LIB) else ifeq "$3" "v" -$1_$2_GHCI_LIB = $1/$2/build/HS$$($1_$2_PACKAGE_KEY).$$($3_osuf) +$1_$2_GHCI_LIB = $1/$2/build/HS$$($1_$2_LIB_NAME).$$($3_osuf) ifeq "$$($1_$2_BUILD_GHCI_LIB)" "YES" # Don't put bootstrapping packages in the bindist ifneq "$4" "0" diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index 6724f3a..47968a1 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -6,6 +6,7 @@ import Distribution.PackageDescription import Distribution.PackageDescription.Check hiding (doesFileExist) import Distribution.PackageDescription.Configuration import Distribution.PackageDescription.Parse +import Distribution.Package import Distribution.System import Distribution.Simple import Distribution.Simple.Configure @@ -438,6 +439,8 @@ generate directory distdir dll0Modules config_args allMods = mods ++ otherMods let xs = [variablePrefix ++ "_VERSION = " ++ display (pkgVersion (package pd)), variablePrefix ++ "_PACKAGE_KEY = " ++ display (pkgKey lbi), + -- copied from mkComponentsLocalBuildInfo + variablePrefix ++ "_LIB_NAME = " ++ packageKeyLibraryName (package pd) (pkgKey lbi), variablePrefix ++ "_MODULES = " ++ unwords mods, variablePrefix ++ "_HIDDEN_MODULES = " ++ unwords otherMods, variablePrefix ++ "_SYNOPSIS =" ++ synopsis pd, From git at git.haskell.org Wed Mar 11 14:44:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 14:44:49 +0000 (UTC) Subject: [commit: ghc] master: Update filepath submodule to filepath-1.4 snapshot (5f356f3) Message-ID: <20150311144449.DCA283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5f356f3e412ae4a808b2a72c10609eaacfb1ce3a/ghc >--------------------------------------------------------------- commit 5f356f3e412ae4a808b2a72c10609eaacfb1ce3a Author: Herbert Valerio Riedel Date: Wed Mar 11 14:20:51 2015 +0100 Update filepath submodule to filepath-1.4 snapshot This also needs to update a couple of other submodules to update the upper bound on filepath to allow this major version bump to 1.4.0.0 >--------------------------------------------------------------- 5f356f3e412ae4a808b2a72c10609eaacfb1ce3a compiler/ghc.cabal.in | 2 +- ghc/ghc-bin.cabal.in | 2 +- libraries/directory | 2 +- libraries/filepath | 2 +- libraries/haskeline | 2 +- libraries/process | 2 +- utils/ghc-cabal/ghc-cabal.cabal | 2 +- utils/hsc2hs | 2 +- 8 files changed, 8 insertions(+), 8 deletions(-) diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index a6624ff..684ee6b 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -51,7 +51,7 @@ Library time < 1.6, containers >= 0.5 && < 0.6, array >= 0.1 && < 0.6, - filepath >= 1 && < 1.4, + filepath >= 1 && < 1.5, hpc, transformers, bin-package-db, diff --git a/ghc/ghc-bin.cabal.in b/ghc/ghc-bin.cabal.in index dcbc695..b4fdf10 100644 --- a/ghc/ghc-bin.cabal.in +++ b/ghc/ghc-bin.cabal.in @@ -32,7 +32,7 @@ Executable ghc bytestring >= 0.9 && < 0.11, directory >= 1 && < 1.3, process >= 1 && < 1.3, - filepath >= 1 && < 1.4, + filepath >= 1 && < 1.5, ghc if os(windows) Build-Depends: Win32 diff --git a/libraries/directory b/libraries/directory index e04430d..7233248 160000 --- a/libraries/directory +++ b/libraries/directory @@ -1 +1 @@ -Subproject commit e04430d2e65baa28ab4fd8c0c044b5819d63006a +Subproject commit 7233248952648ed4dd213f91ed52af2317a3f23b diff --git a/libraries/filepath b/libraries/filepath index c1a3aec..4206435 160000 --- a/libraries/filepath +++ b/libraries/filepath @@ -1 +1 @@ -Subproject commit c1a3aec04cb93315dbc9725139c54d71e5134426 +Subproject commit 4206435bda0929d7a65fc42e5c8629212328120c diff --git a/libraries/haskeline b/libraries/haskeline index 87a01d2..06679b7 160000 --- a/libraries/haskeline +++ b/libraries/haskeline @@ -1 +1 @@ -Subproject commit 87a01d222ef13f89a68204602e3fe9273eeed3ca +Subproject commit 06679b723fc07ca805d0dc6b328a5762255e93ee diff --git a/libraries/process b/libraries/process index ae10a33..c8cdaef 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit ae10a33cd16d9ac9238a193e5355c5c2e05ef0a2 +Subproject commit c8cdaef5585717089a53be61cb6f08b3120f18b4 diff --git a/utils/ghc-cabal/ghc-cabal.cabal b/utils/ghc-cabal/ghc-cabal.cabal index f963c7c..5827333 100644 --- a/utils/ghc-cabal/ghc-cabal.cabal +++ b/utils/ghc-cabal/ghc-cabal.cabal @@ -19,5 +19,5 @@ Executable ghc-cabal bytestring >= 0.10 && < 0.11, Cabal >= 1.22 && < 1.24, directory >= 1.1 && < 1.3, - filepath >= 1.2 && < 1.4 + filepath >= 1.2 && < 1.5 diff --git a/utils/hsc2hs b/utils/hsc2hs index e32b4fa..c16032d 160000 --- a/utils/hsc2hs +++ b/utils/hsc2hs @@ -1 +1 @@ -Subproject commit e32b4faf97833f92708a8f3f8bbb015f5d1dbcc7 +Subproject commit c16032d83c8ce7ac3e11b99f8e80bfdfc77f0d1f From git at git.haskell.org Wed Mar 11 15:36:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 15:36:30 +0000 (UTC) Subject: [commit: ghc] master: Rename ty{Con, peRep}Hash to ty{Con, peRep}Fingerprint (842028b) Message-ID: <20150311153630.B61453A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/842028b4a624e639dc9ee9a4f92fc208c8206e3f/ghc >--------------------------------------------------------------- commit 842028b4a624e639dc9ee9a4f92fc208c8206e3f Author: Herbert Valerio Riedel Date: Wed Mar 11 16:36:09 2015 +0100 Rename ty{Con,peRep}Hash to ty{Con,peRep}Fingerprint This is a follow-up change to 56e0ac98c3a439b8757a2e886db259270bdc85f0 See also discussion at https://groups.google.com/d/msg/haskell-core-libraries/e9N3U6nJeQE/V-TvG3G-3x4J Reviewed By: simonpj Differential Revision: https://phabricator.haskell.org/D726 >--------------------------------------------------------------- 842028b4a624e639dc9ee9a4f92fc208c8206e3f libraries/base/Data/Typeable.hs | 4 ++-- libraries/base/Data/Typeable/Internal.hs | 10 +++++----- libraries/base/changelog.md | 4 ++-- 3 files changed, 9 insertions(+), 9 deletions(-) diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs index 7e501a5..c30a43d 100644 --- a/libraries/base/Data/Typeable.hs +++ b/libraries/base/Data/Typeable.hs @@ -61,12 +61,12 @@ module Data.Typeable -- * Type representations TypeRep, -- abstract, instance of: Eq, Show, Typeable - typeRepHash, + typeRepFingerprint, rnfTypeRep, showsTypeRep, TyCon, -- abstract, instance of: Eq, Show, Typeable - tyConHash, + tyConFingerprint, tyConString, tyConPackage, tyConModule, diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 9285904..4772473 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -44,7 +44,7 @@ module Data.Typeable.Internal ( splitPolyTyConApp, funResultTy, typeRepArgs, - typeRepHash, + typeRepFingerprint, rnfTypeRep, showsTypeRep, tyConString, @@ -83,7 +83,7 @@ instance Ord TypeRep where -- | An abstract representation of a type constructor. 'TyCon' objects can -- be built using 'mkTyCon'. data TyCon = TyCon { - tyConHash :: {-# UNPACK #-} !Fingerprint, -- ^ @since 4.8.0.0 + tyConFingerprint :: {-# UNPACK #-} !Fingerprint, -- ^ @since 4.8.0.0 tyConPackage :: String, -- ^ @since 4.5.0.0 tyConModule :: String, -- ^ @since 4.5.0.0 tyConName :: String -- ^ @since 4.5.0.0 @@ -196,8 +196,8 @@ tyConString = tyConName -- | Observe the 'Fingerprint' of a type representation -- -- @since 4.8.0.0 -typeRepHash :: TypeRep -> Fingerprint -typeRepHash (TypeRep fpr _ _ _) = fpr +typeRepFingerprint :: TypeRep -> Fingerprint +typeRepFingerprint (TypeRep fpr _ _ _) = fpr ------------------------------------------------------------- -- @@ -337,7 +337,7 @@ typeLitTypeRep nm = rep where rep = mkTyConApp tc [] tc = TyCon - { tyConHash = fingerprintString (mk pack modu nm) + { tyConFingerprint = fingerprintString (mk pack modu nm) , tyConPackage = pack , tyConModule = modu , tyConName = nm diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index e99c1b1..e2318a8 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -142,8 +142,8 @@ * Restore invariant in `Data (Ratio a)` instance (#10011) - * Add/expose `rnfTypeRep`, `rnfTyCon`, `TypeRepHash`, and - `TyConHash` helpers to `Data.Typeable`. + * Add/expose `rnfTypeRep`, `rnfTyCon`, `typeRepFingerprint`, and + `tyConFingerprint` helpers to `Data.Typeable`. * Define proper `MINIMAL` pragma for `class Ix`. (#10142) From git at git.haskell.org Wed Mar 11 16:35:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 16:35:07 +0000 (UTC) Subject: [commit: packages/hpc] wip/T9619: Use System.FilePath functions instead of (++) (3e45180) Message-ID: <20150311163507.114A43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/T9619 Link : http://git.haskell.org/packages/hpc.git/commitdiff/3e451809444c163c3caecccb3854d8745932ca93 >--------------------------------------------------------------- commit 3e451809444c163c3caecccb3854d8745932ca93 Author: Thomas Miedema Date: Thu Mar 5 21:36:07 2015 +0100 Use System.FilePath functions instead of (++) >--------------------------------------------------------------- 3e451809444c163c3caecccb3854d8745932ca93 Trace/Hpc/Mix.hs | 4 +++- Trace/Hpc/Tix.hs | 19 ++++++++----------- hpc.cabal | 1 + 3 files changed, 12 insertions(+), 12 deletions(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index 28050ad..4a7fc74 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -27,6 +27,8 @@ import Data.Time (UTCTime) import Data.Tree import Data.Char +import System.FilePath + -- a module index records the attributes of each tick-box that has -- been introduced in that module, accessed by tick-number position -- in the list @@ -107,7 +109,7 @@ readMix dirNames mod' = do _ -> error $ "can not find " ++ modName ++ " in " ++ show dirNames mixName :: FilePath -> String -> String -mixName dirName name = dirName ++ "/" ++ name ++ ".mix" +mixName dirName name = dirName name <.> "mix" ------------------------------------------------------------------------------ diff --git a/Trace/Hpc/Tix.hs b/Trace/Hpc/Tix.hs index 2b03e0a..fa95dbf 100644 --- a/Trace/Hpc/Tix.hs +++ b/Trace/Hpc/Tix.hs @@ -1,6 +1,10 @@ {-# LANGUAGE CPP #-} -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 704 {-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 702 +-- System.FilePath in filepath version 1.2.0.1 isn't marked or implied Safe, +-- as shipped with GHC 7.2. +{-# LANGUAGE Trustworthy #-} #endif ------------------------------------------------------------ -- Andy Gill and Colin Runciman, June 2006 @@ -12,7 +16,8 @@ module Trace.Hpc.Tix(Tix(..), TixModule(..), tixModuleName, tixModuleHash, tixModuleTixs, readTix, writeTix, getTixFileName) where -import Data.List (isSuffixOf) +import System.FilePath (replaceExtension) + import Trace.Hpc.Util (Hash, catchIO) -- | 'Tix' is the storage format for our dynamic information about @@ -52,15 +57,7 @@ writeTix :: String writeTix name tix = writeFile name (show tix) -{- -tixName :: String -> String -tixName name = name ++ ".tix" --} - -- | 'getTixFullName' takes a binary or @.tix at -file name, -- and normalizes it into a @.tix at -file name. getTixFileName :: String -> String -getTixFileName str | ".tix" `isSuffixOf` str - = str - | otherwise - = str ++ ".tix" +getTixFileName str = replaceExtension str "tix" diff --git a/hpc.cabal b/hpc.cabal index 857faba..4e5b6f0 100644 --- a/hpc.cabal +++ b/hpc.cabal @@ -38,5 +38,6 @@ Library base >= 4.4.1 && < 4.9, containers >= 0.4.1 && < 0.6, directory >= 1.1 && < 1.3, + filepath >= 1 && < 1.5, time >= 1.2 && < 1.6 ghc-options: -Wall From git at git.haskell.org Wed Mar 11 16:35:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 16:35:09 +0000 (UTC) Subject: [commit: packages/hpc] wip/T9619: Allow same `Mix` file in different dirs (#9619) (f601495) Message-ID: <20150311163509.184EE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/T9619 Link : http://git.haskell.org/packages/hpc.git/commitdiff/f601495ac5f93f24cbcaa95f45b1bc26ad644ac9 >--------------------------------------------------------------- commit f601495ac5f93f24cbcaa95f45b1bc26ad644ac9 Author: Thomas Miedema Date: Thu Mar 5 21:43:36 2015 +0100 Allow same `Mix` file in different dirs (#9619) >--------------------------------------------------------------- f601495ac5f93f24cbcaa95f45b1bc26ad644ac9 Trace/Hpc/Mix.hs | 12 ++++++++---- tests/simple/tixs/{.hpc => .hpc.copy}/Main.mix | 0 tests/simple/tixs/test.T | 4 ++++ 3 files changed, 12 insertions(+), 4 deletions(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index 4a7fc74..f4025d9 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -49,7 +49,7 @@ data Mix = Mix Hash -- hash of mix entry + timestamp Int -- tab stop value. [MixEntry] -- entries - deriving (Show,Read) + deriving (Show,Read,Eq) type MixEntry = (HpcPos, BoxLabel) @@ -104,9 +104,13 @@ readMix dirNames mod' = do | dirName <- dirNames ] case catMaybes res of - [r] -> return r - xs@(_:_) -> error $ "found " ++ show(length xs) ++ " instances of " ++ modName ++ " in " ++ show dirNames - _ -> error $ "can not find " ++ modName ++ " in " ++ show dirNames + xs@(x:_:_) | any (/= x) (tail xs) -> + -- Only complain if multiple *different* `Mix` files with the + -- same name are found (#9619). + error $ "found " ++ show(length xs) ++ " different instances of " + ++ modName ++ " in " ++ show dirNames + (x:_) -> return x + _ -> error $ "can not find " ++ modName ++ " in " ++ show dirNames mixName :: FilePath -> String -> String mixName dirName name = dirName name <.> "mix" diff --git a/tests/simple/tixs/.hpc/Main.mix b/tests/simple/tixs/.hpc.copy/Main.mix similarity index 100% copy from tests/simple/tixs/.hpc/Main.mix copy to tests/simple/tixs/.hpc.copy/Main.mix diff --git a/tests/simple/tixs/test.T b/tests/simple/tixs/test.T index 48ca67f..8e98d0e 100644 --- a/tests/simple/tixs/test.T +++ b/tests/simple/tixs/test.T @@ -67,3 +67,7 @@ test('hpc_hand_overlay', "{hpc} report total3.tix"]) test('hpc_bad_001', exit_code(1), run_command, ["{hpc} bad arguments"]) + +test('T9619', ignore_output, run_command, + # Having the same mix file in two different hpcdirs should work. + ["{hpc} report hpc_sample.tix --hpcdir=.hpc --hpcdir=.hpc.copy"]) From git at git.haskell.org Wed Mar 11 18:02:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 18:02:29 +0000 (UTC) Subject: [commit: packages/hpc] master's head updated: Update fulltest output (08afa91) Message-ID: <20150311180229.633A03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc Branch 'master' now includes: cb27dd9 Cleanup test.T files using PEP8 style guide 08afa91 Update fulltest output From git at git.haskell.org Wed Mar 11 18:04:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 18:04:40 +0000 (UTC) Subject: [commit: ghc] master: Cleanup test framework string formatting (5258566) Message-ID: <20150311180440.D54103A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5258566ee5c89aa757b0cf1433169346319c018f/ghc >--------------------------------------------------------------- commit 5258566ee5c89aa757b0cf1433169346319c018f Author: Thomas Miedema Date: Fri Mar 6 21:55:36 2015 +0100 Cleanup test framework string formatting * Use format strings instead of string concatenation. * Wrap `config.compiler`, `config.hpc` etc. in quotes in `mk/test.mk`, so we don't have to in .T scripts and driver/testlib.py. Update hpc submodule (test cleanup) Reviewers: austin Differential Revision: https://phabricator.haskell.org/D718 >--------------------------------------------------------------- 5258566ee5c89aa757b0cf1433169346319c018f libraries/hpc | 2 +- testsuite/config/ghc | 4 +- testsuite/driver/testlib.py | 92 ++++++++++++++++++++++----------------------- testsuite/mk/test.mk | 16 +++++--- 4 files changed, 57 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 5258566ee5c89aa757b0cf1433169346319c018f From git at git.haskell.org Wed Mar 11 20:09:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 20:09:03 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: ghc-prim : Hide 64 bit primops when the word size is 32 bits (fixes #9886). (bd785d1) Message-ID: <20150311200903.211DF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/bd785d101766a1207b8d27a45b6ae0bf83cd678a/ghc >--------------------------------------------------------------- commit bd785d101766a1207b8d27a45b6ae0bf83cd678a Author: Erik de Castro Lopo Date: Thu Mar 5 19:39:16 2015 +1100 ghc-prim : Hide 64 bit primops when the word size is 32 bits (fixes #9886). Summary: These primops were failing to compile on PowerPC (32 bit). There is also currently no way to call into these primops from Haskell code. Currently, the *only* way to call any of these C hs_atomic_* functions is via the fetch*IntArray primops which are only defined for Int values and Int is always the native word size. When these functions can be called (and tested) from Haskell code, then it will be worth while implementing them. Test Plan: Compile and run on x86, x86_64, powerpc and arm: testsuite/tests/concurrent/should_run/AtomicPrimops.hs Reviewers: tibbe, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D702 GHC Trac Issues: #9886 (cherry picked from commit 19440ae2bb256f75934949ae57934caee3831a80) >--------------------------------------------------------------- bd785d101766a1207b8d27a45b6ae0bf83cd678a libraries/ghc-prim/cbits/atomic.c | 14 ++++++++++++++ 1 file changed, 14 insertions(+) diff --git a/libraries/ghc-prim/cbits/atomic.c b/libraries/ghc-prim/cbits/atomic.c index e3d6cc1..01cc458 100644 --- a/libraries/ghc-prim/cbits/atomic.c +++ b/libraries/ghc-prim/cbits/atomic.c @@ -32,12 +32,14 @@ hs_atomic_add32(volatile StgWord32 *x, StgWord val) return __sync_fetch_and_add(x, (StgWord32) val); } +#if WORD_SIZE_IN_BITS == 64 extern StgWord64 hs_atomic_add64(volatile StgWord64 *x, StgWord64 val); StgWord64 hs_atomic_add64(volatile StgWord64 *x, StgWord64 val) { return __sync_fetch_and_add(x, val); } +#endif // FetchSubByteArrayOp_Int @@ -62,12 +64,14 @@ hs_atomic_sub32(volatile StgWord32 *x, StgWord val) return __sync_fetch_and_sub(x, (StgWord32) val); } +#if WORD_SIZE_IN_BITS == 64 extern StgWord64 hs_atomic_sub64(volatile StgWord64 *x, StgWord64 val); StgWord64 hs_atomic_sub64(volatile StgWord64 *x, StgWord64 val) { return __sync_fetch_and_sub(x, val); } +#endif // FetchAndByteArrayOp_Int @@ -92,12 +96,14 @@ hs_atomic_and32(volatile StgWord32 *x, StgWord val) return __sync_fetch_and_and(x, (StgWord32) val); } +#if WORD_SIZE_IN_BITS == 64 extern StgWord64 hs_atomic_and64(volatile StgWord64 *x, StgWord64 val); StgWord64 hs_atomic_and64(volatile StgWord64 *x, StgWord64 val) { return __sync_fetch_and_and(x, val); } +#endif // FetchNandByteArrayOp_Int @@ -144,6 +150,7 @@ hs_atomic_nand32(volatile StgWord32 *x, StgWord val) #endif } +#if WORD_SIZE_IN_BITS == 64 extern StgWord64 hs_atomic_nand64(volatile StgWord64 *x, StgWord64 val); StgWord64 hs_atomic_nand64(volatile StgWord64 *x, StgWord64 val) @@ -154,6 +161,7 @@ hs_atomic_nand64(volatile StgWord64 *x, StgWord64 val) return __sync_fetch_and_nand(x, val); #endif } +#endif // FetchOrByteArrayOp_Int @@ -178,12 +186,14 @@ hs_atomic_or32(volatile StgWord32 *x, StgWord val) return __sync_fetch_and_or(x, (StgWord32) val); } +#if WORD_SIZE_IN_BITS == 64 extern StgWord64 hs_atomic_or64(volatile StgWord64 *x, StgWord64 val); StgWord64 hs_atomic_or64(volatile StgWord64 *x, StgWord64 val) { return __sync_fetch_and_or(x, val); } +#endif // FetchXorByteArrayOp_Int @@ -208,12 +218,14 @@ hs_atomic_xor32(volatile StgWord32 *x, StgWord val) return __sync_fetch_and_xor(x, (StgWord32) val); } +#if WORD_SIZE_IN_BITS == 64 extern StgWord64 hs_atomic_xor64(volatile StgWord64 *x, StgWord64 val); StgWord64 hs_atomic_xor64(volatile StgWord64 *x, StgWord64 val) { return __sync_fetch_and_xor(x, val); } +#endif // CasByteArrayOp_Int @@ -238,12 +250,14 @@ hs_cmpxchg32(volatile StgWord32 *x, StgWord old, StgWord new) return __sync_val_compare_and_swap(x, (StgWord32) old, (StgWord32) new); } +#if WORD_SIZE_IN_BITS == 64 extern StgWord hs_cmpxchg64(volatile StgWord64 *x, StgWord64 old, StgWord64 new); StgWord hs_cmpxchg64(volatile StgWord64 *x, StgWord64 old, StgWord64 new) { return __sync_val_compare_and_swap(x, old, new); } +#endif // AtomicReadByteArrayOp_Int From git at git.haskell.org Wed Mar 11 20:10:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 20:10:25 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: RTS/IOManager: fix trac issue #9722. (fb2ab1e) Message-ID: <20150311201025.85B903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/fb2ab1e3e04fde78d8970815f83b90d54359ae82/ghc >--------------------------------------------------------------- commit fb2ab1e3e04fde78d8970815f83b90d54359ae82 Author: Andreas Voellmy Date: Mon Mar 9 18:27:41 2015 -0400 RTS/IOManager: fix trac issue #9722. Summary: Whenever the RTS has been inactive for idleGCDelayTime, the idle timer fires and calls wakeUpRts(), which in turn calls ioManagerWakeup(), which in turn writes a byte (or a few) to a file descriptor (stored in the io_manager_wakeup_fd variable) registered by the TimerManager and on which the TimerManager will wait. (Note that the write will only occur if the file descriptor is non-negative.) When the RTS shuts down, it shuts down the TimerManager, and in this process the file descriptor stored in io_manager_wakeup_fd is closed. In the error case, the idle timer fires after the close of the file occurs, and then the write() call in ioManagerWakeup() fails and the aforementioned error message gets printed. This patch solves the problem by (1) having the TimerManager (via Control) write -1 to io_manager_wakeup_fd just before closing the file descriptor written in io_manager_wakeup_fd, and (2) having ioManagerWakeup() ignore an error returned by write() in the case that the write returned -1 and the io_manager_wakeup_fd is -1. Reviewers: austin, simonmar, hvr, thomie Reviewed By: thomie Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D722 GHC Trac Issues: #9722 (cherry picked from commit 74625d6847e970e8bdc6991c327515b3e10b231b) >--------------------------------------------------------------- fb2ab1e3e04fde78d8970815f83b90d54359ae82 libraries/base/GHC/Event/Control.hs | 7 +++++++ rts/posix/Signals.c | 17 +++++++++++++++-- 2 files changed, 22 insertions(+), 2 deletions(-) diff --git a/libraries/base/GHC/Event/Control.hs b/libraries/base/GHC/Event/Control.hs index 747a416..5dcc66e 100644 --- a/libraries/base/GHC/Event/Control.hs +++ b/libraries/base/GHC/Event/Control.hs @@ -68,6 +68,7 @@ data Control = W { , wakeupReadFd :: {-# UNPACK #-} !Fd , wakeupWriteFd :: {-# UNPACK #-} !Fd #endif + , didRegisterWakeupFd :: !Bool } deriving (Show) #if defined(HAVE_EVENTFD) @@ -108,13 +109,19 @@ newControl shouldRegister = allocaArray 2 $ \fds -> do , wakeupReadFd = fromIntegral wake_rd , wakeupWriteFd = fromIntegral wake_wr #endif + , didRegisterWakeupFd = shouldRegister } -- | Close the control structure used by the IO manager thread. +-- N.B. If this Control is the Control whose wakeup file was registered with +-- the RTS, then *BEFORE* the wakeup file is closed, we must call +-- c_setIOManagerWakeupFd (-1), so that the RTS does not try to use the wakeup +-- file after it has been closed. closeControl :: Control -> IO () closeControl w = do _ <- c_close . fromIntegral . controlReadFd $ w _ <- c_close . fromIntegral . controlWriteFd $ w + when (didRegisterWakeupFd w) $ c_setIOManagerWakeupFd (-1) #if defined(HAVE_EVENTFD) _ <- c_close . fromIntegral . controlEventFd $ w #else diff --git a/rts/posix/Signals.c b/rts/posix/Signals.c index 5fbb917..a2fa07f 100644 --- a/rts/posix/Signals.c +++ b/rts/posix/Signals.c @@ -126,7 +126,7 @@ more_handlers(int sig) } // Here's the pipe into which we will send our signals -static int io_manager_wakeup_fd = -1; +static volatile int io_manager_wakeup_fd = -1; static int timer_manager_control_wr_fd = -1; #define IO_MANAGER_WAKEUP 0xff @@ -161,7 +161,20 @@ ioManagerWakeup (void) StgWord8 byte = (StgWord8)IO_MANAGER_WAKEUP; r = write(io_manager_wakeup_fd, &byte, 1); #endif - if (r == -1) { sysErrorBelch("ioManagerWakeup: write"); } + /* N.B. If the TimerManager is shutting down as we run this + * then there is a possiblity that our first read of + * io_manager_wakeup_fd is non-negative, but before we get to the + * write the file is closed. If this occurs, io_manager_wakeup_fd + * will be written into with -1 (GHC.Event.Control does this prior + * to closing), so checking this allows us to distinguish this case. + * To ensure we observe the correct ordering, we declare the + * io_manager_wakeup_fd as volatile. + * Since this is not an error condition, we do not print the error + * message in this case. + */ + if (r == -1 && io_manager_wakeup_fd >= 0) { + sysErrorBelch("ioManagerWakeup: write"); + } } } From git at git.haskell.org Wed Mar 11 21:06:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 21:06:56 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update Cabal submodule to latest 1.22 snapshot (e8fd618) Message-ID: <20150311210656.031E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/e8fd61862ae572c7d470acdbcc95eff97de0dc54/ghc >--------------------------------------------------------------- commit e8fd61862ae572c7d470acdbcc95eff97de0dc54 Author: Edward Z. Yang Date: Wed Mar 11 14:53:17 2015 +0100 Update Cabal submodule to latest 1.22 snapshot This changes the library file name format NOTE: This patch originally updated to Cabal HEAD, but was reduced to update to Cabal 1.22 HEAD by hvr as this is needed in order to update the filepath submodule to version 1.4.0, and subsequently to be cherry-picked into the ghc-7.10 branch Signed-off-by: Edward Z. Yang (cherry picked from commit 838d8044896b6544d8c80c2ab5de63d97220f06c) >--------------------------------------------------------------- e8fd61862ae572c7d470acdbcc95eff97de0dc54 compiler/ghc.mk | 1 + libraries/Cabal | 2 +- rules/build-package-way.mk | 6 +++--- utils/ghc-cabal/Main.hs | 3 +++ 4 files changed, 8 insertions(+), 4 deletions(-) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index 200ec8f..0955901 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -445,6 +445,7 @@ compiler_stage1_MUNGED_VERSION = $(subst .$(ProjectPatchLevel),,$(ProjectVersion define compiler_PACKAGE_MAGIC compiler_stage1_VERSION = $(compiler_stage1_MUNGED_VERSION) compiler_stage1_PACKAGE_KEY = $(subst .$(ProjectPatchLevel),,$(compiler_stage1_PACKAGE_KEY)) +compiler_stage1_LIB_NAME = $(subst .$(ProjectPatchLevel),,$(compiler_stage1_LIB_NAME)) endef # NB: the PACKAGE_KEY munging has no effect for new-style package keys diff --git a/libraries/Cabal b/libraries/Cabal index a8dfc6f..a9958fe 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit a8dfc6f4cb9cd280299385a50fefc0a4f8103ef1 +Subproject commit a9958fefc737b223b75babc68ecd3122b9697cd9 diff --git a/rules/build-package-way.mk b/rules/build-package-way.mk index 3efe501..27da099 100644 --- a/rules/build-package-way.mk +++ b/rules/build-package-way.mk @@ -23,13 +23,13 @@ $(call hs-objs,$1,$2,$3) # The .a/.so library file, indexed by two different sets of vars: # the first is indexed by the dir, distdir and way # the second is indexed by the package id, distdir and way -$1_$2_$3_LIB_NAME = libHS$$($1_$2_PACKAGE_KEY)$$($3_libsuf) +$1_$2_$3_LIB_NAME = libHS$$($1_$2_LIB_NAME)$$($3_libsuf) $1_$2_$3_LIB = $1/$2/build/$$($1_$2_$3_LIB_NAME) $$($1_$2_PACKAGE_KEY)_$2_$3_LIB = $$($1_$2_$3_LIB) ifeq "$$(HostOS_CPP)" "mingw32" ifneq "$$($1_$2_dll0_HS_OBJS)" "" -$1_$2_$3_LIB0_ROOT = HS$$($1_$2_PACKAGE_KEY)-0$$($3_libsuf) +$1_$2_$3_LIB0_ROOT = HS$$($1_$2_LIB_NAME)-0$$($3_libsuf) $1_$2_$3_LIB0_NAME = lib$$($1_$2_$3_LIB0_ROOT) $1_$2_$3_LIB0 = $1/$2/build/$$($1_$2_$3_LIB0_NAME) endif @@ -136,7 +136,7 @@ ifeq "$$(DYNAMIC_GHC_PROGRAMS)" "YES" $1_$2_GHCI_LIB = $$($1_$2_dyn_LIB) else ifeq "$3" "v" -$1_$2_GHCI_LIB = $1/$2/build/HS$$($1_$2_PACKAGE_KEY).$$($3_osuf) +$1_$2_GHCI_LIB = $1/$2/build/HS$$($1_$2_LIB_NAME).$$($3_osuf) ifeq "$$($1_$2_BUILD_GHCI_LIB)" "YES" # Don't put bootstrapping packages in the bindist ifneq "$4" "0" diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index 6724f3a..47968a1 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -6,6 +6,7 @@ import Distribution.PackageDescription import Distribution.PackageDescription.Check hiding (doesFileExist) import Distribution.PackageDescription.Configuration import Distribution.PackageDescription.Parse +import Distribution.Package import Distribution.System import Distribution.Simple import Distribution.Simple.Configure @@ -438,6 +439,8 @@ generate directory distdir dll0Modules config_args allMods = mods ++ otherMods let xs = [variablePrefix ++ "_VERSION = " ++ display (pkgVersion (package pd)), variablePrefix ++ "_PACKAGE_KEY = " ++ display (pkgKey lbi), + -- copied from mkComponentsLocalBuildInfo + variablePrefix ++ "_LIB_NAME = " ++ packageKeyLibraryName (package pd) (pkgKey lbi), variablePrefix ++ "_MODULES = " ++ unwords mods, variablePrefix ++ "_HIDDEN_MODULES = " ++ unwords otherMods, variablePrefix ++ "_SYNOPSIS =" ++ synopsis pd, From git at git.haskell.org Wed Mar 11 21:06:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 21:06:58 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: testsuite: format commands using config dict (4ce0453) Message-ID: <20150311210658.A94CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/4ce0453f306e11c79da1ddd60a3c3cec021be8ac/ghc >--------------------------------------------------------------- commit 4ce0453f306e11c79da1ddd60a3c3cec021be8ac Author: Thomas Miedema Date: Fri Mar 6 20:17:41 2015 +0100 testsuite: format commands using config dict Allow `cmd_wrapper` to return a format string that can refer to config values. Very useful! This allows for many tests to be defined in pure Python, instead of in an additional script or Makefile. Example: def Thpc(cmd): return(cmd + ' && {hpc} report Thpc.tix') test('Thpc', [cmd_wrapper(Thpc), only_ways['hpc']), compile_and_run, ['']) The `{hpc}` is replaced by the value of `config.hpc`. The result is that the module `Thpc` first gets compiled, then the binary `Thpc` is run, and then the `hpc report` command is run. The output of all of this is redirected (and later appended) to Thpc.run.stdout/stderr as normally. (cherry picked from commit 91c11feacc4c66a7ebcf8a88ab1cb851ce48142a) >--------------------------------------------------------------- 4ce0453f306e11c79da1ddd60a3c3cec021be8ac testsuite/driver/testlib.py | 24 +++++++++++++++++------- 1 file changed, 17 insertions(+), 7 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 6fc86e4..d359fe3 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1314,11 +1314,11 @@ def simple_run( name, way, prog, args ): stdin_comes_from = ' <' + use_stdin if opts.combined_output: - redirection = ' >' + run_stdout \ - + ' 2>&1' + redirection = ' > {} 2>&1'.format(run_stdout) + redirection_append = ' >> {} 2>&1'.format(run_stdout) else: - redirection = ' >' + run_stdout \ - + ' 2>' + run_stderr + redirection = ' > {} 2> {}'.format(run_stdout, run_stderr) + redirection_append = ' >> {} 2>> {}'.format(run_stdout, run_stderr) cmd = prog + ' ' + args + ' ' \ + my_rts_flags + ' ' \ @@ -1326,7 +1326,7 @@ def simple_run( name, way, prog, args ): + redirection if opts.cmd_wrapper != None: - cmd = opts.cmd_wrapper(cmd); + cmd = opts.cmd_wrapper(cmd) + redirection_append cmd = 'cd ' + opts.testdir + ' && ' + cmd @@ -1426,16 +1426,23 @@ def interpreter_run( name, way, extra_hc_opts, compile_only, top_mod ): if getTestOpts().outputdir != None: flags.extend(["-outputdir", getTestOpts().outputdir]) + if getTestOpts().combined_output: + redirection = ' > {} 2>&1'.format(outname) + redirection_append = ' >> {} 2>&1'.format(outname) + else: + redirection = ' > {} 2> {}'.format(outname, errname) + redirection_append = ' >> {} 2>> {}'.format(outname, errname) + cmd = "'" + config.compiler + "' " \ + ' '.join(flags) + ' ' \ + srcname + ' ' \ + ' '.join(config.way_flags(name)[way]) + ' ' \ + extra_hc_opts + ' ' \ + getTestOpts().extra_hc_opts + ' ' \ - + '<' + scriptname + ' 1>' + outname + ' 2>' + errname + + '<' + scriptname + redirection if getTestOpts().cmd_wrapper != None: - cmd = getTestOpts().cmd_wrapper(cmd); + cmd = getTestOpts().cmd_wrapper(cmd) + redirection_append; cmd = 'cd ' + getTestOpts().testdir + " && " + cmd @@ -1830,6 +1837,9 @@ def runCmd( cmd ): return r << 8 def runCmdFor( name, cmd, timeout_multiplier=1.0 ): + # Format cmd using config. Example: cmd='{hpc} report A.tix' + cmd = cmd.format(**config.__dict__) + if_verbose( 3, cmd ) r = 0 if config.os == 'mingw32': From git at git.haskell.org Wed Mar 11 21:07:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 21:07:01 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update filepath submodule to filepath-1.4 snapshot (773b90b) Message-ID: <20150311210701.832E73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/773b90b038c48430d62b21721f6aa09599abdf64/ghc >--------------------------------------------------------------- commit 773b90b038c48430d62b21721f6aa09599abdf64 Author: Herbert Valerio Riedel Date: Wed Mar 11 14:20:51 2015 +0100 Update filepath submodule to filepath-1.4 snapshot This also needs to update a couple of other submodules to update the upper bound on filepath to allow this major version bump to 1.4.0.0 (cherry picked from commit 5f356f3e412ae4a808b2a72c10609eaacfb1ce3a) >--------------------------------------------------------------- 773b90b038c48430d62b21721f6aa09599abdf64 compiler/ghc.cabal.in | 2 +- ghc/ghc-bin.cabal.in | 2 +- libraries/directory | 2 +- libraries/filepath | 2 +- libraries/haskeline | 2 +- libraries/process | 2 +- utils/ghc-cabal/ghc-cabal.cabal | 2 +- utils/hsc2hs | 2 +- 8 files changed, 8 insertions(+), 8 deletions(-) diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index a6624ff..684ee6b 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -51,7 +51,7 @@ Library time < 1.6, containers >= 0.5 && < 0.6, array >= 0.1 && < 0.6, - filepath >= 1 && < 1.4, + filepath >= 1 && < 1.5, hpc, transformers, bin-package-db, diff --git a/ghc/ghc-bin.cabal.in b/ghc/ghc-bin.cabal.in index dcbc695..b4fdf10 100644 --- a/ghc/ghc-bin.cabal.in +++ b/ghc/ghc-bin.cabal.in @@ -32,7 +32,7 @@ Executable ghc bytestring >= 0.9 && < 0.11, directory >= 1 && < 1.3, process >= 1 && < 1.3, - filepath >= 1 && < 1.4, + filepath >= 1 && < 1.5, ghc if os(windows) Build-Depends: Win32 diff --git a/libraries/directory b/libraries/directory index e04430d..7233248 160000 --- a/libraries/directory +++ b/libraries/directory @@ -1 +1 @@ -Subproject commit e04430d2e65baa28ab4fd8c0c044b5819d63006a +Subproject commit 7233248952648ed4dd213f91ed52af2317a3f23b diff --git a/libraries/filepath b/libraries/filepath index c1a3aec..4206435 160000 --- a/libraries/filepath +++ b/libraries/filepath @@ -1 +1 @@ -Subproject commit c1a3aec04cb93315dbc9725139c54d71e5134426 +Subproject commit 4206435bda0929d7a65fc42e5c8629212328120c diff --git a/libraries/haskeline b/libraries/haskeline index 87a01d2..06679b7 160000 --- a/libraries/haskeline +++ b/libraries/haskeline @@ -1 +1 @@ -Subproject commit 87a01d222ef13f89a68204602e3fe9273eeed3ca +Subproject commit 06679b723fc07ca805d0dc6b328a5762255e93ee diff --git a/libraries/process b/libraries/process index 160bdd1..c8cdaef 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 160bdd16722d85c2644bd2353121d8eb5e1597e4 +Subproject commit c8cdaef5585717089a53be61cb6f08b3120f18b4 diff --git a/utils/ghc-cabal/ghc-cabal.cabal b/utils/ghc-cabal/ghc-cabal.cabal index f963c7c..5827333 100644 --- a/utils/ghc-cabal/ghc-cabal.cabal +++ b/utils/ghc-cabal/ghc-cabal.cabal @@ -19,5 +19,5 @@ Executable ghc-cabal bytestring >= 0.10 && < 0.11, Cabal >= 1.22 && < 1.24, directory >= 1.1 && < 1.3, - filepath >= 1.2 && < 1.4 + filepath >= 1.2 && < 1.5 diff --git a/utils/hsc2hs b/utils/hsc2hs index 10696fe..c16032d 160000 --- a/utils/hsc2hs +++ b/utils/hsc2hs @@ -1 +1 @@ -Subproject commit 10696fe17c9d2b4e3498684c6ffbd9f44eda53c4 +Subproject commit c16032d83c8ce7ac3e11b99f8e80bfdfc77f0d1f From git at git.haskell.org Wed Mar 11 21:07:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 21:07:04 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Cleanup test framework string formatting (dde3a23) Message-ID: <20150311210704.732753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/dde3a2378e3961f7eed82d07d2f1e904878cc2b0/ghc >--------------------------------------------------------------- commit dde3a2378e3961f7eed82d07d2f1e904878cc2b0 Author: Thomas Miedema Date: Fri Mar 6 21:55:36 2015 +0100 Cleanup test framework string formatting * Use format strings instead of string concatenation. * Wrap `config.compiler`, `config.hpc` etc. in quotes in `mk/test.mk`, so we don't have to in .T scripts and driver/testlib.py. Update hpc submodule (test cleanup) (cherry picked from commit 5258566ee5c89aa757b0cf1433169346319c018f) >--------------------------------------------------------------- dde3a2378e3961f7eed82d07d2f1e904878cc2b0 libraries/hpc | 2 +- testsuite/config/ghc | 4 +- testsuite/driver/testlib.py | 92 ++++++++++++++++++++++----------------------- testsuite/mk/test.mk | 16 +++++--- 4 files changed, 57 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 dde3a2378e3961f7eed82d07d2f1e904878cc2b0 From git at git.haskell.org Wed Mar 11 22:41:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 22:41:31 +0000 (UTC) Subject: [commit: packages/hpc] master's head updated: Allow same `Mix` file in different dirs (#9619) (f601495) Message-ID: <20150311224131.644503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc Branch 'master' now includes: cf88706 Update maintainer 3e45180 Use System.FilePath functions instead of (++) f601495 Allow same `Mix` file in different dirs (#9619) From git at git.haskell.org Wed Mar 11 22:42:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 22:42:14 +0000 (UTC) Subject: [commit: ghc] master: Update submodule hpc (includes fix for #9619) (41e8400) Message-ID: <20150311224214.D577E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/41e8400a57620978681663e9c804fee405da26d5/ghc >--------------------------------------------------------------- commit 41e8400a57620978681663e9c804fee405da26d5 Author: Thomas Miedema Date: Thu Mar 5 22:06:11 2015 +0100 Update submodule hpc (includes fix for #9619) Reviewers: austin Differential Revision: https://phabricator.haskell.org/D704 >--------------------------------------------------------------- 41e8400a57620978681663e9c804fee405da26d5 libraries/hpc | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/hpc b/libraries/hpc index 08afa91..f601495 160000 --- a/libraries/hpc +++ b/libraries/hpc @@ -1 +1 @@ -Subproject commit 08afa91988b68315a035df4702b84b69ba8e125e +Subproject commit f601495ac5f93f24cbcaa95f45b1bc26ad644ac9 From git at git.haskell.org Wed Mar 11 22:42:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 22:42:17 +0000 (UTC) Subject: [commit: ghc] master: testsuite: use same flags for ghci way and scripts (ec67f81) Message-ID: <20150311224217.A31B33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ec67f8136a8953c4813f875b7c9390aa81c2c9aa/ghc >--------------------------------------------------------------- commit ec67f8136a8953c4813f875b7c9390aa81c2c9aa Author: Thomas Miedema Date: Sun Mar 8 16:56:41 2015 +0100 testsuite: use same flags for ghci way and scripts The ghci script tests were using different RTS flags from the normal ghci tests. This commit makes them use the same flags. Reviewers: austin Differential Revision: https://phabricator.haskell.org/D724 >--------------------------------------------------------------- ec67f8136a8953c4813f875b7c9390aa81c2c9aa testsuite/driver/testlib.py | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index a3c473a..fec6939 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -955,7 +955,7 @@ def ghci_script( name, way, script, override_flags = None ): # actually testing the recompilation behaviour in the GHCi tests. flags = ' '.join(get_compiler_flags(override_flags, noforce=True)) - way_flags = '--interactive -v0 -ignore-dot-ghci' + way_flags = ' '.join(config.way_flags(name)['ghci']) # We pass HC and HC_OPTS as environment variables, so that the # script can invoke the correct compiler by using ':! $HC $HC_OPTS' From git at git.haskell.org Wed Mar 11 23:41:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Mar 2015 23:41:19 +0000 (UTC) Subject: [commit: packages/hpc] branch 'wip/T9619' deleted Message-ID: <20150311234119.624E23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc Deleted branch: wip/T9619 From git at git.haskell.org Thu Mar 12 03:38:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Mar 2015 03:38:33 +0000 (UTC) Subject: [commit: ghc] master: Use the gold linker for linux/ARM and android/ARM targets. (71fcc4c) Message-ID: <20150312033833.530B53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/71fcc4c096ec0b575522e4c2d0104ef7a71a13c5/ghc >--------------------------------------------------------------- commit 71fcc4c096ec0b575522e4c2d0104ef7a71a13c5 Author: Erik de Castro Lopo Date: Thu Mar 12 14:36:50 2015 +1100 Use the gold linker for linux/ARM and android/ARM targets. Fixes #8976 and #9873 by making use of the Binutils ld.gold linker explicit whenever the target is linux/ARM or android/ARM. This does not affect iOS where Apple provides its own linker. In order to achieve this, we need to add `-fuse-ld=gold` to the SettingsCCompilerLinkFlags setting and set SettingsLdCommand to `ld.gold` (or `${target}-ld.gold` when cross-compiling). In addition, simplifying the use of `$(CONF_GCC_LINKER_OPTS_STAGEn)`. This patch was tested by ensuring that the following worked as expected: * Native builds on linux/x86_64 (nothing changed). * Native builds on linux/arm (and uses the gold linker). * Linux to linux/arm cross compiles (and uses the cross gold linker). Contributions by Ben Gamari, Joachim Breitner and Reid Barton. Reviewers: nomeata, bgamari, austin, rwbarton Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D715 GHC Trac Issues: #8976 #9873 >--------------------------------------------------------------- 71fcc4c096ec0b575522e4c2d0104ef7a71a13c5 aclocal.m4 | 5 +++++ configure.ac | 13 ++++++++++++- libffi/ghc.mk | 2 +- mk/config.mk.in | 1 - rules/build-package-data.mk | 2 +- rules/distdir-opts.mk | 1 - 6 files changed, 19 insertions(+), 5 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index a4944c1..871dacc 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -565,6 +565,11 @@ AC_DEFUN([FPTOOLS_SET_C_LD_FLAGS], $3="$$3 -D_HPUX_SOURCE" $5="$$5 -D_HPUX_SOURCE" ;; + arm*linux*) + # On arm/linux and arm/android, tell gcc to link using the gold linker. + # Forcing LD to be ld.gold is done in configre.ac. + $3="$$3 -fuse-ld=gold" + ;; esac # If gcc knows about the stack protector, turn it off. diff --git a/configure.ac b/configure.ac index c64af90..e7d467f 100644 --- a/configure.ac +++ b/configure.ac @@ -438,7 +438,18 @@ AC_SUBST([HaskellCPPArgs]) dnl ** Which ld to use? dnl -------------------------------------------------------------- FP_ARG_WITH_PATH_GNU_PROG([LD], [ld], [ld]) -LdCmd="$LD" +case $target in +arm*linux*) + # Arm requires use of the binutils ld.gold linker. + # This case should catch at least arm-unknown-linux-gnueabihf and + # arm-linux-androideabi. + FP_ARG_WITH_PATH_GNU_PROG([LD_GOLD], [ld.gold], [ld.gold]) + LdCmd="$LD_GOLD" + ;; +*) + LdCmd="$LD" + ;; +esac AC_SUBST([LdCmd]) dnl ** Which nm to use? diff --git a/libffi/ghc.mk b/libffi/ghc.mk index abbe87f..a5645de 100644 --- a/libffi/ghc.mk +++ b/libffi/ghc.mk @@ -100,7 +100,7 @@ $(libffi_STAMP_CONFIGURE): $(TOUCH_DEP) NM=$(NM) \ RANLIB=$(REAL_RANLIB_CMD) \ CFLAGS="$(SRC_CC_OPTS) $(CONF_CC_OPTS_STAGE1) -w" \ - LDFLAGS="$(SRC_LD_OPTS) $(CONF_GCC_LINKER_OPTS_STAGE1) -w" \ + LDFLAGS="$(SRC_LD_OPTS) -w" \ "$(SHELL)" ./configure \ --prefix=$(TOP)/libffi/build/inst \ --libdir=$(TOP)/libffi/build/inst/lib \ diff --git a/mk/config.mk.in b/mk/config.mk.in index b32f227..a6f757a 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -568,7 +568,6 @@ define set_stage_HSC2HS_OPTS # $1 = stage SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --cflag=,$$(filter-out -O,$$(SRC_CC_OPTS) $$(CONF_CC_OPTS_STAGE$1))) SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --cflag=,$$(CONF_CPP_OPTS_STAGE$1)) -SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --lflag=,$$(CONF_GCC_LINKER_OPTS_STAGE$1)) endef $(eval $(call set_stage_HSC2HS_OPTS,0)) $(eval $(call set_stage_HSC2HS_OPTS,1)) diff --git a/rules/build-package-data.mk b/rules/build-package-data.mk index 494b89a..817bf8d 100644 --- a/rules/build-package-data.mk +++ b/rules/build-package-data.mk @@ -50,7 +50,7 @@ endif # for a feature it may not generate warning-free C code, and thus may # think that the feature doesn't exist if -Werror is on. $1_$2_CONFIGURE_CFLAGS = $$(filter-out -Werror,$$(SRC_CC_OPTS)) $$(CONF_CC_OPTS_STAGE$3) $$($1_CC_OPTS) $$($1_$2_CC_OPTS) $$(SRC_CC_WARNING_OPTS) -$1_$2_CONFIGURE_LDFLAGS = $$(SRC_LD_OPTS) $$(CONF_GCC_LINKER_OPTS_STAGE$3) $$($1_LD_OPTS) $$($1_$2_LD_OPTS) +$1_$2_CONFIGURE_LDFLAGS = $$(SRC_LD_OPTS) $$($1_LD_OPTS) $$($1_$2_LD_OPTS) $1_$2_CONFIGURE_CPPFLAGS = $$(SRC_CPP_OPTS) $$(CONF_CPP_OPTS_STAGE$3) $$($1_CPP_OPTS) $$($1_$2_CPP_OPTS) $1_$2_CONFIGURE_OPTS += --configure-option=CFLAGS="$$($1_$2_CONFIGURE_CFLAGS)" diff --git a/rules/distdir-opts.mk b/rules/distdir-opts.mk index 3126a88..b2f0d1b 100644 --- a/rules/distdir-opts.mk +++ b/rules/distdir-opts.mk @@ -65,7 +65,6 @@ $1_$2_DIST_LD_LIB_DIRS := $$(subst $$(space)',$$(space)-L',$$(space)$$($1_$2_DEP endif $1_$2_DIST_LD_OPTS = \ - $$(CONF_GCC_LINKER_OPTS_STAGE$3) \ $$(SRC_LD_OPTS) \ $$($1_LD_OPTS) \ $$($1_$2_LD_OPTS) \ From git at git.haskell.org Thu Mar 12 08:57:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Mar 2015 08:57:00 +0000 (UTC) Subject: [commit: packages/hpc] master: Update changelog for upcoming GHC 7.10.1 release (154eecf) Message-ID: <20150312085700.4947E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : master Link : http://git.haskell.org/packages/hpc.git/commitdiff/154eecf3ca10f9252bf75213d091221ee3c551d6 >--------------------------------------------------------------- commit 154eecf3ca10f9252bf75213d091221ee3c551d6 Author: Herbert Valerio Riedel Date: Thu Mar 12 09:56:07 2015 +0100 Update changelog for upcoming GHC 7.10.1 release This also adds the missing changelog entry for bd8051965e6aae70bf87b36e17745dbba6ca6986 >--------------------------------------------------------------- 154eecf3ca10f9252bf75213d091221ee3c551d6 changelog.md | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index 1bd2a96..dfb36fd 100644 --- a/changelog.md +++ b/changelog.md @@ -1,9 +1,11 @@ # Changelog for [`hpc` package](http://hackage.haskell.org/package/hpc) -## 0.6.0.2 *TBA* +## 0.6.0.2 *Mar 2015* * Bundled with GHC 7.10.1 + * Allow same `Mix` file in different dirs (#9619) + ## 0.6.0.1 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 12 08:57:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Mar 2015 08:57:48 +0000 (UTC) Subject: [commit: packages/hpc] branch 'wip/cleanup-tests' deleted Message-ID: <20150312085748.039153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc Deleted branch: wip/cleanup-tests From git at git.haskell.org Thu Mar 12 09:00:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Mar 2015 09:00:34 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update submodule hpc (includes fix for #9619) (029a296) Message-ID: <20150312090034.1DAED3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/029a296a770addbd096bbfd6de0936327ee620d4/ghc >--------------------------------------------------------------- commit 029a296a770addbd096bbfd6de0936327ee620d4 Author: Thomas Miedema Date: Thu Mar 5 22:06:11 2015 +0100 Update submodule hpc (includes fix for #9619) (cherry picked from commit 41e8400a57620978681663e9c804fee405da26d5) >--------------------------------------------------------------- 029a296a770addbd096bbfd6de0936327ee620d4 libraries/hpc | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/hpc b/libraries/hpc index 08afa91..f601495 160000 --- a/libraries/hpc +++ b/libraries/hpc @@ -1 +1 @@ -Subproject commit 08afa91988b68315a035df4702b84b69ba8e125e +Subproject commit f601495ac5f93f24cbcaa95f45b1bc26ad644ac9 From git at git.haskell.org Fri Mar 13 07:42:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 13 Mar 2015 07:42:48 +0000 (UTC) Subject: [commit: ghc] branch 'ghc-july' deleted Message-ID: <20150313074248.6AFD03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: ghc-july From git at git.haskell.org Fri Mar 13 07:43:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 13 Mar 2015 07:43:40 +0000 (UTC) Subject: [commit: ghc] branch 'ghc-instvis' deleted Message-ID: <20150313074340.0E3933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: ghc-instvis From git at git.haskell.org Fri Mar 13 20:08:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 13 Mar 2015 20:08:40 +0000 (UTC) Subject: [commit: ghc] master: Move the function strip_quotes to testutil.py (cc07a0b) Message-ID: <20150313200840.39AF23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cc07a0ba64b554ffd1ff85757b02cd79d30ed57a/ghc >--------------------------------------------------------------- commit cc07a0ba64b554ffd1ff85757b02cd79d30ed57a Author: Thomas Miedema Date: Fri Mar 13 21:07:15 2015 +0100 Move the function strip_quotes to testutil.py If one runs the testsuite with a profiling compiler, during the import of `testlib.py`, `testlib.py` sets the global variable `gs_working`. To do so, it executes a few statements which require the function `strip_quotes` to be in scope. But that function only gets defined at the very end of testlib.py. This patch moves the definition of `strip_quotes` to testutil.py, which is imported at the very top of testlib.py. This unbreaks the nightly builders. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D728 >--------------------------------------------------------------- cc07a0ba64b554ffd1ff85757b02cd79d30ed57a testsuite/driver/testlib.py | 4 ---- testsuite/driver/testutil.py | 3 +++ 2 files changed, 3 insertions(+), 4 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index fec6939..1d3ef11 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -2283,7 +2283,3 @@ def getStdout(cmd): return stdout else: raise Exception("Need subprocess to get stdout, but don't have it") - -def strip_quotes(s): - # Don't wrap commands to subprocess.call/Popen in quotes. - return s.strip('\'"') diff --git a/testsuite/driver/testutil.py b/testsuite/driver/testutil.py index ec45e93..2cfa8f1 100644 --- a/testsuite/driver/testutil.py +++ b/testsuite/driver/testutil.py @@ -15,3 +15,6 @@ def version_gt(x, y): def version_ge(x, y): return version_to_ints(x) >= version_to_ints(y) +def strip_quotes(s): + # Don't wrap commands to subprocess.call/Popen in quotes. + return s.strip('\'"') From git at git.haskell.org Fri Mar 13 21:49:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 13 Mar 2015 21:49:00 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Custom `Typeable` solver, that keeps track of kinds. (6f46fe1) Message-ID: <20150313214900.C39823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/6f46fe15af397d448438c6b93babcdd68dd78df8/ghc >--------------------------------------------------------------- commit 6f46fe15af397d448438c6b93babcdd68dd78df8 Author: Iavor S. Diatchki Date: Sat Mar 7 10:37:31 2015 -0600 Custom `Typeable` solver, that keeps track of kinds. Summary: This implements the new `Typeable` solver: when GHC sees `Typeable` constraints it solves them on the spot. The current implementation creates `TyCon` representations on the spot. Pro: No overhead at all in code that does not use `Typeable` Cons: Code that uses `Typeable` may create multipe `TyCon` represntations. We have discussed an implementation where representations of `TyCons` are computed once, in the module, where a datatype is declared. This would lead to more code being generated: for a promotable datatype we need to generate `2 + number_of_data_cons` type-constructro representations, and we have to do that for all programs, even ones that do not intend to use typeable. I added code to emit warning whenevar `deriving Typeable` is encountered--- the idea being that this is not needed anymore, and shold be fixed. Also, we allow `instance Typeable T` in .hs-boot files, but they result in a warning, and are ignored. This last one was to avoid breaking exisitng code, and should become an error, eventually. Test Plan: 1. GHC can compile itself. 2. I compiled a number of large libraries, including `lens`. - I had to make some small changes: `unordered-containers` uses internals of `TypeReps`, so I had to do a 1 line fix - `lens` needed one instance changed, due to a poly-kinded `Typeble` instance 3. I also run some code that uses `syb` to traverse a largish datastrucutre. I didn't notice any signifiant performance difference between the 7.8.3 version, and this implementation. Reviewers: simonpj, simonmar, austin, hvr Reviewed By: austin, hvr Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D652 GHC Trac Issues: #9858 (cherry picked from commit b359c886cd7578ed083bcedcea05d315ecaeeb54) >--------------------------------------------------------------- 6f46fe15af397d448438c6b93babcdd68dd78df8 compiler/basicTypes/MkId.hs | 1 + compiler/deSugar/DsBinds.hs | 129 +++++++++- compiler/main/DynFlags.hs | 2 + compiler/prelude/PrelNames.hs | 43 +++- compiler/typecheck/TcDeriv.hs | 232 +++++++----------- compiler/typecheck/TcEvidence.hs | 35 ++- compiler/typecheck/TcGenDeriv.hs | 52 ----- compiler/typecheck/TcHsSyn.hs | 14 ++ compiler/typecheck/TcInstDcls.hs | 49 ++-- compiler/typecheck/TcInteract.hs | 62 ++++- docs/users_guide/flags.xml | 19 +- docs/users_guide/glasgow_exts.xml | 53 +++-- libraries/base/Data/Typeable/Internal.hs | 260 ++++----------------- testsuite/tests/deriving/should_compile/all.T | 2 +- testsuite/tests/deriving/should_fail/T2604.hs | 9 - testsuite/tests/deriving/should_fail/T2604.stderr | 10 - testsuite/tests/deriving/should_fail/T5863a.hs | 12 - testsuite/tests/deriving/should_fail/T5863a.stderr | 10 - testsuite/tests/deriving/should_fail/T7800.hs | 7 - testsuite/tests/deriving/should_fail/T7800.stderr | 6 - testsuite/tests/deriving/should_fail/T7800a.hs | 4 - testsuite/tests/deriving/should_fail/T9687.stderr | 4 +- testsuite/tests/deriving/should_fail/all.T | 6 +- .../tests/ghci.debugger/scripts/print019.stderr | 12 +- testsuite/tests/polykinds/T8132.stderr | 4 +- testsuite/tests/typecheck/should_compile/T9999.hs | 13 -- testsuite/tests/typecheck/should_compile/all.T | 1 - .../should_fail/TcStaticPointersFail02.stderr | 4 +- testsuite/tests/typecheck/should_fail/all.T | 1 + 29 files changed, 486 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 6f46fe15af397d448438c6b93babcdd68dd78df8 From git at git.haskell.org Fri Mar 13 21:49:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 13 Mar 2015 21:49:04 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Add missed test (uuugh) (89465bc) Message-ID: <20150313214904.5136A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/89465bc619b2aa8d841dfa4f5ae89dfb7501ec6e/ghc >--------------------------------------------------------------- commit 89465bc619b2aa8d841dfa4f5ae89dfb7501ec6e Author: Austin Seipp Date: Sat Mar 7 10:40:18 2015 -0600 Add missed test (uuugh) Signed-off-by: Austin Seipp (cherry picked from commit 34ba68c2aeb6fb2d1ea25a1a5e45c233ed7efc9c) >--------------------------------------------------------------- 89465bc619b2aa8d841dfa4f5ae89dfb7501ec6e testsuite/tests/typecheck/should_fail/T9999.hs | 13 +++++++++++++ testsuite/tests/typecheck/should_fail/T9999.stderr | 11 +++++++++++ 2 files changed, 24 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T9999.hs b/testsuite/tests/typecheck/should_fail/T9999.hs new file mode 100644 index 0000000..656e913 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9999.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE AutoDeriveTypeable, PolyKinds, TypeFamilies, StandaloneDeriving #-} + +module T9999 where + +import Data.Typeable + +data family F a + +class C a where + data F1 a + type F2 a + +main = typeRep (Proxy :: Proxy F) == typeRep (Proxy :: Proxy F1) diff --git a/testsuite/tests/typecheck/should_fail/T9999.stderr b/testsuite/tests/typecheck/should_fail/T9999.stderr new file mode 100644 index 0000000..6fa61d9 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T9999.stderr @@ -0,0 +1,11 @@ + +T9999.hs:13:38: + No instance for (Typeable F1) + (maybe you haven't applied enough arguments to a function?) + arising from a use of ?typeRep? + In the second argument of ?(==)?, namely + ?typeRep (Proxy :: Proxy F1)? + In the expression: + typeRep (Proxy :: Proxy F) == typeRep (Proxy :: Proxy F1) + In an equation for ?main?: + main = typeRep (Proxy :: Proxy F) == typeRep (Proxy :: Proxy F1) From git at git.haskell.org Fri Mar 13 22:18:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 13 Mar 2015 22:18:17 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Rename ty{Con, peRep}Hash to ty{Con, peRep}Fingerprint (cc39344) Message-ID: <20150313221817.B82DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/cc393440b5d890b0944200d5762c49cc70c4ce4b/ghc >--------------------------------------------------------------- commit cc393440b5d890b0944200d5762c49cc70c4ce4b Author: Herbert Valerio Riedel Date: Wed Mar 11 16:36:09 2015 +0100 Rename ty{Con,peRep}Hash to ty{Con,peRep}Fingerprint This is a follow-up change to 56e0ac98c3a439b8757a2e886db259270bdc85f0 See also discussion at https://groups.google.com/d/msg/haskell-core-libraries/e9N3U6nJeQE/V-TvG3G-3x4J (cherry picked from commit 842028b4a624e639dc9ee9a4f92fc208c8206e3f) >--------------------------------------------------------------- cc393440b5d890b0944200d5762c49cc70c4ce4b libraries/base/Data/Typeable.hs | 4 ++-- libraries/base/Data/Typeable/Internal.hs | 10 +++++----- libraries/base/changelog.md | 4 ++-- 3 files changed, 9 insertions(+), 9 deletions(-) diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs index 7e501a5..c30a43d 100644 --- a/libraries/base/Data/Typeable.hs +++ b/libraries/base/Data/Typeable.hs @@ -61,12 +61,12 @@ module Data.Typeable -- * Type representations TypeRep, -- abstract, instance of: Eq, Show, Typeable - typeRepHash, + typeRepFingerprint, rnfTypeRep, showsTypeRep, TyCon, -- abstract, instance of: Eq, Show, Typeable - tyConHash, + tyConFingerprint, tyConString, tyConPackage, tyConModule, diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 4cdc57d..60402f3 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -45,7 +45,7 @@ module Data.Typeable.Internal ( splitPolyTyConApp, funResultTy, typeRepArgs, - typeRepHash, + typeRepFingerprint, rnfTypeRep, showsTypeRep, tyConString, @@ -84,7 +84,7 @@ instance Ord TypeRep where -- | An abstract representation of a type constructor. 'TyCon' objects can -- be built using 'mkTyCon'. data TyCon = TyCon { - tyConHash :: {-# UNPACK #-} !Fingerprint, -- ^ @since 4.8.0.0 + tyConFingerprint :: {-# UNPACK #-} !Fingerprint, -- ^ @since 4.8.0.0 tyConPackage :: String, -- ^ @since 4.5.0.0 tyConModule :: String, -- ^ @since 4.5.0.0 tyConName :: String -- ^ @since 4.5.0.0 @@ -197,8 +197,8 @@ tyConString = tyConName -- | Observe the 'Fingerprint' of a type representation -- -- @since 4.8.0.0 -typeRepHash :: TypeRep -> Fingerprint -typeRepHash (TypeRep fpr _ _ _) = fpr +typeRepFingerprint :: TypeRep -> Fingerprint +typeRepFingerprint (TypeRep fpr _ _ _) = fpr ------------------------------------------------------------- -- @@ -338,7 +338,7 @@ typeLitTypeRep nm = rep where rep = mkTyConApp tc [] tc = TyCon - { tyConHash = fingerprintString (mk pack modu nm) + { tyConFingerprint = fingerprintString (mk pack modu nm) , tyConPackage = pack , tyConModule = modu , tyConName = nm diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index e99c1b1..e2318a8 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -142,8 +142,8 @@ * Restore invariant in `Data (Ratio a)` instance (#10011) - * Add/expose `rnfTypeRep`, `rnfTyCon`, `TypeRepHash`, and - `TyConHash` helpers to `Data.Typeable`. + * Add/expose `rnfTypeRep`, `rnfTyCon`, `typeRepFingerprint`, and + `tyConFingerprint` helpers to `Data.Typeable`. * Define proper `MINIMAL` pragma for `class Ix`. (#10142) From git at git.haskell.org Sat Mar 14 08:07:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Mar 2015 08:07:32 +0000 (UTC) Subject: [commit: ghc] master: Link temporary shared objects with `--no-as-needed` (1b7f597) Message-ID: <20150314080732.654163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1b7f59769052fd8193c6acc561216e070d0ca335/ghc >--------------------------------------------------------------- commit 1b7f59769052fd8193c6acc561216e070d0ca335 Author: Peter Trommler Date: Sat Mar 14 09:05:41 2015 +0100 Link temporary shared objects with `--no-as-needed` Some ELF link editors default to `--as-needed` and record only those libraries in DT_NEEDED tags that are needed to resolve undefined symbols in the shared object to be created. In Template Haskell we rely on all symbols that were defined in modules compiled so far to be available in the current temporary shared object. To prevent the link editor from dropping the DT_NEEDED tag for the previously linked temporary shared object we need to override the link editors default and specify `--no-as-needed` on the command line. This is for GNU ld and GOLD ld. This addresses #10110 TODO: regression test Reviewed By: hvr Differential Revision: https://phabricator.haskell.org/D731 >--------------------------------------------------------------- 1b7f59769052fd8193c6acc561216e070d0ca335 compiler/main/SysTools.hs | 19 ++++++++++++++----- 1 file changed, 14 insertions(+), 5 deletions(-) diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs index aba4a1b..e6e7fa6 100644 --- a/compiler/main/SysTools.hs +++ b/compiler/main/SysTools.hs @@ -690,7 +690,7 @@ in terror). {- Note [Run-time linker info] -See also: Trac #5240, Trac #6063 +See also: Trac #5240, Trac #6063, Trac #10110 Before 'runLink', we need to be sure to get the relevant information about the linker we're using at runtime to see if we need any extra @@ -717,6 +717,13 @@ We cache the LinkerInfo inside DynFlags, since clients may link multiple times. The definition of LinkerInfo is there to avoid a circular dependency. +Some distributions change the link editor's default handling of +ELF DT_NEEDED tags to include only those shared objects that are +needed to resolve undefined symbols. For Template Haskell we need +the last temporary shared library also if it is not needed for the +currently linked temporary shared library. We specify --no-as-needed +to override the default. This flag exists in GNU ld and GNU gold. + -} @@ -753,12 +760,14 @@ getLinkerInfo' dflags = do | any ("GNU ld" `isPrefixOf`) stdo = -- GNU ld specifically needs to use less memory. This especially -- hurts on small object files. Trac #5240. + -- Set DT_NEEDED for all shared libraries. Trac #10110. return (GnuLD $ map Option ["-Wl,--hash-size=31", - "-Wl,--reduce-memory-overheads"]) + "-Wl,--reduce-memory-overheads", + "-Wl,--no-as-needed"]) | any ("GNU gold" `isPrefixOf`) stdo = - -- GNU gold does not require any special arguments. - return (GnuGold []) + -- GNU gold only needs --no-as-needed. Trac #10110. + return (GnuGold [Option "-Wl,--no-as-needed"]) -- Unknown linker. | otherwise = fail "invalid --version output, or linker is unsupported" @@ -875,7 +884,7 @@ runLink dflags args = do linkargs <- neededLinkArgs `fmap` getLinkerInfo dflags let (p,args0) = pgm_l dflags args1 = map Option (getOpts dflags opt_l) - args2 = args0 ++ args1 ++ args ++ linkargs + args2 = args0 ++ linkargs ++ args1 ++ args mb_env <- getGccEnv args2 runSomethingFiltered dflags ld_filter "Linker" p args2 mb_env where From git at git.haskell.org Sat Mar 14 08:11:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Mar 2015 08:11:08 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Move the function strip_quotes to testutil.py (65753a9) Message-ID: <20150314081108.4BD543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/65753a9d3414d52b9a97cb23e3c8cff84f7528e5/ghc >--------------------------------------------------------------- commit 65753a9d3414d52b9a97cb23e3c8cff84f7528e5 Author: Thomas Miedema Date: Fri Mar 13 21:07:15 2015 +0100 Move the function strip_quotes to testutil.py If one runs the testsuite with a profiling compiler, during the import of `testlib.py`, `testlib.py` sets the global variable `gs_working`. To do so, it executes a few statements which require the function `strip_quotes` to be in scope. But that function only gets defined at the very end of testlib.py. This patch moves the definition of `strip_quotes` to testutil.py, which is imported at the very top of testlib.py. This unbreaks the nightly builders. (cherry picked from commit cc07a0ba64b554ffd1ff85757b02cd79d30ed57a) >--------------------------------------------------------------- 65753a9d3414d52b9a97cb23e3c8cff84f7528e5 testsuite/driver/testlib.py | 4 ---- testsuite/driver/testutil.py | 3 +++ 2 files changed, 3 insertions(+), 4 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index fcf86dd..58375c1 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -2271,7 +2271,3 @@ def getStdout(cmd): return stdout else: raise Exception("Need subprocess to get stdout, but don't have it") - -def strip_quotes(s): - # Don't wrap commands to subprocess.call/Popen in quotes. - return s.strip('\'"') diff --git a/testsuite/driver/testutil.py b/testsuite/driver/testutil.py index ec45e93..2cfa8f1 100644 --- a/testsuite/driver/testutil.py +++ b/testsuite/driver/testutil.py @@ -15,3 +15,6 @@ def version_gt(x, y): def version_ge(x, y): return version_to_ints(x) >= version_to_ints(y) +def strip_quotes(s): + # Don't wrap commands to subprocess.call/Popen in quotes. + return s.strip('\'"') From git at git.haskell.org Sat Mar 14 08:11:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Mar 2015 08:11:11 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Link temporary shared objects with `--no-as-needed` (3ea3492) Message-ID: <20150314081111.13FF83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/3ea349220c3b72c97530c32c767e278570d497e4/ghc >--------------------------------------------------------------- commit 3ea349220c3b72c97530c32c767e278570d497e4 Author: Peter Trommler Date: Sat Mar 14 09:05:41 2015 +0100 Link temporary shared objects with `--no-as-needed` Some ELF link editors default to `--as-needed` and record only those libraries in DT_NEEDED tags that are needed to resolve undefined symbols in the shared object to be created. In Template Haskell we rely on all symbols that were defined in modules compiled so far to be available in the current temporary shared object. To prevent the link editor from dropping the DT_NEEDED tag for the previously linked temporary shared object we need to override the link editors default and specify `--no-as-needed` on the command line. This is for GNU ld and GOLD ld. This addresses #10110 TODO: regression test (cherry picked from commit 1b7f59769052fd8193c6acc561216e070d0ca335) >--------------------------------------------------------------- 3ea349220c3b72c97530c32c767e278570d497e4 compiler/main/SysTools.hs | 19 ++++++++++++++----- 1 file changed, 14 insertions(+), 5 deletions(-) diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs index bef8d0c..26e8cf6 100644 --- a/compiler/main/SysTools.hs +++ b/compiler/main/SysTools.hs @@ -688,7 +688,7 @@ in terror). {- Note [Run-time linker info] -See also: Trac #5240, Trac #6063 +See also: Trac #5240, Trac #6063, Trac #10110 Before 'runLink', we need to be sure to get the relevant information about the linker we're using at runtime to see if we need any extra @@ -715,6 +715,13 @@ We cache the LinkerInfo inside DynFlags, since clients may link multiple times. The definition of LinkerInfo is there to avoid a circular dependency. +Some distributions change the link editor's default handling of +ELF DT_NEEDED tags to include only those shared objects that are +needed to resolve undefined symbols. For Template Haskell we need +the last temporary shared library also if it is not needed for the +currently linked temporary shared library. We specify --no-as-needed +to override the default. This flag exists in GNU ld and GNU gold. + -} @@ -751,12 +758,14 @@ getLinkerInfo' dflags = do | any ("GNU ld" `isPrefixOf`) stdo = -- GNU ld specifically needs to use less memory. This especially -- hurts on small object files. Trac #5240. + -- Set DT_NEEDED for all shared libraries. Trac #10110. return (GnuLD $ map Option ["-Wl,--hash-size=31", - "-Wl,--reduce-memory-overheads"]) + "-Wl,--reduce-memory-overheads", + "-Wl,--no-as-needed"]) | any ("GNU gold" `isPrefixOf`) stdo = - -- GNU gold does not require any special arguments. - return (GnuGold []) + -- GNU gold only needs --no-as-needed. Trac #10110. + return (GnuGold [Option "-Wl,--no-as-needed"]) -- Unknown linker. | otherwise = fail "invalid --version output, or linker is unsupported" @@ -873,7 +882,7 @@ runLink dflags args = do linkargs <- neededLinkArgs `fmap` getLinkerInfo dflags let (p,args0) = pgm_l dflags args1 = map Option (getOpts dflags opt_l) - args2 = args0 ++ args1 ++ args ++ linkargs + args2 = args0 ++ linkargs ++ args1 ++ args mb_env <- getGccEnv args2 runSomethingFiltered dflags ld_filter "Linker" p args2 mb_env where From git at git.haskell.org Sat Mar 14 08:18:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Mar 2015 08:18:45 +0000 (UTC) Subject: [commit: ghc] master: We need to import 'cast' on Windows (11314b9) Message-ID: <20150314081845.430DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/11314b936340a0980c27a01400b7dfec2ffdfa42/ghc >--------------------------------------------------------------- commit 11314b936340a0980c27a01400b7dfec2ffdfa42 Author: Edward Z. Yang Date: Sat Mar 14 09:16:44 2015 +0100 We need to import 'cast' on Windows This fixes breakage introduced via 47b5b5c2b2c92ba091313c36489588edadceaa9d Signed-off-by: Edward Z. Yang Reviewed By: hvr Differential Revision: https://phabricator.haskell.org/D732 >--------------------------------------------------------------- 11314b936340a0980c27a01400b7dfec2ffdfa42 libraries/base/GHC/Conc/Sync.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/libraries/base/GHC/Conc/Sync.hs b/libraries/base/GHC/Conc/Sync.hs index 1295982..48a3b2a 100644 --- a/libraries/base/GHC/Conc/Sync.hs +++ b/libraries/base/GHC/Conc/Sync.hs @@ -99,6 +99,8 @@ import Foreign.C #ifndef mingw32_HOST_OS import Data.Dynamic +#else +import Data.Typeable #endif import Data.Maybe From git at git.haskell.org Sat Mar 14 08:19:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Mar 2015 08:19:21 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: We need to import 'cast' on Windows (d6f5b4c) Message-ID: <20150314081921.78D3B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/d6f5b4cf7cf1e3a8946fe6a77ce68ec96baad8fd/ghc >--------------------------------------------------------------- commit d6f5b4cf7cf1e3a8946fe6a77ce68ec96baad8fd Author: Edward Z. Yang Date: Sat Mar 14 09:16:44 2015 +0100 We need to import 'cast' on Windows This fixes breakage introduced via 47b5b5c2b2c92ba091313c36489588edadceaa9d Signed-off-by: Edward Z. Yang (cherry picked from commit 11314b936340a0980c27a01400b7dfec2ffdfa42) >--------------------------------------------------------------- d6f5b4cf7cf1e3a8946fe6a77ce68ec96baad8fd libraries/base/GHC/Conc/Sync.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/libraries/base/GHC/Conc/Sync.hs b/libraries/base/GHC/Conc/Sync.hs index eb07137..0c0f26b 100644 --- a/libraries/base/GHC/Conc/Sync.hs +++ b/libraries/base/GHC/Conc/Sync.hs @@ -104,6 +104,8 @@ import Data.Typeable #ifndef mingw32_HOST_OS import Data.Dynamic +#else +import Data.Typeable #endif import Data.Maybe From git at git.haskell.org Sun Mar 15 07:41:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Mar 2015 07:41:18 +0000 (UTC) Subject: [commit: ghc] master: Update Haddock submodule (cbc7103) Message-ID: <20150315074118.BF0313A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cbc7103044cff890c9916c8418b2f93cbece9b83/ghc >--------------------------------------------------------------- commit cbc7103044cff890c9916c8418b2f93cbece9b83 Author: Herbert Valerio Riedel Date: Sun Mar 15 08:36:49 2015 +0100 Update Haddock submodule This pulls in a cherry-picked commit adding support for the new `--package-name` and `--package-version` flags and thus helps addressing #10115. >--------------------------------------------------------------- cbc7103044cff890c9916c8418b2f93cbece9b83 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 4bb685b..f9ae6aa 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 4bb685bd0f5774584c6bef3f8786daffeac13b56 +Subproject commit f9ae6aaf269474228f368380966fc80b73587832 From git at git.haskell.org Sun Mar 15 07:41:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Mar 2015 07:41:21 +0000 (UTC) Subject: [commit: ghc] master: Update Cabal submodule to latest 1.22.1.2 snapshot (14b78eb) Message-ID: <20150315074121.9A8913A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/14b78eb7390dcf78c104501f4c24ac013a70a766/ghc >--------------------------------------------------------------- commit 14b78eb7390dcf78c104501f4c24ac013a70a766 Author: Herbert Valerio Riedel Date: Sun Mar 15 07:14:32 2015 +0100 Update Cabal submodule to latest 1.22.1.2 snapshot This addresses the Cabal side of #10115 as this pulls in the following two commits: > Make sure to pass the package key to ghc > Haddock: Use --package-{name|version} when available >--------------------------------------------------------------- 14b78eb7390dcf78c104501f4c24ac013a70a766 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index a9958fe..cbd9d53 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit a9958fefc737b223b75babc68ecd3122b9697cd9 +Subproject commit cbd9d53bc028717323417316a5ed10d65c704d87 From git at git.haskell.org Sun Mar 15 08:02:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Mar 2015 08:02:56 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update Cabal submodule to latest 1.22.1.2 snapshot (cb51506) Message-ID: <20150315080256.1942E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/cb51506b02a2ecf7b5e67a8069e61f4e8375ba67/ghc >--------------------------------------------------------------- commit cb51506b02a2ecf7b5e67a8069e61f4e8375ba67 Author: Herbert Valerio Riedel Date: Sun Mar 15 07:14:32 2015 +0100 Update Cabal submodule to latest 1.22.1.2 snapshot This addresses the Cabal side of #10115 as this pulls in the following two commits: > Make sure to pass the package key to ghc > Haddock: Use --package-{name|version} when available (cherry picked from commit 14b78eb7390dcf78c104501f4c24ac013a70a766) >--------------------------------------------------------------- cb51506b02a2ecf7b5e67a8069e61f4e8375ba67 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index a9958fe..cbd9d53 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit a9958fefc737b223b75babc68ecd3122b9697cd9 +Subproject commit cbd9d53bc028717323417316a5ed10d65c704d87 From git at git.haskell.org Mon Mar 16 06:59:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Mar 2015 06:59:29 +0000 (UTC) Subject: [commit: ghc] master: libraries/win32: update submodule (e935a7f) Message-ID: <20150316065929.4BC043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e935a7f4584f02e67196bb1f1978b32f0fdb310c/ghc >--------------------------------------------------------------- commit e935a7f4584f02e67196bb1f1978b32f0fdb310c Author: Austin Seipp Date: Mon Mar 16 01:59:16 2015 -0500 libraries/win32: update submodule Signed-off-by: Austin Seipp >--------------------------------------------------------------- e935a7f4584f02e67196bb1f1978b32f0fdb310c libraries/Win32 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Win32 b/libraries/Win32 index a955d59..8fc5486 160000 --- a/libraries/Win32 +++ b/libraries/Win32 @@ -1 +1 @@ -Subproject commit a955d59c48f8b3bdab7eeea29660d98b0d44343b +Subproject commit 8fc5486f4e31ddeacd46c6b07d62934c3ce8f378 From git at git.haskell.org Mon Mar 16 07:31:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Mar 2015 07:31:16 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: libraries/win32: update submodule (e1bc45c) Message-ID: <20150316073116.3C36C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/e1bc45cee33ec9c4ea9e00c8d479318b4f58216b/ghc >--------------------------------------------------------------- commit e1bc45cee33ec9c4ea9e00c8d479318b4f58216b Author: Austin Seipp Date: Mon Mar 16 02:00:10 2015 -0500 libraries/win32: update submodule Signed-off-by: Austin Seipp >--------------------------------------------------------------- e1bc45cee33ec9c4ea9e00c8d479318b4f58216b libraries/Win32 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Win32 b/libraries/Win32 index a955d59..8fc5486 160000 --- a/libraries/Win32 +++ b/libraries/Win32 @@ -1 +1 @@ -Subproject commit a955d59c48f8b3bdab7eeea29660d98b0d44343b +Subproject commit 8fc5486f4e31ddeacd46c6b07d62934c3ce8f378 From git at git.haskell.org Mon Mar 16 07:31:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Mar 2015 07:31:19 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: libraries/base: Remove redundant import (feccb32) Message-ID: <20150316073119.1A8EE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/feccb32bd54e0d01d4393c0eeaf7da890760664a/ghc >--------------------------------------------------------------- commit feccb32bd54e0d01d4393c0eeaf7da890760664a Author: Austin Seipp Date: Mon Mar 16 02:30:44 2015 -0500 libraries/base: Remove redundant import Signed-off-by: Austin Seipp >--------------------------------------------------------------- feccb32bd54e0d01d4393c0eeaf7da890760664a libraries/base/GHC/Conc/Sync.hs | 4 ---- 1 file changed, 4 deletions(-) diff --git a/libraries/base/GHC/Conc/Sync.hs b/libraries/base/GHC/Conc/Sync.hs index 0c0f26b..eb70a5e 100644 --- a/libraries/base/GHC/Conc/Sync.hs +++ b/libraries/base/GHC/Conc/Sync.hs @@ -98,10 +98,6 @@ module GHC.Conc.Sync import Foreign import Foreign.C -#ifdef mingw32_HOST_OS -import Data.Typeable -#endif - #ifndef mingw32_HOST_OS import Data.Dynamic #else From git at git.haskell.org Mon Mar 16 14:56:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Mar 2015 14:56:31 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #10156 (817d2c3) Message-ID: <20150316145631.290873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/817d2c3436a99d998c79c5f9755c03aa21ced32c/ghc >--------------------------------------------------------------- commit 817d2c3436a99d998c79c5f9755c03aa21ced32c Author: Simon Peyton Jones Date: Mon Mar 16 14:54:50 2015 +0000 Test Trac #10156 >--------------------------------------------------------------- 817d2c3436a99d998c79c5f9755c03aa21ced32c testsuite/tests/typecheck/should_compile/T10156.hs | 15 +++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 16 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T10156.hs b/testsuite/tests/typecheck/should_compile/T10156.hs new file mode 100644 index 0000000..d452122 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T10156.hs @@ -0,0 +1,15 @@ +{-# LANGUAGE FlexibleContexts, TypeFamilies #-} + +module T10156 where + +import Data.Coerce + +data Iso a b = Iso (a -> b) (b -> a) + +coerceIso :: Coercible a b => Iso a b +coerceIso = Iso coerce coerce + +type family F x + +f :: (Coercible a (F b), Coercible c (F b)) => a -> b -> c +f x _ = coerce x diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 7b3fb9f..a4b497e 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -443,3 +443,4 @@ test('T9971', normal, compile, ['']) test('T10031', normal, compile, ['']) test('T10072', normal, compile_fail, ['']) test('T10100', normal, compile, ['']) +test('T10156', normal, compile, ['']) From git at git.haskell.org Mon Mar 16 17:39:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Mar 2015 17:39:32 +0000 (UTC) Subject: [commit: ghc] master: Fix testsuite driver for a profiling compiler (beee618) Message-ID: <20150316173932.8F8983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/beee618c4ab8f725acd4dce3ef8a0d4ce84bb6ec/ghc >--------------------------------------------------------------- commit beee618c4ab8f725acd4dce3ef8a0d4ce84bb6ec Author: Thomas Miedema Date: Sun Mar 15 21:06:39 2015 +0100 Fix testsuite driver for a profiling compiler This should have been part of commit 5258566ee5c8, to allow expansion of '{hp2ps}' in a command string to `config.hp2ps`. Reviewed by: austin Differential Revision: https://phabricator.haskell.org/D734 >--------------------------------------------------------------- beee618c4ab8f725acd4dce3ef8a0d4ce84bb6ec testsuite/driver/testlib.py | 3 +++ 1 file changed, 3 insertions(+) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 1d3ef11..59230ab 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1828,6 +1828,9 @@ def rawSystemWithTimeout(cmd_and_args): # Then, when using the native Python, os.system will invoke the cmd shell def runCmd( cmd ): + # Format cmd using config. Example: cmd='{hpc} report A.tix' + cmd = cmd.format(**config.__dict__) + if_verbose( 3, cmd ) r = 0 if config.os == 'mingw32': From git at git.haskell.org Mon Mar 16 17:39:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Mar 2015 17:39:36 +0000 (UTC) Subject: [commit: ghc] master: Dont call unsafeGlobalDynFlags if it is not set (5166ee9) Message-ID: <20150316173936.412833A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5166ee94e439375a4e6acb80f88ec6ee65476bbd/ghc >--------------------------------------------------------------- commit 5166ee94e439375a4e6acb80f88ec6ee65476bbd Author: Thomas Miedema Date: Mon Mar 16 18:36:59 2015 +0100 Dont call unsafeGlobalDynFlags if it is not set Parsing of static and mode flags happens before any session is started, i.e., before the first call to 'GHC.withGhc'. Therefore, to report errors for invalid usage of these two types of flags, we can not call any function that needs DynFlags, as there are no DynFlags available yet (unsafeGlobalDynFlags is not set either). So we always print "on the commandline" as the location, which is true except for Api users, which is probably ok. When reporting errors for invalid usage of dynamic flags we /can/ make use of DynFlags, and we do so explicitly in DynFlags.parseDynamicFlagsFull. Before, we called unsafeGlobalDynFlags when an invalid (combination of) flag(s) was given on the commandline, resulting in panics (#9963). This regression was introduced in 1d6124de. Also rename showSDocSimple to showSDocUnsafe, to hopefully prevent this from happening again. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D730 GHC Trac Issues: #9963 >--------------------------------------------------------------- 5166ee94e439375a4e6acb80f88ec6ee65476bbd compiler/basicTypes/SrcLoc.hs | 5 +---- compiler/main/CmdLineParser.hs | 24 +++++++++++++++++++++--- compiler/main/DynFlags.hs | 10 +++++++--- compiler/main/StaticFlags.hs | 7 +++++-- compiler/typecheck/TcGenDeriv.hs | 6 ++++-- compiler/utils/Outputable.hs | 8 +++++--- ghc/Main.hs | 9 ++++++--- testsuite/tests/driver/T9963.stderr | 2 ++ testsuite/tests/driver/all.T | 3 +++ 9 files changed, 54 insertions(+), 20 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5166ee94e439375a4e6acb80f88ec6ee65476bbd From git at git.haskell.org Mon Mar 16 19:56:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Mar 2015 19:56:28 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Avoid a < 0 branch for switches on unsigned values (6beea8b) Message-ID: <20150316195628.B7FBA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/6beea8b6c6dcd45272ad12b178a8128547768b09/ghc >--------------------------------------------------------------- commit 6beea8b6c6dcd45272ad12b178a8128547768b09 Author: Joachim Breitner Date: Mon Mar 16 20:55:55 2015 +0100 CmmSwitch: Avoid a < 0 branch for switches on unsigned values >--------------------------------------------------------------- 6beea8b6c6dcd45272ad12b178a8128547768b09 compiler/cmm/CmmSwitch.hs | 17 ++++++++++------- 1 file changed, 10 insertions(+), 7 deletions(-) diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index e0055e2..60fa8ed 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -195,7 +195,7 @@ createSwitchPlan ids = plan where signed = switchTargetsSigned ids - (range, m, wrap) = addRange ids + (range, m, wrap) = addRange signed ids pieces = concatMap breakTooSmall $ splitAtHoles 10 m flatPlan = findSingleValues $ wrap $ mkFlatSwitchPlan signed (switchTargetsDefault ids) range pieces plan = buildTree signed $ flatPlan @@ -207,26 +207,29 @@ createSwitchPlan ids = -- All switch targets surviving this stage needs a range. This adds the range, -- together with the neccessary branching. -addRange :: SwitchTargets -> +addRange :: Bool -> SwitchTargets -> ((Integer, Integer), M.Map Integer Label, FlatSwitchPlan -> FlatSwitchPlan) -- There is a range, nothing to do -addRange (SwitchTargets _ (Just r) _ m) = (r, m, id) +addRange _ (SwitchTargets _ (Just r) _ m) = (r, m, id) -- There is no range, but also no default. We can set the range -- to whatever is found in the map -addRange (SwitchTargets _ Nothing Nothing m) = ((lo,hi), m, id) +addRange _ (SwitchTargets _ Nothing Nothing m) = ((lo,hi), m, id) where (lo,_) = M.findMin m (hi,_) = M.findMax m --- No range, but a default. Create a range, but also emit SwitchPlans for outside the range -addRange (SwitchTargets _ Nothing (Just l) m) +-- No range, but a default. Create a range, but also emit SwitchPlans for +-- outside the range. +addRange signed (SwitchTargets _ Nothing (Just l) m) = ( (lo,hi) , m - , \plan -> (Unconditionally l, lo) `consSL` plan `snocSL` (hi+1, Unconditionally l) + , \plan -> lower_chunk plan `snocSL` (hi+1, Unconditionally l) ) where (lo,_) = M.findMin m (hi,_) = M.findMax m + lower_chunk = if not signed && lo == 0 then id else + ((Unconditionally l, lo) `consSL`) --- From git at git.haskell.org Mon Mar 16 20:32:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Mar 2015 20:32:08 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Avoid a -1 for jump tables (01164fc) Message-ID: <20150316203208.5EDE23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/01164fc91f00245b3c946840027532a1b2c17a22/ghc >--------------------------------------------------------------- commit 01164fc91f00245b3c946840027532a1b2c17a22 Author: Joachim Breitner Date: Mon Mar 16 21:10:59 2015 +0100 CmmSwitch: Avoid a -1 for jump tables >--------------------------------------------------------------- 01164fc91f00245b3c946840027532a1b2c17a22 compiler/cmm/CmmSwitch.hs | 29 ++++++++++++++++++++++++++++- 1 file changed, 28 insertions(+), 1 deletion(-) diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index 60fa8ed..b062964 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -127,10 +127,37 @@ switchTargetsToTable :: SwitchTargets -> (Int, [Maybe Label]) switchTargetsToTable (SwitchTargets _ Nothing _mbdef _branches) = pprPanic "switchTargetsToTable" empty switchTargetsToTable (SwitchTargets _ (Just (lo,hi)) mbdef branches) - = (fromIntegral (-lo), [ labelFor i | i <- [lo..hi] ]) + = (fromIntegral (-start), [ labelFor i | i <- [start..hi] ]) where labelFor i = case M.lookup i branches of Just l -> Just l Nothing -> mbdef + start | lo >= 0 && lo < 2 = 0 -- See Note [Jump Table Offset] + | otherwise = lo + +-- Note [Jump Table Offset] +-- ~~~~~~~~~~~~~~~~~~~~~~~~ +-- +-- Usually, the code for a jump table starting at x will first subtract x from +-- the value, to avoid a large amount of empty entries. But if x is very small, +-- the extra entries are no worse than the subtraction in terms of code size, and +-- not having to do the subtraction is quicker. +-- +-- I.e. instead of +-- _u20N: +-- leaq -1(%r14),%rax +-- jmp *_n20R(,%rax,8) +-- _n20R: +-- .quad _c20p +-- .quad _c20q +-- do +-- _u20N: +-- jmp *_n20Q(,%r14,8) +-- +-- _n20Q: +-- .quad 0 +-- .quad _c20p +-- .quad _c20q +-- .quad _c20r switchTargetsToList :: SwitchTargets -> [Label] switchTargetsToList (SwitchTargets _ _ mbdef branches) From git at git.haskell.org Mon Mar 16 20:32:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Mar 2015 20:32:11 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Name and document all magic numbers in one section (a5fd487) Message-ID: <20150316203211.254AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/a5fd487fa18da43c1e83fe51148e73d2d3719623/ghc >--------------------------------------------------------------- commit a5fd487fa18da43c1e83fe51148e73d2d3719623 Author: Joachim Breitner Date: Mon Mar 16 21:31:36 2015 +0100 CmmSwitch: Name and document all magic numbers in one section >--------------------------------------------------------------- a5fd487fa18da43c1e83fe51148e73d2d3719623 compiler/cmm/CmmSwitch.hs | 39 +++++++++++++++++++++++++++------------ 1 file changed, 27 insertions(+), 12 deletions(-) diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index b062964..11b46ef 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -42,6 +42,28 @@ import qualified Data.Map as M -- statements alone, as we can turn a SwitchTargets value into a nice -- switch-statement in LLVM resp. C, and leave the rest to the compiler. +----------------------------------------------------------------------------- +-- Magic Constants +-- +-- There are a lot of heuristics here that depend on magic values where it is +-- hard to determine the "best" value (for whatever that means). These are the +-- magic values: + +-- | Number of consecutive default values allowed in a jump table. If there are +-- more of them, the jump tables are split. +-- Currently 10, for no particular good reason. +maxJumpTableHole :: Integer +maxJumpTableHole = 10 + +-- | Minimum size of a jump table. If the number is smaller, the switch is +-- implemented using conditionals. +-- Currently 5, because an if-then-else tree of 4 values is nice and compact. +minJumpTableSize :: Int +minJumpTableSize = 5 + +-- | Minimum non-zero offset for a jump table. See Note [Jump Table Offset]. +minJumpTableOffset :: Integer +minJumpTableOffset = 2 ----------------------------------------------------------------------------- @@ -131,8 +153,8 @@ switchTargetsToTable (SwitchTargets _ (Just (lo,hi)) mbdef branches) where labelFor i = case M.lookup i branches of Just l -> Just l Nothing -> mbdef - start | lo >= 0 && lo < 2 = 0 -- See Note [Jump Table Offset] - | otherwise = lo + start | lo >= 0 && lo < minJumpTableOffset = 0 -- See Note [Jump Table Offset] + | otherwise = lo -- Note [Jump Table Offset] -- ~~~~~~~~~~~~~~~~~~~~~~~~ @@ -223,7 +245,7 @@ createSwitchPlan ids = where signed = switchTargetsSigned ids (range, m, wrap) = addRange signed ids - pieces = concatMap breakTooSmall $ splitAtHoles 10 m + pieces = concatMap breakTooSmall $ splitAtHoles maxJumpTableHole m flatPlan = findSingleValues $ wrap $ mkFlatSwitchPlan signed (switchTargetsDefault ids) range pieces plan = buildTree signed $ flatPlan @@ -271,13 +293,6 @@ splitAtHoles holeSize m = map (\range -> restrictMap range m) nonHoles (lo,_) = M.findMin m (hi,_) = M.findMax m --- Note [When to split SwitchTargets] --- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --- --- TODO: What is a sensible number here? Probably at least the size of the code --- for a comparision + a conditional jump + an addition + a relative jump --- For now we use 10. - --- --- Step 3: Avoid small jump tables --- @@ -285,8 +300,8 @@ splitAtHoles holeSize m = map (\range -> restrictMap range m) nonHoles -- (into singleton maps, for now) breakTooSmall :: M.Map Integer a -> [M.Map Integer a] breakTooSmall m - | M.size m > 4 = [m] - | otherwise = [M.singleton k v | (k,v) <- M.toList m] + | M.size m > minJumpTableSize = [m] + | otherwise = [M.singleton k v | (k,v) <- M.toList m] --- --- Step 4: Fill in the blanks From git at git.haskell.org Mon Mar 16 21:40:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Mar 2015 21:40:26 +0000 (UTC) Subject: [commit: ghc] master: Fix build on amd64/solaris. (83afcd1) Message-ID: <20150316214026.A68973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/83afcd174cdbf4fb770371da764f91ca9ad414a7/ghc >--------------------------------------------------------------- commit 83afcd174cdbf4fb770371da764f91ca9ad414a7 Author: Erik de Castro Lopo Date: Fri Mar 13 20:38:13 2015 +0000 Fix build on amd64/solaris. Summary: Commit 71fcc4c096ec0 breaks the 64bit build on Solaris 11. Solaris is a multi-lib OS so both 32bit and 64bit binaries may be run, but by default it compiles to 32bit so that -m64 needs to be added in the appropriate place when compiling for 64 bits. Patch-from: Karel Gardas Reviewers: kgardas, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D733 >--------------------------------------------------------------- 83afcd174cdbf4fb770371da764f91ca9ad414a7 mk/config.mk.in | 1 + 1 file changed, 1 insertion(+) diff --git a/mk/config.mk.in b/mk/config.mk.in index a6f757a..b32f227 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -568,6 +568,7 @@ define set_stage_HSC2HS_OPTS # $1 = stage SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --cflag=,$$(filter-out -O,$$(SRC_CC_OPTS) $$(CONF_CC_OPTS_STAGE$1))) SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --cflag=,$$(CONF_CPP_OPTS_STAGE$1)) +SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --lflag=,$$(CONF_GCC_LINKER_OPTS_STAGE$1)) endef $(eval $(call set_stage_HSC2HS_OPTS,0)) $(eval $(call set_stage_HSC2HS_OPTS,1)) From git at git.haskell.org Tue Mar 17 08:24:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 08:24:16 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Add a test case (3418d2e) Message-ID: <20150317082416.7FBB23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/3418d2eb30e54a4dc7764c633e9002a77da95759/ghc >--------------------------------------------------------------- commit 3418d2eb30e54a4dc7764c633e9002a77da95759 Author: Joachim Breitner Date: Tue Mar 17 09:23:48 2015 +0100 CmmSwitch: Add a test case with a script to generate it. Exhibits problems around MAXINT. >--------------------------------------------------------------- 3418d2eb30e54a4dc7764c633e9002a77da95759 testsuite/tests/codeGen/should_run/CmmSwitch.hs | 210 +++++++++++++++++++++ testsuite/tests/codeGen/should_run/CmmSwitchGen.hs | 86 +++++++++ testsuite/tests/codeGen/should_run/all.T | 1 + 3 files changed, 297 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 3418d2eb30e54a4dc7764c633e9002a77da95759 From git at git.haskell.org Tue Mar 17 10:31:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 10:31:40 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Take into account the range of values of Int# and Word# (6b8421d) Message-ID: <20150317103140.BBA443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/6b8421da148a78f57e745ad7de88faac4eeed8c3/ghc >--------------------------------------------------------------- commit 6b8421da148a78f57e745ad7de88faac4eeed8c3 Author: Joachim Breitner Date: Tue Mar 17 11:30:38 2015 +0100 CmmSwitch: Take into account the range of values of Int# and Word# to avoid problems around MAXINT and avoid unnecessary branches. Simplifies the types and code a bit. >--------------------------------------------------------------- 6b8421da148a78f57e745ad7de88faac4eeed8c3 compiler/cmm/CmmParse.y | 5 ++- compiler/cmm/CmmSwitch.hs | 94 +++++++++++------------------------------ compiler/cmm/PprCmm.hs | 6 +-- compiler/codeGen/StgCmmUtils.hs | 13 +++--- 4 files changed, 37 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 6b8421da148a78f57e745ad7de88faac4eeed8c3 From git at git.haskell.org Tue Mar 17 11:10:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 11:10:34 +0000 (UTC) Subject: [commit: ghc] master: Fix Windows testsuite driver (9987c66) Message-ID: <20150317111034.1F1FA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9987c66d7c3a1186acb5a32e92cd6846d71987a5/ghc >--------------------------------------------------------------- commit 9987c66d7c3a1186acb5a32e92cd6846d71987a5 Author: Thomas Miedema Date: Tue Mar 17 12:08:59 2015 +0100 Fix Windows testsuite driver This got broken in commit 5258566. >--------------------------------------------------------------- 9987c66d7c3a1186acb5a32e92cd6846d71987a5 testsuite/driver/testlib.py | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 59230ab..961f545 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -2272,17 +2272,17 @@ def printFailingTestInfosSummary(file, testInfos): ' (' + ','.join(testInfos[directory][test][reason]) + ')\n') file.write('\n') -def getStdout(cmd): +def getStdout(cmd_and_args): if have_subprocess: - p = subprocess.Popen(strip_quotes(cmd), + p = subprocess.Popen([strip_quotes(cmd_and_args[0])] + cmd_and_args[1:], stdout=subprocess.PIPE, stderr=subprocess.PIPE) (stdout, stderr) = p.communicate() r = p.wait() if r != 0: - raise Exception("Command failed: " + str(cmd)) + raise Exception("Command failed: " + str(cmd_and_args)) if stderr != '': - raise Exception("stderr from command: " + str(cmd)) + raise Exception("stderr from command: " + str(cmd_and_args)) return stdout else: raise Exception("Need subprocess to get stdout, but don't have it") From git at git.haskell.org Tue Mar 17 12:00:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 12:00:35 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Add Word# test to the test case (1a7425f) Message-ID: <20150317120035.A8FBF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/1a7425fd530c21da5507b2efef52464b697e96ac/ghc >--------------------------------------------------------------- commit 1a7425fd530c21da5507b2efef52464b697e96ac Author: Joachim Breitner Date: Tue Mar 17 12:40:30 2015 +0100 CmmSwitch: Add Word# test to the test case >--------------------------------------------------------------- 1a7425fd530c21da5507b2efef52464b697e96ac testsuite/tests/codeGen/should_run/CmmSwitch.hs | 658 ++++++++++++++++++--- testsuite/tests/codeGen/should_run/CmmSwitchGen.hs | 34 +- testsuite/tests/codeGen/should_run/all.T | 2 +- 3 files changed, 623 insertions(+), 71 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1a7425fd530c21da5507b2efef52464b697e96ac From git at git.haskell.org Tue Mar 17 12:00:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 12:00:38 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Remove Literal.onlyWithinBounds, not needed any more (4356473) Message-ID: <20150317120038.6D37E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/43564736edb645c2c3418e96df77abd37e9a7c20/ghc >--------------------------------------------------------------- commit 43564736edb645c2c3418e96df77abd37e9a7c20 Author: Joachim Breitner Date: Tue Mar 17 12:42:24 2015 +0100 Remove Literal.onlyWithinBounds, not needed any more >--------------------------------------------------------------- 43564736edb645c2c3418e96df77abd37e9a7c20 compiler/basicTypes/Literal.hs | 11 ----------- 1 file changed, 11 deletions(-) diff --git a/compiler/basicTypes/Literal.hs b/compiler/basicTypes/Literal.hs index 8be78a2..08dfafe 100644 --- a/compiler/basicTypes/Literal.hs +++ b/compiler/basicTypes/Literal.hs @@ -30,7 +30,6 @@ module Literal , inIntRange, inWordRange, tARGET_MAX_INT, inCharRange , isZeroLit , litFitsInChar - , onlyWithinBounds , litValue -- ** Coercions @@ -370,16 +369,6 @@ litIsLifted :: Literal -> Bool litIsLifted (LitInteger {}) = True litIsLifted _ = False --- | x `onlyWithinBounds` (l,h) is true if l <= y < h ==> x = y -onlyWithinBounds :: Literal -> (Literal, Literal) -> Bool -onlyWithinBounds (MachChar x) (MachChar l, MachChar h) = x == l && succ x == h -onlyWithinBounds (MachInt x) (MachInt l, MachInt h) = x == l && succ x == h -onlyWithinBounds (MachWord x) (MachWord l, MachWord h) = x == l && succ x == h -onlyWithinBounds (MachInt64 x) (MachInt64 l, MachInt64 h) = x == l && succ x == h -onlyWithinBounds (MachWord64 x) (MachWord64 l, MachWord64 h) = x == l && succ x == h -onlyWithinBounds _ _ = False - - {- Types ~~~~~ From git at git.haskell.org Tue Mar 17 12:00:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 12:00:42 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Use a different filename for the test as for the ghc module (7711461) Message-ID: <20150317120042.1E82C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/7711461e0689981369516eb4979d9e5a0ba29a03/ghc >--------------------------------------------------------------- commit 7711461e0689981369516eb4979d9e5a0ba29a03 Author: Joachim Breitner Date: Tue Mar 17 12:59:44 2015 +0100 CmmSwitch: Use a different filename for the test as for the ghc module >--------------------------------------------------------------- 7711461e0689981369516eb4979d9e5a0ba29a03 testsuite/tests/codeGen/should_run/CmmSwitch.hs | 736 --------------------- .../tests/codeGen/should_run/CmmSwitchTest.hs | 507 ++++++++++++++ .../{CmmSwitchGen.hs => CmmSwitchTestGen.hs} | 17 +- testsuite/tests/codeGen/should_run/all.T | 2 +- 4 files changed, 518 insertions(+), 744 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7711461e0689981369516eb4979d9e5a0ba29a03 From git at git.haskell.org Tue Mar 17 12:00:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 12:00:44 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Add -ddump-cmm-switch, for consistency (800b80e) Message-ID: <20150317120044.C763C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/800b80eb7f4398f71f918d8a74f649e4ee33039d/ghc >--------------------------------------------------------------- commit 800b80eb7f4398f71f918d8a74f649e4ee33039d Author: Joachim Breitner Date: Tue Mar 17 13:00:25 2015 +0100 Add -ddump-cmm-switch, for consistency >--------------------------------------------------------------- 800b80eb7f4398f71f918d8a74f649e4ee33039d compiler/cmm/CmmPipeline.hs | 3 +-- compiler/main/DynFlags.hs | 2 ++ 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/compiler/cmm/CmmPipeline.hs b/compiler/cmm/CmmPipeline.hs index 7bbbe97..eb89325 100644 --- a/compiler/cmm/CmmPipeline.hs +++ b/compiler/cmm/CmmPipeline.hs @@ -74,8 +74,7 @@ cpsTop hsc_env proc = g <- {-# SCC "createSwitchPlans" #-} runUniqSM $ cmmCreateSwitchPlans dflags g - dump Opt_D_dump_cmm_cfg "Post switch plan" g - -- TODO: dump Opt_D_dump_cmm_sp "Layout Stack" g + dump Opt_D_dump_cmm_switch "Post switch plan" g ----------- Proc points ------------------------------------------------- let call_pps = {-# SCC "callProcPoints" #-} callProcPoints g diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index ef9b4e6..dfe2b75 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -241,6 +241,7 @@ data DumpFlag -- enabled if you run -ddump-cmm | Opt_D_dump_cmm_cfg | Opt_D_dump_cmm_cbe + | Opt_D_dump_cmm_switch | Opt_D_dump_cmm_proc | Opt_D_dump_cmm_sink | Opt_D_dump_cmm_sp @@ -2444,6 +2445,7 @@ dynamic_flags = [ , defGhcFlag "ddump-cmm-raw" (setDumpFlag Opt_D_dump_cmm_raw) , defGhcFlag "ddump-cmm-cfg" (setDumpFlag Opt_D_dump_cmm_cfg) , defGhcFlag "ddump-cmm-cbe" (setDumpFlag Opt_D_dump_cmm_cbe) + , defGhcFlag "ddump-cmm-switch" (setDumpFlag Opt_D_dump_cmm_switch) , defGhcFlag "ddump-cmm-proc" (setDumpFlag Opt_D_dump_cmm_proc) , defGhcFlag "ddump-cmm-sink" (setDumpFlag Opt_D_dump_cmm_sink) , defGhcFlag "ddump-cmm-sp" (setDumpFlag Opt_D_dump_cmm_sp) From git at git.haskell.org Tue Mar 17 12:03:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 12:03:42 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Replace TODO by a reference to the test case (9e2a5e0) Message-ID: <20150317120342.99ADC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/9e2a5e02d0a7e3d540c4e36fd349f61c1f7da2dd/ghc >--------------------------------------------------------------- commit 9e2a5e02d0a7e3d540c4e36fd349f61c1f7da2dd Author: Joachim Breitner Date: Tue Mar 17 13:03:36 2015 +0100 CmmSwitch: Replace TODO by a reference to the test case >--------------------------------------------------------------- 9e2a5e02d0a7e3d540c4e36fd349f61c1f7da2dd compiler/cmm/CmmSwitch.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index c44c37c..d91d693 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -138,8 +138,8 @@ switchTargetsSigned (SwitchTargets signed _ _ _) = signed -- switchTargetsToTable creates a dense jump table, usable for code generation. -- Returns an offset to add to the value; the list is 0-based on the result --- --- TODO: Is the conversion from Integral to Int fishy? +-- The conversion from Integer to Int is a bit of a wart, but works due to +-- wrap-around arithmetic (as verified by the CmmSwitchTest test case). switchTargetsToTable :: SwitchTargets -> (Int, [Maybe Label]) switchTargetsToTable (SwitchTargets _ (lo,hi) mbdef branches) = (fromIntegral (-start), [ labelFor i | i <- [start..hi] ]) From git at git.haskell.org Tue Mar 17 12:06:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 12:06:21 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Make haddock happier (8bfea7a) Message-ID: <20150317120621.3D6923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/8bfea7a949b815ddbf00102e94ca2535de3a93f2/ghc >--------------------------------------------------------------- commit 8bfea7a949b815ddbf00102e94ca2535de3a93f2 Author: Joachim Breitner Date: Tue Mar 17 13:06:25 2015 +0100 CmmSwitch: Make haddock happier >--------------------------------------------------------------- 8bfea7a949b815ddbf00102e94ca2535de3a93f2 compiler/cmm/CmmNode.hs | 4 ++-- compiler/cmm/CmmSwitch.hs | 8 ++++---- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index 3bdc70f..45538d3 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -91,8 +91,8 @@ data CmmNode e x where } -> CmmNode O C CmmSwitch - :: CmmExpr -- ^ Scrutinee, of some integral type - -> SwitchTargets -- ^ Cases. See [Note SwitchTargets] + :: CmmExpr -- Scrutinee, of some integral type + -> SwitchTargets -- Cases. See [Note SwitchTargets] -> CmmNode O C CmmCall :: { -- A native call or tail call diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index d91d693..2fd9ef5 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -91,10 +91,10 @@ minJumpTableOffset = 2 -- See Note [SwitchTargets] data SwitchTargets = SwitchTargets - Bool -- ^ Signed values - (Integer, Integer) -- ^ Range - (Maybe Label) -- ^ Default value - (M.Map Integer Label) -- ^ The branches + Bool -- Signed values + (Integer, Integer) -- Range + (Maybe Label) -- Default value + (M.Map Integer Label) -- The branches deriving (Show, Eq) -- mkSwitchTargets normalises the map a bit: From git at git.haskell.org Tue Mar 17 12:15:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 12:15:18 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Major rewrite: Pt 1: Syntax (a3fa61c) Message-ID: <20150317121518.4D96F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/a3fa61cf06324ad5f37349788280ac6fc2c00235/ghc >--------------------------------------------------------------- commit a3fa61cf06324ad5f37349788280ac6fc2c00235 Author: George Karachalias Date: Tue Mar 17 13:14:27 2015 +0100 Major rewrite: Pt 1: Syntax Also parts of translation >--------------------------------------------------------------- a3fa61cf06324ad5f37349788280ac6fc2c00235 compiler/deSugar/Check.hs | 136 ++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 136 insertions(+) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 8719a7f..d984ea5 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -6,6 +6,7 @@ {-# OPTIONS_GHC -Wwarn #-} -- unused variables {-# LANGUAGE CPP #-} +{-# LANGUAGE DataKinds, GADTs, KindSignatures #-} module Check ( checkpm, PmResult, pprUncovered, toTcTypeBag ) where @@ -46,6 +47,13 @@ import MonadUtils -- MonadIO import Var (EvVar) import Type +import UniqSupply ( UniqSupply + , splitUniqSupply -- :: UniqSupply -> (UniqSupply, UniqSupply) + , listSplitUniqSupply -- :: UniqSupply -> [UniqSupply] + , uniqFromSupply -- :: UniqSupply -> Unique + , uniqsFromSupply -- :: UniqSupply -> [Unique] + , takeUniqFromSupply ) -- :: UniqSupply -> (Unique, UniqSupply) + {- This module checks pattern matches for: \begin{enumerate} @@ -705,3 +713,131 @@ To check this match, we should perform arbitrary computations at compile time returning a @Nothing at . -} + + + +-- ---------------------------------------------------------------------------- +-- | Rewrite the whole thing + +-- | A pattern matching constraint may either be +-- * A term-level constraint: always of the form: x ~= e +-- * A type-level constraint: tau ~ tau and everything else the system supports +data PmConstraint = TmConstraint Id (HsExpr Id) + | TyConstraint [EvVar] -- we usually add more than one + +data Abstraction = P -- Pattern abstraction + | V -- Value abstraction + +{- COMEHERE: Replace PmPat2 with simple PmPat when the time comes -} +{- COMEHERE: Ignore lazy and strict patterns for now -} + +data PmPat2 :: Abstraction -> * where +-- GLetAbs :: PmPat2 P -> HsExpr Id -> PmPat2 P -- Guard: let P = e (lazy) + GBindAbs :: PmPat2 P -> HsExpr Id -> PmPat2 P -- Guard: P <- e (strict) + ConAbs :: DataCon -> [PmPat2 abs] -> PmPat2 abs -- Constructor: K ps + VarAbs :: Id -> PmPat2 abs -- Variable: x + +type ValAbs = PmPat2 V -- Either ConAbs or VarAbs (No Guards in it) +type PatAbs = PmPat2 P -- All possible forms +type PatternVec = [PatAbs] -- Just a type synonym for pattern vectors ps + +data ValSetAbs + = Empty -- {} + | Union ValSetAbs ValSetAbs -- S1 u S2 + | Singleton -- { |- empty |> empty } + | Constraint [PmConstraint] ValSetAbs -- Extend Delta + | Cons ValAbs ValSetAbs -- map (ucon u) vs + +-- ----------------------------------------------------------------------- +-- | Transform a Pat Id into a list of (PmPat Id) -- Note [Translation to PmPat] + +-- Syntax only for now, NO TYPES USED +translatePat :: UniqSupply -> Pat Id -> PatternVec -- Do not return UniqSupply. It is just for us (we need laziness) +translatePat usupply pat = case pat of + WildPat ty -> [mkPmVar usupply ty] + VarPat id -> [VarAbs id] + ParPat p -> translatePat usupply (unLoc p) + LazyPat p -> translatePat usupply (unLoc p) -- COMEHERE: We ignore laziness for now + BangPat p -> translatePat usupply (unLoc p) -- COMEHERE: We ignore strictness for now + AsPat lid p -> translatePat usupply (unLoc p) -- COMEHERE: FIXME: `lid' may appear in view patterns etc. + SigPatOut p ty -> translatePat usupply (unLoc p) -- COMEHERE: FIXME: What to do with the ty?? + CoPat wrapper p ty -> error "COMEHERE: FIXME: CoPat" -- CAREFUL WITH THIS + NPlusKPat n k ge minus -> error "COMEHERE" + ViewPat lexpr lpat arg_ty -> error "COMEHERE" + ListPat _ _ (Just (_,_)) -> error "COMEHERE: FIXME: Overloaded List" + ConPatOut { pat_con = L _ (PatSynCon _) } -> error "COMEHERE: FIXME: Pattern Synonym" -- PATTERN SYNONYM - WHAT TO DO WITH IT? + + ConPatOut { pat_con = L _ (RealDataCon con), pat_args = ps } -> -- DO WE NEED OTHER STUFF FROM IT? + [ConAbs con (translateConPats usupply con ps)] + + NPat lit mb_neg eq -> -- COMEHERE: Double check this. Also do something with the fixity? + let var = mkPmId usupply (hsPatType pat) + var_pat = VarAbs var + hs_var = noLoc (HsVar var) + pattern = ConAbs trueDataCon [] -- COMEHERE: I do not like the noLoc thing + expr_lit = noLoc (negateOrNot mb_neg lit) -- COMEHERE: I do not like the noLoc thing + expr = OpApp hs_var (noLoc eq) no_fixity expr_lit -- COMEHERE: I do not like the noLoc thing + in [VarAbs var, GBindAbs pattern expr] + + LitPat lit -> [mkPmVar usupply (hsPatType pat)] -- COMEHERE: Wrong. Should be like NPat (which eq to use?) + + ListPat ps ty Nothing -> -- WHAT TO DO WITH TY?? + let tidy_ps = translatePats usupply (map unLoc ps) + mkListPat x y = [ConAbs consDataCon (x++y)] + in foldr mkListPat [ConAbs nilDataCon []] tidy_ps + + PArrPat ps tys -> -- WHAT TO DO WITH TYS?? + let tidy_ps = translatePats usupply (map unLoc ps) + fake_con = parrFakeCon (length ps) + in [ConAbs fake_con (concat tidy_ps)] + + TuplePat ps boxity tys -> -- WHAT TO DO WITH TYS?? + let tidy_ps = translatePats usupply (map unLoc ps) + tuple_con = tupleCon (boxityNormalTupleSort boxity) (length ps) + in [ConAbs tuple_con (concat tidy_ps)] + + -- -------------------------------------------------------------------------- + -- Not supposed to happen + ConPatIn {} -> panic "Check.translatePat: ConPatIn" + SplicePat {} -> panic "Check.translatePat: SplicePat" + QuasiQuotePat {} -> panic "Check.translatePat: QuasiQuotePat" + SigPatIn {} -> panic "Check.translatePat: SigPatIn" + +no_fixity :: a +no_fixity = panic "COMEHERE: no fixity!!" + +negateOrNot :: Maybe (SyntaxExpr Id) -> HsOverLit Id -> HsExpr Id +negateOrNot Nothing lit = HsOverLit lit +negateOrNot (Just neg) lit = NegApp (noLoc (HsOverLit lit)) neg -- COMEHERE: I do not like the noLoc thing + +translatePats :: UniqSupply -> [Pat Id] -> [PatternVec] -- Do not concatenate them (sometimes we need them separately) +translatePats usupply pats = map (uncurry translatePat) uniqs_pats + where uniqs_pats = listSplitUniqSupply usupply `zip` pats + +translateConPats :: UniqSupply -> DataCon -> HsConPatDetails Id -> PatternVec +translateConPats usupply _ (PrefixCon ps) = concat (translatePats usupply (map unLoc ps)) +translateConPats usupply _ (InfixCon p1 p2) = concat (translatePats usupply (map unLoc [p1,p2])) +translateConPats usupply c (RecCon (HsRecFields fs _)) + | null fs = map (uncurry mkPmVar) $ listSplitUniqSupply usupply `zip` dataConOrigArgTys c + | otherwise = concat (translatePats usupply (map (unLoc . snd) all_pats)) + where + -- COMEHERE: The functions below are ugly and they do not care much about types too + field_pats = map (\lbl -> (lbl, noLoc (WildPat (dataConFieldType c lbl)))) (dataConFieldLabels c) + all_pats = foldr (\(L _ (HsRecField id p _)) acc -> insertNm (getName (unLoc id)) p acc) + field_pats fs + + insertNm nm p [] = [(nm,p)] + insertNm nm p (x@(n,_):xs) + | nm == n = (nm,p):xs + | otherwise = x : insertNm nm p xs + +mkPmVar :: UniqSupply -> Type -> PmPat2 abs +mkPmVar usupply ty = VarAbs (mkPmId usupply ty) + +mkPmId :: UniqSupply -> Type -> Id +mkPmId usupply ty = mkLocalId name ty + where + unique = uniqFromSupply usupply + occname = mkVarOccFS (fsLit (show unique)) + name = mkInternalName unique occname noSrcSpan + From git at git.haskell.org Tue Mar 17 12:38:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 12:38:15 +0000 (UTC) Subject: [commit: ghc] master: Refactor the extra-deps stuff for hs-boot (9c9e973) Message-ID: <20150317123815.477E73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9c9e973904ab2c637321da734a8b8588fd11c710/ghc >--------------------------------------------------------------- commit 9c9e973904ab2c637321da734a8b8588fd11c710 Author: Simon Peyton Jones Date: Wed Mar 11 22:58:15 2015 +0000 Refactor the extra-deps stuff for hs-boot See Note [Extra dependencies from .hs-boot files] in RnSource No change in behaviour >--------------------------------------------------------------- 9c9e973904ab2c637321da734a8b8588fd11c710 compiler/basicTypes/Name.hs | 14 ++++++++- compiler/rename/RnSource.hs | 65 ++++++++++++++++++++++++---------------- compiler/rename/RnSplice.hs | 4 +-- compiler/typecheck/TcHsSyn.hs | 14 ++++++--- compiler/typecheck/TcRnDriver.hs | 24 +++++++-------- compiler/typecheck/TcRnTypes.hs | 2 ++ 6 files changed, 77 insertions(+), 46 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9c9e973904ab2c637321da734a8b8588fd11c710 From git at git.haskell.org Tue Mar 17 12:38:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 12:38:18 +0000 (UTC) Subject: [commit: ghc] master: Comments, white space, and small refactoring (cf6c307) Message-ID: <20150317123818.21B323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cf6c30719e503bf67c74b3790ae3adf7e0b81180/ghc >--------------------------------------------------------------- commit cf6c30719e503bf67c74b3790ae3adf7e0b81180 Author: Simon Peyton Jones Date: Mon Mar 16 23:53:14 2015 +0000 Comments, white space, and small refactoring The only real change is a new type synonym ImpRuleEdges No significant changes at all >--------------------------------------------------------------- cf6c30719e503bf67c74b3790ae3adf7e0b81180 compiler/simplCore/OccurAnal.hs | 68 +++++++++++++++++++++++------------------ 1 file changed, 39 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 cf6c30719e503bf67c74b3790ae3adf7e0b81180 From git at git.haskell.org Tue Mar 17 12:38:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 12:38:20 +0000 (UTC) Subject: [commit: ghc] master: Move declaration of Rulebase from Rules to CoreSyn (dbd9299) Message-ID: <20150317123820.ED2223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dbd929971c05b5a05129029657a354ddfb658e61/ghc >--------------------------------------------------------------- commit dbd929971c05b5a05129029657a354ddfb658e61 Author: Simon Peyton Jones Date: Tue Mar 17 00:00:31 2015 +0000 Move declaration of Rulebase from Rules to CoreSyn This allow HscTypes to import CoreSyn rather than Rules, which makes module loops easier to avoid. At one point in my recent travels this was important; I'm not sure it's so important now, but it's a good thing anyway. In any case CoreRule is defined in CoreSyn, so this move make sense. >--------------------------------------------------------------- dbd929971c05b5a05129029657a354ddfb658e61 compiler/coreSyn/CoreSyn.hs | 8 +++++++- compiler/main/HscTypes.hs | 3 +-- compiler/simplCore/CoreMonad.hs | 1 - compiler/simplCore/SimplCore.hs | 9 +++++++-- compiler/simplCore/SimplMonad.hs | 2 +- compiler/specialise/Rules.hs | 8 +------- 6 files changed, 17 insertions(+), 14 deletions(-) diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index 32ebd8a..86939bd 100644 --- a/compiler/coreSyn/CoreSyn.hs +++ b/compiler/coreSyn/CoreSyn.hs @@ -71,7 +71,7 @@ module CoreSyn ( deAnnotate, deAnnotate', deAnnAlt, collectAnnBndrs, -- * Core rule data types - CoreRule(..), -- CoreSubst, CoreTidy, CoreFVs, PprCore only + CoreRule(..), RuleBase, RuleName, RuleFun, IdUnfoldingFun, InScopeEnv, -- ** Operations on 'CoreRule's @@ -91,6 +91,7 @@ import Var import Type import Coercion import Name +import NameEnv( NameEnv ) import Literal import DataCon import Module @@ -708,6 +709,11 @@ The CoreRule type and its friends are dealt with mainly in CoreRules, but CoreFVs, Subst, PprCore, CoreTidy also inspect the representation. -} +-- | Gathers a collection of 'CoreRule's. Maps (the name of) an 'Id' to its rules +type RuleBase = NameEnv [CoreRule] + -- The rules are are unordered; + -- we sort out any overlaps on lookup + -- | A 'CoreRule' is: -- -- * \"Local\" if the function it is a rule for is defined in the diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs index 09f643c..90ed559 100644 --- a/compiler/main/HscTypes.hs +++ b/compiler/main/HscTypes.hs @@ -140,8 +140,7 @@ import Avail import Module import InstEnv ( InstEnv, ClsInst, identicalClsInstHead ) import FamInstEnv -import Rules ( RuleBase ) -import CoreSyn ( CoreProgram ) +import CoreSyn ( CoreProgram, RuleBase ) import Name import NameEnv import NameSet diff --git a/compiler/simplCore/CoreMonad.hs b/compiler/simplCore/CoreMonad.hs index e9c828d..dec41bb 100644 --- a/compiler/simplCore/CoreMonad.hs +++ b/compiler/simplCore/CoreMonad.hs @@ -62,7 +62,6 @@ import HscTypes import Module import DynFlags import StaticFlags -import Rules ( RuleBase ) import BasicTypes ( CompilerPhase(..) ) import Annotations diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index 3e82084..0fd929a 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -15,7 +15,7 @@ import CoreSyn import CoreSubst import HscTypes import CSE ( cseProgram ) -import Rules ( RuleBase, emptyRuleBase, mkRuleBase, unionRuleBase, +import Rules ( emptyRuleBase, mkRuleBase, unionRuleBase, extendRuleBaseList, ruleCheckProgram, addSpecInfo, ) import PprCore ( pprCoreBindings, pprCoreExpr ) import OccurAnal ( occurAnalysePgm, occurAnalyseExpr ) @@ -625,7 +625,8 @@ simplifyPgmIO pass@(CoreDoSimplify max_iterations mode) InitialPhase -> (mg_vect_decls guts, vectVars) _ -> ([], vectVars) ; tagged_binds = {-# SCC "OccAnal" #-} - occurAnalysePgm this_mod active_rule rules maybeVects maybeVectVars binds + occurAnalysePgm this_mod active_rule rules + maybeVects maybeVectVars binds } ; Err.dumpIfSet_dyn dflags Opt_D_dump_occur_anal "Occurrence analysis" (pprCoreBindings tagged_binds); @@ -646,6 +647,10 @@ simplifyPgmIO pass@(CoreDoSimplify max_iterations mode) -- Simplify the program (env1, counts1) <- initSmpl dflags rule_base2 fam_envs us1 sz simpl_binds ; + -- Apply the substitution to rules defined in this module + -- for imported Ids. Eg RULE map my_f = blah + -- If we have a substitution my_f :-> other_f, we'd better + -- apply it to the rule to, or it'll never match let { binds1 = getFloatBinds env1 ; rules1 = substRulesForImportedIds (mkCoreSubst (text "imp-rules") env1) rules } ; diff --git a/compiler/simplCore/SimplMonad.hs b/compiler/simplCore/SimplMonad.hs index 0069106..fbf23d7 100644 --- a/compiler/simplCore/SimplMonad.hs +++ b/compiler/simplCore/SimplMonad.hs @@ -22,7 +22,7 @@ module SimplMonad ( import Id ( Id, mkSysLocal ) import Type ( Type ) import FamInstEnv ( FamInstEnv ) -import Rules ( RuleBase ) +import CoreSyn ( RuleBase ) import UniqSupply import DynFlags import CoreMonad diff --git a/compiler/specialise/Rules.hs b/compiler/specialise/Rules.hs index b66d973..e6e5359 100644 --- a/compiler/specialise/Rules.hs +++ b/compiler/specialise/Rules.hs @@ -9,9 +9,6 @@ -- | Functions for collecting together and applying rewrite rules to a module. -- The 'CoreRule' datatype itself is declared elsewhere. module Rules ( - -- * RuleBase - RuleBase, - -- ** Constructing emptyRuleBase, mkRuleBase, extendRuleBaseList, unionRuleBase, pprRuleBase, @@ -315,10 +312,7 @@ but that isn't quite right: ************************************************************************ -} --- | Gathers a collection of 'CoreRule's. Maps (the name of) an 'Id' to its rules -type RuleBase = NameEnv [CoreRule] - -- The rules are are unordered; - -- we sort out any overlaps on lookup +-- RuleBase itself is defined in CoreSyn, along with CoreRule emptyRuleBase :: RuleBase emptyRuleBase = emptyNameEnv From git at git.haskell.org Tue Mar 17 12:49:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 12:49:42 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Be explicit that CmmSwitch only imports Label from Compiler.Hoopl (4378e87) Message-ID: <20150317124942.2208D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/4378e87b7c2598406df8dc8a14aff89e3c14963f/ghc >--------------------------------------------------------------- commit 4378e87b7c2598406df8dc8a14aff89e3c14963f Author: Joachim Breitner Date: Tue Mar 17 13:49:46 2015 +0100 Be explicit that CmmSwitch only imports Label from Compiler.Hoopl >--------------------------------------------------------------- 4378e87b7c2598406df8dc8a14aff89e3c14963f compiler/cmm/CmmSwitch.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index 2fd9ef5..130e7e4 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -11,7 +11,7 @@ module CmmSwitch ( ) where import Outputable -import Compiler.Hoopl +import Compiler.Hoopl (Label) import Data.Maybe import Data.List (groupBy) From git at git.haskell.org Tue Mar 17 15:05:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 15:05:18 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Add haddock comments to all new exported top-level entities (e965edc) Message-ID: <20150317150518.AC1813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/e965edc31800b809eaa4266d8932f9af1000d95a/ghc >--------------------------------------------------------------- commit e965edc31800b809eaa4266d8932f9af1000d95a Author: Joachim Breitner Date: Tue Mar 17 16:04:43 2015 +0100 Add haddock comments to all new exported top-level entities (although it partly states the obvoius, and partly replicates information contained in the Notes.) >--------------------------------------------------------------- e965edc31800b809eaa4266d8932f9af1000d95a compiler/basicTypes/Literal.hs | 2 ++ compiler/cmm/CmmCreateSwitchPlans.hs | 2 ++ compiler/cmm/CmmSwitch.hs | 36 +++++++++++++++++++++++++----------- 3 files changed, 29 insertions(+), 11 deletions(-) diff --git a/compiler/basicTypes/Literal.hs b/compiler/basicTypes/Literal.hs index 08dfafe..ced05a4 100644 --- a/compiler/basicTypes/Literal.hs +++ b/compiler/basicTypes/Literal.hs @@ -271,6 +271,8 @@ isZeroLit (MachFloat 0) = True isZeroLit (MachDouble 0) = True isZeroLit _ = False +-- | Returns the 'Integer' contained in the 'Literal', for when that makes +-- sense, i.e. for 'Char', 'Int', 'Word' and 'LitInteger'. litValue :: Literal -> Integer litValue (MachChar c) = toInteger $ ord c litValue (MachInt i) = i diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmCreateSwitchPlans.hs index 089839d..0fac30c 100644 --- a/compiler/cmm/CmmCreateSwitchPlans.hs +++ b/compiler/cmm/CmmCreateSwitchPlans.hs @@ -26,6 +26,8 @@ import DynFlags -- SwitchTargets, a data type exported abstractly by CmmSwitch. -- +-- | Traverses the 'CmmGraph', making sure that 'CmmSwitch' are suitable for +-- code generation. cmmCreateSwitchPlans :: DynFlags -> CmmGraph -> UniqSM CmmGraph cmmCreateSwitchPlans dflags g = do blocks' <- concat `fmap` mapM (visitSwitches dflags) (toBlockList g) diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index 130e7e4..800ee7d 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -88,7 +88,9 @@ minJumpTableOffset = 2 -- See switchTargetsToTable. --- See Note [SwitchTargets] +-- | A value of type SwitchTargets contains the alternatives for a 'CmmSwitch' +-- value, and knows whether the value is signed, the possible range, an +-- optional default value and a map from values to jump labels. data SwitchTargets = SwitchTargets Bool -- Signed values @@ -97,10 +99,10 @@ data SwitchTargets = (M.Map Integer Label) -- The branches deriving (Show, Eq) --- mkSwitchTargets normalises the map a bit: +-- | The smart constructr mkSwitchTargets normalises the map a bit: -- * No entries outside the range -- * No entries equal to the default --- * No default if there is a range, and all elements have explicit values +-- * No default if all elements have explicit values mkSwitchTargets :: Bool -> (Integer, Integer) -> Maybe Label -> M.Map Integer Label -> SwitchTargets mkSwitchTargets signed range@(lo,hi) mbdef ids = SwitchTargets signed range mbdef' ids' @@ -120,24 +122,29 @@ mkSwitchTargets signed range@(lo,hi) mbdef ids defaultNeeded = fromIntegral (M.size ids') /= hi-lo+1 +-- | Changes all labels mentioned in the SwitchTargets value mapSwitchTargets :: (Label -> Label) -> SwitchTargets -> SwitchTargets mapSwitchTargets f (SwitchTargets signed range mbdef branches) = SwitchTargets signed range (fmap f mbdef) (fmap f branches) +-- | Returns the list of non-default branches of the SwitchTargets value switchTargetsCases :: SwitchTargets -> [(Integer, Label)] switchTargetsCases (SwitchTargets _ _ _ branches) = M.toList branches +-- | Return the default label of the SwitchTargets value switchTargetsDefault :: SwitchTargets -> Maybe Label switchTargetsDefault (SwitchTargets _ _ mbdef _) = mbdef +-- | Return the range of the SwitchTargets value switchTargetsRange :: SwitchTargets -> (Integer, Integer) switchTargetsRange (SwitchTargets _ range _ _) = range +-- | Return whether this is used for a signed value switchTargetsSigned :: SwitchTargets -> Bool switchTargetsSigned (SwitchTargets signed _ _ _) = signed --- switchTargetsToTable creates a dense jump table, usable for code generation. --- Returns an offset to add to the value; the list is 0-based on the result +-- | switchTargetsToTable creates a dense jump table, usable for code generation. +-- Returns an offset to add to the value; the list is 0-based on the result. -- The conversion from Integer to Int is a bit of a wart, but works due to -- wrap-around arithmetic (as verified by the CmmSwitchTest test case). switchTargetsToTable :: SwitchTargets -> (Int, [Maybe Label]) @@ -174,6 +181,7 @@ switchTargetsToTable (SwitchTargets _ (lo,hi) mbdef branches) -- .quad _c20q -- .quad _c20r +-- | The list of all labels occuring in the SwitchTargets value. switchTargetsToList :: SwitchTargets -> [Label] switchTargetsToList (SwitchTargets _ _ mbdef branches) = maybeToList mbdef ++ M.elems branches @@ -187,6 +195,7 @@ switchTargetsFallThrough (SwitchTargets _ _ mbdef branches) = (groups, mbdef) groupBy ((==) `on` snd) $ M.toList branches +-- | Custom equality helper, needed for "CmmCommonBlockElim" eqSwitchTargetWith :: (Label -> Label -> Bool) -> SwitchTargets -> SwitchTargets -> Bool eqSwitchTargetWith eq (SwitchTargets signed1 range1 mbdef1 ids1) (SwitchTargets signed2 range2 mbdef2 ids2) = signed1 == signed2 && range1 == range2 && goMB mbdef1 mbdef2 && goList (M.toList ids1) (M.toList ids2) @@ -202,6 +211,15 @@ eqSwitchTargetWith eq (SwitchTargets signed1 range1 mbdef1 ids1) (SwitchTargets -- Code generation for Switches +-- | A SwitchPlan abstractly descries how a Switch statement ought to be +-- implemented. See Note [createSwitchPlan] +data SwitchPlan + = Unconditionally Label + | IfEqual Integer Label SwitchPlan + | IfLT Bool Integer SwitchPlan SwitchPlan + | JumpTable SwitchTargets + deriving Show +-- -- Note [createSwitchPlan] -- ~~~~~~~~~~~~~~~~~~~~~~~ -- @@ -219,15 +237,11 @@ eqSwitchTargetWith eq (SwitchTargets signed1 range1 mbdef1 ids1) (SwitchTargets -- findSingleValues -- 5. The thus collected pieces are assembled to a balanced binary tree. -data SwitchPlan - = Unconditionally Label - | IfEqual Integer Label SwitchPlan - | IfLT Bool Integer SwitchPlan SwitchPlan - | JumpTable SwitchTargets - deriving Show type FlatSwitchPlan = SeparatedList Integer SwitchPlan +-- | This function creates a SwitchPlan from a SwitchTargets value, breaking it +-- down into smaller pieces suitable for code generation. createSwitchPlan :: SwitchTargets -> SwitchPlan createSwitchPlan (SwitchTargets signed mbdef range m) = -- pprTrace "createSwitchPlan" (text (show ids) $$ text (show (range,m)) $$ text (show pieces) $$ text (show flatPlan) $$ text (show plan)) $ From git at git.haskell.org Tue Mar 17 15:18:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 15:18:38 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Build the if-then-else branch with >= instead of < (c0f7bc7) Message-ID: <20150317151838.995333A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/c0f7bc7599a58a9044a1b8f81eb2715cd90ea028/ghc >--------------------------------------------------------------- commit c0f7bc7599a58a9044a1b8f81eb2715cd90ea028 Author: Joachim Breitner Date: Tue Mar 17 16:18:26 2015 +0100 CmmSwitch: Build the if-then-else branch with >= instead of < >--------------------------------------------------------------- c0f7bc7599a58a9044a1b8f81eb2715cd90ea028 compiler/cmm/CmmCreateSwitchPlans.hs | 6 +++--- compiler/cmm/CmmSwitch.hs | 4 ++-- compiler/cmm/CmmUtils.hs | 5 +++-- 3 files changed, 8 insertions(+), 7 deletions(-) diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmCreateSwitchPlans.hs index 0fac30c..450e399 100644 --- a/compiler/cmm/CmmCreateSwitchPlans.hs +++ b/compiler/cmm/CmmCreateSwitchPlans.hs @@ -57,13 +57,13 @@ implementSwitchPlan dflags scope expr = go = return (emptyBlock `blockJoinTail` CmmBranch l, []) go (JumpTable ids) = return (emptyBlock `blockJoinTail` CmmSwitch expr ids, []) - go (IfLT signed i ids1 ids2) + go (IfGe signed i ids1 ids2) = do (bid1, newBlocks1) <- go' ids1 (bid2, newBlocks2) <- go' ids2 - let lt | signed = cmmSLtWord - | otherwise = cmmULtWord + let lt | signed = cmmSGeWord + | otherwise = cmmUGeWord scrut = lt dflags expr $ CmmLit $ mkWordCLit dflags i lastNode = CmmCondBranch scrut bid1 bid2 lastBlock = emptyBlock `blockJoinTail` lastNode diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index 800ee7d..c16818d 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -216,7 +216,7 @@ eqSwitchTargetWith eq (SwitchTargets signed1 range1 mbdef1 ids1) (SwitchTargets data SwitchPlan = Unconditionally Label | IfEqual Integer Label SwitchPlan - | IfLT Bool Integer SwitchPlan SwitchPlan + | IfGe Bool Integer SwitchPlan SwitchPlan | JumpTable SwitchTargets deriving Show -- @@ -341,7 +341,7 @@ findSingleValues (p, []) -- Build a balanced tree from a separated list buildTree :: Bool -> FlatSwitchPlan -> SwitchPlan buildTree _ (p,[]) = p -buildTree signed sl = IfLT signed m (buildTree signed sl1) (buildTree signed sl2) +buildTree signed sl = IfGe signed m (buildTree signed sl2) (buildTree signed sl1) where (sl1, m, sl2) = divideSL sl diff --git a/compiler/cmm/CmmUtils.hs b/compiler/cmm/CmmUtils.hs index be1b1fe..ef67bfc 100644 --- a/compiler/cmm/CmmUtils.hs +++ b/compiler/cmm/CmmUtils.hs @@ -29,7 +29,7 @@ module CmmUtils( cmmIndex, cmmIndexExpr, cmmLoadIndex, cmmLoadIndexW, cmmNegate, cmmULtWord, cmmUGeWord, cmmUGtWord, cmmUShrWord, - cmmSLtWord, + cmmSLtWord, cmmSGeWord, cmmNeWord, cmmEqWord, cmmOrWord, cmmAndWord, cmmSubWord, cmmAddWord, cmmMulWord, cmmQuotWord, @@ -314,7 +314,7 @@ cmmLoadIndexW dflags base off ty = CmmLoad (cmmOffsetW dflags base off) ty ----------------------- cmmULtWord, cmmUGeWord, cmmUGtWord, cmmUShrWord, - cmmSLtWord, + cmmSLtWord, cmmSGeWord, cmmNeWord, cmmEqWord, cmmOrWord, cmmAndWord, cmmSubWord, cmmAddWord, cmmMulWord, cmmQuotWord @@ -328,6 +328,7 @@ cmmUGeWord dflags e1 e2 = CmmMachOp (mo_wordUGe dflags) [e1, e2] cmmUGtWord dflags e1 e2 = CmmMachOp (mo_wordUGt dflags) [e1, e2] --cmmShlWord dflags e1 e2 = CmmMachOp (mo_wordShl dflags) [e1, e2] cmmSLtWord dflags e1 e2 = CmmMachOp (mo_wordSLt dflags) [e1, e2] +cmmSGeWord dflags e1 e2 = CmmMachOp (mo_wordSGe dflags) [e1, e2] cmmUShrWord dflags e1 e2 = CmmMachOp (mo_wordUShr dflags) [e1, e2] cmmAddWord dflags e1 e2 = CmmMachOp (mo_wordAdd dflags) [e1, e2] cmmSubWord dflags e1 e2 = CmmMachOp (mo_wordSub dflags) [e1, e2] From git at git.haskell.org Tue Mar 17 15:58:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 15:58:40 +0000 (UTC) Subject: [commit: ghc] wip/T10137: Revert "CmmSwitch: Build the if-then-else branch with >= instead of <" (27a5e9e) Message-ID: <20150317155840.9D4253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/27a5e9e53699a00471d0255faf514dda4b603ed6/ghc >--------------------------------------------------------------- commit 27a5e9e53699a00471d0255faf514dda4b603ed6 Author: Joachim Breitner Date: Tue Mar 17 16:56:51 2015 +0100 Revert "CmmSwitch: Build the if-then-else branch with >= instead of <" This reverts commit c0f7bc7599a58a9044a1b8f81eb2715cd90ea028. >--------------------------------------------------------------- 27a5e9e53699a00471d0255faf514dda4b603ed6 compiler/cmm/CmmCreateSwitchPlans.hs | 6 +++--- compiler/cmm/CmmSwitch.hs | 4 ++-- compiler/cmm/CmmUtils.hs | 5 ++--- 3 files changed, 7 insertions(+), 8 deletions(-) diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmCreateSwitchPlans.hs index 450e399..0fac30c 100644 --- a/compiler/cmm/CmmCreateSwitchPlans.hs +++ b/compiler/cmm/CmmCreateSwitchPlans.hs @@ -57,13 +57,13 @@ implementSwitchPlan dflags scope expr = go = return (emptyBlock `blockJoinTail` CmmBranch l, []) go (JumpTable ids) = return (emptyBlock `blockJoinTail` CmmSwitch expr ids, []) - go (IfGe signed i ids1 ids2) + go (IfLT signed i ids1 ids2) = do (bid1, newBlocks1) <- go' ids1 (bid2, newBlocks2) <- go' ids2 - let lt | signed = cmmSGeWord - | otherwise = cmmUGeWord + let lt | signed = cmmSLtWord + | otherwise = cmmULtWord scrut = lt dflags expr $ CmmLit $ mkWordCLit dflags i lastNode = CmmCondBranch scrut bid1 bid2 lastBlock = emptyBlock `blockJoinTail` lastNode diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index c16818d..800ee7d 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -216,7 +216,7 @@ eqSwitchTargetWith eq (SwitchTargets signed1 range1 mbdef1 ids1) (SwitchTargets data SwitchPlan = Unconditionally Label | IfEqual Integer Label SwitchPlan - | IfGe Bool Integer SwitchPlan SwitchPlan + | IfLT Bool Integer SwitchPlan SwitchPlan | JumpTable SwitchTargets deriving Show -- @@ -341,7 +341,7 @@ findSingleValues (p, []) -- Build a balanced tree from a separated list buildTree :: Bool -> FlatSwitchPlan -> SwitchPlan buildTree _ (p,[]) = p -buildTree signed sl = IfGe signed m (buildTree signed sl2) (buildTree signed sl1) +buildTree signed sl = IfLT signed m (buildTree signed sl1) (buildTree signed sl2) where (sl1, m, sl2) = divideSL sl diff --git a/compiler/cmm/CmmUtils.hs b/compiler/cmm/CmmUtils.hs index ef67bfc..be1b1fe 100644 --- a/compiler/cmm/CmmUtils.hs +++ b/compiler/cmm/CmmUtils.hs @@ -29,7 +29,7 @@ module CmmUtils( cmmIndex, cmmIndexExpr, cmmLoadIndex, cmmLoadIndexW, cmmNegate, cmmULtWord, cmmUGeWord, cmmUGtWord, cmmUShrWord, - cmmSLtWord, cmmSGeWord, + cmmSLtWord, cmmNeWord, cmmEqWord, cmmOrWord, cmmAndWord, cmmSubWord, cmmAddWord, cmmMulWord, cmmQuotWord, @@ -314,7 +314,7 @@ cmmLoadIndexW dflags base off ty = CmmLoad (cmmOffsetW dflags base off) ty ----------------------- cmmULtWord, cmmUGeWord, cmmUGtWord, cmmUShrWord, - cmmSLtWord, cmmSGeWord, + cmmSLtWord, cmmNeWord, cmmEqWord, cmmOrWord, cmmAndWord, cmmSubWord, cmmAddWord, cmmMulWord, cmmQuotWord @@ -328,7 +328,6 @@ cmmUGeWord dflags e1 e2 = CmmMachOp (mo_wordUGe dflags) [e1, e2] cmmUGtWord dflags e1 e2 = CmmMachOp (mo_wordUGt dflags) [e1, e2] --cmmShlWord dflags e1 e2 = CmmMachOp (mo_wordShl dflags) [e1, e2] cmmSLtWord dflags e1 e2 = CmmMachOp (mo_wordSLt dflags) [e1, e2] -cmmSGeWord dflags e1 e2 = CmmMachOp (mo_wordSGe dflags) [e1, e2] cmmUShrWord dflags e1 e2 = CmmMachOp (mo_wordUShr dflags) [e1, e2] cmmAddWord dflags e1 e2 = CmmMachOp (mo_wordAdd dflags) [e1, e2] cmmSubWord dflags e1 e2 = CmmMachOp (mo_wordSub dflags) [e1, e2] From git at git.haskell.org Tue Mar 17 15:59:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 15:59:08 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update release notes about better solver, with known bugs. (ec5e7b1) Message-ID: <20150317155908.E71963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/ec5e7b179059593d5c135ea29b3572451c0d2924/ghc >--------------------------------------------------------------- commit ec5e7b179059593d5c135ea29b3572451c0d2924 Author: Richard Eisenberg Date: Tue Mar 17 10:57:53 2015 -0500 Update release notes about better solver, with known bugs. Release notes in reaction to hvr's comment:26 on #10079. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D735 >--------------------------------------------------------------- ec5e7b179059593d5c135ea29b3572451c0d2924 docs/users_guide/7.10.1-notes.xml | 29 +++++++++++++++++++++++++++-- 1 file changed, 27 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 1bb5a5a..df7359e 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -193,7 +193,16 @@ , or ). - + + + + The solvers for both type family reductions and + Coercible instances have been improved. + This should lead to faster compilation of type-family-heavy + code and more Coercible instances to be + found. However, some bugs remain: see 'Known Bugs' below. + + warning flag is turned on by @@ -886,7 +895,23 @@ echo "[]" > package.conf GHCi fails to appropriately load .dyn_o files (issue #8736). - + + + + Not all cases of non-terminating type-level computation (with both + recursive type families and recursive newtypes) are caught. This + means that GHC might hang, but it should do so only when the program + is ill-typed (due to non-terminating type-level features). The bugs + are reported as #7788 + and #10139. + There also remain certain obscure scenarios where the solver for + Coercible instances is known to be still + incomplete. See comments in #10079. + + From git at git.haskell.org Tue Mar 17 16:07:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 16:07:21 +0000 (UTC) Subject: [commit: ghc] master: Add more MonadZip instances (3f3782d) Message-ID: <20150317160721.886B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3f3782df63f7c55382a25687a8e5c7f64202fa0a/ghc >--------------------------------------------------------------- commit 3f3782df63f7c55382a25687a8e5c7f64202fa0a Author: Oleg Grenrus Date: Tue Mar 17 11:03:44 2015 -0500 Add more MonadZip instances Summary: Add MonadZip Alt and MonadFix Alt instances Reviewers: ekmett, dfeuer, hvr, austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D716 GHC Trac Issues: #10107 >--------------------------------------------------------------- 3f3782df63f7c55382a25687a8e5c7f64202fa0a libraries/base/Control/Monad/Fix.hs | 6 +++++- libraries/base/Control/Monad/Zip.hs | 24 +++++++++++++++++++++++- 2 files changed, 28 insertions(+), 2 deletions(-) diff --git a/libraries/base/Control/Monad/Fix.hs b/libraries/base/Control/Monad/Fix.hs index ef8eeee..ae37911 100644 --- a/libraries/base/Control/Monad/Fix.hs +++ b/libraries/base/Control/Monad/Fix.hs @@ -26,7 +26,8 @@ module Control.Monad.Fix ( import Data.Either import Data.Function ( fix ) import Data.Maybe -import Data.Monoid ( Dual(..), Sum(..), Product(..), First(..), Last(..) ) +import Data.Monoid ( Dual(..), Sum(..), Product(..) + , First(..), Last(..), Alt(..) ) import GHC.Base ( Monad, error, (.) ) import GHC.List ( head, tail ) import GHC.ST @@ -99,3 +100,6 @@ instance MonadFix First where instance MonadFix Last where mfix f = Last (mfix (getLast . f)) + +instance MonadFix f => MonadFix (Alt f) where + mfix f = Alt (mfix (getAlt . f)) diff --git a/libraries/base/Control/Monad/Zip.hs b/libraries/base/Control/Monad/Zip.hs index df096b1..1f63cab 100644 --- a/libraries/base/Control/Monad/Zip.hs +++ b/libraries/base/Control/Monad/Zip.hs @@ -17,7 +17,8 @@ module Control.Monad.Zip where -import Control.Monad (liftM) +import Control.Monad (liftM, liftM2) +import Data.Monoid -- | `MonadZip` type class. Minimal definition: `mzip` or `mzipWith` -- @@ -53,3 +54,24 @@ instance MonadZip [] where mzipWith = zipWith munzip = unzip +instance MonadZip Dual where + -- Cannot use coerce, it's unsafe + mzipWith = liftM2 + +instance MonadZip Sum where + mzipWith = liftM2 + +instance MonadZip Product where + mzipWith = liftM2 + +instance MonadZip Maybe where + mzipWith = liftM2 + +instance MonadZip First where + mzipWith = liftM2 + +instance MonadZip Last where + mzipWith = liftM2 + +instance MonadZip f => MonadZip (Alt f) where + mzipWith f (Alt ma) (Alt mb) = Alt (mzipWith f ma mb) From git at git.haskell.org Tue Mar 17 16:07:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 16:07:24 +0000 (UTC) Subject: [commit: ghc] master: Add release note entry for D716 (ac14af3) Message-ID: <20150317160724.69E4E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ac14af3715aba725ef4b8ece24508fc5824389eb/ghc >--------------------------------------------------------------- commit ac14af3715aba725ef4b8ece24508fc5824389eb Author: Austin Seipp Date: Tue Mar 17 11:07:15 2015 -0500 Add release note entry for D716 Signed-off-by: Austin Seipp >--------------------------------------------------------------- ac14af3715aba725ef4b8ece24508fc5824389eb libraries/base/changelog.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index e2318a8..2ebad45 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -1,5 +1,9 @@ # Changelog for [`base` package](http://hackage.haskell.org/package/base) +## FUTURE VERSION *TBA* + + * `Alt` now has `MonadZip` and `MonadFix` instances. + ## 4.8.0.0 *TBA* * Bundled with GHC 7.10.1 From git at git.haskell.org Tue Mar 17 16:22:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 16:22:46 +0000 (UTC) Subject: [commit: ghc] master: Expose listPackageConfigMap (86eff3d) Message-ID: <20150317162246.EBBB83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/86eff3d92ffa3c9be29e037c01fd9b3fec8976e7/ghc >--------------------------------------------------------------- commit 86eff3d92ffa3c9be29e037c01fd9b3fec8976e7 Author: Edsko de Vries Date: Tue Mar 17 11:12:51 2015 -0500 Expose listPackageConfigMap This is useful for code that needs to search the package config map for packages satisfying a certain condition. Reviewed By: ezyang Differential Revision: https://phabricator.haskell.org/D695 >--------------------------------------------------------------- 86eff3d92ffa3c9be29e037c01fd9b3fec8976e7 compiler/main/Packages.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index e36221b..4f8afb5 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -13,6 +13,7 @@ module Packages ( getPackageConfRefs, resolvePackageConfig, readPackageConfig, + listPackageConfigMap, -- * Querying the package config lookupPackage, From git at git.haskell.org Tue Mar 17 16:22:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 16:22:51 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix Windows testsuite driver (67c3062) Message-ID: <20150317162251.361403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/67c30624cd1561f3aa8ac8c33075a20ff70d34fb/ghc >--------------------------------------------------------------- commit 67c30624cd1561f3aa8ac8c33075a20ff70d34fb Author: Thomas Miedema Date: Tue Mar 17 12:08:59 2015 +0100 Fix Windows testsuite driver This got broken in commit 5258566. (cherry picked from commit 9987c66d7c3a1186acb5a32e92cd6846d71987a5) >--------------------------------------------------------------- 67c30624cd1561f3aa8ac8c33075a20ff70d34fb testsuite/driver/testlib.py | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 58375c1..653796b 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -2257,17 +2257,17 @@ def printFailingTestInfosSummary(file, testInfos): ' (' + ','.join(testInfos[directory][test][reason]) + ')\n') file.write('\n') -def getStdout(cmd): +def getStdout(cmd_and_args): if have_subprocess: - p = subprocess.Popen(strip_quotes(cmd), + p = subprocess.Popen([strip_quotes(cmd_and_args[0])] + cmd_and_args[1:], stdout=subprocess.PIPE, stderr=subprocess.PIPE) (stdout, stderr) = p.communicate() r = p.wait() if r != 0: - raise Exception("Command failed: " + str(cmd)) + raise Exception("Command failed: " + str(cmd_and_args)) if stderr != '': - raise Exception("stderr from command: " + str(cmd)) + raise Exception("stderr from command: " + str(cmd_and_args)) return stdout else: raise Exception("Need subprocess to get stdout, but don't have it") From git at git.haskell.org Tue Mar 17 16:22:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 16:22:54 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Dont call unsafeGlobalDynFlags if it is not set (f92acd8) Message-ID: <20150317162254.DED003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/f92acd8ed223ebbbf62fab930c6c346f5531d431/ghc >--------------------------------------------------------------- commit f92acd8ed223ebbbf62fab930c6c346f5531d431 Author: Thomas Miedema Date: Mon Mar 16 18:36:59 2015 +0100 Dont call unsafeGlobalDynFlags if it is not set Parsing of static and mode flags happens before any session is started, i.e., before the first call to 'GHC.withGhc'. Therefore, to report errors for invalid usage of these two types of flags, we can not call any function that needs DynFlags, as there are no DynFlags available yet (unsafeGlobalDynFlags is not set either). So we always print "on the commandline" as the location, which is true except for Api users, which is probably ok. When reporting errors for invalid usage of dynamic flags we /can/ make use of DynFlags, and we do so explicitly in DynFlags.parseDynamicFlagsFull. Before, we called unsafeGlobalDynFlags when an invalid (combination of) flag(s) was given on the commandline, resulting in panics (#9963). This regression was introduced in 1d6124de. Also rename showSDocSimple to showSDocUnsafe, to hopefully prevent this from happening again. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D730 GHC Trac Issues: #9963 (cherry picked from commit 5166ee94e439375a4e6acb80f88ec6ee65476bbd) >--------------------------------------------------------------- f92acd8ed223ebbbf62fab930c6c346f5531d431 compiler/basicTypes/SrcLoc.hs | 5 +---- compiler/main/CmdLineParser.hs | 24 +++++++++++++++++++++--- compiler/main/DynFlags.hs | 10 +++++++--- compiler/main/StaticFlags.hs | 7 +++++-- compiler/typecheck/TcGenDeriv.hs | 6 ++++-- compiler/utils/Outputable.hs | 8 +++++--- ghc/Main.hs | 9 ++++++--- testsuite/tests/driver/T9963.stderr | 2 ++ testsuite/tests/driver/all.T | 2 ++ 9 files changed, 53 insertions(+), 20 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f92acd8ed223ebbbf62fab930c6c346f5531d431 From git at git.haskell.org Tue Mar 17 16:22:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 16:22:57 +0000 (UTC) Subject: [commit: ghc] master: Expose listPackageConfigMap (86eff3d) Message-ID: <20150317162257.D1D843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/86eff3d92ffa3c9be29e037c01fd9b3fec8976e7/ghc >--------------------------------------------------------------- commit 86eff3d92ffa3c9be29e037c01fd9b3fec8976e7 Author: Edsko de Vries Date: Tue Mar 17 11:12:51 2015 -0500 Expose listPackageConfigMap This is useful for code that needs to search the package config map for packages satisfying a certain condition. Reviewed By: ezyang Differential Revision: https://phabricator.haskell.org/D695 >--------------------------------------------------------------- 86eff3d92ffa3c9be29e037c01fd9b3fec8976e7 compiler/main/Packages.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index e36221b..4f8afb5 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -13,6 +13,7 @@ module Packages ( getPackageConfRefs, resolvePackageConfig, readPackageConfig, + listPackageConfigMap, -- * Querying the package config lookupPackage, From git at git.haskell.org Tue Mar 17 16:23:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 16:23:55 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix testsuite driver for a profiling compiler (7974c66) Message-ID: <20150317162355.C24783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/7974c66cc8e765cf62bb3bb4f85a88ce83858daa/ghc >--------------------------------------------------------------- commit 7974c66cc8e765cf62bb3bb4f85a88ce83858daa Author: Thomas Miedema Date: Sun Mar 15 21:06:39 2015 +0100 Fix testsuite driver for a profiling compiler This should have been part of commit 5258566ee5c8, to allow expansion of '{hp2ps}' in a command string to `config.hp2ps`. Reviewed by: austin Differential Revision: https://phabricator.haskell.org/D734 (cherry picked from commit beee618c4ab8f725acd4dce3ef8a0d4ce84bb6ec) >--------------------------------------------------------------- 7974c66cc8e765cf62bb3bb4f85a88ce83858daa testsuite/driver/testlib.py | 3 +++ 1 file changed, 3 insertions(+) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 653796b..29ceedb 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1816,6 +1816,9 @@ def rawSystemWithTimeout(cmd_and_args): # Then, when using the native Python, os.system will invoke the cmd shell def runCmd( cmd ): + # Format cmd using config. Example: cmd='{hpc} report A.tix' + cmd = cmd.format(**config.__dict__) + if_verbose( 3, cmd ) r = 0 if config.os == 'mingw32': From git at git.haskell.org Tue Mar 17 17:22:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Mar 2015 17:22:39 +0000 (UTC) Subject: [commit: ghc] master: hpc: use System.FilePath.() instead of (++) (801f4b9) Message-ID: <20150317172239.407043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/801f4b98fa5198ab7e033949dd84aaae00162993/ghc >--------------------------------------------------------------- commit 801f4b98fa5198ab7e033949dd84aaae00162993 Author: Thomas Miedema Date: Tue Mar 17 18:09:18 2015 +0100 hpc: use System.FilePath.() instead of (++) Summary: BAD: "." ++ "/" ++ "/absolute/path" == ".//absolute/path" GOOD: "." "/absolute/path" == "/absolute path" Also replace `++ ".ext"` with `<.> "ext"`. Although it doesn't fix any bugs in this instance, it might in some other. As a general rule it's better not to use (++) on FilePaths. Reviewed By: austin, hvr Differential Revision: https://phabricator.haskell.org/D703 GHC Trac Issues: #10138 >--------------------------------------------------------------- 801f4b98fa5198ab7e033949dd84aaae00162993 testsuite/tests/hpc/.hpc.T10138/Main.mix | 1 + testsuite/tests/hpc/T10138.tix | 1 + testsuite/tests/hpc/all.T | 7 ++++++- utils/hpc/HpcFlags.hs | 3 ++- utils/hpc/HpcMarkup.hs | 9 +++++---- utils/hpc/HpcUtils.hs | 3 ++- utils/hpc/hpc-bin.cabal | 1 + 7 files changed, 18 insertions(+), 7 deletions(-) diff --git a/testsuite/tests/hpc/.hpc.T10138/Main.mix b/testsuite/tests/hpc/.hpc.T10138/Main.mix new file mode 100644 index 0000000..26611fe --- /dev/null +++ b/testsuite/tests/hpc/.hpc.T10138/Main.mix @@ -0,0 +1 @@ +Mix "T10138.hs" 2015-03-09 18:22:16.403500034 UTC 2143033233 8 [(1:15-1:16,ExpBox False),(1:8-1:16,ExpBox False),(1:1-1:16,TopLevelBox ["main"])] diff --git a/testsuite/tests/hpc/T10138.tix b/testsuite/tests/hpc/T10138.tix new file mode 100644 index 0000000..f348f70 --- /dev/null +++ b/testsuite/tests/hpc/T10138.tix @@ -0,0 +1 @@ +Tix [ TixModule "Main" 2143033233 3 [0,1,1]] diff --git a/testsuite/tests/hpc/all.T b/testsuite/tests/hpc/all.T index d279018..0289733 100644 --- a/testsuite/tests/hpc/all.T +++ b/testsuite/tests/hpc/all.T @@ -1,8 +1,13 @@ +test('T10138', ignore_output, run_command, + # Using --hpcdir with an absolute path should work (exit code 0). + ['{hpc} report T10138.tix --hpcdir="`pwd`/.hpc.T10138"']) + +# Run tests below only for the hpc way. +# # Do not explicitly specify '-fhpc' in extra_hc_opts, unless also setting # '-hpcdir' to a different value for each test. Only the `hpc` way does this # automatically. This way the tests in this directory can be run concurrently # (Main.mix might overlap otherwise). - setTestOpts([only_compiler_types(['ghc']), only_ways(['hpc']), ]) diff --git a/utils/hpc/HpcFlags.hs b/utils/hpc/HpcFlags.hs index 0170309..dd1d9f7 100644 --- a/utils/hpc/HpcFlags.hs +++ b/utils/hpc/HpcFlags.hs @@ -8,6 +8,7 @@ import Data.Char import Trace.Hpc.Tix import Trace.Hpc.Mix import System.Exit +import System.FilePath data Flags = Flags { outputFile :: String @@ -154,7 +155,7 @@ unionModuleOpt = noArg "union" ------------------------------------------------------------------------------- readMixWithFlags :: Flags -> Either String TixModule -> IO Mix -readMixWithFlags flags modu = readMix [ dir ++ "/" ++ hpcDir +readMixWithFlags flags modu = readMix [ dir hpcDir | dir <- srcDirs flags , hpcDir <- hpcDirs flags ] modu diff --git a/utils/hpc/HpcMarkup.hs b/utils/hpc/HpcMarkup.hs index 1373bfb..31327fc 100644 --- a/utils/hpc/HpcMarkup.hs +++ b/utils/hpc/HpcMarkup.hs @@ -13,6 +13,7 @@ import HpcFlags import HpcUtils import System.Directory +import System.FilePath import System.IO (localeEncoding) import Data.List import Data.Maybe(fromJust) @@ -78,9 +79,9 @@ markup_main flags (prog:modNames) = do let mods' = sortBy cmp mods unless (verbosity flags < Normal) $ - putStrLn $ "Writing: " ++ (filename ++ ".html") + putStrLn $ "Writing: " ++ (filename <.> "html") - writeFileUsing (dest_dir ++ "/" ++ filename ++ ".html") $ + writeFileUsing (dest_dir filename <.> "html") $ "" ++ "" ++ charEncodingTag ++ @@ -224,10 +225,10 @@ genHtmlFromMod dest_dir flags tix theFunTotals invertOutput = do let content' = markup tabStop info content let addLine n xs = "" ++ padLeft 5 ' ' (show n) ++ " " ++ xs let addLines = unlines . map (uncurry addLine) . zip [1 :: Int ..] . lines - let fileName = modName0 ++ ".hs.html" + let fileName = modName0 <.> "hs" <.> "html" unless (verbosity flags < Normal) $ putStrLn $ "Writing: " ++ fileName - writeFileUsing (dest_dir ++ "/" ++ fileName) $ + writeFileUsing (dest_dir fileName) $ unlines ["", "", charEncodingTag, diff --git a/utils/hpc/HpcUtils.hs b/utils/hpc/HpcUtils.hs index 4f98556..6ee44b1 100644 --- a/utils/hpc/HpcUtils.hs +++ b/utils/hpc/HpcUtils.hs @@ -2,6 +2,7 @@ module HpcUtils where import Trace.Hpc.Util import qualified Data.Map as Map +import System.FilePath dropWhileEndLE :: (a -> Bool) -> [a] -> [a] -- Spec: dropWhileEndLE p = reverse . dropWhile p . reverse @@ -30,6 +31,6 @@ readFileFromPath err filename path0 = readTheFile path0 readTheFile [] = err $ "could not find " ++ show filename ++ " in path " ++ show path0 readTheFile (dir:dirs) = - catchIO (do str <- readFile (dir ++ "/" ++ filename) + catchIO (do str <- readFile (dir filename) return str) (\ _ -> readTheFile dirs) diff --git a/utils/hpc/hpc-bin.cabal b/utils/hpc/hpc-bin.cabal index 8ec6e5b..0257fb9 100644 --- a/utils/hpc/hpc-bin.cabal +++ b/utils/hpc/hpc-bin.cabal @@ -43,6 +43,7 @@ Executable hpc if flag(base3) || flag(base4) Build-Depends: directory >= 1 && < 1.3, + filepath >= 1 && < 1.5, containers >= 0.1 && < 0.6, array >= 0.1 && < 0.6 Build-Depends: hpc From git at git.haskell.org Wed Mar 18 01:34:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Mar 2015 01:34:27 +0000 (UTC) Subject: [commit: ghc] master: Typos in comments (6f40060) Message-ID: <20150318013427.616DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6f4006034af1b63da75ef34ced70b26325ac86f4/ghc >--------------------------------------------------------------- commit 6f4006034af1b63da75ef34ced70b26325ac86f4 Author: Gabor Greif Date: Wed Mar 18 02:25:13 2015 +0100 Typos in comments >--------------------------------------------------------------- 6f4006034af1b63da75ef34ced70b26325ac86f4 compiler/basicTypes/Id.hs | 2 +- compiler/coreSyn/CoreSyn.hs | 2 +- compiler/coreSyn/CoreUnfold.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 2 +- compiler/typecheck/TcValidity.hs | 2 +- compiler/types/InstEnv.hs | 2 +- libraries/base/Foreign/C/Types.hs | 4 ++-- libraries/base/GHC/Generics.hs | 2 +- 8 files changed, 9 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/Id.hs b/compiler/basicTypes/Id.hs index 14e789b..2a97445 100644 --- a/compiler/basicTypes/Id.hs +++ b/compiler/basicTypes/Id.hs @@ -449,7 +449,7 @@ isImplicitId id PrimOpId {} -> True DataConWorkId {} -> True DataConWrapId {} -> True - -- These are are implied by their type or class decl; + -- These are implied by their type or class decl; -- remember that all type and class decls appear in the interface file. -- The dfun id is not an implicit Id; it must *not* be omitted, because -- it carries version info for the instance decl diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index 86939bd..b744ea2 100644 --- a/compiler/coreSyn/CoreSyn.hs +++ b/compiler/coreSyn/CoreSyn.hs @@ -711,7 +711,7 @@ but CoreFVs, Subst, PprCore, CoreTidy also inspect the representation. -- | Gathers a collection of 'CoreRule's. Maps (the name of) an 'Id' to its rules type RuleBase = NameEnv [CoreRule] - -- The rules are are unordered; + -- The rules are unordered; -- we sort out any overlaps on lookup -- | A 'CoreRule' is: diff --git a/compiler/coreSyn/CoreUnfold.hs b/compiler/coreSyn/CoreUnfold.hs index 1dbd5ed..92160c7 100644 --- a/compiler/coreSyn/CoreUnfold.hs +++ b/compiler/coreSyn/CoreUnfold.hs @@ -981,7 +981,7 @@ StrictAnal.addStrictnessInfoToTopId callSiteInline :: DynFlags -> Id -- The Id -> Bool -- True <=> unfolding is active - -> Bool -- True if there are are no arguments at all (incl type args) + -> Bool -- True if there are no arguments at all (incl type args) -> [ArgSummary] -- One for each value arg; True if it is interesting -> CallCtxt -- True <=> continuation is interesting -> Maybe CoreExpr -- Unfolding, if any diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 6eb23b0..9c9481f 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -458,7 +458,7 @@ kcLTyClDecl (L loc decl) kcTyClDecl :: TyClDecl Name -> TcM () -- This function is used solely for its side effect on kind variables -- NB kind signatures on the type variables and --- result kind signature have aready been dealt with +-- result kind signature have already been dealt with -- by getInitialKind, so we can ignore them here. kcTyClDecl (DataDecl { tcdLName = L _ name, tcdTyVars = hs_tvs, tcdDataDefn = defn }) diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index 3d01f50..293f7cf 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -227,7 +227,7 @@ to a Type, performing kind checking, and then check various things that should be true about it. We don't want to perform these checks at the same time as the initial translation because (a) they are unnecessary for interface-file types and (b) when checking a mutually recursive group of type and class decls, -we can't "look" at the tycons/classes yet. Also, the checks are are rather +we can't "look" at the tycons/classes yet. Also, the checks are rather diverse, and used to really mess up the other code. One thing we check for is 'rank'. diff --git a/compiler/types/InstEnv.hs b/compiler/types/InstEnv.hs index da34cf8..8d1c855 100644 --- a/compiler/types/InstEnv.hs +++ b/compiler/types/InstEnv.hs @@ -981,7 +981,7 @@ not incoherent, but we still want this to compile. Hence the "all-but-one-logic". The implementation is in insert_overlapping, where we remove matching -incoherent instances as long as there are are others. +incoherent instances as long as there are others. diff --git a/libraries/base/Foreign/C/Types.hs b/libraries/base/Foreign/C/Types.hs index 2b9939c..cc0eb1b 100644 --- a/libraries/base/Foreign/C/Types.hs +++ b/libraries/base/Foreign/C/Types.hs @@ -24,7 +24,7 @@ module Foreign.C.Types -- $ctypes -- ** Integral types - -- | These types are are represented as @newtype at s of + -- | These types are represented as @newtype at s of -- types in "Data.Int" and "Data.Word", and are instances of -- 'Prelude.Eq', 'Prelude.Ord', 'Prelude.Num', 'Prelude.Read', -- 'Prelude.Show', 'Prelude.Enum', 'Typeable', 'Storable', @@ -53,7 +53,7 @@ module Foreign.C.Types -- -- ** Floating types - -- | These types are are represented as @newtype at s of + -- | These types are represented as @newtype at s of -- 'Prelude.Float' and 'Prelude.Double', and are instances of -- 'Prelude.Eq', 'Prelude.Ord', 'Prelude.Num', 'Prelude.Read', -- 'Prelude.Show', 'Prelude.Enum', 'Typeable', 'Storable', diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs index 3970005..0b4ebc6 100644 --- a/libraries/base/GHC/Generics.hs +++ b/libraries/base/GHC/Generics.hs @@ -29,7 +29,7 @@ module GHC.Generics ( -- -- | -- --- Datatype-generic functions are are based on the idea of converting values of +-- Datatype-generic functions are based on the idea of converting values of -- a datatype @T@ into corresponding values of a (nearly) isomorphic type @'Rep' T at . -- The type @'Rep' T@ is -- built from a limited set of type constructors, all provided by this module. A From git at git.haskell.org Wed Mar 18 08:59:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Mar 2015 08:59:58 +0000 (UTC) Subject: [commit: ghc] master: Comments only (fad7bb0) Message-ID: <20150318085958.A69D93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fad7bb0bfdb4bf2d323f8833e29ce42d6c807ee0/ghc >--------------------------------------------------------------- commit fad7bb0bfdb4bf2d323f8833e29ce42d6c807ee0 Author: Simon Peyton Jones Date: Mon Jan 19 16:44:25 2015 +0000 Comments only >--------------------------------------------------------------- fad7bb0bfdb4bf2d323f8833e29ce42d6c807ee0 compiler/coreSyn/CoreUtils.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index 166fe6c..08f4fcd 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -907,8 +907,8 @@ exprIsCheap' good_app other_expr -- Applications and variables -- good plan go (Var f) args - | good_app f (length args) - = go_pap args + | good_app f (length args) -- Typically holds of data constructor applications + = go_pap args -- E.g. good_app = isCheapApp below | otherwise = case idDetails f of From git at git.haskell.org Wed Mar 18 09:30:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Mar 2015 09:30:00 +0000 (UTC) Subject: [commit: ghc] master: Remove mention of `-unreg` in error message (3508b68) Message-ID: <20150318093000.746B13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3508b68f1a1e9a7ba4cdea5bac4e557739349da1/ghc >--------------------------------------------------------------- commit 3508b68f1a1e9a7ba4cdea5bac4e557739349da1 Author: Thomas Miedema Date: Wed Mar 18 10:21:18 2015 +0100 Remove mention of `-unreg` in error message The `-unreg` flag was removed in commit dade8ab (2007), see #1008. [skip-ci] >--------------------------------------------------------------- 3508b68f1a1e9a7ba4cdea5bac4e557739349da1 ghc/Main.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc/Main.hs b/ghc/Main.hs index d30a50b..da95ebf 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -315,7 +315,7 @@ checkOptions mode dflags srcs objs = do when ((filter (not . wayRTSOnly) (ways dflags) /= interpWays) && isInterpretiveMode mode) $ do throwGhcException (UsageError - "--interactive can't be used with -prof or -unreg.") + "--interactive can't be used with -prof.") -- -ohi sanity check if (isJust (outputHi dflags) && (isCompManagerMode mode || srcs `lengthExceeds` 1)) From git at git.haskell.org Wed Mar 18 10:14:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Mar 2015 10:14:47 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Major rewrite: Pt 2: function covered (e5f2eb7) Message-ID: <20150318101447.E4B123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/e5f2eb742e4383a230b4f8aa5aa78709890fe15e/ghc >--------------------------------------------------------------- commit e5f2eb742e4383a230b4f8aa5aa78709890fe15e Author: George Karachalias Date: Wed Mar 18 11:12:29 2015 +0100 Major rewrite: Pt 2: function covered Introduced even more holes and typing is almost fully ignored (or even wrongly implemented at some places) >--------------------------------------------------------------- e5f2eb742e4383a230b4f8aa5aa78709890fe15e compiler/deSugar/Check.hs | 148 ++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 148 insertions(+) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index d984ea5..7c8b545 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -841,3 +841,151 @@ mkPmId usupply ty = mkLocalId name ty occname = mkVarOccFS (fsLit (show unique)) name = mkInternalName unique occname noSrcSpan +-- ---------------------------------------------------------------------------- +-- | Utility function `tailValSetAbs' and `wrapK' + +tailValSetAbs :: ValSetAbs -> ValSetAbs +tailValSetAbs Empty = Empty +tailValSetAbs Singleton = panic "tailValSetAbs: Singleton" +tailValSetAbs (Union vsa1 vsa2) = Union (tailValSetAbs vsa1) (tailValSetAbs vsa2) +tailValSetAbs (Constraint cs vsa) = Constraint cs (tailValSetAbs vsa) -- [1] +tailValSetAbs (Cons _ vsa) = vsa -- actual work + +-- COMEHERE: Optimisation for [1]: +-- tailValSetAbs (Constraint cs vsa) | vsa' <- tailValSetAbs vsa +-- = cs `addConstraints` vsa' -- In case more cs emerge at the head of vsa' + +wrapK :: DataCon -> ValSetAbs -> ValSetAbs +wrapK con = wrapK_aux (dataConSourceArity con) emptylist + where + wrapK_aux :: Int -> DList ValAbs -> ValSetAbs -> ValSetAbs + wrapK_aux _ _ Empty = Empty + wrapK_aux 0 args vsa = Cons (ConAbs con (toList args)) vsa + wrapK_aux _ _ Singleton = panic "wrapK: Singleton" + wrapK_aux n args (Cons vs vsa) = wrapK_aux (n-1) (args `snoc` vs) vsa + wrapK_aux n args (Constraint cs vsa) = Constraint cs (wrapK_aux n args vsa) + wrapK_aux n args (Union vsa1 vsa2) = Union (wrapK_aux n args vsa1) (wrapK_aux n args vsa2) + +-- ---------------------------------------------------------------------------- +-- | Some difference lists stuff for efficiency + +newtype DList a = DL { unDL :: [a] -> [a] } + +toList :: DList a -> [a] +toList = ($[]) . unDL +{-# INLINE toList #-} + +emptylist :: DList a +emptylist = DL id +{-# INLINE emptylist #-} + +infixl `snoc` +snoc :: DList a -> a -> DList a +snoc xs x = DL (unDL xs . (x:)) +{-# INLINE snoc #-} + +-- ---------------------------------------------------------------------------- +-- | Main function 1 (covered) + +covered :: UniqSupply -> PatternVec -> ValSetAbs -> ValSetAbs + +-- CEmpty (New case because of representation) +covered _usupply _vec Empty = Empty + +-- CNil +covered _usupply [] Singleton = Singleton + +-- Pure induction (New case because of representation) +covered usupply vec (Union vsa1 vsa2) = Union (covered usupply1 vec vsa1) (covered usupply2 vec vsa2) + where (usupply1, usupply2) = splitUniqSupply usupply + +-- Pure induction (New case because of representation) +covered usupply vec (Constraint cs vsa) = Constraint cs (covered usupply vec vsa) + +-- CGuard +covered usupply (GBindAbs p e : ps) vsa + = Constraint cs $ tailValSetAbs $ covered usupply2 (p:ps) (Cons (VarAbs y) vsa) -- [3] + where + (usupply1, usupply2) = splitUniqSupply usupply + y = mkPmId usupply1 undefined -- COMEHERE: WHAT TYPE?? + cs = [TmConstraint y e] + +-- COMEHERE: Optimisation for [3]: +-- covered usupply (GBindAbs p e : ps) vsa +-- | vsa' <- tailValSetAbs $ covered usupply2 (p:ps) (Cons (VarAbs y) vsa) +-- = cs `addConstraints` vsa' +-- where +-- (usupply1, usupply2) = splitUniqSupply usupply +-- y = mkPmVar usupply1 undefined -- COMEHERE: WHAT TYPE?? +-- cs = [TmConstraint y e] + +-- CVar +covered usupply (VarAbs x : ps) (Cons va vsa) + = Cons va $ Constraint cs $ covered usupply ps vsa -- [2] + where cs = [TmConstraint x (valAbsToHsExpr va)] + +-- COMEHERE: Optimisation for [2]: +-- covered usupply (VarAbs x : ps) (Cons va vsa) +-- | vsa' <- covered ps vsa +-- = Cons va $ cs `addConstraints` vsa' +-- where cs = [TmConstraint x (valAbsToHsExpr va)] + +-- CConCon +covered usupply (ConAbs c1 args1 : ps) (Cons (ConAbs c2 args2) vsa) + | c1 /= c2 = Empty + | otherwise = wrapK c1 (covered usupply (args1 ++ ps) (foldr Cons vsa args2)) + +-- CConVar +covered usupply (ConAbs con args : ps) (Cons (VarAbs x) vsa) + = Constraint all_cs $ covered usupply4 (ConAbs con args : ps) (Cons con_abs vsa) + where + -- Some more uniqSupplies + (usupply1, usupply' ) = splitUniqSupply usupply + (usupply2, usupply'') = splitUniqSupply usupply' + (usupply3, usupply4 ) = splitUniqSupply usupply'' + + -- Instantiate variable with the approproate constructor pattern + (_tvs, qs, _arg_tys, res_ty) = dataConSig con -- take the constructor apart + con_abs = mkConFull2 usupply1 con -- (Ki ys), ys fresh + + -- All generated/collected constraints + ty_eq_ct = TyConstraint [newEqPmM2 usupply2 (idType x) res_ty] -- type_eq: tau_x ~ tau (result type of the constructor) + tm_eq_ct = TmConstraint x (valAbsToHsExpr con_abs) -- term_eq: x ~ K ys + uniqs_cs = listSplitUniqSupply usupply3 `zip` qs + thetas = map (uncurry (nameType2 "cconvar")) uniqs_cs -- constructors_thetas: the Qs from K's sig + all_cs = [tm_eq_ct, ty_eq_ct, TyConstraint thetas] -- all constraints + +covered _usupply (ConAbs _ _ : _) Singleton = panic "covered: length mismatch: constructor-sing" +covered _usupply (VarAbs _ : _) Singleton = panic "covered: length mismatch: variable-sing" +covered _usupply [] (Cons _ _) = panic "covered: length mismatch: Cons" + +-- ---------------------------------------------------------------------------- +-- | Some more utility functions (COMEHERE: Remove 2 from their name) + +mkConFull2 :: UniqSupply -> DataCon -> ValAbs +mkConFull2 usupply con = ConAbs con args + where + uniqs_tys = listSplitUniqSupply usupply `zip` dataConOrigArgTys con + args = map (uncurry mkPmVar) uniqs_tys + +newEqPmM2 :: UniqSupply -> Type -> Type -> EvVar +newEqPmM2 usupply ty1 ty2 = newEvVar name (mkTcEqPred ty1 ty2) + where + unique = uniqFromSupply usupply + name = mkSystemName unique (mkVarOccFS (fsLit "pmcobox")) + +nameType2 :: String -> UniqSupply -> Type -> EvVar +nameType2 name usupply ty = newEvVar idname ty + where + unique = uniqFromSupply usupply + occname = mkVarOccFS (fsLit (name++"_"++show unique)) + idname = mkInternalName unique occname noSrcSpan + +valAbsToHsExpr :: ValAbs -> HsExpr Id +valAbsToHsExpr (VarAbs x) = HsVar x +valAbsToHsExpr (ConAbs c ps) = foldl lHsApp cexpr psexprs + where + cexpr = HsVar (dataConWrapId c) -- var representation of the constructor -- COMEHERE: Fishy. Ask Simon + psexprs = map valAbsToHsExpr ps + lHsApp le re = noLoc le `HsApp` noLoc re -- add locations (useless) to arguments + From git at git.haskell.org Wed Mar 18 12:29:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Mar 2015 12:29:15 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Major rewrite: Pt 3: function uncovered (a54fa60) Message-ID: <20150318122915.BFC753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/a54fa60b59d2cc0ebc166ebdcda27fc99453738e/ghc >--------------------------------------------------------------- commit a54fa60b59d2cc0ebc166ebdcda27fc99453738e Author: George Karachalias Date: Wed Mar 18 13:28:50 2015 +0100 Major rewrite: Pt 3: function uncovered >--------------------------------------------------------------- a54fa60b59d2cc0ebc166ebdcda27fc99453738e compiler/deSugar/Check.hs | 79 ++++++++++++++++++++++++++++++++++++++++++----- 1 file changed, 72 insertions(+), 7 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 7c8b545..84f6272 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -937,12 +937,75 @@ covered usupply (ConAbs c1 args1 : ps) (Cons (ConAbs c2 args2) vsa) -- CConVar covered usupply (ConAbs con args : ps) (Cons (VarAbs x) vsa) - = Constraint all_cs $ covered usupply4 (ConAbs con args : ps) (Cons con_abs vsa) + = covered usupply2 (ConAbs con args : ps) (Cons con_abs (Constraint all_cs vsa)) -- [4] + where + (usupply1, usupply2) = splitUniqSupply usupply + (con_abs, all_cs) = mkOneConFull x usupply1 con + +covered _usupply (ConAbs _ _ : _) Singleton = panic "covered: length mismatch: constructor-sing" +covered _usupply (VarAbs _ : _) Singleton = panic "covered: length mismatch: variable-sing" +covered _usupply [] (Cons _ _) = panic "covered: length mismatch: Cons" + +-- ---------------------------------------------------------------------------- +-- | Main function 2 (uncovered) + +uncovered :: UniqSupply -> PatternVec -> ValSetAbs -> ValSetAbs + +-- UEmpty (New case because of representation) +uncovered _usupply _vec Empty = Empty + +-- UNil +uncovered _usupply [] Singleton = Empty + +-- Pure induction (New case because of representation) +uncovered usupply vec (Union vsa1 vsa2) = Union (uncovered usupply1 vec vsa1) (uncovered usupply2 vec vsa2) + where (usupply1, usupply2) = splitUniqSupply usupply + +-- Pure induction (New case because of representation) +uncovered usupply vec (Constraint cs vsa) = Constraint cs (uncovered usupply vec vsa) + +-- UGuard +uncovered usupply (GBindAbs p e : ps) vsa + = Constraint cs $ tailValSetAbs $ uncovered usupply2 (p:ps) (Cons (VarAbs y) vsa) -- [3] + where + (usupply1, usupply2) = splitUniqSupply usupply + y = mkPmId usupply1 undefined -- COMEHERE: WHAT TYPE?? + cs = [TmConstraint y e] + +-- UVar +uncovered usupply (VarAbs x : ps) (Cons va vsa) + = Cons va $ Constraint cs $ uncovered usupply ps vsa -- [2] + where cs = [TmConstraint x (valAbsToHsExpr va)] + +-- UConCon +uncovered usupply (ConAbs c1 args1 : ps) (Cons (ConAbs c2 args2) vsa) + | c1 /= c2 = Cons (ConAbs c2 args2) vsa + | otherwise = wrapK c1 (uncovered usupply (args1 ++ ps) (foldr Cons vsa args2)) + +-- CConVar +uncovered usupply (ConAbs con args : ps) (Cons (VarAbs x) vsa) + -- = Constraint all_cs $ covered usupply4 (ConAbs con args : ps) (Cons con_abs vsa) + = covered usupply2 (ConAbs con args : ps) inst_vsa -- instantiated vsa [x \mapsto K_j ys] + where + -- Some more uniqSupplies + (usupply1, usupply2) = splitUniqSupply usupply + + -- Unfold the variable to all possible constructor patterns + uniqs_cons = listSplitUniqSupply usupply1 `zip` allConstructors con + cons_cs = map (uncurry (mkOneConFull x)) uniqs_cons + add_one (va,cs) valset = Cons va $ Constraint cs valset + inst_vsa = foldr add_one vsa cons_cs + +uncovered _usupply (ConAbs _ _ : _) Singleton = panic "uncovered: length mismatch: constructor-sing" +uncovered _usupply (VarAbs _ : _) Singleton = panic "uncovered: length mismatch: variable-sing" +uncovered _usupply [] (Cons _ _) = panic "uncovered: length mismatch: Cons" + +mkOneConFull :: Id -> UniqSupply -> DataCon -> (ValAbs, [PmConstraint]) +mkOneConFull x usupply con = (con_abs, all_cs) where -- Some more uniqSupplies - (usupply1, usupply' ) = splitUniqSupply usupply - (usupply2, usupply'') = splitUniqSupply usupply' - (usupply3, usupply4 ) = splitUniqSupply usupply'' + (usupply1, usupply') = splitUniqSupply usupply + (usupply2, usupply3) = splitUniqSupply usupply' -- Instantiate variable with the approproate constructor pattern (_tvs, qs, _arg_tys, res_ty) = dataConSig con -- take the constructor apart @@ -955,9 +1018,11 @@ covered usupply (ConAbs con args : ps) (Cons (VarAbs x) vsa) thetas = map (uncurry (nameType2 "cconvar")) uniqs_cs -- constructors_thetas: the Qs from K's sig all_cs = [tm_eq_ct, ty_eq_ct, TyConstraint thetas] -- all constraints -covered _usupply (ConAbs _ _ : _) Singleton = panic "covered: length mismatch: constructor-sing" -covered _usupply (VarAbs _ : _) Singleton = panic "covered: length mismatch: variable-sing" -covered _usupply [] (Cons _ _) = panic "covered: length mismatch: Cons" +-- ---------------------------------------------------------------------------- +-- | Main function 3 (divergent) + +-- Since there is so much repetition, it may be +-- better to merge the three functions after all -- ---------------------------------------------------------------------------- -- | Some more utility functions (COMEHERE: Remove 2 from their name) From git at git.haskell.org Thu Mar 19 09:12:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 09:12:05 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Add Note [CmmSwitch vs. CmmCreateSwitchPlans] (c70c544) Message-ID: <20150319091205.CCA903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/c70c544ccda182321d8f7c1829f53338ee07253e/ghc >--------------------------------------------------------------- commit c70c544ccda182321d8f7c1829f53338ee07253e Author: Joachim Breitner Date: Thu Mar 19 10:00:02 2015 +0100 CmmSwitch: Add Note [CmmSwitch vs. CmmCreateSwitchPlans] >--------------------------------------------------------------- c70c544ccda182321d8f7c1829f53338ee07253e compiler/cmm/CmmSwitch.hs | 23 +++++++++++++++++++++++ 1 file changed, 23 insertions(+) diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index 800ee7d..7190d6e 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -41,6 +41,9 @@ import qualified Data.Map as M -- When compiling to LLVM or C, CmmCreateSwitchPlans leaves the switch -- statements alone, as we can turn a SwitchTargets value into a nice -- switch-statement in LLVM resp. C, and leave the rest to the compiler. +-- +-- See Note [CmmSwitch vs. CmmCreateSwitchPlans] why the two module are +-- separated. ----------------------------------------------------------------------------- -- Magic Constants @@ -379,3 +382,23 @@ reassocTuples initial [] last reassocTuples initial ((a,b):tuples) last = (initial,a) : reassocTuples b tuples last +-- Note [CmmSwitch vs. CmmCreateSwitchPlans] +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- I (Joachim) separated the two somewhat closely related modules +-- +-- - CmmSwitch, which provides the CmmSwitchTargets type and contains the strategy +-- for implementing a Cmm switch (createSwitchPlan), and +-- - CmmCreateSwitchPlans, which contains the actuall Cmm graph modification, +-- +-- for these reasons: +-- +-- * CmmSwitch is very low in the dependency tree, i.e. does not depend on any +-- GHC specific modules at all (with the exception of Output and Hoople +-- (Literal)). CmmCreateSwitchPlans is the Cmm transformation and hence very +-- high in the dependency tree. +-- * CmmSwitch provides the CmmSwitchTargets data type, which is abstract, but +-- used in CmmNodes. +-- * Because CmmSwitch is low in the dependency tree, the separation allows +-- for more parallelism when building GHC. +-- * The interaction between the modules is very explicit and easy to +-- understande, due to the small and simple interface. From git at git.haskell.org Thu Mar 19 09:12:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 09:12:08 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Actually do nothing when targetting C or LLVM (92452b3) Message-ID: <20150319091208.8FDA93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/92452b36417da684de9b81d8b0731731b632605d/ghc >--------------------------------------------------------------- commit 92452b36417da684de9b81d8b0731731b632605d Author: Joachim Breitner Date: Thu Mar 19 10:12:00 2015 +0100 CmmSwitch: Actually do nothing when targetting C or LLVM >--------------------------------------------------------------- 92452b36417da684de9b81d8b0731731b632605d compiler/cmm/CmmCreateSwitchPlans.hs | 4 +++- compiler/cmm/CmmSwitch.hs | 9 +++++++++ 2 files changed, 12 insertions(+), 1 deletion(-) diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmCreateSwitchPlans.hs index 0fac30c..1ca0cd4 100644 --- a/compiler/cmm/CmmCreateSwitchPlans.hs +++ b/compiler/cmm/CmmCreateSwitchPlans.hs @@ -29,7 +29,9 @@ import DynFlags -- | Traverses the 'CmmGraph', making sure that 'CmmSwitch' are suitable for -- code generation. cmmCreateSwitchPlans :: DynFlags -> CmmGraph -> UniqSM CmmGraph -cmmCreateSwitchPlans dflags g = do +cmmCreateSwitchPlans dflags g + | targetSupportsSwitch (hscTarget dflags) = return g + | otherwise = do blocks' <- concat `fmap` mapM (visitSwitches dflags) (toBlockList g) return $ ofBlockList (g_entry g) blocks' diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index 7190d6e..edb2087 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -7,10 +7,12 @@ module CmmSwitch ( switchTargetsToList, eqSwitchTargetWith, SwitchPlan(..), + targetSupportsSwitch, createSwitchPlan, ) where import Outputable +import DynFlags import Compiler.Hoopl (Label) import Data.Maybe @@ -243,6 +245,13 @@ data SwitchPlan type FlatSwitchPlan = SeparatedList Integer SwitchPlan +-- | Does the target support switch out of the box? Then leave this to the +-- target! +targetSupportsSwitch :: HscTarget -> Bool +targetSupportsSwitch HscC = True +targetSupportsSwitch HscLlvm = True +targetSupportsSwitch _ = False + -- | This function creates a SwitchPlan from a SwitchTargets value, breaking it -- down into smaller pieces suitable for code generation. createSwitchPlan :: SwitchTargets -> SwitchPlan From git at git.haskell.org Thu Mar 19 09:47:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 09:47:30 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Choose maxJumpTableHole more systematically (e2733bc) Message-ID: <20150319094730.D8B0E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/e2733bcd54afd9edc2329f57f4ead6734b4f71da/ghc >--------------------------------------------------------------- commit e2733bcd54afd9edc2329f57f4ead6734b4f71da Author: Joachim Breitner Date: Thu Mar 19 10:47:25 2015 +0100 CmmSwitch: Choose maxJumpTableHole more systematically >--------------------------------------------------------------- e2733bcd54afd9edc2329f57f4ead6734b4f71da compiler/cmm/CmmSwitch.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index edb2087..e58b049 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -56,9 +56,11 @@ import qualified Data.Map as M -- | Number of consecutive default values allowed in a jump table. If there are -- more of them, the jump tables are split. --- Currently 10, for no particular good reason. +-- +-- Currently 7, as it costs 7 words of additional code when a jump table is +-- split (at least on x64, determined experimentally). maxJumpTableHole :: Integer -maxJumpTableHole = 10 +maxJumpTableHole = 7 -- | Minimum size of a jump table. If the number is smaller, the switch is -- implemented using conditionals. From git at git.haskell.org Thu Mar 19 10:07:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 10:07:14 +0000 (UTC) Subject: [commit: ghc] wip/T10137: mk_float_switch: Pass through Width (7795595) Message-ID: <20150319100714.239543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/779559552864ead16bdd8360615e9b6729cf24dd/ghc >--------------------------------------------------------------- commit 779559552864ead16bdd8360615e9b6729cf24dd Author: Joachim Breitner Date: Thu Mar 19 11:07:04 2015 +0100 mk_float_switch: Pass through Width >--------------------------------------------------------------- 779559552864ead16bdd8360615e9b6729cf24dd compiler/codeGen/StgCmmUtils.hs | 17 +++++++---------- 1 file changed, 7 insertions(+), 10 deletions(-) diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index c1d89d9..b9b8016 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -523,6 +523,7 @@ emitCmmLitSwitch scrut branches deflt = do dflags <- getDynFlags let cmm_ty = cmmExprType dflags scrut + rep = typeWidth cmm_ty -- We find the necessary type information in the literals in the branches let signed = case head branches of @@ -534,7 +535,7 @@ emitCmmLitSwitch scrut branches deflt = do | otherwise = (0, tARGET_MAX_WORD dflags) if isFloatType cmm_ty - then emit =<< mk_float_switch scrut' deflt_lbl noBound branches_lbls + then emit =<< mk_float_switch rep scrut' deflt_lbl noBound branches_lbls else emit $ mk_discrete_switch signed scrut' @@ -549,25 +550,23 @@ type LitBound = (Maybe Literal, Maybe Literal) noBound :: LitBound noBound = (Nothing, Nothing) -mk_float_switch :: CmmExpr -> BlockId +mk_float_switch :: Width -> CmmExpr -> BlockId -> LitBound -> [(Literal,BlockId)] -> FCode CmmAGraph -mk_float_switch scrut deflt _bounds [(lit,blk)] +mk_float_switch rep scrut deflt _bounds [(lit,blk)] = do dflags <- getDynFlags return $ mkCbranch (cond dflags) deflt blk where cond dflags = CmmMachOp ne [scrut, CmmLit cmm_lit] where cmm_lit = mkSimpleLit dflags lit - cmm_ty = cmmLitType dflags cmm_lit - rep = typeWidth cmm_ty ne = MO_F_Ne rep -mk_float_switch scrut deflt_blk_id (lo_bound, hi_bound) branches +mk_float_switch rep scrut deflt_blk_id (lo_bound, hi_bound) branches = do dflags <- getDynFlags - lo_blk <- mk_float_switch scrut deflt_blk_id bounds_lo lo_branches - hi_blk <- mk_float_switch scrut deflt_blk_id bounds_hi hi_branches + lo_blk <- mk_float_switch rep scrut deflt_blk_id bounds_lo lo_branches + hi_blk <- mk_float_switch rep scrut deflt_blk_id bounds_hi hi_branches mkCmmIfThenElse (cond dflags) lo_blk hi_blk where (lo_branches, mid_lit, hi_branches) = divideBranches branches @@ -578,8 +577,6 @@ mk_float_switch scrut deflt_blk_id (lo_bound, hi_bound) branches cond dflags = CmmMachOp lt [scrut, CmmLit cmm_lit] where cmm_lit = mkSimpleLit dflags mid_lit - cmm_ty = cmmLitType dflags cmm_lit - rep = typeWidth cmm_ty lt = MO_F_Lt rep From git at git.haskell.org Thu Mar 19 11:32:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:32:50 +0000 (UTC) Subject: [commit: packages/filepath] tag 'v1.4.0.0' created Message-ID: <20150319113250.DFF583A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath New tag : v1.4.0.0 Referencing: dd4bd026af3a348303899db8cb4d2c126b5a7027 From git at git.haskell.org Thu Mar 19 11:32:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:32:52 +0000 (UTC) Subject: [commit: packages/filepath] master: Update travis badge in README.md (3239275) Message-ID: <20150319113252.E8FFE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/32392756273d28ef4639e1423fcd5cdd3501d03c >--------------------------------------------------------------- commit 32392756273d28ef4639e1423fcd5cdd3501d03c Author: Herbert Valerio Riedel Date: Mon Sep 15 22:33:30 2014 +0200 Update travis badge in README.md >--------------------------------------------------------------- 32392756273d28ef4639e1423fcd5cdd3501d03c README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 77eba7b..da7eb55 100644 --- a/README.md +++ b/README.md @@ -1,4 +1,4 @@ -System.FilePath [![Build Status](https://travis-ci.org/ghc/packages-filepath.png?branch=master)](https://travis-ci.org/ghc/packages-filepath) +System.FilePath [![Build Status](https://travis-ci.org/haskell/filepath.svg)](https://travis-ci.org/haskell/filepath) =============== I have written a `System.FilePath` module in part based on the one in From git at git.haskell.org Thu Mar 19 11:32:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:32:54 +0000 (UTC) Subject: [commit: packages/filepath] master: Update .travis.yml (03ba1d4) Message-ID: <20150319113254.EEC0D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/03ba1d436fff2d5cc1a76aba22c152637b75f7b4 >--------------------------------------------------------------- commit 03ba1d436fff2d5cc1a76aba22c152637b75f7b4 Author: Herbert Valerio Riedel Date: Mon Sep 15 22:48:24 2014 +0200 Update .travis.yml This adds GHC 7.8.3 and GHC HEAD to the build-matrix, and removes a couple of redundant GHC versions. >--------------------------------------------------------------- 03ba1d436fff2d5cc1a76aba22c152637b75f7b4 .travis.yml | 50 +++++++++++++++++++++++++++++++------------------- 1 file changed, 31 insertions(+), 19 deletions(-) diff --git a/.travis.yml b/.travis.yml index 9c9c7de..c54ba64 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,36 +1,48 @@ env: - GHCVER=6.12.3 - GHCVER=7.0.1 - - GHCVER=7.0.2 - - GHCVER=7.0.3 - GHCVER=7.0.4 - - GHCVER=7.2.1 - GHCVER=7.2.2 - - GHCVER=7.4.1 - GHCVER=7.4.2 - - GHCVER=7.6.1 - - GHCVER=7.6.2 - GHCVER=7.6.3 + - GHCVER=7.8.3 + - GHCVER=head + +matrix: + allow_failures: + - env: GHCVER=head before_install: - - sudo add-apt-repository -y ppa:hvr/ghc - - sudo apt-get update - - sudo apt-get install cabal-install-1.18 ghc-$GHCVER - - export PATH=/opt/ghc/$GHCVER/bin:$PATH + - travis_retry sudo add-apt-repository -y ppa:hvr/ghc + - travis_retry sudo apt-get update + - travis_retry sudo apt-get install cabal-install-1.18 ghc-$GHCVER + - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/1.18/bin:$PATH install: - - cabal-1.18 update + - cabal update - if [ "$GHCVER" = "6.12.3" ]; then - cabal-1.18 install --only-dependencies; - cabal-1.18 install 'QuickCheck==2.6.*'; + cabal install --only-dependencies; + cabal install 'QuickCheck==2.6.*'; else - cabal-1.18 install --only-dependencies --enable-tests; + cabal install --only-dependencies --enable-tests; fi script: - cd tests/ && runghc ./GenTests.hs && cd .. - - cabal-1.18 configure --enable-tests -v2 - - cabal-1.18 build - - cabal-1.18 test - - cabal-1.18 check - - cabal-1.18 sdist + - cabal configure --enable-tests -v2 + - cabal build + - cabal test + - cabal check + - cabal sdist + +# The following scriptlet checks that the resulting source distribution can be built & installed + - function install_from_tarball { + export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; + if [ -f "dist/$SRC_TGZ" ]; then + cabal install "dist/$SRC_TGZ"; + else + echo "expected 'dist/$SRC_TGZ' not found"; + exit 1; + fi + } + - install_from_tarball From git at git.haskell.org Thu Mar 19 11:32:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:32:57 +0000 (UTC) Subject: [commit: packages/filepath] master: Drop GHC 6.12.3 from build-matrix (5dab4b2) Message-ID: <20150319113257.01BA43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/5dab4b2e065a8325eb5c8d98f3a92aa624e91949 >--------------------------------------------------------------- commit 5dab4b2e065a8325eb5c8d98f3a92aa624e91949 Author: Herbert Valerio Riedel Date: Mon Sep 15 22:54:09 2014 +0200 Drop GHC 6.12.3 from build-matrix It's starting to require too many workarounds... >--------------------------------------------------------------- 5dab4b2e065a8325eb5c8d98f3a92aa624e91949 .travis.yml | 8 +------- 1 file changed, 1 insertion(+), 7 deletions(-) diff --git a/.travis.yml b/.travis.yml index c54ba64..babe140 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,5 +1,4 @@ env: - - GHCVER=6.12.3 - GHCVER=7.0.1 - GHCVER=7.0.4 - GHCVER=7.2.2 @@ -20,12 +19,7 @@ before_install: install: - cabal update - - if [ "$GHCVER" = "6.12.3" ]; then - cabal install --only-dependencies; - cabal install 'QuickCheck==2.6.*'; - else - cabal install --only-dependencies --enable-tests; - fi + - cabal install --only-dependencies --enable-tests; script: - cd tests/ && runghc ./GenTests.hs && cd .. From git at git.haskell.org Thu Mar 19 11:32:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:32:59 +0000 (UTC) Subject: [commit: packages/filepath] master: Update the README (92ab027) Message-ID: <20150319113259.090D13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/92ab027a58050df949235b507a75d83b34eb1978 >--------------------------------------------------------------- commit 92ab027a58050df949235b507a75d83b34eb1978 Author: Neil Mitchell Date: Sat Oct 18 20:34:04 2014 +0100 Update the README >--------------------------------------------------------------- 92ab027a58050df949235b507a75d83b34eb1978 README.md | 65 ++++++--------------------------------------------------------- 1 file changed, 6 insertions(+), 59 deletions(-) diff --git a/README.md b/README.md index da7eb55..0063212 100644 --- a/README.md +++ b/README.md @@ -1,62 +1,9 @@ -System.FilePath [![Build Status](https://travis-ci.org/haskell/filepath.svg)](https://travis-ci.org/haskell/filepath) -=============== +# FilePath [![Hackage version](https://img.shields.io/hackage/v/filepath.svg?style=flat)](http://hackage.haskell.org/package/filepath) [![Build Status](http://img.shields.io/travis/haskell/filepath.svg?style=flat)](https://travis-ci.org/haskell/filepath) -I have written a `System.FilePath` module in part based on the one in -Yhc, and in part based on the one in Cabal (thanks to Lemmih). The aim -is to try and get this module into the base package, as `FilePath`s -are something many programs use, but its all too easy to hack up a -little function that gets it right most of the time on most platforms, -and there lies a source of bugs. +This package provides functionality for manipulating `FilePath` values. It provides three modules: -This module is Posix (Linux) and Windows capable - just import -`System.FilePath` and it will pick the right one. Of course, if you -demand Windows paths on all OSes, then `System.FilePath.Windows` will -give you that (same with Posix). Written in Haskell 98 with -Hierarchical Modules. +* [`System.FilePath.Posix`](http://hackage.haskell.org/package/filepath/docs/System-FilePath-Posix.html) manipulates POSIX/Linux style `FilePath` values (with `/` as the path separator). +* [`System.FilePath.Windows`](http://hackage.haskell.org/package/filepath/docs/System-FilePath-Windows.html) manipulates Windows style `FilePath` values (with either `/` or `\` as the path separator, and dealing with drives). +* [`System.FilePath`](http://hackage.haskell.org/package/filepath/docs/System-FilePath.html) which is an alias for the module appropriate to your platform. -If you go to the -[Haddock](http://hackage.haskell.org/package/filepath/docs/System-FilePath.html) -page, there are a few little examples at the top of the re-exported module. - - -Acknowledgments ---------------- - -Thanks to Marc Webber, shapr, David House, Lemmih, others... - - -Competitors ------------ - -`System.FilePath` from Cabal, by Lemmih `FilePath.hs` and -`NameManip.hs` from MissingH - -The one from Cabal and `FilePath.hs` in MissingH are both very -similar, I stole lots of good ideas from those two. - -`NameManip.hs` seems to be more unix specific, but all functions in -that module have equivalents in this new `System.FilePath` module. - -Hopefully this new module can be used without noticing any lost -functions, and certainly adds new features/functions to the table. - - -Should `FilePath` be an abstract data type? -------------------------------------------- - -The answer for this library is no. This is a deliberate design decision. - -In Haskell 98 the definition is `type FilePath = String`, and all -functions operating on `FilePath`s, i.e. `readFile`/`writeFile` etc -take `FilePath`s. The only way to introduce an abstract type is to -provide wrappers for these functions or casts between `String`s and -`FilePathAbstract`s. - -There are also additional questions as to what constitutes a -`FilePath`, and what is just a pure `String`. For example, -"/path/file.ext" is a `FilePath`. Is "/" ? "/path" ? "path" ? -"file.ext" ? ".ext" ? "file" ? - -With that being accepted, it should be trivial to write -`System.FilePath.ByteString` which has the same interface as -`System.FilePath` yet operates on `ByteString`s. +All modules provide the same API, and the same documentation (calling out differences on different platforms). From git at git.haskell.org Thu Mar 19 11:33:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:01 +0000 (UTC) Subject: [commit: packages/filepath] master: More tweaks to the README (60c84ae) Message-ID: <20150319113301.0F4E93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/60c84ae0e650673cdc31b6ed7bac13bd346a350e >--------------------------------------------------------------- commit 60c84ae0e650673cdc31b6ed7bac13bd346a350e Author: Neil Mitchell Date: Sat Oct 18 20:36:38 2014 +0100 More tweaks to the README >--------------------------------------------------------------- 60c84ae0e650673cdc31b6ed7bac13bd346a350e README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 0063212..7be73db 100644 --- a/README.md +++ b/README.md @@ -1,9 +1,9 @@ # FilePath [![Hackage version](https://img.shields.io/hackage/v/filepath.svg?style=flat)](http://hackage.haskell.org/package/filepath) [![Build Status](http://img.shields.io/travis/haskell/filepath.svg?style=flat)](https://travis-ci.org/haskell/filepath) -This package provides functionality for manipulating `FilePath` values. It provides three modules: +The `filepath` package provides functionality for manipulating `FilePath` values, and is shipped with both [GHC](https://www.haskell.org/ghc/) and the [Haskell Platform](https://www.haskell.org/platform/). It provides three modules: * [`System.FilePath.Posix`](http://hackage.haskell.org/package/filepath/docs/System-FilePath-Posix.html) manipulates POSIX/Linux style `FilePath` values (with `/` as the path separator). * [`System.FilePath.Windows`](http://hackage.haskell.org/package/filepath/docs/System-FilePath-Windows.html) manipulates Windows style `FilePath` values (with either `/` or `\` as the path separator, and dealing with drives). * [`System.FilePath`](http://hackage.haskell.org/package/filepath/docs/System-FilePath.html) which is an alias for the module appropriate to your platform. -All modules provide the same API, and the same documentation (calling out differences on different platforms). +All three modules provide the same API, and the same documentation (calling out differences in the different variants). From git at git.haskell.org Thu Mar 19 11:33:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:03 +0000 (UTC) Subject: [commit: packages/filepath] master: Update the license (8654bfb) Message-ID: <20150319113303.156DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/8654bfb7b3b246bd7c44e9b72bca8f919578b89c >--------------------------------------------------------------- commit 8654bfb7b3b246bd7c44e9b72bca8f919578b89c Author: Neil Mitchell Date: Sat Oct 18 20:37:13 2014 +0100 Update the license >--------------------------------------------------------------- 8654bfb7b3b246bd7c44e9b72bca8f919578b89c LICENSE | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/LICENSE b/LICENSE index 401ab57..c556af9 100644 --- a/LICENSE +++ b/LICENSE @@ -1,4 +1,4 @@ -Copyright Neil Mitchell 2005-2007. +Copyright Neil Mitchell 2005-2014. All rights reserved. Redistribution and use in source and binary forms, with or without From git at git.haskell.org Thu Mar 19 11:33:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:05 +0000 (UTC) Subject: [commit: packages/filepath] master: Use consistent lexical conventions in the .cabal file (542aca4) Message-ID: <20150319113305.1B5FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/542aca40ab1ab1e442c21cc95a2be23dea08646b >--------------------------------------------------------------- commit 542aca40ab1ab1e442c21cc95a2be23dea08646b Author: Neil Mitchell Date: Sun Oct 19 12:50:30 2014 +0100 Use consistent lexical conventions in the .cabal file >--------------------------------------------------------------- 542aca40ab1ab1e442c21cc95a2be23dea08646b filepath.cabal | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/filepath.cabal b/filepath.cabal index 37f1de0..949c081 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -1,15 +1,15 @@ -Name: filepath -Version: 1.3.0.3 +name: filepath +version: 1.3.0.3 -- NOTE: Don't forget to update ./changelog.md -License: BSD3 +license: BSD3 license-file: LICENSE -Author: Neil Mitchell -Maintainer: libraries at haskell.org +author: Neil Mitchell +maintainer: libraries at haskell.org bug-reports: https://github.com/haskell/filepath/issues -Homepage: http://www-users.cs.york.ac.uk/~ndm/filepath/ -Category: System +homepage: http://www-users.cs.york.ac.uk/~ndm/filepath/ +category: System build-type: Simple -Synopsis: Library for manipulating FilePaths in a cross platform way. +synopsis: Library for manipulating FilePaths in a cross platform way. cabal-version: >=1.10 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.2.1, GHC==7.0.4, GHC==7.0.3, GHC==7.0.2, GHC==7.0.1, GHC==6.12.3 description: @@ -20,24 +20,24 @@ description: the same interface. See either for examples and a list of the available functions. -Extra-Source-Files: +extra-source-files: System/FilePath/Internal.hs README.md changelog.md -Library +library default-language: Haskell98 other-extensions: CPP - if impl(GHC>=7.2) + if impl(GHC >= 7.2) other-extensions: Safe - Exposed-modules: + exposed-modules: System.FilePath System.FilePath.Posix System.FilePath.Windows - Build-Depends: + build-depends: base >= 4 && < 4.9 ghc-options: -Wall @@ -46,7 +46,7 @@ Library -- generate the tests/FilePath_Tests.hs file via -- -- cd tests/ && runghc ./GenTests.hs -Test-Suite filepath-tests +test-suite filepath-tests type: exitcode-stdio-1.0 default-language: Haskell98 main-is: FilePath_Test.hs From git at git.haskell.org Thu Mar 19 11:33:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:07 +0000 (UTC) Subject: [commit: packages/filepath] master: Switch the maintainer (0cf9f03) Message-ID: <20150319113307.225E73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/0cf9f03599ee4d936138c93b3e5ee7a30d1e4717 >--------------------------------------------------------------- commit 0cf9f03599ee4d936138c93b3e5ee7a30d1e4717 Author: Neil Mitchell Date: Sun Oct 19 12:52:50 2014 +0100 Switch the maintainer >--------------------------------------------------------------- 0cf9f03599ee4d936138c93b3e5ee7a30d1e4717 filepath.cabal | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/filepath.cabal b/filepath.cabal index 949c081..bcbfa52 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -3,8 +3,9 @@ version: 1.3.0.3 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE -author: Neil Mitchell -maintainer: libraries at haskell.org +author: Neil Mitchell +maintainer: Neil Mitchell +copyright: Neil Mitchell 2005-2014 bug-reports: https://github.com/haskell/filepath/issues homepage: http://www-users.cs.york.ac.uk/~ndm/filepath/ category: System From git at git.haskell.org Thu Mar 19 11:33:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:09 +0000 (UTC) Subject: [commit: packages/filepath] master: Add a trailing newline to the Cabal file (b2d09de) Message-ID: <20150319113309.281943A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/b2d09dea6482fe6ebdddc7616da0fc6356141571 >--------------------------------------------------------------- commit b2d09dea6482fe6ebdddc7616da0fc6356141571 Author: Neil Mitchell Date: Sun Oct 19 12:53:40 2014 +0100 Add a trailing newline to the Cabal file >--------------------------------------------------------------- b2d09dea6482fe6ebdddc7616da0fc6356141571 filepath.cabal | 0 1 file changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Thu Mar 19 11:33:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:11 +0000 (UTC) Subject: [commit: packages/filepath] master: Shorten Setup.hs, make it more obvious it is uninteresting (113285a) Message-ID: <20150319113311.2E4AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/113285ad32218e641c5f9685f8d48e578e00e567 >--------------------------------------------------------------- commit 113285ad32218e641c5f9685f8d48e578e00e567 Author: Neil Mitchell Date: Sun Oct 19 13:02:19 2014 +0100 Shorten Setup.hs, make it more obvious it is uninteresting >--------------------------------------------------------------- 113285ad32218e641c5f9685f8d48e578e00e567 Setup.hs | 4 ---- 1 file changed, 4 deletions(-) diff --git a/Setup.hs b/Setup.hs index 6fa548c..9a994af 100644 --- a/Setup.hs +++ b/Setup.hs @@ -1,6 +1,2 @@ -module Main (main) where - import Distribution.Simple - -main :: IO () main = defaultMain From git at git.haskell.org Thu Mar 19 11:33:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:13 +0000 (UTC) Subject: [commit: packages/filepath] master: Remove some redundant whitespace (65289ab) Message-ID: <20150319113313.343BE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/65289ab1b0e431c763614dca5fd92452d31389b8 >--------------------------------------------------------------- commit 65289ab1b0e431c763614dca5fd92452d31389b8 Author: Neil Mitchell Date: Sun Oct 19 13:36:20 2014 +0100 Remove some redundant whitespace >--------------------------------------------------------------- 65289ab1b0e431c763614dca5fd92452d31389b8 .travis.yml | 0 1 file changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Thu Mar 19 11:33:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:15 +0000 (UTC) Subject: [commit: packages/filepath] master: Improve the README (2c758fd) Message-ID: <20150319113315.3B6893A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/2c758fdbd4c94a82c5ae1b0497ba5552ce8a23c0 >--------------------------------------------------------------- commit 2c758fdbd4c94a82c5ae1b0497ba5552ce8a23c0 Author: Neil Mitchell Date: Sun Oct 19 13:36:30 2014 +0100 Improve the README >--------------------------------------------------------------- 2c758fdbd4c94a82c5ae1b0497ba5552ce8a23c0 README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 7be73db..bf67c71 100644 --- a/README.md +++ b/README.md @@ -3,7 +3,7 @@ The `filepath` package provides functionality for manipulating `FilePath` values, and is shipped with both [GHC](https://www.haskell.org/ghc/) and the [Haskell Platform](https://www.haskell.org/platform/). It provides three modules: * [`System.FilePath.Posix`](http://hackage.haskell.org/package/filepath/docs/System-FilePath-Posix.html) manipulates POSIX/Linux style `FilePath` values (with `/` as the path separator). -* [`System.FilePath.Windows`](http://hackage.haskell.org/package/filepath/docs/System-FilePath-Windows.html) manipulates Windows style `FilePath` values (with either `/` or `\` as the path separator, and dealing with drives). -* [`System.FilePath`](http://hackage.haskell.org/package/filepath/docs/System-FilePath.html) which is an alias for the module appropriate to your platform. +* [`System.FilePath.Windows`](http://hackage.haskell.org/package/filepath/docs/System-FilePath-Windows.html) manipulates Windows style `FilePath` values (with either `\` or `/` as the path separator, and deals with drives). +* [`System.FilePath`](http://hackage.haskell.org/package/filepath/docs/System-FilePath.html) is an alias for the module appropriate to your platform. All three modules provide the same API, and the same documentation (calling out differences in the different variants). From git at git.haskell.org Thu Mar 19 11:33:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:17 +0000 (UTC) Subject: [commit: packages/filepath] master: Update some copyright/contact bits and pieces (d82e3a1) Message-ID: <20150319113317.423213A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/d82e3a1bee4afb3ec0b4db847d4f83d8112ae73b >--------------------------------------------------------------- commit d82e3a1bee4afb3ec0b4db847d4f83d8112ae73b Author: Neil Mitchell Date: Sun Oct 19 13:36:52 2014 +0100 Update some copyright/contact bits and pieces >--------------------------------------------------------------- d82e3a1bee4afb3ec0b4db847d4f83d8112ae73b System/FilePath.hs | 4 ++-- System/FilePath/Internal.hs | 4 ++-- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/System/FilePath.hs b/System/FilePath.hs index fcfc351..ab0edcb 100644 --- a/System/FilePath.hs +++ b/System/FilePath.hs @@ -4,10 +4,10 @@ #endif {- | Module : System.FilePath -Copyright : (c) Neil Mitchell 2005-2007 +Copyright : (c) Neil Mitchell 2005-2014 License : BSD3 -Maintainer : libraries at haskell.org +Maintainer : ndmitchell at gmail.com Stability : stable Portability : portable diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 09f3560..3db81b9 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -8,10 +8,10 @@ -- | -- Module : System.FilePath.MODULE_NAME --- Copyright : (c) Neil Mitchell 2005-2007 +-- Copyright : (c) Neil Mitchell 2005-2014 -- License : BSD3 -- --- Maintainer : libraries at haskell.org +-- Maintainer : ndmitchell at gmail.com -- Stability : stable -- Portability : portable -- From git at git.haskell.org Thu Mar 19 11:33:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:19 +0000 (UTC) Subject: [commit: packages/filepath] master: Refactor so less is conditional on CPP (f3b0b08) Message-ID: <20150319113319.4A9DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/f3b0b08481f5929ed166033fb52d149dbe8fc8b6 >--------------------------------------------------------------- commit f3b0b08481f5929ed166033fb52d149dbe8fc8b6 Author: Neil Mitchell Date: Sun Oct 19 13:38:22 2014 +0100 Refactor so less is conditional on CPP >--------------------------------------------------------------- f3b0b08481f5929ed166033fb52d149dbe8fc8b6 System/FilePath.hs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/System/FilePath.hs b/System/FilePath.hs index ab0edcb..73947db 100644 --- a/System/FilePath.hs +++ b/System/FilePath.hs @@ -19,11 +19,10 @@ same interface. See either for examples and a list of the available functions. -} +module System.FilePath(module X) where + #if defined(mingw32_HOST_OS) || defined(__MINGW32__) -module System.FilePath(module System.FilePath.Windows) where -import System.FilePath.Windows +import System.FilePath.Windows as X #else -module System.FilePath(module System.FilePath.Posix) where -import System.FilePath.Posix +import System.FilePath.Posix as X #endif - From git at git.haskell.org Thu Mar 19 11:33:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:21 +0000 (UTC) Subject: [commit: packages/filepath] master: Add a .ghci file (6a25a41) Message-ID: <20150319113321.548D23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/6a25a41a3707a1bd76e3248aad30a88a8faa351d >--------------------------------------------------------------- commit 6a25a41a3707a1bd76e3248aad30a88a8faa351d Author: Neil Mitchell Date: Sun Oct 19 13:42:44 2014 +0100 Add a .ghci file >--------------------------------------------------------------- 6a25a41a3707a1bd76e3248aad30a88a8faa351d .ghci | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/.ghci b/.ghci new file mode 100644 index 0000000..f0e38f8 --- /dev/null +++ b/.ghci @@ -0,0 +1,6 @@ +:set -fwarn-unused-binds -fwarn-unused-imports +:set -isrc -itest +:load System.FilePath System.FilePath.Windows System.FilePath.Posix +import qualified System.FilePath.Windows as Windows +import qualified System.FilePath.Posix as Posix + From git at git.haskell.org Thu Mar 19 11:33:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:23 +0000 (UTC) Subject: [commit: packages/filepath] master: Add dist to the .gitignore (6259b6a) Message-ID: <20150319113323.5A2363A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/6259b6a6c6a3933a482aa20692c995ef11609a60 >--------------------------------------------------------------- commit 6259b6a6c6a3933a482aa20692c995ef11609a60 Author: Neil Mitchell Date: Sun Oct 19 13:45:24 2014 +0100 Add dist to the .gitignore >--------------------------------------------------------------- 6259b6a6c6a3933a482aa20692c995ef11609a60 .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index d83c989..089a3e5 100644 --- a/.gitignore +++ b/.gitignore @@ -1,3 +1,4 @@ GNUmakefile dist-install/ +dist/ ghc.mk From git at git.haskell.org Thu Mar 19 11:33:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:25 +0000 (UTC) Subject: [commit: packages/filepath] master: Add ghci targets for building the docs (7282939) Message-ID: <20150319113325.601E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/72829393ec0e61d63a7ab5304ed909f917bce1bb >--------------------------------------------------------------- commit 72829393ec0e61d63a7ab5304ed909f917bce1bb Author: Neil Mitchell Date: Sun Oct 19 13:45:34 2014 +0100 Add ghci targets for building the docs >--------------------------------------------------------------- 72829393ec0e61d63a7ab5304ed909f917bce1bb .ghci | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.ghci b/.ghci index f0e38f8..f075783 100644 --- a/.ghci +++ b/.ghci @@ -4,3 +4,5 @@ import qualified System.FilePath.Windows as Windows import qualified System.FilePath.Posix as Posix +:def docs_ const $ return $ unlines [":!cabal haddock"] +:def docs const $ return $ unlines [":docs_",":!start dist\\doc\\html\\filepath\\System-FilePath.html"] From git at git.haskell.org Thu Mar 19 11:33:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:27 +0000 (UTC) Subject: [commit: packages/filepath] master: Add a :test target (bb3489d) Message-ID: <20150319113327.65E063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/bb3489d3764615da4e9b94ba2ada05956fed2706 >--------------------------------------------------------------- commit bb3489d3764615da4e9b94ba2ada05956fed2706 Author: Neil Mitchell Date: Sun Oct 19 13:48:02 2014 +0100 Add a :test target >--------------------------------------------------------------- bb3489d3764615da4e9b94ba2ada05956fed2706 .ghci | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.ghci b/.ghci index f075783..404232e 100644 --- a/.ghci +++ b/.ghci @@ -6,3 +6,5 @@ import qualified System.FilePath.Posix as Posix :def docs_ const $ return $ unlines [":!cabal haddock"] :def docs const $ return $ unlines [":docs_",":!start dist\\doc\\html\\filepath\\System-FilePath.html"] + +:def test const $ return $ unlines [":!cd tests && runhaskell GenTests.hs",":!cd tests && runhaskell FilePath_Test.hs"] From git at git.haskell.org Thu Mar 19 11:33:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:29 +0000 (UTC) Subject: [commit: packages/filepath] master: Fix up the docs so the code has the correct indentation (e447cc5) Message-ID: <20150319113329.6CC153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/e447cc5fd19b43bac57311b9a4400bc8790cbaa2 >--------------------------------------------------------------- commit e447cc5fd19b43bac57311b9a4400bc8790cbaa2 Author: Neil Mitchell Date: Sun Oct 19 14:00:32 2014 +0100 Fix up the docs so the code has the correct indentation >--------------------------------------------------------------- e447cc5fd19b43bac57311b9a4400bc8790cbaa2 System/FilePath/Internal.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 3db81b9..167766d 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -30,8 +30,10 @@ -- -- You want to download a file from the web and save it to disk: -- --- @do let file = 'makeValid' url --- System.IO.createDirectoryIfMissing True ('takeDirectory' file)@ +--@ +--do let file = 'makeValid' url +-- System.IO.createDirectoryIfMissing True ('takeDirectory' file) +--@ -- -- You want to compile a Haskell file, but put the hi file under \"interface\" -- From git at git.haskell.org Thu Mar 19 11:33:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:31 +0000 (UTC) Subject: [commit: packages/filepath] master: #4, make QFilePath have the right set Char instance (e6e5b6f) Message-ID: <20150319113331.722603A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/e6e5b6faec1d80f88fe4b18ccfe194399252dbd1 >--------------------------------------------------------------- commit e6e5b6faec1d80f88fe4b18ccfe194399252dbd1 Author: Neil Mitchell Date: Sun Oct 19 14:01:13 2014 +0100 #4, make QFilePath have the right set Char instance >--------------------------------------------------------------- e6e5b6faec1d80f88fe4b18ccfe194399252dbd1 tests/AutoTest.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/tests/AutoTest.hs b/tests/AutoTest.hs index c186570..8902869 100644 --- a/tests/AutoTest.hs +++ b/tests/AutoTest.hs @@ -21,16 +21,16 @@ constTest False = error "Failed on constTest" -data QFilePath = QFilePath FilePath +newtype QFilePath = QFilePath FilePath deriving Show instance Arbitrary QFilePath where - arbitrary = liftM QFilePath arbitrary + arbitrary = fmap (QFilePath . map fromQChar) arbitrary +newtype QChar = QChar {fromQChar :: Char} --- QuickCheck 2.4.1.1 has its own Arbitrary Char instance, so commented out for now --- instance Arbitrary Char where --- arbitrary = elements "?|./:\\abcd 123;_" +instance Arbitrary QChar where + arbitrary = fmap QChar $ elements "?|./:\\abcd 123;_" From git at git.haskell.org Thu Mar 19 11:33:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:33 +0000 (UTC) Subject: [commit: packages/filepath] master: #4, make sure the tests fail if there is an error (9db4bd5) Message-ID: <20150319113333.78FB93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/9db4bd5aef95521d021129519c525996fe783579 >--------------------------------------------------------------- commit 9db4bd5aef95521d021129519c525996fe783579 Author: Neil Mitchell Date: Sun Oct 19 14:01:25 2014 +0100 #4, make sure the tests fail if there is an error >--------------------------------------------------------------- 9db4bd5aef95521d021129519c525996fe783579 tests/AutoTest.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/tests/AutoTest.hs b/tests/AutoTest.hs index 8902869..8526c99 100644 --- a/tests/AutoTest.hs +++ b/tests/AutoTest.hs @@ -35,7 +35,11 @@ instance Arbitrary QChar where quickSafe :: Testable a => a -> IO () -quickSafe prop = quickCheckWith (stdArgs { chatty = False }) prop +quickSafe prop = do + res <- quickCheckWithResult (stdArgs { chatty = False }) prop + case res of + Success{} -> return () + _ -> error $ show res -- checkit quick prop -- below is mainly stolen from Test.QuickCheck, modified to crash out on failure From git at git.haskell.org Thu Mar 19 11:33:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:35 +0000 (UTC) Subject: [commit: packages/filepath] master: Remove dead code (ed063fb) Message-ID: <20150319113335.7FC9F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/ed063fbdb110afe40ca17814806c0627278a1e00 >--------------------------------------------------------------- commit ed063fbdb110afe40ca17814806c0627278a1e00 Author: Neil Mitchell Date: Sun Oct 19 14:02:19 2014 +0100 Remove dead code >--------------------------------------------------------------- ed063fbdb110afe40ca17814806c0627278a1e00 tests/AutoTest.hs | 68 ------------------------------------------------------- 1 file changed, 68 deletions(-) diff --git a/tests/AutoTest.hs b/tests/AutoTest.hs index 8526c99..38a9501 100644 --- a/tests/AutoTest.hs +++ b/tests/AutoTest.hs @@ -40,71 +40,3 @@ quickSafe prop = do case res of Success{} -> return () _ -> error $ show res - -- checkit quick prop - --- below is mainly stolen from Test.QuickCheck, modified to crash out on failure --- Doesn't compile with QuickCheck 2.4.1.1, so we just use the quickCheck function for now - -{- -quick :: Config -quick = Config - { configMaxTest = 500 - , configMaxFail = 1000 - , configSize = (+ 3) . (`div` 2) - , configEvery = \n args -> let s = show n in s ++ [ '\b' | _ <- s ] - } - -checkit :: Testable a => Config -> a -> IO () -checkit config a = - do rnd <- newStdGen - tests config (evaluate a) rnd 0 0 [] - - -tests :: Config -> Gen Result -> StdGen -> Int -> Int -> [[String]] -> IO () -tests config gen rnd0 ntest nfail stamps - | ntest == configMaxTest config = do done "OK, passed" ntest stamps - | nfail == configMaxFail config = do done "Arguments exhausted after" ntest stamps - error "More entropy required!" - | otherwise = - do putStr (configEvery config ntest (arguments result)) - case ok result of - Nothing -> - tests config gen rnd1 ntest (nfail+1) stamps - Just True -> - tests config gen rnd1 (ntest+1) nfail (stamp result:stamps) - Just False -> - error ( "Falsifiable, after " - ++ show ntest - ++ " tests:\n" - ++ unlines (arguments result) - ) - where - result = generate (configSize config ntest) rnd2 gen - (rnd1,rnd2) = split rnd0 - -done :: String -> Int -> [[String]] -> IO () -done mesg ntest stamps = - do putStr ( mesg ++ " " ++ show ntest ++ " tests" ++ table ) - where - table = display - . map entry - . reverse - . sort - . map pairLength - . group - . sort - . filter (not . null) - $ stamps - - display [] = ".\n" - display [x] = " (" ++ x ++ ").\n" - display xs = ".\n" ++ unlines (map (++ ".") xs) - - pairLength xss@(xs:_) = (length xss, xs) - entry (n, xs) = percentage n ntest - ++ " " - ++ concat (intersperse ", " xs) - - percentage n m = show ((100 * n) `div` m) ++ "%" --} - From git at git.haskell.org Thu Mar 19 11:33:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:37 +0000 (UTC) Subject: [commit: packages/filepath] master: Reformat whitespace (6fb3fcb) Message-ID: <20150319113337.854C73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/6fb3fcb22b283e6d41d062bafa96d61387c91d0d >--------------------------------------------------------------- commit 6fb3fcb22b283e6d41d062bafa96d61387c91d0d Author: Neil Mitchell Date: Sun Oct 19 14:02:26 2014 +0100 Reformat whitespace >--------------------------------------------------------------- 6fb3fcb22b283e6d41d062bafa96d61387c91d0d tests/AutoTest.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/AutoTest.hs b/tests/AutoTest.hs index 38a9501..96e6fbb 100644 --- a/tests/AutoTest.hs +++ b/tests/AutoTest.hs @@ -22,7 +22,7 @@ constTest False = error "Failed on constTest" newtype QFilePath = QFilePath FilePath - deriving Show + deriving Show instance Arbitrary QFilePath where arbitrary = fmap (QFilePath . map fromQChar) arbitrary From git at git.haskell.org Thu Mar 19 11:33:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:39 +0000 (UTC) Subject: [commit: packages/filepath] master: Revert the clever import trick - it confuses Haddock (d03fd87) Message-ID: <20150319113339.8C86E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/d03fd877bdd0b05c9b6e943711a4fe60406f937f >--------------------------------------------------------------- commit d03fd877bdd0b05c9b6e943711a4fe60406f937f Author: Neil Mitchell Date: Sun Oct 19 14:10:28 2014 +0100 Revert the clever import trick - it confuses Haddock >--------------------------------------------------------------- d03fd877bdd0b05c9b6e943711a4fe60406f937f System/FilePath.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/System/FilePath.hs b/System/FilePath.hs index 73947db..331ae81 100644 --- a/System/FilePath.hs +++ b/System/FilePath.hs @@ -19,10 +19,11 @@ same interface. See either for examples and a list of the available functions. -} -module System.FilePath(module X) where #if defined(mingw32_HOST_OS) || defined(__MINGW32__) -import System.FilePath.Windows as X +module System.FilePath(module System.FilePath.Windows) where +import System.FilePath.Windows #else -import System.FilePath.Posix as X +module System.FilePath(module System.FilePath.Posix) where +import System.FilePath.Posix #endif From git at git.haskell.org Thu Mar 19 11:33:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:41 +0000 (UTC) Subject: [commit: packages/filepath] master: Improve the module description (28b7f1b) Message-ID: <20150319113341.935813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/28b7f1bbdee5f71b47e6320727d1c3f809f20bb0 >--------------------------------------------------------------- commit 28b7f1bbdee5f71b47e6320727d1c3f809f20bb0 Author: Neil Mitchell Date: Sun Oct 19 14:10:44 2014 +0100 Improve the module description >--------------------------------------------------------------- 28b7f1bbdee5f71b47e6320727d1c3f809f20bb0 filepath.cabal | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/filepath.cabal b/filepath.cabal index c93a78e..1d093c5 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -14,12 +14,15 @@ synopsis: Library for manipulating FilePaths in a cross platform way. cabal-version: >=1.10 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.2.1, GHC==7.0.4, GHC==7.0.3, GHC==7.0.2, GHC==7.0.1, GHC==6.12.3 description: - A library for 'FilePath' manipulations, using Posix or Windows filepaths - depending on the platform. + This package provides functionality for manipulating @FilePath@ values, and is shipped with both and the . It provides three modules: . - Both "System.FilePath.Posix" and "System.FilePath.Windows" provide - the same interface. See either for examples and a list of the - available functions. + * "System.FilePath.Posix" manipulates POSIX\/Linux style @FilePath@ values (with @\/@ as the path separator). + . + * "System.FilePath.Windows" manipulates Windows style @FilePath@ values (with either @\\@ or @\/@ as the path separator, and deals with drives). + . + * "System.FilePath" is an alias for the module appropriate to your platform. + . + All three modules provide the same API, and the same documentation (calling out differences in the different variants). extra-source-files: System/FilePath/Internal.hs From git at git.haskell.org Thu Mar 19 11:33:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:43 +0000 (UTC) Subject: [commit: packages/filepath] master: Fix the homepage to actually exist (de23b8a) Message-ID: <20150319113343.999193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/de23b8a6ac960624a555a78011ae87c8ac9f5680 >--------------------------------------------------------------- commit de23b8a6ac960624a555a78011ae87c8ac9f5680 Author: Neil Mitchell Date: Sun Oct 19 14:10:59 2014 +0100 Fix the homepage to actually exist >--------------------------------------------------------------- de23b8a6ac960624a555a78011ae87c8ac9f5680 filepath.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/filepath.cabal b/filepath.cabal index 1d093c5..b229e91 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -7,7 +7,7 @@ author: Neil Mitchell maintainer: Neil Mitchell copyright: Neil Mitchell 2005-2014 bug-reports: https://github.com/haskell/filepath/issues -homepage: http://www-users.cs.york.ac.uk/~ndm/filepath/ +homepage: https://github.com/haskell/filepath#readme category: System build-type: Simple synopsis: Library for manipulating FilePaths in a cross platform way. From git at git.haskell.org Thu Mar 19 11:33:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:45 +0000 (UTC) Subject: [commit: packages/filepath] master: Put the docs back, it seems to conflict with CPP some weird way (4285ef6) Message-ID: <20150319113345.A04173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/4285ef68d720d8c74666653b2ee32be1bd9b626c >--------------------------------------------------------------- commit 4285ef68d720d8c74666653b2ee32be1bd9b626c Author: Neil Mitchell Date: Sun Oct 19 14:13:35 2014 +0100 Put the docs back, it seems to conflict with CPP some weird way >--------------------------------------------------------------- 4285ef68d720d8c74666653b2ee32be1bd9b626c System/FilePath/Internal.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 167766d..18a4ee4 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -30,10 +30,8 @@ -- -- You want to download a file from the web and save it to disk: -- ---@ ---do let file = 'makeValid' url --- System.IO.createDirectoryIfMissing True ('takeDirectory' file) ---@ +-- @do let file = 'makeValid' url +-- System.IO.createDirectoryIfMissing True ('takeDirectory' file)@ -- -- You want to compile a Haskell file, but put the hi file under \"interface\" -- From git at git.haskell.org Thu Mar 19 11:33:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:47 +0000 (UTC) Subject: [commit: packages/filepath] master: Move isRelativeDrive tests to isRelative (db0d2ff) Message-ID: <20150319113347.A85E33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/db0d2ff7d934de41a3be6c16b5acd298e614e54d >--------------------------------------------------------------- commit db0d2ff7d934de41a3be6c16b5acd298e614e54d Author: Thomas Miedema Date: Sun Sep 14 16:52:40 2014 +0200 Move isRelativeDrive tests to isRelative Those tests were commented out, because isRelativeDrive is not normally exported from the module. Instead of doing a special testing compilation by passing the TESTING=1 environment variable, it seemed easier to rewrite the tests to use isRelative. Only the following trivial test is not accounted for: isRelativeDrive "" == True >--------------------------------------------------------------- db0d2ff7d934de41a3be6c16b5acd298e614e54d System/FilePath/Internal.hs | 16 +++------------- 1 file changed, 3 insertions(+), 13 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 18a4ee4..16790fc 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -79,11 +79,6 @@ module System.FilePath.MODULE_NAME makeRelative, isRelative, isAbsolute, isValid, makeValid - -#ifdef TESTING - , isRelativeDrive -#endif - ) where @@ -813,23 +808,18 @@ makeValid path = joinDrive drv $ validElements $ validChars pth -- > Windows: isRelative "path\\test" == True -- > Windows: isRelative "c:\\test" == False -- > Windows: isRelative "c:test" == True +-- > Windows: isRelative "c:\\" == False +-- > Windows: isRelative "c:/" == False -- > Windows: isRelative "c:" == True -- > Windows: isRelative "\\\\foo" == False -- > Windows: isRelative "/foo" == True -- > Posix: isRelative "test/path" == True -- > Posix: isRelative "/test" == False +-- > Posix: isRelative "/" == False isRelative :: FilePath -> Bool isRelative = isRelativeDrive . takeDrive --- Disable these tests for now, as we want to be able to run the --- testsuite without doing a special TESTING compilation --- -- > isRelativeDrive "" == True --- -- > Windows: isRelativeDrive "c:\\" == False --- -- > Windows: isRelativeDrive "c:/" == False --- -- > Windows: isRelativeDrive "c:" == True --- -- > Windows: isRelativeDrive "\\\\foo" == False --- -- > Posix: isRelativeDrive "/" == False isRelativeDrive :: String -> Bool isRelativeDrive x = null x || maybe False (not . isPathSeparator . last . fst) (readDriveLetter x) From git at git.haskell.org Thu Mar 19 11:33:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:49 +0000 (UTC) Subject: [commit: packages/filepath] master: Fix links and add more tests and comments (5fbec04) Message-ID: <20150319113349.B0B533A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/5fbec041d755403b2fe72c2d4bfd415349443c71 >--------------------------------------------------------------- commit 5fbec041d755403b2fe72c2d4bfd415349443c71 Author: Thomas Miedema Date: Sun Sep 14 16:52:05 2014 +0200 Fix links and add more tests and comments No tests are removed, only new ones added. The semantics of `combine` is questionable. See also #8752. Not changing anything for the moment. >--------------------------------------------------------------- 5fbec041d755403b2fe72c2d4bfd415349443c71 System/FilePath/Internal.hs | 70 +++++++++++++++++++++++++++++++++++++++------ 1 file changed, 62 insertions(+), 8 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 16790fc..36e88e4 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -39,6 +39,10 @@ -- -- The examples in code format descibed by each function are used to generate -- tests, and should give clear semantics for the functions. +-- +-- References: +-- [1] "Naming Files, Paths, and Namespaces" +-- http://msdn.microsoft.com/en-us/library/windows/desktop/aa365247.aspx ----------------------------------------------------------------------------- module System.FilePath.MODULE_NAME @@ -337,9 +341,8 @@ addSlash :: FilePath -> FilePath -> (FilePath, FilePath) addSlash a xs = (a++c,d) where (c,d) = span isPathSeparator xs --- http://msdn.microsoft.com/library/default.asp?url=/library/en-us/fileio/fs/naming_a_file.asp +-- See [1]. -- "\\?\D:\" or "\\?\UNC\\" --- a is "\\?\" readDriveUNC :: FilePath -> Maybe (FilePath, FilePath) readDriveUNC (s1:s2:'?':s3:xs) | all isPathSeparator [s1,s2,s3] = case map toUpper xs of @@ -347,6 +350,7 @@ readDriveUNC (s1:s2:'?':s3:xs) | all isPathSeparator [s1,s2,s3] = let (a,b) = readDriveShareName (drop 4 xs) in Just (s1:s2:'?':s3:take 4 xs ++ a, b) _ -> case readDriveLetter xs of + -- Extended-length path. Just (a,b) -> Just (s1:s2:'?':s3:a,b) Nothing -> Nothing readDriveUNC _ = Nothing @@ -365,7 +369,7 @@ readDriveShare (s1:s2:xs) | isPathSeparator s1 && isPathSeparator s2 = readDriveShare _ = Nothing {- assume you have already seen \\ -} -{- share\bob -> "share","\","bob" -} +{- share\bob -> "share\", "bob" -} readDriveShareName :: String -> (FilePath, FilePath) readDriveShareName name = addSlash a b where (a,b) = break isPathSeparator name @@ -403,11 +407,21 @@ dropDrive = snd . splitDrive -- | Does a path have a drive. -- -- > not (hasDrive x) == null (takeDrive x) +-- > Posix: hasDrive "/foo" == True +-- > Windows: hasDrive "C:\\foo" == True +-- > Windows: hasDrive "C:foo" == True +-- > hasDrive "foo" == False +-- > hasDrive "" == False hasDrive :: FilePath -> Bool hasDrive = not . null . takeDrive -- | Is an element a drive +-- +-- > Posix: isDrive "/" == True +-- > Posix: isDrive "/foo" == False +-- > Windows: isDrive "C:\\" == True +-- > Windows: isDrive "C:\\foo" == False isDrive :: FilePath -> Bool isDrive = null . dropDrive @@ -509,9 +523,9 @@ addTrailingPathSeparator x = if hasTrailingPathSeparator x then x else x ++ [pat -- | Remove any trailing path separators -- -- > dropTrailingPathSeparator "file/test/" == "file/test" --- > Posix: not (hasTrailingPathSeparator (dropTrailingPathSeparator x)) || isDrive x -- > Posix: dropTrailingPathSeparator "/" == "/" -- > Windows: dropTrailingPathSeparator "\\" == "\\" +-- > Posix: not (hasTrailingPathSeparator (dropTrailingPathSeparator x)) || isDrive x dropTrailingPathSeparator :: FilePath -> FilePath dropTrailingPathSeparator x = if hasTrailingPathSeparator x && not (isDrive x) @@ -524,6 +538,8 @@ dropTrailingPathSeparator x = -- -- > takeDirectory x `isPrefixOf` x || takeDirectory x == "." -- > takeDirectory "foo" == "." +-- > takeDirectory "/" == "/" +-- > takeDirectory "/foo" == "/" -- > takeDirectory "/foo/bar/baz" == "/foo/bar" -- > takeDirectory "/foo/bar/baz/" == "/foo/bar/baz" -- > takeDirectory "foo/bar/baz" == "foo/bar" @@ -547,10 +563,35 @@ replaceDirectory x dir = combineAlways dir (takeFileName x) -- | Combine two paths, if the second path 'isAbsolute', then it returns the second. -- -- > Valid x => combine (takeDirectory x) (takeFileName x) `equalFilePath` x +-- +-- Combined: -- > Posix: combine "/" "test" == "/test" -- > Posix: combine "home" "bob" == "home/bob" +-- > Posix: combine "x:" "foo" == "x:/foo" +-- > Windows: combine "C:\\foo" "bar" == "C:\\foo\\bar" -- > Windows: combine "home" "bob" == "home\\bob" +-- +-- Not combined: +-- > Posix: combine "home" "/bob" == "/bob" +-- > Windows: combine "home" "C:\\bob" == "C:\\bob" +-- +-- Not combined (tricky): +-- On Windows, if a filepath starts with a single slash, it is relative to the +-- root of the current drive. In [1], this is (confusingly) referred to as an +-- absolute path. +-- The current behavior of @combine@ is to never combine these forms. +-- -- > Windows: combine "home" "/bob" == "/bob" +-- > Windows: combine "home" "\\bob" == "\\bob" +-- > Windows: combine "C:\\home" "\\bob" == "\\bob" +-- +-- On Windows, from [1]: "If a file name begins with only a disk designator +-- but not the backslash after the colon, it is interpreted as a relative path +-- to the current directory on the drive with the specified letter." +-- The current behavior of @combine@ is to never combine these forms. +-- +-- > Windows: combine "D:\\foo" "C:bar" == "C:bar" +-- > Windows: combine "C:\\foo" "C:bar" == "C:bar" combine :: FilePath -> FilePath -> FilePath combine a b | hasDrive b || (not (null b) && isPathSeparator (head b)) = b | otherwise = combineAlways a b @@ -590,8 +631,9 @@ splitPath x = [drive | drive /= ""] ++ f path -- | Just as 'splitPath', but don't add the trailing slashes to each element. -- --- > splitDirectories "test/file" == ["test","file"] --- > splitDirectories "/test/file" == ["/","test","file"] +-- > splitDirectories "test/file" == ["test","file"] +-- > splitDirectories "/test/file" == ["/","test","file"] +-- > Windows: splitDirectories "C:\\test\\file" == ["C:\\", "test", "file"] -- > Valid x => joinPath (splitDirectories x) `equalFilePath` x -- > splitDirectories "" == [] splitDirectories :: FilePath -> [FilePath] @@ -741,8 +783,7 @@ normaliseDrive drive = if isJust $ readDriveLetter x2 repSlash x = if isPathSeparator x then pathSeparator else x --- information for validity functions on Windows --- see http://msdn.microsoft.com/library/default.asp?url=/library/en-us/fileio/fs/naming_a_file.asp +-- Information for validity functions on Windows. See [1]. badCharacters :: [Char] badCharacters = ":*?><|\"" badElements :: [FilePath] @@ -812,14 +853,27 @@ makeValid path = joinDrive drv $ validElements $ validChars pth -- > Windows: isRelative "c:/" == False -- > Windows: isRelative "c:" == True -- > Windows: isRelative "\\\\foo" == False +-- > Windows: isRelative "\\\\?\\foo" == False +-- > Windows: isRelative "\\\\?\\UNC\\foo" == False -- > Windows: isRelative "/foo" == True +-- > Windows: isRelative "\\foo" == True -- > Posix: isRelative "test/path" == True -- > Posix: isRelative "/test" == False -- > Posix: isRelative "/" == False +-- +-- According to [1]: +-- +-- * "A UNC name of any format [is never relative]." +-- +-- * "You cannot use the "\\?\" prefix with a relative path." isRelative :: FilePath -> Bool isRelative = isRelativeDrive . takeDrive +{- c:foo -} +-- From [1]: "If a file name begins with only a disk designator but not the +-- backslash after the colon, it is interpreted as a relative path to the +-- current directory on the drive with the specified letter." isRelativeDrive :: String -> Bool isRelativeDrive x = null x || maybe False (not . isPathSeparator . last . fst) (readDriveLetter x) From git at git.haskell.org Thu Mar 19 11:33:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:51 +0000 (UTC) Subject: [commit: packages/filepath] master: Refactor: use hasTrailingPathSeparator (9db8af2) Message-ID: <20150319113351.B75843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/9db8af2520acdfeba945c6221ed3db6b2c3ba81f >--------------------------------------------------------------- commit 9db8af2520acdfeba945c6221ed3db6b2c3ba81f Author: Thomas Miedema Date: Sun Sep 14 18:26:21 2014 +0200 Refactor: use hasTrailingPathSeparator hasTrailingPathSeparator is defined as: hasTrailingPathSeparator "" = False hasTrailingPathSeparator x = isPathSeparator (last x) >--------------------------------------------------------------- 9db8af2520acdfeba945c6221ed3db6b2c3ba81f System/FilePath/Internal.hs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 36e88e4..977eae9 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -683,7 +683,7 @@ equalFilePath a b = f a == f b f x | isWindows = dropTrailSlash $ map toLower $ normalise x | otherwise = dropTrailSlash $ normalise x - dropTrailSlash x | length x >= 2 && isPathSeparator (last x) = init x + dropTrailSlash x | length x >= 2 && hasTrailingPathSeparator x = init x | otherwise = x @@ -758,9 +758,8 @@ normalise path = joinDrive' (normaliseDrive drv) (f pth) joinDrive' "" "" = "." joinDrive' d p = joinDrive d p - isDirPath xs = lastSep xs - || not (null xs) && last xs == '.' && lastSep (init xs) - lastSep xs = not (null xs) && isPathSeparator (last xs) + isDirPath xs = hasTrailingPathSeparator xs + || not (null xs) && last xs == '.' && hasTrailingPathSeparator (init xs) f = joinPath . dropDots . splitDirectories . propSep @@ -876,7 +875,7 @@ isRelative = isRelativeDrive . takeDrive -- current directory on the drive with the specified letter." isRelativeDrive :: String -> Bool isRelativeDrive x = null x || - maybe False (not . isPathSeparator . last . fst) (readDriveLetter x) + maybe False (not . hasTrailingPathSeparator . fst) (readDriveLetter x) -- | @not . 'isRelative'@ From git at git.haskell.org Thu Mar 19 11:33:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:53 +0000 (UTC) Subject: [commit: packages/filepath] master: Bug fix: pathSeparator can be forward slash on Windows (6ab7023) Message-ID: <20150319113353.BD2CE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/6ab7023fb3b8c4ee5305036684dae2d92115c1bc >--------------------------------------------------------------- commit 6ab7023fb3b8c4ee5305036684dae2d92115c1bc Author: Thomas Miedema Date: Sun Sep 14 21:19:30 2014 +0200 Bug fix: pathSeparator can be forward slash on Windows dropTrailingPathSeparator "/" would return "\\" on Windows, since that is the default: pathSeparator = if isWindows then '\\' else '/' The function `normalise` can be used to normalise pathSeparators in filepaths, the function `dropTrailingPathSeparator` shouldn't do it for you. The test now runs for both Posix as Windows. >--------------------------------------------------------------- 6ab7023fb3b8c4ee5305036684dae2d92115c1bc System/FilePath/Internal.hs | 4 ++-- changelog.md | 3 +++ 2 files changed, 5 insertions(+), 2 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 7db6c04..7220804 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -528,14 +528,14 @@ addTrailingPathSeparator x = if hasTrailingPathSeparator x then x else x ++ [pat -- | Remove any trailing path separators -- -- > dropTrailingPathSeparator "file/test/" == "file/test" --- > Posix: dropTrailingPathSeparator "/" == "/" +-- > dropTrailingPathSeparator "/" == "/" -- > Windows: dropTrailingPathSeparator "\\" == "\\" -- > Posix: not (hasTrailingPathSeparator (dropTrailingPathSeparator x)) || isDrive x dropTrailingPathSeparator :: FilePath -> FilePath dropTrailingPathSeparator x = if hasTrailingPathSeparator x && not (isDrive x) then let x' = reverse $ dropWhile isPathSeparator $ reverse x - in if null x' then [pathSeparator] else x' + in if null x' then [last x] else x' else x diff --git a/changelog.md b/changelog.md index 2feaf5a..13dad0e 100644 --- a/changelog.md +++ b/changelog.md @@ -4,6 +4,9 @@ * Bundled with GHC 7.10.1 + * Bug fix: on Windows, `dropTrailingPathSeparator "/"` now returns `"/"` + unchanged, instead of the normalised `"\\"`. + ## 1.3.0.2 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 11:33:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:55 +0000 (UTC) Subject: [commit: packages/filepath] master: Refactor: introduce function hasLeadingPathSeparator for clarity (df3f13e) Message-ID: <20150319113355.C59723A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/df3f13e7353cdd9ee15e91b475c29aeb72c61c4d >--------------------------------------------------------------- commit df3f13e7353cdd9ee15e91b475c29aeb72c61c4d Author: Thomas Miedema Date: Sun Sep 14 17:46:28 2014 +0200 Refactor: introduce function hasLeadingPathSeparator for clarity Also fix the comment to reflect the code. This fixes #8752. >--------------------------------------------------------------- df3f13e7353cdd9ee15e91b475c29aeb72c61c4d System/FilePath/Internal.hs | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 977eae9..7db6c04 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -511,6 +511,11 @@ hasTrailingPathSeparator "" = False hasTrailingPathSeparator x = isPathSeparator (last x) +hasLeadingPathSeparator :: FilePath -> Bool +hasLeadingPathSeparator "" = False +hasLeadingPathSeparator x = isPathSeparator (head x) + + -- | Add a trailing file path separator if one is not already present. -- -- > hasTrailingPathSeparator (addTrailingPathSeparator x) @@ -560,7 +565,8 @@ replaceDirectory :: FilePath -> String -> FilePath replaceDirectory x dir = combineAlways dir (takeFileName x) --- | Combine two paths, if the second path 'isAbsolute', then it returns the second. +-- | Combine two paths, if the second path starts with a path separator or a +-- drive letter, then it returns the second. -- -- > Valid x => combine (takeDirectory x) (takeFileName x) `equalFilePath` x -- @@ -593,7 +599,7 @@ replaceDirectory x dir = combineAlways dir (takeFileName x) -- > Windows: combine "D:\\foo" "C:bar" == "C:bar" -- > Windows: combine "C:\\foo" "C:bar" == "C:bar" combine :: FilePath -> FilePath -> FilePath -combine a b | hasDrive b || (not (null b) && isPathSeparator (head b)) = b +combine a b | hasLeadingPathSeparator b || hasDrive b = b | otherwise = combineAlways a b -- | Combine two paths, assuming rhs is NOT absolute. From git at git.haskell.org Thu Mar 19 11:33:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:57 +0000 (UTC) Subject: [commit: packages/filepath] master: Refactor: break instead of span and 3x reverse (4283661) Message-ID: <20150319113357.CC5423A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/428366140210c616c1bbfb9a5bf6c31114c6c8b2 >--------------------------------------------------------------- commit 428366140210c616c1bbfb9a5bf6c31114c6c8b2 Author: Thomas Miedema Date: Sun Sep 14 23:45:40 2014 +0200 Refactor: break instead of span and 3x reverse This works because pathSeparators can only occur at the end of splitPath elements. h is passed a pathElement without separators. Add a test to show that superfluous (and a weird combination of) pathSeparators are still preserved. This function does not normalise pathSeparators, otherwise it could be simplified further. >--------------------------------------------------------------- 428366140210c616c1bbfb9a5bf6c31114c6c8b2 System/FilePath/Internal.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 7220804..e8cf9a4 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -824,6 +824,7 @@ isValid path = -- > isValid (makeValid x) -- > isValid x ==> makeValid x == x -- > makeValid "" == "_" +-- > Windows: makeValid "c:\\already\\/valid" == "c:\\already\\/valid" -- > Windows: makeValid "c:\\test:of_test" == "c:\\test_of_test" -- > Windows: makeValid "test*" == "test_" -- > Windows: makeValid "c:\\test\\nul" == "c:\\test\\nul_" @@ -843,8 +844,8 @@ makeValid path = joinDrive drv $ validElements $ validChars pth | otherwise = x validElements x = joinPath $ map g $ splitPath x - g x = h (reverse b) ++ reverse a - where (a,b) = span isPathSeparator $ reverse x + g x = h a ++ b + where (a,b) = break isPathSeparator x h x = if map toUpper a `elem` badElements then a ++ "_" <.> b else x where (a,b) = splitExtensions x From git at git.haskell.org Thu Mar 19 11:33:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:33:59 +0000 (UTC) Subject: [commit: packages/filepath] master: Make splitFileName quickcheck test Posix only (0dd40ad) Message-ID: <20150319113359.D45FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/0dd40adf8d4a8a3f409f3a877dba2ae7e98a5c5b >--------------------------------------------------------------- commit 0dd40adf8d4a8a3f409f3a877dba2ae7e98a5c5b Author: Thomas Miedema Date: Thu Oct 23 19:41:19 2014 +0200 Make splitFileName quickcheck test Posix only See Github #14. >--------------------------------------------------------------- 0dd40adf8d4a8a3f409f3a877dba2ae7e98a5c5b System/FilePath/Internal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index e8cf9a4..f85e635 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -432,7 +432,7 @@ isDrive = null . dropDrive -- | Split a filename into directory and file. 'combine' is the inverse. -- -- > Valid x => uncurry () (splitFileName x) == x || fst (splitFileName x) == "./" --- > Valid x => isValid (fst (splitFileName x)) +-- > Posix: Valid x => isValid (fst (splitFileName x)) -- > splitFileName "file/bob.txt" == ("file/", "bob.txt") -- > splitFileName "file/" == ("file/", "") -- > splitFileName "bob" == ("./", "bob") From git at git.haskell.org Thu Mar 19 11:34:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:01 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge pull request #1 from thomie/cleanup (fd201b7) Message-ID: <20150319113401.DB3373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/fd201b7fbe55ad1594599e47bd24a50f77430b77 >--------------------------------------------------------------- commit fd201b7fbe55ad1594599e47bd24a50f77430b77 Merge: 4285ef6 0dd40ad Author: Neil Mitchell Date: Sun Oct 26 20:20:37 2014 +0000 Merge pull request #1 from thomie/cleanup Cleanup >--------------------------------------------------------------- fd201b7fbe55ad1594599e47bd24a50f77430b77 System/FilePath/Internal.hs | 116 +++++++++++++++++++++++++++++++------------- changelog.md | 3 ++ 2 files changed, 86 insertions(+), 33 deletions(-) From git at git.haskell.org Thu Mar 19 11:34:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:03 +0000 (UTC) Subject: [commit: packages/filepath] master: Bug fix: equalFilePath "C:\\" "C:" == False (bdc0446) Message-ID: <20150319113403.E1F353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/bdc0446d7a0fe3b6d344d92fbe21fde0ce1f014d >--------------------------------------------------------------- commit bdc0446d7a0fe3b6d344d92fbe21fde0ce1f014d Author: Thomas Miedema Date: Thu Oct 23 13:00:27 2014 +0200 Bug fix: equalFilePath "C:\\" "C:" == False This started out as a simple refactoring of `equalFilePath`, and later turned out to also fix a small bug. The refactoring is: use `dropTrailingPathSeparator` instead of the custom function `dropTrailSlash`. A difference between these two functions is that `dropTrailingPathSeparator` potentially removes multiple trailing slashes, whereas `dropTrailSlash` only removes the last one. But since we `normalise` the FilePath first, which removes superfluous pathSeparators, this difference does not matter to us. Another difference is that `dropTrailingPathSeparator` does not drop slashes when the FilePath isDrive, but `dropTrailSlash` does: dropTrailSlash "C:\\" == "C:" dropTrailSlash "C:\\\\" == "C:\\" dropTrailingPathSeparator "C:\\" == "C:\\" dropTrailingPathSeparator "C:\\\\" == "C:\\\\" As a result, equalFilePath of drives on Windows changes slightly: Before: equalFilePath "C:\\" "C:" == True equalFilePath "C:\\\\" "C:" == False After: equalFilePath "C:\\" "C:" == False equalFilePath "C:\\\\" "C:" == False This can be considered a bug fix, since "C:\\foo" and "C:foo", and thus "C:\\" and "C:", are not the same thing. >--------------------------------------------------------------- bdc0446d7a0fe3b6d344d92fbe21fde0ce1f014d System/FilePath/Internal.hs | 7 ++----- changelog.md | 3 +++ 2 files changed, 5 insertions(+), 5 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index f85e635..83be81d 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -686,11 +686,8 @@ joinPath = foldr combine "" equalFilePath :: FilePath -> FilePath -> Bool equalFilePath a b = f a == f b where - f x | isWindows = dropTrailSlash $ map toLower $ normalise x - | otherwise = dropTrailSlash $ normalise x - - dropTrailSlash x | length x >= 2 && hasTrailingPathSeparator x = init x - | otherwise = x + f x | isWindows = dropTrailingPathSeparator $ map toLower $ normalise x + | otherwise = dropTrailingPathSeparator $ normalise x -- | Contract a filename, based on a relative path. diff --git a/changelog.md b/changelog.md index 13dad0e..b62ac45 100644 --- a/changelog.md +++ b/changelog.md @@ -7,6 +7,9 @@ * Bug fix: on Windows, `dropTrailingPathSeparator "/"` now returns `"/"` unchanged, instead of the normalised `"\\"`. + * Bug fix: on Windows, `equalFilePath "C:\\" "C:"` now retuns `False`, + instead of `True`. + ## 1.3.0.2 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 11:34:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:05 +0000 (UTC) Subject: [commit: packages/filepath] master: #15, increase 100x the number of property tests (9a353ab) Message-ID: <20150319113405.E84AD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/9a353ab3c09bf3e90bafa15fbccc389875bb2cd8 >--------------------------------------------------------------- commit 9a353ab3c09bf3e90bafa15fbccc389875bb2cd8 Author: Neil Mitchell Date: Sun Oct 26 20:28:48 2014 +0000 #15, increase 100x the number of property tests >--------------------------------------------------------------- 9a353ab3c09bf3e90bafa15fbccc389875bb2cd8 tests/AutoTest.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/AutoTest.hs b/tests/AutoTest.hs index 96e6fbb..f9d8a90 100644 --- a/tests/AutoTest.hs +++ b/tests/AutoTest.hs @@ -36,7 +36,7 @@ instance Arbitrary QChar where quickSafe :: Testable a => a -> IO () quickSafe prop = do - res <- quickCheckWithResult (stdArgs { chatty = False }) prop + res <- quickCheckWithResult stdArgs{chatty=False, maxSuccess=10000} prop case res of Success{} -> return () _ -> error $ show res From git at git.haskell.org Thu Mar 19 11:34:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:07 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge branch 'master' of https://github.com/haskell/filepath (4e1e39f) Message-ID: <20150319113407.EF0C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/4e1e39f35009b44b008a15cd2999644ffea9bac9 >--------------------------------------------------------------- commit 4e1e39f35009b44b008a15cd2999644ffea9bac9 Merge: 9a353ab fd201b7 Author: Neil Mitchell Date: Sun Oct 26 20:30:07 2014 +0000 Merge branch 'master' of https://github.com/haskell/filepath >--------------------------------------------------------------- 4e1e39f35009b44b008a15cd2999644ffea9bac9 System/FilePath/Internal.hs | 116 +++++++++++++++++++++++++++++++------------- changelog.md | 3 ++ 2 files changed, 86 insertions(+), 33 deletions(-) From git at git.haskell.org Thu Mar 19 11:34:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:10 +0000 (UTC) Subject: [commit: packages/filepath] master: Bug fix: isDrive "" == False (f9ae34b) Message-ID: <20150319113410.01AC73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/f9ae34b04cf5644e31f2920a001af37edcd3f946 >--------------------------------------------------------------- commit f9ae34b04cf5644e31f2920a001af37edcd3f946 Author: Thomas Miedema Date: Mon Sep 15 09:48:41 2014 +0200 Bug fix: isDrive "" == False isDrive is only called from `dropTrailingPathSeparator` and `combineAlways`. Both times occur after a check if the argument is not empty (i.e. null for combineAlways, and hasTrailingPathSeparator for dropTrailingPathSeparator). So this change is safe. >--------------------------------------------------------------- f9ae34b04cf5644e31f2920a001af37edcd3f946 System/FilePath/Internal.hs | 3 ++- changelog.md | 2 ++ 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index f85e635..b82b2ab 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -422,8 +422,9 @@ hasDrive = not . null . takeDrive -- > Posix: isDrive "/foo" == False -- > Windows: isDrive "C:\\" == True -- > Windows: isDrive "C:\\foo" == False +-- > isDrive "" == False isDrive :: FilePath -> Bool -isDrive = null . dropDrive +isDrive x = not (null x) && null (dropDrive x) --------------------------------------------------------------------- diff --git a/changelog.md b/changelog.md index 13dad0e..2825edb 100644 --- a/changelog.md +++ b/changelog.md @@ -4,6 +4,8 @@ * Bundled with GHC 7.10.1 + * Bug fix: `isDrive ""` now retuns `False`, instead of `True`. + * Bug fix: on Windows, `dropTrailingPathSeparator "/"` now returns `"/"` unchanged, instead of the normalised `"\\"`. From git at git.haskell.org Thu Mar 19 11:34:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:12 +0000 (UTC) Subject: [commit: packages/filepath] master: Bug fix: isValid "\\\\\\foo" == False (bef533f) Message-ID: <20150319113412.0986B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/bef533f555111f697d23ab27e9b506169e2ca1a7 >--------------------------------------------------------------- commit bef533f555111f697d23ab27e9b506169e2ca1a7 Author: Thomas Miedema Date: Sun Oct 26 00:21:24 2014 +0200 Bug fix: isValid "\\\\\\foo" == False Share name can not start with a slash. >--------------------------------------------------------------- bef533f555111f697d23ab27e9b506169e2ca1a7 System/FilePath/Internal.hs | 9 +++++++-- changelog.md | 3 +++ 2 files changed, 10 insertions(+), 2 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index f85e635..263836f 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -807,14 +807,16 @@ badElements = ["CON", "PRN", "AUX", "NUL", "COM1", "COM2", "COM3", "COM4", "COM5 -- > Windows: isValid "c:\\test\\prn.txt" == False -- > Windows: isValid "c:\\nul\\file" == False -- > Windows: isValid "\\\\" == False +-- > Windows: isValid "\\\\\\foo" == False isValid :: FilePath -> Bool isValid "" = False isValid _ | isPosix = True isValid path = not (any (`elem` badCharacters) x2) && not (any f $ splitDirectories x2) && - not (length path >= 2 && all isPathSeparator path) + not (length x1 >= 2 && all isPathSeparator x1) where + x1 = head (splitPath path) x2 = dropDrive path f x = map toUpper (dropExtensions x) `elem` badElements @@ -831,10 +833,13 @@ isValid path = -- > Windows: makeValid "c:\\test\\prn.txt" == "c:\\test\\prn_.txt" -- > Windows: makeValid "c:\\test/prn.txt" == "c:\\test/prn_.txt" -- > Windows: makeValid "c:\\nul\\file" == "c:\\nul_\\file" +-- > Windows: makeValid "\\\\\\foo" == "\\\\drive" makeValid :: FilePath -> FilePath makeValid "" = "_" makeValid path | isPosix = path -makeValid x | length x >= 2 && all isPathSeparator x = take 2 x ++ "drive" +makeValid xs | length x >= 2 && all isPathSeparator x = take 2 x ++ "drive" + where + x = head (splitPath xs) makeValid path = joinDrive drv $ validElements $ validChars pth where (drv,pth) = splitDrive path diff --git a/changelog.md b/changelog.md index 13dad0e..1637673 100644 --- a/changelog.md +++ b/changelog.md @@ -7,6 +7,9 @@ * Bug fix: on Windows, `dropTrailingPathSeparator "/"` now returns `"/"` unchanged, instead of the normalised `"\\"`. + * Bug fix: on Windows, `isValid "\\\\\\foo"` now returns `False`, instead + of `True`. + ## 1.3.0.2 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 11:34:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:14 +0000 (UTC) Subject: [commit: packages/filepath] master: Refactor splitDirectories (ba8bae5) Message-ID: <20150319113414.116183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/ba8bae53fe80189112b9f19e46fad2edf1530ab3 >--------------------------------------------------------------- commit ba8bae53fe80189112b9f19e46fad2edf1530ab3 Author: Thomas Miedema Date: Thu Oct 23 12:59:29 2014 +0200 Refactor splitDirectories Use `dropTrailingPathSeparator` instead of the custom function `g` to remove trailing path separators from FilePath components generated with `splitPath`. Since `dropTrailingPathSeparator` does not change FilePath components for which isDrive is True, it is no longer necessary to handle the first FilePath component in a special way. >--------------------------------------------------------------- ba8bae53fe80189112b9f19e46fad2edf1530ab3 System/FilePath/Internal.hs | 10 +--------- 1 file changed, 1 insertion(+), 9 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index f85e635..c684070 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -643,15 +643,7 @@ splitPath x = [drive | drive /= ""] ++ f path -- > Valid x => joinPath (splitDirectories x) `equalFilePath` x -- > splitDirectories "" == [] splitDirectories :: FilePath -> [FilePath] -splitDirectories path = - if hasDrive path then head pathComponents : f (tail pathComponents) - else f pathComponents - where - pathComponents = splitPath path - - f = map g - g x = if null res then x else res - where res = takeWhile (not . isPathSeparator) x +splitDirectories = map dropTrailingPathSeparator . splitPath -- | Join path elements back together. From git at git.haskell.org Thu Mar 19 11:34:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:16 +0000 (UTC) Subject: [commit: packages/filepath] master: Refactor takeDirectory (c8521d6) Message-ID: <20150319113416.194EA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/c8521d6b327007a288c3c3dbab7f26214882ff97 >--------------------------------------------------------------- commit c8521d6b327007a288c3c3dbab7f26214882ff97 Author: Thomas Miedema Date: Thu Oct 23 14:17:20 2014 +0200 Refactor takeDirectory Do not reimplement `dropTrailingPathSeparator`. >--------------------------------------------------------------- c8521d6b327007a288c3c3dbab7f26214882ff97 System/FilePath/Internal.hs | 7 +------ 1 file changed, 1 insertion(+), 6 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 138fd85..c101610 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -88,7 +88,6 @@ module System.FilePath.MODULE_NAME import Data.Char(toLower, toUpper, isAsciiLower, isAsciiUpper) import Data.Maybe(isJust, fromJust) -import Data.List(isPrefixOf) import System.Environment(getEnv) @@ -552,11 +551,7 @@ dropTrailingPathSeparator x = -- > Windows: takeDirectory "foo\\bar\\\\" == "foo\\bar" -- > Windows: takeDirectory "C:\\" == "C:\\" takeDirectory :: FilePath -> FilePath -takeDirectory x = if isDrive dir || null res then dir else res - where - res = reverse $ dropWhile isPathSeparator $ reverse dir - dir = dropFileName x - _ = isPrefixOf x -- warning suppression +takeDirectory = dropTrailingPathSeparator . dropFileName -- | Set the directory, keeping the filename the same. -- From git at git.haskell.org Thu Mar 19 11:34:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:18 +0000 (UTC) Subject: [commit: packages/filepath] master: Cleanup: rename file to dir in takeDirectory (53db747) Message-ID: <20150319113418.1FD143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/53db7473fb3338fe8e47d58320234bd82c52466b >--------------------------------------------------------------- commit 53db7473fb3338fe8e47d58320234bd82c52466b Author: Thomas Miedema Date: Sun Sep 14 20:49:52 2014 +0200 Cleanup: rename file to dir in takeDirectory >--------------------------------------------------------------- 53db7473fb3338fe8e47d58320234bd82c52466b System/FilePath/Internal.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index f85e635..5ea2be5 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -552,10 +552,10 @@ dropTrailingPathSeparator x = -- > Windows: takeDirectory "foo\\bar\\\\" == "foo\\bar" -- > Windows: takeDirectory "C:\\" == "C:\\" takeDirectory :: FilePath -> FilePath -takeDirectory x = if isDrive file || (null res && not (null file)) then file else res +takeDirectory x = if isDrive dir || (null res && not (null dir)) then dir else res where - res = reverse $ dropWhile isPathSeparator $ reverse file - file = dropFileName x + res = reverse $ dropWhile isPathSeparator $ reverse dir + dir = dropFileName x _ = isPrefixOf x -- warning suppression -- | Set the directory, keeping the filename the same. From git at git.haskell.org Thu Mar 19 11:34:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:20 +0000 (UTC) Subject: [commit: packages/filepath] master: Remove unnecessary `not . null` check (4fdf3b4) Message-ID: <20150319113420.2859D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/4fdf3b432582118a259faf76d9b9e1d2f43e1322 >--------------------------------------------------------------- commit 4fdf3b432582118a259faf76d9b9e1d2f43e1322 Author: Thomas Miedema Date: Thu Oct 23 14:14:30 2014 +0200 Remove unnecessary `not . null` check If `res` and `dir` are both null, it doesn't matter which one we return. >--------------------------------------------------------------- 4fdf3b432582118a259faf76d9b9e1d2f43e1322 System/FilePath/Internal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 5ea2be5..138fd85 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -552,7 +552,7 @@ dropTrailingPathSeparator x = -- > Windows: takeDirectory "foo\\bar\\\\" == "foo\\bar" -- > Windows: takeDirectory "C:\\" == "C:\\" takeDirectory :: FilePath -> FilePath -takeDirectory x = if isDrive dir || (null res && not (null dir)) then dir else res +takeDirectory x = if isDrive dir || null res then dir else res where res = reverse $ dropWhile isPathSeparator $ reverse dir dir = dropFileName x From git at git.haskell.org Thu Mar 19 11:34:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:22 +0000 (UTC) Subject: [commit: packages/filepath] master: Allow a broader range of QuickCheck (35c1012) Message-ID: <20150319113422.319E43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/35c1012b6f88552ba1a4eaf65b3e960710875dc4 >--------------------------------------------------------------- commit 35c1012b6f88552ba1a4eaf65b3e960710875dc4 Author: Neil Mitchell Date: Sun Oct 26 20:43:06 2014 +0000 Allow a broader range of QuickCheck >--------------------------------------------------------------- 35c1012b6f88552ba1a4eaf65b3e960710875dc4 filepath.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/filepath.cabal b/filepath.cabal index b229e91..2c72d54 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -59,7 +59,7 @@ test-suite filepath-tests build-depends: filepath, base, - QuickCheck == 2.6.*, + QuickCheck > 2.6 && < 2.8, random == 1.0.* source-repository head From git at git.haskell.org Thu Mar 19 11:34:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:24 +0000 (UTC) Subject: [commit: packages/filepath] master: Make sure :test is actually using the new code (0986318) Message-ID: <20150319113424.37A5B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/0986318f95ae32ac183209060b678666d74e6d68 >--------------------------------------------------------------- commit 0986318f95ae32ac183209060b678666d74e6d68 Author: Neil Mitchell Date: Sun Oct 26 20:43:16 2014 +0000 Make sure :test is actually using the new code >--------------------------------------------------------------- 0986318f95ae32ac183209060b678666d74e6d68 .ghci | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.ghci b/.ghci index 404232e..7d3ecc9 100644 --- a/.ghci +++ b/.ghci @@ -7,4 +7,4 @@ import qualified System.FilePath.Posix as Posix :def docs_ const $ return $ unlines [":!cabal haddock"] :def docs const $ return $ unlines [":docs_",":!start dist\\doc\\html\\filepath\\System-FilePath.html"] -:def test const $ return $ unlines [":!cd tests && runhaskell GenTests.hs",":!cd tests && runhaskell FilePath_Test.hs"] +:def test const $ return $ unlines [":!cd tests && runhaskell GenTests.hs",":!cd tests && runhaskell -i.. FilePath_Test.hs"] From git at git.haskell.org Thu Mar 19 11:34:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:26 +0000 (UTC) Subject: [commit: packages/filepath] master: Add a shrink method for QFilePath (0a2c5a4) Message-ID: <20150319113426.3D4EE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/0a2c5a48b25cd8e0dcf0537f3cfa175487e7be3c >--------------------------------------------------------------- commit 0a2c5a48b25cd8e0dcf0537f3cfa175487e7be3c Author: Neil Mitchell Date: Sun Oct 26 20:43:28 2014 +0000 Add a shrink method for QFilePath >--------------------------------------------------------------- 0a2c5a48b25cd8e0dcf0537f3cfa175487e7be3c tests/AutoTest.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/tests/AutoTest.hs b/tests/AutoTest.hs index f9d8a90..56b6ec6 100644 --- a/tests/AutoTest.hs +++ b/tests/AutoTest.hs @@ -26,6 +26,7 @@ newtype QFilePath = QFilePath FilePath instance Arbitrary QFilePath where arbitrary = fmap (QFilePath . map fromQChar) arbitrary + shrink (QFilePath x) = map QFilePath $ shrink x newtype QChar = QChar {fromQChar :: Char} From git at git.haskell.org Thu Mar 19 11:34:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:28 +0000 (UTC) Subject: [commit: packages/filepath] master: Bug fix: normalize "\\" == "\\" (9cacf87) Message-ID: <20150319113428.43D203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/9cacf87d541fb8e92655228b21de926b96139bdd >--------------------------------------------------------------- commit 9cacf87d541fb8e92655228b21de926b96139bdd Author: Thomas Miedema Date: Sat Oct 25 23:38:17 2014 +0200 Bug fix: normalize "\\" == "\\" >--------------------------------------------------------------- 9cacf87d541fb8e92655228b21de926b96139bdd System/FilePath/Internal.hs | 3 ++- changelog.md | 3 +++ 2 files changed, 5 insertions(+), 1 deletion(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index f85e635..3abebe9 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -750,6 +750,7 @@ makeRelative root path -- > Windows: normalise "c:\\" == "C:\\" -- > Windows: normalise "\\\\server\\test" == "\\\\server\\test" -- > Windows: normalise "c:/file" == "C:\\file" +-- > Windows: normalise "\\" == "\\" -- > normalise "." == "." -- > Posix: normalise "./" == "./" -- > Posix: normalise "./." == "./" @@ -757,7 +758,7 @@ makeRelative root path -- > Posix: normalise "bob/fred/." == "bob/fred/" normalise :: FilePath -> FilePath normalise path = joinDrive' (normaliseDrive drv) (f pth) - ++ [pathSeparator | isDirPath pth] + ++ [pathSeparator | isDirPath pth && length pth > 1] where (drv,pth) = splitDrive path diff --git a/changelog.md b/changelog.md index 13dad0e..81d832a 100644 --- a/changelog.md +++ b/changelog.md @@ -7,6 +7,9 @@ * Bug fix: on Windows, `dropTrailingPathSeparator "/"` now returns `"/"` unchanged, instead of the normalised `"\\"`. + * Bug fix: on Windows, `normalise "\\"` now retuns `"\\"` unchanged, + instead of `"\\\\"`. + ## 1.3.0.2 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 11:34:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:30 +0000 (UTC) Subject: [commit: packages/filepath] master: Bug fix: normalise "//server/test" == "\\\\server\\test" (645d297) Message-ID: <20150319113430.4A6D83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/645d2972ec3929d1e22975879082e3afcae516c8 >--------------------------------------------------------------- commit 645d2972ec3929d1e22975879082e3afcae516c8 Author: Thomas Miedema Date: Sun Oct 26 21:19:39 2014 +0100 Bug fix: normalise "//server/test" == "\\\\server\\test" When drive represents a network share, slashes were not being normalised properly. >--------------------------------------------------------------- 645d2972ec3929d1e22975879082e3afcae516c8 System/FilePath/Internal.hs | 3 ++- changelog.md | 3 +++ 2 files changed, 5 insertions(+), 1 deletion(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 3abebe9..7256991 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -749,6 +749,7 @@ makeRelative root path -- > Windows: normalise "c:\\file/bob\\" == "C:\\file\\bob\\" -- > Windows: normalise "c:\\" == "C:\\" -- > Windows: normalise "\\\\server\\test" == "\\\\server\\test" +-- > Windows: normalise "//server/test" == "\\\\server\\test" -- > Windows: normalise "c:/file" == "C:\\file" -- > Windows: normalise "\\" == "\\" -- > normalise "." == "." @@ -783,7 +784,7 @@ normaliseDrive :: FilePath -> FilePath normaliseDrive drive | isPosix = drive normaliseDrive drive = if isJust $ readDriveLetter x2 then map toUpper x2 - else drive + else x2 where x2 = map repSlash drive diff --git a/changelog.md b/changelog.md index 81d832a..3e87a9c 100644 --- a/changelog.md +++ b/changelog.md @@ -10,6 +10,9 @@ * Bug fix: on Windows, `normalise "\\"` now retuns `"\\"` unchanged, instead of `"\\\\"`. + * Bug fix: on Windows, `normalise "//server/test"` now retuns + `"\\\\server\\test"`, instead of `"//server/test"` unchanged. + ## 1.3.0.2 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 11:34:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:32 +0000 (UTC) Subject: [commit: packages/filepath] master: Refactor normalise: simplify propSep (eca255a) Message-ID: <20150319113432.514923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/eca255a41c6e6cf427f22f468f5c051ecad3d4e3 >--------------------------------------------------------------- commit eca255a41c6e6cf427f22f468f5c051ecad3d4e3 Author: Thomas Miedema Date: Mon Sep 15 00:20:52 2014 +0200 Refactor normalise: simplify propSep Only when a path on Windows starts with a leading forward slash does propSep need to do something, all others path separators are properly taken care of by joinPath. Add 2 tests to show that splitDirectories can handle superfluous pathSeparators, and a test to show that (this new version of) propSep is indeed needed to normalise relative-to-root paths on Windows. >--------------------------------------------------------------- eca255a41c6e6cf427f22f468f5c051ecad3d4e3 System/FilePath/Internal.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 7256991..8b67fb2 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -642,6 +642,8 @@ splitPath x = [drive | drive /= ""] ++ f path -- > Windows: splitDirectories "C:\\test\\file" == ["C:\\", "test", "file"] -- > Valid x => joinPath (splitDirectories x) `equalFilePath` x -- > splitDirectories "" == [] +-- > Windows: splitDirectories "C:\\test\\\\\\file" == ["C:\\", "test", "file"] +-- > splitDirectories "/test///file" == ["/","test","file"] splitDirectories :: FilePath -> [FilePath] splitDirectories path = if hasDrive path then head pathComponents : f (tail pathComponents) @@ -751,6 +753,7 @@ makeRelative root path -- > Windows: normalise "\\\\server\\test" == "\\\\server\\test" -- > Windows: normalise "//server/test" == "\\\\server\\test" -- > Windows: normalise "c:/file" == "C:\\file" +-- > Windows: normalise "/file" == "\\file" -- > Windows: normalise "\\" == "\\" -- > normalise "." == "." -- > Posix: normalise "./" == "./" @@ -769,13 +772,10 @@ normalise path = joinDrive' (normaliseDrive drv) (f pth) isDirPath xs = hasTrailingPathSeparator xs || not (null xs) && last xs == '.' && hasTrailingPathSeparator (init xs) - f = joinPath . dropDots . splitDirectories . propSep + f = joinPath . dropDots . propSep . splitDirectories - propSep (a:b:xs) - | isPathSeparator a && isPathSeparator b = propSep (a:xs) - propSep (a:xs) - | isPathSeparator a = pathSeparator : propSep xs - propSep (x:xs) = x : propSep xs + propSep (x:xs) | all isPathSeparator x = [pathSeparator] : xs + | otherwise = x : xs propSep [] = [] dropDots = filter ("." /=) From git at git.haskell.org Thu Mar 19 11:34:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:34 +0000 (UTC) Subject: [commit: packages/filepath] master: Change the .ghci things to run the tests via Cabal - faster (9e9f9cf) Message-ID: <20150319113434.585033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/9e9f9cf58d3884a47c69071bd4143d8a412c67ac >--------------------------------------------------------------- commit 9e9f9cf58d3884a47c69071bd4143d8a412c67ac Author: Neil Mitchell Date: Sun Oct 26 20:59:50 2014 +0000 Change the .ghci things to run the tests via Cabal - faster >--------------------------------------------------------------- 9e9f9cf58d3884a47c69071bd4143d8a412c67ac .ghci | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.ghci b/.ghci index 7d3ecc9..6676709 100644 --- a/.ghci +++ b/.ghci @@ -7,4 +7,4 @@ import qualified System.FilePath.Posix as Posix :def docs_ const $ return $ unlines [":!cabal haddock"] :def docs const $ return $ unlines [":docs_",":!start dist\\doc\\html\\filepath\\System-FilePath.html"] -:def test const $ return $ unlines [":!cd tests && runhaskell GenTests.hs",":!cd tests && runhaskell -i.. FilePath_Test.hs"] +:def test const $ return $ unlines [":!cd tests && runhaskell GenTests.hs",":!cabal test"] From git at git.haskell.org Thu Mar 19 11:34:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:36 +0000 (UTC) Subject: [commit: packages/filepath] master: #24, comment out a failing test (396d8b8) Message-ID: <20150319113436.648043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/396d8b8ee6588fd08264a89472542b0e766fc2d9 >--------------------------------------------------------------- commit 396d8b8ee6588fd08264a89472542b0e766fc2d9 Author: Neil Mitchell Date: Sun Oct 26 21:00:00 2014 +0000 #24, comment out a failing test >--------------------------------------------------------------- 396d8b8ee6588fd08264a89472542b0e766fc2d9 System/FilePath/Internal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index f85e635..ac10ff3 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -640,7 +640,7 @@ splitPath x = [drive | drive /= ""] ++ f path -- > splitDirectories "test/file" == ["test","file"] -- > splitDirectories "/test/file" == ["/","test","file"] -- > Windows: splitDirectories "C:\\test\\file" == ["C:\\", "test", "file"] --- > Valid x => joinPath (splitDirectories x) `equalFilePath` x +-- > Posix: Valid x => joinPath (splitDirectories x) `equalFilePath` x -- > splitDirectories "" == [] splitDirectories :: FilePath -> [FilePath] splitDirectories path = From git at git.haskell.org Thu Mar 19 11:34:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:38 +0000 (UTC) Subject: [commit: packages/filepath] master: #22, comment out a failing test (49264b6) Message-ID: <20150319113438.6BE6E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/49264b6bd2f9ce776ec32d10114e7f53785d45a9 >--------------------------------------------------------------- commit 49264b6bd2f9ce776ec32d10114e7f53785d45a9 Author: Neil Mitchell Date: Sun Oct 26 21:00:20 2014 +0000 #22, comment out a failing test >--------------------------------------------------------------- 49264b6bd2f9ce776ec32d10114e7f53785d45a9 System/FilePath/Internal.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index ac10ff3..aa24364 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -700,7 +700,6 @@ equalFilePath a b = f a == f b -- -- > Valid y => equalFilePath x y || (isRelative x && makeRelative y x == x) || equalFilePath (y makeRelative y x) x -- > makeRelative x x == "." --- > null y || equalFilePath (makeRelative x (x y)) y || null (takeFileName x) -- > Windows: makeRelative "C:\\Home" "c:\\home\\bob" == "bob" -- > Windows: makeRelative "C:\\Home" "c:/home/bob" == "bob" -- > Windows: makeRelative "C:\\Home" "D:\\Home\\Bob" == "D:\\Home\\Bob" From git at git.haskell.org Thu Mar 19 11:34:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:40 +0000 (UTC) Subject: [commit: packages/filepath] master: #16, generalise some equalFilePath tests (11b5e32) Message-ID: <20150319113440.71C813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/11b5e329b17110eb33c3770e2727967e67cab462 >--------------------------------------------------------------- commit 11b5e329b17110eb33c3770e2727967e67cab462 Author: Neil Mitchell Date: Sun Oct 26 21:09:23 2014 +0000 #16, generalise some equalFilePath tests >--------------------------------------------------------------- 11b5e329b17110eb33c3770e2727967e67cab462 System/FilePath/Internal.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index aa24364..8167eb6 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -679,8 +679,8 @@ joinPath = foldr combine "" -- -- > x == y ==> equalFilePath x y -- > normalise x == normalise y ==> equalFilePath x y --- > Posix: equalFilePath "foo" "foo/" --- > Posix: not (equalFilePath "foo" "/foo") +-- > equalFilePath "foo" "foo/" +-- > not (equalFilePath "foo" "/foo") -- > Posix: not (equalFilePath "foo" "FOO") -- > Windows: equalFilePath "foo" "FOO" equalFilePath :: FilePath -> FilePath -> Bool From git at git.haskell.org Thu Mar 19 11:34:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:42 +0000 (UTC) Subject: [commit: packages/filepath] master: #25, comment out another test (89e779d) Message-ID: <20150319113442.784703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/89e779d28b97593338b0213659a617d69e4356e7 >--------------------------------------------------------------- commit 89e779d28b97593338b0213659a617d69e4356e7 Author: Neil Mitchell Date: Sun Oct 26 21:09:44 2014 +0000 #25, comment out another test >--------------------------------------------------------------- 89e779d28b97593338b0213659a617d69e4356e7 System/FilePath/Internal.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 8167eb6..fa7d96a 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -698,7 +698,6 @@ equalFilePath a b = f a == f b -- There is no corresponding @makeAbsolute@ function, instead use -- @System.Directory.canonicalizePath@ which has the same effect. -- --- > Valid y => equalFilePath x y || (isRelative x && makeRelative y x == x) || equalFilePath (y makeRelative y x) x -- > makeRelative x x == "." -- > Windows: makeRelative "C:\\Home" "c:\\home\\bob" == "bob" -- > Windows: makeRelative "C:\\Home" "c:/home/bob" == "bob" From git at git.haskell.org Thu Mar 19 11:34:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:44 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge pull request #16 from thomie/equalFilePath (1847583) Message-ID: <20150319113444.802793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/184758381610a54966f5a053f8a851d8097fa48f >--------------------------------------------------------------- commit 184758381610a54966f5a053f8a851d8097fa48f Merge: 49264b6 bdc0446 Author: Neil Mitchell Date: Sun Oct 26 21:10:29 2014 +0000 Merge pull request #16 from thomie/equalFilePath Bug fix: equalFilePath "C:\\" "C:" == False >--------------------------------------------------------------- 184758381610a54966f5a053f8a851d8097fa48f System/FilePath/Internal.hs | 7 ++----- changelog.md | 3 +++ 2 files changed, 5 insertions(+), 5 deletions(-) From git at git.haskell.org Thu Mar 19 11:34:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:46 +0000 (UTC) Subject: [commit: packages/filepath] master: #16, add a specific example of the Windows weirdity (598fa3d) Message-ID: <20150319113446.870E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/598fa3d3f323bb7ec6b08952223c87e7763c82fd >--------------------------------------------------------------- commit 598fa3d3f323bb7ec6b08952223c87e7763c82fd Author: Neil Mitchell Date: Sun Oct 26 21:11:57 2014 +0000 #16, add a specific example of the Windows weirdity >--------------------------------------------------------------- 598fa3d3f323bb7ec6b08952223c87e7763c82fd System/FilePath/Internal.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index fa7d96a..9c9606c 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -683,6 +683,7 @@ joinPath = foldr combine "" -- > not (equalFilePath "foo" "/foo") -- > Posix: not (equalFilePath "foo" "FOO") -- > Windows: equalFilePath "foo" "FOO" +-- > Windows: not (equalFilePath "C:" "C:/") equalFilePath :: FilePath -> FilePath -> Bool equalFilePath a b = f a == f b where From git at git.haskell.org Thu Mar 19 11:34:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:48 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge branch 'master' of https://github.com/haskell/filepath (ffcd007) Message-ID: <20150319113448.8F60F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/ffcd00736046445bd95f673e4e7a3a0ce65fe4d2 >--------------------------------------------------------------- commit ffcd00736046445bd95f673e4e7a3a0ce65fe4d2 Merge: 598fa3d 1847583 Author: Neil Mitchell Date: Sun Oct 26 21:12:20 2014 +0000 Merge branch 'master' of https://github.com/haskell/filepath >--------------------------------------------------------------- ffcd00736046445bd95f673e4e7a3a0ce65fe4d2 System/FilePath/Internal.hs | 7 ++----- changelog.md | 3 +++ 2 files changed, 5 insertions(+), 5 deletions(-) From git at git.haskell.org Thu Mar 19 11:34:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:50 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge branch 'isValid' of https://github.com/thomie/filepath into thomie-isValid (6ddfe0c) Message-ID: <20150319113450.959A23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/6ddfe0c2e73430342db97c0f73bb2fcb5a46b2db >--------------------------------------------------------------- commit 6ddfe0c2e73430342db97c0f73bb2fcb5a46b2db Merge: ffcd007 bef533f Author: Neil Mitchell Date: Sun Oct 26 21:18:34 2014 +0000 Merge branch 'isValid' of https://github.com/thomie/filepath into thomie-isValid Conflicts: changelog.md >--------------------------------------------------------------- 6ddfe0c2e73430342db97c0f73bb2fcb5a46b2db System/FilePath/Internal.hs | 9 +++++++-- changelog.md | 3 +++ 2 files changed, 10 insertions(+), 2 deletions(-) diff --cc changelog.md index b62ac45,1637673..dc2f4c8 --- a/changelog.md +++ b/changelog.md @@@ -7,9 -7,9 +7,12 @@@ * Bug fix: on Windows, `dropTrailingPathSeparator "/"` now returns `"/"` unchanged, instead of the normalised `"\\"`. + * Bug fix: on Windows, `equalFilePath "C:\\" "C:"` now retuns `False`, + instead of `True`. + + * Bug fix: on Windows, `isValid "\\\\\\foo"` now returns `False`, instead + of `True`. + ## 1.3.0.2 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 11:34:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:52 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge branch 'thomie-isValid' (6f0ca6e) Message-ID: <20150319113452.9C0FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/6f0ca6eadcdade21028cfac9c5395d728981d09a >--------------------------------------------------------------- commit 6f0ca6eadcdade21028cfac9c5395d728981d09a Merge: ffcd007 6ddfe0c Author: Neil Mitchell Date: Sun Oct 26 21:18:44 2014 +0000 Merge branch 'thomie-isValid' >--------------------------------------------------------------- 6f0ca6eadcdade21028cfac9c5395d728981d09a System/FilePath/Internal.hs | 9 +++++++-- changelog.md | 3 +++ 2 files changed, 10 insertions(+), 2 deletions(-) From git at git.haskell.org Thu Mar 19 11:34:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:54 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge pull request #17 from thomie/fix-isDrive-empty (ab0fc3a) Message-ID: <20150319113454.A58F73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/ab0fc3a4a6c529766fce960cf935c74d894efcaf >--------------------------------------------------------------- commit ab0fc3a4a6c529766fce960cf935c74d894efcaf Merge: 6f0ca6e f9ae34b Author: Neil Mitchell Date: Sun Oct 26 21:21:40 2014 +0000 Merge pull request #17 from thomie/fix-isDrive-empty Bug fix: isDrive "" == False >--------------------------------------------------------------- ab0fc3a4a6c529766fce960cf935c74d894efcaf System/FilePath/Internal.hs | 3 ++- changelog.md | 2 ++ 2 files changed, 4 insertions(+), 1 deletion(-) From git at git.haskell.org Thu Mar 19 11:34:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:56 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge pull request #19 from thomie/splitDirectories (cdeba89) Message-ID: <20150319113456.AC9503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/cdeba8910025e568a9003273e463daade5bb422d >--------------------------------------------------------------- commit cdeba8910025e568a9003273e463daade5bb422d Merge: ab0fc3a ba8bae5 Author: Neil Mitchell Date: Sun Oct 26 21:24:14 2014 +0000 Merge pull request #19 from thomie/splitDirectories Refactor splitDirectories >--------------------------------------------------------------- cdeba8910025e568a9003273e463daade5bb422d System/FilePath/Internal.hs | 10 +--------- 1 file changed, 1 insertion(+), 9 deletions(-) diff --cc System/FilePath/Internal.hs index 8fc9314,c684070..832192d --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@@ -641,18 -640,10 +641,10 @@@ splitPath x = [drive | drive /= ""] ++ -- > splitDirectories "test/file" == ["test","file"] -- > splitDirectories "/test/file" == ["/","test","file"] -- > Windows: splitDirectories "C:\\test\\file" == ["C:\\", "test", "file"] --- > Valid x => joinPath (splitDirectories x) `equalFilePath` x +-- > Posix: Valid x => joinPath (splitDirectories x) `equalFilePath` x -- > splitDirectories "" == [] splitDirectories :: FilePath -> [FilePath] - splitDirectories path = - if hasDrive path then head pathComponents : f (tail pathComponents) - else f pathComponents - where - pathComponents = splitPath path - - f = map g - g x = if null res then x else res - where res = takeWhile (not . isPathSeparator) x + splitDirectories = map dropTrailingPathSeparator . splitPath -- | Join path elements back together. From git at git.haskell.org Thu Mar 19 11:34:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:58 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge pull request #20 from thomie/takeDirectory (e183b40) Message-ID: <20150319113458.B3E903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/e183b4083f953ee0010a1d0494a2fecccf357c6c >--------------------------------------------------------------- commit e183b4083f953ee0010a1d0494a2fecccf357c6c Merge: cdeba89 c8521d6 Author: Neil Mitchell Date: Sun Oct 26 21:29:18 2014 +0000 Merge pull request #20 from thomie/takeDirectory Refactor takeDirectory >--------------------------------------------------------------- e183b4083f953ee0010a1d0494a2fecccf357c6c System/FilePath/Internal.hs | 7 +------ 1 file changed, 1 insertion(+), 6 deletions(-) From git at git.haskell.org Thu Mar 19 11:34:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:34:58 +0000 (UTC) Subject: [commit: packages/deepseq] branch 'typeable-with-kinds' created Message-ID: <20150319113458.D8FDA3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq New branch : typeable-with-kinds Referencing: c0794e1e84229bf61816c26f8f90b43488cd57c6 From git at git.haskell.org Thu Mar 19 11:35:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:00 +0000 (UTC) Subject: [commit: packages/filepath] master: #24, turn back on the splitDirectories test (72543cc) Message-ID: <20150319113500.BA9483A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/72543cc23359c78dee147d48c56e953e0a2eb794 >--------------------------------------------------------------- commit 72543cc23359c78dee147d48c56e953e0a2eb794 Author: Neil Mitchell Date: Sun Oct 26 21:36:43 2014 +0000 #24, turn back on the splitDirectories test >--------------------------------------------------------------- 72543cc23359c78dee147d48c56e953e0a2eb794 System/FilePath/Internal.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 997af79..1c0e012 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -636,8 +636,8 @@ splitPath x = [drive | drive /= ""] ++ f path -- > splitDirectories "test/file" == ["test","file"] -- > splitDirectories "/test/file" == ["/","test","file"] -- > Windows: splitDirectories "C:\\test\\file" == ["C:\\", "test", "file"] --- > Posix: Valid x => joinPath (splitDirectories x) `equalFilePath` x --- > splitDirectories "" == [] +-- > Valid x => joinPath (splitDirectories x) `equalFilePath` x +-- > splitDirectories "" == [] splitDirectories :: FilePath -> [FilePath] splitDirectories = map dropTrailingPathSeparator . splitPath From git at git.haskell.org Thu Mar 19 11:35:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:00 +0000 (UTC) Subject: [commit: packages/deepseq] tag 'v1.4.1.0' created Message-ID: <20150319113500.D9A603A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq New tag : v1.4.1.0 Referencing: f5470d88699a72f3116d6e488d8294283795c19e From git at git.haskell.org Thu Mar 19 11:35:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:02 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge branch 'normalise' of https://github.com/thomie/filepath into thomie-normalise (c30d722) Message-ID: <20150319113502.C1D2D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/c30d7224b3a648f2bdb0d0e19140f1a273f7cb06 >--------------------------------------------------------------- commit c30d7224b3a648f2bdb0d0e19140f1a273f7cb06 Merge: 72543cc eca255a Author: Neil Mitchell Date: Sun Oct 26 21:41:11 2014 +0000 Merge branch 'normalise' of https://github.com/thomie/filepath into thomie-normalise Conflicts: System/FilePath/Internal.hs changelog.md >--------------------------------------------------------------- c30d7224b3a648f2bdb0d0e19140f1a273f7cb06 System/FilePath/Internal.hs | 18 ++++++++++-------- changelog.md | 6 ++++++ 2 files changed, 16 insertions(+), 8 deletions(-) diff --cc System/FilePath/Internal.hs index 1c0e012,8b67fb2..7dec998 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@@ -636,10 -640,20 +636,12 @@@ splitPath x = [drive | drive /= ""] ++ -- > splitDirectories "test/file" == ["test","file"] -- > splitDirectories "/test/file" == ["/","test","file"] -- > Windows: splitDirectories "C:\\test\\file" == ["C:\\", "test", "file"] --- > Valid x => joinPath (splitDirectories x) `equalFilePath` x --- > splitDirectories "" == [] +-- > Valid x => joinPath (splitDirectories x) `equalFilePath` x +-- > splitDirectories "" == [] + -- > Windows: splitDirectories "C:\\test\\\\\\file" == ["C:\\", "test", "file"] + -- > splitDirectories "/test///file" == ["/","test","file"] splitDirectories :: FilePath -> [FilePath] -splitDirectories path = - if hasDrive path then head pathComponents : f (tail pathComponents) - else f pathComponents - where - pathComponents = splitPath path - - f = map g - g x = if null res then x else res - where res = takeWhile (not . isPathSeparator) x +splitDirectories = map dropTrailingPathSeparator . splitPath -- | Join path elements back together. diff --cc changelog.md index 7297e2f,3e87a9c..b037c48 --- a/changelog.md +++ b/changelog.md @@@ -9,12 -7,12 +9,18 @@@ * Bug fix: on Windows, `dropTrailingPathSeparator "/"` now returns `"/"` unchanged, instead of the normalised `"\\"`. + * Bug fix: on Windows, `equalFilePath "C:\\" "C:"` now retuns `False`, + instead of `True`. + + * Bug fix: on Windows, `isValid "\\\\\\foo"` now returns `False`, instead + of `True`. + + * Bug fix: on Windows, `normalise "\\"` now retuns `"\\"` unchanged, + instead of `"\\\\"`. + + * Bug fix: on Windows, `normalise "//server/test"` now retuns + `"\\\\server\\test"`, instead of `"//server/test"` unchanged. + ## 1.3.0.2 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 11:35:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:02 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Fixup changelog extension in deepseq.cabal (62b7256) Message-ID: <20150319113502.E18D73A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/62b72563738f7661f41ad64b04bd55c62123b546 >--------------------------------------------------------------- commit 62b72563738f7661f41ad64b04bd55c62123b546 Author: Herbert Valerio Riedel Date: Thu Oct 16 08:43:22 2014 +0200 Fixup changelog extension in deepseq.cabal This was broken in 3815fe819ba46 >--------------------------------------------------------------- 62b72563738f7661f41ad64b04bd55c62123b546 deepseq.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/deepseq.cabal b/deepseq.cabal index e043ca1..53ff7e2 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -28,7 +28,7 @@ build-type: Simple cabal-version: >=1.10 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.2.1, GHC==7.0.4, GHC==7.0.3, GHC==7.0.2, GHC==7.0.1 -extra-source-files: changelog +extra-source-files: changelog.md source-repository head type: git From git at git.haskell.org Thu Mar 19 11:35:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:04 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Update build-icon in README.md (4150273) Message-ID: <20150319113504.E77EC3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/4150273e8994cc302fb64a045b08bc52d4af5742 >--------------------------------------------------------------- commit 4150273e8994cc302fb64a045b08bc52d4af5742 Author: Herbert Valerio Riedel Date: Thu Oct 16 09:09:18 2014 +0200 Update build-icon in README.md As `deepseq` now hosted on GitHub, it now has its own Travis job to allow validating PRs >--------------------------------------------------------------- 4150273e8994cc302fb64a045b08bc52d4af5742 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 3ff11b8..f2859d3 100644 --- a/README.md +++ b/README.md @@ -1,4 +1,4 @@ -The `deepseq` Package [![Build Status](https://travis-ci.org/ghc/packages-deepseq.png?branch=master)](https://travis-ci.org/ghc/packages-deepseq) +The `deepseq` Package [![Hackage](https://img.shields.io/hackage/v/deepseq.svg)](https://hackage.haskell.org/package/deepseq) [![Build Status](https://travis-ci.org/haskell/deepseq.svg)](https://travis-ci.org/haskell/deepseq) ===================== See [`deepseq` on Hackage](http://hackage.haskell.org/package/deepseq) for more information. From git at git.haskell.org Thu Mar 19 11:35:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:04 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge branch 'thomie-normalise' (2989311) Message-ID: <20150319113504.C8C733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/2989311e49d27d281ba7d7e519eff12d26adfe24 >--------------------------------------------------------------- commit 2989311e49d27d281ba7d7e519eff12d26adfe24 Merge: 72543cc c30d722 Author: Neil Mitchell Date: Sun Oct 26 21:41:24 2014 +0000 Merge branch 'thomie-normalise' >--------------------------------------------------------------- 2989311e49d27d281ba7d7e519eff12d26adfe24 System/FilePath/Internal.hs | 18 ++++++++++-------- changelog.md | 6 ++++++ 2 files changed, 16 insertions(+), 8 deletions(-) From git at git.haskell.org Thu Mar 19 11:35:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:06 +0000 (UTC) Subject: [commit: packages/filepath] master: Allow multiple "Valid =>" clauses in QuickCheck properties (611b6c5) Message-ID: <20150319113506.CF4DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/611b6c57e69c428ad7e2049584d57a93949704c0 >--------------------------------------------------------------- commit 611b6c57e69c428ad7e2049584d57a93949704c0 Author: Thomas Miedema Date: Sun Oct 26 22:12:28 2014 +0100 Allow multiple "Valid =>" clauses in QuickCheck properties >--------------------------------------------------------------- 611b6c57e69c428ad7e2049584d57a93949704c0 tests/GenTests.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/GenTests.hs b/tests/GenTests.hs index 7915c16..722ffc0 100644 --- a/tests/GenTests.hs +++ b/tests/GenTests.hs @@ -68,7 +68,7 @@ splitLex x = case lex x of -- Valid a => z ===> (\a -> z) (makeValid a) makeValid :: [String] -> [String] -makeValid ("Valid":a:"=>":z) = "(\\":a:"->":z ++ ")":"(":"makeValid":a:")":[] +makeValid ("Valid":a:"=>":z) = "(\\":a:"->":makeValid z ++ ")":"(":"makeValid":a:")":[] makeValid x = x From git at git.haskell.org Thu Mar 19 11:35:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:06 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Update Travis Job (36bc4fa) Message-ID: <20150319113506.ECC083A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/36bc4fa3dad851750150cc5b932eaeaae91f5636 >--------------------------------------------------------------- commit 36bc4fa3dad851750150cc5b932eaeaae91f5636 Author: Herbert Valerio Riedel Date: Thu Oct 16 09:30:05 2014 +0200 Update Travis Job >--------------------------------------------------------------- 36bc4fa3dad851750150cc5b932eaeaae91f5636 .travis.yml | 53 +++++++++++++++++++++++++++++------------------------ 1 file changed, 29 insertions(+), 24 deletions(-) diff --git a/.travis.yml b/.travis.yml index f649faa..c5deba1 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,39 +1,44 @@ env: - - GHCVER=7.0.1 - - GHCVER=7.0.2 - - GHCVER=7.0.3 - - GHCVER=7.0.4 - - GHCVER=7.2.1 - - GHCVER=7.2.2 - - GHCVER=7.4.1 - - GHCVER=7.4.2 - - GHCVER=7.6.1 - - GHCVER=7.6.2 - - GHCVER=7.6.3 - - GHCVER=head + - GHCVER=7.0.1 CABALVER=1.16 + - GHCVER=7.0.2 CABALVER=1.16 + - GHCVER=7.0.3 CABALVER=1.16 + - GHCVER=7.0.4 CABALVER=1.16 + - GHCVER=7.2.1 CABALVER=1.16 + - GHCVER=7.2.2 CABALVER=1.16 + - GHCVER=7.4.1 CABALVER=1.16 + - GHCVER=7.4.2 CABALVER=1.16 + - GHCVER=7.6.1 CABALVER=1.16 + - GHCVER=7.6.2 CABALVER=1.16 + - GHCVER=7.6.3 CABALVER=1.16 + - GHCVER=7.8.1 CABALVER=1.18 + - GHCVER=7.8.2 CABALVER=1.18 + - GHCVER=7.8.3 CABALVER=1.18 + - GHCVER=head CABALVER=1.20 matrix: allow_failures: - - env: GHCVER=head + - env: GHCVER=head CABALVER=1.20 before_install: - - sudo add-apt-repository -y ppa:hvr/ghc - - sudo apt-get update - - sudo apt-get install cabal-install-1.18 ghc-$GHCVER - - export PATH=/opt/ghc/$GHCVER/bin:$PATH + - travis_retry sudo add-apt-repository -y ppa:hvr/ghc + - travis_retry sudo apt-get update + - travis_retry sudo apt-get install cabal-install-$CABALVER ghc-$GHCVER + - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH install: - - cabal-1.18 update + - cabal update + - ghc --version script: - - cabal-1.18 configure -v2 - - cabal-1.18 build - - cabal-1.18 check - - cabal-1.18 sdist - - export SRC_TGZ=$(cabal-1.18 info . | awk '{print $2 ".tar.gz";exit}') ; + - cabal configure -v2 + - cabal build -v2 + - cabal check + - cabal sdist +# The following scriptlet checks that the resulting source distribution can be built & installed + - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; cd dist/; if [ -f "$SRC_TGZ" ]; then - cabal-1.18 install "$SRC_TGZ"; + cabal install "$SRC_TGZ"; else echo "expected '$SRC_TGZ' not found"; exit 1; From git at git.haskell.org Thu Mar 19 11:35:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:08 +0000 (UTC) Subject: [commit: packages/filepath] master: Refactor: use hasTrailingPathSeparator in joinDrive and combineAlways (facd0db) Message-ID: <20150319113508.D65A23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/facd0dbfc465ab2f727eb1add7d9803ba462b56f >--------------------------------------------------------------- commit facd0dbfc465ab2f727eb1add7d9803ba462b56f Author: Thomas Miedema Date: Fri Oct 24 21:11:09 2014 +0200 Refactor: use hasTrailingPathSeparator in joinDrive and combineAlways >--------------------------------------------------------------- facd0dbfc465ab2f727eb1add7d9803ba462b56f System/FilePath/Internal.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 7dec998..e48d01b 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -386,7 +386,7 @@ joinDrive :: FilePath -> FilePath -> FilePath joinDrive a b | isPosix = a ++ b | null a = b | null b = a - | isPathSeparator (last a) = a ++ b + | hasTrailingPathSeparator a = a ++ b | otherwise = case a of [a1,':'] | isLetter a1 -> a ++ b _ -> a ++ [pathSeparator] ++ b @@ -602,7 +602,7 @@ combine a b | hasLeadingPathSeparator b || hasDrive b = b combineAlways :: FilePath -> FilePath -> FilePath combineAlways a b | null a = b | null b = a - | isPathSeparator (last a) = a ++ b + | hasTrailingPathSeparator a = a ++ b | isDrive a = joinDrive a b | otherwise = a ++ [pathSeparator] ++ b From git at git.haskell.org Thu Mar 19 11:35:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:08 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Update Cabal meta-data to reflect new upstream (3e2e996) Message-ID: <20150319113508.F3E873A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/3e2e996fe2f935aaa4e68de8fb43264e9ff3e956 >--------------------------------------------------------------- commit 3e2e996fe2f935aaa4e68de8fb43264e9ff3e956 Author: Herbert Valerio Riedel Date: Thu Oct 16 09:43:05 2014 +0200 Update Cabal meta-data to reflect new upstream [skip ci] >--------------------------------------------------------------- 3e2e996fe2f935aaa4e68de8fb43264e9ff3e956 deepseq.cabal | 8 ++------ 1 file changed, 2 insertions(+), 6 deletions(-) diff --git a/deepseq.cabal b/deepseq.cabal index 53ff7e2..856c3fb 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -4,6 +4,7 @@ version: 1.3.0.3 license: BSD3 license-file: LICENSE maintainer: libraries at haskell.org +bug-reports: https://github.com/haskell/deepseq/issues synopsis: Deep evaluation of data structures category: Control description: @@ -32,12 +33,7 @@ extra-source-files: changelog.md source-repository head type: git - location: http://git.haskell.org/packages/deepseq.git - -source-repository this - type: git - location: http://git.haskell.org/packages/deepseq.git - tag: deepseq-1.3.0.2-release + location: https://github.com/haskell/deepseq.git library default-language: Haskell2010 From git at git.haskell.org Thu Mar 19 11:35:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:10 +0000 (UTC) Subject: [commit: packages/filepath] master: Insert slash when first argument to joinDrive does not end with one (c986cde) Message-ID: <20150319113510.DCD1F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/c986cde979992074dabda71088474630f459cd13 >--------------------------------------------------------------- commit c986cde979992074dabda71088474630f459cd13 Author: Thomas Miedema Date: Thu Oct 23 18:23:56 2014 +0200 Insert slash when first argument to joinDrive does not end with one Before: joinDrive "/foo" "bar" == "/foobar" After: joinDrive "/foo" "bar" == "/foo/bar" The first argument to `joinDrive` should arguably always be a drive. On Posix this means it should be, and thus end with, a single slash. It is currently undocumented what should happen when it doesn't end with a slash (throw an exception?). Since it is unlikely anyone is relying on the original behavior, this change is hopefully ok to make. The reason for this change is to make `joinDrive` similar in semantics to `combineAlways`. >--------------------------------------------------------------- c986cde979992074dabda71088474630f459cd13 System/FilePath/Internal.hs | 5 ++--- changelog.md | 3 +++ 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index e48d01b..1e2cdc9 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -383,12 +383,11 @@ readDriveShareName name = addSlash a b -- > Windows: joinDrive "\\\\share" "foo" == "\\\\share\\foo" -- > Windows: joinDrive "/:" "foo" == "/:\\foo" joinDrive :: FilePath -> FilePath -> FilePath -joinDrive a b | isPosix = a ++ b - | null a = b +joinDrive a b | null a = b | null b = a | hasTrailingPathSeparator a = a ++ b | otherwise = case a of - [a1,':'] | isLetter a1 -> a ++ b + [a1,':'] | isWindows && isLetter a1 -> a ++ b _ -> a ++ [pathSeparator] ++ b -- | Get the drive from a filepath. diff --git a/changelog.md b/changelog.md index b037c48..f79c011 100644 --- a/changelog.md +++ b/changelog.md @@ -4,6 +4,9 @@ * Bundled with GHC 7.10.1 + * Semantic change: `joinDrive "/foo" "bar"` now returns `"/foo/bar"`, + instead of `"/foobar"`. + * Bug fix: `isDrive ""` now retuns `False`, instead of `True`. * Bug fix: on Windows, `dropTrailingPathSeparator "/"` now returns `"/"` From git at git.haskell.org Thu Mar 19 11:35:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:11 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Fix indentation in changelog file (ef54941) Message-ID: <20150319113511.054C83A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/ef5494120895be8fcc2c09ad88c8a9de403cecb8 >--------------------------------------------------------------- commit ef5494120895be8fcc2c09ad88c8a9de403cecb8 Author: Herbert Valerio Riedel Date: Fri Nov 7 11:26:03 2014 +0100 Fix indentation in changelog file >--------------------------------------------------------------- ef5494120895be8fcc2c09ad88c8a9de403cecb8 changelog.md | 34 +++++++++++++++++----------------- 1 file changed, 17 insertions(+), 17 deletions(-) diff --git a/changelog.md b/changelog.md index 10ef7cc..e978a31 100644 --- a/changelog.md +++ b/changelog.md @@ -6,44 +6,44 @@ ## 1.3.0.2 *Nov 2013* - * Bundled with GHC 7.8.1 - * Update package description to Cabal 1.10 format - * Add support for GHC 7.8 - * Drop support for GHCs older than GHC 7.0.1 - * Add `/since: .../` annotations to Haddock comments - * Add changelog + * Bundled with GHC 7.8.1 + * Update package description to Cabal 1.10 format + * Add support for GHC 7.8 + * Drop support for GHCs older than GHC 7.0.1 + * Add `/since: .../` annotations to Haddock comments + * Add changelog ## 1.3.0.1 *Sep 2012* - * No changes + * No changes ## 1.3.0.0 *Feb 2012* - * Add instances for `Fixed`, `a->b` and `Version` + * Add instances for `Fixed`, `a->b` and `Version` ## 1.2.0.1 *Sep 2011* - * Disable SafeHaskell for GHC 7.2 + * Disable SafeHaskell for GHC 7.2 ## 1.2.0.0 *Sep 2011* - * New function `force` - * New operator `$!!` - * Add SafeHaskell support - * Dropped dependency on containers + * New function `force` + * New operator `$!!` + * Add SafeHaskell support + * Dropped dependency on containers ## 1.1.0.2 *Nov 2010* - * Improve Haddock documentation + * Improve Haddock documentation ## 1.1.0.1 *Oct 2010* - * Enable support for containers-0.4.x + * Enable support for containers-0.4.x ## 1.1.0.0 *Nov 2009* - * Major rewrite + * Major rewrite ## 1.0.0.0 *Nov 2009* - * Initial release + * Initial release From git at git.haskell.org Thu Mar 19 11:35:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:12 +0000 (UTC) Subject: [commit: packages/filepath] master: joinDrive=combineAlways (e0a3634) Message-ID: <20150319113512.E37473A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/e0a363478b840fc1788dcbc9dce0f939dc2e30b3 >--------------------------------------------------------------- commit e0a363478b840fc1788dcbc9dce0f939dc2e30b3 Author: Thomas Miedema Date: Thu Oct 23 19:14:24 2014 +0200 joinDrive=combineAlways >--------------------------------------------------------------- e0a363478b840fc1788dcbc9dce0f939dc2e30b3 System/FilePath/Internal.hs | 7 +------ 1 file changed, 1 insertion(+), 6 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 417feec..80817cc 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -383,12 +383,7 @@ readDriveShareName name = addSlash a b -- > Windows: joinDrive "\\\\share" "foo" == "\\\\share\\foo" -- > Windows: joinDrive "/:" "foo" == "/:\\foo" joinDrive :: FilePath -> FilePath -> FilePath -joinDrive a b | null a = b - | null b = a - | hasTrailingPathSeparator a = a ++ b - | otherwise = case a of - [a1,':'] | isWindows && isLetter a1 -> a ++ b - _ -> a ++ [pathSeparator] ++ b +joinDrive = combineAlways -- | Get the drive from a filepath. -- From git at git.haskell.org Thu Mar 19 11:35:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:13 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Update Travis CI job (aea3237) Message-ID: <20150319113513.0B5573A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/aea3237cb62fc469328d5fa9d7ec146fefd8f79c >--------------------------------------------------------------- commit aea3237cb62fc469328d5fa9d7ec146fefd8f79c Author: Herbert Valerio Riedel Date: Fri Nov 7 11:23:22 2014 +0100 Update Travis CI job >--------------------------------------------------------------- aea3237cb62fc469328d5fa9d7ec146fefd8f79c .travis.yml | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/.travis.yml b/.travis.yml index c5deba1..aad0071 100644 --- a/.travis.yml +++ b/.travis.yml @@ -13,11 +13,11 @@ env: - GHCVER=7.8.1 CABALVER=1.18 - GHCVER=7.8.2 CABALVER=1.18 - GHCVER=7.8.3 CABALVER=1.18 - - GHCVER=head CABALVER=1.20 + - GHCVER=head CABALVER=head matrix: allow_failures: - - env: GHCVER=head CABALVER=1.20 + - env: GHCVER=head CABALVER=head before_install: - travis_retry sudo add-apt-repository -y ppa:hvr/ghc @@ -32,7 +32,7 @@ install: script: - cabal configure -v2 - cabal build -v2 - - cabal check + - if [ "$CABALVER" != "1.16" ]; then cabal check; fi - cabal sdist # The following scriptlet checks that the resulting source distribution can be built & installed - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; From git at git.haskell.org Thu Mar 19 11:35:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:14 +0000 (UTC) Subject: [commit: packages/filepath] master: Inline call to joinDrive in combineAlways (aaa3efb) Message-ID: <20150319113514.EAB243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/aaa3efbc1a8d75e3659dd4580ec5e7581c62f997 >--------------------------------------------------------------- commit aaa3efbc1a8d75e3659dd4580ec5e7581c62f997 Author: Thomas Miedema Date: Thu Oct 23 19:05:53 2014 +0200 Inline call to joinDrive in combineAlways The first 3 guards of both functions are the same, so copy-paste only the last guard of joinDrive into combineAlways. >--------------------------------------------------------------- aaa3efbc1a8d75e3659dd4580ec5e7581c62f997 System/FilePath/Internal.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 1e2cdc9..8e54138 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -602,7 +602,9 @@ combineAlways :: FilePath -> FilePath -> FilePath combineAlways a b | null a = b | null b = a | hasTrailingPathSeparator a = a ++ b - | isDrive a = joinDrive a b + | isDrive a = case a of + [a1,':'] | isWindows && isLetter a1 -> a ++ b + _ -> a ++ [pathSeparator] ++ b | otherwise = a ++ [pathSeparator] ++ b From git at git.haskell.org Thu Mar 19 11:35:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:15 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Merge `deepseq-generics` into `deepseq` (3b5c957) Message-ID: <20150319113515.11F193A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/3b5c957ce7bba7b63b4483a43c6762c3f5d8ee28 >--------------------------------------------------------------- commit 3b5c957ce7bba7b63b4483a43c6762c3f5d8ee28 Author: Herbert Valerio Riedel Date: Thu Oct 16 11:19:16 2014 +0200 Merge `deepseq-generics` into `deepseq` This also replaces the existing `rnf x = seq x ()` default implementation with a `Generics`-based `DefaultSignature` `rnf` method implementation This requires to drop support for GHCs older than GHC 7.2 to avoid conditional exports due to lack of `Generics` support For more details, see original proposal http://permalink.gmane.org/gmane.comp.lang.haskell.libraries/23031 >--------------------------------------------------------------- 3b5c957ce7bba7b63b4483a43c6762c3f5d8ee28 Control/DeepSeq.hs | 118 +++++++++++++++++++++++++++++++++++++++++------------ changelog.md | 15 ++++++- deepseq.cabal | 24 ++++++++--- 3 files changed, 124 insertions(+), 33 deletions(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 88aa5c3..f451b1b 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -1,6 +1,12 @@ +{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} -#if __GLASGOW_HASKELL__ >= 702 && MIN_VERSION_array(0,4,0) +#if __GLASGOW_HASKELL__ >= 702 +{-# LANGUAGE DefaultSignatures #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE TypeOperators #-} +# if MIN_VERSION_array(0,4,0) {-# LANGUAGE Safe #-} +# endif #endif ----------------------------------------------------------------------------- -- | @@ -59,6 +65,37 @@ import Data.Array import Data.Fixed import Data.Version +#if __GLASGOW_HASKELL__ >= 702 +import GHC.Generics + +-- | Hidden internal type-class +class GNFData f where + grnf :: f a -> () + +instance GNFData V1 where + grnf = error "Control.DeepSeq.rnf: uninhabited type" + +instance GNFData U1 where + grnf U1 = () + +instance NFData a => GNFData (K1 i a) where + grnf = rnf . unK1 + {-# INLINEABLE grnf #-} + +instance GNFData a => GNFData (M1 i c a) where + grnf = grnf . unM1 + {-# INLINEABLE grnf #-} + +instance (GNFData a, GNFData b) => GNFData (a :*: b) where + grnf (x :*: y) = grnf x `seq` grnf y + {-# INLINEABLE grnf #-} + +instance (GNFData a, GNFData b) => GNFData (a :+: b) where + grnf (L1 x) = grnf x + grnf (R1 x) = grnf x + {-# INLINEABLE grnf #-} +#endif + infixr 0 $!! -- | 'deepseq': fully evaluates the first argument, before returning the @@ -108,46 +145,77 @@ force x = x `deepseq` x -- -- /Since: 1.1.0.0/ class NFData a where - -- | rnf should reduce its argument to normal form (that is, fully + -- | 'rnf' should reduce its argument to normal form (that is, fully -- evaluate all sub-components), and then return '()'. -- - -- The default implementation of 'rnf' is + -- Starting with GHC 7.2, you can automatically derive instances + -- for types possessing a 'Generic' instance. + -- + -- > {-# LANGUAGE DeriveGeneric #-} + -- > + -- > import GHC.Generics (Generic) + -- > import Control.DeepSeq + -- > + -- > data Foo a = Foo a String + -- > deriving (Eq, Generic) + -- > + -- > instance NFData a => NFData (Foo a) + -- > + -- > data Colour = Red | Green | Blue + -- > deriving Generic + -- > + -- > instance NFData Colour + -- + -- __Compatibility Note__: Prior to version 1.4.0, the default + -- implementation of 'rnf' was \"@'rnf' a = 'seq' a ()@\", + -- however, starting with @deepseq-1.4.0.0@, the default + -- implementation is based on @DefaultSignatures@ allowing for + -- more accurate auto-derived 'NFData' instances. If you need the + -- previously used exact default 'rnf' method implementation + -- semantics, use + -- + -- > instance NFData Colour where rnf x = seq x () -- - -- > rnf a = a `seq` () + -- or alternatively + -- + -- > {-# LANGUAGE BangPatterns #-} + -- > instance NFData Colour where rnf !_ = () -- - -- which may be convenient when defining instances for data types with - -- no unevaluated fields (e.g. enumerations). rnf :: a -> () - rnf a = a `seq` () -instance NFData Int -instance NFData Word -instance NFData Integer -instance NFData Float -instance NFData Double +#if __GLASGOW_HASKELL__ >= 702 + default rnf :: (Generic a, GNFData (Rep a)) => a -> () + rnf = grnf . from +#endif + +instance NFData Int where rnf !_ = () +instance NFData Word where rnf !_ = () +instance NFData Integer where rnf !_ = () +instance NFData Float where rnf !_ = () +instance NFData Double where rnf !_ = () -instance NFData Char -instance NFData Bool -instance NFData () +instance NFData Char where rnf !_ = () +instance NFData Bool where rnf !_ = () +instance NFData () where rnf !_ = () -instance NFData Int8 -instance NFData Int16 -instance NFData Int32 -instance NFData Int64 +instance NFData Int8 where rnf !_ = () +instance NFData Int16 where rnf !_ = () +instance NFData Int32 where rnf !_ = () +instance NFData Int64 where rnf !_ = () -instance NFData Word8 -instance NFData Word16 -instance NFData Word32 -instance NFData Word64 +instance NFData Word8 where rnf !_ = () +instance NFData Word16 where rnf !_ = () +instance NFData Word32 where rnf !_ = () +instance NFData Word64 where rnf !_ = () -- |/Since: 1.3.0.0/ -instance NFData (Fixed a) +instance NFData (Fixed a) where rnf !_ = () -- |This instance is for convenience and consistency with 'seq'. -- This assumes that WHNF is equivalent to NF for functions. -- -- /Since: 1.3.0.0/ -instance NFData (a -> b) +instance NFData (a -> b) where rnf !_ = () --Rational and complex numbers. diff --git a/changelog.md b/changelog.md index e978a31..9d1b80d 100644 --- a/changelog.md +++ b/changelog.md @@ -1,8 +1,19 @@ # Changelog for [`deepseq` package](http://hackage.haskell.org/package/deepseq) -## 1.3.0.3 *TBA* +## 1.4.0.0 *TBA* - * Bundled with GHC 7.10 + * Bundled with GHC 7.10.1 + * Switch to Generics based `DefaultSignature` `rnf` method + implementation (based on code from `deepseq-generics`) + + **Compatibility Note**: if you need the exact default-method + semantics of `deepseq` prior to 1.4, replace occurences of + + instance NFData XYZ + + by + + instance NFData XYZ where rnf x = seq x () ## 1.3.0.2 *Nov 2013* diff --git a/deepseq.cabal b/deepseq.cabal index 856c3fb..261b01d 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -1,5 +1,5 @@ name: deepseq -version: 1.3.0.3 +version: 1.4.0.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE @@ -27,7 +27,7 @@ description: which builds on top of this package. build-type: Simple cabal-version: >=1.10 -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.2.1, GHC==7.0.4, GHC==7.0.3, GHC==7.0.2, GHC==7.0.1 +tested-with: GHC==7.8.3, GHC==7.8.2, GHC==7.8.1, 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.2.1, GHC==7.0.4, GHC==7.0.3, GHC==7.0.2, GHC==7.0.1 extra-source-files: changelog.md @@ -37,10 +37,22 @@ source-repository head library default-language: Haskell2010 - other-extensions: CPP - if impl(ghc >= 7.2) - other-extensions: Safe - exposed-modules: Control.DeepSeq + other-extensions: + BangPatterns + CPP + + if impl(ghc>=7.2) + -- Enable Generics-backed DefaultSignatures for `rnf` + other-extensions: + DefaultSignatures + FlexibleContexts + Safe + TypeOperators + + build-depends: ghc-prim >= 0.2 && < 0.4 + build-depends: base >= 4.3 && < 4.9, array >= 0.3 && < 0.6 ghc-options: -Wall + + exposed-modules: Control.DeepSeq From git at git.haskell.org Thu Mar 19 11:35:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:17 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Merge pull request #1 from hvr/pr-generics (75ce576) Message-ID: <20150319113517.18E7B3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/75ce5767488774065025df34cbc80de6f03c4fd1 >--------------------------------------------------------------- commit 75ce5767488774065025df34cbc80de6f03c4fd1 Merge: 3e2e996 3b5c957 Author: Herbert Valerio Riedel Date: Fri Nov 14 13:52:46 2014 +0100 Merge pull request #1 from hvr/pr-generics Add `Generics`-backed `DefaultSignature` `rnf`-method >--------------------------------------------------------------- 75ce5767488774065025df34cbc80de6f03c4fd1 .travis.yml | 6 +-- Control/DeepSeq.hs | 118 +++++++++++++++++++++++++++++++++++++++++------------ changelog.md | 49 +++++++++++++--------- deepseq.cabal | 24 ++++++++--- 4 files changed, 144 insertions(+), 53 deletions(-) From git at git.haskell.org Thu Mar 19 11:35:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:16 +0000 (UTC) Subject: [commit: packages/filepath] master: Remove unnecessary isDrive check in combineAlways (fd2f07f) Message-ID: <20150319113516.F1E123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/fd2f07ffeb8480c2e0cae7ca7481a050a1060e93 >--------------------------------------------------------------- commit fd2f07ffeb8480c2e0cae7ca7481a050a1060e93 Author: Thomas Miedema Date: Thu Oct 23 19:09:26 2014 +0200 Remove unnecessary isDrive check in combineAlways `isWindows && isLetter a1` implies `isDrive [a1, ':']` >--------------------------------------------------------------- fd2f07ffeb8480c2e0cae7ca7481a050a1060e93 System/FilePath/Internal.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 8e54138..417feec 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -602,10 +602,9 @@ combineAlways :: FilePath -> FilePath -> FilePath combineAlways a b | null a = b | null b = a | hasTrailingPathSeparator a = a ++ b - | isDrive a = case a of + | otherwise = case a of [a1,':'] | isWindows && isLetter a1 -> a ++ b _ -> a ++ [pathSeparator] ++ b - | otherwise = a ++ [pathSeparator] ++ b -- | A nice alias for 'combine'. From git at git.haskell.org Thu Mar 19 11:35:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:19 +0000 (UTC) Subject: [commit: packages/filepath] master: Reenable and fix QuickCheck property for makeRelative (#25) (1903af3) Message-ID: <20150319113519.079263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/1903af3aeb575234418f70b33c8dc749a6f5360f >--------------------------------------------------------------- commit 1903af3aeb575234418f70b33c8dc749a6f5360f Author: Thomas Miedema Date: Sun Oct 26 22:13:08 2014 +0100 Reenable and fix QuickCheck property for makeRelative (#25) Both x and y should be valid. >--------------------------------------------------------------- 1903af3aeb575234418f70b33c8dc749a6f5360f System/FilePath/Internal.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 7dec998..0a8726f 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -686,6 +686,7 @@ equalFilePath a b = f a == f b -- There is no corresponding @makeAbsolute@ function, instead use -- @System.Directory.canonicalizePath@ which has the same effect. -- +-- > Valid y => Valid x => equalFilePath x y || (isRelative x && makeRelative y x == x) || equalFilePath (y makeRelative y x) x -- > makeRelative x x == "." -- > Windows: makeRelative "C:\\Home" "c:\\home\\bob" == "bob" -- > Windows: makeRelative "C:\\Home" "c:/home/bob" == "bob" From git at git.haskell.org Thu Mar 19 11:35:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:19 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Add `NFData` instance for new `Natural` type (#2) (eca9e86) Message-ID: <20150319113519.214F23A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/eca9e861402060a3b83cb569e360fd291e89308d >--------------------------------------------------------------- commit eca9e861402060a3b83cb569e360fd291e89308d Author: Herbert Valerio Riedel Date: Sun Nov 23 16:25:32 2014 +0100 Add `NFData` instance for new `Natural` type (#2) >--------------------------------------------------------------- eca9e861402060a3b83cb569e360fd291e89308d Control/DeepSeq.hs | 8 ++++++++ changelog.md | 3 +++ 2 files changed, 11 insertions(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index f451b1b..c6bd510 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -64,6 +64,9 @@ import Data.Complex import Data.Array import Data.Fixed import Data.Version +#if MIN_VERSION_base(4,8,0) +import Numeric.Natural ( Natural ) +#endif #if __GLASGOW_HASKELL__ >= 702 import GHC.Generics @@ -208,6 +211,11 @@ instance NFData Word16 where rnf !_ = () instance NFData Word32 where rnf !_ = () instance NFData Word64 where rnf !_ = () +#if MIN_VERSION_base(4,8,0) +-- |/Since: 1.4.0.0/ +instance NFData Natural where rnf !_ = () +#endif + -- |/Since: 1.3.0.0/ instance NFData (Fixed a) where rnf !_ = () diff --git a/changelog.md b/changelog.md index 9d1b80d..dd0170e 100644 --- a/changelog.md +++ b/changelog.md @@ -15,6 +15,9 @@ instance NFData XYZ where rnf x = seq x () + * New `NFData` instances for `base` types: + - `Numeric.Natural.Natural` + ## 1.3.0.2 *Nov 2013* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 11:35:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:21 +0000 (UTC) Subject: [commit: packages/filepath] master: Bug fix: on Windows, makeRelative "/" "//" == "//" (03dfb79) Message-ID: <20150319113521.0E6CB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/03dfb79c75436f27730a0edc1f45a98f75320137 >--------------------------------------------------------------- commit 03dfb79c75436f27730a0edc1f45a98f75320137 Author: Thomas Miedema Date: Sun Oct 26 22:16:00 2014 +0100 Bug fix: on Windows, makeRelative "/" "//" == "//" >--------------------------------------------------------------- 03dfb79c75436f27730a0edc1f45a98f75320137 System/FilePath/Internal.hs | 5 +++-- changelog.md | 3 +++ 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 0a8726f..739aa60 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -693,6 +693,7 @@ equalFilePath a b = f a == f b -- > Windows: makeRelative "C:\\Home" "D:\\Home\\Bob" == "D:\\Home\\Bob" -- > Windows: makeRelative "C:\\Home" "C:Home\\Bob" == "C:Home\\Bob" -- > Windows: makeRelative "/Home" "/home/bob" == "bob" +-- > Windows: makeRelative "/" "//" == "//" -- > Posix: makeRelative "/Home" "/home/bob" == "/home/bob" -- > Posix: makeRelative "/home/" "/home/bob/foo/bar" == "bob/foo/bar" -- > Posix: makeRelative "/fred" "bob" == "bob" @@ -714,10 +715,10 @@ makeRelative root path where (a,b) = break isPathSeparator $ dropWhile isPathSeparator x -- on windows, need to drop '/' which is kind of absolute, but not a drive - dropAbs (x:xs) | isPathSeparator x = xs + dropAbs x | hasLeadingPathSeparator x && not (hasDrive x) = tail x dropAbs x = dropDrive x - takeAbs (x:_) | isPathSeparator x = [pathSeparator] + takeAbs x | hasLeadingPathSeparator x && not (hasDrive x) = [pathSeparator] takeAbs x = map (\y -> if isPathSeparator y then pathSeparator else toLower y) $ takeDrive x -- | Normalise a file diff --git a/changelog.md b/changelog.md index b037c48..77405bf 100644 --- a/changelog.md +++ b/changelog.md @@ -21,6 +21,9 @@ * Bug fix: on Windows, `normalise "//server/test"` now retuns `"\\\\server\\test"`, instead of `"//server/test"` unchanged. + * Bug fix: on Windows, `makeRelative "/" "//"` now returns `"//"`, instead + of `""`. + ## 1.3.0.2 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 11:35:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:21 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Add `NFData` instance for `Proxy` (3158132) Message-ID: <20150319113521.270E73A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/3158132b3e958f847e65851ab831c7ff7bf43165 >--------------------------------------------------------------- commit 3158132b3e958f847e65851ab831c7ff7bf43165 Author: Herbert Valerio Riedel Date: Sun Nov 23 16:57:52 2014 +0100 Add `NFData` instance for `Proxy` >--------------------------------------------------------------- 3158132b3e958f847e65851ab831c7ff7bf43165 Control/DeepSeq.hs | 10 ++++++++++ changelog.md | 1 + 2 files changed, 11 insertions(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index c6bd510..c374a6c 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -64,6 +64,11 @@ import Data.Complex import Data.Array import Data.Fixed import Data.Version + +#if MIN_VERSION_base(4,7,0) +import Data.Proxy ( Proxy(Proxy) ) +#endif + #if MIN_VERSION_base(4,8,0) import Numeric.Natural ( Natural ) #endif @@ -211,6 +216,11 @@ instance NFData Word16 where rnf !_ = () instance NFData Word32 where rnf !_ = () instance NFData Word64 where rnf !_ = () +#if MIN_VERSION_base(4,7,0) +-- |/Since: 1.4.0.0/ +instance NFData (Proxy a) where rnf Proxy = () +#endif + #if MIN_VERSION_base(4,8,0) -- |/Since: 1.4.0.0/ instance NFData Natural where rnf !_ = () diff --git a/changelog.md b/changelog.md index dd0170e..891cd89 100644 --- a/changelog.md +++ b/changelog.md @@ -17,6 +17,7 @@ * New `NFData` instances for `base` types: - `Numeric.Natural.Natural` + - `Data.Proxy.Proxy` ## 1.3.0.2 *Nov 2013* From git at git.haskell.org Thu Mar 19 11:35:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:23 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge pull request #21 from thomie/joinDrive-combineAlways (a528760) Message-ID: <20150319113523.147D63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/a528760b2a4991399d0c11954bc9c8319bbe73ec >--------------------------------------------------------------- commit a528760b2a4991399d0c11954bc9c8319bbe73ec Merge: 2989311 e0a3634 Author: Neil Mitchell Date: Mon Oct 27 13:21:53 2014 +0000 Merge pull request #21 from thomie/joinDrive-combineAlways Refactor: joinDrive and combineAlways >--------------------------------------------------------------- a528760b2a4991399d0c11954bc9c8319bbe73ec System/FilePath/Internal.hs | 15 +++++---------- changelog.md | 3 +++ 2 files changed, 8 insertions(+), 10 deletions(-) From git at git.haskell.org Thu Mar 19 11:35:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:23 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Update `.gitignore` and tweak Travis CI Job (140f611) Message-ID: <20150319113523.2C64B3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/140f611ab3ecfd53f526cc293c243650285049b0 >--------------------------------------------------------------- commit 140f611ab3ecfd53f526cc293c243650285049b0 Author: Herbert Valerio Riedel Date: Sun Nov 23 17:00:01 2014 +0100 Update `.gitignore` and tweak Travis CI Job `--force-reinstalls` to avoid failures for GHC HEAD >--------------------------------------------------------------- 140f611ab3ecfd53f526cc293c243650285049b0 .gitignore | 3 ++- .travis.yml | 2 +- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/.gitignore b/.gitignore index 8f4d267..89cf73d 100644 --- a/.gitignore +++ b/.gitignore @@ -1,3 +1,4 @@ GNUmakefile -dist-install +/dist-install/ +/dist/ ghc.mk diff --git a/.travis.yml b/.travis.yml index aad0071..5028b91 100644 --- a/.travis.yml +++ b/.travis.yml @@ -38,7 +38,7 @@ script: - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; cd dist/; if [ -f "$SRC_TGZ" ]; then - cabal install "$SRC_TGZ"; + cabal install --force-reinstalls "$SRC_TGZ"; else echo "expected '$SRC_TGZ' not found"; exit 1; From git at git.haskell.org Thu Mar 19 11:35:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:25 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge pull request #26 from thomie/makeRelative (342601f) Message-ID: <20150319113525.1BCBF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/342601f56f48643aa1f904dd1ed0d16d4580e23b >--------------------------------------------------------------- commit 342601f56f48643aa1f904dd1ed0d16d4580e23b Merge: a528760 03dfb79 Author: Neil Mitchell Date: Mon Oct 27 14:40:11 2014 +0000 Merge pull request #26 from thomie/makeRelative Reenable test #25 and bug fix for makeRelative >--------------------------------------------------------------- 342601f56f48643aa1f904dd1ed0d16d4580e23b System/FilePath/Internal.hs | 6 ++++-- changelog.md | 3 +++ tests/GenTests.hs | 2 +- 3 files changed, 8 insertions(+), 3 deletions(-) From git at git.haskell.org Thu Mar 19 11:35:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:25 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Add `NFData` instance for `Identity` functor (#2) (9e95a3b) Message-ID: <20150319113525.3204F3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/9e95a3b18fa8ff12c6704070b52ac2eae9642c67 >--------------------------------------------------------------- commit 9e95a3b18fa8ff12c6704070b52ac2eae9642c67 Author: Herbert Valerio Riedel Date: Sun Nov 23 17:03:56 2014 +0100 Add `NFData` instance for `Identity` functor (#2) >--------------------------------------------------------------- 9e95a3b18fa8ff12c6704070b52ac2eae9642c67 Control/DeepSeq.hs | 5 +++++ changelog.md | 4 +++- 2 files changed, 8 insertions(+), 1 deletion(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index c374a6c..aebc5ba 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -70,6 +70,7 @@ import Data.Proxy ( Proxy(Proxy) ) #endif #if MIN_VERSION_base(4,8,0) +import Data.Functor.Identity ( Identity(..) ) import Numeric.Natural ( Natural ) #endif @@ -223,6 +224,10 @@ instance NFData (Proxy a) where rnf Proxy = () #if MIN_VERSION_base(4,8,0) -- |/Since: 1.4.0.0/ +instance NFData a => NFData (Identity a) where + rnf = rnf . runIdentity + +-- |/Since: 1.4.0.0/ instance NFData Natural where rnf !_ = () #endif diff --git a/changelog.md b/changelog.md index 891cd89..73490e3 100644 --- a/changelog.md +++ b/changelog.md @@ -16,8 +16,10 @@ instance NFData XYZ where rnf x = seq x () * New `NFData` instances for `base` types: - - `Numeric.Natural.Natural` + + - `Data.Functor.Identity.Identity` - `Data.Proxy.Proxy` + - `Numeric.Natural.Natural` ## 1.3.0.2 *Nov 2013* From git at git.haskell.org Thu Mar 19 11:35:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:27 +0000 (UTC) Subject: [commit: packages/filepath] master: Bug fix: normalise "/./" == "/" on Posix, "\\" on Windows (f7869ab) Message-ID: <20150319113527.2271C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/f7869ab03c0759c6035c2bbb025eb5df4ab8e92f >--------------------------------------------------------------- commit f7869ab03c0759c6035c2bbb025eb5df4ab8e92f Author: Thomas Miedema Date: Mon Oct 27 16:04:48 2014 +0100 Bug fix: normalise "/./" == "/" on Posix, "\\" on Windows >--------------------------------------------------------------- f7869ab03c0759c6035c2bbb025eb5df4ab8e92f System/FilePath/Internal.hs | 9 +++++++-- changelog.md | 3 +++ 2 files changed, 10 insertions(+), 2 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index b748b52..5014c48 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -736,20 +736,25 @@ makeRelative root path -- > Windows: normalise "c:/file" == "C:\\file" -- > Windows: normalise "/file" == "\\file" -- > Windows: normalise "\\" == "\\" +-- > Windows: normalise "/./" == "\\" -- > normalise "." == "." -- > Posix: normalise "./" == "./" -- > Posix: normalise "./." == "./" +-- > Posix: normalise "/./" == "/" -- > Posix: normalise "/" == "/" -- > Posix: normalise "bob/fred/." == "bob/fred/" normalise :: FilePath -> FilePath -normalise path = joinDrive' (normaliseDrive drv) (f pth) - ++ [pathSeparator | isDirPath pth && length pth > 1] +normalise path = result ++ [pathSeparator | addPathSeparator] where (drv,pth) = splitDrive path + result = joinDrive' (normaliseDrive drv) (f pth) joinDrive' "" "" = "." joinDrive' d p = joinDrive d p + addPathSeparator = isDirPath pth + && not (hasTrailingPathSeparator result) + isDirPath xs = hasTrailingPathSeparator xs || not (null xs) && last xs == '.' && hasTrailingPathSeparator (init xs) diff --git a/changelog.md b/changelog.md index 9303b4b..5fda80a 100644 --- a/changelog.md +++ b/changelog.md @@ -7,6 +7,9 @@ * Semantic change: `joinDrive "/foo" "bar"` now returns `"/foo/bar"`, instead of `"/foobar"`. + * Bug fix, `normalise "/./"` now returns "/" on Posix and "\\" on Windows, + instead of "//" and "\\\\". + * Bug fix: `isDrive ""` now retuns `False`, instead of `True`. * Bug fix: on Windows, `dropTrailingPathSeparator "/"` now returns `"/"` From git at git.haskell.org Thu Mar 19 11:35:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:27 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Add `NFData` instances for `Monoid` wrappers (693fe5a) Message-ID: <20150319113527.38D513A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/693fe5a36f5c21b9f1e032f39731e252e41b0e05 >--------------------------------------------------------------- commit 693fe5a36f5c21b9f1e032f39731e252e41b0e05 Author: Herbert Valerio Riedel Date: Sun Nov 23 17:07:46 2014 +0100 Add `NFData` instances for `Monoid` wrappers Specifically for `Data.Monoid.{Dual,First,Last,Any,All,Sum,Product}` >--------------------------------------------------------------- 693fe5a36f5c21b9f1e032f39731e252e41b0e05 Control/DeepSeq.hs | 27 +++++++++++++++++++++++++++ changelog.md | 1 + 2 files changed, 28 insertions(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index aebc5ba..6b4906f 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -64,6 +64,7 @@ import Data.Complex import Data.Array import Data.Fixed import Data.Version +import Data.Monoid #if MIN_VERSION_base(4,7,0) import Data.Proxy ( Proxy(Proxy) ) @@ -269,6 +270,32 @@ instance NFData a => NFData [a] where instance (Ix a, NFData a, NFData b) => NFData (Array a b) where rnf x = rnf (bounds x, Data.Array.elems x) +-- |/Since: 1.4.0.0/ +instance NFData a => NFData (Dual a) where + rnf = rnf . getDual + +-- |/Since: 1.4.0.0/ +instance NFData a => NFData (First a) where + rnf = rnf . getFirst + +-- |/Since: 1.4.0.0/ +instance NFData a => NFData (Last a) where + rnf = rnf . getLast + +-- |/Since: 1.4.0.0/ +instance NFData Any where rnf = rnf . getAny + +-- |/Since: 1.4.0.0/ +instance NFData All where rnf = rnf . getAll + +-- |/Since: 1.4.0.0/ +instance NFData a => NFData (Sum a) where + rnf = rnf . getSum + +-- |/Since: 1.4.0.0/ +instance NFData a => NFData (Product a) where + rnf = rnf . getProduct + instance (NFData a, NFData b) => NFData (a,b) where rnf (x,y) = rnf x `seq` rnf y diff --git a/changelog.md b/changelog.md index 73490e3..1e6c805 100644 --- a/changelog.md +++ b/changelog.md @@ -20,6 +20,7 @@ - `Data.Functor.Identity.Identity` - `Data.Proxy.Proxy` - `Numeric.Natural.Natural` + - `Data.Monoid.{Dual,First,Last,Any,All,Sum,Product}` ## 1.3.0.2 *Nov 2013* From git at git.haskell.org Thu Mar 19 11:35:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:29 +0000 (UTC) Subject: [commit: packages/filepath] master: Bug fix: normalise "//home" == "/home" (Posix) (ee25534) Message-ID: <20150319113529.2A0AF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/ee255344c1b071558dba1cced136c8229e6a452a >--------------------------------------------------------------- commit ee255344c1b071558dba1cced136c8229e6a452a Author: Thomas Miedema Date: Mon Oct 27 18:53:33 2014 +0100 Bug fix: normalise "//home" == "/home" (Posix) >--------------------------------------------------------------- ee255344c1b071558dba1cced136c8229e6a452a System/FilePath/Internal.hs | 4 +++- changelog.md | 3 +++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 5014c48..709751c 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -743,6 +743,7 @@ makeRelative root path -- > Posix: normalise "/./" == "/" -- > Posix: normalise "/" == "/" -- > Posix: normalise "bob/fred/." == "bob/fred/" +-- > Posix: normalise "//home" == "/home" normalise :: FilePath -> FilePath normalise path = result ++ [pathSeparator | addPathSeparator] where @@ -767,7 +768,8 @@ normalise path = result ++ [pathSeparator | addPathSeparator] dropDots = filter ("." /=) normaliseDrive :: FilePath -> FilePath -normaliseDrive drive | isPosix = drive +normaliseDrive "" = "" +normaliseDrive _ | isPosix = [pathSeparator] normaliseDrive drive = if isJust $ readDriveLetter x2 then map toUpper x2 else x2 diff --git a/changelog.md b/changelog.md index 5fda80a..6e5f2df 100644 --- a/changelog.md +++ b/changelog.md @@ -7,6 +7,9 @@ * Semantic change: `joinDrive "/foo" "bar"` now returns `"/foo/bar"`, instead of `"/foobar"`. + * Bug fix, on Posix systems, `normalise "//home"` now returns `"/home"`, + instead of `"//home"`. + * Bug fix, `normalise "/./"` now returns "/" on Posix and "\\" on Windows, instead of "//" and "\\\\". From git at git.haskell.org Thu Mar 19 11:35:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:29 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Add `NFData` instance for `Const` & `ZipList` (6188247) Message-ID: <20150319113529.3E7E03A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/61882473cc857e489ec52277204084199a982f76 >--------------------------------------------------------------- commit 61882473cc857e489ec52277204084199a982f76 Author: Herbert Valerio Riedel Date: Sun Nov 23 17:25:39 2014 +0100 Add `NFData` instance for `Const` & `ZipList` >--------------------------------------------------------------- 61882473cc857e489ec52277204084199a982f76 Control/DeepSeq.hs | 9 +++++++++ changelog.md | 4 +++- 2 files changed, 12 insertions(+), 1 deletion(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 6b4906f..c6fc69d 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -57,6 +57,7 @@ module Control.DeepSeq ( NFData(..), ) where +import Control.Applicative import Data.Int import Data.Word import Data.Ratio @@ -267,6 +268,14 @@ instance NFData a => NFData [a] where rnf [] = () rnf (x:xs) = rnf x `seq` rnf xs +-- |/Since: 1.4.0.0/ +instance NFData a => NFData (ZipList a) where + rnf = rnf . getZipList + +-- |/Since: 1.4.0.0/ +instance NFData a => NFData (Const a b) where + rnf = rnf . getConst + instance (Ix a, NFData a, NFData b) => NFData (Array a b) where rnf x = rnf (bounds x, Data.Array.elems x) diff --git a/changelog.md b/changelog.md index 1e6c805..be83f71 100644 --- a/changelog.md +++ b/changelog.md @@ -17,10 +17,12 @@ * New `NFData` instances for `base` types: + - `Control.Applicative.Const` + - `Control.Applicative.ZipList` - `Data.Functor.Identity.Identity` + - `Data.Monoid.{Dual,First,Last,Any,All,Sum,Product}` - `Data.Proxy.Proxy` - `Numeric.Natural.Natural` - - `Data.Monoid.{Dual,First,Last,Any,All,Sum,Product}` ## 1.3.0.2 *Nov 2013* From git at git.haskell.org Thu Mar 19 11:35:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:31 +0000 (UTC) Subject: [commit: packages/filepath] master: Bug fix: normalise "C:.\\" == "C:" (00e784d) Message-ID: <20150319113531.30A273A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/00e784d32cbe28405a73c3cc404a1ac45c045a08 >--------------------------------------------------------------- commit 00e784d32cbe28405a73c3cc404a1ac45c045a08 Author: Thomas Miedema Date: Mon Oct 27 19:47:44 2014 +0100 Bug fix: normalise "C:.\\" == "C:" Another other option would be `normalise "C:.\\" == "C:.\\"`, but this is nicer since we already have: > normalise "C:.\\foo" "C:foo" >--------------------------------------------------------------- 00e784d32cbe28405a73c3cc404a1ac45c045a08 System/FilePath/Internal.hs | 7 +++++-- changelog.md | 3 +++ 2 files changed, 8 insertions(+), 2 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 709751c..c3f2721 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -731,6 +731,7 @@ makeRelative root path -- > Posix: normalise "./bob/fred/" == "bob/fred/" -- > Windows: normalise "c:\\file/bob\\" == "C:\\file\\bob\\" -- > Windows: normalise "c:\\" == "C:\\" +-- > Windows: normalise "C:.\\" == "C:" -- > Windows: normalise "\\\\server\\test" == "\\\\server\\test" -- > Windows: normalise "//server/test" == "\\\\server\\test" -- > Windows: normalise "c:/file" == "C:\\file" @@ -755,6 +756,7 @@ normalise path = result ++ [pathSeparator | addPathSeparator] addPathSeparator = isDirPath pth && not (hasTrailingPathSeparator result) + && not (isRelativeDrive drv) isDirPath xs = hasTrailingPathSeparator xs || not (null xs) && last xs == '.' && hasTrailingPathSeparator (init xs) @@ -868,7 +870,8 @@ makeValid path = joinDrive drv $ validElements $ validChars pth -- -- * "You cannot use the "\\?\" prefix with a relative path." isRelative :: FilePath -> Bool -isRelative = isRelativeDrive . takeDrive +isRelative x = null drive || isRelativeDrive drive + where drive = takeDrive x {- c:foo -} @@ -876,7 +879,7 @@ isRelative = isRelativeDrive . takeDrive -- backslash after the colon, it is interpreted as a relative path to the -- current directory on the drive with the specified letter." isRelativeDrive :: String -> Bool -isRelativeDrive x = null x || +isRelativeDrive x = maybe False (not . hasTrailingPathSeparator . fst) (readDriveLetter x) diff --git a/changelog.md b/changelog.md index 6e5f2df..f46153f 100644 --- a/changelog.md +++ b/changelog.md @@ -27,6 +27,9 @@ * Bug fix: on Windows, `normalise "\\"` now retuns `"\\"` unchanged, instead of `"\\\\"`. + * Bug fix: on Windows, `normalise "C:.\\"` now retuns `"C:"`, instead of + `"C:\\"`. + * Bug fix: on Windows, `normalise "//server/test"` now retuns `"\\\\server\\test"`, instead of `"//server/test"` unchanged. From git at git.haskell.org Thu Mar 19 11:35:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:31 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Extend `rnf` documentation to mention GHC 7.10's `DeriveAnyClass` extension (7618263) Message-ID: <20150319113531.42FE03A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/7618263f57988c81117d3d1703409bf592b15398 >--------------------------------------------------------------- commit 7618263f57988c81117d3d1703409bf592b15398 Author: Herbert Valerio Riedel Date: Sun Nov 23 17:39:39 2014 +0100 Extend `rnf` documentation to mention GHC 7.10's `DeriveAnyClass` extension >--------------------------------------------------------------- 7618263f57988c81117d3d1703409bf592b15398 Control/DeepSeq.hs | 28 +++++++++++++++++++++++++--- 1 file changed, 25 insertions(+), 3 deletions(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index c6fc69d..7ab8257 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -159,6 +159,8 @@ class NFData a where -- | 'rnf' should reduce its argument to normal form (that is, fully -- evaluate all sub-components), and then return '()'. -- + -- === 'Generic' 'NFData' deriving + -- -- Starting with GHC 7.2, you can automatically derive instances -- for types possessing a 'Generic' instance. -- @@ -177,9 +179,29 @@ class NFData a where -- > -- > instance NFData Colour -- - -- __Compatibility Note__: Prior to version 1.4.0, the default - -- implementation of 'rnf' was \"@'rnf' a = 'seq' a ()@\", - -- however, starting with @deepseq-1.4.0.0@, the default + -- Starting with GHC 7.10, the example above can be written more + -- concisely by enabling the new @DeriveAnyClass@ extension: + -- + -- > {-# LANGUAGE DeriveGeneric, DeriveAnyClass #-} + -- > + -- > import GHC.Generics (Generic) + -- > import Control.DeepSeq + -- > + -- > data Foo a = Foo a String + -- > deriving (Eq, Generic, NFData) + -- > + -- > data Colour = Red | Green | Blue + -- > deriving (Generic, NFData) + -- > + -- + -- === Compatibility with previous @deepseq@ versions + -- + -- Prior to version 1.4.0, the default implementation of the 'rnf' + -- method was defined as + -- + -- @'rnf' a = 'seq' a ()@ + -- + -- However, starting with @deepseq-1.4.0.0@, the default -- implementation is based on @DefaultSignatures@ allowing for -- more accurate auto-derived 'NFData' instances. If you need the -- previously used exact default 'rnf' method implementation From git at git.haskell.org Thu Mar 19 11:35:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:33 +0000 (UTC) Subject: [commit: packages/filepath] master: Revert "Make splitFileName quickcheck test Posix only" (#14) (0ea8ed5) Message-ID: <20150319113533.3782B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/0ea8ed51e9e30f4324e58f02eff18db092ad08f1 >--------------------------------------------------------------- commit 0ea8ed51e9e30f4324e58f02eff18db092ad08f1 Author: Thomas Miedema Date: Mon Oct 27 14:32:26 2014 +0100 Revert "Make splitFileName quickcheck test Posix only" (#14) This reverts commit 0dd40adf8d4a8a3f409f3a877dba2ae7e98a5c5b. >--------------------------------------------------------------- 0ea8ed51e9e30f4324e58f02eff18db092ad08f1 System/FilePath/Internal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index c3f2721..323f8e3 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -426,7 +426,7 @@ isDrive x = not (null x) && null (dropDrive x) -- | Split a filename into directory and file. 'combine' is the inverse. -- -- > Valid x => uncurry () (splitFileName x) == x || fst (splitFileName x) == "./" --- > Posix: Valid x => isValid (fst (splitFileName x)) +-- > Valid x => isValid (fst (splitFileName x)) -- > splitFileName "file/bob.txt" == ("file/", "bob.txt") -- > splitFileName "file/" == ("file/", "") -- > splitFileName "bob" == ("./", "bob") From git at git.haskell.org Thu Mar 19 11:35:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:33 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: instance NFData GHC.Fingerprint.Type.Fingerprint (af4abf7) Message-ID: <20150319113533.48BC23A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/af4abf7891be87d5b378edb280c3496928f4d53f >--------------------------------------------------------------- commit af4abf7891be87d5b378edb280c3496928f4d53f Author: Herbert Valerio Riedel Date: Tue Nov 25 11:56:52 2014 +0100 instance NFData GHC.Fingerprint.Type.Fingerprint >--------------------------------------------------------------- af4abf7891be87d5b378edb280c3496928f4d53f Control/DeepSeq.hs | 13 +++++++++++++ 1 file changed, 13 insertions(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 7ab8257..0472277 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -77,6 +77,7 @@ import Numeric.Natural ( Natural ) #endif #if __GLASGOW_HASKELL__ >= 702 +import GHC.Fingerprint.Type ( Fingerprint(..) ) import GHC.Generics -- | Hidden internal type-class @@ -327,6 +328,18 @@ instance NFData a => NFData (Sum a) where instance NFData a => NFData (Product a) where rnf = rnf . getProduct +---------------------------------------------------------------------------- +-- GHC Specifics + +#if __GLASGOW_HASKELL__ >= 702 +-- |/Since: 1.4.0.0/ +instance NFData Fingerprint where + rnf (Fingerprint _ _) = () +#endif + +---------------------------------------------------------------------------- +-- Tuples + instance (NFData a, NFData b) => NFData (a,b) where rnf (x,y) = rnf x `seq` rnf y From git at git.haskell.org Thu Mar 19 11:35:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:35 +0000 (UTC) Subject: [commit: packages/filepath] master: Change min QuickCheck version back to 2.6 (#28) (2e6b73f) Message-ID: <20150319113535.3E6B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/2e6b73f717b008739e1cd6b24a66104daf7d13d8 >--------------------------------------------------------------- commit 2e6b73f717b008739e1cd6b24a66104daf7d13d8 Author: Thomas Miedema Date: Mon Oct 27 21:47:05 2014 +0100 Change min QuickCheck version back to 2.6 (#28) >--------------------------------------------------------------- 2e6b73f717b008739e1cd6b24a66104daf7d13d8 filepath.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/filepath.cabal b/filepath.cabal index 2c72d54..f34bc40 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -59,7 +59,7 @@ test-suite filepath-tests build-depends: filepath, base, - QuickCheck > 2.6 && < 2.8, + QuickCheck >= 2.6 && < 2.8, random == 1.0.* source-repository head From git at git.haskell.org Thu Mar 19 11:35:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:35 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: `NFData` instances for `TyCon` and `TypeRep` (50b5f3f) Message-ID: <20150319113535.4FD2F3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/50b5f3fba01a8ef3b1f86e6a82817238d03c76d4 >--------------------------------------------------------------- commit 50b5f3fba01a8ef3b1f86e6a82817238d03c76d4 Author: Herbert Valerio Riedel Date: Tue Nov 25 12:00:38 2014 +0100 `NFData` instances for `TyCon` and `TypeRep` >--------------------------------------------------------------- 50b5f3fba01a8ef3b1f86e6a82817238d03c76d4 Control/DeepSeq.hs | 16 ++++++++++++++++ changelog.md | 3 +++ 2 files changed, 19 insertions(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 0472277..aaef007 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -73,6 +73,8 @@ import Data.Proxy ( Proxy(Proxy) ) #if MIN_VERSION_base(4,8,0) import Data.Functor.Identity ( Identity(..) ) +-- NB: Data.Typeable.Internal is "Trustworthy" only starting w/ base-4.8 +import Data.Typeable.Internal ( TypeRep(..), TyCon(..) ) import Numeric.Natural ( Natural ) #endif @@ -328,6 +330,20 @@ instance NFData a => NFData (Sum a) where instance NFData a => NFData (Product a) where rnf = rnf . getProduct +#if MIN_VERSION_base(4,8,0) +-- | __NOTE__: Only defined for @base-4.8.0.0@ and later +-- +-- /Since: 1.4.0.0/ +instance NFData TypeRep where + rnf (TypeRep _ tycon tyrep) = rnf tycon `seq` rnf tyrep + +-- | __NOTE__: Only defined for @base-4.8.0.0@ and later +-- +-- /Since: 1.4.0.0/ +instance NFData TyCon where + rnf (TyCon _ tcp tcm tcn) = rnf tcp `seq` rnf tcm `seq` rnf tcn +#endif + ---------------------------------------------------------------------------- -- GHC Specifics diff --git a/changelog.md b/changelog.md index be83f71..8b14bd9 100644 --- a/changelog.md +++ b/changelog.md @@ -22,6 +22,9 @@ - `Data.Functor.Identity.Identity` - `Data.Monoid.{Dual,First,Last,Any,All,Sum,Product}` - `Data.Proxy.Proxy` + - `Data.Typeable.Internal.TyCon` + - `Data.Typeable.Internal.TypeRep` + - `GHC.Fingerprint.Type.Fingerprint` - `Numeric.Natural.Natural` ## 1.3.0.2 *Nov 2013* From git at git.haskell.org Thu Mar 19 11:35:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:37 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge pull request #29 from thomie/bugFixes (c9c1d58) Message-ID: <20150319113537.4661A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/c9c1d5801fa9db68b4336b594d1b30d6f12c5d45 >--------------------------------------------------------------- commit c9c1d5801fa9db68b4336b594d1b30d6f12c5d45 Merge: 342601f 2e6b73f Author: Neil Mitchell Date: Mon Oct 27 21:09:33 2014 +0000 Merge pull request #29 from thomie/bugFixes Bug fixes for normalise #12 >--------------------------------------------------------------- c9c1d5801fa9db68b4336b594d1b30d6f12c5d45 System/FilePath/Internal.hs | 22 ++++++++++++++++------ changelog.md | 9 +++++++++ filepath.cabal | 2 +- 3 files changed, 26 insertions(+), 7 deletions(-) From git at git.haskell.org Thu Mar 19 11:35:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:37 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: `NFData` instance for `StableName` (676ea70) Message-ID: <20150319113537.545A13A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/676ea7031e91d730da79ad6b9a7fd9c5c101f85a >--------------------------------------------------------------- commit 676ea7031e91d730da79ad6b9a7fd9c5c101f85a Author: Herbert Valerio Riedel Date: Tue Nov 25 12:10:26 2014 +0100 `NFData` instance for `StableName` >--------------------------------------------------------------- 676ea7031e91d730da79ad6b9a7fd9c5c101f85a Control/DeepSeq.hs | 6 ++++++ changelog.md | 1 + 2 files changed, 7 insertions(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index aaef007..aad5c9c 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -67,6 +67,8 @@ import Data.Fixed import Data.Version import Data.Monoid +import System.Mem.StableName ( StableName ) + #if MIN_VERSION_base(4,7,0) import Data.Proxy ( Proxy(Proxy) ) #endif @@ -330,6 +332,10 @@ instance NFData a => NFData (Sum a) where instance NFData a => NFData (Product a) where rnf = rnf . getProduct +-- |/Since: 1.4.0.0/ +instance NFData (StableName a) where + rnf !_ = () + #if MIN_VERSION_base(4,8,0) -- | __NOTE__: Only defined for @base-4.8.0.0@ and later -- diff --git a/changelog.md b/changelog.md index 8b14bd9..b938e4c 100644 --- a/changelog.md +++ b/changelog.md @@ -26,6 +26,7 @@ - `Data.Typeable.Internal.TypeRep` - `GHC.Fingerprint.Type.Fingerprint` - `Numeric.Natural.Natural` + - `System.Mem.StableName.StableName` ## 1.3.0.2 *Nov 2013* From git at git.haskell.org Thu Mar 19 11:35:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:39 +0000 (UTC) Subject: [commit: packages/filepath] master: quickSafe: do not call show on already escaped output (#30) (7392405) Message-ID: <20150319113539.5048D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/739240511a9a8b978d726a4ea7832bc6d1a9bb0d >--------------------------------------------------------------- commit 739240511a9a8b978d726a4ea7832bc6d1a9bb0d Author: Thomas Miedema Date: Tue Oct 28 15:22:35 2014 +0100 quickSafe: do not call show on already escaped output (#30) This output: *** Failed! ... QFilePath "/\\?/a:a" is much easier to digest than: "*** FAILED! ... \NQFILEPATH \"/\\\\?/A:A\"\N" >--------------------------------------------------------------- 739240511a9a8b978d726a4ea7832bc6d1a9bb0d tests/AutoTest.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/tests/AutoTest.hs b/tests/AutoTest.hs index 56b6ec6..e65960b 100644 --- a/tests/AutoTest.hs +++ b/tests/AutoTest.hs @@ -40,4 +40,5 @@ quickSafe prop = do res <- quickCheckWithResult stdArgs{chatty=False, maxSuccess=10000} prop case res of Success{} -> return () - _ -> error $ show res + -- Output is already escaped. Do not call show on it, but print as-is. + _ -> error $ show res{output=""} ++ "\n" ++ (output res) From git at git.haskell.org Thu Mar 19 11:35:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:39 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Add `NFData` instances for `Foreign.C.Types` (8dc617d) Message-ID: <20150319113539.5B96E3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/8dc617dad456e16c67b0f629495dcf266a58ab0a >--------------------------------------------------------------- commit 8dc617dad456e16c67b0f629495dcf266a58ab0a Author: Herbert Valerio Riedel Date: Tue Nov 25 12:35:16 2014 +0100 Add `NFData` instances for `Foreign.C.Types` >--------------------------------------------------------------- 8dc617dad456e16c67b0f629495dcf266a58ab0a Control/DeepSeq.hs | 95 +++++++++++++++++++++++++++++++++++++++++++++++++++++- changelog.md | 1 + 2 files changed, 95 insertions(+), 1 deletion(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index aad5c9c..dfefe3e 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -66,7 +66,7 @@ import Data.Array import Data.Fixed import Data.Version import Data.Monoid - +import Foreign.C.Types import System.Mem.StableName ( StableName ) #if MIN_VERSION_base(4,7,0) @@ -360,6 +360,99 @@ instance NFData Fingerprint where #endif ---------------------------------------------------------------------------- +-- Foreign.C.Types + +-- |/Since: 1.4.0.0/ +instance NFData CChar where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CSChar where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CUChar where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CShort where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CUShort where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CInt where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CUInt where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CLong where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CULong where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CPtrdiff where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CSize where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CWchar where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CSigAtomic where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CLLong where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CULLong where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CIntPtr where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CUIntPtr where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CIntMax where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CUIntMax where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CClock where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CTime where rnf !_ = () + +#if MIN_VERSION_base(4,4,0) +-- |/Since: 1.4.0.0/ +instance NFData CUSeconds where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CSUSeconds where rnf !_ = () +#endif + +-- |/Since: 1.4.0.0/ +instance NFData CFloat where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CDouble where rnf !_ = () + +-- NOTE: The types `CFile`, `CFPos`, and `CJmpBuf` below are not +-- newtype wrappers rather defined as field-less single-constructor +-- types. + +-- |/Since: 1.4.0.0/ +instance NFData CFile where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CFpos where rnf !_ = () + +-- |/Since: 1.4.0.0/ +instance NFData CJmpBuf where rnf !_ = () + +---------------------------------------------------------------------------- -- Tuples instance (NFData a, NFData b) => NFData (a,b) where diff --git a/changelog.md b/changelog.md index b938e4c..c2bfa84 100644 --- a/changelog.md +++ b/changelog.md @@ -27,6 +27,7 @@ - `GHC.Fingerprint.Type.Fingerprint` - `Numeric.Natural.Natural` - `System.Mem.StableName.StableName` + - `Foreign.C.Types.C*` ## 1.3.0.2 *Nov 2013* From git at git.haskell.org Thu Mar 19 11:35:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:41 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge pull request #31 from thomie/output (f3c268f) Message-ID: <20150319113541.56A763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/f3c268f3f736ea7b74b3d3337114e3d8aa67f9ae >--------------------------------------------------------------- commit f3c268f3f736ea7b74b3d3337114e3d8aa67f9ae Merge: c9c1d58 7392405 Author: Neil Mitchell Date: Tue Oct 28 15:19:35 2014 +0000 Merge pull request #31 from thomie/output quickSafe: do not call show on already escaped output (#30) >--------------------------------------------------------------- f3c268f3f736ea7b74b3d3337114e3d8aa67f9ae tests/AutoTest.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) From git at git.haskell.org Thu Mar 19 11:35:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:41 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: `NFData` instances for `TyCon` and `TypeRep` (4beca42) Message-ID: <20150319113541.60E4D3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/4beca425214d11064e12c32bbf8e3d7a2ccd4df9 >--------------------------------------------------------------- commit 4beca425214d11064e12c32bbf8e3d7a2ccd4df9 Author: Herbert Valerio Riedel Date: Fri Dec 5 17:35:24 2014 +0100 `NFData` instances for `TyCon` and `TypeRep` >--------------------------------------------------------------- 4beca425214d11064e12c32bbf8e3d7a2ccd4df9 Control/DeepSeq.hs | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index dfefe3e..c6763e5 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -58,6 +58,7 @@ module Control.DeepSeq ( ) where import Control.Applicative +import Control.Concurrent ( ThreadId ) import Data.Int import Data.Word import Data.Ratio @@ -66,6 +67,7 @@ import Data.Array import Data.Fixed import Data.Version import Data.Monoid +import Data.Unique ( Unique ) import Foreign.C.Types import System.Mem.StableName ( StableName ) @@ -334,7 +336,15 @@ instance NFData a => NFData (Product a) where -- |/Since: 1.4.0.0/ instance NFData (StableName a) where - rnf !_ = () + rnf !_ = () -- assumes `data StableName a = StableName (StableName# a)` + +-- |/Since: 1.4.0.0/ +instance NFData ThreadId where + rnf !_ = () -- assumes `data ThreadId = ThreadId ThreadId#` + +-- |/Since: 1.4.0.0/ +instance NFData Unique where + rnf !_ = () -- assumes `newtype Unique = Unique Integer` #if MIN_VERSION_base(4,8,0) -- | __NOTE__: Only defined for @base-4.8.0.0@ and later From git at git.haskell.org Thu Mar 19 11:35:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:43 +0000 (UTC) Subject: [commit: packages/filepath] master: Refactor isValid and makeValid (2d37bc2) Message-ID: <20150319113543.5CB443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/2d37bc25735bd658358092ff2209ef3abcf35160 >--------------------------------------------------------------- commit 2d37bc25735bd658358092ff2209ef3abcf35160 Author: Thomas Miedema Date: Tue Oct 28 19:16:52 2014 +0100 Refactor isValid and makeValid `head (splitPath path)` is not equal to `takeDrive path` in general: head (splitPath "\\foo") == "\\" fst (splitDrive "\\foo") == "" We can do this refactoring because they /are/ equal within the constraint: `length drv >= 2 && all isPathSeparator drv` >--------------------------------------------------------------- 2d37bc25735bd658358092ff2209ef3abcf35160 System/FilePath/Internal.hs | 12 +++++------- 1 file changed, 5 insertions(+), 7 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 323f8e3..fedb014 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -808,8 +808,7 @@ isValid path = not (any f $ splitDirectories x2) && not (length x1 >= 2 && all isPathSeparator x1) where - x1 = head (splitPath path) - x2 = dropDrive path + (x1,x2) = splitDrive path f x = map toUpper (dropExtensions x) `elem` badElements @@ -828,11 +827,10 @@ isValid path = -- > Windows: makeValid "\\\\\\foo" == "\\\\drive" makeValid :: FilePath -> FilePath makeValid "" = "_" -makeValid path | isPosix = path -makeValid xs | length x >= 2 && all isPathSeparator x = take 2 x ++ "drive" - where - x = head (splitPath xs) -makeValid path = joinDrive drv $ validElements $ validChars pth +makeValid path + | isPosix = path + | length drv >= 2 && all isPathSeparator drv = take 2 drv ++ "drive" + | otherwise = joinDrive drv $ validElements $ validChars pth where (drv,pth) = splitDrive path From git at git.haskell.org Thu Mar 19 11:35:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:43 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Changelog entry for 4beca42 (91f0711) Message-ID: <20150319113543.668C63A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/91f071102ca85456f9adac33e8865cb986073ade >--------------------------------------------------------------- commit 91f071102ca85456f9adac33e8865cb986073ade Author: Herbert Valerio Riedel Date: Fri Dec 5 17:39:01 2014 +0100 Changelog entry for 4beca42 >--------------------------------------------------------------- 91f071102ca85456f9adac33e8865cb986073ade changelog.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/changelog.md b/changelog.md index c2bfa84..28fd840 100644 --- a/changelog.md +++ b/changelog.md @@ -19,11 +19,13 @@ - `Control.Applicative.Const` - `Control.Applicative.ZipList` + - `Control.Concurrent.ThreadId` - `Data.Functor.Identity.Identity` - `Data.Monoid.{Dual,First,Last,Any,All,Sum,Product}` - `Data.Proxy.Proxy` - `Data.Typeable.Internal.TyCon` - `Data.Typeable.Internal.TypeRep` + - `Data.Unique.Unique` - `GHC.Fingerprint.Type.Fingerprint` - `Numeric.Natural.Natural` - `System.Mem.StableName.StableName` From git at git.haskell.org Thu Mar 19 11:35:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:45 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: `NFData` instances for `Data.Ord.Down` wrapper (f5d69c4) Message-ID: <20150319113545.6C1473A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/f5d69c46793f15202bb01a98bdee63a7f8a0ca9a >--------------------------------------------------------------- commit f5d69c46793f15202bb01a98bdee63a7f8a0ca9a Author: Herbert Valerio Riedel Date: Fri Dec 5 17:42:05 2014 +0100 `NFData` instances for `Data.Ord.Down` wrapper >--------------------------------------------------------------- f5d69c46793f15202bb01a98bdee63a7f8a0ca9a Control/DeepSeq.hs | 10 ++++++++++ changelog.md | 1 + 2 files changed, 11 insertions(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index c6763e5..5da51f8 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -71,6 +71,10 @@ import Data.Unique ( Unique ) import Foreign.C.Types import System.Mem.StableName ( StableName ) +#if MIN_VERSION_base(4,6,0) +import Data.Ord ( Down(Down) ) +#endif + #if MIN_VERSION_base(4,7,0) import Data.Proxy ( Proxy(Proxy) ) #endif @@ -308,6 +312,12 @@ instance NFData a => NFData (Const a b) where instance (Ix a, NFData a, NFData b) => NFData (Array a b) where rnf x = rnf (bounds x, Data.Array.elems x) +#if MIN_VERSION_base(4,6,0) +-- |/Since: 1.4.0.0/ +instance NFData a => NFData (Down a) where + rnf (Down x) = rnf x +#endif + -- |/Since: 1.4.0.0/ instance NFData a => NFData (Dual a) where rnf = rnf . getDual diff --git a/changelog.md b/changelog.md index 28fd840..7ba3108 100644 --- a/changelog.md +++ b/changelog.md @@ -22,6 +22,7 @@ - `Control.Concurrent.ThreadId` - `Data.Functor.Identity.Identity` - `Data.Monoid.{Dual,First,Last,Any,All,Sum,Product}` + - `Data.Ord.Down` - `Data.Proxy.Proxy` - `Data.Typeable.Internal.TyCon` - `Data.Typeable.Internal.TypeRep` From git at git.haskell.org Thu Mar 19 11:35:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:45 +0000 (UTC) Subject: [commit: packages/filepath] master: Bug fix: isValid "\\\\?\\D:file" == False (d6613d7) Message-ID: <20150319113545.6437D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/d6613d73cf6da7c93db9739a8324f8f585ffbab6 >--------------------------------------------------------------- commit d6613d73cf6da7c93db9739a8324f8f585ffbab6 Author: Thomas Miedema Date: Tue Oct 28 19:55:42 2014 +0100 Bug fix: isValid "\\\\?\\D:file" == False From http://msdn.microsoft.com/en-us/library/windows/desktop/aa365247.aspx: * "A UNC name of any format [is never relative]." * "You cannot use the "\\?\" prefix with a relative path." >--------------------------------------------------------------- d6613d73cf6da7c93db9739a8324f8f585ffbab6 System/FilePath/Internal.hs | 7 ++++++- changelog.md | 3 +++ 2 files changed, 9 insertions(+), 1 deletion(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index fedb014..e3fa7cb 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -800,13 +800,15 @@ badElements = ["CON", "PRN", "AUX", "NUL", "COM1", "COM2", "COM3", "COM4", "COM5 -- > Windows: isValid "c:\\nul\\file" == False -- > Windows: isValid "\\\\" == False -- > Windows: isValid "\\\\\\foo" == False +-- > Windows: isValid "\\\\?\\D:file" == False isValid :: FilePath -> Bool isValid "" = False isValid _ | isPosix = True isValid path = not (any (`elem` badCharacters) x2) && not (any f $ splitDirectories x2) && - not (length x1 >= 2 && all isPathSeparator x1) + not (length x1 >= 2 && all isPathSeparator x1) && + not (isJust (readDriveUNC x1) && not (hasTrailingPathSeparator x1)) where (x1,x2) = splitDrive path f x = map toUpper (dropExtensions x) `elem` badElements @@ -825,11 +827,14 @@ isValid path = -- > Windows: makeValid "c:\\test/prn.txt" == "c:\\test/prn_.txt" -- > Windows: makeValid "c:\\nul\\file" == "c:\\nul_\\file" -- > Windows: makeValid "\\\\\\foo" == "\\\\drive" +-- > Windows: makeValid "\\\\?\\D:file" == "\\\\?\\D:\\file" makeValid :: FilePath -> FilePath makeValid "" = "_" makeValid path | isPosix = path | length drv >= 2 && all isPathSeparator drv = take 2 drv ++ "drive" + | isJust (readDriveUNC drv) && not (hasTrailingPathSeparator drv) = + makeValid (drv ++ [pathSeparator] ++ pth) | otherwise = joinDrive drv $ validElements $ validChars pth where (drv,pth) = splitDrive path diff --git a/changelog.md b/changelog.md index f46153f..ec5f0c0 100644 --- a/changelog.md +++ b/changelog.md @@ -24,6 +24,9 @@ * Bug fix: on Windows, `isValid "\\\\\\foo"` now returns `False`, instead of `True`. + * Bug fix: on Windows, `isValid "\\\\?\\D:file"` now returns `False`, + instead of `True`. + * Bug fix: on Windows, `normalise "\\"` now retuns `"\\"` unchanged, instead of `"\\\\"`. From git at git.haskell.org Thu Mar 19 11:35:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:47 +0000 (UTC) Subject: [commit: packages/filepath] master: Put "Valid x =>" constraint on joinDrive QuickCheck property (7420444) Message-ID: <20150319113547.6B16E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/7420444bb461968a5da58f6a5b8707b0a7efeb4e >--------------------------------------------------------------- commit 7420444bb461968a5da58f6a5b8707b0a7efeb4e Author: Thomas Miedema Date: Tue Oct 28 19:57:32 2014 +0100 Put "Valid x =>" constraint on joinDrive QuickCheck property Counterexample: $ let x = "\\\\?\\D:file" $ splitDrive x ("\\\\?\\D:","file") $ uncurry joinDrive (splitDrive x) "\\\\?\\D:\\file" The "problem" is that the current implementation of splitDrive can sometimes return invalid drives, such as in the above example. However, if it wouldn't do so, it would make the implementation of isValid and makeValid more difficult. My guideline is currently as follows: splitDrive makes the rough cut of what is and what isn't a drive, isValid and makeValid finish the job, all other functions assume drives and paths are valid. This is also the reason joinDrive (=combineAlways) should not be changed to not insert the extra slash, solely to handle an invalid path. >--------------------------------------------------------------- 7420444bb461968a5da58f6a5b8707b0a7efeb4e System/FilePath/Internal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index e3fa7cb..8f2c51b 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -377,7 +377,7 @@ readDriveShareName name = addSlash a b -- | Join a drive and the rest of the path. -- --- > uncurry joinDrive (splitDrive x) == x +-- > Valid x => uncurry joinDrive (splitDrive x) == x -- > Windows: joinDrive "C:" "foo" == "C:foo" -- > Windows: joinDrive "C:\\" "bar" == "C:\\bar" -- > Windows: joinDrive "\\\\share" "foo" == "\\\\share\\foo" From git at git.haskell.org Thu Mar 19 11:35:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:47 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: `NFData` instance for `Data.Void.Void` (d047c9e) Message-ID: <20150319113547.71B293A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/d047c9edd98cf09234e6e5f62dcf24c560f25f9d >--------------------------------------------------------------- commit d047c9edd98cf09234e6e5f62dcf24c560f25f9d Author: Herbert Valerio Riedel Date: Sat Dec 6 10:31:21 2014 +0100 `NFData` instance for `Data.Void.Void` >--------------------------------------------------------------- d047c9edd98cf09234e6e5f62dcf24c560f25f9d Control/DeepSeq.hs | 7 +++++++ changelog.md | 1 + 2 files changed, 8 insertions(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 5da51f8..9f60d88 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -83,6 +83,7 @@ import Data.Proxy ( Proxy(Proxy) ) import Data.Functor.Identity ( Identity(..) ) -- NB: Data.Typeable.Internal is "Trustworthy" only starting w/ base-4.8 import Data.Typeable.Internal ( TypeRep(..), TyCon(..) ) +import Data.Void ( Void, absurd ) import Numeric.Natural ( Natural ) #endif @@ -262,6 +263,12 @@ instance NFData (Proxy a) where rnf Proxy = () instance NFData a => NFData (Identity a) where rnf = rnf . runIdentity +-- | Defined as @'rnf' = 'absurd'@. +-- +-- /Since: 1.4.0.0/ +instance NFData Void where + rnf = absurd + -- |/Since: 1.4.0.0/ instance NFData Natural where rnf !_ = () #endif diff --git a/changelog.md b/changelog.md index 7ba3108..5226ed2 100644 --- a/changelog.md +++ b/changelog.md @@ -27,6 +27,7 @@ - `Data.Typeable.Internal.TyCon` - `Data.Typeable.Internal.TypeRep` - `Data.Unique.Unique` + - `Data.Void.Void` - `GHC.Fingerprint.Type.Fingerprint` - `Numeric.Natural.Natural` - `System.Mem.StableName.StableName` From git at git.haskell.org Thu Mar 19 11:35:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:49 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge pull request #32 from thomie/unc (a3a3d50) Message-ID: <20150319113549.737AA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/a3a3d50fd816cf565b59cd0db68b0980ecf7593e >--------------------------------------------------------------- commit a3a3d50fd816cf565b59cd0db68b0980ecf7593e Merge: f3c268f 7420444 Author: Neil Mitchell Date: Tue Oct 28 20:05:49 2014 +0000 Merge pull request #32 from thomie/unc Bug fix: isValid "\\\\?\\D:file" == False >--------------------------------------------------------------- a3a3d50fd816cf565b59cd0db68b0980ecf7593e System/FilePath/Internal.hs | 21 ++++++++++++--------- changelog.md | 3 +++ 2 files changed, 15 insertions(+), 9 deletions(-) From git at git.haskell.org Thu Mar 19 11:35:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:49 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Add simple test-suite for Generics deriving (733f4af) Message-ID: <20150319113549.78E623A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/733f4af3d34d28e004e58c38451575b655efb8b8 >--------------------------------------------------------------- commit 733f4af3d34d28e004e58c38451575b655efb8b8 Author: Herbert Valerio Riedel Date: Sat Dec 6 11:39:21 2014 +0100 Add simple test-suite for Generics deriving This does not use ChasingBottoms as we're interested in testing each field is evaluated exactly once which ChasingBottoms doesn't provide afaics. >--------------------------------------------------------------- 733f4af3d34d28e004e58c38451575b655efb8b8 deepseq.cabal | 29 +++++++++++ tests/Main.hs | 152 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 2 files changed, 181 insertions(+) diff --git a/deepseq.cabal b/deepseq.cabal index 261b01d..2e4aff6 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -56,3 +56,32 @@ library ghc-options: -Wall exposed-modules: Control.DeepSeq + + +test-suite deepseq-generics-tests + default-language: Haskell2010 + if !impl(ghc>=7.2) + buildable: False + type: exitcode-stdio-1.0 + hs-source-dirs: . tests + main-is: Main.hs + other-extensions: + CPP + BangPatterns + DefaultSignatures + DeriveDataTypeable + DeriveGeneric + FlexibleContexts + Safe + TupleSections + TypeOperators + + ghc-options: -Wall + + build-depends: + array, + base, + -- end of packages with inherited version constraints + test-framework == 0.8.*, + test-framework-hunit == 0.3.*, + HUnit == 1.2.* diff --git a/tests/Main.hs b/tests/Main.hs new file mode 100644 index 0000000..5199a17 --- /dev/null +++ b/tests/Main.hs @@ -0,0 +1,152 @@ +-- Code reused from http://hackage.haskell.org/package/deepseq-generics + +{-# LANGUAGE CPP #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE TupleSections #-} + +module Main (main) where + +import Control.Concurrent.MVar +import Control.Exception +import Control.Monad +import Data.Bits +import Data.IORef +import Data.Typeable +import Data.Word +import GHC.Generics +import System.IO.Unsafe (unsafePerformIO) + +-- import Test.Framework (defaultMain, testGroup, testCase) +import Test.Framework +import Test.Framework.Providers.HUnit +import Test.HUnit + +-- IUT +import Control.DeepSeq + +-- needed for GHC-7.4 compatibility +#if !MIN_VERSION_base(4,6,0) +atomicModifyIORef' :: IORef a -> (a -> (a,b)) -> IO b +atomicModifyIORef' ref f = do + b <- atomicModifyIORef ref + (\x -> let (a, b) = f x + in (a, a `seq` b)) + b `seq` return b +#endif + +---------------------------------------------------------------------------- +-- simple hacky abstraction for testing forced evaluation via `rnf`-like functions + +seqStateLock :: MVar () +seqStateLock = unsafePerformIO $ newMVar () +{-# NOINLINE seqStateLock #-} + +withSeqState :: Word64 -> IO () -> IO () +withSeqState expectedState act = withMVar seqStateLock $ \() -> do + 0 <- resetSeqState + () <- act + st <- resetSeqState + unless (st == expectedState) $ + assertFailure ("withSeqState: actual seq-state ("++show st++") doesn't match expected value ("++ + show expectedState++")") + +seqState :: IORef Word64 +seqState = unsafePerformIO $ newIORef 0 +{-# NOINLINE seqState #-} + +resetSeqState :: IO Word64 +resetSeqState = atomicModifyIORef' seqState (0,) + +-- |Set flag and raise exception is flag already set +setSeqState :: Int -> IO () +setSeqState i | 0 <= i && i < 64 = atomicModifyIORef' seqState go + | otherwise = error "seqSeqState: flag index must be in [0..63]" + where + go x | testBit x i = error ("setSeqState: flag #"++show i++" already set") + | otherwise = (setBit x i, ()) + +-- weird type whose NFData instacne calls 'setSeqState' when rnf-ed +data SeqSet = SeqSet !Int | SeqIgnore + deriving Show + +instance NFData SeqSet where + rnf (SeqSet i) = unsafePerformIO $ setSeqState i + rnf (SeqIgnore) = () + {-# NOINLINE rnf #-} + +-- |Exception to be thrown for testing 'seq'/'rnf' +data RnfEx = RnfEx deriving (Eq, Show, Typeable) + +instance Exception RnfEx + +instance NFData RnfEx where rnf e = throw e + +assertRnfEx :: () -> IO () +assertRnfEx v = handleJust isWanted (const $ return ()) $ do + () <- evaluate v + assertFailure "failed to trigger expected RnfEx exception" + where isWanted = guard . (== RnfEx) + +---------------------------------------------------------------------------- + +case_1, case_2, case_3, case_4_1, case_4_2, case_4_3, case_4_4 :: Test.Framework.Test + +newtype Case1 = Case1 Int + deriving (Generic) + +instance NFData Case1 + +case_1 = testCase "Case1" $ do + assertRnfEx $ rnf $ (Case1 (throw RnfEx)) + +---- + +data Case2 = Case2 Int + deriving (Generic) + +instance NFData Case2 + +case_2 = testCase "Case2" $ do + assertRnfEx $ rnf $ (Case2 (throw RnfEx)) + +---- + +data Case3 = Case3 RnfEx + deriving (Generic) + +instance NFData Case3 + +case_3 = testCase "Case3" $ do + assertRnfEx $ rnf $ Case3 RnfEx + +---- + +data Case4 a = Case4a + | Case4b a a + | Case4c a (Case4 a) + deriving (Generic) + +instance NFData a => NFData (Case4 a) + +case_4_1 = testCase "Case4.1" $ withSeqState 0x0 $ do + evaluate $ rnf $ (Case4a :: Case4 SeqSet) + +case_4_2 = testCase "Case4.2" $ withSeqState 0x3 $ do + evaluate $ rnf $ (Case4b (SeqSet 0) (SeqSet 1) :: Case4 SeqSet) + +case_4_3 = testCase "Case4.3" $ withSeqState (bit 55) $ do + evaluate $ rnf $ (Case4b SeqIgnore (SeqSet 55) :: Case4 SeqSet) + +case_4_4 = testCase "Case4.4" $ withSeqState 0xffffffffffffffff $ do + evaluate $ rnf $ (genCase 63) + where + genCase n | n > 1 = Case4c (SeqSet n) (genCase (n-1)) + | otherwise = Case4b (SeqSet 0) (SeqSet 1) + +---------------------------------------------------------------------------- + +main :: IO () +main = defaultMain [tests] + where + tests = testGroup "" [case_1, case_2, case_3, case_4_1, case_4_2, case_4_3, case_4_4] From git at git.haskell.org Thu Mar 19 11:35:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:51 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Remove obsolete `deepseq-generics` reference (45377fa) Message-ID: <20150319113551.7ECF73A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/45377fac1e8d1d199a1118ee9812f3b787742f41 >--------------------------------------------------------------- commit 45377fac1e8d1d199a1118ee9812f3b787742f41 Author: Herbert Valerio Riedel Date: Wed Dec 17 12:23:12 2014 +0100 Remove obsolete `deepseq-generics` reference ...and detabify deepseq.cabal file >--------------------------------------------------------------- 45377fac1e8d1d199a1118ee9812f3b787742f41 deepseq.cabal | 15 +++++---------- 1 file changed, 5 insertions(+), 10 deletions(-) diff --git a/deepseq.cabal b/deepseq.cabal index 2e4aff6..a718551 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -1,11 +1,11 @@ -name: deepseq +name: deepseq version: 1.4.0.0 -- NOTE: Don't forget to update ./changelog.md -license: BSD3 -license-file: LICENSE -maintainer: libraries at haskell.org +license: BSD3 +license-file: LICENSE +maintainer: libraries at haskell.org bug-reports: https://github.com/haskell/deepseq/issues -synopsis: Deep evaluation of data structures +synopsis: Deep evaluation of data structures category: Control description: This package provides methods for fully evaluating data structures @@ -20,11 +20,6 @@ description: typeclass (\"Normal Form Data\", data structures with no unevaluated components) which defines strategies for fully evaluating different data types. - . - If you want to automatically derive 'NFData' instances via the - "GHC.Generics" facility, there is a companion package - - which builds on top of this package. build-type: Simple cabal-version: >=1.10 tested-with: GHC==7.8.3, GHC==7.8.2, GHC==7.8.1, 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.2.1, GHC==7.0.4, GHC==7.0.3, GHC==7.0.2, GHC==7.0.1 From git at git.haskell.org Thu Mar 19 11:35:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:51 +0000 (UTC) Subject: [commit: packages/filepath] master: Remove "|bcd123" from character set for tests (#15) (3bd5fa0) Message-ID: <20150319113551.798083A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/3bd5fa01a770850302d3a8342b009a785aa0ce03 >--------------------------------------------------------------- commit 3bd5fa01a770850302d3a8342b009a785aa0ce03 Author: Thomas Miedema Date: Tue Oct 28 21:17:38 2014 +0100 Remove "|bcd123" from character set for tests (#15) >--------------------------------------------------------------- 3bd5fa01a770850302d3a8342b009a785aa0ce03 tests/AutoTest.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/AutoTest.hs b/tests/AutoTest.hs index e65960b..00ddd30 100644 --- a/tests/AutoTest.hs +++ b/tests/AutoTest.hs @@ -31,7 +31,7 @@ instance Arbitrary QFilePath where newtype QChar = QChar {fromQChar :: Char} instance Arbitrary QChar where - arbitrary = fmap QChar $ elements "?|./:\\abcd 123;_" + arbitrary = fmap QChar $ elements "?./:\\a ;_" From git at git.haskell.org Thu Mar 19 11:35:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:53 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge pull request #33 from thomie/arbitrary (ff126cd) Message-ID: <20150319113553.804753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/ff126cdb05a1f493bdb54a49a34572d8c91f1034 >--------------------------------------------------------------- commit ff126cdb05a1f493bdb54a49a34572d8c91f1034 Merge: a3a3d50 3bd5fa0 Author: Neil Mitchell Date: Tue Oct 28 20:53:46 2014 +0000 Merge pull request #33 from thomie/arbitrary Remove "|bcd123" from character set for tests (#15) >--------------------------------------------------------------- ff126cdb05a1f493bdb54a49a34572d8c91f1034 tests/AutoTest.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Thu Mar 19 11:35:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:53 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Update release month for 1.4.0.0 (09f9402) Message-ID: <20150319113553.842F73A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/09f9402366060f8f8190d2733679aaf3cb9da54d >--------------------------------------------------------------- commit 09f9402366060f8f8190d2733679aaf3cb9da54d Author: Herbert Valerio Riedel Date: Wed Dec 17 12:30:54 2014 +0100 Update release month for 1.4.0.0 >--------------------------------------------------------------- 09f9402366060f8f8190d2733679aaf3cb9da54d changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index 5226ed2..75aaf8f 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`deepseq` package](http://hackage.haskell.org/package/deepseq) -## 1.4.0.0 *TBA* +## 1.4.0.0 *Dec 2014* * Bundled with GHC 7.10.1 * Switch to Generics based `DefaultSignature` `rnf` method From git at git.haskell.org Thu Mar 19 11:35:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:55 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Minor doc fix (a79bee5) Message-ID: <20150319113555.8A5C63A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/a79bee5f5da25353b88759cf5ed8d0df2b59946c >--------------------------------------------------------------- commit a79bee5f5da25353b88759cf5ed8d0df2b59946c Author: Herbert Valerio Riedel Date: Wed Dec 17 12:34:39 2014 +0100 Minor doc fix [skip ci] >--------------------------------------------------------------- a79bee5f5da25353b88759cf5ed8d0df2b59946c Control/DeepSeq.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 9f60d88..4213e92 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -208,7 +208,7 @@ class NFData a where -- -- === Compatibility with previous @deepseq@ versions -- - -- Prior to version 1.4.0, the default implementation of the 'rnf' + -- Prior to version 1.4.0.0, the default implementation of the 'rnf' -- method was defined as -- -- @'rnf' a = 'seq' a ()@ From git at git.haskell.org Thu Mar 19 11:35:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:55 +0000 (UTC) Subject: [commit: packages/filepath] master: Reformat and make everything consistent, don't quote \, or it gets too confusing (95ed27b) Message-ID: <20150319113555.868863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/95ed27b131017eaf6b3a77b0a256dfb2e3af3688 >--------------------------------------------------------------- commit 95ed27b131017eaf6b3a77b0a256dfb2e3af3688 Author: Neil Mitchell Date: Tue Oct 28 21:42:36 2014 +0000 Reformat and make everything consistent, don't quote \, or it gets too confusing >--------------------------------------------------------------- 95ed27b131017eaf6b3a77b0a256dfb2e3af3688 changelog.md | 39 +++++++++++++++------------------------ 1 file changed, 15 insertions(+), 24 deletions(-) diff --git a/changelog.md b/changelog.md index ec5f0c0..83ff2a5 100644 --- a/changelog.md +++ b/changelog.md @@ -1,43 +1,34 @@ # Changelog for [`filepath` package](http://hackage.haskell.org/package/filepath) +_Note: below all `FilePath` values are unquoted, so `\\` really means two backslashes. + ## 1.3.0.3 *TBA* * Bundled with GHC 7.10.1 - * Semantic change: `joinDrive "/foo" "bar"` now returns `"/foo/bar"`, - instead of `"/foobar"`. + * Semantic change: `joinDrive /foo bar` now returns `/foo/bar`, instead of `/foobar` - * Bug fix, on Posix systems, `normalise "//home"` now returns `"/home"`, - instead of `"//home"`. + * Bug fix: on Posix systems, `normalise //home` now returns `/home`, instead of `//home` - * Bug fix, `normalise "/./"` now returns "/" on Posix and "\\" on Windows, - instead of "//" and "\\\\". + * Bug fix: `normalise /./` now returns `/` on Posix and `\` on Windows, instead of `//` and `\\` - * Bug fix: `isDrive ""` now retuns `False`, instead of `True`. + * Bug fix: `isDrive ""` now returns `False`, instead of `True` - * Bug fix: on Windows, `dropTrailingPathSeparator "/"` now returns `"/"` - unchanged, instead of the normalised `"\\"`. + * Bug fix: on Windows, `dropTrailingPathSeparator /` now returns `/` unchanged, instead of the normalised `\` - * Bug fix: on Windows, `equalFilePath "C:\\" "C:"` now retuns `False`, - instead of `True`. + * Bug fix: on Windows, `equalFilePath C:\ C:` now returns `False`, instead of `True` - * Bug fix: on Windows, `isValid "\\\\\\foo"` now returns `False`, instead - of `True`. + * Bug fix: on Windows, `isValid \\\foo` now returns `False`, instead of `True` - * Bug fix: on Windows, `isValid "\\\\?\\D:file"` now returns `False`, - instead of `True`. + * Bug fix: on Windows, `isValid \\?\D:file` now returns `False`, instead of `True` - * Bug fix: on Windows, `normalise "\\"` now retuns `"\\"` unchanged, - instead of `"\\\\"`. + * Bug fix: on Windows, `normalise \` now returns `\` unchanged, instead of `\\` - * Bug fix: on Windows, `normalise "C:.\\"` now retuns `"C:"`, instead of - `"C:\\"`. + * Bug fix: on Windows, `normalise C:.\` now returns `C:`, instead of `C:\\` - * Bug fix: on Windows, `normalise "//server/test"` now retuns - `"\\\\server\\test"`, instead of `"//server/test"` unchanged. + * Bug fix: on Windows, `normalise //server/test` now returns `\\server\test`, instead of `//server/test` unchanged - * Bug fix: on Windows, `makeRelative "/" "//"` now returns `"//"`, instead - of `""`. + * Bug fix: on Windows, `makeRelative / //` now returns `//`, instead of `""` ## 1.3.0.2 *Mar 2014* @@ -59,4 +50,4 @@ * Add support for SafeHaskell - * Fix `normalise "/"` to result in `"/"` rather than `"/."` + * Bug fix: `normalise /` now returns `/`, instead of `/.` From git at git.haskell.org Thu Mar 19 11:35:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:57 +0000 (UTC) Subject: [commit: packages/filepath] master: Check in the filepath tests (68e3a0e) Message-ID: <20150319113557.908373A2FF@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/68e3a0e955c8539b3032c5b320d9e1af895eff07 >--------------------------------------------------------------- commit 68e3a0e955c8539b3032c5b320d9e1af895eff07 Author: Neil Mitchell Date: Wed Oct 29 07:26:04 2014 +0000 Check in the filepath tests >--------------------------------------------------------------- 68e3a0e955c8539b3032c5b320d9e1af895eff07 tests/.gitignore | 1 - tests/FilePath_Test.hs | 706 +++++++++++++++++++++++++++++++++++++++++++++++++ 2 files changed, 706 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 68e3a0e955c8539b3032c5b320d9e1af895eff07 From git at git.haskell.org Thu Mar 19 11:35:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:57 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Remove redundant constraints, discovered by -fwarn-redundant-constraints (de1bc89) Message-ID: <20150319113557.901383A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/de1bc894de1ffdd34e6eb8be4fb9e057198060c6 >--------------------------------------------------------------- commit de1bc894de1ffdd34e6eb8be4fb9e057198060c6 Author: Simon Peyton Jones Date: Tue Jan 6 12:19:50 2015 +0000 Remove redundant constraints, discovered by -fwarn-redundant-constraints >--------------------------------------------------------------- de1bc894de1ffdd34e6eb8be4fb9e057198060c6 Control/DeepSeq.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 4213e92..418b081 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -284,10 +284,10 @@ instance NFData (a -> b) where rnf !_ = () --Rational and complex numbers. -instance (Integral a, NFData a) => NFData (Ratio a) where +instance NFData a => NFData (Ratio a) where rnf x = rnf (numerator x, denominator x) -instance (RealFloat a, NFData a) => NFData (Complex a) where +instance (NFData a) => NFData (Complex a) where rnf (x:+y) = rnf x `seq` rnf y `seq` () @@ -316,7 +316,7 @@ instance NFData a => NFData (ZipList a) where instance NFData a => NFData (Const a b) where rnf = rnf . getConst -instance (Ix a, NFData a, NFData b) => NFData (Array a b) where +instance (NFData a, NFData b) => NFData (Array a b) where rnf x = rnf (bounds x, Data.Array.elems x) #if MIN_VERSION_base(4,6,0) From git at git.haskell.org Thu Mar 19 11:35:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:59 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Recover breakage for GHC<7.11 caused by de1bc89 (153520a) Message-ID: <20150319113559.977B13A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/153520ab033fd26beb47757cc6512f177cb1ae8f >--------------------------------------------------------------- commit 153520ab033fd26beb47757cc6512f177cb1ae8f Author: Herbert Valerio Riedel Date: Thu Jan 15 13:16:41 2015 +0100 Recover breakage for GHC<7.11 caused by de1bc89 de1bc89 dropped a few redundant constraints, some of which are not yet redundant in prior GHC/base versions. >--------------------------------------------------------------- 153520ab033fd26beb47757cc6512f177cb1ae8f Control/DeepSeq.hs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 418b081..a732feb 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -284,7 +284,11 @@ instance NFData (a -> b) where rnf !_ = () --Rational and complex numbers. +#if __GLASGOW_HASKELL__ >= 711 instance NFData a => NFData (Ratio a) where +#else +instance (Integral a, NFData a) => NFData (Ratio a) where +#endif rnf x = rnf (numerator x, denominator x) instance (NFData a) => NFData (Complex a) where @@ -316,7 +320,11 @@ instance NFData a => NFData (ZipList a) where instance NFData a => NFData (Const a b) where rnf = rnf . getConst +#if __GLASGOW_HASKELL__ >= 711 instance (NFData a, NFData b) => NFData (Array a b) where +#else +instance (Ix a, NFData a, NFData b) => NFData (Array a b) where +#endif rnf x = rnf (bounds x, Data.Array.elems x) #if MIN_VERSION_base(4,6,0) From git at git.haskell.org Thu Mar 19 11:35:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:35:59 +0000 (UTC) Subject: [commit: packages/filepath] master: Since the generated code is checked in, no need to run the generator (0caec5f) Message-ID: <20150319113559.981F03A2FF@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/0caec5fe2dc526c720cc18570a9619e1d0365baf >--------------------------------------------------------------- commit 0caec5fe2dc526c720cc18570a9619e1d0365baf Author: Neil Mitchell Date: Wed Oct 29 07:31:28 2014 +0000 Since the generated code is checked in, no need to run the generator >--------------------------------------------------------------- 0caec5fe2dc526c720cc18570a9619e1d0365baf .travis.yml | 1 - filepath.cabal | 4 ---- 2 files changed, 5 deletions(-) diff --git a/.travis.yml b/.travis.yml index 0451896..10b2f23 100644 --- a/.travis.yml +++ b/.travis.yml @@ -22,7 +22,6 @@ install: - cabal install --only-dependencies --enable-tests; script: - - cd tests/ && runghc ./GenTests.hs && cd .. - cabal configure --enable-tests -v2 - cabal build - cabal test diff --git a/filepath.cabal b/filepath.cabal index f34bc40..ed836f3 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -46,10 +46,6 @@ library ghc-options: -Wall --- When run directly from the Git repo, you need to --- generate the tests/FilePath_Tests.hs file via --- --- cd tests/ && runghc ./GenTests.hs test-suite filepath-tests type: exitcode-stdio-1.0 default-language: Haskell98 From git at git.haskell.org Thu Mar 19 11:36:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:01 +0000 (UTC) Subject: [commit: packages/filepath] master: Move the generator (ee6451a) Message-ID: <20150319113601.9EE3C3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/ee6451a2892b2c3c1184795109c73d5b8ad67de1 >--------------------------------------------------------------- commit ee6451a2892b2c3c1184795109c73d5b8ad67de1 Author: Neil Mitchell Date: Wed Oct 29 07:31:51 2014 +0000 Move the generator >--------------------------------------------------------------- ee6451a2892b2c3c1184795109c73d5b8ad67de1 .ghci | 2 +- tests/GenTests.hs => Generate.hs | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/.ghci b/.ghci index 6676709..dc49947 100644 --- a/.ghci +++ b/.ghci @@ -7,4 +7,4 @@ import qualified System.FilePath.Posix as Posix :def docs_ const $ return $ unlines [":!cabal haddock"] :def docs const $ return $ unlines [":docs_",":!start dist\\doc\\html\\filepath\\System-FilePath.html"] -:def test const $ return $ unlines [":!cd tests && runhaskell GenTests.hs",":!cabal test"] +:def test const $ return $ unlines [":!runhaskell Generate.hs",":!cabal test"] diff --git a/tests/GenTests.hs b/Generate.hs old mode 100644 new mode 100755 similarity index 95% rename from tests/GenTests.hs rename to Generate.hs index 722ffc0..53ec8c6 --- a/tests/GenTests.hs +++ b/Generate.hs @@ -14,9 +14,9 @@ isExpr (Expr{}) = True isExpr _ = False -main = do src <- readFile "../System/FilePath/Internal.hs" +main = do src <- readFile "System/FilePath/Internal.hs" let tests = concatMap getTest $ zip [1..] (lines src) - writeFile "FilePath_Test.hs" (prefix ++ genTests tests) + writeFile "tests/FilePath_Test.hs" (prefix ++ genTests tests) prefix = unlines ["import AutoTest" From git at git.haskell.org Thu Mar 19 11:36:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:01 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Bump version to 1.4.1.0 (6dc253b) Message-ID: <20150319113601.9D71E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/6dc253b6797c638894658805290132cca5fdd889 >--------------------------------------------------------------- commit 6dc253b6797c638894658805290132cca5fdd889 Author: Herbert Valerio Riedel Date: Thu Jan 15 13:39:37 2015 +0100 Bump version to 1.4.1.0 Let's use a minor bump because dropping redundant constraints is something that affects the type-signatures and could require to be detectable in client-code via `MIN_VERSION_deepseq()`. >--------------------------------------------------------------- 6dc253b6797c638894658805290132cca5fdd889 deepseq.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/deepseq.cabal b/deepseq.cabal index a718551..ad07416 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -1,5 +1,5 @@ name: deepseq -version: 1.4.0.0 +version: 1.4.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE From git at git.haskell.org Thu Mar 19 11:36:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:03 +0000 (UTC) Subject: [commit: packages/filepath] master: Remove the really old GHC tests, no longer interesting (although no intention of breaking it) (ce186a2) Message-ID: <20150319113603.A66333A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/ce186a24e31adc6b35928ed4d23f204bf4ac42d4 >--------------------------------------------------------------- commit ce186a24e31adc6b35928ed4d23f204bf4ac42d4 Author: Neil Mitchell Date: Wed Oct 29 07:32:26 2014 +0000 Remove the really old GHC tests, no longer interesting (although no intention of breaking it) >--------------------------------------------------------------- ce186a24e31adc6b35928ed4d23f204bf4ac42d4 .travis.yml | 2 -- 1 file changed, 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 10b2f23..a41e51b 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,6 +1,4 @@ env: - - GHCVER=7.0.1 - - GHCVER=7.0.4 - GHCVER=7.2.2 - GHCVER=7.4.2 - GHCVER=7.6.3 From git at git.haskell.org Thu Mar 19 11:36:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:03 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Restore compatibility with base-4.3 (5077f36) Message-ID: <20150319113603.A438B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/5077f36c1422c70cf426b2466d12a3c5476040cc >--------------------------------------------------------------- commit 5077f36c1422c70cf426b2466d12a3c5476040cc Author: Herbert Valerio Riedel Date: Thu Jan 15 13:41:10 2015 +0100 Restore compatibility with base-4.3 This is fallout from de1bc89 >--------------------------------------------------------------- 5077f36c1422c70cf426b2466d12a3c5476040cc Control/DeepSeq.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index a732feb..31a42d7 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -291,7 +291,11 @@ instance (Integral a, NFData a) => NFData (Ratio a) where #endif rnf x = rnf (numerator x, denominator x) +#if MIN_VERSION_base(4,4,0) instance (NFData a) => NFData (Complex a) where +#else +instance (RealFloat a, NFData a) => NFData (Complex a) where +#endif rnf (x:+y) = rnf x `seq` rnf y `seq` () From git at git.haskell.org Thu Mar 19 11:36:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:05 +0000 (UTC) Subject: [commit: packages/filepath] master: Move to the neil standard test (61ba13a) Message-ID: <20150319113605.ACF343A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/61ba13a544583b9b4b7b535f4e289e2139005f57 >--------------------------------------------------------------- commit 61ba13a544583b9b4b7b535f4e289e2139005f57 Author: Neil Mitchell Date: Wed Oct 29 08:00:28 2014 +0000 Move to the neil standard test >--------------------------------------------------------------- 61ba13a544583b9b4b7b535f4e289e2139005f57 .travis.yml | 28 +--------------------------- 1 file changed, 1 insertion(+), 27 deletions(-) diff --git a/.travis.yml b/.travis.yml index a41e51b..8783444 100644 --- a/.travis.yml +++ b/.travis.yml @@ -9,31 +9,5 @@ matrix: allow_failures: - env: GHCVER=head -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-$GHCVER - - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/1.18/bin:$PATH - -install: - - cabal update - - cabal install --only-dependencies --enable-tests; - script: - - cabal configure --enable-tests -v2 - - cabal build - - cabal test - - cabal check - - cabal sdist - -# The following scriptlet checks that the resulting source distribution can be built & installed - - function install_from_tarball { - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; - if [ -f "dist/$SRC_TGZ" ]; then - cabal install "dist/$SRC_TGZ"; - else - echo "expected 'dist/$SRC_TGZ' not found"; - exit 1; - fi - } - - install_from_tarball + - wget https://raw.github.com/ndmitchell/neil/master/travis.sh -O - --no-check-certificate --quiet | sh From git at git.haskell.org Thu Mar 19 11:36:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:05 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Add changelog entry (re de1bc89) (63db1f3) Message-ID: <20150319113605.A95543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/63db1f329d3ba5f022f8da513b3f9f7e33df4c00 >--------------------------------------------------------------- commit 63db1f329d3ba5f022f8da513b3f9f7e33df4c00 Author: Herbert Valerio Riedel Date: Thu Jan 15 13:41:59 2015 +0100 Add changelog entry (re de1bc89) >--------------------------------------------------------------- 63db1f329d3ba5f022f8da513b3f9f7e33df4c00 changelog.md | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/changelog.md b/changelog.md index 75aaf8f..1e526b5 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,10 @@ # Changelog for [`deepseq` package](http://hackage.haskell.org/package/deepseq) +## 1.4.1.0 *TBA* + + * Drop redundant constraints from a few `NFData` instances (if + possible for a given `base` version) + ## 1.4.0.0 *Dec 2014* * Bundled with GHC 7.10.1 From git at git.haskell.org Thu Mar 19 11:36:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:07 +0000 (UTC) Subject: [commit: packages/filepath] master: Update the tested-with line to what we currently test against (ca4ca8f) Message-ID: <20150319113607.B3C6F3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/ca4ca8f5daf6a202fe0da9a04f1dadf6ff6fce43 >--------------------------------------------------------------- commit ca4ca8f5daf6a202fe0da9a04f1dadf6ff6fce43 Author: Neil Mitchell Date: Wed Oct 29 08:00:48 2014 +0000 Update the tested-with line to what we currently test against >--------------------------------------------------------------- ca4ca8f5daf6a202fe0da9a04f1dadf6ff6fce43 filepath.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/filepath.cabal b/filepath.cabal index ed836f3..e1d5615 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -12,7 +12,7 @@ category: System build-type: Simple synopsis: Library for manipulating FilePaths in a cross platform way. cabal-version: >=1.10 -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.2.1, GHC==7.0.4, GHC==7.0.3, GHC==7.0.2, GHC==7.0.1, GHC==6.12.3 +tested-with: GHC==7.8.3, GHC==7.6.3, GHC==7.4.2, GHC==7.2.2 description: This package provides functionality for manipulating @FilePath@ values, and is shipped with both and the . It provides three modules: . From git at git.haskell.org Thu Mar 19 11:36:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:07 +0000 (UTC) Subject: [commit: packages/deepseq] master, typeable-with-kinds: Update Travis-CI build-matrix (9e58024) Message-ID: <20150319113607.AFEC23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branches: master,typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/9e5802455dcd84d5b79c4a538be6ba1c8acbeea1 >--------------------------------------------------------------- commit 9e5802455dcd84d5b79c4a538be6ba1c8acbeea1 Author: Herbert Valerio Riedel Date: Thu Jan 15 13:43:13 2015 +0100 Update Travis-CI build-matrix >--------------------------------------------------------------- 9e5802455dcd84d5b79c4a538be6ba1c8acbeea1 .travis.yml | 34 ++++++++++++++++++---------------- 1 file changed, 18 insertions(+), 16 deletions(-) diff --git a/.travis.yml b/.travis.yml index 5028b91..82be4d5 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,23 +1,25 @@ env: - - GHCVER=7.0.1 CABALVER=1.16 - - GHCVER=7.0.2 CABALVER=1.16 - - GHCVER=7.0.3 CABALVER=1.16 - - GHCVER=7.0.4 CABALVER=1.16 - - GHCVER=7.2.1 CABALVER=1.16 - - GHCVER=7.2.2 CABALVER=1.16 - - GHCVER=7.4.1 CABALVER=1.16 - - GHCVER=7.4.2 CABALVER=1.16 - - GHCVER=7.6.1 CABALVER=1.16 - - GHCVER=7.6.2 CABALVER=1.16 - - GHCVER=7.6.3 CABALVER=1.16 - - GHCVER=7.8.1 CABALVER=1.18 - - GHCVER=7.8.2 CABALVER=1.18 - - GHCVER=7.8.3 CABALVER=1.18 - - GHCVER=head CABALVER=head + - CABALVER=1.16 GHCVER=7.0.1 + - CABALVER=1.16 GHCVER=7.0.2 + - CABALVER=1.16 GHCVER=7.0.3 + - CABALVER=1.16 GHCVER=7.0.4 + - CABALVER=1.16 GHCVER=7.2.1 + - CABALVER=1.16 GHCVER=7.2.2 + - CABALVER=1.16 GHCVER=7.4.1 + - CABALVER=1.16 GHCVER=7.4.2 + - CABALVER=1.16 GHCVER=7.6.1 + - CABALVER=1.16 GHCVER=7.6.2 + - CABALVER=1.16 GHCVER=7.6.3 + - CABALVER=1.18 GHCVER=7.8.1 + - CABALVER=1.18 GHCVER=7.8.2 + - CABALVER=1.18 GHCVER=7.8.3 + - CABALVER=1.18 GHCVER=7.8.4 + - CABALVER=1.22 GHCVER=7.10.1 + - CABALVER=head GHCVER=head matrix: allow_failures: - - env: GHCVER=head CABALVER=head + - env: CABALVER=head GHCVER=head before_install: - travis_retry sudo add-apt-repository -y ppa:hvr/ghc From git at git.haskell.org Thu Mar 19 11:36:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:09 +0000 (UTC) Subject: [commit: packages/filepath] master: Add a travis.hs script to ensure the generator ran (fa77022) Message-ID: <20150319113609.B9F223A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/fa7702211e2a69d0d4f4177dc2db3c624775fa46 >--------------------------------------------------------------- commit fa7702211e2a69d0d4f4177dc2db3c624775fa46 Author: Neil Mitchell Date: Wed Oct 29 08:01:04 2014 +0000 Add a travis.hs script to ensure the generator ran >--------------------------------------------------------------- fa7702211e2a69d0d4f4177dc2db3c624775fa46 travis.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/travis.hs b/travis.hs new file mode 100755 index 0000000..ae22fd2 --- /dev/null +++ b/travis.hs @@ -0,0 +1,4 @@ + +import System.Process.Extra + +main = system_ "runhaskell Generate" From git at git.haskell.org Thu Mar 19 11:36:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:09 +0000 (UTC) Subject: [commit: packages/deepseq] typeable-with-kinds: Update for new representation of TypeRep (c0794e1) Message-ID: <20150319113609.B5ABF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : typeable-with-kinds Link : http://git.haskell.org/packages/deepseq.git/commitdiff/c0794e1e84229bf61816c26f8f90b43488cd57c6 >--------------------------------------------------------------- commit c0794e1e84229bf61816c26f8f90b43488cd57c6 Author: Iavor S. Diatchki Date: Mon Feb 9 17:06:52 2015 -0800 Update for new representation of TypeRep >--------------------------------------------------------------- c0794e1e84229bf61816c26f8f90b43488cd57c6 Control/DeepSeq.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 31a42d7..207e19f 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -380,7 +380,7 @@ instance NFData Unique where -- -- /Since: 1.4.0.0/ instance NFData TypeRep where - rnf (TypeRep _ tycon tyrep) = rnf tycon `seq` rnf tyrep + rnf (TypeRep _ tycon kis tyrep) = rnf tycon `seq` rnf kis `seq` rnf tyrep -- | __NOTE__: Only defined for @base-4.8.0.0@ and later -- From git at git.haskell.org Thu Mar 19 11:36:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:11 +0000 (UTC) Subject: [commit: packages/filepath] master: Change the generator to write a file with Unix line endings on all platforms (1580b35) Message-ID: <20150319113611.C04E43A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/1580b35105a819f8127ce66bd9947532980ab678 >--------------------------------------------------------------- commit 1580b35105a819f8127ce66bd9947532980ab678 Author: Neil Mitchell Date: Wed Oct 29 08:02:59 2014 +0000 Change the generator to write a file with Unix line endings on all platforms >--------------------------------------------------------------- 1580b35105a819f8127ce66bd9947532980ab678 Generate.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/Generate.hs b/Generate.hs index 53ec8c6..7f956e7 100755 --- a/Generate.hs +++ b/Generate.hs @@ -16,7 +16,7 @@ isExpr _ = False main = do src <- readFile "System/FilePath/Internal.hs" let tests = concatMap getTest $ zip [1..] (lines src) - writeFile "tests/FilePath_Test.hs" (prefix ++ genTests tests) + writeFileBinary "tests/FilePath_Test.hs" (prefix ++ genTests tests) prefix = unlines ["import AutoTest" @@ -107,3 +107,6 @@ genTest (Test free x) = "quickSafe (\\" ++ concatMap ((' ':) . f) free ++ " -> ( where f [a] | a >= 'x' = "(QFilePath " ++ [a] ++ ")" f x = x + +writeFileBinary :: FilePath -> String -> IO () +writeFileBinary file x = withBinaryFile file WriteMode $ \h -> hPutStr h x From git at git.haskell.org Thu Mar 19 11:36:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:11 +0000 (UTC) Subject: [commit: packages/deepseq] master: Change TypeRep and TyCon instances to use new internal GHC utilities (5cbc7d1) Message-ID: <20150319113611.BC2DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/5cbc7d1c1d51838b5a147b3fb2d4b6f87b0eda09 >--------------------------------------------------------------- commit 5cbc7d1c1d51838b5a147b3fb2d4b6f87b0eda09 Author: Austin Seipp Date: Thu Mar 5 13:31:03 2015 -0600 Change TypeRep and TyCon instances to use new internal GHC utilities Signed-off-by: Austin Seipp >--------------------------------------------------------------- 5cbc7d1c1d51838b5a147b3fb2d4b6f87b0eda09 Control/DeepSeq.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 31a42d7..43edc0b 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -81,8 +81,7 @@ import Data.Proxy ( Proxy(Proxy) ) #if MIN_VERSION_base(4,8,0) import Data.Functor.Identity ( Identity(..) ) --- NB: Data.Typeable.Internal is "Trustworthy" only starting w/ base-4.8 -import Data.Typeable.Internal ( TypeRep(..), TyCon(..) ) +import Data.Typeable ( TypeRep, TyCon, rnfTypeRep, rnfTyCon ) import Data.Void ( Void, absurd ) import Numeric.Natural ( Natural ) #endif @@ -380,13 +379,13 @@ instance NFData Unique where -- -- /Since: 1.4.0.0/ instance NFData TypeRep where - rnf (TypeRep _ tycon tyrep) = rnf tycon `seq` rnf tyrep + rnf tyrep = rnfTypeRep tyrep -- | __NOTE__: Only defined for @base-4.8.0.0@ and later -- -- /Since: 1.4.0.0/ instance NFData TyCon where - rnf (TyCon _ tcp tcm tcn) = rnf tcp `seq` rnf tcm `seq` rnf tcn + rnf tycon = rnfTyCon tycon #endif ---------------------------------------------------------------------------- From git at git.haskell.org Thu Mar 19 11:36:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:13 +0000 (UTC) Subject: [commit: packages/directory] branch 'tmp' created Message-ID: <20150319113613.2B0633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory New branch : tmp Referencing: 5522a30b6c126d446600524d5c8b181ebdbc06bb From git at git.haskell.org Thu Mar 19 11:36:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:13 +0000 (UTC) Subject: [commit: packages/deepseq] master: Extend documentation of `force` with usage examples (beecf97) Message-ID: <20150319113613.C2D503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/beecf972eb35257396299818559d710c847e056a >--------------------------------------------------------------- commit beecf972eb35257396299818559d710c847e056a Author: Herbert Valerio Riedel Date: Sun Mar 8 12:00:47 2015 +0100 Extend documentation of `force` with usage examples >--------------------------------------------------------------- beecf972eb35257396299818559d710c847e056a Control/DeepSeq.hs | 20 ++++++++++++++++++++ 1 file changed, 20 insertions(+) diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 43edc0b..c39906e 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -159,6 +159,26 @@ f $!! x = x `deepseq` f x -- itself is demanded, so essentially it turns shallow evaluation into -- deep evaluation. -- +-- 'force' can be conveniently used in combination with @ViewPatterns@: +-- +-- > {-# LANGUAGE BangPatterns, ViewPatterns #-} +-- > import Control.DeepSeq +-- > +-- > someFun :: ComplexData -> SomeResult +-- > someFun (force -> !arg) = {- 'arg' will be fully evaluated -} +-- +-- Another useful application is to combine 'force' with +-- 'Control.Exception.evaluate' in order to force deep evaluation +-- relative to other 'IO' operations: +-- +-- > import Control.Exception (evaluate) +-- > import Control.DeepSeq +-- > +-- > main = do +-- > result <- evaluate $ force $ pureComputation +-- > {- 'result' will be fully evaluated at this point -} +-- > return () +-- -- /Since: 1.2.0.0/ force :: (NFData a) => a -> a force x = x `deepseq` x From git at git.haskell.org Thu Mar 19 11:36:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:13 +0000 (UTC) Subject: [commit: packages/filepath] master: Basic generator cleanups (909d6e6) Message-ID: <20150319113613.C6D8F3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/909d6e6bbf52700ac0813f8a65aad63b35202e2b >--------------------------------------------------------------- commit 909d6e6bbf52700ac0813f8a65aad63b35202e2b Author: Neil Mitchell Date: Wed Oct 29 08:04:26 2014 +0000 Basic generator cleanups >--------------------------------------------------------------- 909d6e6bbf52700ac0813f8a65aad63b35202e2b Generate.hs | 17 ++++++++++------- 1 file changed, 10 insertions(+), 7 deletions(-) diff --git a/Generate.hs b/Generate.hs index 7f956e7..8453818 100755 --- a/Generate.hs +++ b/Generate.hs @@ -1,22 +1,25 @@ -module Main where +module Generate(main) where import Data.Char import Data.List import System.IO -data Test = Expr String - | Test [String] String - deriving Show +data Test + = Expr String + | Test [String] String + deriving Show isExpr (Expr{}) = True isExpr _ = False -main = do src <- readFile "System/FilePath/Internal.hs" - let tests = concatMap getTest $ zip [1..] (lines src) - writeFileBinary "tests/FilePath_Test.hs" (prefix ++ genTests tests) +main :: IO () +main = do + src <- readFile "System/FilePath/Internal.hs" + let tests = concatMap getTest $ zip [1..] (lines src) + writeFileBinary "tests/FilePath_Test.hs" (prefix ++ genTests tests) prefix = unlines ["import AutoTest" From git at git.haskell.org Thu Mar 19 11:36:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:15 +0000 (UTC) Subject: [commit: packages/directory] branch 'improve-tests-for-real' created Message-ID: <20150319113615.2C20D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory New branch : improve-tests-for-real Referencing: 09747218f5b464db74dbad318c84a23783fd67b4 From git at git.haskell.org Thu Mar 19 11:36:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:15 +0000 (UTC) Subject: [commit: packages/filepath] master: Delete all the GHC test suite stuff, FilePath is now GHC test-suite free (567e386) Message-ID: <20150319113615.CE36D3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/567e386dd9817af6bacc1728e5ae0589e5d5d954 >--------------------------------------------------------------- commit 567e386dd9817af6bacc1728e5ae0589e5d5d954 Author: Neil Mitchell Date: Wed Oct 29 08:08:05 2014 +0000 Delete all the GHC test suite stuff, FilePath is now GHC test-suite free >--------------------------------------------------------------- 567e386dd9817af6bacc1728e5ae0589e5d5d954 tests/.gitignore | 12 --- tests/Makefile | 19 ---- tests/all.T | 10 -- tests/filepath.stdout | 287 -------------------------------------------------- 4 files changed, 328 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 567e386dd9817af6bacc1728e5ae0589e5d5d954 From git at git.haskell.org Thu Mar 19 11:36:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:15 +0000 (UTC) Subject: [commit: packages/deepseq] master: Update changelog for upcoming 1.4.1.0 release (56809c3) Message-ID: <20150319113615.C87D73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/56809c3e45c3a266564672b968817ca8b6d496c1 >--------------------------------------------------------------- commit 56809c3e45c3a266564672b968817ca8b6d496c1 Author: Herbert Valerio Riedel Date: Tue Mar 10 10:24:17 2015 +0100 Update changelog for upcoming 1.4.1.0 release >--------------------------------------------------------------- 56809c3e45c3a266564672b968817ca8b6d496c1 changelog.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md index 1e526b5..e21fb5d 100644 --- a/changelog.md +++ b/changelog.md @@ -1,13 +1,13 @@ # Changelog for [`deepseq` package](http://hackage.haskell.org/package/deepseq) -## 1.4.1.0 *TBA* +## 1.4.1.0 *Mar 2015* + * Bundled with GHC 7.10.1 * Drop redundant constraints from a few `NFData` instances (if possible for a given `base` version) ## 1.4.0.0 *Dec 2014* - * Bundled with GHC 7.10.1 * Switch to Generics based `DefaultSignature` `rnf` method implementation (based on code from `deepseq-generics`) From git at git.haskell.org Thu Mar 19 11:36:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:17 +0000 (UTC) Subject: [commit: packages/directory] branch 'improve-tests' created Message-ID: <20150319113617.2D0B43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory New branch : improve-tests Referencing: 8ae20b245786056aeeb8c20e2cb5992237aee2c3 From git at git.haskell.org Thu Mar 19 11:36:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:17 +0000 (UTC) Subject: [commit: packages/filepath] master: Rename FilePath_Test to Test (f4e568e) Message-ID: <20150319113617.D74743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/f4e568e3f4101d3325016e73cf9809d6b815d1da >--------------------------------------------------------------- commit f4e568e3f4101d3325016e73cf9809d6b815d1da Author: Neil Mitchell Date: Wed Oct 29 08:10:34 2014 +0000 Rename FilePath_Test to Test >--------------------------------------------------------------- f4e568e3f4101d3325016e73cf9809d6b815d1da Generate.hs | 2 +- filepath.cabal | 2 +- tests/{FilePath_Test.hs => Test.hs} | 0 3 files changed, 2 insertions(+), 2 deletions(-) diff --git a/Generate.hs b/Generate.hs index 8453818..52efebd 100755 --- a/Generate.hs +++ b/Generate.hs @@ -19,7 +19,7 @@ main :: IO () main = do src <- readFile "System/FilePath/Internal.hs" let tests = concatMap getTest $ zip [1..] (lines src) - writeFileBinary "tests/FilePath_Test.hs" (prefix ++ genTests tests) + writeFileBinary "tests/Test.hs" (prefix ++ genTests tests) prefix = unlines ["import AutoTest" diff --git a/filepath.cabal b/filepath.cabal index e1d5615..069ce29 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -49,7 +49,7 @@ library test-suite filepath-tests type: exitcode-stdio-1.0 default-language: Haskell98 - main-is: FilePath_Test.hs + main-is: Test.hs hs-source-dirs: tests other-modules: AutoTest build-depends: diff --git a/tests/FilePath_Test.hs b/tests/Test.hs similarity index 100% rename from tests/FilePath_Test.hs rename to tests/Test.hs From git at git.haskell.org Thu Mar 19 11:36:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:19 +0000 (UTC) Subject: [commit: packages/directory] tag 'v1.2.2.0' created Message-ID: <20150319113619.2E2823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory New tag : v1.2.2.0 Referencing: 82d895cdaa3513e8753bdf34ef1f3ecf7b889c58 From git at git.haskell.org Thu Mar 19 11:36:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:19 +0000 (UTC) Subject: [commit: packages/filepath] master: Load the generator into ghci (5dd2ad5) Message-ID: <20150319113619.DD1563A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/5dd2ad5fc39cdefb838f8abcbb5e5d080d7c9b78 >--------------------------------------------------------------- commit 5dd2ad5fc39cdefb838f8abcbb5e5d080d7c9b78 Author: Neil Mitchell Date: Wed Oct 29 08:21:47 2014 +0000 Load the generator into ghci >--------------------------------------------------------------- 5dd2ad5fc39cdefb838f8abcbb5e5d080d7c9b78 .ghci | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/.ghci b/.ghci index dc49947..f265108 100644 --- a/.ghci +++ b/.ghci @@ -1,10 +1,11 @@ :set -fwarn-unused-binds -fwarn-unused-imports :set -isrc -itest -:load System.FilePath System.FilePath.Windows System.FilePath.Posix +:load System.FilePath System.FilePath.Windows System.FilePath.Posix Generate import qualified System.FilePath.Windows as Windows import qualified System.FilePath.Posix as Posix :def docs_ const $ return $ unlines [":!cabal haddock"] :def docs const $ return $ unlines [":docs_",":!start dist\\doc\\html\\filepath\\System-FilePath.html"] +:def gen const $ return "Generate.main" :def test const $ return $ unlines [":!runhaskell Generate.hs",":!cabal test"] From git at git.haskell.org Thu Mar 19 11:36:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:21 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Fix incorrect comment about removeDirectoryRecursive and symlinks (db88005) Message-ID: <20150319113621.36B933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/db88005a736f88ac212152d69ce4002f4d852219/directory >--------------------------------------------------------------- commit db88005a736f88ac212152d69ce4002f4d852219 Author: Gracjan Polak Date: Fri Jun 6 17:03:34 2014 +0200 Fix incorrect comment about removeDirectoryRecursive and symlinks >--------------------------------------------------------------- db88005a736f88ac212152d69ce4002f4d852219 System/Directory.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/System/Directory.hs b/System/Directory.hs index 739892c..a7f85ad 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -460,9 +460,10 @@ removeDirectory path = #endif --- | @'removeDirectoryRecursive' dir@ removes an existing directory /dir/ --- together with its content and all subdirectories. Be careful, --- if the directory contains symlinks, the function will follow them. +-- | @'removeDirectoryRecursive' dir@ removes an existing directory +-- /dir/ together with its content and all subdirectories. If the +-- directory contains symlinks this function removes but does not +-- follow them. removeDirectoryRecursive :: FilePath -> IO () removeDirectoryRecursive startLoc = do cont <- getDirectoryContents startLoc From git at git.haskell.org Thu Mar 19 11:36:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:21 +0000 (UTC) Subject: [commit: packages/filepath] master: Use W and P for the qualifications in ghci, so its test suite compatible (09e2691) Message-ID: <20150319113621.E3EF53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/09e269191b9c98dc994920bfd9b74bdc36c8f54e >--------------------------------------------------------------- commit 09e269191b9c98dc994920bfd9b74bdc36c8f54e Author: Neil Mitchell Date: Wed Oct 29 08:22:04 2014 +0000 Use W and P for the qualifications in ghci, so its test suite compatible >--------------------------------------------------------------- 09e269191b9c98dc994920bfd9b74bdc36c8f54e .ghci | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.ghci b/.ghci index f265108..9f4d61b 100644 --- a/.ghci +++ b/.ghci @@ -1,8 +1,8 @@ :set -fwarn-unused-binds -fwarn-unused-imports :set -isrc -itest :load System.FilePath System.FilePath.Windows System.FilePath.Posix Generate -import qualified System.FilePath.Windows as Windows -import qualified System.FilePath.Posix as Posix +import qualified System.FilePath.Windows as W +import qualified System.FilePath.Posix as P :def docs_ const $ return $ unlines [":!cabal haddock"] :def docs const $ return $ unlines [":docs_",":!start dist\\doc\\html\\filepath\\System-FilePath.html"] From git at git.haskell.org Thu Mar 19 11:36:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:23 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Bump `base` constraint (2cb6678) Message-ID: <20150319113623.3E6FF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/2cb66787cc3599d5ded2b8c7f8b23bc7b152b58d/directory >--------------------------------------------------------------- commit 2cb66787cc3599d5ded2b8c7f8b23bc7b152b58d Author: Herbert Valerio Riedel Date: Tue Sep 9 16:31:37 2014 +0200 Bump `base` constraint >--------------------------------------------------------------- 2cb66787cc3599d5ded2b8c7f8b23bc7b152b58d changelog.md | 4 ++++ directory.cabal | 11 +++-------- 2 files changed, 7 insertions(+), 8 deletions(-) diff --git a/changelog.md b/changelog.md index 4796194..c361237 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,9 @@ # Changelog for [`directory` package](http://hackage.haskell.org/package/directory) +## 1.2.1.1 *TBA* + + * Bundled with GHC 7.10.1(?) + ## 1.2.1.0 *Mar 2014* * Bundled with GHC 7.8.1 diff --git a/directory.cabal b/directory.cabal index de282df..a4a0d44 100644 --- a/directory.cabal +++ b/directory.cabal @@ -1,6 +1,6 @@ name: directory -version: 1.2.1.0 --- GHC 7.6.3 released with 1.2.0.1 +version: 1.2.1.1 +-- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE maintainer: libraries at haskell.org @@ -33,11 +33,6 @@ source-repository head type: git location: http://git.haskell.org/packages/directory.git -source-repository this - type: git - location: http://git.haskell.org/packages/directory.git - tag: directory-1.2.0.2-release - Library default-language: Haskell2010 other-extensions: @@ -57,7 +52,7 @@ Library HsDirectory.h build-depends: - base >= 4.5 && < 4.8, + base >= 4.5 && < 4.9, time >= 1.4 && < 1.5, filepath >= 1.3 && < 1.4 if os(windows) From git at git.haskell.org Thu Mar 19 11:36:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:23 +0000 (UTC) Subject: [commit: packages/filepath] master: Simplify the :docs_ target (fdde77a) Message-ID: <20150319113623.E9A9C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/fdde77aacc0a458794c6791c1e30eb126f090157 >--------------------------------------------------------------- commit fdde77aacc0a458794c6791c1e30eb126f090157 Author: Neil Mitchell Date: Wed Oct 29 08:22:18 2014 +0000 Simplify the :docs_ target >--------------------------------------------------------------- fdde77aacc0a458794c6791c1e30eb126f090157 .ghci | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.ghci b/.ghci index 9f4d61b..60189f7 100644 --- a/.ghci +++ b/.ghci @@ -4,7 +4,7 @@ import qualified System.FilePath.Windows as W import qualified System.FilePath.Posix as P -:def docs_ const $ return $ unlines [":!cabal haddock"] +:def docs_ const $ return ":!cabal haddock" :def docs const $ return $ unlines [":docs_",":!start dist\\doc\\html\\filepath\\System-FilePath.html"] :def gen const $ return "Generate.main" From git at git.haskell.org Thu Mar 19 11:36:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:25 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Use import list for `Data.Time(.Clock.POSIX)` (5e3524b) Message-ID: <20150319113625.459313A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/5e3524b7567a1c5709efef9f76f561390ba6d723/directory >--------------------------------------------------------------- commit 5e3524b7567a1c5709efef9f76f561390ba6d723 Author: Herbert Valerio Riedel Date: Wed Sep 10 23:16:19 2014 +0200 Use import list for `Data.Time(.Clock.POSIX)` This makes it more obvious why `directory` depends on `time` in the first place, i.e. for the `UTCTime` and `POSIXTime` types, as well as for the `posixSecondsToUTCTime` conversion function between those two. >--------------------------------------------------------------- 5e3524b7567a1c5709efef9f76f561390ba6d723 System/Directory.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/System/Directory.hs b/System/Directory.hs index 739892c..203f4aa 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -95,8 +95,8 @@ import Foreign.C import Data.Maybe -import Data.Time -import Data.Time.Clock.POSIX +import Data.Time ( UTCTime ) +import Data.Time.Clock.POSIX ( POSIXTime, posixSecondsToUTCTime ) #ifdef __GLASGOW_HASKELL__ @@ -1041,7 +1041,7 @@ withFileOrSymlinkStatus loc name f = do modificationTime :: Ptr CStat -> IO UTCTime modificationTime stat = do mtime <- st_mtime stat - return $ posixSecondsToUTCTime $ realToFrac (mtime :: CTime) + return $ posixSecondsToUTCTime (realToFrac (mtime :: CTime) :: POSIXTime) isDirectory :: Ptr CStat -> IO Bool isDirectory stat = do From git at git.haskell.org Thu Mar 19 11:36:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:25 +0000 (UTC) Subject: [commit: packages/filepath] master: Change the generated file to be in module Test (c14bd97) Message-ID: <20150319113625.F0C8F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/c14bd978e59dd4c9564d253e8d56a5173432da8b >--------------------------------------------------------------- commit c14bd978e59dd4c9564d253e8d56a5173432da8b Author: Neil Mitchell Date: Wed Oct 29 08:27:15 2014 +0000 Change the generated file to be in module Test >--------------------------------------------------------------- c14bd978e59dd4c9564d253e8d56a5173432da8b Generate.hs | 4 +++- filepath.cabal | 4 +++- tests/Test.hs | 2 ++ 3 files changed, 8 insertions(+), 2 deletions(-) diff --git a/Generate.hs b/Generate.hs index 52efebd..48e88c6 100755 --- a/Generate.hs +++ b/Generate.hs @@ -22,9 +22,11 @@ main = do writeFileBinary "tests/Test.hs" (prefix ++ genTests tests) prefix = unlines - ["import AutoTest" + ["module Test(main) where" + ,"import AutoTest" ,"import qualified System.FilePath.Windows as W" ,"import qualified System.FilePath.Posix as P" + ,"main :: IO ()" ,"main = do" ] diff --git a/filepath.cabal b/filepath.cabal index 069ce29..70c4520 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -50,8 +50,10 @@ test-suite filepath-tests type: exitcode-stdio-1.0 default-language: Haskell98 main-is: Test.hs + ghc-options: -main-is Test hs-source-dirs: tests - other-modules: AutoTest + other-modules: + AutoTest build-depends: filepath, base, diff --git a/tests/Test.hs b/tests/Test.hs index bbad53c..c5fb57d 100755 --- a/tests/Test.hs +++ b/tests/Test.hs @@ -1,6 +1,8 @@ +module Test(main) where import AutoTest import qualified System.FilePath.Windows as W import qualified System.FilePath.Posix as P +main :: IO () main = do block1 block2 From git at git.haskell.org Thu Mar 19 11:36:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:27 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Relax upper bound to allow `time-1.5` (deb530a) Message-ID: <20150319113627.4EC7C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/deb530aa8a80214af6cf06e9b1ecc3390a5413dd/directory >--------------------------------------------------------------- commit deb530aa8a80214af6cf06e9b1ecc3390a5413dd Author: Herbert Valerio Riedel Date: Wed Sep 10 23:18:01 2014 +0200 Relax upper bound to allow `time-1.5` >--------------------------------------------------------------- deb530aa8a80214af6cf06e9b1ecc3390a5413dd directory.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/directory.cabal b/directory.cabal index a4a0d44..91cafb0 100644 --- a/directory.cabal +++ b/directory.cabal @@ -53,7 +53,7 @@ Library build-depends: base >= 4.5 && < 4.9, - time >= 1.4 && < 1.5, + time >= 1.4 && < 1.6, filepath >= 1.3 && < 1.4 if os(windows) build-depends: Win32 >= 2.2.2 && < 2.4 From git at git.haskell.org Thu Mar 19 11:36:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:28 +0000 (UTC) Subject: [commit: packages/filepath] master: Fix up the .ghci file so it loads the tests (ef49439) Message-ID: <20150319113628.047CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/ef494392c2a9c58dbef611ccfed89131df649426 >--------------------------------------------------------------- commit ef494392c2a9c58dbef611ccfed89131df649426 Author: Neil Mitchell Date: Wed Oct 29 08:28:02 2014 +0000 Fix up the .ghci file so it loads the tests >--------------------------------------------------------------- ef494392c2a9c58dbef611ccfed89131df649426 .ghci | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/.ghci b/.ghci index 60189f7..e9e1bba 100644 --- a/.ghci +++ b/.ghci @@ -1,6 +1,6 @@ :set -fwarn-unused-binds -fwarn-unused-imports -:set -isrc -itest -:load System.FilePath System.FilePath.Windows System.FilePath.Posix Generate +:set -isrc -itests +:load System.FilePath System.FilePath.Windows System.FilePath.Posix Generate Test import qualified System.FilePath.Windows as W import qualified System.FilePath.Posix as P @@ -8,4 +8,6 @@ import qualified System.FilePath.Posix as P :def docs const $ return $ unlines [":docs_",":!start dist\\doc\\html\\filepath\\System-FilePath.html"] :def gen const $ return "Generate.main" -:def test const $ return $ unlines [":!runhaskell Generate.hs",":!cabal test"] +:def test const $ return "Test.main" +:def go const $ return $ unlines [":reload",":gen",":reload",":test",":gen",":reload"] +:def testfull const $ return $ unlines [":reload","gen",":reload","!cabal test"] From git at git.haskell.org Thu Mar 19 11:36:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:29 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Update config.{guess, sub} to GNU automake 1.14.1 (3294737) Message-ID: <20150319113629.5829F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/329473730c36827f06358e137b469c59b490aaa8/directory >--------------------------------------------------------------- commit 329473730c36827f06358e137b469c59b490aaa8 Author: Herbert Valerio Riedel Date: Tue Sep 16 12:04:36 2014 +0200 Update config.{guess,sub} to GNU automake 1.14.1 >--------------------------------------------------------------- 329473730c36827f06358e137b469c59b490aaa8 config.guess | 192 +++++++++-------------------------------------------------- config.sub | 23 +++---- 2 files changed, 40 insertions(+), 175 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 329473730c36827f06358e137b469c59b490aaa8 From git at git.haskell.org Thu Mar 19 11:36:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:30 +0000 (UTC) Subject: [commit: packages/filepath] master: Remove missing imports from AutoTest (8c9ab52) Message-ID: <20150319113630.0A8BF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/8c9ab5252e93748dc9a6df874dfdea581534af4d >--------------------------------------------------------------- commit 8c9ab5252e93748dc9a6df874dfdea581534af4d Author: Neil Mitchell Date: Wed Oct 29 08:28:11 2014 +0000 Remove missing imports from AutoTest >--------------------------------------------------------------- 8c9ab5252e93748dc9a6df874dfdea581534af4d tests/AutoTest.hs | 3 --- 1 file changed, 3 deletions(-) diff --git a/tests/AutoTest.hs b/tests/AutoTest.hs index 00ddd30..2781543 100644 --- a/tests/AutoTest.hs +++ b/tests/AutoTest.hs @@ -6,10 +6,7 @@ module AutoTest( ) where import Test.QuickCheck hiding ((==>)) -import Data.Char -import System.Random import Data.List -import Control.Monad infixr 0 ==> a ==> b = not a || b From git at git.haskell.org Thu Mar 19 11:36:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:31 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Update Travis-CI badge (8740c74) Message-ID: <20150319113631.5FA763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/8740c7402381be5da5f32ed9819b9d0f20dab3eb/directory >--------------------------------------------------------------- commit 8740c7402381be5da5f32ed9819b9d0f20dab3eb Author: Herbert Valerio Riedel Date: Tue Sep 16 12:08:27 2014 +0200 Update Travis-CI badge >--------------------------------------------------------------- 8740c7402381be5da5f32ed9819b9d0f20dab3eb README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index e4d6e7f..07b0438 100644 --- a/README.md +++ b/README.md @@ -1,4 +1,4 @@ -The `directory` Package [![Build Status](https://travis-ci.org/ghc/packages-directory.png?branch=master)](https://travis-ci.org/ghc/packages-directory) +The `directory` Package [![Build Status](https://travis-ci.org/haskell/directory.svg?branch=master)](https://travis-ci.org/haskell/directory) ======================= See [`directory` on Hackage](http://hackage.haskell.org/package/directory) for From git at git.haskell.org Thu Mar 19 11:36:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:32 +0000 (UTC) Subject: [commit: packages/filepath] master: Rename AutoTest to TestUtil (e0684e9) Message-ID: <20150319113632.10FCA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/e0684e9e79f9fdcb8f719a442a905bbbe1fb06b3 >--------------------------------------------------------------- commit e0684e9e79f9fdcb8f719a442a905bbbe1fb06b3 Author: Neil Mitchell Date: Wed Oct 29 08:31:02 2014 +0000 Rename AutoTest to TestUtil >--------------------------------------------------------------- e0684e9e79f9fdcb8f719a442a905bbbe1fb06b3 Generate.hs | 2 +- filepath.cabal | 2 +- tests/Test.hs | 2 +- tests/{AutoTest.hs => TestUtil.hs} | 4 ++-- 4 files changed, 5 insertions(+), 5 deletions(-) diff --git a/Generate.hs b/Generate.hs index 48e88c6..9d7dcc0 100755 --- a/Generate.hs +++ b/Generate.hs @@ -23,7 +23,7 @@ main = do prefix = unlines ["module Test(main) where" - ,"import AutoTest" + ,"import TestUtil" ,"import qualified System.FilePath.Windows as W" ,"import qualified System.FilePath.Posix as P" ,"main :: IO ()" diff --git a/filepath.cabal b/filepath.cabal index 70c4520..fcd3f1b 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -53,7 +53,7 @@ test-suite filepath-tests ghc-options: -main-is Test hs-source-dirs: tests other-modules: - AutoTest + TestUtil build-depends: filepath, base, diff --git a/tests/Test.hs b/tests/Test.hs index c5fb57d..13b023b 100755 --- a/tests/Test.hs +++ b/tests/Test.hs @@ -1,5 +1,5 @@ module Test(main) where -import AutoTest +import TestUtil import qualified System.FilePath.Windows as W import qualified System.FilePath.Posix as P main :: IO () diff --git a/tests/AutoTest.hs b/tests/TestUtil.hs similarity index 96% rename from tests/AutoTest.hs rename to tests/TestUtil.hs index 2781543..acd91ec 100644 --- a/tests/AutoTest.hs +++ b/tests/TestUtil.hs @@ -1,6 +1,6 @@ -module AutoTest( - module AutoTest, +module TestUtil( + module TestUtil, module Test.QuickCheck, module Data.List ) where From git at git.haskell.org Thu Mar 19 11:36:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:33 +0000 (UTC) Subject: [commit: packages/process] branch 'wip/issue15' created Message-ID: <20150319113633.370713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process New branch : wip/issue15 Referencing: 5143c7895d9aeab37a7b72b416b855fe9c0cad87 From git at git.haskell.org Thu Mar 19 11:36:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:33 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Replace obsolete `defaultUserHooks` by `autoconfUserHooks` (bcb8c40) Message-ID: <20150319113633.6504A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/bcb8c40b5e0a17030bcc085b46bf8718ea713107/directory >--------------------------------------------------------------- commit bcb8c40b5e0a17030bcc085b46bf8718ea713107 Author: Herbert Valerio Riedel Date: Sat Sep 27 09:57:51 2014 +0200 Replace obsolete `defaultUserHooks` by `autoconfUserHooks` >--------------------------------------------------------------- bcb8c40b5e0a17030bcc085b46bf8718ea713107 Setup.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Setup.hs b/Setup.hs index 7cf9bfd..54f57d6 100644 --- a/Setup.hs +++ b/Setup.hs @@ -3,4 +3,4 @@ module Main (main) where import Distribution.Simple main :: IO () -main = defaultMainWithHooks defaultUserHooks +main = defaultMainWithHooks autoconfUserHooks From git at git.haskell.org Thu Mar 19 11:36:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:34 +0000 (UTC) Subject: [commit: packages/filepath] master: Ad a new Test module to sit in front of the generated tests, move the generate code to TestGen (c1a25a1) Message-ID: <20150319113634.1BD603A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/c1a25a1324876bdaf5990a8976501298298ae414 >--------------------------------------------------------------- commit c1a25a1324876bdaf5990a8976501298298ae414 Author: Neil Mitchell Date: Wed Oct 29 09:13:36 2014 +0000 Ad a new Test module to sit in front of the generated tests, move the generate code to TestGen >--------------------------------------------------------------- c1a25a1324876bdaf5990a8976501298298ae414 Generate.hs | 8 +- filepath.cabal | 1 + tests/Test.hs | 711 +----------------------------------------- tests/{Test.hs => TestGen.hs} | 6 +- 4 files changed, 13 insertions(+), 713 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c1a25a1324876bdaf5990a8976501298298ae414 From git at git.haskell.org Thu Mar 19 11:36:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:35 +0000 (UTC) Subject: [commit: packages/process] tag 'v1.2.3.0' created Message-ID: <20150319113635.382263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process New tag : v1.2.3.0 Referencing: 77527b3f9b577c7e1c92a4645f25ebe99ba051d1 From git at git.haskell.org Thu Mar 19 11:36:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:35 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Update Travis CI job (a872d1b) Message-ID: <20150319113635.6C9033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/a872d1bdfb79d4d51cc97e62a65d0703c07f0e29/directory >--------------------------------------------------------------- commit a872d1bdfb79d4d51cc97e62a65d0703c07f0e29 Author: Herbert Valerio Riedel Date: Sat Nov 1 11:54:09 2014 +0100 Update Travis CI job >--------------------------------------------------------------- a872d1bdfb79d4d51cc97e62a65d0703c07f0e29 .travis.yml | 42 ++++++++++++++++++++++++------------------ 1 file changed, 24 insertions(+), 18 deletions(-) diff --git a/.travis.yml b/.travis.yml index c62e226..ea01c3c 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,33 +1,39 @@ env: - - GHCVER=7.4.1 - - GHCVER=7.4.2 - - GHCVER=7.6.1 - - GHCVER=7.6.2 - - GHCVER=7.6.3 + # we have to use CABALVER=1.16 for GHC<7.6 as well, as there's + # no package for earlier cabal versions in the PPA + - GHCVER=7.4.1 CABALVER=1.16 + - GHCVER=7.4.2 CABALVER=1.16 + - GHCVER=7.6.3 CABALVER=1.16 + - GHCVER=7.8.3 CABALVER=1.18 + - GHCVER=head CABALVER=head + +matrix: + allow_failures: + - env: GHCVER=head CABALVER=head before_install: - - sudo add-apt-repository -y ppa:hvr/ghc - - sudo apt-get update - - sudo apt-get install cabal-install-1.18 ghc-$GHCVER autoconf - - export PATH=/opt/ghc/$GHCVER/bin:$PATH + - travis_retry sudo add-apt-repository -y ppa:hvr/ghc + - travis_retry sudo apt-get update + - travis_retry sudo apt-get install cabal-install-$CABALVER ghc-$GHCVER + - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH + - cabal --version install: - - cabal-1.18 update - - cabal-1.18 install --only-dependencies + - travis_retry cabal update + - cabal install --only-dependencies - ghc --version script: - autoreconf -i - - cabal-1.18 configure -v2 - - cabal-1.18 build - - cabal-1.18 check - - cabal-1.18 sdist - + - cabal configure -v2 + - cabal build + - cabal check + - cabal sdist # The following scriptlet checks that the resulting source distribution can be built & installed - - export SRC_TGZ=$(cabal-1.18 info . | awk '{print $2 ".tar.gz";exit}') ; + - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; cd dist/; if [ -f "$SRC_TGZ" ]; then - cabal-1.18 install "$SRC_TGZ"; + cabal install --force-reinstalls "$SRC_TGZ"; else echo "expected '$SRC_TGZ' not found"; exit 1; From git at git.haskell.org Thu Mar 19 11:36:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:36 +0000 (UTC) Subject: [commit: packages/filepath] master: Only write out a new generated file if it has changed (e8d126c) Message-ID: <20150319113636.22F663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/e8d126cf8bccd11e9361d372b05c9a6abcae5ed6 >--------------------------------------------------------------- commit e8d126cf8bccd11e9361d372b05c9a6abcae5ed6 Author: Neil Mitchell Date: Wed Oct 29 09:19:18 2014 +0000 Only write out a new generated file if it has changed >--------------------------------------------------------------- e8d126cf8bccd11e9361d372b05c9a6abcae5ed6 Generate.hs | 18 +++++++++++++++++- 1 file changed, 17 insertions(+), 1 deletion(-) diff --git a/Generate.hs b/Generate.hs index 0dee626..e228cbf 100755 --- a/Generate.hs +++ b/Generate.hs @@ -1,8 +1,11 @@ module Generate(main) where +import Control.Exception +import Control.Monad import Data.Char import Data.List +import System.Directory import System.IO @@ -19,7 +22,7 @@ main :: IO () main = do src <- readFile "System/FilePath/Internal.hs" let tests = concatMap getTest $ zip [1..] (lines src) - writeFileBinary "tests/TestGen.hs" (prefix ++ genTests tests) + writeFileBinaryChanged "tests/TestGen.hs" (prefix ++ genTests tests) prefix = unlines ["module TestGen(tests) where" @@ -115,3 +118,16 @@ genTest (Test free x) = "quickSafe (\\" ++ concatMap ((' ':) . f) free ++ " -> ( writeFileBinary :: FilePath -> String -> IO () writeFileBinary file x = withBinaryFile file WriteMode $ \h -> hPutStr h x + +readFileBinary' :: FilePath -> IO String +readFileBinary' file = withBinaryFile file ReadMode $ \h -> do + s <- hGetContents h + evaluate $ length s + return s + +writeFileBinaryChanged :: FilePath -> String -> IO () +writeFileBinaryChanged file x = do + b <- doesFileExist file + old <- if b then fmap Just $ readFileBinary' file else return Nothing + when (Just x /= old) $ + writeFileBinary file x From git at git.haskell.org Thu Mar 19 11:36:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:37 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: fix process010 test run on Solaris where false exits with status 255 (d9a9991) Message-ID: <20150319113637.40D853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/d9a999142f38e02dde45efa10bb7db25fb6e14bc/process >--------------------------------------------------------------- commit d9a999142f38e02dde45efa10bb7db25fb6e14bc Author: Karel Gardas Date: Sun Aug 3 00:04:43 2014 +0200 fix process010 test run on Solaris where false exits with status 255 >--------------------------------------------------------------- d9a999142f38e02dde45efa10bb7db25fb6e14bc tests/{process010.stdout => process010.stdout-i386-unknown-solaris2} | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/process010.stdout b/tests/process010.stdout-i386-unknown-solaris2 similarity index 88% copy from tests/process010.stdout copy to tests/process010.stdout-i386-unknown-solaris2 index 71b3f8e..316b23c 100644 --- a/tests/process010.stdout +++ b/tests/process010.stdout-i386-unknown-solaris2 @@ -1,4 +1,4 @@ ExitSuccess -ExitFailure 1 +ExitFailure 255 Exc: /non/existent: rawSystem: runInteractiveProcess: exec: does not exist (No such file or directory) Done From git at git.haskell.org Thu Mar 19 11:36:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:37 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Add Hackage-shield to README.md (69efcfc) Message-ID: <20150319113637.729B03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/69efcfcc092eff6e732085471722aeadf0e313ca/directory >--------------------------------------------------------------- commit 69efcfcc092eff6e732085471722aeadf0e313ca Author: Herbert Valerio Riedel Date: Sat Nov 1 12:00:19 2014 +0100 Add Hackage-shield to README.md [skip ci] >--------------------------------------------------------------- 69efcfcc092eff6e732085471722aeadf0e313ca README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 07b0438..2b1cedc 100644 --- a/README.md +++ b/README.md @@ -1,4 +1,4 @@ -The `directory` Package [![Build Status](https://travis-ci.org/haskell/directory.svg?branch=master)](https://travis-ci.org/haskell/directory) +The `directory` Package [![Hackage](https://img.shields.io/hackage/v/directory.svg)](https://hackage.haskell.org/package/directory) [![Build Status](https://travis-ci.org/haskell/directory.svg?branch=master)](https://travis-ci.org/haskell/directory) ======================= See [`directory` on Hackage](http://hackage.haskell.org/package/directory) for From git at git.haskell.org Thu Mar 19 11:36:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:38 +0000 (UTC) Subject: [commit: packages/filepath] master: Always generate test, and always use quickCheck even for constant values (71b6e67) Message-ID: <20150319113638.2BC243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/71b6e67b086911ebc4684ff108e9414cfa4b4dd8 >--------------------------------------------------------------- commit 71b6e67b086911ebc4684ff108e9414cfa4b4dd8 Author: Neil Mitchell Date: Wed Oct 29 09:22:44 2014 +0000 Always generate test, and always use quickCheck even for constant values >--------------------------------------------------------------- 71b6e67b086911ebc4684ff108e9414cfa4b4dd8 Generate.hs | 4 +- tests/TestGen.hs | 674 +++++++++++++++++++++++++++--------------------------- tests/TestUtil.hs | 10 +- 3 files changed, 341 insertions(+), 347 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 71b6e67b086911ebc4684ff108e9414cfa4b4dd8 From git at git.haskell.org Thu Mar 19 11:36:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:39 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Merge pull request #1 from kgardas/master (2911fbd) Message-ID: <20150319113639.48FCE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/2911fbd24147b8aaa3ad5cff720ee1d344bc3ed8/process >--------------------------------------------------------------- commit 2911fbd24147b8aaa3ad5cff720ee1d344bc3ed8 Merge: b39e340 d9a9991 Author: Gregory Collins Date: Mon Aug 11 09:08:07 2014 -0700 Merge pull request #1 from kgardas/master fix process010 test run on Solaris where false exits with status 255 >--------------------------------------------------------------- 2911fbd24147b8aaa3ad5cff720ee1d344bc3ed8 tests/{process010.stdout => process010.stdout-i386-unknown-solaris2} | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Thu Mar 19 11:36:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:39 +0000 (UTC) Subject: [commit: packages/directory] master: renameFile now consistently reports an error if the destination is a directory, as specified by documentation. (60667c8) Message-ID: <20150319113639.7D0AA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/60667c87b8a499a07e1ed0d578cf72dec9806cf7/directory >--------------------------------------------------------------- commit 60667c87b8a499a07e1ed0d578cf72dec9806cf7 Author: Gintautas Miliauskas Date: Mon Nov 3 19:49:04 2014 +0100 renameFile now consistently reports an error if the destination is a directory, as specified by documentation. Previously the exceptions raised would be quite inconsistent. For example, given a file 'f' and a directory 'd', on Linux, the simple case worked: Prelude System.Directory> renameFile "f" "d" *** Exception: f: rename: inappropriate type (Is a directory) however: Prelude System.Directory> renameFile "f" "d/" *** Exception: f: rename: inappropriate type (Not a directory) Prelude System.Directory> renameFile "f" "." *** Exception: e: rename: resource busy (Device or resource busy) Prelude System.Directory> renameFile "f" "/tmp" *** Exception: e: rename: unsatisified constraints (Directory not empty) Windows was inconsistent with the documentation even in the general case: Prelude System.Directory> renameFile "f" "d" *** Exception: f: MoveFileEx "f" "d": permission denied (Access is denied.) The additional check should not incur noticeable cost as an extra stat to check for a directory is only performed in case of an IO exception. I am not sure if this is actually the right abstraction level to fix these inconsistencies. Perhaps they should be pushed down to libraries/Win32, but the thing is, the Win32 documentation does not try to specify which errors are raised in which settings, but System.Directory does, and the implementation goes against the documentation, which seems wrong. >--------------------------------------------------------------- 60667c87b8a499a07e1ed0d578cf72dec9806cf7 System/Directory.hs | 39 +++++++++++++++++++++++---------------- tests/T8482.hs | 16 ++++++++++++++++ tests/T8482.stdout | 3 +++ tests/all.T | 1 + 4 files changed, 43 insertions(+), 16 deletions(-) diff --git a/System/Directory.hs b/System/Directory.hs index 203f4aa..14b89ff 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -638,24 +638,31 @@ Either path refers to an existing directory. renameFile :: FilePath -> FilePath -> IO () renameFile opath npath = do - -- XXX this test isn't performed atomically with the following rename -#ifdef mingw32_HOST_OS - -- ToDo: use Win32 API - withFileOrSymlinkStatus "renameFile" opath $ \st -> do - is_dir <- isDirectory st -#else - stat <- Posix.getSymbolicLinkStatus opath - let is_dir = Posix.isDirectory stat -#endif - if is_dir - then ioError (ioeSetErrorString - (mkIOError InappropriateType "renameFile" Nothing (Just opath)) - "is a directory") - else do + -- XXX the isDirectory tests are not performed atomically with the rename + checkNotDir opath + doRename `E.catch` renameExcHandler + where checkNotDir path = do + isdir <- pathIsDir path `E.catch` ((\ _ -> return False) :: IOException -> IO Bool) + when isdir $ dirIoError path + dirIoError path = ioError $ ioeSetErrorString (mkIOError InappropriateType "renameFile" Nothing (Just path)) "is a directory" + renameExcHandler :: IOException -> IO () + renameExcHandler exc = do + -- The underlying rename implementation throws odd exceptions + -- sometimes when the destination is a directory. For example, + -- Windows throws a permission error. In those cases check + -- if the cause is actually the destination being a directory + -- and throw InapprioriateType in that case. + checkNotDir npath + throw exc + doRename :: IO () + pathIsDir :: FilePath -> IO (Bool) #ifdef mingw32_HOST_OS - Win32.moveFileEx opath npath Win32.mOVEFILE_REPLACE_EXISTING + -- ToDo: use Win32 API + pathIsDir path = withFileOrSymlinkStatus "renameFile" path isDirectory + doRename = Win32.moveFileEx opath npath Win32.mOVEFILE_REPLACE_EXISTING #else - Posix.rename opath npath + pathIsDir path = Posix.isDirectory `fmap` Posix.getSymbolicLinkStatus path + doRename = Posix.rename opath npath #endif #endif /* __GLASGOW_HASKELL__ */ diff --git a/tests/T8482.hs b/tests/T8482.hs new file mode 100644 index 0000000..3bea8af --- /dev/null +++ b/tests/T8482.hs @@ -0,0 +1,16 @@ +import System.Directory +import Control.Exception + +tmp1 = "T8482.tmp1" +testdir = "T8482.dir" + +main = do + writeFile tmp1 "hello" + createDirectory testdir + tryRenameFile testdir tmp1 >>= print -- InappropriateType + tryRenameFile tmp1 testdir >>= print -- InappropriateType + tryRenameFile tmp1 "." >>= print -- InappropriateType + removeDirectory testdir + removeFile tmp1 + where tryRenameFile :: FilePath -> FilePath -> IO (Either IOException ()) + tryRenameFile opath npath = try $ renameFile opath npath diff --git a/tests/T8482.stdout b/tests/T8482.stdout new file mode 100644 index 0000000..277bc18 --- /dev/null +++ b/tests/T8482.stdout @@ -0,0 +1,3 @@ +Left T8482.dir: renameFile: inappropriate type (is a directory) +Left T8482.dir: renameFile: inappropriate type (is a directory) +Left .: renameFile: inappropriate type (is a directory) diff --git a/tests/all.T b/tests/all.T index 4efd688..ac6c909 100644 --- a/tests/all.T +++ b/tests/all.T @@ -27,3 +27,4 @@ test('createDirectoryIfMissing001', normal, compile_and_run, ['']) test('getHomeDirectory001', ignore_output, compile_and_run, ['']) test('T4113', when(platform('i386-apple-darwin'), expect_broken(7604)), compile_and_run, ['']) +test('T8482', normal, compile_and_run, ['']) From git at git.haskell.org Thu Mar 19 11:36:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:40 +0000 (UTC) Subject: [commit: packages/filepath] master: Remove the Expr constructor from the Generate module (259f9e2) Message-ID: <20150319113640.31C3A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/259f9e21e0cdacb8b44dcab01861b5fb12f87462 >--------------------------------------------------------------- commit 259f9e21e0cdacb8b44dcab01861b5fb12f87462 Author: Neil Mitchell Date: Wed Oct 29 09:27:20 2014 +0000 Remove the Expr constructor from the Generate module >--------------------------------------------------------------- 259f9e21e0cdacb8b44dcab01861b5fb12f87462 Generate.hs | 14 ++++---------- 1 file changed, 4 insertions(+), 10 deletions(-) diff --git a/Generate.hs b/Generate.hs index 274e1ca..c990a05 100755 --- a/Generate.hs +++ b/Generate.hs @@ -9,14 +9,9 @@ import System.Directory import System.IO -data Test - = Expr String - | Test [String] String +data Test = Test {testVars :: [String], _testBody :: String} deriving Show -isExpr (Expr{}) = True -isExpr _ = False - main :: IO () main = do @@ -41,7 +36,6 @@ getTest (line,xs) | "-- > " `isPrefixOf` xs = f $ drop 5 xs | "Posix:" `isPrefixOf` x = let res = grabTest (drop 6 x) in [g "P" res] | otherwise = let res = grabTest x in [g "W" res, g "P" res] - g p (Expr x) = (line,Expr (h p x)) g p (Test a x) = (line,Test a (h p x)) h p x = joinLex $ map (addPrefix p) $ makeValid $ splitLex x @@ -61,7 +55,7 @@ fpops = ["","<.>"] grabTest :: String -> Test -grabTest x = if null free then Expr x else Test free x +grabTest x = Test free x where free = sort $ nub [x | x <- lexs, length x == 1, all isAlpha x] lexs = splitLex x @@ -102,7 +96,7 @@ rejoinTests xs = unlines $ genTests :: [(Int, Test)] -> String genTests xs = rejoinTests $ concatMap f $ zip [1..] (one++many) where - (one,many) = partition (isExpr . snd) xs + (one,many) = partition (null . testVars . snd) xs f (tno,(lno,test)) = [" putStrLn \"Test " ++ show tno ++ ", from line " ++ show lno ++ "\"" @@ -110,7 +104,7 @@ genTests xs = rejoinTests $ concatMap f $ zip [1..] (one++many) -- the result must be a line of the type "IO ()" genTest :: Test -> String -genTest (Expr x) = "test (" ++ x ++ ")" +genTest (Test [] x) = "test (" ++ x ++ ")" genTest (Test free x) = "test (\\" ++ concatMap ((' ':) . f) free ++ " -> (" ++ x ++ "))" where f [a] | a >= 'x' = "(QFilePath " ++ [a] ++ ")" From git at git.haskell.org Thu Mar 19 11:36:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:41 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: make `getModificationTime` support sub-second resolution on windows (96327cd) Message-ID: <20150319113641.837063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/96327cd8d4c15396e93251a66535179ad81a7f22/directory >--------------------------------------------------------------- commit 96327cd8d4c15396e93251a66535179ad81a7f22 Author: Marios Titas Date: Fri Dec 19 19:11:24 2014 +0000 make `getModificationTime` support sub-second resolution on windows >--------------------------------------------------------------- 96327cd8d4c15396e93251a66535179ad81a7f22 System/Directory.hs | 36 +++++++++++++++++++----------------- 1 file changed, 19 insertions(+), 17 deletions(-) diff --git a/System/Directory.hs b/System/Directory.hs index 203f4aa..86135a5 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -96,7 +96,7 @@ import Foreign.C import Data.Maybe import Data.Time ( UTCTime ) -import Data.Time.Clock.POSIX ( POSIXTime, posixSecondsToUTCTime ) +import Data.Time.Clock.POSIX ( posixSecondsToUTCTime ) #ifdef __GLASGOW_HASKELL__ @@ -996,28 +996,35 @@ The operation may fail with: * 'isDoesNotExistError' if the file or directory does not exist. -Note: When linked against @unix-2.6.0.0@ or later the reported time -supports sub-second precision if provided by the underlying system -call. - +Note: This function returns a timestamp with sub-second resolution +only if this package is compiled against @unix-2.6.0.0@ or later +for unix systems, and @Win32-2.3.1.0@ or later for windows systems. +Of course this also requires that the underlying file system supports +such high resolution timestamps. -} getModificationTime :: FilePath -> IO UTCTime getModificationTime name = do #ifdef mingw32_HOST_OS - -- ToDo: use Win32 API so we can get sub-second resolution - withFileStatus "getModificationTime" name $ \ st -> do - modificationTime st +#if MIN_VERSION_Win32(2,3,1) + fad <- Win32.getFileAttributesExStandard name + let win32_epoch_adjust = 116444736000000000 + Win32.FILETIME ft = Win32.fadLastWriteTime fad + mod_time = fromIntegral (ft - win32_epoch_adjust) / 10000000 +#else + mod_time <- withFileStatus "getModificationTime" name $ \stat -> do + mtime <- st_mtime stat + return $ realToFrac (mtime :: CTime) +#endif #else stat <- Posix.getFileStatus name - let mod_time :: POSIXTime #if MIN_VERSION_unix(2,6,0) - mod_time = Posix.modificationTimeHiRes stat + let mod_time = Posix.modificationTimeHiRes stat #else - mod_time = realToFrac $ Posix.modificationTime stat + let mod_time = realToFrac $ Posix.modificationTime stat #endif - return $ posixSecondsToUTCTime mod_time #endif + return $ posixSecondsToUTCTime mod_time #endif /* __GLASGOW_HASKELL__ */ @@ -1038,11 +1045,6 @@ withFileOrSymlinkStatus loc name f = do throwErrnoIfMinus1Retry_ loc (lstat s p) f p -modificationTime :: Ptr CStat -> IO UTCTime -modificationTime stat = do - mtime <- st_mtime stat - return $ posixSecondsToUTCTime (realToFrac (mtime :: CTime) :: POSIXTime) - isDirectory :: Ptr CStat -> IO Bool isDirectory stat = do mode <- st_mode stat From git at git.haskell.org Thu Mar 19 11:36:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:41 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Merge remote-tracking branch 'git.haskell.org/master' into HEAD (262d86b) Message-ID: <20150319113641.50EE73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/262d86b6d15d2d3b37f772106f99b3fafc486551/process >--------------------------------------------------------------- commit 262d86b6d15d2d3b37f772106f99b3fafc486551 Merge: 2911fbd 35bf51c Author: Herbert Valerio Riedel Date: Mon Aug 25 09:33:25 2014 +0200 Merge remote-tracking branch 'git.haskell.org/master' into HEAD >--------------------------------------------------------------- 262d86b6d15d2d3b37f772106f99b3fafc486551 tests/.gitignore | 31 +++++++++++++++++++++++++++++++ 1 file changed, 31 insertions(+) From git at git.haskell.org Thu Mar 19 11:36:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:42 +0000 (UTC) Subject: [commit: packages/filepath] master: Cleanup: explicit is better than implicit (05f4f71) Message-ID: <20150319113642.38E583A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/05f4f71ba731a94081f4904ac15b6d96ca6e1d8a >--------------------------------------------------------------- commit 05f4f71ba731a94081f4904ac15b6d96ca6e1d8a Author: Thomas Miedema Date: Fri Oct 31 23:50:04 2014 +0100 Cleanup: explicit is better than implicit >--------------------------------------------------------------- 05f4f71ba731a94081f4904ac15b6d96ca6e1d8a System/FilePath/Internal.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 8f2c51b..bd02ddd 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -807,7 +807,7 @@ isValid _ | isPosix = True isValid path = not (any (`elem` badCharacters) x2) && not (any f $ splitDirectories x2) && - not (length x1 >= 2 && all isPathSeparator x1) && + not (isJust (readDriveShare x1) && all isPathSeparator x1) && not (isJust (readDriveUNC x1) && not (hasTrailingPathSeparator x1)) where (x1,x2) = splitDrive path @@ -832,7 +832,7 @@ makeValid :: FilePath -> FilePath makeValid "" = "_" makeValid path | isPosix = path - | length drv >= 2 && all isPathSeparator drv = take 2 drv ++ "drive" + | isJust (readDriveShare drv) && all isPathSeparator drv = take 2 drv ++ "drive" | isJust (readDriveUNC drv) && not (hasTrailingPathSeparator drv) = makeValid (drv ++ [pathSeparator] ++ pth) | otherwise = joinDrive drv $ validElements $ validChars pth From git at git.haskell.org Thu Mar 19 11:36:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:43 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Bump `base` constraint and convert changelog to MD (ec5df5c) Message-ID: <20150319113643.57EEB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/ec5df5c5752e1cfa02d13685d912a26809ce6c81/process >--------------------------------------------------------------- commit ec5df5c5752e1cfa02d13685d912a26809ce6c81 Author: Herbert Valerio Riedel Date: Tue Sep 9 17:23:11 2014 +0200 Bump `base` constraint and convert changelog to MD >--------------------------------------------------------------- ec5df5c5752e1cfa02d13685d912a26809ce6c81 changelog | 15 --------------- changelog.md | 21 +++++++++++++++++++++ process.cabal | 15 +++++---------- 3 files changed, 26 insertions(+), 25 deletions(-) diff --git a/changelog b/changelog deleted file mode 100644 index 1409eea..0000000 --- a/changelog +++ /dev/null @@ -1,15 +0,0 @@ -1.2.0.0 Dec 2013 - - * Update to Cabal 1.10 format - * Remove NHC specific code - * Add support for `base-4.7.0.0` - * Improve `showCommandForUser` to reduce redundant quoting - * New functions `callProcess`, `callCommand`, `spawnProcess` and `spawnCommand` - * Implement WCE handling according to http://www.cons.org/cracauer/sigint.html - * New `delegate_ctlc` field in `CreateProcess` for WCE handling - * Use `ExitFailure (-signum)` on Unix when a proc is terminated due to - a signal. - * Deprecate `module System.Cmd` - * On non-Windows, the child thread now comunicates any errors back - to the parent thread via pipes. - * Fix deadlocks in `readProcess` and `readProcessWithExitCode` diff --git a/changelog.md b/changelog.md new file mode 100644 index 0000000..b361dea --- /dev/null +++ b/changelog.md @@ -0,0 +1,21 @@ +# Changelog for [`process` package](http://hackage.haskell.org/package/process) + +## 1.2.0.1 *TBA* + + * Add support for `base-4.8.0.0` + +## 1.2.0.0 *Dec 2013* + + * Update to Cabal 1.10 format + * Remove NHC specific code + * Add support for `base-4.7.0.0` + * Improve `showCommandForUser` to reduce redundant quoting + * New functions `callProcess`, `callCommand`, `spawnProcess` and `spawnCommand` + * Implement WCE handling according to http://www.cons.org/cracauer/sigint.html + * New `delegate_ctlc` field in `CreateProcess` for WCE handling + * Use `ExitFailure (-signum)` on Unix when a proc is terminated due to + a signal. + * Deprecate `module System.Cmd` + * On non-Windows, the child thread now comunicates any errors back + to the parent thread via pipes. + * Fix deadlocks in `readProcess` and `readProcessWithExitCode` diff --git a/process.cabal b/process.cabal index e8d07b5..fef761c 100644 --- a/process.cabal +++ b/process.cabal @@ -1,10 +1,10 @@ name: process -version: 1.2.0.0 --- GHC 7.6.1 released with 1.1.0.2 +version: 1.2.0.1 +-- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE maintainer: libraries at haskell.org -bug-reports: http://ghc.haskell.org/trac/ghc/newticket?component=libraries/process +bug-reports: https://github.com/haskell/process/issues synopsis: Process libraries category: System build-type: Configure @@ -28,12 +28,7 @@ extra-tmp-files: source-repository head type: git - location: http://git.haskell.org/packages/process.git - -source-repository this - type: git - location: http://git.haskell.org/packages/process.git - tag: process-1.2.0.0-release + location: https://github.com/haskell/process.git library default-language: Haskell2010 @@ -62,7 +57,7 @@ library ghc-options: -Wall - build-depends: base >= 4.4 && < 4.8, + build-depends: base >= 4.4 && < 4.9, directory >= 1.1 && < 1.3, filepath >= 1.2 && < 1.4, deepseq >= 1.1 && < 1.4 From git at git.haskell.org Thu Mar 19 11:36:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:43 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Merge pull request #11 from redneb/win32-hi-res-mtime (1d2c3b9) Message-ID: <20150319113643.8ADA33A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/1d2c3b9039ba32d48d1629146cd418db106317e1/directory >--------------------------------------------------------------- commit 1d2c3b9039ba32d48d1629146cd418db106317e1 Merge: 69efcfc 96327cd Author: Herbert Valerio Riedel Date: Fri Dec 19 21:23:39 2014 +0100 Merge pull request #11 from redneb/win32-hi-res-mtime make `getModificationTime` support sub-second resolution on windows >--------------------------------------------------------------- 1d2c3b9039ba32d48d1629146cd418db106317e1 System/Directory.hs | 36 +++++++++++++++++++----------------- 1 file changed, 19 insertions(+), 17 deletions(-) From git at git.haskell.org Thu Mar 19 11:36:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:44 +0000 (UTC) Subject: [commit: packages/filepath] master: Add 'Valid x =>' to splitExtension(s) QuickCheck property (#34) (d05cbe9) Message-ID: <20150319113644.40BF63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/d05cbe90e5d74e30aa3544a4e3d37b3c8170d71a >--------------------------------------------------------------- commit d05cbe90e5d74e30aa3544a4e3d37b3c8170d71a Author: Thomas Miedema Date: Fri Oct 31 23:52:26 2014 +0100 Add 'Valid x =>' to splitExtension(s) QuickCheck property (#34) >--------------------------------------------------------------- d05cbe90e5d74e30aa3544a4e3d37b3c8170d71a System/FilePath/Internal.hs | 4 ++-- tests/TestGen.hs | 8 ++++---- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index bd02ddd..2487167 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -202,7 +202,7 @@ getSearchPath = fmap splitSearchPath (getEnv "PATH") -- | Split on the extension. 'addExtension' is the inverse. -- -- > uncurry (++) (splitExtension x) == x --- > uncurry addExtension (splitExtension x) == x +-- > Valid x => uncurry addExtension (splitExtension x) == x -- > splitExtension "file.txt" == ("file",".txt") -- > splitExtension "file" == ("file","") -- > splitExtension "file/file.txt" == ("file/file",".txt") @@ -274,7 +274,7 @@ hasExtension = any isExtSeparator . takeFileName -- | Split on all extensions -- -- > uncurry (++) (splitExtensions x) == x --- > uncurry addExtension (splitExtensions x) == x +-- > Valid x => uncurry addExtension (splitExtensions x) == x -- > splitExtensions "file.tar.gz" == ("file",".tar.gz") splitExtensions :: FilePath -> (FilePath, String) splitExtensions x = (a ++ c, d) diff --git a/tests/TestGen.hs b/tests/TestGen.hs index 378b9f0..b2c5457 100755 --- a/tests/TestGen.hs +++ b/tests/TestGen.hs @@ -536,9 +536,9 @@ block11 = do putStrLn "Test 253, from line 204" test (\ (QFilePath x) -> (uncurry ( ++ ) ( P.splitExtension x ) == x)) putStrLn "Test 254, from line 205" - test (\ (QFilePath x) -> (uncurry W.addExtension ( W.splitExtension x ) == x)) + test (\ (QFilePath x) -> ((\ x -> uncurry W.addExtension ( W.splitExtension x ) == x ) ( W.makeValid x ))) putStrLn "Test 255, from line 205" - test (\ (QFilePath x) -> (uncurry P.addExtension ( P.splitExtension x ) == x)) + test (\ (QFilePath x) -> ((\ x -> uncurry P.addExtension ( P.splitExtension x ) == x ) ( P.makeValid x ))) putStrLn "Test 256, from line 223" test (\ (QFilePath x) -> (W.takeExtension x == snd ( W.splitExtension x ))) putStrLn "Test 257, from line 223" @@ -568,9 +568,9 @@ block11 = do putStrLn "Test 269, from line 276" test (\ (QFilePath x) -> (uncurry ( ++ ) ( P.splitExtensions x ) == x)) putStrLn "Test 270, from line 277" - test (\ (QFilePath x) -> (uncurry W.addExtension ( W.splitExtensions x ) == x)) + test (\ (QFilePath x) -> ((\ x -> uncurry W.addExtension ( W.splitExtensions x ) == x ) ( W.makeValid x ))) putStrLn "Test 271, from line 277" - test (\ (QFilePath x) -> (uncurry P.addExtension ( P.splitExtensions x ) == x)) + test (\ (QFilePath x) -> ((\ x -> uncurry P.addExtension ( P.splitExtensions x ) == x ) ( P.makeValid x ))) putStrLn "Test 272, from line 287" test (\ (QFilePath x) -> (not $ W.hasExtension ( W.dropExtensions x ))) putStrLn "Test 273, from line 287" From git at git.haskell.org Thu Mar 19 11:36:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:45 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Replace obsolete `defaultUserHooks` by `autoconfUserHooks` (7b3ede7) Message-ID: <20150319113645.5E8863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/7b3ede7dbbb2de80b906c76f747d0b3196c4669a/process >--------------------------------------------------------------- commit 7b3ede7dbbb2de80b906c76f747d0b3196c4669a Author: Herbert Valerio Riedel Date: Sat Sep 27 09:54:36 2014 +0200 Replace obsolete `defaultUserHooks` by `autoconfUserHooks` >--------------------------------------------------------------- 7b3ede7dbbb2de80b906c76f747d0b3196c4669a Setup.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Setup.hs b/Setup.hs index 7cf9bfd..54f57d6 100644 --- a/Setup.hs +++ b/Setup.hs @@ -3,4 +3,4 @@ module Main (main) where import Distribution.Simple main :: IO () -main = defaultMainWithHooks defaultUserHooks +main = defaultMainWithHooks autoconfUserHooks From git at git.haskell.org Thu Mar 19 11:36:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:45 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Prepare for upcoming release (e22771f) Message-ID: <20150319113645.915C73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/e22771f4e9fbd30b2ed4af75cf4b19b9e4e94c7c/directory >--------------------------------------------------------------- commit e22771f4e9fbd30b2ed4af75cf4b19b9e4e94c7c Author: Herbert Valerio Riedel Date: Fri Dec 19 21:26:38 2014 +0100 Prepare for upcoming release >--------------------------------------------------------------- e22771f4e9fbd30b2ed4af75cf4b19b9e4e94c7c changelog.md | 6 ++++-- directory.cabal | 2 +- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/changelog.md b/changelog.md index c361237..c7213cd 100644 --- a/changelog.md +++ b/changelog.md @@ -1,8 +1,10 @@ # Changelog for [`directory` package](http://hackage.haskell.org/package/directory) -## 1.2.1.1 *TBA* +## 1.2.1.1 *Dec 2014* - * Bundled with GHC 7.10.1(?) + * Bundled with GHC 7.10.1 + + * make `getModificationTime` support sub-second resolution on windows ## 1.2.1.0 *Mar 2014* diff --git a/directory.cabal b/directory.cabal index 91cafb0..5736d90 100644 --- a/directory.cabal +++ b/directory.cabal @@ -11,7 +11,7 @@ description: category: System build-type: Configure cabal-version: >= 1.10 -tested-with: GHC==7.6.3, GHC==7.6.2, GHC==7.6.1, GHC==7.4.2, GHC==7.4.1 +tested-with: GHC>=7.4.1 extra-tmp-files: autom4te.cache From git at git.haskell.org Thu Mar 19 11:36:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:46 +0000 (UTC) Subject: [commit: packages/filepath] master: Refactor: don't use reverse explicitly (#6) (881afa5) Message-ID: <20150319113646.46FDF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/881afa569b02769ef33f798d2c78d97f902bfa6a >--------------------------------------------------------------- commit 881afa569b02769ef33f798d2c78d97f902bfa6a Author: Thomas Miedema Date: Sat Nov 1 13:32:37 2014 +0100 Refactor: don't use reverse explicitly (#6) I couldn't decide between the different implementations of dropWhileEnd and takeWhileEnd from https://ghc.haskell.org/trac/ghc/ticket/9623#comment:7, so I choose the simplest solution using two times reverse instead of foldr. See also: https://www.haskell.org/pipermail/libraries/2014-September/023835.html >--------------------------------------------------------------- 881afa569b02769ef33f798d2c78d97f902bfa6a System/FilePath/Internal.hs | 35 +++++++++++++++++++++++++++-------- 1 file changed, 27 insertions(+), 8 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 2487167..bef907a 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -211,12 +211,12 @@ getSearchPath = fmap splitSearchPath (getEnv "PATH") -- > splitExtension "file/path.txt.bob.fred" == ("file/path.txt.bob",".fred") -- > splitExtension "file/path.txt/" == ("file/path.txt/","") splitExtension :: FilePath -> (String, String) -splitExtension x = case d of +splitExtension x = case nameDot of "" -> (x,"") - (y:ys) -> (a ++ reverse ys, y : reverse c) + _ -> (dir ++ init nameDot, extSeparator : ext) where - (a,b) = splitFileName_ x - (c,d) = break isExtSeparator $ reverse b + (dir,file) = splitFileName_ x + (nameDot,ext) = breakEnd isExtSeparator file -- | Get the extension of a file, returns @\"\"@ for no extension, @.ext@ otherwise. -- @@ -444,10 +444,10 @@ splitFileName x = (if null dir then "./" else dir, name) -- look strange and upset simple equality properties. See -- e.g. replaceFileName. splitFileName_ :: FilePath -> (String, String) -splitFileName_ x = (c ++ reverse b, reverse a) +splitFileName_ x = (drv ++ dir, file) where - (a,b) = break isPathSeparator $ reverse d - (c,d) = splitDrive x + (drv,pth) = splitDrive x + (dir,file) = breakEnd isPathSeparator pth -- | Set the filename. -- @@ -528,7 +528,7 @@ addTrailingPathSeparator x = if hasTrailingPathSeparator x then x else x ++ [pat dropTrailingPathSeparator :: FilePath -> FilePath dropTrailingPathSeparator x = if hasTrailingPathSeparator x && not (isDrive x) - then let x' = reverse $ dropWhile isPathSeparator $ reverse x + then let x' = dropWhileEnd isPathSeparator x in if null x' then [last x] else x' else x @@ -891,3 +891,22 @@ isRelativeDrive x = -- > isAbsolute x == not (isRelative x) isAbsolute :: FilePath -> Bool isAbsolute = not . isRelative + + +----------------------------------------------------------------------------- +-- dropWhileEnd (>2) [1,2,3,4,1,2,3,4] == [1,2,3,4,1,2]) +-- Note that Data.List.dropWhileEnd is only available in base >= 4.5. +dropWhileEnd :: (a -> Bool) -> [a] -> [a] +dropWhileEnd p = reverse . dropWhile p . reverse + +-- takeWhileEnd (>2) [1,2,3,4,1,2,3,4] == [3,4]) +takeWhileEnd :: (a -> Bool) -> [a] -> [a] +takeWhileEnd p = reverse . takeWhile p . reverse + +-- spanEnd (>2) [1,2,3,4,1,2,3,4] = ([1,2,3,4,1,2], [3,4]) +spanEnd :: (a -> Bool) -> [a] -> ([a], [a]) +spanEnd p xs = (dropWhileEnd p xs, takeWhileEnd p xs) + +-- breakEnd (< 2) [1,2,3,4,1,2,3,4] == ([1,2,3,4,1],[2,3,4]) +breakEnd :: (a -> Bool) -> [a] -> ([a], [a]) +breakEnd p = spanEnd (not . p) From git at git.haskell.org Thu Mar 19 11:36:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:47 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Fix cabal file referencing old changelog name (e4d2168) Message-ID: <20150319113647.6472D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/e4d2168b1ee55699bf2202e5dc6cb3945bdf09cd/process >--------------------------------------------------------------- commit e4d2168b1ee55699bf2202e5dc6cb3945bdf09cd Author: Herbert Valerio Riedel Date: Sat Nov 1 08:56:26 2014 +0100 Fix cabal file referencing old changelog name >--------------------------------------------------------------- e4d2168b1ee55699bf2202e5dc6cb3945bdf09cd process.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/process.cabal b/process.cabal index fef761c..0afdca7 100644 --- a/process.cabal +++ b/process.cabal @@ -14,7 +14,7 @@ description: extra-source-files: aclocal.m4 - changelog + changelog.md configure configure.ac include/HsProcessConfig.h.in From git at git.haskell.org Thu Mar 19 11:36:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:47 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Belated bump to 1.2.2.0 (406b933) Message-ID: <20150319113647.96AB63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/406b93306ce464b67d7b3aca86673964d49bd4ce/directory >--------------------------------------------------------------- commit 406b93306ce464b67d7b3aca86673964d49bd4ce Author: Herbert Valerio Riedel Date: Thu Jan 15 14:02:43 2015 +0100 Belated bump to 1.2.2.0 Version 1.2.1.1 was never officially released, and it's better to use a minor version bump for the `getModificationTime` change, so client-code has a chance of detecting this (minor) semantic change via `MIN_VERSION_directory()`. >--------------------------------------------------------------- 406b93306ce464b67d7b3aca86673964d49bd4ce changelog.md | 2 +- directory.cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md index c7213cd..6891d2f 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`directory` package](http://hackage.haskell.org/package/directory) -## 1.2.1.1 *Dec 2014* +## 1.2.2.0 *Jan 2014* * Bundled with GHC 7.10.1 diff --git a/directory.cabal b/directory.cabal index 5736d90..69266c6 100644 --- a/directory.cabal +++ b/directory.cabal @@ -1,5 +1,5 @@ name: directory -version: 1.2.1.1 +version: 1.2.2.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE From git at git.haskell.org Thu Mar 19 11:36:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:48 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge pull request #35 from thomie/splitExtensions (7ab78f9) Message-ID: <20150319113648.4FE233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/7ab78f9592673ee4a18c7796a3657488df280ef7 >--------------------------------------------------------------- commit 7ab78f9592673ee4a18c7796a3657488df280ef7 Merge: 259f9e2 881afa5 Author: Neil Mitchell Date: Sat Nov 1 13:08:40 2014 +0000 Merge pull request #35 from thomie/splitExtensions Refactor and fix test for splitExtension(s) >--------------------------------------------------------------- 7ab78f9592673ee4a18c7796a3657488df280ef7 System/FilePath/Internal.hs | 43 +++++++++++++++++++++++++++++++------------ tests/TestGen.hs | 8 ++++---- 2 files changed, 35 insertions(+), 16 deletions(-) From git at git.haskell.org Thu Mar 19 11:36:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:49 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Update Travis CI Job (101a7f5) Message-ID: <20150319113649.6CA573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/101a7f5bb1f8416555f9066a3aef0a5b6a8d1e2b/process >--------------------------------------------------------------- commit 101a7f5bb1f8416555f9066a3aef0a5b6a8d1e2b Author: Herbert Valerio Riedel Date: Sat Nov 1 08:54:25 2014 +0100 Update Travis CI Job >--------------------------------------------------------------- 101a7f5bb1f8416555f9066a3aef0a5b6a8d1e2b .travis.yml | 45 +++++++++++++++++++++++++-------------------- 1 file changed, 25 insertions(+), 20 deletions(-) diff --git a/.travis.yml b/.travis.yml index 17b5adf..ddb661a 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,35 +1,40 @@ env: - - GHCVER=7.2.1 - - GHCVER=7.2.2 - - GHCVER=7.4.1 - - GHCVER=7.4.2 - - GHCVER=7.6.1 - - GHCVER=7.6.2 - - GHCVER=7.6.3 + - GHCVER=7.2.1 CABALVER=1.16 + - GHCVER=7.2.2 CABALVER=1.16 + - GHCVER=7.4.2 CABALVER=1.16 + # we have to use CABALVER=1.16 for GHC<7.6 as well, as there's + # no package for earlier cabal versions in the PPA + - GHCVER=7.6.3 CABALVER=1.16 + - GHCVER=7.8.3 CABALVER=1.18 + - GHCVER=head CABALVER=head + +matrix: + allow_failures: + - env: GHCVER=head CABALVER=head before_install: - - sudo add-apt-repository -y ppa:hvr/ghc - - sudo apt-get update - - sudo apt-get install cabal-install-1.18 ghc-$GHCVER autoconf - - export PATH=/opt/ghc/$GHCVER/bin:$PATH + - travis_retry sudo add-apt-repository -y ppa:hvr/ghc + - travis_retry sudo apt-get update + - travis_retry sudo apt-get install cabal-install-$CABALVER ghc-$GHCVER + - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH + - cabal --version install: - - cabal-1.18 update - - cabal-1.18 install --only-dependencies + - travis_retry cabal update + - cabal install --only-dependencies - ghc --version script: - autoreconf -i - - cabal-1.18 configure -v2 - - cabal-1.18 build - - cabal-1.18 check - - cabal-1.18 sdist - + - cabal configure -v2 + - cabal build + - cabal check || [ "$CABALVER" == "1.16" ] + - cabal sdist # The following scriptlet checks that the resulting source distribution can be built & installed - - export SRC_TGZ=$(cabal-1.18 info . | awk '{print $2 ".tar.gz";exit}') ; + - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; cd dist/; if [ -f "$SRC_TGZ" ]; then - cabal-1.18 install "$SRC_TGZ"; + cabal install --force-reinstalls "$SRC_TGZ"; else echo "expected '$SRC_TGZ' not found"; exit 1; From git at git.haskell.org Thu Mar 19 11:36:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:49 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Merge pull request #1 from gracjan/master (c43340d) Message-ID: <20150319113649.9F2983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/c43340dc29874c80570a7295d5d4c93756b4bc03/directory >--------------------------------------------------------------- commit c43340dc29874c80570a7295d5d4c93756b4bc03 Merge: 406b933 db88005 Author: Herbert Valerio Riedel Date: Fri Jan 16 17:28:33 2015 +0100 Merge pull request #1 from gracjan/master Fix incorrect comment about removeDirectoryRecursive and symlinks >--------------------------------------------------------------- c43340dc29874c80570a7295d5d4c93756b4bc03 System/Directory.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) From git at git.haskell.org Thu Mar 19 11:36:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:50 +0000 (UTC) Subject: [commit: packages/filepath] master: Remove double quotes around searchPath elements on Windows (89b7171) Message-ID: <20150319113650.598FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/89b7171c38dbad3db5decf1c5ca2c9c70fb81107 >--------------------------------------------------------------- commit 89b7171c38dbad3db5decf1c5ca2c9c70fb81107 Author: Thomas Miedema Date: Sat Nov 1 18:39:42 2014 +0100 Remove double quotes around searchPath elements on Windows >--------------------------------------------------------------- 89b7171c38dbad3db5decf1c5ca2c9c70fb81107 System/FilePath/Internal.hs | 2 + changelog.md | 4 +- tests/TestGen.hs | 668 ++++++++++++++++++++++---------------------- 3 files changed, 340 insertions(+), 334 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 89b7171c38dbad3db5decf1c5ca2c9c70fb81107 From git at git.haskell.org Thu Mar 19 11:36:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:51 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Add/update hackage/travis shields in README.md (9300c80) Message-ID: <20150319113651.71C113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/9300c80e044de3db36150fa344416efe373a9546/process >--------------------------------------------------------------- commit 9300c80e044de3db36150fa344416efe373a9546 Author: Herbert Valerio Riedel Date: Sat Nov 1 09:28:19 2014 +0100 Add/update hackage/travis shields in README.md >--------------------------------------------------------------- 9300c80e044de3db36150fa344416efe373a9546 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index e9b0a3f..f0698ea 100644 --- a/README.md +++ b/README.md @@ -1,4 +1,4 @@ -The `process` Package [![Build Status](https://travis-ci.org/ghc/packages-process.png?branch=master)](https://travis-ci.org/ghc/packages-process) +The `process` Package [![Hackage](https://img.shields.io/hackage/v/process.svg)](https://hackage.haskell.org/package/process) [![Build Status](https://travis-ci.org/haskell/process.svg)](https://travis-ci.org/haskell/process) ===================== See [`process` on Hackage](http://hackage.haskell.org/package/process) for From git at git.haskell.org Thu Mar 19 11:36:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:51 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Replace `throw` by `throwIO` (a5d0c5b) Message-ID: <20150319113651.A6BB53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/a5d0c5ba9d6f6603278a7b8e86edd7a29c51641d/directory >--------------------------------------------------------------- commit a5d0c5ba9d6f6603278a7b8e86edd7a29c51641d Author: Herbert Valerio Riedel Date: Mon Jan 19 13:49:34 2015 +0100 Replace `throw` by `throwIO` With `throwIO` it's better defined when the exception is actually triggered. >--------------------------------------------------------------- a5d0c5ba9d6f6603278a7b8e86edd7a29c51641d System/Directory.hs | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/System/Directory.hs b/System/Directory.hs index 1bf4172..98e4c20 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -366,11 +366,11 @@ createDirectoryIfMissing create_parents path0 parents = reverse . scanl1 () . splitDirectories . normalise createDirs [] = return () - createDirs (dir:[]) = createDir dir throw + createDirs (dir:[]) = createDir dir throwIO createDirs (dir:dirs) = createDir dir $ \_ -> do createDirs dirs - createDir dir throw + createDir dir throwIO createDir :: FilePath -> (IOException -> IO ()) -> IO () createDir dir notExistHandler = do @@ -398,15 +398,15 @@ createDirectoryIfMissing create_parents path0 withFileStatus "createDirectoryIfMissing" dir $ \st -> do isDir <- isDirectory st if isDir then return () - else throw e + else throwIO e #else stat <- Posix.getFileStatus dir if Posix.isDirectory stat then return () - else throw e + else throwIO e #endif ) `E.catch` ((\_ -> return ()) :: IOException -> IO ()) - | otherwise -> throw e + | otherwise -> throwIO e #if __GLASGOW_HASKELL__ {- | @'removeDirectory' dir@ removes an existing directory /dir/. The @@ -475,7 +475,7 @@ removeDirectoryRecursive startLoc = do case temp of Left e -> do isDir <- doesDirectoryExist f -- If f is not a directory, re-throw the error - unless isDir $ throw (e :: SomeException) + unless isDir $ throwIO (e :: SomeException) removeDirectoryRecursive f Right _ -> return () @@ -669,7 +669,7 @@ copied to /new/, if possible. copyFile :: FilePath -> FilePath -> IO () copyFile fromFPath toFPath = - copy `catchIOError` (\exc -> throw $ ioeSetLocation exc "copyFile") + copy `catchIOError` (\exc -> throwIO $ ioeSetLocation exc "copyFile") where copy = bracket (openBinaryFile fromFPath ReadMode) hClose $ \hFrom -> bracketOnError openTmp cleanTmp $ \(tmpFPath, hTmp) -> do allocaBytes bufferSize $ copyContents hFrom hTmp @@ -1209,7 +1209,7 @@ getTemporaryDirectory = do #else getEnv "TMPDIR" `catchIOError` \e -> if isDoesNotExistError e then return "/tmp" - else throw e + else throwIO e #endif -- ToDo: This should be determined via autoconf (AC_EXEEXT) From git at git.haskell.org Thu Mar 19 11:36:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:52 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge pull request #36 from thomie/searchPath (83b6d8c) Message-ID: <20150319113652.617403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/83b6d8c555d278f5bb79cef6661d02bc38e72c1e >--------------------------------------------------------------- commit 83b6d8c555d278f5bb79cef6661d02bc38e72c1e Merge: 7ab78f9 89b7171 Author: Neil Mitchell Date: Sat Nov 1 19:12:52 2014 +0000 Merge pull request #36 from thomie/searchPath Remove double quotes around searchPath elements on Windows >--------------------------------------------------------------- 83b6d8c555d278f5bb79cef6661d02bc38e72c1e System/FilePath/Internal.hs | 2 + changelog.md | 4 +- tests/TestGen.hs | 668 ++++++++++++++++++++++---------------------- 3 files changed, 340 insertions(+), 334 deletions(-) From git at git.haskell.org Thu Mar 19 11:36:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:53 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Build Haddock documentation for System.Process.Internals (ef81bea) Message-ID: <20150319113653.788B13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/ef81bea4153b64637356c70947c67165c72747fe/process >--------------------------------------------------------------- commit ef81bea4153b64637356c70947c67165c72747fe Author: Simon Hengel Date: Sat Nov 1 11:03:00 2014 +0800 Build Haddock documentation for System.Process.Internals From my perspective the module name already clearly states that this is internal stuff + currently we have a 404 on Hackage for this one + I actually want to read the Haddocks. Fixes #7 >--------------------------------------------------------------- ef81bea4153b64637356c70947c67165c72747fe System/Process/Internals.hs | 6 ++++-- changelog.md | 2 ++ 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index 9dc2af7..4cf6b1a 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -1,5 +1,5 @@ {-# LANGUAGE CPP, RecordWildCards, BangPatterns #-} -{-# OPTIONS_HADDOCK hide #-} +{-# OPTIONS_HADDOCK not-home #-} #ifdef __GLASGOW_HASKELL__ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE InterruptibleFFI #-} @@ -15,7 +15,9 @@ -- Stability : experimental -- Portability : portable -- --- Operations for creating and interacting with sub-processes. +-- __Note:__ This module exports internal implementation details that may +-- change anytime. If you want a more stable API, use "System.Process" +-- instead. -- ----------------------------------------------------------------------------- diff --git a/changelog.md b/changelog.md index b361dea..86b04df 100644 --- a/changelog.md +++ b/changelog.md @@ -4,6 +4,8 @@ * Add support for `base-4.8.0.0` + * Expose documentation for `System.Process.Internals` + ## 1.2.0.0 *Dec 2013* * Update to Cabal 1.10 format From git at git.haskell.org Thu Mar 19 11:36:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:53 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Fix `createDirectoryIfMissing` silently failing (1f11393) Message-ID: <20150319113653.AE40A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/1f113935439a381443b945eb5177fb122881f182/directory >--------------------------------------------------------------- commit 1f113935439a381443b945eb5177fb122881f182 Author: Herbert Valerio Riedel Date: Mon Jan 19 14:18:09 2015 +0100 Fix `createDirectoryIfMissing` silently failing In some cases, `createDirectoryIfMissing` would silently fail. For example the following invocation would fail to report via an exception that it couldn't create a folder: let testdir = "/tmp/sometestdir" writeFile testdir "" createDirectoryIfMissing False testdir A related issue was the failure to create a folder hierarchy due to lack of permissions, for instance createDirectoryIfMissing True "/foo" for a non-priviledged user would silently fail (i.e. no exception thrown), even though "/foo" was not created. Fixes #4 (see also #10 for discussion) >--------------------------------------------------------------- 1f113935439a381443b945eb5177fb122881f182 System/Directory.hs | 16 ++++++---------- tests/createDirectoryIfMissing001.hs | 12 ++++++++++++ tests/createDirectoryIfMissing001.stdout | 2 ++ 3 files changed, 20 insertions(+), 10 deletions(-) diff --git a/System/Directory.hs b/System/Directory.hs index 98e4c20..26600a0 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -393,19 +393,15 @@ createDirectoryIfMissing create_parents path0 -- This caused GHCi to crash when loading a module in the root -- directory. | isAlreadyExistsError e - || isPermissionError e -> (do + || isPermissionError e -> do #ifdef mingw32_HOST_OS - withFileStatus "createDirectoryIfMissing" dir $ \st -> do - isDir <- isDirectory st - if isDir then return () - else throwIO e + canIgnore <- (withFileStatus "createDirectoryIfMissing" dir isDirectory) #else - stat <- Posix.getFileStatus dir - if Posix.isDirectory stat - then return () - else throwIO e + canIgnore <- (Posix.isDirectory `fmap` Posix.getFileStatus dir) #endif - ) `E.catch` ((\_ -> return ()) :: IOException -> IO ()) + `catch` ((\ _ -> return (isAlreadyExistsError e)) + :: IOException -> IO Bool) + unless canIgnore (throwIO e) | otherwise -> throwIO e #if __GLASGOW_HASKELL__ diff --git a/tests/createDirectoryIfMissing001.hs b/tests/createDirectoryIfMissing001.hs index ec09318..bd80761 100644 --- a/tests/createDirectoryIfMissing001.hs +++ b/tests/createDirectoryIfMissing001.hs @@ -43,6 +43,18 @@ main = do cleanup + -- these are all supposed to fail + + writeFile testdir testdir + report $ createDirectoryIfMissing False testdir + removeFile testdir + cleanup + + writeFile testdir testdir + report $ createDirectoryIfMissing True testdir_a + removeFile testdir + cleanup + -- createDirectoryIfMissing is allowed to fail with isDoesNotExistError if -- another process/thread removes one of the directories during the proces -- of creating the hierarchy. diff --git a/tests/createDirectoryIfMissing001.stdout b/tests/createDirectoryIfMissing001.stdout index f792318..d1061a8 100644 --- a/tests/createDirectoryIfMissing001.stdout +++ b/tests/createDirectoryIfMissing001.stdout @@ -4,3 +4,5 @@ createDirectoryIfMissing001.d/a: createDirectory: does not exist (No such file o () () () +createDirectoryIfMissing001.d: createDirectory: already exists (File exists) +createDirectoryIfMissing001.d/a: createDirectory: inappropriate type (Not a directory) From git at git.haskell.org Thu Mar 19 11:36:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:54 +0000 (UTC) Subject: [commit: packages/filepath] master: Make off the things in the generator which are utilities (8cb60d5) Message-ID: <20150319113654.674803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/8cb60d591f31fc3ccafb7b149977b1891f6c54c3 >--------------------------------------------------------------- commit 8cb60d591f31fc3ccafb7b149977b1891f6c54c3 Author: Neil Mitchell Date: Sun Nov 2 21:46:30 2014 +0000 Make off the things in the generator which are utilities >--------------------------------------------------------------- 8cb60d591f31fc3ccafb7b149977b1891f6c54c3 Generate.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/Generate.hs b/Generate.hs index c990a05..8918bcf 100755 --- a/Generate.hs +++ b/Generate.hs @@ -110,6 +110,10 @@ genTest (Test free x) = "test (\\" ++ concatMap ((' ':) . f) free ++ " -> (" ++ f [a] | a >= 'x' = "(QFilePath " ++ [a] ++ ")" f x = x + +--------------------------------------------------------------------- +-- UTILITIES + writeFileBinary :: FilePath -> String -> IO () writeFileBinary file x = withBinaryFile file WriteMode $ \h -> hPutStr h x From git at git.haskell.org Thu Mar 19 11:36:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:55 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Add `/dist/` to `.gitignore` (aaa55d2) Message-ID: <20150319113655.7EF903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/aaa55d2a39c78c5937cd8a0433114325d92b226d/process >--------------------------------------------------------------- commit aaa55d2a39c78c5937cd8a0433114325d92b226d Author: Simon Hengel Date: Sat Nov 1 12:34:02 2014 +0800 Add `/dist/` to `.gitignore` >--------------------------------------------------------------- aaa55d2a39c78c5937cd8a0433114325d92b226d .gitignore | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.gitignore b/.gitignore index bd6e173..3934cb6 100644 --- a/.gitignore +++ b/.gitignore @@ -1,3 +1,5 @@ +/dist/ + # Specific generated files GNUmakefile autom4te.cache/ From git at git.haskell.org Thu Mar 19 11:36:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:55 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Add mingw32 output for 1f113935439a3814 (768a840) Message-ID: <20150319113655.B40103A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/768a8402770989f6625eba1f15ec8f756e9d1f41/directory >--------------------------------------------------------------- commit 768a8402770989f6625eba1f15ec8f756e9d1f41 Author: Herbert Valerio Riedel Date: Mon Jan 19 14:37:06 2015 +0100 Add mingw32 output for 1f113935439a3814 >--------------------------------------------------------------- 768a8402770989f6625eba1f15ec8f756e9d1f41 tests/createDirectoryIfMissing001.stdout-mingw32 | 2 ++ 1 file changed, 2 insertions(+) diff --git a/tests/createDirectoryIfMissing001.stdout-mingw32 b/tests/createDirectoryIfMissing001.stdout-mingw32 index d271f78..0e9fb52 100644 --- a/tests/createDirectoryIfMissing001.stdout-mingw32 +++ b/tests/createDirectoryIfMissing001.stdout-mingw32 @@ -4,3 +4,5 @@ CreateDirectory "createDirectoryIfMissing001.d\\a": does not exist (The system c () () () +CreateDirectory "createDirectoryIfMissing001.d": already exists (Cannot create a file when that file already exists.) +CreateDirectory "createDirectoryIfMissing001.d": already exists (Cannot create a file when that file already exists.) From git at git.haskell.org Thu Mar 19 11:36:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:56 +0000 (UTC) Subject: [commit: packages/filepath] master: Remove the QChar type, rewrite an arbitraryFilePath type (66f7c57) Message-ID: <20150319113656.6D38F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/66f7c574456c3570a2ba49963dfaa39a9925c248 >--------------------------------------------------------------- commit 66f7c574456c3570a2ba49963dfaa39a9925c248 Author: Neil Mitchell Date: Sun Nov 2 21:47:09 2014 +0000 Remove the QChar type, rewrite an arbitraryFilePath type >--------------------------------------------------------------- 66f7c574456c3570a2ba49963dfaa39a9925c248 tests/TestUtil.hs | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/tests/TestUtil.hs b/tests/TestUtil.hs index 83f2d48..1c1718c 100644 --- a/tests/TestUtil.hs +++ b/tests/TestUtil.hs @@ -7,23 +7,23 @@ module TestUtil( import Test.QuickCheck hiding ((==>)) import Data.List +import Control.Monad infixr 0 ==> a ==> b = not a || b -newtype QFilePath = QFilePath FilePath - deriving Show +newtype QFilePath = QFilePath FilePath deriving Show instance Arbitrary QFilePath where - arbitrary = fmap (QFilePath . map fromQChar) arbitrary + arbitrary = fmap QFilePath arbitraryFilePath shrink (QFilePath x) = map QFilePath $ shrink x -newtype QChar = QChar {fromQChar :: Char} - -instance Arbitrary QChar where - arbitrary = fmap QChar $ elements "?./:\\a ;_" +arbitraryFilePath :: Gen FilePath +arbitraryFilePath = sized $ \n -> do + k <- choose (0,n) + replicateM k $ elements "?./:\\a ;_" test :: Testable a => a -> IO () From git at git.haskell.org Thu Mar 19 11:36:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:57 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Adapt documentation of `readProcess` (63fdc81) Message-ID: <20150319113657.85A7B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/63fdc819972fc579b1b27be4ced7bf9489b45351/process >--------------------------------------------------------------- commit 63fdc819972fc579b1b27be4ced7bf9489b45351 Author: Simon Hengel Date: Sat Nov 1 12:14:21 2014 +0800 Adapt documentation of `readProcess` (a program does not have a standard input) >--------------------------------------------------------------- 63fdc819972fc579b1b27be4ced7bf9489b45351 System/Process.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Process.hs b/System/Process.hs index 87e9a41..010b95a 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -409,7 +409,7 @@ processFailedException fun cmd args exit_code = -- -- * A list of separate command line arguments to the program -- --- * A string to pass on the standard input to the program. +-- * A string to pass on standard input to the forked process. -- readProcess :: FilePath -- ^ Filename of the executable (see 'proc' for details) From git at git.haskell.org Thu Mar 19 11:36:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:57 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Update changelog (b78c422) Message-ID: <20150319113657.B9DB63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/b78c422d9433141334d072a85f530dbacdadd1f7/directory >--------------------------------------------------------------- commit b78c422d9433141334d072a85f530dbacdadd1f7 Author: Herbert Valerio Riedel Date: Mon Jan 19 14:39:05 2015 +0100 Update changelog >--------------------------------------------------------------- b78c422d9433141334d072a85f530dbacdadd1f7 changelog.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/changelog.md b/changelog.md index 6891d2f..c2a41f8 100644 --- a/changelog.md +++ b/changelog.md @@ -6,6 +6,10 @@ * make `getModificationTime` support sub-second resolution on windows + * Fix silent failure in `createDirectoryIfMissing` + + * Replace `throw` by better defined `throwIO`s + ## 1.2.1.0 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 11:36:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:58 +0000 (UTC) Subject: [commit: packages/filepath] master: Add an explicit export list to the generator (8dc3b8f) Message-ID: <20150319113658.730A63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/8dc3b8f6f7d5d527176ff903e0b281ced72a91a9 >--------------------------------------------------------------- commit 8dc3b8f6f7d5d527176ff903e0b281ced72a91a9 Author: Neil Mitchell Date: Sun Nov 2 21:48:13 2014 +0000 Add an explicit export list to the generator >--------------------------------------------------------------- 8dc3b8f6f7d5d527176ff903e0b281ced72a91a9 tests/TestUtil.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/TestUtil.hs b/tests/TestUtil.hs index 1c1718c..7f01f8f 100644 --- a/tests/TestUtil.hs +++ b/tests/TestUtil.hs @@ -1,6 +1,6 @@ module TestUtil( - module TestUtil, + (==>), QFilePath(..), test, module Test.QuickCheck, module Data.List ) where From git at git.haskell.org Thu Mar 19 11:36:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:59 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Document that `readProcess` works with relative paths (58aa7f7) Message-ID: <20150319113659.8C94D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/58aa7f7ad5b6c16ee18962b5caf9f461133f7569/process >--------------------------------------------------------------- commit 58aa7f7ad5b6c16ee18962b5caf9f461133f7569 Author: Simon Hengel Date: Sat Nov 1 12:21:46 2014 +0800 Document that `readProcess` works with relative paths >--------------------------------------------------------------- 58aa7f7ad5b6c16ee18962b5caf9f461133f7569 System/Process.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Process.hs b/System/Process.hs index 010b95a..b73dba3 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -405,7 +405,7 @@ processFailedException fun cmd args exit_code = -- -- The arguments are: -- --- * The command to run, which must be in the $PATH, or an absolute path +-- * The command to run, which must be in the $PATH, or an absolute or relative path -- -- * A list of separate command line arguments to the program -- From git at git.haskell.org Thu Mar 19 11:36:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:36:59 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Fix source repository (486f14d) Message-ID: <20150319113659.BF8683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/486f14ddd149eb43e57b3e8341638cc7f1542317/directory >--------------------------------------------------------------- commit 486f14ddd149eb43e57b3e8341638cc7f1542317 Author: Michael Snoyman Date: Tue Feb 17 10:29:11 2015 +0200 Fix source repository >--------------------------------------------------------------- 486f14ddd149eb43e57b3e8341638cc7f1542317 directory.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/directory.cabal b/directory.cabal index 69266c6..32f22a1 100644 --- a/directory.cabal +++ b/directory.cabal @@ -31,7 +31,7 @@ extra-source-files: source-repository head type: git - location: http://git.haskell.org/packages/directory.git + location: https://github.com/haskell/directory Library default-language: Haskell2010 From git at git.haskell.org Thu Mar 19 11:37:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:00 +0000 (UTC) Subject: [commit: packages/filepath] master: Add newtypes for valid paths on Windows and Posix, make sure to be smart about shrinking with valid function (4409c75) Message-ID: <20150319113700.7B90C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/4409c75af7bc122ae2ed3e45bf7bc27e62460de1 >--------------------------------------------------------------- commit 4409c75af7bc122ae2ed3e45bf7bc27e62460de1 Author: Neil Mitchell Date: Sun Nov 2 22:00:38 2014 +0000 Add newtypes for valid paths on Windows and Posix, make sure to be smart about shrinking with valid function >--------------------------------------------------------------- 4409c75af7bc122ae2ed3e45bf7bc27e62460de1 tests/TestUtil.hs | 28 ++++++++++++++++++++++++++-- 1 file changed, 26 insertions(+), 2 deletions(-) diff --git a/tests/TestUtil.hs b/tests/TestUtil.hs index 7f01f8f..08aa443 100644 --- a/tests/TestUtil.hs +++ b/tests/TestUtil.hs @@ -1,6 +1,6 @@ module TestUtil( - (==>), QFilePath(..), test, + (==>), QFilePath(..), QFilePathValidW(..), QFilePathValidP(..), test, module Test.QuickCheck, module Data.List ) where @@ -8,23 +8,47 @@ module TestUtil( import Test.QuickCheck hiding ((==>)) import Data.List import Control.Monad +import qualified System.FilePath.Windows as W +import qualified System.FilePath.Posix as P infixr 0 ==> a ==> b = not a || b +newtype QFilePathValidW = QFilePathValidW FilePath deriving Show + +instance Arbitrary QFilePathValidW where + arbitrary = fmap (QFilePathValidW . W.makeValid) arbitraryFilePath + shrink (QFilePathValidW x) = shrinkValid QFilePathValidW W.makeValid x + +newtype QFilePathValidP = QFilePathValidP FilePath deriving Show + +instance Arbitrary QFilePathValidP where + arbitrary = fmap (QFilePathValidP . P.makeValid) arbitraryFilePath + shrink (QFilePathValidP x) = shrinkValid QFilePathValidP P.makeValid x + newtype QFilePath = QFilePath FilePath deriving Show instance Arbitrary QFilePath where arbitrary = fmap QFilePath arbitraryFilePath - shrink (QFilePath x) = map QFilePath $ shrink x + shrink (QFilePath x) = shrinkValid QFilePath id x +-- | Generate an arbitrary FilePath use a few special (interesting) characters. arbitraryFilePath :: Gen FilePath arbitraryFilePath = sized $ \n -> do k <- choose (0,n) replicateM k $ elements "?./:\\a ;_" +-- | Shrink, but also apply a validity function. Try and make shorter, or use more +-- @a@ (since @a@ is pretty dull), but make sure you terminate even after valid. +shrinkValid :: (FilePath -> a) -> (FilePath -> FilePath) -> FilePath -> [a] +shrinkValid wrap valid o = + [ wrap y + | y <- map valid $ shrinkList (\x -> ['a' | x /= 'a']) o + , length y < length o || (length y == length o && countA y > countA o)] + where countA = length . filter (== 'a') + test :: Testable a => a -> IO () test prop = do From git at git.haskell.org Thu Mar 19 11:37:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:01 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Move docs on semantics for raw commands from `proc` to `RawCommand` (6446907) Message-ID: <20150319113701.93E413A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/64469076c4ed520c9213267ed1eaf7317034b5b9/process >--------------------------------------------------------------- commit 64469076c4ed520c9213267ed1eaf7317034b5b9 Author: Simon Hengel Date: Sat Nov 1 12:34:20 2014 +0800 Move docs on semantics for raw commands from `proc` to `RawCommand` (This is where it belongs to, IMHO.) Closes #8 >--------------------------------------------------------------- 64469076c4ed520c9213267ed1eaf7317034b5b9 System/Process.hs | 29 +++++------------------------ System/Process/Internals.hs | 27 +++++++++++++++++++++++---- 2 files changed, 28 insertions(+), 28 deletions(-) diff --git a/System/Process.hs b/System/Process.hs index b73dba3..cafe2cc 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -111,26 +111,7 @@ import System.Posix.Signals -- | Construct a 'CreateProcess' record for passing to 'createProcess', -- representing a raw command with arguments. -- --- The 'FilePath' argument names the executable, and is interpreted according --- to the platform's standard policy for searching for --- executables. Specifically: --- --- * on Unix systems the --- --- semantics is used, where if the executable filename does not --- contain a slash (@/@) then the @PATH@ environment variable is --- searched for the executable. --- --- * on Windows systems the Win32 @CreateProcess@ semantics is used. --- Briefly: if the filename does not contain a path, then the --- directory containing the parent executable is searched, followed --- by the current directory, then some standard locations, and --- finally the current @PATH at . An @.exe@ extension is added if the --- filename does not already have an extension. For full details --- see the --- --- for the Windows @SearchPath@ API. - +-- See 'RawCommand' for precise semantics of the specified @FilePath at . proc :: FilePath -> [String] -> CreateProcess proc cmd args = CreateProcess { cmdspec = RawCommand cmd args, cwd = Nothing, @@ -412,7 +393,7 @@ processFailedException fun cmd args exit_code = -- * A string to pass on standard input to the forked process. -- readProcess - :: FilePath -- ^ Filename of the executable (see 'proc' for details) + :: FilePath -- ^ Filename of the executable (see 'RawCommand' for details) -> [String] -- ^ any arguments -> String -- ^ standard input -> IO String -- ^ stdout @@ -468,7 +449,7 @@ when the process died as the result of a signal. -} readProcessWithExitCode - :: FilePath -- ^ Filename of the executable (see 'proc' for details) + :: FilePath -- ^ Filename of the executable (see 'RawCommand' for details) -> [String] -- ^ any arguments -> String -- ^ standard input -> IO (ExitCode,String,String) -- ^ exitcode, stdout, stderr @@ -747,7 +728,7 @@ runCommand string = do 'runProcess'. -} runProcess - :: FilePath -- ^ Filename of the executable (see 'proc' for details) + :: FilePath -- ^ Filename of the executable (see 'RawCommand' for details) -> [String] -- ^ Arguments to pass to the executable -> Maybe FilePath -- ^ Optional path to the working directory -> Maybe [(String,String)] -- ^ Optional environment (otherwise inherit) @@ -814,7 +795,7 @@ runInteractiveCommand string = in text mode then use 'hSetBinaryMode'. -} runInteractiveProcess - :: FilePath -- ^ Filename of the executable (see 'proc' for details) + :: FilePath -- ^ Filename of the executable (see 'RawCommand' for details) -> [String] -- ^ Arguments to pass to the executable -> Maybe FilePath -- ^ Optional path to the working directory -> Maybe [(String,String)] -- ^ Optional environment (otherwise inherit) diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index 4cf6b1a..d5cc90b 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -184,11 +184,30 @@ data CreateProcess = CreateProcess{ data CmdSpec = ShellCommand String - -- ^ a command line to execute using the shell + -- ^ A command line to execute using the shell | RawCommand FilePath [String] - -- ^ the filename of an executable with a list of arguments. - -- see 'System.Process.proc' for the precise interpretation of - -- the @FilePath@ field. + -- ^ The name of an executable with a list of arguments + -- + -- The 'FilePath' argument names the executable, and is interpreted + -- according to the platform's standard policy for searching for + -- executables. Specifically: + -- + -- * on Unix systems the + -- + -- semantics is used, where if the executable filename does not + -- contain a slash (@/@) then the @PATH@ environment variable is + -- searched for the executable. + -- + -- * on Windows systems the Win32 @CreateProcess@ semantics is used. + -- Briefly: if the filename does not contain a path, then the + -- directory containing the parent executable is searched, followed + -- by the current directory, then some standard locations, and + -- finally the current @PATH at . An @.exe@ extension is added if the + -- filename does not already have an extension. For full details + -- see the + -- + -- for the Windows @SearchPath@ API. + data StdStream = Inherit -- ^ Inherit Handle from parent From git at git.haskell.org Thu Mar 19 11:37:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:01 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: More efficient getDirectoryContents (81be17f) Message-ID: <20150319113701.C657D3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/81be17f03b1a9c47c0fcd318a446a643639058d9/directory >--------------------------------------------------------------- commit 81be17f03b1a9c47c0fcd318a446a643639058d9 Author: Michael Snoyman Date: Tue Feb 17 10:32:21 2015 +0200 More efficient getDirectoryContents See https://ghc.haskell.org/trac/ghc/ticket/9266 >--------------------------------------------------------------- 81be17f03b1a9c47c0fcd318a446a643639058d9 System/Directory.hs | 15 +++++++++------ 1 file changed, 9 insertions(+), 6 deletions(-) diff --git a/System/Directory.hs b/System/Directory.hs index 26600a0..29addf1 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -839,13 +839,16 @@ getDirectoryContents path = bracket (Posix.openDirStream path) Posix.closeDirStream - loop + start where - loop dirp = do - e <- Posix.readDirStream dirp - if null e then return [] else do - es <- loop dirp - return (e:es) + start dirp = + loop id + where + loop acc = do + e <- Posix.readDirStream dirp + if null e + then return (acc []) + else loop (acc . (e:)) #else bracket (Win32.findFirstFile (path "*")) From git at git.haskell.org Thu Mar 19 11:37:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:02 +0000 (UTC) Subject: [commit: packages/filepath] master: #37, rewrite the generator (fa41e60) Message-ID: <20150319113702.836883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/fa41e606e06ffb4176c2a47c086887fed3f2fd63 >--------------------------------------------------------------- commit fa41e606e06ffb4176c2a47c086887fed3f2fd63 Author: Neil Mitchell Date: Mon Nov 3 10:44:17 2014 +0000 #37, rewrite the generator >--------------------------------------------------------------- fa41e606e06ffb4176c2a47c086887fed3f2fd63 Generate.hs | 126 ++---- System/FilePath/Internal.hs | 2 +- tests/Test.hs | 17 +- tests/TestGen.hs | 1047 ++++++++++++++----------------------------- tests/TestUtil.hs | 18 +- 5 files changed, 414 insertions(+), 796 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fa41e606e06ffb4176c2a47c086887fed3f2fd63 From git at git.haskell.org Thu Mar 19 11:37:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:03 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Tighten Safe Haskell bounds, fixes new warning in GHC 7.10. (ed489db) Message-ID: <20150319113703.9ACBF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/ed489dbf461a0fc10c83a7ca75460f595ce7b646/process >--------------------------------------------------------------- commit ed489dbf461a0fc10c83a7ca75460f595ce7b646 Author: David Terei Date: Wed Nov 12 18:15:28 2014 -0800 Tighten Safe Haskell bounds, fixes new warning in GHC 7.10. >--------------------------------------------------------------- ed489dbf461a0fc10c83a7ca75460f595ce7b646 System/Cmd.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/System/Cmd.hs b/System/Cmd.hs index a16a685..4f1de4d 100644 --- a/System/Cmd.hs +++ b/System/Cmd.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP #-} -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif From git at git.haskell.org Thu Mar 19 11:37:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:03 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Add fledgeling test suite (e5ab065) Message-ID: <20150319113703.CDEF13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/e5ab0653643c18ec6106be1674179ae94c66e858/directory >--------------------------------------------------------------- commit e5ab0653643c18ec6106be1674179ae94c66e858 Author: Michael Snoyman Date: Tue Feb 17 11:29:58 2015 +0200 Add fledgeling test suite We should really get this to run all of the tests in the tests directory instead. >--------------------------------------------------------------- e5ab0653643c18ec6106be1674179ae94c66e858 .travis.yml | 3 ++- directory.cabal | 9 +++++++++ test/main.hs | 20 ++++++++++++++++++++ 3 files changed, 31 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index ea01c3c..05ed4e4 100644 --- a/.travis.yml +++ b/.travis.yml @@ -25,10 +25,11 @@ install: script: - autoreconf -i - - cabal configure -v2 + - cabal configure -v2 --enable-tests - cabal build - cabal check - cabal sdist + - cabal test # The following scriptlet checks that the resulting source distribution can be built & installed - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; cd dist/; diff --git a/directory.cabal b/directory.cabal index 32f22a1..83e4109 100644 --- a/directory.cabal +++ b/directory.cabal @@ -61,3 +61,12 @@ Library build-depends: unix >= 2.5.1 && < 2.8 ghc-options: -Wall + +test-suite test + default-language: Haskell2010 + hs-source-dirs: test + main-is: main.hs + type: exitcode-stdio-1.0 + build-depends: base + , directory + , containers diff --git a/test/main.hs b/test/main.hs new file mode 100644 index 0000000..7a9fcb3 --- /dev/null +++ b/test/main.hs @@ -0,0 +1,20 @@ +{-# LANGUAGE NoImplicitPrelude #-} +-- Simplistic test suite for now. Worthwhile to add a dependency on a +-- test framework at some point. +module Main (main) where + +import qualified Data.Set as Set +import Prelude (IO, error, fmap, return, show, (==)) +import System.Directory (getDirectoryContents) + +main :: IO () +main = do + let expected = Set.fromList + [ "." + , ".." + , "main.hs" + ] + actual <- fmap Set.fromList (getDirectoryContents "test") + if expected == actual + then return () + else error (show (expected, actual)) From git at git.haskell.org Thu Mar 19 11:37:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:04 +0000 (UTC) Subject: [commit: packages/filepath] master: #37, let the generator take an argument of the number of tests (654be5b) Message-ID: <20150319113704.8AB763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/654be5bc8baf2cf0efba5b176a5934323dc57832 >--------------------------------------------------------------- commit 654be5bc8baf2cf0efba5b176a5934323dc57832 Author: Neil Mitchell Date: Mon Nov 3 10:50:14 2014 +0000 #37, let the generator take an argument of the number of tests >--------------------------------------------------------------- 654be5bc8baf2cf0efba5b176a5934323dc57832 .ghci | 2 +- tests/Test.hs | 6 +++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/.ghci b/.ghci index e9e1bba..c05f736 100644 --- a/.ghci +++ b/.ghci @@ -8,6 +8,6 @@ import qualified System.FilePath.Posix as P :def docs const $ return $ unlines [":docs_",":!start dist\\doc\\html\\filepath\\System-FilePath.html"] :def gen const $ return "Generate.main" -:def test const $ return "Test.main" +:def test \x -> return $ if null x then "Test.main" else "System.Environment.withArgs [" ++ show x ++ "] Test.main" :def go const $ return $ unlines [":reload",":gen",":reload",":test",":gen",":reload"] :def testfull const $ return $ unlines [":reload","gen",":reload","!cabal test"] diff --git a/tests/Test.hs b/tests/Test.hs index 5f8fbdc..9b96db4 100755 --- a/tests/Test.hs +++ b/tests/Test.hs @@ -1,6 +1,7 @@ module Test(main) where +import System.Environment import TestGen import Control.Monad import Test.QuickCheck @@ -8,10 +9,13 @@ import Test.QuickCheck main :: IO () main = do + args <- getArgs + let count = case args of i:_ -> read i; _ -> 10000 + putStrLn $ "Testing with " ++ show count ++ " repetitions" let total = length tests bs <- forM (zip [1..] tests) $ \(i,(msg,prop)) -> do putStrLn $ "Test " ++ show i ++ " of " ++ show total ++ ": " ++ msg - res <- quickCheckWithResult stdArgs{maxSuccess=10000} prop + res <- quickCheckWithResult stdArgs{maxSuccess=count} prop case res of Success{} -> return True _ -> putStrLn "TEST FAILURE!" >> return False From git at git.haskell.org Thu Mar 19 11:37:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:05 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Merge pull request #10 from dterei/safe710fixes (565caaf) Message-ID: <20150319113705.A1A8C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/565caaff5724b694ae0e1d2ad7a1e7526e199da2/process >--------------------------------------------------------------- commit 565caaff5724b694ae0e1d2ad7a1e7526e199da2 Merge: 6446907 ed489db Author: Herbert Valerio Riedel Date: Fri Nov 14 18:14:38 2014 +0100 Merge pull request #10 from dterei/safe710fixes Tighten Safe Haskell bounds, fixes new warning in GHC 7.10. >--------------------------------------------------------------- 565caaff5724b694ae0e1d2ad7a1e7526e199da2 System/Cmd.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) From git at git.haskell.org Thu Mar 19 11:37:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:05 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Disambiguate catch for older GHC (9393527) Message-ID: <20150319113705.D4C083A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/9393527136c2fbac675c4afd7e1f4f3266d331da/directory >--------------------------------------------------------------- commit 9393527136c2fbac675c4afd7e1f4f3266d331da Author: Michael Snoyman Date: Tue Feb 17 14:26:11 2015 +0200 Disambiguate catch for older GHC >--------------------------------------------------------------- 9393527136c2fbac675c4afd7e1f4f3266d331da System/Directory.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Directory.hs b/System/Directory.hs index 29addf1..5e77f4d 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -399,7 +399,7 @@ createDirectoryIfMissing create_parents path0 #else canIgnore <- (Posix.isDirectory `fmap` Posix.getFileStatus dir) #endif - `catch` ((\ _ -> return (isAlreadyExistsError e)) + `E.catch` ((\ _ -> return (isAlreadyExistsError e)) :: IOException -> IO Bool) unless canIgnore (throwIO e) | otherwise -> throwIO e From git at git.haskell.org Thu Mar 19 11:37:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:06 +0000 (UTC) Subject: [commit: packages/filepath] master: Turn off chatty tests, otherwise we exceed the travis size limit (37ec740) Message-ID: <20150319113706.905433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/37ec7403e544ceb16dc4e01a67a83a46afdb38d7 >--------------------------------------------------------------- commit 37ec7403e544ceb16dc4e01a67a83a46afdb38d7 Author: Neil Mitchell Date: Mon Nov 3 10:57:17 2014 +0000 Turn off chatty tests, otherwise we exceed the travis size limit >--------------------------------------------------------------- 37ec7403e544ceb16dc4e01a67a83a46afdb38d7 tests/Test.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/Test.hs b/tests/Test.hs index 9b96db4..e3e0103 100755 --- a/tests/Test.hs +++ b/tests/Test.hs @@ -15,7 +15,7 @@ main = do let total = length tests bs <- forM (zip [1..] tests) $ \(i,(msg,prop)) -> do putStrLn $ "Test " ++ show i ++ " of " ++ show total ++ ": " ++ msg - res <- quickCheckWithResult stdArgs{maxSuccess=count} prop + res <- quickCheckWithResult stdArgs{chatty=False, maxSuccess=count} prop case res of Success{} -> return True _ -> putStrLn "TEST FAILURE!" >> return False From git at git.haskell.org Thu Mar 19 11:37:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:07 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Bump upper bound of `deepseq` (bc5f234) Message-ID: <20150319113707.A7AB83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/bc5f2348b982d9e86bf2f15065187a0ba535a1a3/process >--------------------------------------------------------------- commit bc5f2348b982d9e86bf2f15065187a0ba535a1a3 Author: Herbert Valerio Riedel Date: Fri Nov 14 18:16:39 2014 +0100 Bump upper bound of `deepseq` `process` doesn't define any `NFData` instances of its own, so isn't affected by the changes in `deepseq-1.4.0.0`. >--------------------------------------------------------------- bc5f2348b982d9e86bf2f15065187a0ba535a1a3 process.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/process.cabal b/process.cabal index 0afdca7..f42d3c4 100644 --- a/process.cabal +++ b/process.cabal @@ -60,7 +60,7 @@ library build-depends: base >= 4.4 && < 4.9, directory >= 1.1 && < 1.3, filepath >= 1.2 && < 1.4, - deepseq >= 1.1 && < 1.4 + deepseq >= 1.1 && < 1.5 if os(windows) build-depends: Win32 >=2.2 && < 2.4 extra-libraries: kernel32 From git at git.haskell.org Thu Mar 19 11:37:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:07 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Merge pull request #17 from snoyberg/better-getDirectoryContents (c51ade2) Message-ID: <20150319113707.DD6253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/c51ade29e1a69c0d4f85213a76188a03780cacf2/directory >--------------------------------------------------------------- commit c51ade29e1a69c0d4f85213a76188a03780cacf2 Merge: b78c422 9393527 Author: Michael Snoyman Date: Tue Feb 17 15:43:51 2015 +0200 Merge pull request #17 from snoyberg/better-getDirectoryContents Better get directory contents >--------------------------------------------------------------- c51ade29e1a69c0d4f85213a76188a03780cacf2 .travis.yml | 3 ++- System/Directory.hs | 17 ++++++++++------- directory.cabal | 11 ++++++++++- test/main.hs | 20 ++++++++++++++++++++ 4 files changed, 42 insertions(+), 9 deletions(-) From git at git.haskell.org Thu Mar 19 11:37:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:08 +0000 (UTC) Subject: [commit: packages/filepath] master: Support :go taking a numeric argument (0b9122f) Message-ID: <20150319113708.966EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/0b9122f91f203238903fbd103cd931b57a24bf02 >--------------------------------------------------------------- commit 0b9122f91f203238903fbd103cd931b57a24bf02 Author: Neil Mitchell Date: Mon Nov 3 15:49:50 2014 +0000 Support :go taking a numeric argument >--------------------------------------------------------------- 0b9122f91f203238903fbd103cd931b57a24bf02 .ghci | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.ghci b/.ghci index c05f736..6e8b1b3 100644 --- a/.ghci +++ b/.ghci @@ -9,5 +9,5 @@ import qualified System.FilePath.Posix as P :def gen const $ return "Generate.main" :def test \x -> return $ if null x then "Test.main" else "System.Environment.withArgs [" ++ show x ++ "] Test.main" -:def go const $ return $ unlines [":reload",":gen",":reload",":test",":gen",":reload"] +:def go \x -> return $ unlines [":reload",":gen",":reload",":test " ++ x,":gen",":reload"] :def testfull const $ return $ unlines [":reload","gen",":reload","!cabal test"] From git at git.haskell.org Thu Mar 19 11:37:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:09 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Fix warning of weaker safe haskell bound on System.Process under 7.10 (d3b8152) Message-ID: <20150319113709.AEBC13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/d3b815269f3f107a43822fb5710e8b87ec20c6fb/process >--------------------------------------------------------------- commit d3b815269f3f107a43822fb5710e8b87ec20c6fb Author: David Terei Date: Mon Nov 24 12:44:46 2014 -0500 Fix warning of weaker safe haskell bound on System.Process under 7.10 >--------------------------------------------------------------- d3b815269f3f107a43822fb5710e8b87ec20c6fb System/Process.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/System/Process.hs b/System/Process.hs index cafe2cc..bff7f5d 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -1,6 +1,10 @@ {-# LANGUAGE CPP #-} #ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#else {-# LANGUAGE Trustworthy #-} +#endif {-# LANGUAGE InterruptibleFFI #-} #endif From git at git.haskell.org Thu Mar 19 11:37:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:09 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Changelog update (90584af) Message-ID: <20150319113709.E31323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/90584af7d353e11e7d39fa842f10fd8741c92574/directory >--------------------------------------------------------------- commit 90584af7d353e11e7d39fa842f10fd8741c92574 Author: Michael Snoyman Date: Tue Feb 17 15:46:14 2015 +0200 Changelog update >--------------------------------------------------------------- 90584af7d353e11e7d39fa842f10fd8741c92574 changelog.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/changelog.md b/changelog.md index c2a41f8..7800551 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,9 @@ # Changelog for [`directory` package](http://hackage.haskell.org/package/directory) +## Unreleased + + * Avoid stack overflow in `getDirectoryContents` [#17](https://github.com/haskell/directory/pull/17) + ## 1.2.2.0 *Jan 2014* * Bundled with GHC 7.10.1 From git at git.haskell.org Thu Mar 19 11:37:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:10 +0000 (UTC) Subject: [commit: packages/filepath] master: Improve the formatting of the generated code, makes the messages more pleasant (8916216) Message-ID: <20150319113710.9D1383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/8916216d3bb96be2b662a73c529c8a162384fbb4 >--------------------------------------------------------------- commit 8916216d3bb96be2b662a73c529c8a162384fbb4 Author: Neil Mitchell Date: Mon Nov 3 15:50:08 2014 +0000 Improve the formatting of the generated code, makes the messages more pleasant >--------------------------------------------------------------- 8916216d3bb96be2b662a73c529c8a162384fbb4 Generate.hs | 19 ++++++++++++++----- 1 file changed, 14 insertions(+), 5 deletions(-) diff --git a/Generate.hs b/Generate.hs index 4289fa2..36b19a2 100755 --- a/Generate.hs +++ b/Generate.hs @@ -21,7 +21,7 @@ main = do ,"import qualified System.FilePath.Posix as P" ,"tests :: [(String, Test)]" ,"tests ="] ++ - [" " ++ c ++ "(" ++ show t1 ++ "," ++ t2 ++ ")" | (c,(t1,t2)) <- zip ("[":repeat ",") tests] ++ + [" " ++ c ++ "(" ++ show t1 ++ ", " ++ t2 ++ ")" | (c,(t1,t2)) <- zip ("[":repeat ",") tests] ++ [" ]"] @@ -45,8 +45,8 @@ parseTest (stripPrefix "-- > " -> Just x) = platform $ toLexemes x where (a,b) = break (== "=>") x valid p x = free p [] x - free p val x = Test p [(ctor v, v) | v <- nub vars] x - where vars = [v | v@[c] <- x, isAlpha c] + free p val x = Test p [(ctor v, v) | v <- vars] x + where vars = nub $ sort [v | v@[c] <- x, isAlpha c] ctor v = if v < "x" then "" else if v `elem` val then "QFilePathValid" ++ show p else "QFilePath" parseTest _ = [] @@ -58,13 +58,22 @@ toLexemes x = case lex x of y -> error $ "Generate.toLexemes, " ++ show x ++ " -> " ++ show y +fromLexemes :: [String] -> String +fromLexemes = unwords . f + where + f ("`":x:"`":xs) = ("`" ++ x ++ "`") : f xs + f (x:y:xs) | x `elem` ["[","("] || y `elem` [",",")","]"] = f $ (x ++ y) : xs + f (x:xs) = x : f xs + f [] = [] + + renderTest :: Test -> (String, String) renderTest Test{..} = (body, code) where code = "test $ " ++ if null testVars then body else "\\" ++ unwords vars ++ " -> " ++ body - vars = ["(" ++ ctor ++ " " ++ v ++ ")" | (ctor,v) <- testVars] + vars = [if null ctor then v else "(" ++ ctor ++ " " ++ v ++ ")" | (ctor,v) <- testVars] - body = unwords $ map (qualify testPlatform) testBody + body = fromLexemes $ map (qualify testPlatform) testBody qualify :: PW -> String -> String From git at git.haskell.org Thu Mar 19 11:37:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:11 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Update `.cabal` and `changelog` re `SafeHaskell` (7139346) Message-ID: <20150319113711.B53883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/71393467c6ee004d3ccdde27df80c90b63926531/process >--------------------------------------------------------------- commit 71393467c6ee004d3ccdde27df80c90b63926531 Author: Herbert Valerio Riedel Date: Tue Nov 25 10:30:50 2014 +0100 Update `.cabal` and `changelog` re `SafeHaskell` >--------------------------------------------------------------- 71393467c6ee004d3ccdde27df80c90b63926531 changelog.md | 3 +++ process.cabal | 2 ++ 2 files changed, 5 insertions(+) diff --git a/changelog.md b/changelog.md index 86b04df..3f5647e 100644 --- a/changelog.md +++ b/changelog.md @@ -6,6 +6,9 @@ * Expose documentation for `System.Process.Internals` + * With GHC 7.10, `System.Cmd` and `System.Process` are now `Safe` + (when compiled with older GHC versions they are just `Trustworthy`) + ## 1.2.0.0 *Dec 2013* * Update to Cabal 1.10 format diff --git a/process.cabal b/process.cabal index f42d3c4..729faa9 100644 --- a/process.cabal +++ b/process.cabal @@ -38,6 +38,8 @@ library InterruptibleFFI RecordWildCards Trustworthy + if impl(ghc>=7.9) + other-extensions: Safe exposed-modules: System.Cmd From git at git.haskell.org Thu Mar 19 11:37:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:11 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Include README.md in tarball (f363f31) Message-ID: <20150319113711.E99D23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/f363f31ca24fe4c42e27bec4bed0001306406a99/directory >--------------------------------------------------------------- commit f363f31ca24fe4c42e27bec4bed0001306406a99 Author: Michael Snoyman Date: Tue Feb 17 15:46:22 2015 +0200 Include README.md in tarball >--------------------------------------------------------------- f363f31ca24fe4c42e27bec4bed0001306406a99 directory.cabal | 1 + 1 file changed, 1 insertion(+) diff --git a/directory.cabal b/directory.cabal index 83e4109..c648e0d 100644 --- a/directory.cabal +++ b/directory.cabal @@ -21,6 +21,7 @@ extra-tmp-files: extra-source-files: changelog.md + README.md config.guess config.sub configure From git at git.haskell.org Thu Mar 19 11:37:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:12 +0000 (UTC) Subject: [commit: packages/filepath] master: Improve the generator (c8d0498) Message-ID: <20150319113712.A4E073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/c8d0498f542ce5ea8c61c49dddf04cf32687d80b >--------------------------------------------------------------- commit c8d0498f542ce5ea8c61c49dddf04cf32687d80b Author: Neil Mitchell Date: Mon Nov 3 15:50:17 2014 +0000 Improve the generator >--------------------------------------------------------------- c8d0498f542ce5ea8c61c49dddf04cf32687d80b tests/TestGen.hs | 676 +++++++++++++++++++++++++++---------------------------- 1 file changed, 338 insertions(+), 338 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c8d0498f542ce5ea8c61c49dddf04cf32687d80b From git at git.haskell.org Thu Mar 19 11:37:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:13 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Add IsString instance for CmdSpec (6f91454) Message-ID: <20150319113713.BB7373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/6f9145466365ebc71b7e6a343f26b966e3c850d7/process >--------------------------------------------------------------- commit 6f9145466365ebc71b7e6a343f26b966e3c850d7 Author: Simon Hengel Date: Sat Nov 1 10:36:16 2014 +0800 Add IsString instance for CmdSpec >--------------------------------------------------------------- 6f9145466365ebc71b7e6a343f26b966e3c850d7 System/Process/Internals.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index d5cc90b..3de8944 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -45,6 +45,7 @@ module System.Process.Internals ( import Control.Concurrent import Control.Exception import Data.Bits +import Data.String import Foreign.C import Foreign.Marshal import Foreign.Ptr @@ -209,6 +210,10 @@ data CmdSpec -- for the Windows @SearchPath@ API. +-- | construct a `ShellCommand` from a string literal +instance IsString CmdSpec where + fromString = ShellCommand + data StdStream = Inherit -- ^ Inherit Handle from parent | UseHandle Handle -- ^ Use the supplied Handle From git at git.haskell.org Thu Mar 19 11:37:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:13 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Fix changelog (21e8bed) Message-ID: <20150319113713.F023A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/21e8bed9a0b6ed60e37c6174a936db68165453e5/directory >--------------------------------------------------------------- commit 21e8bed9a0b6ed60e37c6174a936db68165453e5 Author: Michael Snoyman Date: Tue Feb 17 15:49:24 2015 +0200 Fix changelog Why is 1.2.2.0 implied to be released already? >--------------------------------------------------------------- 21e8bed9a0b6ed60e37c6174a936db68165453e5 changelog.md | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/changelog.md b/changelog.md index 7800551..ed06b47 100644 --- a/changelog.md +++ b/changelog.md @@ -1,9 +1,5 @@ # Changelog for [`directory` package](http://hackage.haskell.org/package/directory) -## Unreleased - - * Avoid stack overflow in `getDirectoryContents` [#17](https://github.com/haskell/directory/pull/17) - ## 1.2.2.0 *Jan 2014* * Bundled with GHC 7.10.1 @@ -14,6 +10,8 @@ * Replace `throw` by better defined `throwIO`s + * Avoid stack overflow in `getDirectoryContents` [#17](https://github.com/haskell/directory/pull/17) + ## 1.2.1.0 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 11:37:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:14 +0000 (UTC) Subject: [commit: packages/filepath] master: Add a note that TestGen is generated (6a242ae) Message-ID: <20150319113714.AB9413A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/6a242ae72a88e4696d457db498a01221e42aa725 >--------------------------------------------------------------- commit 6a242ae72a88e4696d457db498a01221e42aa725 Author: Neil Mitchell Date: Mon Nov 3 15:51:14 2014 +0000 Add a note that TestGen is generated >--------------------------------------------------------------- 6a242ae72a88e4696d457db498a01221e42aa725 Generate.hs | 3 ++- tests/TestGen.hs | 1 + 2 files changed, 3 insertions(+), 1 deletion(-) diff --git a/Generate.hs b/Generate.hs index 36b19a2..573866a 100755 --- a/Generate.hs +++ b/Generate.hs @@ -15,7 +15,8 @@ main = do src <- readFile "System/FilePath/Internal.hs" let tests = map renderTest $ concatMap parseTest $ lines src writeFileBinaryChanged "tests/TestGen.hs" $ unlines $ - ["module TestGen(tests) where" + ["-- GENERATED CODE: See ../Generate.hs" + ,"module TestGen(tests) where" ,"import TestUtil" ,"import qualified System.FilePath.Windows as W" ,"import qualified System.FilePath.Posix as P" diff --git a/tests/TestGen.hs b/tests/TestGen.hs index bd5c29a..7bae497 100755 --- a/tests/TestGen.hs +++ b/tests/TestGen.hs @@ -1,3 +1,4 @@ +-- GENERATED CODE: See ../Generate.hs module TestGen(tests) where import TestUtil import qualified System.FilePath.Windows as W From git at git.haskell.org Thu Mar 19 11:37:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:15 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Add `changelog` entry for `IsString` & ver bump (339fb1a) Message-ID: <20150319113715.C2C043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/339fb1abd9ef1e70b842614b363aea6fe41af5b7/process >--------------------------------------------------------------- commit 339fb1abd9ef1e70b842614b363aea6fe41af5b7 Author: Herbert Valerio Riedel Date: Tue Nov 25 10:34:36 2014 +0100 Add `changelog` entry for `IsString` & ver bump A new instance requires at least a minor version bump, hence bump from 1.2.0 to 1.2.1 >--------------------------------------------------------------- 339fb1abd9ef1e70b842614b363aea6fe41af5b7 changelog.md | 4 +++- process.cabal | 2 +- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md index 3f5647e..896d581 100644 --- a/changelog.md +++ b/changelog.md @@ -1,9 +1,11 @@ # Changelog for [`process` package](http://hackage.haskell.org/package/process) -## 1.2.0.1 *TBA* +## 1.2.1.0 *TBA* * Add support for `base-4.8.0.0` + * New `IsString CmdSpec` instance + * Expose documentation for `System.Process.Internals` * With GHC 7.10, `System.Cmd` and `System.Process` are now `Safe` diff --git a/process.cabal b/process.cabal index 729faa9..a50146f 100644 --- a/process.cabal +++ b/process.cabal @@ -1,5 +1,5 @@ name: process -version: 1.2.0.1 +version: 1.2.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE From git at git.haskell.org Thu Mar 19 11:37:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:16 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master, tmp: Expose findExecutables #14 (2921280) Message-ID: <20150319113716.039ED3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master,tmp Link : http://ghc.haskell.org/trac/ghc/changeset/292128071c4dee154b43f9d3a40e9113a4da6e8b/directory >--------------------------------------------------------------- commit 292128071c4dee154b43f9d3a40e9113a4da6e8b Author: Michael Snoyman Date: Tue Feb 17 15:53:59 2015 +0200 Expose findExecutables #14 >--------------------------------------------------------------- 292128071c4dee154b43f9d3a40e9113a4da6e8b System/Directory.hs | 3 ++- changelog.md | 2 ++ 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/System/Directory.hs b/System/Directory.hs index 5e77f4d..8f9b2c1 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -46,6 +46,7 @@ module System.Directory , canonicalizePath , makeRelativeToCurrentDirectory , findExecutable + , findExecutables , findFile , findFiles , findFilesWith @@ -755,7 +756,7 @@ findExecutable fileName = do -- | Given a file name, searches for the file and returns a list of all -- occurences that are executable. -- --- /Since: 1.2.1.0/ +-- /Since: 1.2.2.0/ findExecutables :: String -> IO [FilePath] findExecutables binary = do #if defined(mingw32_HOST_OS) diff --git a/changelog.md b/changelog.md index ed06b47..361b37c 100644 --- a/changelog.md +++ b/changelog.md @@ -12,6 +12,8 @@ * Avoid stack overflow in `getDirectoryContents` [#17](https://github.com/haskell/directory/pull/17) + * Expose `findExecutables` [#14](https://github.com/haskell/directory/issues/14) + ## 1.2.1.0 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 11:37:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:16 +0000 (UTC) Subject: [commit: packages/filepath] master: Don't use Extra in the travis script, since filepath is required by extra (e86b6cd) Message-ID: <20150319113716.B1B6C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/e86b6cd97bcb6b4f535fc516d452b4214a4746b9 >--------------------------------------------------------------- commit e86b6cd97bcb6b4f535fc516d452b4214a4746b9 Author: Neil Mitchell Date: Tue Nov 4 19:21:35 2014 +0000 Don't use Extra in the travis script, since filepath is required by extra >--------------------------------------------------------------- e86b6cd97bcb6b4f535fc516d452b4214a4746b9 travis.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/travis.hs b/travis.hs index ae22fd2..887e56b 100755 --- a/travis.hs +++ b/travis.hs @@ -1,4 +1,8 @@ -import System.Process.Extra +import System.Exit +import System.Process + +main = do + ExitSuccess <- system "runhaskell Generate" + return () -main = system_ "runhaskell Generate" From git at git.haskell.org Thu Mar 19 11:37:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:17 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Expose createProcess_ and document UseHandle behavior #2 (8d9cde7) Message-ID: <20150319113717.CA3203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/8d9cde7744a239689baa6717482fc7208d1f7d6e/process >--------------------------------------------------------------- commit 8d9cde7744a239689baa6717482fc7208d1f7d6e Author: Michael Snoyman Date: Wed Nov 26 10:37:37 2014 +0200 Expose createProcess_ and document UseHandle behavior #2 >--------------------------------------------------------------- 8d9cde7744a239689baa6717482fc7208d1f7d6e System/Process.hs | 7 +++++++ System/Process/Internals.hs | 11 +++++++++++ changelog.md | 3 +++ 3 files changed, 21 insertions(+) diff --git a/System/Process.hs b/System/Process.hs index bff7f5d..a5f92ff 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -41,6 +41,7 @@ module System.Process ( -- * Running sub-processes createProcess, + createProcess_, shell, proc, CreateProcess(..), CmdSpec(..), @@ -179,6 +180,12 @@ To also set the directory in which to run @ls@: > createProcess (proc "ls" []){ cwd = Just "\home\bob", > std_out = CreatePipe } +Note that @Handle at s provided for @std_in@, @std_out@, or @std_err@ via the + at UseHandle@ constructor will be closed by calling this function. This is not +always the desired behavior. In cases where you would like to leave the + at Handle@ open after spawning the child process, please use 'createProcess_' +instead. + -} createProcess :: CreateProcess diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index 3de8944..b3fd8bd 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -222,6 +222,17 @@ data StdStream -- and newline translation mode (just -- like @Handle at s created by @openFile@). +-- | This function is almost identical to @createProcess at . The only differences +-- are: +-- +-- * @Handle at s provided via @UseHandle@ are not closed automatically. +-- +-- * This function takes an extra @String@ argument to be used in creating +-- error messages. +-- +-- This function has been available from the @System.Process.Internals@ module +-- for some time, and is part of the @System.Process@ module since version +-- 1.2.1.0. createProcess_ :: String -- ^ function name (for error messages) -> CreateProcess diff --git a/changelog.md b/changelog.md index 896d581..8a1d630 100644 --- a/changelog.md +++ b/changelog.md @@ -11,6 +11,9 @@ * With GHC 7.10, `System.Cmd` and `System.Process` are now `Safe` (when compiled with older GHC versions they are just `Trustworthy`) + * Expose `createProcess_` function, and document behavior of `UseHandle` for + `createProcess`. See [issue #2](https://github.com/haskell/process/issues/2). + ## 1.2.0.0 *Dec 2013* * Update to Cabal 1.10 format From git at git.haskell.org Thu Mar 19 11:37:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:18 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master: Update docs on Windows location of AppUserDataDirectory (a1ebcf8) Message-ID: <20150319113718.0AFBF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master Link : http://ghc.haskell.org/trac/ghc/changeset/a1ebcf8044874aaca380c44d044749d80628634a/directory >--------------------------------------------------------------- commit a1ebcf8044874aaca380c44d044749d80628634a Author: Phil Ruffwind Date: Wed Feb 18 01:53:23 2015 -0500 Update docs on Windows location of AppUserDataDirectory The location of AppUserDataDirectory since Windows Vista should be Users/user/AppData/Roaming rather than the archaic Documents and Settings/user/Application Data I think it's time for the docs to drop support for Windows XP :) >--------------------------------------------------------------- a1ebcf8044874aaca380c44d044749d80628634a System/Directory.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Directory.hs b/System/Directory.hs index 8f9b2c1..0a4e845 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -1124,7 +1124,7 @@ writable. On Unix, this function returns @$HOME\/.appName at . On Windows, a typical path might be -> C:/Documents And Settings/user/Application Data/appName +> C:/Users/user/AppData/Roaming/appName The operation may fail with: From git at git.haskell.org Thu Mar 19 11:37:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:18 +0000 (UTC) Subject: [commit: packages/filepath] master: Try making the travis script work even after you break directory (2bfbf70) Message-ID: <20150319113718.B7F593A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/2bfbf70c419cd35913c2687872d4712365f5168f >--------------------------------------------------------------- commit 2bfbf70c419cd35913c2687872d4712365f5168f Author: Neil Mitchell Date: Tue Nov 4 20:02:27 2014 +0000 Try making the travis script work even after you break directory >--------------------------------------------------------------- 2bfbf70c419cd35913c2687872d4712365f5168f travis.hs | 8 +------- 1 file changed, 1 insertion(+), 7 deletions(-) diff --git a/travis.hs b/travis.hs index 887e56b..5d52e76 100755 --- a/travis.hs +++ b/travis.hs @@ -1,8 +1,2 @@ -import System.Exit -import System.Process - -main = do - ExitSuccess <- system "runhaskell Generate" - return () - +import Generate From git at git.haskell.org Thu Mar 19 11:37:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:19 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Merge pull request #12 from snoyberg/master (3b10764) Message-ID: <20150319113719.D16C33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/3b1076454d6fb73281b4746d0ccbdbd047c95581/process >--------------------------------------------------------------- commit 3b1076454d6fb73281b4746d0ccbdbd047c95581 Merge: 339fb1a 8d9cde7 Author: Herbert Valerio Riedel Date: Fri Nov 28 16:41:59 2014 +0100 Merge pull request #12 from snoyberg/master very well then... :-) >--------------------------------------------------------------- 3b1076454d6fb73281b4746d0ccbdbd047c95581 System/Process.hs | 7 +++++++ System/Process/Internals.hs | 11 +++++++++++ changelog.md | 3 +++ 3 files changed, 21 insertions(+) From git at git.haskell.org Thu Mar 19 11:37:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:20 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master: Revert "Fix incorrect comment about removeDirectoryRecursive and symlinks" (692ae76) Message-ID: <20150319113720.12A8A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master Link : http://ghc.haskell.org/trac/ghc/changeset/692ae76983380871115bd3bb84182000f961aeda/directory >--------------------------------------------------------------- commit 692ae76983380871115bd3bb84182000f961aeda Author: Elliot Robinson Date: Wed Feb 18 15:13:37 2015 -0500 Revert "Fix incorrect comment about removeDirectoryRecursive and symlinks" This reverts commit db88005a736f88ac212152d69ce4002f4d852219. >--------------------------------------------------------------- 692ae76983380871115bd3bb84182000f961aeda System/Directory.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/System/Directory.hs b/System/Directory.hs index 8f9b2c1..c44cad6 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -457,10 +457,9 @@ removeDirectory path = #endif --- | @'removeDirectoryRecursive' dir@ removes an existing directory --- /dir/ together with its content and all subdirectories. If the --- directory contains symlinks this function removes but does not --- follow them. +-- | @'removeDirectoryRecursive' dir@ removes an existing directory /dir/ +-- together with its content and all subdirectories. Be careful, +-- if the directory contains symlinks, the function will follow them. removeDirectoryRecursive :: FilePath -> IO () removeDirectoryRecursive startLoc = do cont <- getDirectoryContents startLoc From git at git.haskell.org Thu Mar 19 11:37:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:20 +0000 (UTC) Subject: [commit: packages/filepath] master: Require GHC Head to pass (6854fc2) Message-ID: <20150319113720.BE36B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/6854fc27459e39085b9566456210170ed6aa5880 >--------------------------------------------------------------- commit 6854fc27459e39085b9566456210170ed6aa5880 Author: Neil Mitchell Date: Tue Nov 4 20:18:16 2014 +0000 Require GHC Head to pass >--------------------------------------------------------------- 6854fc27459e39085b9566456210170ed6aa5880 .travis.yml | 4 ---- 1 file changed, 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 8783444..ca85eb5 100644 --- a/.travis.yml +++ b/.travis.yml @@ -5,9 +5,5 @@ env: - GHCVER=7.8.3 - GHCVER=head -matrix: - allow_failures: - - env: GHCVER=head - script: - wget https://raw.github.com/ndmitchell/neil/master/travis.sh -O - --no-check-certificate --quiet | sh From git at git.haskell.org Thu Mar 19 11:37:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:21 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Implement System.Process.createPipe operation (0246baf) Message-ID: <20150319113721.DA3083A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/0246baf953e6b0d1b511f4d831528a9a5e8b71e2/process >--------------------------------------------------------------- commit 0246baf953e6b0d1b511f4d831528a9a5e8b71e2 Author: Johan Tibell Date: Sun Mar 30 17:18:12 2014 +0200 Implement System.Process.createPipe operation Neccesary for implementing 'tee' like behavior. See - http://comments.gmane.org/gmane.comp.lang.haskell.libraries/21373 - https://ghc.haskell.org/trac/ghc/ticket/8943 for more details. >--------------------------------------------------------------- 0246baf953e6b0d1b511f4d831528a9a5e8b71e2 System/{Process.hs => Process.hsc} | 61 ++++++++++++++++++++++++++++---------- changelog.md | 2 ++ 2 files changed, 48 insertions(+), 15 deletions(-) diff --git a/System/Process.hs b/System/Process.hsc similarity index 95% rename from System/Process.hs rename to System/Process.hsc index a5f92ff..4fca71e 100644 --- a/System/Process.hs +++ b/System/Process.hsc @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP #-} +{-# LANGUAGE CPP, ForeignFunctionInterface #-} #ifdef __GLASGOW_HASKELL__ #if __GLASGOW_HASKELL__ >= 709 {-# LANGUAGE Safe #-} @@ -25,19 +25,6 @@ -- ToDo: -- * Flag to control whether exiting the parent also kills the child. -{- NOTES on createPipe: - - createPipe is no longer exported, because of the following problems: - - - it wasn't used to implement runInteractiveProcess on Unix, because - the file descriptors for the unused ends of the pipe need to be closed - in the child process. - - - on Windows, a special version of createPipe is needed that sets - the inheritance flags correctly on the ends of the pipe (see - mkAnonPipe below). --} - module System.Process ( -- * Running sub-processes createProcess, @@ -68,6 +55,9 @@ module System.Process ( terminateProcess, interruptProcessGroupOf, + -- Interprocess communication + createPipe, + -- * Old deprecated functions -- | These functions pre-date 'createProcess' which is much more -- flexible. @@ -95,8 +85,14 @@ import System.Exit ( ExitCode(..) ) import System.IO import System.IO.Error (mkIOError, ioeSetErrorString) -#if !defined(mingw32_HOST_OS) +#if defined(mingw32_HOST_OS) +# include /* for _close and _pipe */ +# include /* for _O_BINARY */ +import Control.Exception (onException) +import Foreign.C.Types (CInt(..), CUInt(..)) +#else import System.Posix.Process (getProcessGroupIDOf) +import qualified System.Posix.IO as Posix import System.Posix.Types #endif @@ -887,3 +883,38 @@ rawSystem cmd args = system (showCommandForUser cmd args) #else rawSystem cmd args = system (showCommandForUser cmd args) #endif + +-- --------------------------------------------------------------------------- +-- createPipe + +-- | Create a pipe for interprocess communication and return a +-- @(readEnd, writeEnd)@ `Handle` pair. +-- +-- /Since: 1.2.1.0/ +createPipe :: IO (Handle, Handle) +#if !mingw32_HOST_OS +createPipe = do + (readfd, writefd) <- Posix.createPipe + readh <- Posix.fdToHandle readfd + writeh <- Posix.fdToHandle writefd + return (readh, writeh) +#else +createPipe = do + (readfd, writefd) <- allocaArray 2 $ \ pfds -> do + throwErrnoIfMinus1_ "_pipe" $ c__pipe pfds 2 (#const _O_BINARY) + readfd <- peek pfds + writefd <- peekElemOff pfds 1 + return (readfd, writefd) + (do readh <- fdToHandle readfd + writeh <- fdToHandle writefd + return (readh, writeh)) `onException` (close readfd >> close writefd) + +close :: CInt -> IO () +close = throwErrnoIfMinus1_ "_close" . c__close + +foreign import ccall "io.h _pipe" c__pipe :: + Ptr CInt -> CUInt -> CInt -> IO CInt + +foreign import ccall "io.h _close" c__close :: + CInt -> IO CInt +#endif diff --git a/changelog.md b/changelog.md index 8a1d630..13b5824 100644 --- a/changelog.md +++ b/changelog.md @@ -14,6 +14,8 @@ * Expose `createProcess_` function, and document behavior of `UseHandle` for `createProcess`. See [issue #2](https://github.com/haskell/process/issues/2). + * New `System.Process.createPipe` operation + ## 1.2.0.0 *Dec 2013* * Update to Cabal 1.10 format From git at git.haskell.org Thu Mar 19 11:37:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:22 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master: Clarifies the situations under which removeDirectoryRecursive may fail (fd8c99d) Message-ID: <20150319113722.19B443A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master Link : http://ghc.haskell.org/trac/ghc/changeset/fd8c99d7b36226f3485de83d4f953d54f61fbcb3/directory >--------------------------------------------------------------- commit fd8c99d7b36226f3485de83d4f953d54f61fbcb3 Author: Elliot Robinson Date: Wed Feb 18 15:16:33 2015 -0500 Clarifies the situations under which removeDirectoryRecursive may fail >--------------------------------------------------------------- fd8c99d7b36226f3485de83d4f953d54f61fbcb3 System/Directory.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/System/Directory.hs b/System/Directory.hs index c44cad6..d6d21eb 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -458,8 +458,9 @@ removeDirectory path = #endif -- | @'removeDirectoryRecursive' dir@ removes an existing directory /dir/ --- together with its content and all subdirectories. Be careful, --- if the directory contains symlinks, the function will follow them. +-- together with its content and all subdirectories. Be careful, if the +-- directory contains symlinks, this function will follow them if you don't +-- have permission to delete them. removeDirectoryRecursive :: FilePath -> IO () removeDirectoryRecursive startLoc = do cont <- getDirectoryContents startLoc From git at git.haskell.org Thu Mar 19 11:37:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:22 +0000 (UTC) Subject: [commit: packages/filepath] master: #9, add -<.> as an alias for replaceExtension (d4a47fb) Message-ID: <20150319113722.C6D6F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/d4a47fb1b28e5fd23388e05f12633eca0b36f519 >--------------------------------------------------------------- commit d4a47fb1b28e5fd23388e05f12633eca0b36f519 Author: Neil Mitchell Date: Mon Nov 10 07:33:44 2014 +0000 #9, add -<.> as an alias for replaceExtension >--------------------------------------------------------------- d4a47fb1b28e5fd23388e05f12633eca0b36f519 Generate.hs | 2 +- System/FilePath/Internal.hs | 10 ++++++++-- changelog.md | 2 ++ tests/TestGen.hs | 2 ++ 4 files changed, 13 insertions(+), 3 deletions(-) diff --git a/Generate.hs b/Generate.hs index 573866a..649f510 100755 --- a/Generate.hs +++ b/Generate.hs @@ -84,7 +84,7 @@ qualify pw str where prelude = ["elem","uncurry","snd","fst","not","null","if","then","else" ,"True","False","concat","isPrefixOf","isSuffixOf"] - fpops = ["","<.>"] + fpops = ["","<.>","-<.>"] --------------------------------------------------------------------- diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index af20ad6..e97bba5 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -58,7 +58,7 @@ module System.FilePath.MODULE_NAME -- * Extension methods splitExtension, - takeExtension, replaceExtension, dropExtension, addExtension, hasExtension, (<.>), + takeExtension, replaceExtension, (-<.>), dropExtension, addExtension, hasExtension, (<.>), splitExtensions, dropExtensions, takeExtensions, -- * Drive methods @@ -92,7 +92,7 @@ import Data.Maybe(isJust, fromJust) import System.Environment(getEnv) -infixr 7 <.> +infixr 7 <.>, -<.> infixr 5 @@ -228,6 +228,12 @@ splitExtension x = case nameDot of takeExtension :: FilePath -> String takeExtension = snd . splitExtension +-- | Remove the current extension and add another, an alias for 'replaceExtension'. +-- +-- > "foo.o" -<.> "c" == "foo.c" +(-<.>) :: FilePath -> String -> FilePath +(-<.>) = replaceExtension + -- | Set the extension of a file, overwriting one if already present. -- -- > replaceExtension "file.txt" ".bob" == "file.bob" diff --git a/changelog.md b/changelog.md index 807c652..f8e14f1 100644 --- a/changelog.md +++ b/changelog.md @@ -6,6 +6,8 @@ _Note: below all `FilePath` values are unquoted, so `\\` really means two backsl * Bundled with GHC 7.10.1 + * New function: Add `-<.>` as an alias for `replaceExtension`. + * Semantic change: `joinDrive /foo bar` now returns `/foo/bar`, instead of `/foobar` * Semantic change: on Windows, `splitSearchPath File1;\"File 2\"` now returns `[File1,File2]` instead of `[File1,\"File2\"]` diff --git a/tests/TestGen.hs b/tests/TestGen.hs index 7bae497..014275f 100755 --- a/tests/TestGen.hs +++ b/tests/TestGen.hs @@ -52,6 +52,8 @@ tests = ,("W.takeExtension (W.addExtension x \"ext\") == \".ext\"", test $ \(QFilePathValidW x) -> W.takeExtension (W.addExtension x "ext") == ".ext") ,("P.takeExtension (P.replaceExtension x \"ext\") == \".ext\"", test $ \(QFilePathValidP x) -> P.takeExtension (P.replaceExtension x "ext") == ".ext") ,("W.takeExtension (W.replaceExtension x \"ext\") == \".ext\"", test $ \(QFilePathValidW x) -> W.takeExtension (W.replaceExtension x "ext") == ".ext") + ,("\"foo.o\" P.-<.> \"c\" == \"foo.c\"", test $ "foo.o" P.-<.> "c" == "foo.c") + ,("\"foo.o\" W.-<.> \"c\" == \"foo.c\"", test $ "foo.o" W.-<.> "c" == "foo.c") ,("P.replaceExtension \"file.txt\" \".bob\" == \"file.bob\"", test $ P.replaceExtension "file.txt" ".bob" == "file.bob") ,("W.replaceExtension \"file.txt\" \".bob\" == \"file.bob\"", test $ W.replaceExtension "file.txt" ".bob" == "file.bob") ,("P.replaceExtension \"file.txt\" \"bob\" == \"file.bob\"", test $ P.replaceExtension "file.txt" "bob" == "file.bob") From git at git.haskell.org Thu Mar 19 11:37:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:23 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Tweak Haddock markup and add /since/-annotation (90540d7) Message-ID: <20150319113723.E17463A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/90540d7cf0435bf433b97186994b137ba3ffc41a/process >--------------------------------------------------------------- commit 90540d7cf0435bf433b97186994b137ba3ffc41a Author: Herbert Valerio Riedel Date: Thu Dec 18 22:22:03 2014 +0100 Tweak Haddock markup and add /since/-annotation >--------------------------------------------------------------- 90540d7cf0435bf433b97186994b137ba3ffc41a System/Process/Internals.hs | 16 ++++++++++------ 1 file changed, 10 insertions(+), 6 deletions(-) diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index b3fd8bd..90651d0 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -102,7 +102,7 @@ import System.FilePath -- ProcessHandle type {- | A handle to a process, which can be used to wait for termination - of the process using 'waitForProcess'. + of the process using 'System.Process.waitForProcess'. None of the process-creation functions in this library wait for termination: they all return a 'ProcessHandle' which may be used @@ -211,6 +211,8 @@ data CmdSpec -- | construct a `ShellCommand` from a string literal +-- +-- /Since: 1.2.1.0/ instance IsString CmdSpec where fromString = ShellCommand @@ -222,17 +224,19 @@ data StdStream -- and newline translation mode (just -- like @Handle at s created by @openFile@). --- | This function is almost identical to @createProcess at . The only differences --- are: +-- | This function is almost identical to +-- 'System.Process.createProcess'. The only differences are: -- --- * @Handle at s provided via @UseHandle@ are not closed automatically. +-- * 'Handle's provided via 'UseHandle' are not closed automatically. -- -- * This function takes an extra @String@ argument to be used in creating -- error messages. -- --- This function has been available from the @System.Process.Internals@ module --- for some time, and is part of the @System.Process@ module since version +-- This function has been available from the "System.Process.Internals" module +-- for some time, and is part of the "System.Process" module since version -- 1.2.1.0. +-- +-- /Since: 1.2.1.0/ createProcess_ :: String -- ^ function name (for error messages) -> CreateProcess From git at git.haskell.org Thu Mar 19 11:37:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:24 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master: Changelog update (d70feb5) Message-ID: <20150319113724.1FBD13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master Link : http://ghc.haskell.org/trac/ghc/changeset/d70feb54cfd795c43148c76a2d0ea99bb39a449c/directory >--------------------------------------------------------------- commit d70feb54cfd795c43148c76a2d0ea99bb39a449c Author: Elliot Robinson Date: Wed Feb 18 15:42:32 2015 -0500 Changelog update >--------------------------------------------------------------- d70feb54cfd795c43148c76a2d0ea99bb39a449c changelog.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/changelog.md b/changelog.md index 361b37c..79b8841 100644 --- a/changelog.md +++ b/changelog.md @@ -14,6 +14,8 @@ * Expose `findExecutables` [#14](https://github.com/haskell/directory/issues/14) + * Clarify conditions under which `removeDirectoryRecursive` may follow a symlink + ## 1.2.1.0 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 11:37:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:24 +0000 (UTC) Subject: [commit: packages/filepath] master: Note that any is a Prelude function (19006f6) Message-ID: <20150319113724.CDE7A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/19006f6dbf4924e20a83c7aea9b536bcb561e661 >--------------------------------------------------------------- commit 19006f6dbf4924e20a83c7aea9b536bcb561e661 Author: Neil Mitchell Date: Mon Nov 10 11:05:31 2014 +0000 Note that any is a Prelude function >--------------------------------------------------------------- 19006f6dbf4924e20a83c7aea9b536bcb561e661 Generate.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Generate.hs b/Generate.hs index 649f510..f0972fc 100755 --- a/Generate.hs +++ b/Generate.hs @@ -83,7 +83,7 @@ qualify pw str | otherwise = str where prelude = ["elem","uncurry","snd","fst","not","null","if","then","else" - ,"True","False","concat","isPrefixOf","isSuffixOf"] + ,"True","False","concat","isPrefixOf","isSuffixOf","any"] fpops = ["","<.>","-<.>"] From git at git.haskell.org Thu Mar 19 11:37:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:25 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Update changelog for 1.2.1.0 release (1a62f86) Message-ID: <20150319113725.E72C83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/1a62f86e77118520143985d9baf62d31a9d1c748/process >--------------------------------------------------------------- commit 1a62f86e77118520143985d9baf62d31a9d1c748 Author: Herbert Valerio Riedel Date: Thu Dec 18 22:22:29 2014 +0100 Update changelog for 1.2.1.0 release >--------------------------------------------------------------- 1a62f86e77118520143985d9baf62d31a9d1c748 changelog.md | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md index 13b5824..42719b4 100644 --- a/changelog.md +++ b/changelog.md @@ -1,9 +1,11 @@ # Changelog for [`process` package](http://hackage.haskell.org/package/process) -## 1.2.1.0 *TBA* +## 1.2.1.0 *Dec 2014* * Add support for `base-4.8.0.0` + * Remove Hugs98 specific code + * New `IsString CmdSpec` instance * Expose documentation for `System.Process.Internals` @@ -14,7 +16,8 @@ * Expose `createProcess_` function, and document behavior of `UseHandle` for `createProcess`. See [issue #2](https://github.com/haskell/process/issues/2). - * New `System.Process.createPipe` operation + * New `System.Process.createPipe` operation. + See also [GHC #8943](https://ghc.haskell.org/trac/ghc/ticket/8943) ## 1.2.0.0 *Dec 2013* From git at git.haskell.org Thu Mar 19 11:37:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:26 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master: Merge pull request #18 from Rufflewind/documentation-update (b2b1781) Message-ID: <20150319113726.266523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master Link : http://ghc.haskell.org/trac/ghc/changeset/b2b1781cccea31f392348abb8c31d6f7a839d55b/directory >--------------------------------------------------------------- commit b2b1781cccea31f392348abb8c31d6f7a839d55b Merge: d70feb5 a1ebcf8 Author: Phil Ruffwind Date: Sat Feb 21 02:44:32 2015 -0500 Merge pull request #18 from Rufflewind/documentation-update Update docs on Windows location of AppUserDataDirectory >--------------------------------------------------------------- b2b1781cccea31f392348abb8c31d6f7a839d55b System/Directory.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Thu Mar 19 11:37:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:26 +0000 (UTC) Subject: [commit: packages/filepath] master: If there is an error, show the messages again at the end, so you don't have to scroll back (7c628b3) Message-ID: <20150319113726.D4BCF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/7c628b352dd7367a6f8850ccd1bf2cfd7fad9235 >--------------------------------------------------------------- commit 7c628b352dd7367a6f8850ccd1bf2cfd7fad9235 Author: Neil Mitchell Date: Mon Nov 10 11:05:56 2014 +0000 If there is an error, show the messages again at the end, so you don't have to scroll back >--------------------------------------------------------------- 7c628b352dd7367a6f8850ccd1bf2cfd7fad9235 tests/Test.hs | 17 ++++++++++------- 1 file changed, 10 insertions(+), 7 deletions(-) diff --git a/tests/Test.hs b/tests/Test.hs index e3e0103..a7d82df 100755 --- a/tests/Test.hs +++ b/tests/Test.hs @@ -4,6 +4,7 @@ module Test(main) where import System.Environment import TestGen import Control.Monad +import Data.Maybe import Test.QuickCheck @@ -13,14 +14,16 @@ main = do let count = case args of i:_ -> read i; _ -> 10000 putStrLn $ "Testing with " ++ show count ++ " repetitions" let total = length tests - bs <- forM (zip [1..] tests) $ \(i,(msg,prop)) -> do + bad <- fmap catMaybes $ forM (zip [1..] tests) $ \(i,(msg,prop)) -> do putStrLn $ "Test " ++ show i ++ " of " ++ show total ++ ": " ++ msg res <- quickCheckWithResult stdArgs{chatty=False, maxSuccess=count} prop case res of - Success{} -> return True - _ -> putStrLn "TEST FAILURE!" >> return False - let bad = length $ filter (== False) bs - if bad == 0 then + Success{} -> return Nothing + bad -> do print bad; putStrLn "TEST FAILURE!"; return $ Just (msg,bad) + if null bad then putStrLn $ "Success, " ++ show total ++ " tests passed" - else - fail $ "FAILURE, failed " ++ show bad ++ " of " ++ show total ++ " tests (look for FAILURE)" + else do + putStrLn $ show (length bad) ++ " FAILURES\n" + forM_ (zip [1..] bad) $ \(i,(a,b)) -> + putStrLn $ "FAILURE " ++ show i ++ ": " ++ a ++ "\n" ++ show b ++ "\n" + fail $ "FAILURE, failed " ++ show (length bad) ++ " of " ++ show total ++ " tests" From git at git.haskell.org Thu Mar 19 11:37:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:27 +0000 (UTC) Subject: [commit: packages/process] master: Wait on child PID after pre-exec failure in child. (77dc6dc) Message-ID: <20150319113727.ED35B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/77dc6dc7142eb13104e2fbcc4d1ff706a48488d4/process >--------------------------------------------------------------- commit 77dc6dc7142eb13104e2fbcc4d1ff706a48488d4 Author: David Turner Date: Fri Jan 9 14:15:12 2015 +0000 Wait on child PID after pre-exec failure in child. >--------------------------------------------------------------- 77dc6dc7142eb13104e2fbcc4d1ff706a48488d4 cbits/runProcess.c | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/cbits/runProcess.c b/cbits/runProcess.c index 90bc2c9..e6d7c77 100644 --- a/cbits/runProcess.c +++ b/cbits/runProcess.c @@ -288,6 +288,11 @@ runInteractiveProcess (char *const args[], // get the errno of whatever else went wrong instead. errno = err; } + + // We forked the child, but the child had a problem and stopped so it's + // our responsibility to reap here as nobody else can. + waitpid(pid, NULL, 0); + pid = -1; } else if (r != 0) { From git at git.haskell.org Thu Mar 19 11:37:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:28 +0000 (UTC) Subject: [commit: packages/directory] improve-tests, improve-tests-for-real, master: Make behavior of `removeDirectoryRecursive` more consistent (ca34a87) Message-ID: <20150319113728.2D5F03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests,improve-tests-for-real,master Link : http://ghc.haskell.org/trac/ghc/changeset/ca34a8774fd19131d594972934940267483b27ab/directory >--------------------------------------------------------------- commit ca34a8774fd19131d594972934940267483b27ab Author: Phil Ruffwind Date: Sat Jan 31 18:41:34 2015 -0500 Make behavior of `removeDirectoryRecursive` more consistent The way `removeDirectoryRecursive dir` works right now is totally inconsistent: - If there's a directory-like symbolic link, the function removes it without recursing into it, *unless* the symbolic link is not removable for some reason (e.g. no permission), in which case it recurses into it and wipes out everything inside. - If `dir` itself is actually a directory-like symbolic link, it will recurse into it but fail to remove `dir` itself. The causes of these two problems are: - Instead of explicitly checking whether path refers to a true directory, it assumes any unremovable file that also satisfies `directoryExists` must necessarily be a directory. This is false, because `directoryExists` dereferences the symbolic link. - `getDirectoryContents` should not be called until `dir` is verified to be a true directory. There are two possible ways to handle the case where `dir` is not a true directory: - One can delete it silently, similar to the behavior of the POSIX command `rm -r`. - Or one can raise an error, similar to the behavior of the Python function `shutil.rmtree`. The former is more elegant to implement but for backward compatibility `removeDirectoryRecursive` shall retain the Python-like behavior. Another function `removePathRecursive` was added to implement the POSIX behavior, although the decision of to export this function will be left for the future. On Windows, there are two kinds of symbolic links: - directory symbolic links, and - file symbolic links. Directory symbolic links are treated as directories on Windows, which means `lstat` considers them directories and `DeleteFile` doesn't work. To remedy this, `removePathRecursive` was tweaked to handle these unusual cases and avoid following symbolic links. >--------------------------------------------------------------- ca34a8774fd19131d594972934940267483b27ab System/Directory.hs | 104 ++++++++++++++++++++++++++++++++-------------------- changelog.md | 4 +- 2 files changed, 68 insertions(+), 40 deletions(-) diff --git a/System/Directory.hs b/System/Directory.hs index beb30c8..6ed772e 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -406,6 +406,33 @@ createDirectoryIfMissing create_parents path0 | otherwise -> throwIO e #if __GLASGOW_HASKELL__ + +-- | * @'NotDirectory'@: not a directory. +-- * @'Directory'@: a true directory (not a symbolic link). +-- * @'DirectoryLink'@: a directory symbolic link (only exists on Windows). +data DirectoryType = NotDirectory + | Directory + | DirectoryLink + deriving (Enum, Eq, Ord, Read, Show) + +-- | Obtain the type of a directory. +getDirectoryType :: FilePath -> IO DirectoryType +getDirectoryType path = + (`ioeSetLocation` "getDirectoryType") `modifyIOError` do +#ifdef mingw32_HOST_OS + fmap classify (Win32.getFileAttributes path) + where fILE_ATTRIBUTE_REPARSE_POINT = 0x400 + classify attr + | attr .&. Win32.fILE_ATTRIBUTE_DIRECTORY == 0 = NotDirectory + | attr .&. fILE_ATTRIBUTE_REPARSE_POINT == 0 = Directory + | otherwise = DirectoryLink +#else + stat <- Posix.getSymbolicLinkStatus path + return $ if Posix.isDirectory stat + then Directory + else NotDirectory +#endif + {- | @'removeDirectory' dir@ removes an existing directory /dir/. The implementation may specify additional constraints which must be satisfied before a directory can be removed (e.g. the directory has to @@ -457,24 +484,39 @@ removeDirectory path = #endif --- | @'removeDirectoryRecursive' dir@ removes an existing directory /dir/ --- together with its content and all subdirectories. Be careful, if the --- directory contains symlinks, this function will follow them if you don't --- have permission to delete them. +-- | @'removeDirectoryRecursive' dir@ removes an existing directory /dir/ +-- together with its contents and subdirectories. Symbolic links are removed +-- without affecting their the targets. removeDirectoryRecursive :: FilePath -> IO () -removeDirectoryRecursive startLoc = do - cont <- getDirectoryContents startLoc - sequence_ [rm (startLoc x) | x <- cont, x /= "." && x /= ".."] - removeDirectory startLoc - where - rm :: FilePath -> IO () - rm f = do temp <- E.try (removeFile f) - case temp of - Left e -> do isDir <- doesDirectoryExist f - -- If f is not a directory, re-throw the error - unless isDir $ throwIO (e :: SomeException) - removeDirectoryRecursive f - Right _ -> return () +removeDirectoryRecursive path = + (`ioeSetLocation` "removeDirectoryRecursive") `modifyIOError` do + dirType <- getDirectoryType path + case dirType of + Directory -> removeContentsRecursive path + _ -> ioError . (`ioeSetErrorString` "not a directory") $ + mkIOError InappropriateType "" Nothing (Just path) + +-- | @'removePathRecursive' path@ removes an existing file or directory at +-- /path/ together with its contents and subdirectories. Symbolic links are +-- removed without affecting their the targets. +removePathRecursive :: FilePath -> IO () +removePathRecursive path = + (`ioeSetLocation` "removePathRecursive") `modifyIOError` do + dirType <- getDirectoryType path + case dirType of + NotDirectory -> removeFile path + Directory -> removeContentsRecursive path + DirectoryLink -> removeDirectory path + +-- | @'removeContentsRecursive' dir@ removes the contents of the directory +-- /dir/ recursively. Symbolic links are removed without affecting their the +-- targets. +removeContentsRecursive :: FilePath -> IO () +removeContentsRecursive path = + (`ioeSetLocation` "removeContentsRecursive") `modifyIOError` do + cont <- getDirectoryContents path + mapM_ removePathRecursive [path x | x <- cont, x /= "." && x /= ".."] + removeDirectory path #if __GLASGOW_HASKELL__ {- |'removeFile' /file/ removes the directory entry for an existing file @@ -635,21 +677,13 @@ Either path refers to an existing directory. -} renameFile :: FilePath -> FilePath -> IO () -renameFile opath npath = do +renameFile opath npath = (`ioeSetLocation` "renameFile") `modifyIOError` do -- XXX this test isn't performed atomically with the following rename -#ifdef mingw32_HOST_OS - -- ToDo: use Win32 API - withFileOrSymlinkStatus "renameFile" opath $ \st -> do - is_dir <- isDirectory st -#else - stat <- Posix.getSymbolicLinkStatus opath - let is_dir = Posix.isDirectory stat -#endif - if is_dir - then ioError (ioeSetErrorString - (mkIOError InappropriateType "renameFile" Nothing (Just opath)) - "is a directory") - else do + dirType <- getDirectoryType opath + case dirType of + Directory -> ioError . (`ioeSetErrorString` "is a directory") $ + mkIOError InappropriateType "" Nothing (Just opath) + _ -> return () #ifdef mingw32_HOST_OS Win32.moveFileEx opath npath Win32.mOVEFILE_REPLACE_EXISTING #else @@ -1038,14 +1072,6 @@ withFileStatus loc name f = do throwErrnoIfMinus1Retry_ loc (c_stat s p) f p -withFileOrSymlinkStatus :: String -> FilePath -> (Ptr CStat -> IO a) -> IO a -withFileOrSymlinkStatus loc name f = do - modifyIOError (`ioeSetFileName` name) $ - allocaBytes sizeof_stat $ \p -> - withFilePath name $ \s -> do - throwErrnoIfMinus1Retry_ loc (lstat s p) - f p - isDirectory :: Ptr CStat -> IO Bool isDirectory stat = do mode <- st_mode stat diff --git a/changelog.md b/changelog.md index 79b8841..bc2d62a 100644 --- a/changelog.md +++ b/changelog.md @@ -14,7 +14,9 @@ * Expose `findExecutables` [#14](https://github.com/haskell/directory/issues/14) - * Clarify conditions under which `removeDirectoryRecursive` may follow a symlink + * `removeDirectoryRecursive` no longer follows symlinks under any + circumstances, fixing the inconsistency as noted in + [#15](https://github.com/haskell/directory/issues/15) ## 1.2.1.0 *Mar 2014* From git at git.haskell.org Thu Mar 19 11:37:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:28 +0000 (UTC) Subject: [commit: packages/filepath] master: #11, more top-level documentation (ee1dd9e) Message-ID: <20150319113728.DB24A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/ee1dd9e8b1b1c227fe9f072f7204b1d70005dfed >--------------------------------------------------------------- commit ee1dd9e8b1b1c227fe9f072f7204b1d70005dfed Author: Neil Mitchell Date: Mon Nov 10 11:14:51 2014 +0000 #11, more top-level documentation >--------------------------------------------------------------- ee1dd9e8b1b1c227fe9f072f7204b1d70005dfed System/FilePath/Internal.hs | 45 ++++++++++++++++++++++++++++++--------------- 1 file changed, 30 insertions(+), 15 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index e97bba5..1f5c855 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -15,36 +15,51 @@ -- Stability : stable -- Portability : portable -- --- A library for FilePath manipulations, using MODULE_NAME style paths on +-- A library for 'FilePath' manipulations, using MODULE_NAME style paths on -- all platforms. Importing "System.FilePath" is usually better. -- --- Some short examples: +-- Given the eample 'FilePath': @\/directory\/file.ext@ -- --- You are given a C file, you want to figure out the corresponding object (.o) file: +-- We can use the following functions to extract pieces. -- --- @'replaceExtension' file \"o\"@ +-- * 'takeFileName' gives @\"file.ext\"@ -- --- Haskell module Main imports Test, you have the file named main: +-- * 'takeDirectory' gives @\"\/directory\"@ +-- +-- * 'takeExtension' gives @\".ext\"@ +-- +-- * 'dropExtension' gives @\"\/directory\/file\"@ +-- +-- * 'takeBaseName' gives @\"file\"@ +-- +-- And we could have built an equivalent path with the following expressions: +-- +-- * @\"\/directory\" '' \"file.ext\"@. +-- +-- * @\"\/directory\/file" '<.>' \"ext\"@. +-- +-- * @\"\/directory\/file.txt" '-<.>' \"ext\"@. +-- +-- Each function in this module is documented with several examples, +-- which are also used as tests. +-- +-- Here are a few examples of using the @filepath@ functions together: +-- +-- /Example 1:/ Find the possible locations of a Haskell module @Test@ imported from module @Main@: -- -- @['replaceFileName' path_to_main \"Test\" '<.>' ext | ext <- [\"hs\",\"lhs\"] ]@ -- --- You want to download a file from the web and save it to disk: +-- /Example 2:/ Download a file from @url@ and save it to disk: -- -- @do let file = 'makeValid' url -- System.IO.createDirectoryIfMissing True ('takeDirectory' file)@ -- --- You want to compile a Haskell file, but put the hi file under \"interface\" +-- /Example 3:/ Compile a Haskell file, putting the @.hi@ file under @interface@: -- --- @'takeDirectory' file '' \"interface\" '' ('takeFileName' file \`replaceExtension\` \"hi\"@) --- --- The examples in code format descibed by each function are used to generate --- tests, and should give clear semantics for the functions. +-- @'takeDirectory' file '' \"interface\" '' ('takeFileName' file '-<.>' \"hi\")@ -- -- References: --- [1] "Naming Files, Paths, and Namespaces" --- http://msdn.microsoft.com/en-us/library/windows/desktop/aa365247.aspx ------------------------------------------------------------------------------ - +-- [1] (Microsoft MSDN) module System.FilePath.MODULE_NAME ( -- * Separator predicates From git at git.haskell.org Thu Mar 19 11:37:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:29 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: If create process fails, reset ctl-C delegation (2293a4c) Message-ID: <20150319113729.F410C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/2293a4ca4cceba8e7ec42627f7e86eee6e6383cf/process >--------------------------------------------------------------- commit 2293a4ca4cceba8e7ec42627f7e86eee6e6383cf Author: Duncan Coutts Date: Sat Jan 10 20:45:37 2015 +0000 If create process fails, reset ctl-C delegation createProcess has a feature for delegated control-C handling. If createProcess fails to start the new process then we must undo the delegated control-C handling. This fixes issue #15. >--------------------------------------------------------------- 2293a4ca4cceba8e7ec42627f7e86eee6e6383cf System/Process/Internals.hs | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index 90651d0..e46ddb6 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -293,6 +293,8 @@ createProcess_ fun CreateProcess{ cmdspec = cmdsp, when (proc_handle == -1) $ do cFailedDoing <- peek pFailedDoing failedDoing <- peekCString cFailedDoing + when mb_delegate_ctlc + stopDelegateControlC throwErrno (fun ++ ": " ++ failedDoing) hndStdInput <- mbPipe mb_stdin pfdStdInput WriteMode @@ -349,8 +351,8 @@ startDelegateControlC = let !count' = count + 1 return (Just (count', old_int, old_quit)) -endDelegateControlC :: ExitCode -> IO () -endDelegateControlC exitCode = do +stopDelegateControlC :: IO () +stopDelegateControlC = modifyMVar_ runInteractiveProcess_delegate_ctlc $ \delegating -> do case delegating of Just (1, old_int, old_quit) -> do @@ -368,6 +370,10 @@ endDelegateControlC exitCode = do Nothing -> return Nothing -- should be impossible +endDelegateControlC :: ExitCode -> IO () +endDelegateControlC exitCode = do + stopDelegateControlC + -- And if the process did die due to SIGINT or SIGQUIT then -- we throw our equivalent exception here (synchronously). -- From git at git.haskell.org Thu Mar 19 11:37:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:30 +0000 (UTC) Subject: [commit: packages/directory] improve-tests: Add tests for removeDirectoryRecursive (8ae20b2) Message-ID: <20150319113730.35CFD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : improve-tests Link : http://ghc.haskell.org/trac/ghc/changeset/8ae20b245786056aeeb8c20e2cb5992237aee2c3/directory >--------------------------------------------------------------- commit 8ae20b245786056aeeb8c20e2cb5992237aee2c3 Author: Phil Ruffwind Date: Wed Feb 18 03:22:49 2015 -0500 Add tests for removeDirectoryRecursive >--------------------------------------------------------------- 8ae20b245786056aeeb8c20e2cb5992237aee2c3 directory.cabal | 8 +++- test/TestUtils.hs | 88 ++++++++++++++++++++++++++++++++++++++++ test/main.hs | 119 ++++++++++++++++++++++++++++++++++++++++++++++++------ 3 files changed, 201 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 8ae20b245786056aeeb8c20e2cb5992237aee2c3 From git at git.haskell.org Thu Mar 19 11:37:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:30 +0000 (UTC) Subject: [commit: packages/filepath] master: #11, give better section titles (772cc9b) Message-ID: <20150319113730.E26CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/772cc9bf352066660947f12e221a29a01a5d395c >--------------------------------------------------------------- commit 772cc9bf352066660947f12e221a29a01a5d395c Author: Neil Mitchell Date: Mon Nov 10 11:15:11 2014 +0000 #11, give better section titles >--------------------------------------------------------------- 772cc9bf352066660947f12e221a29a01a5d395c System/FilePath/Internal.hs | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 1f5c855..07eafb2 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -68,19 +68,15 @@ module System.FilePath.MODULE_NAME searchPathSeparator, isSearchPathSeparator, extSeparator, isExtSeparator, - -- * Path methods (environment $PATH) + -- * @$PATH@ methods splitSearchPath, getSearchPath, - -- * Extension methods + -- * Extension functions splitExtension, takeExtension, replaceExtension, (-<.>), dropExtension, addExtension, hasExtension, (<.>), splitExtensions, dropExtensions, takeExtensions, - -- * Drive methods - splitDrive, joinDrive, - takeDrive, hasDrive, dropDrive, isDrive, - - -- * Operations on a FilePath, as a list of directories + -- * Filename\/directory functions splitFileName, takeFileName, replaceFileName, dropFileName, takeBaseName, replaceBaseName, @@ -88,12 +84,16 @@ module System.FilePath.MODULE_NAME combine, (), splitPath, joinPath, splitDirectories, - -- * Low level FilePath operators + -- * Drive functions + splitDrive, joinDrive, + takeDrive, hasDrive, dropDrive, isDrive, + + -- * Trailing slash functions hasTrailingPathSeparator, addTrailingPathSeparator, dropTrailingPathSeparator, - -- * File name manipulators + -- * File name manipulations normalise, equalFilePath, makeRelative, isRelative, isAbsolute, From git at git.haskell.org Thu Mar 19 11:37:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:32 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: In cleanupProcess, stop the ctl-C delegation synchronously (3b5804e) Message-ID: <20150319113732.074853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/3b5804ebe54c672146994cfc525d45280650043e/process >--------------------------------------------------------------- commit 3b5804ebe54c672146994cfc525d45280650043e Author: Duncan Coutts Date: Sat Jan 10 20:52:10 2015 +0000 In cleanupProcess, stop the ctl-C delegation synchronously So it's immediate, rather than deferred to another thread (and until the process actually terminates). >--------------------------------------------------------------- 3b5804ebe54c672146994cfc525d45280650043e System/Process.hsc | 14 +++++++++++--- System/Process/Internals.hs | 1 + 2 files changed, 12 insertions(+), 3 deletions(-) diff --git a/System/Process.hsc b/System/Process.hsc index 4fca71e..4aadb50 100644 --- a/System/Process.hsc +++ b/System/Process.hsc @@ -236,7 +236,8 @@ withCreateProcess_ fun c action = cleanupProcess :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO () -cleanupProcess (mb_stdin, mb_stdout, mb_stderr, ph) = do +cleanupProcess (mb_stdin, mb_stdout, mb_stderr, + ph@(ProcessHandle _ delegating_ctlc)) = do terminateProcess ph -- Note, it's important that other threads that might be reading/writing -- these handles also get killed off, since otherwise they might be holding @@ -248,9 +249,16 @@ cleanupProcess (mb_stdin, mb_stdout, mb_stderr, ph) = do -- Indeed on Unix it's SIGTERM, which asks nicely but does not guarantee -- that it stops. If it doesn't stop, we don't want to hang, so we wait -- asynchronously using forkIO. - _ <- forkIO (waitForProcess ph >> return ()) - return () + -- However we want to end the Ctl-C handling synchronously, so we'll do + -- that synchronously, and set delegating_ctlc as False for the + -- waitForProcess (which would otherwise end the Ctl-C delegation itself). + when delegating_ctlc + stopDelegateControlC + _ <- forkIO (waitForProcess (resetCtlcDelegation ph) >> return ()) + return () + where + resetCtlcDelegation (ProcessHandle m _) = ProcessHandle m False -- ---------------------------------------------------------------------------- -- spawnProcess/spawnCommand diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index e46ddb6..e03e12c 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -33,6 +33,7 @@ module System.Process.Internals ( #endif startDelegateControlC, endDelegateControlC, + stopDelegateControlC, #if !defined(mingw32_HOST_OS) && !defined(__MINGW32__) pPrPr_disableITimers, c_execvpe, ignoreSignal, defaultSignal, From git at git.haskell.org Thu Mar 19 11:37:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:32 +0000 (UTC) Subject: [commit: packages/directory] improve-tests-for-real, master: Merge pull request #16 from Rufflewind/remove-directory-recursive (cd7b52e) Message-ID: <20150319113732.3C3CB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branches: improve-tests-for-real,master Link : http://ghc.haskell.org/trac/ghc/changeset/cd7b52e73fe9d6ea65714df1a2f4394060405100/directory >--------------------------------------------------------------- commit cd7b52e73fe9d6ea65714df1a2f4394060405100 Merge: b2b1781 ca34a87 Author: Phil Ruffwind Date: Sat Feb 21 19:56:17 2015 -0500 Merge pull request #16 from Rufflewind/remove-directory-recursive Make behavior of removeDirectoryRecursive more consistent >--------------------------------------------------------------- cd7b52e73fe9d6ea65714df1a2f4394060405100 System/Directory.hs | 104 ++++++++++++++++++++++++++++++++-------------------- changelog.md | 4 +- 2 files changed, 68 insertions(+), 40 deletions(-) From git at git.haskell.org Thu Mar 19 11:37:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:32 +0000 (UTC) Subject: [commit: packages/filepath] master: Optimise isPathSeparator (aeaeb4d) Message-ID: <20150319113732.EA4073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/aeaeb4da9044186087971bb14c076bea64e92c1f >--------------------------------------------------------------- commit aeaeb4da9044186087971bb14c076bea64e92c1f Author: Neil Mitchell Date: Mon Nov 10 11:15:23 2014 +0000 Optimise isPathSeparator >--------------------------------------------------------------- aeaeb4da9044186087971bb14c076bea64e92c1f System/FilePath/Internal.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 07eafb2..0e40fc6 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -151,7 +151,9 @@ pathSeparators = if isWindows then "\\/" else "/" -- -- > isPathSeparator a == (a `elem` pathSeparators) isPathSeparator :: Char -> Bool -isPathSeparator = (`elem` pathSeparators) +isPathSeparator '/' = True +isPathSeparator '\\' = isWindows +isPathSeparator _ = False -- | The character that is used to separate the entries in the $PATH environment variable. From git at git.haskell.org Thu Mar 19 11:37:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:34 +0000 (UTC) Subject: [commit: packages/process] master, wip/issue15: Remove some old stray debug code (5143c78) Message-ID: <20150319113734.0DAF83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: master,wip/issue15 Link : http://ghc.haskell.org/trac/ghc/changeset/5143c7895d9aeab37a7b72b416b855fe9c0cad87/process >--------------------------------------------------------------- commit 5143c7895d9aeab37a7b72b416b855fe9c0cad87 Author: Duncan Coutts Date: Sat Jan 10 20:49:43 2015 +0000 Remove some old stray debug code >--------------------------------------------------------------- 5143c7895d9aeab37a7b72b416b855fe9c0cad87 System/Process/Internals.hs | 4 ---- 1 file changed, 4 deletions(-) diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index e03e12c..03b19b3 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -335,7 +335,6 @@ startDelegateControlC = modifyMVar_ runInteractiveProcess_delegate_ctlc $ \delegating -> do case delegating of Nothing -> do --- print ("startDelegateControlC", "Nothing") -- We're going to ignore ^C in the parent while there are any -- processes using ^C delegation. -- @@ -347,7 +346,6 @@ startDelegateControlC = return (Just (1, old_int, old_quit)) Just (count, old_int, old_quit) -> do --- print ("startDelegateControlC", count) -- If we're already doing it, just increment the count let !count' = count + 1 return (Just (count', old_int, old_quit)) @@ -357,14 +355,12 @@ stopDelegateControlC = modifyMVar_ runInteractiveProcess_delegate_ctlc $ \delegating -> do case delegating of Just (1, old_int, old_quit) -> do --- print ("endDelegateControlC", exitCode, 1 :: Int) -- Last process, so restore the old signal handlers _ <- installHandler sigINT old_int Nothing _ <- installHandler sigQUIT old_quit Nothing return Nothing Just (count, old_int, old_quit) -> do --- print ("endDelegateControlC", exitCode, count) -- Not the last, just decrement the count let !count' = count - 1 return (Just (count', old_int, old_quit)) From git at git.haskell.org Thu Mar 19 11:37:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:34 +0000 (UTC) Subject: [commit: packages/directory] master: Fixes inconsistent results from calling canonicalizePath on an empty string (d1d3528) Message-ID: <20150319113734.44CCA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d1d35287c2b154e15f8f1587e35dd147f15c1ee9/directory >--------------------------------------------------------------- commit d1d35287c2b154e15f8f1587e35dd147f15c1ee9 Author: Elliot Robinson Date: Sun Feb 22 14:48:50 2015 -0500 Fixes inconsistent results from calling canonicalizePath on an empty string Calling canonicalizePath on an empty string now explicitly calls canonicalizePath on the current directory. This should fix #21 for all platforms. >--------------------------------------------------------------- d1d35287c2b154e15f8f1587e35dd147f15c1ee9 System/Directory.hs | 7 +++++- tests/all.T | 1 + tests/canonicalizePath001.hs | 28 ++++++++++++++++++++++ ...yExist001.stdout => canonicalizePath001.stdout} | 0 4 files changed, 35 insertions(+), 1 deletion(-) diff --git a/System/Directory.hs b/System/Directory.hs index 6ed772e..0a24e11 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -736,7 +736,11 @@ copyFile fromFPath toFPath = -- on paths that do not exist is known to vary from platform -- to platform. Some platforms do not alter the input, some -- do, and on some an exception will be thrown. +-- +-- If passed an empty string, behaviour is equivalent to +-- calling canonicalizePath on the current directory. canonicalizePath :: FilePath -> IO FilePath +canonicalizePath "" = canonicalizePath "." canonicalizePath fpath = #if defined(mingw32_HOST_OS) do path <- Win32.getFullPathName fpath @@ -744,7 +748,8 @@ canonicalizePath fpath = do enc <- getFileSystemEncoding GHC.withCString enc fpath $ \pInPath -> allocaBytes long_path_size $ \pOutPath -> - do _ <- throwErrnoPathIfNull "canonicalizePath" fpath $ c_realpath pInPath pOutPath + do _ <-c_realpath pInPath pOutPath + -- NB: pOutPath will be passed thru as result pointer by c_realpath path <- GHC.peekCString enc pOutPath #endif diff --git a/tests/all.T b/tests/all.T index 4efd688..a29a5d8 100644 --- a/tests/all.T +++ b/tests/all.T @@ -1,3 +1,4 @@ +test('canonicalizePath001', normal, compile_and_run, ['']) test('currentDirectory001', normal, compile_and_run, ['']) test('directory001', normal, compile_and_run, ['']) test('doesDirectoryExist001', normal, compile_and_run, ['']) diff --git a/tests/canonicalizePath001.hs b/tests/canonicalizePath001.hs new file mode 100644 index 0000000..48108a4 --- /dev/null +++ b/tests/canonicalizePath001.hs @@ -0,0 +1,28 @@ +module Main(main) where + +import Control.Concurrent +import Control.Monad +import Control.Exception +import System.Directory +import System.FilePath +import System.IO.Error + +main = do + dot <- canonicalizePath "." + nul <- (canonicalizePath "") + `catch` ((\_ -> return "") :: IOException -> IO String) + print $ dot == nul + +report :: Show a => IO a -> IO () +report io = do + r <- try io + case r of + Left e -> print (e :: SomeException) + Right a -> print a + +ignore :: IO a -> IO () +ignore io = do + r <- try io + case r of + Left e -> let _ = e :: SomeException in return () + Right a -> return () diff --git a/tests/doesDirectoryExist001.stdout b/tests/canonicalizePath001.stdout similarity index 100% copy from tests/doesDirectoryExist001.stdout copy to tests/canonicalizePath001.stdout From git at git.haskell.org Thu Mar 19 11:37:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:34 +0000 (UTC) Subject: [commit: packages/filepath] master: #10, more concrete examples (e6617ea) Message-ID: <20150319113734.F2CE23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/e6617ea7a96c4db3b251e631c2a7ef877ad16d79 >--------------------------------------------------------------- commit e6617ea7a96c4db3b251e631c2a7ef877ad16d79 Author: Neil Mitchell Date: Mon Nov 10 11:15:54 2014 +0000 #10, more concrete examples >--------------------------------------------------------------- e6617ea7a96c4db3b251e631c2a7ef877ad16d79 System/FilePath/Internal.hs | 66 +++++++++++++++++++++++++++++++++------------ tests/TestGen.hs | 66 +++++++++++++++++++++++++++++++++++++++++++-- 2 files changed, 113 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 e6617ea7a96c4db3b251e631c2a7ef877ad16d79 From git at git.haskell.org Thu Mar 19 11:37:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:36 +0000 (UTC) Subject: [commit: packages/directory] master: Fixes throwErrnoPathIfNull ommission in d1d3528 (933e173) Message-ID: <20150319113736.4B8103A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/933e1737cf2c46c300a0d5362f3175b61762c5cd/directory >--------------------------------------------------------------- commit 933e1737cf2c46c300a0d5362f3175b61762c5cd Author: Elliot Robinson Date: Sun Feb 22 15:06:14 2015 -0500 Fixes throwErrnoPathIfNull ommission in d1d3528 >--------------------------------------------------------------- 933e1737cf2c46c300a0d5362f3175b61762c5cd System/Directory.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Directory.hs b/System/Directory.hs index 0a24e11..7cbaa50 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -748,7 +748,7 @@ canonicalizePath fpath = do enc <- getFileSystemEncoding GHC.withCString enc fpath $ \pInPath -> allocaBytes long_path_size $ \pOutPath -> - do _ <-c_realpath pInPath pOutPath + do _ <- throwErrnoPathIfNull "canonicalizePath" fpath $ c_realpath pInPath pOutPath -- NB: pOutPath will be passed thru as result pointer by c_realpath path <- GHC.peekCString enc pOutPath From git at git.haskell.org Thu Mar 19 11:37:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:36 +0000 (UTC) Subject: [commit: packages/process] master: Improve docs of readProcess and readProcessWithExitCode (300ff16) Message-ID: <20150319113736.148373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/300ff16d32d4a8ef0493b9e3a6b6407c13cadc62/process >--------------------------------------------------------------- commit 300ff16d32d4a8ef0493b9e3a6b6407c13cadc62 Author: Duncan Coutts Date: Sat Jan 10 22:01:20 2015 +0000 Improve docs of readProcess and readProcessWithExitCode Stop claiming that they're simple wrappers. Fixes issue #3. >--------------------------------------------------------------- 300ff16d32d4a8ef0493b9e3a6b6407c13cadc62 System/Process.hsc | 38 +++++++++++++++----------------------- 1 file changed, 15 insertions(+), 23 deletions(-) diff --git a/System/Process.hsc b/System/Process.hsc index 4fca71e..bdbb9d0 100644 --- a/System/Process.hsc +++ b/System/Process.hsc @@ -372,17 +372,18 @@ processFailedException fun cmd args exit_code = -- | @readProcess@ forks an external process, reads its standard output -- strictly, blocking until the process terminates, and returns the output --- string. +-- string. The external process inherits the standard error. -- -- If an asynchronous exception is thrown to the thread executing --- @readProcess at . The forked process will be terminated and @readProcess@ will +-- @readProcess@, the forked process will be terminated and @readProcess@ will -- wait (block) until the process has been terminated. -- -- Output is returned strictly, so this is not suitable for -- interactive applications. -- -- This function throws an 'IOError' if the process 'ExitCode' is --- anything other than 'ExitSuccess'. +-- anything other than 'ExitSuccess'. If instead you want to get the +-- 'ExitCode' then use 'readProcessWithExitCode'. -- -- Users of this function should compile with @-threaded@ if they -- want other Haskell threads to keep running while waiting on @@ -435,26 +436,17 @@ readProcess cmd args input = do ExitSuccess -> return output ExitFailure r -> processFailedException "readProcess" cmd args r -{- | - at readProcessWithExitCode@ creates an external process, reads its -standard output and standard error strictly, waits until the process -terminates, and then returns the 'ExitCode' of the process, -the standard output, and the standard error. - -If an asynchronous exception is thrown to the thread executing - at readProcessWithExitCode@. The forked process will be terminated and - at readProcessWithExitCode@ will wait (block) until the process has been -terminated. - -'readProcess' and 'readProcessWithExitCode' are fairly simple wrappers -around 'createProcess'. Constructing variants of these functions is -quite easy: follow the link to the source code to see how -'readProcess' is implemented. - -On Unix systems, see 'waitForProcess' for the meaning of exit codes -when the process died as the result of a signal. --} - +-- | @readProcessWithExitCode@ is like @readProcess@ but with two differences: +-- +-- * it returns the 'ExitCode' of the process, and does not throw any +-- exception if the code is not 'ExitSuccess'. +-- +-- * it reads and returns the output from process' standard error handle, +-- rather than the process inheriting the standard error handle. +-- +-- On Unix systems, see 'waitForProcess' for the meaning of exit codes +-- when the process died as the result of a signal. +-- readProcessWithExitCode :: FilePath -- ^ Filename of the executable (see 'RawCommand' for details) -> [String] -- ^ any arguments From git at git.haskell.org Thu Mar 19 11:37:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:37 +0000 (UTC) Subject: [commit: packages/filepath] master: Bump the version after adding -<.> and changing semantics (f447a80) Message-ID: <20150319113737.0507D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/f447a8034d59a9426b4ba42964b745ba532ba6d1 >--------------------------------------------------------------- commit f447a8034d59a9426b4ba42964b745ba532ba6d1 Author: Neil Mitchell Date: Mon Nov 10 11:30:47 2014 +0000 Bump the version after adding -<.> and changing semantics >--------------------------------------------------------------- f447a8034d59a9426b4ba42964b745ba532ba6d1 changelog.md | 2 +- filepath.cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md index f8e14f1..2eb93c8 100644 --- a/changelog.md +++ b/changelog.md @@ -2,7 +2,7 @@ _Note: below all `FilePath` values are unquoted, so `\\` really means two backslashes. -## 1.3.0.3 *TBA* +## 1.3.1.0 *TBA* * Bundled with GHC 7.10.1 diff --git a/filepath.cabal b/filepath.cabal index 1aaed72..87b1f4c 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -1,5 +1,5 @@ name: filepath -version: 1.3.0.3 +version: 1.3.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE From git at git.haskell.org Thu Mar 19 11:37:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:38 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #14 from DaveCTurner/patch-1 (29f0480) Message-ID: <20150319113738.1C66F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/29f048030ce68e6e22e76ef0a2f7019ea46a49b2/process >--------------------------------------------------------------- commit 29f048030ce68e6e22e76ef0a2f7019ea46a49b2 Merge: 300ff16 77dc6dc Author: Duncan Coutts Date: Sun Jan 11 23:34:19 2015 +0000 Merge pull request #14 from DaveCTurner/patch-1 Wait on child PID after failed exec >--------------------------------------------------------------- 29f048030ce68e6e22e76ef0a2f7019ea46a49b2 cbits/runProcess.c | 5 +++++ 1 file changed, 5 insertions(+) From git at git.haskell.org Thu Mar 19 11:37:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:38 +0000 (UTC) Subject: [commit: packages/directory] master: Removes test T4113 as no longer relevant (dd65dca) Message-ID: <20150319113738.52A303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dd65dca8fc91e9b19e94ecd748e09a90012cfa48/directory >--------------------------------------------------------------- commit dd65dca8fc91e9b19e94ecd748e09a90012cfa48 Author: Elliot Robinson Date: Sun Feb 22 15:45:57 2015 -0500 Removes test T4113 as no longer relevant This test had expected failures pending resolution of 7604. 7604 was resolved in such a way that we can't determine reasonable output for T4113. canonicalizePath001 provides a reasonable replacement >--------------------------------------------------------------- dd65dca8fc91e9b19e94ecd748e09a90012cfa48 tests/T4113.hs | 19 ------------------- tests/T4113.stdout | 2 -- tests/T4113.stdout-mingw32 | 2 -- tests/all.T | 2 -- 4 files changed, 25 deletions(-) diff --git a/tests/T4113.hs b/tests/T4113.hs deleted file mode 100644 index e19f7d4..0000000 --- a/tests/T4113.hs +++ /dev/null @@ -1,19 +0,0 @@ - -module Main (main) where - -import Control.Exception -import System.Directory - -main :: IO () -main = do doit "" - doit "/no/such/file" - -doit :: FilePath -> IO () -doit fp = do fp' <- canonicalizePath fp - print (fp, mangle fp') - `catch` \e -> putStrLn ("Exception: " ++ show (e :: IOException)) - where -- On Windows, "/no/such/file" -> "C:\\no\\such\\file", so - -- we remove the drive letter so as to get consistent output - mangle (_ : ':' : xs) = "drive:" ++ xs - mangle xs = xs - diff --git a/tests/T4113.stdout b/tests/T4113.stdout deleted file mode 100644 index 86a7e9e..0000000 --- a/tests/T4113.stdout +++ /dev/null @@ -1,2 +0,0 @@ -Exception: : canonicalizePath: does not exist (No such file or directory) -Exception: /no/such/file: canonicalizePath: does not exist (No such file or directory) diff --git a/tests/T4113.stdout-mingw32 b/tests/T4113.stdout-mingw32 deleted file mode 100644 index 16f302c..0000000 --- a/tests/T4113.stdout-mingw32 +++ /dev/null @@ -1,2 +0,0 @@ -Exception: getFullPathName: invalid argument (The filename, directory name, or volume label syntax is incorrect.) -("/no/such/file","drive:\\no\\such\\file") diff --git a/tests/all.T b/tests/all.T index a29a5d8..bdde734 100644 --- a/tests/all.T +++ b/tests/all.T @@ -26,5 +26,3 @@ test('createDirectoryIfMissing001', normal, compile_and_run, ['']) # No sane way to tell whether the output is reasonable here... test('getHomeDirectory001', ignore_output, compile_and_run, ['']) \ No newline at end of file - -test('T4113', when(platform('i386-apple-darwin'), expect_broken(7604)), compile_and_run, ['']) From git at git.haskell.org Thu Mar 19 11:37:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:39 +0000 (UTC) Subject: [commit: packages/filepath] master: #22, put back in some makeRelative tests, far more restricted (e1e3d22) Message-ID: <20150319113739.0B9903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/e1e3d222a1c5bd23d712a92a68d03d5608dc7104 >--------------------------------------------------------------- commit e1e3d222a1c5bd23d712a92a68d03d5608dc7104 Author: Neil Mitchell Date: Mon Nov 10 18:13:55 2014 +0000 #22, put back in some makeRelative tests, far more restricted >--------------------------------------------------------------- e1e3d222a1c5bd23d712a92a68d03d5608dc7104 System/FilePath/Internal.hs | 4 +++- tests/TestGen.hs | 8 ++++++-- 2 files changed, 9 insertions(+), 3 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 62be343..3e8c952 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -738,8 +738,10 @@ equalFilePath a b = f a == f b -- There is no corresponding @makeAbsolute@ function, instead use -- @System.Directory.canonicalizePath@ which has the same effect. -- --- > Valid x y => equalFilePath x y || (isRelative x && makeRelative y x == x) || equalFilePath (y makeRelative y x) x +-- > makeRelative "/directory" "/directory/file.ext" == "file.ext" +-- > Valid x => makeRelative (takeDirectory x) x `equalFilePath` takeFileName x -- > makeRelative x x == "." +-- > Valid x y => equalFilePath x y || (isRelative x && makeRelative y x == x) || equalFilePath (y makeRelative y x) x -- > Windows: makeRelative "C:\\Home" "c:\\home\\bob" == "bob" -- > Windows: makeRelative "C:\\Home" "c:/home/bob" == "bob" -- > Windows: makeRelative "C:\\Home" "D:\\Home\\Bob" == "D:\\Home\\Bob" diff --git a/tests/TestGen.hs b/tests/TestGen.hs index 8510eff..a96ad54 100755 --- a/tests/TestGen.hs +++ b/tests/TestGen.hs @@ -325,10 +325,14 @@ tests = ,("not (P.equalFilePath \"foo\" \"FOO\")", test $ not (P.equalFilePath "foo" "FOO")) ,("W.equalFilePath \"foo\" \"FOO\"", test $ W.equalFilePath "foo" "FOO") ,("not (W.equalFilePath \"C:\" \"C:/\")", test $ not (W.equalFilePath "C:" "C:/")) - ,("P.equalFilePath x y || (P.isRelative x && P.makeRelative y x == x) || P.equalFilePath (y P. P.makeRelative y x) x", test $ \(QFilePathValidP x) (QFilePathValidP y) -> P.equalFilePath x y || (P.isRelative x && P.makeRelative y x == x) || P.equalFilePath (y P. P.makeRelative y x) x) - ,("W.equalFilePath x y || (W.isRelative x && W.makeRelative y x == x) || W.equalFilePath (y W. W.makeRelative y x) x", test $ \(QFilePathValidW x) (QFilePathValidW y) -> W.equalFilePath x y || (W.isRelative x && W.makeRelative y x == x) || W.equalFilePath (y W. W.makeRelative y x) x) + ,("P.makeRelative \"/directory\" \"/directory/file.ext\" == \"file.ext\"", test $ P.makeRelative "/directory" "/directory/file.ext" == "file.ext") + ,("W.makeRelative \"/directory\" \"/directory/file.ext\" == \"file.ext\"", test $ W.makeRelative "/directory" "/directory/file.ext" == "file.ext") + ,("P.makeRelative (P.takeDirectory x) x `P.equalFilePath` P.takeFileName x", test $ \(QFilePathValidP x) -> P.makeRelative (P.takeDirectory x) x `P.equalFilePath` P.takeFileName x) + ,("W.makeRelative (W.takeDirectory x) x `W.equalFilePath` W.takeFileName x", test $ \(QFilePathValidW x) -> W.makeRelative (W.takeDirectory x) x `W.equalFilePath` W.takeFileName x) ,("P.makeRelative x x == \".\"", test $ \(QFilePath x) -> P.makeRelative x x == ".") ,("W.makeRelative x x == \".\"", test $ \(QFilePath x) -> W.makeRelative x x == ".") + ,("P.equalFilePath x y || (P.isRelative x && P.makeRelative y x == x) || P.equalFilePath (y P. P.makeRelative y x) x", test $ \(QFilePathValidP x) (QFilePathValidP y) -> P.equalFilePath x y || (P.isRelative x && P.makeRelative y x == x) || P.equalFilePath (y P. P.makeRelative y x) x) + ,("W.equalFilePath x y || (W.isRelative x && W.makeRelative y x == x) || W.equalFilePath (y W. W.makeRelative y x) x", test $ \(QFilePathValidW x) (QFilePathValidW y) -> W.equalFilePath x y || (W.isRelative x && W.makeRelative y x == x) || W.equalFilePath (y W. W.makeRelative y x) x) ,("W.makeRelative \"C:\\\\Home\" \"c:\\\\home\\\\bob\" == \"bob\"", test $ W.makeRelative "C:\\Home" "c:\\home\\bob" == "bob") ,("W.makeRelative \"C:\\\\Home\" \"c:/home/bob\" == \"bob\"", test $ W.makeRelative "C:\\Home" "c:/home/bob" == "bob") ,("W.makeRelative \"C:\\\\Home\" \"D:\\\\Home\\\\Bob\" == \"D:\\\\Home\\\\Bob\"", test $ W.makeRelative "C:\\Home" "D:\\Home\\Bob" == "D:\\Home\\Bob") From git at git.haskell.org Thu Mar 19 11:37:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:40 +0000 (UTC) Subject: [commit: packages/process] master: Add GHC 7.10.1 to test-matrix; update to GHC 7.8.4 (58e8963) Message-ID: <20150319113740.218FC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/58e896360f3cdc577f99fee3d3bfafb7964e76c2/process >--------------------------------------------------------------- commit 58e896360f3cdc577f99fee3d3bfafb7964e76c2 Author: Herbert Valerio Riedel Date: Wed Jan 14 08:26:44 2015 +0100 Add GHC 7.10.1 to test-matrix; update to GHC 7.8.4 >--------------------------------------------------------------- 58e896360f3cdc577f99fee3d3bfafb7964e76c2 .travis.yml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index ddb661a..a3096e5 100644 --- a/.travis.yml +++ b/.travis.yml @@ -5,7 +5,8 @@ env: # we have to use CABALVER=1.16 for GHC<7.6 as well, as there's # no package for earlier cabal versions in the PPA - GHCVER=7.6.3 CABALVER=1.16 - - GHCVER=7.8.3 CABALVER=1.18 + - GHCVER=7.8.4 CABALVER=1.18 + - GHCVER=7.10.1 CABALVER=1.22 - GHCVER=head CABALVER=head matrix: From git at git.haskell.org Thu Mar 19 11:37:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:40 +0000 (UTC) Subject: [commit: packages/directory] master: Cleans up canonicalizePath (abfa69b) Message-ID: <20150319113740.584CE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/abfa69b28b55ff2dd2b541f8c881b028b960cc7e/directory >--------------------------------------------------------------- commit abfa69b28b55ff2dd2b541f8c881b028b960cc7e Author: Elliot Robinson Date: Sun Feb 22 15:46:11 2015 -0500 Cleans up canonicalizePath >--------------------------------------------------------------- abfa69b28b55ff2dd2b541f8c881b028b960cc7e tests/canonicalizePath001.hs | 20 +------------------- 1 file changed, 1 insertion(+), 19 deletions(-) diff --git a/tests/canonicalizePath001.hs b/tests/canonicalizePath001.hs index 48108a4..dc21cd8 100644 --- a/tests/canonicalizePath001.hs +++ b/tests/canonicalizePath001.hs @@ -1,28 +1,10 @@ module Main(main) where -import Control.Concurrent -import Control.Monad import Control.Exception import System.Directory -import System.FilePath -import System.IO.Error main = do dot <- canonicalizePath "." nul <- (canonicalizePath "") `catch` ((\_ -> return "") :: IOException -> IO String) - print $ dot == nul - -report :: Show a => IO a -> IO () -report io = do - r <- try io - case r of - Left e -> print (e :: SomeException) - Right a -> print a - -ignore :: IO a -> IO () -ignore io = do - r <- try io - case r of - Left e -> let _ = e :: SomeException in return () - Right a -> return () + print (dot == nul) From git at git.haskell.org Thu Mar 19 11:37:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:41 +0000 (UTC) Subject: [commit: packages/filepath] master: When there is a failure, show the QuickCheck output in a better format (2d7ddec) Message-ID: <20150319113741.110F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/2d7ddec7db144e8a3c3612b060603b15e97b9e18 >--------------------------------------------------------------- commit 2d7ddec7db144e8a3c3612b060603b15e97b9e18 Author: Neil Mitchell Date: Mon Nov 10 18:14:11 2014 +0000 When there is a failure, show the QuickCheck output in a better format >--------------------------------------------------------------- 2d7ddec7db144e8a3c3612b060603b15e97b9e18 tests/Test.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/tests/Test.hs b/tests/Test.hs index a7d82df..b9b695b 100755 --- a/tests/Test.hs +++ b/tests/Test.hs @@ -14,16 +14,17 @@ main = do let count = case args of i:_ -> read i; _ -> 10000 putStrLn $ "Testing with " ++ show count ++ " repetitions" let total = length tests + let showOutput x = show x{output=""} ++ "\n" ++ output x bad <- fmap catMaybes $ forM (zip [1..] tests) $ \(i,(msg,prop)) -> do putStrLn $ "Test " ++ show i ++ " of " ++ show total ++ ": " ++ msg res <- quickCheckWithResult stdArgs{chatty=False, maxSuccess=count} prop case res of Success{} -> return Nothing - bad -> do print bad; putStrLn "TEST FAILURE!"; return $ Just (msg,bad) + bad -> do putStrLn $ showOutput bad; putStrLn "TEST FAILURE!"; return $ Just (msg,bad) if null bad then putStrLn $ "Success, " ++ show total ++ " tests passed" else do putStrLn $ show (length bad) ++ " FAILURES\n" forM_ (zip [1..] bad) $ \(i,(a,b)) -> - putStrLn $ "FAILURE " ++ show i ++ ": " ++ a ++ "\n" ++ show b ++ "\n" + putStrLn $ "FAILURE " ++ show i ++ ": " ++ a ++ "\n" ++ showOutput b ++ "\n" fail $ "FAILURE, failed " ++ show (length bad) ++ " of " ++ show total ++ " tests" From git at git.haskell.org Thu Mar 19 11:37:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:42 +0000 (UTC) Subject: [commit: packages/process] master: Merge branch 'wip/issue15' (7d516fc) Message-ID: <20150319113742.28F5A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7d516fc0a9a017b7f30d2441993bcc6e093a344a/process >--------------------------------------------------------------- commit 7d516fc0a9a017b7f30d2441993bcc6e093a344a Merge: 58e8963 5143c78 Author: Herbert Valerio Riedel Date: Thu Jan 15 13:25:38 2015 +0100 Merge branch 'wip/issue15' >--------------------------------------------------------------- 7d516fc0a9a017b7f30d2441993bcc6e093a344a System/Process.hsc | 14 +++++++++++--- System/Process/Internals.hs | 15 +++++++++------ 2 files changed, 20 insertions(+), 9 deletions(-) From git at git.haskell.org Thu Mar 19 11:37:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:42 +0000 (UTC) Subject: [commit: packages/directory] tmp: Test something using Travis (5522a30) Message-ID: <20150319113742.5F3D73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : tmp Link : http://ghc.haskell.org/trac/ghc/changeset/5522a30b6c126d446600524d5c8b181ebdbc06bb/directory >--------------------------------------------------------------- commit 5522a30b6c126d446600524d5c8b181ebdbc06bb Author: Phil Ruffwind Date: Wed Feb 25 07:31:53 2015 -0500 Test something using Travis >--------------------------------------------------------------- 5522a30b6c126d446600524d5c8b181ebdbc06bb System/Directory.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Directory.hs b/System/Directory.hs index 8f9b2c1..eab5e99 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -400,7 +400,7 @@ createDirectoryIfMissing create_parents path0 #else canIgnore <- (Posix.isDirectory `fmap` Posix.getFileStatus dir) #endif - `E.catch` ((\ _ -> return (isAlreadyExistsError e)) + `catchIOError` ((\ _ -> return (isAlreadyExistsError e)) :: IOException -> IO Bool) unless canIgnore (throwIO e) | otherwise -> throwIO e From git at git.haskell.org Thu Mar 19 11:37:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:43 +0000 (UTC) Subject: [commit: packages/filepath] master: Change to https links (cc162a6) Message-ID: <20150319113743.17D593A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/cc162a69a2474066e31b891eb82e49b76bab19f6 >--------------------------------------------------------------- commit cc162a69a2474066e31b891eb82e49b76bab19f6 Author: Neil Mitchell Date: Fri Nov 21 08:25:16 2014 +0000 Change to https links >--------------------------------------------------------------- cc162a69a2474066e31b891eb82e49b76bab19f6 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index bf67c71..33fdce7 100644 --- a/README.md +++ b/README.md @@ -1,4 +1,4 @@ -# FilePath [![Hackage version](https://img.shields.io/hackage/v/filepath.svg?style=flat)](http://hackage.haskell.org/package/filepath) [![Build Status](http://img.shields.io/travis/haskell/filepath.svg?style=flat)](https://travis-ci.org/haskell/filepath) +# FilePath [![Hackage version](https://img.shields.io/hackage/v/filepath.svg?style=flat)](https://hackage.haskell.org/package/filepath) [![Build Status](https://img.shields.io/travis/haskell/filepath.svg?style=flat)](https://travis-ci.org/haskell/filepath) The `filepath` package provides functionality for manipulating `FilePath` values, and is shipped with both [GHC](https://www.haskell.org/ghc/) and the [Haskell Platform](https://www.haskell.org/platform/). It provides three modules: From git at git.haskell.org Thu Mar 19 11:37:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:44 +0000 (UTC) Subject: [commit: packages/process] master: Bump version to 1.2.2.0 and update changelog (93d8b62) Message-ID: <20150319113744.2EBF73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/93d8b624252feea034683508eb3f112f9dc76662/process >--------------------------------------------------------------- commit 93d8b624252feea034683508eb3f112f9dc76662 Author: Herbert Valerio Riedel Date: Thu Jan 15 13:32:44 2015 +0100 Bump version to 1.2.2.0 and update changelog This adds changelog entries for the issues #14 and #15 addressed in 1.2.2 so far. >--------------------------------------------------------------- 93d8b624252feea034683508eb3f112f9dc76662 changelog.md | 9 +++++++++ process.cabal | 2 +- 2 files changed, 10 insertions(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index 42719b4..debfcaa 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,14 @@ # Changelog for [`process` package](http://hackage.haskell.org/package/process) +## 1.2.2.0 *Jan 2015* + + * Fix delegated CTRL-C handling in `createProcess` in case of failed + process creation. See [issue #15](https://github.com/haskell/process/issues/15) + for more details. + + * `waitpid` on child PID after pre-exec failure in child to prevent zombies. + See also [issue #14](https://github.com/haskell/process/issues/14). + ## 1.2.1.0 *Dec 2014* * Add support for `base-4.8.0.0` diff --git a/process.cabal b/process.cabal index a50146f..cfdd7a4 100644 --- a/process.cabal +++ b/process.cabal @@ -1,5 +1,5 @@ name: process -version: 1.2.1.0 +version: 1.2.2.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE From git at git.haskell.org Thu Mar 19 11:37:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:44 +0000 (UTC) Subject: [commit: packages/directory] improve-tests-for-real: Automatically run the GHC test framework (41e1131) Message-ID: <20150319113744.669543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : improve-tests-for-real Link : http://ghc.haskell.org/trac/ghc/changeset/41e11313bdc171ab7b570acf21622eae598a5138/directory >--------------------------------------------------------------- commit 41e11313bdc171ab7b570acf21622eae598a5138 Author: Phil Ruffwind Date: Sun Mar 1 16:02:42 2015 -0500 Automatically run the GHC test framework >--------------------------------------------------------------- 41e11313bdc171ab7b570acf21622eae598a5138 testsuite/ghc.patch | 62 +++++++++++++++++++++++++++++++++++++++++++++++++++++ testsuite/run | 35 ++++++++++++++++++++++++++++++ 2 files changed, 97 insertions(+) diff --git a/testsuite/ghc.patch b/testsuite/ghc.patch new file mode 100644 index 0000000..61ce567 --- /dev/null +++ b/testsuite/ghc.patch @@ -0,0 +1,62 @@ +# allow ghc and its tools to be located in different directories +--- testsuite/mk/boilerplate.mk ++++ testsuite/mk/boilerplate.mk +@@ -56,6 +56,7 @@ TEST_HC := $(STAGE2_GHC) + endif + + else ++implicit_compiler = YES + IN_TREE_COMPILER = NO + TEST_HC := $(shell which ghc) + endif +@@ -87,24 +88,30 @@ endif + # containing spaces + BIN_ROOT = $(shell dirname '$(TEST_HC)') + ++ifeq "$(implicit_compiler)" "YES" ++find_tool = $(shell which $(1)) ++else ++find_tool = $(BIN_ROOT)/$(1) ++endif ++ + ifeq "$(GHC_PKG)" "" +-GHC_PKG := $(BIN_ROOT)/ghc-pkg ++GHC_PKG := $(call find_tool,ghc-pkg) + endif + + ifeq "$(RUNGHC)" "" +-RUNGHC := $(BIN_ROOT)/runghc ++RUNGHC := $(call find_tool,runghc) + endif + + ifeq "$(HSC2HS)" "" +-HSC2HS := $(BIN_ROOT)/hsc2hs ++HSC2HS := $(call find_tool,hsc2hs) + endif + + ifeq "$(HP2PS_ABS)" "" +-HP2PS_ABS := $(BIN_ROOT)/hp2ps ++HP2PS_ABS := $(call find_tool,hp2ps) + endif + + ifeq "$(HPC)" "" +-HPC := $(BIN_ROOT)/hpc ++HPC := $(call find_tool,hpc) + endif + + $(eval $(call canonicaliseExecutable,TEST_HC)) + +# 'die' is not available until GHC 7.10 +--- testsuite/timeout/timeout.hs ++++ testsuite/timeout/timeout.hs +@@ -30,8 +30,8 @@ main = do + [secs,cmd] -> + case reads secs of + [(secs', "")] -> run secs' cmd +- _ -> die ("Can't parse " ++ show secs ++ " as a number of seconds") +- _ -> die ("Bad arguments " ++ show args) ++ _ -> ((>> exitFailure) . hPutStrLn stderr) ("Can't parse " ++ show secs ++ " as a number of seconds") ++ _ -> ((>> exitFailure) . hPutStrLn stderr) ("Bad arguments " ++ show args) + + timeoutMsg :: String + timeoutMsg = "Timeout happened...killing process..." diff --git a/testsuite/run b/testsuite/run new file mode 100755 index 0000000..6725d39 --- /dev/null +++ b/testsuite/run @@ -0,0 +1,35 @@ +#!/bin/sh +# run all of the tests under the `tests` directory using the GHC test +# framework; for more info about this framework, see: +# https://ghc.haskell.org/trac/ghc/wiki/Building/RunningTests +# +# arguments received by this script are passed as arguments to the `make` +# invocation that initiates the tests +set -e + +[ -z "$HSFLAGS" ] || HSFLAGS=\ $HSFLAGS +HSFLAGS='-package-db ../dist/package.conf.inplace '$HSFLAGS +HSFLAGS='-optP-include -optP../dist/build/autogen/cabal_macros.h '$HSFLAGS +export HSFLAGS + +# download the GHC repository +[ -d dist/testsuite/ghc ] || { + git clone --depth 1 https://github.com/ghc/ghc dist/testsuite/ghc + patch dist/testsuite/Makefile \ + "s|^TOP=.*$|TOP=../dist/testsuite/ghc/testsuite|" \ + tests/Makefile + +# there's no way to pass arguments when `sh` is in `-s` mode, so we have to +# write the shell commands to an actual file +cat >dist/testsuite/run.sh <<"EOF" +cd tests +make -f ../dist/testsuite/Makefile WAY=normal EXTRA_HC_OPTS="$HSFLAGS" "$@" +EOF + +cabal build +exec cabal exec sh -- -e dist/testsuite/run.sh "$@" From git at git.haskell.org Thu Mar 19 11:37:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:45 +0000 (UTC) Subject: [commit: packages/filepath] master: Avoid using isJust/fromJust, switch to pattern guards (acf23e1) Message-ID: <20150319113745.1F2DF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/acf23e116c039143af56896874033825cc1b7c73 >--------------------------------------------------------------- commit acf23e116c039143af56896874033825cc1b7c73 Author: Neil Mitchell Date: Fri Nov 21 16:30:25 2014 +0000 Avoid using isJust/fromJust, switch to pattern guards >--------------------------------------------------------------- acf23e116c039143af56896874033825cc1b7c73 System/FilePath/Internal.hs | 16 +++++----------- 1 file changed, 5 insertions(+), 11 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index 3e8c952..f7b3469 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -1,6 +1,7 @@ #if __GLASGOW_HASKELL__ >= 704 {-# LANGUAGE Safe #-} #endif +{-# LANGUAGE PatternGuards #-} -- This template expects CPP definitions for: -- MODULE_NAME = Posix | Windows @@ -102,7 +103,7 @@ module System.FilePath.MODULE_NAME where import Data.Char(toLower, toUpper, isAsciiLower, isAsciiUpper) -import Data.Maybe(isJust, fromJust) +import Data.Maybe(isJust) import System.Environment(getEnv) @@ -366,16 +367,9 @@ isLetter x = isAsciiLower x || isAsciiUpper x -- > Posix: splitDrive "file" == ("","file") splitDrive :: FilePath -> (FilePath, FilePath) splitDrive x | isPosix = span (== '/') x - -splitDrive x | isJust y = fromJust y - where y = readDriveLetter x - -splitDrive x | isJust y = fromJust y - where y = readDriveUNC x - -splitDrive x | isJust y = fromJust y - where y = readDriveShare x - +splitDrive x | Just y <- readDriveLetter x = y +splitDrive x | Just y <- readDriveUNC x = y +splitDrive x | Just y <- readDriveShare x = y splitDrive x = ("",x) addSlash :: FilePath -> FilePath -> (FilePath, FilePath) From git at git.haskell.org Thu Mar 19 11:37:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:46 +0000 (UTC) Subject: [commit: packages/process] master: Add test case for GHC Trac 3649 (fa25980) Message-ID: <20150319113746.37B6B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fa2598000f61235a319c6f9697e1f21808d6ba31/process >--------------------------------------------------------------- commit fa2598000f61235a319c6f9697e1f21808d6ba31 Author: Michael Snoyman Date: Tue Feb 17 16:28:03 2015 +0200 Add test case for GHC Trac 3649 >--------------------------------------------------------------- fa2598000f61235a319c6f9697e1f21808d6ba31 .travis.yml | 3 ++- process.cabal | 8 ++++++++ test/main.hs | 14 ++++++++++++++ 3 files changed, 24 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index a3096e5..ee93e6f 100644 --- a/.travis.yml +++ b/.travis.yml @@ -27,9 +27,10 @@ install: script: - autoreconf -i - - cabal configure -v2 + - cabal configure -v2 --enable-tests - cabal build - cabal check || [ "$CABALVER" == "1.16" ] + - ./dist/build/test/test # Using cabal test was giving trouble with cabal 1.22 - cabal sdist # The following scriptlet checks that the resulting source distribution can be built & installed - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; diff --git a/process.cabal b/process.cabal index cfdd7a4..d33e7bc 100644 --- a/process.cabal +++ b/process.cabal @@ -68,3 +68,11 @@ library extra-libraries: kernel32 else build-depends: unix >= 2.5 && < 2.8 + +test-suite test + default-language: Haskell2010 + hs-source-dirs: test + main-is: main.hs + type: exitcode-stdio-1.0 + build-depends: base + , process diff --git a/test/main.hs b/test/main.hs new file mode 100644 index 0000000..2d415ce --- /dev/null +++ b/test/main.hs @@ -0,0 +1,14 @@ +import Control.Exception +import System.IO.Error +import System.Process + +main :: IO () +main = do + res <- handle (return . Left . isDoesNotExistError) $ do + (_, _, _, ph) <- createProcess (proc "definitelydoesnotexist" []) + { close_fds = True + } + fmap Right $ waitForProcess ph + case res of + Left True -> return () + _ -> error $ show res From git at git.haskell.org Thu Mar 19 11:37:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:46 +0000 (UTC) Subject: [commit: packages/directory] improve-tests-for-real: Hook testsuite to cabal test (5bd7e05) Message-ID: <20150319113746.6ED233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : improve-tests-for-real Link : http://ghc.haskell.org/trac/ghc/changeset/5bd7e0511066404503fa9dd19429815166f9c8ce/directory >--------------------------------------------------------------- commit 5bd7e0511066404503fa9dd19429815166f9c8ce Author: Phil Ruffwind Date: Mon Mar 2 05:09:03 2015 -0500 Hook testsuite to cabal test >--------------------------------------------------------------- 5bd7e0511066404503fa9dd19429815166f9c8ce directory.cabal | 6 +++--- test/main.hs | 20 -------------------- testsuite/Main.hs | 9 +++++++++ testsuite/run | 7 ------- 4 files changed, 12 insertions(+), 30 deletions(-) diff --git a/directory.cabal b/directory.cabal index c648e0d..bb6f9b3 100644 --- a/directory.cabal +++ b/directory.cabal @@ -65,9 +65,9 @@ Library test-suite test default-language: Haskell2010 - hs-source-dirs: test - main-is: main.hs + hs-source-dirs: testsuite + main-is: Main.hs type: exitcode-stdio-1.0 build-depends: base , directory - , containers + , process diff --git a/test/main.hs b/test/main.hs deleted file mode 100644 index 7a9fcb3..0000000 --- a/test/main.hs +++ /dev/null @@ -1,20 +0,0 @@ -{-# LANGUAGE NoImplicitPrelude #-} --- Simplistic test suite for now. Worthwhile to add a dependency on a --- test framework at some point. -module Main (main) where - -import qualified Data.Set as Set -import Prelude (IO, error, fmap, return, show, (==)) -import System.Directory (getDirectoryContents) - -main :: IO () -main = do - let expected = Set.fromList - [ "." - , ".." - , "main.hs" - ] - actual <- fmap Set.fromList (getDirectoryContents "test") - if expected == actual - then return () - else error (show (expected, actual)) diff --git a/testsuite/Main.hs b/testsuite/Main.hs new file mode 100644 index 0000000..052add8 --- /dev/null +++ b/testsuite/Main.hs @@ -0,0 +1,9 @@ +module Main (main) where +import System.Directory () +import System.Environment (getArgs) +import System.Process (callProcess) + +main :: IO () +main = + -- execute in the Cabal sandbox environment + callProcess "cabal" . (["exec", "--", "sh", "testsuite/run"] ++) =<< getArgs diff --git a/testsuite/run b/testsuite/run index 6725d39..329011d 100755 --- a/testsuite/run +++ b/testsuite/run @@ -24,12 +24,5 @@ sed >dist/testsuite/Makefile \ "s|^TOP=.*$|TOP=../dist/testsuite/ghc/testsuite|" \ tests/Makefile -# there's no way to pass arguments when `sh` is in `-s` mode, so we have to -# write the shell commands to an actual file -cat >dist/testsuite/run.sh <<"EOF" cd tests make -f ../dist/testsuite/Makefile WAY=normal EXTRA_HC_OPTS="$HSFLAGS" "$@" -EOF - -cabal build -exec cabal exec sh -- -e dist/testsuite/run.sh "$@" From git at git.haskell.org Thu Mar 19 11:37:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:47 +0000 (UTC) Subject: [commit: packages/filepath] master: Fixup markdown (c1a3aec) Message-ID: <20150319113747.26D853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/c1a3aec04cb93315dbc9725139c54d71e5134426 >--------------------------------------------------------------- commit c1a3aec04cb93315dbc9725139c54d71e5134426 Author: Neil Mitchell Date: Sat Dec 13 21:16:50 2014 +0000 Fixup markdown >--------------------------------------------------------------- c1a3aec04cb93315dbc9725139c54d71e5134426 changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index 2eb93c8..2d4aa01 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`filepath` package](http://hackage.haskell.org/package/filepath) -_Note: below all `FilePath` values are unquoted, so `\\` really means two backslashes. +_Note: below all `FilePath` values are unquoted, so `\\` really means two backslashes._ ## 1.3.1.0 *TBA* From git at git.haskell.org Thu Mar 19 11:37:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:48 +0000 (UTC) Subject: [commit: packages/process] master: Fix for GHC Trac 3649, comment 10 (3b4842d) Message-ID: <20150319113748.414303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3b4842d322574f2854aa4f2f4bb43b0a813d3e82/process >--------------------------------------------------------------- commit 3b4842d322574f2854aa4f2f4bb43b0a813d3e82 Author: Michael Snoyman Date: Tue Feb 17 16:30:14 2015 +0200 Fix for GHC Trac 3649, comment 10 >--------------------------------------------------------------- 3b4842d322574f2854aa4f2f4bb43b0a813d3e82 cbits/runProcess.c | 4 +++- changelog.md | 5 +++++ 2 files changed, 8 insertions(+), 1 deletion(-) diff --git a/cbits/runProcess.c b/cbits/runProcess.c index e6d7c77..f7828af 100644 --- a/cbits/runProcess.c +++ b/cbits/runProcess.c @@ -200,7 +200,9 @@ runInteractiveProcess (char *const args[], } // XXX Not the pipe for (i = 3; i < max_fd; i++) { - close(i); + if (i != forkCommunicationFds[1]) { + close(i); + } } } diff --git a/changelog.md b/changelog.md index debfcaa..cb3a55f 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,10 @@ # Changelog for [`process` package](http://hackage.haskell.org/package/process) +## Unreleased + + * [Meaningful error message when exe not found on close\_fds is + True](https://ghc.haskell.org/trac/ghc/ticket/3649#comment:10) + ## 1.2.2.0 *Jan 2015* * Fix delegated CTRL-C handling in `createProcess` in case of failed From git at git.haskell.org Thu Mar 19 11:37:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:48 +0000 (UTC) Subject: [commit: packages/directory] improve-tests-for-real: Add test-related files to extra-source-files (4d58b3a) Message-ID: <20150319113748.76D133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : improve-tests-for-real Link : http://ghc.haskell.org/trac/ghc/changeset/4d58b3ad4e2b5afa6373e7adadc3adfa55e59d71/directory >--------------------------------------------------------------- commit 4d58b3ad4e2b5afa6373e7adadc3adfa55e59d71 Author: Phil Ruffwind Date: Mon Mar 2 08:30:55 2015 -0500 Add test-related files to extra-source-files >--------------------------------------------------------------- 4d58b3ad4e2b5afa6373e7adadc3adfa55e59d71 directory.cabal | 18 ++++++ testsuite/update-extra-source-files | 119 ++++++++++++++++++++++++++++++++++++ 2 files changed, 137 insertions(+) diff --git a/directory.cabal b/directory.cabal index bb6f9b3..ad62a8b 100644 --- a/directory.cabal +++ b/directory.cabal @@ -29,6 +29,24 @@ extra-source-files: directory.buildinfo include/HsDirectoryConfig.h.in install-sh + tests/*.hs + tests/*.stderr + tests/*.stdout + tests/Makefile + tests/T4113.stdout-mingw32 + tests/all.T + tests/copyFile001dir/source + tests/copyFile002dir/source + tests/createDirectory001.stdout-mingw32 + tests/createDirectoryIfMissing001.stdout-mingw32 + tests/getDirContents002.stderr-mingw32 + tests/getPermissions001.stdout-alpha-dec-osf3 + tests/getPermissions001.stdout-i386-unknown-freebsd + tests/getPermissions001.stdout-i386-unknown-openbsd + tests/getPermissions001.stdout-mingw + tests/getPermissions001.stdout-x86_64-unknown-openbsd + testsuite/ghc.patch + testsuite/run source-repository head type: git diff --git a/testsuite/update-extra-source-files b/testsuite/update-extra-source-files new file mode 100755 index 0000000..4711734 --- /dev/null +++ b/testsuite/update-extra-source-files @@ -0,0 +1,119 @@ +#!/usr/bin/env python +# since cabal is rather picky about wildcards in 'extra-source-files', +# we have to fill this in ourselves; this script automates that +import os, re, subprocess + +ensure_str_encoding = [] +def ensure_str(string): + '''Make sure that the argument is in fact a Unicode string. If the + argument is not, then: + + - on Python 2, it will be decoded using the preferred encoding; + - on Python 3, it will cause a `TypeError`. + ''' + if getattr(str, "decode") and getattr(str, "encode"): + if isinstance(string, unicode): + return string + if not ensure_str_encoding: + import locale + ensure_str_encoding[0] = locale.getpreferredencoding(False) + return string.decode(ensure_str_encoding[0]) + if isinstance(string, str): + return string + raise TypeError("not an instance of 'str': " + repr(string)) + +def rename(src_filename, dest_filename): + '''Rename a file (allows overwrites on Windows).''' + import os + if os.name == "nt": + import ctypes + success = ctypes.windll.kernel32.MoveFileExW( + ensure_str(src_filename), + ensure_str(dest_filename), + ctypes.c_ulong(0x1)) + if not success: + raise ctypes.WinError() + else: + os.rename(src_filename, dest_filename) + +def read_file(filename, binary=False): + '''Read the contents of a file.''' + with open(filename, "rb" if binary else "rt") as file: + return file.read() + +def write_file(filename, contents, binary=False): + '''Write the contents to a file as atomically as possible.''' + from tempfile import NamedTemporaryFile + def cleanup(): + try: + os.remove(tmp_filename) + except Exception: + pass + try: + with NamedTemporaryFile( + mode="wb" if binary else "wt", + suffix=".tmp", + prefix=os.path.basename(filename) + ".", + dir=os.path.dirname(filename), + delete=False) as tmp_file: + tmp_file.write(contents) + tmp_filename = tmp_file.name + except: + cleanup() + raise + try: + rename(tmp_filename, filename) + except OSError: # only remove if the rename failed + cleanup() + raise + +def find_cabal_fn(): + '''Obtain the filename of the `*.cabal` file.''' + fns = [fn for fn in os.listdir() + if re.match(r"[\w-]+.cabal", fn) and os.path.isfile(fn)] + if len(fns) < 1: + raise Exception("can't find .cabal file in current directory") + elif len(fns) > 1: + raise Exception("too many .cabal files in current directory") + return fns[0] + +def git_tracked_files(): + '''Obtain the list of file tracked by Git.''' + return subprocess.check_output( + ["git", "ls-tree", "-r", "--name-only", "HEAD"] + ).decode("utf-8").split("\n") + +indent = " " * 4 + +dir_name = "tests" + +# extensions that are always included by default +src_extensions = [ + ".hs", + ".stderr", + ".stdout", +] + +# additional source files not covered by 'src_extensions' +def check_fn(fn): + if os.path.basename(fn) == ".gitignore": + return + if not fn.startswith(dir_name + "/"): + return + if (os.path.dirname(fn) == dir_name and + os.path.splitext(fn)[1] in src_extensions): + return + return True +srcs = [indent + fn + "\n" for fn in git_tracked_files() if check_fn(fn)] + +# convert the extensions into patterns +src_patterns = [indent + dir_name + "/*" + ext + "\n" + for ext in src_extensions] + +# update the .cabal file +cabal_fn = find_cabal_fn() +contents = read_file(cabal_fn) +write_file(cabal_fn, + re.sub(r"\n(\s*" + dir_name + "/\S*\n)+", + "\n" + "".join(src_patterns + srcs), + contents, count=1)) From git at git.haskell.org Thu Mar 19 11:37:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:49 +0000 (UTC) Subject: [commit: packages/filepath] master: Test on GHC 7.10.1 (16ddd98) Message-ID: <20150319113749.2E68D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/16ddd983ee51cb462cf58d079631ea47c07cf2c6 >--------------------------------------------------------------- commit 16ddd983ee51cb462cf58d079631ea47c07cf2c6 Author: Neil Mitchell Date: Mon Mar 9 21:47:51 2015 +0000 Test on GHC 7.10.1 >--------------------------------------------------------------- 16ddd983ee51cb462cf58d079631ea47c07cf2c6 .travis.yml | 1 + filepath.cabal | 2 +- 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index ca85eb5..274cc53 100644 --- a/.travis.yml +++ b/.travis.yml @@ -3,6 +3,7 @@ env: - GHCVER=7.4.2 - GHCVER=7.6.3 - GHCVER=7.8.3 + - GHCVER=7.10.1 - GHCVER=head script: diff --git a/filepath.cabal b/filepath.cabal index 87b1f4c..a42c920 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -12,7 +12,7 @@ category: System build-type: Simple synopsis: Library for manipulating FilePaths in a cross platform way. cabal-version: >=1.10 -tested-with: GHC==7.8.3, GHC==7.6.3, GHC==7.4.2, GHC==7.2.2 +tested-with: GHC==7.10.1, GHC==7.8.3, GHC==7.6.3, GHC==7.4.2, GHC==7.2.2 description: This package provides functionality for manipulating @FilePath@ values, and is shipped with both and the . It provides three modules: . From git at git.haskell.org Thu Mar 19 11:37:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:50 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #22 from snoyberg/3649-does-not-exist-exc (0fb914a) Message-ID: <20150319113750.4A07E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0fb914a165edc468b67100e9f6324bd6f92e1019/process >--------------------------------------------------------------- commit 0fb914a165edc468b67100e9f6324bd6f92e1019 Merge: 93d8b62 3b4842d Author: Michael Snoyman Date: Wed Feb 18 06:45:17 2015 +0200 Merge pull request #22 from snoyberg/3649-does-not-exist-exc 3649 does not exist exc >--------------------------------------------------------------- 0fb914a165edc468b67100e9f6324bd6f92e1019 .travis.yml | 3 ++- cbits/runProcess.c | 4 +++- changelog.md | 5 +++++ process.cabal | 8 ++++++++ test/main.hs | 14 ++++++++++++++ 5 files changed, 32 insertions(+), 2 deletions(-) From git at git.haskell.org Thu Mar 19 11:37:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:50 +0000 (UTC) Subject: [commit: packages/directory] improve-tests-for-real: Update .travis.yml for new test system (5553a46) Message-ID: <20150319113750.7D3CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : improve-tests-for-real Link : http://ghc.haskell.org/trac/ghc/changeset/5553a46f01d01cca7f3e86f456e1a5182a6a78a6/directory >--------------------------------------------------------------- commit 5553a46f01d01cca7f3e86f456e1a5182a6a78a6 Author: Phil Ruffwind Date: Mon Mar 2 08:34:59 2015 -0500 Update .travis.yml for new test system >--------------------------------------------------------------- 5553a46f01d01cca7f3e86f456e1a5182a6a78a6 .travis.yml | 14 +++----------- 1 file changed, 3 insertions(+), 11 deletions(-) diff --git a/.travis.yml b/.travis.yml index 05ed4e4..3848906 100644 --- a/.travis.yml +++ b/.travis.yml @@ -20,7 +20,7 @@ before_install: install: - travis_retry cabal update - - cabal install --only-dependencies + - cabal install --enable-tests --only-dependencies - ghc --version script: @@ -29,13 +29,5 @@ script: - cabal build - cabal check - cabal sdist - - cabal test -# The following scriptlet checks that the resulting source distribution can be built & installed - - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; - cd dist/; - if [ -f "$SRC_TGZ" ]; then - cabal install --force-reinstalls "$SRC_TGZ"; - else - echo "expected '$SRC_TGZ' not found"; - exit 1; - fi + - cabal test --show-details=streaming --test-options=WAY= + - cabal install --force-reinstalls --run-tests dist/*-*.tar.gz From git at git.haskell.org Thu Mar 19 11:37:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:51 +0000 (UTC) Subject: [commit: packages/filepath] master: Update the copyright year to 2015 (28fd0a0) Message-ID: <20150319113751.3585B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/28fd0a07bafd8936dfb21ddc6395115d2976790a >--------------------------------------------------------------- commit 28fd0a07bafd8936dfb21ddc6395115d2976790a Author: Neil Mitchell Date: Mon Mar 9 21:48:02 2015 +0000 Update the copyright year to 2015 >--------------------------------------------------------------- 28fd0a07bafd8936dfb21ddc6395115d2976790a LICENSE | 2 +- filepath.cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/LICENSE b/LICENSE index c556af9..86a4451 100644 --- a/LICENSE +++ b/LICENSE @@ -1,4 +1,4 @@ -Copyright Neil Mitchell 2005-2014. +Copyright Neil Mitchell 2005-2015. All rights reserved. Redistribution and use in source and binary forms, with or without diff --git a/filepath.cabal b/filepath.cabal index a42c920..e3260e4 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -5,7 +5,7 @@ license: BSD3 license-file: LICENSE author: Neil Mitchell maintainer: Neil Mitchell -copyright: Neil Mitchell 2005-2014 +copyright: Neil Mitchell 2005-2015 bug-reports: https://github.com/haskell/filepath/issues homepage: https://github.com/haskell/filepath#readme category: System From git at git.haskell.org Thu Mar 19 11:37:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:52 +0000 (UTC) Subject: [commit: packages/process] master: Add stopDelegateControlC for Windows 32bit (deeb7c8) Message-ID: <20150319113752.5126C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/deeb7c8a303c744684afa0f29c2b332a89262294/process >--------------------------------------------------------------- commit deeb7c8a303c744684afa0f29c2b332a89262294 Author: Takenobu Tani Date: Tue Feb 17 23:08:21 2015 +0900 Add stopDelegateControlC for Windows 32bit `Internals.hs` has an expect list for `stopDelegateControlC`. But the implementation is `#ifdef`'d between Unix and Windows. And `stopDelegateControlC` was not defined on Windows. This patch fixes Windows case by a no-op function for the issue #21 >--------------------------------------------------------------- deeb7c8a303c744684afa0f29c2b332a89262294 System/Process/Internals.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index 03b19b3..23e92a2 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -469,6 +469,9 @@ startDelegateControlC = return () endDelegateControlC :: ExitCode -> IO () endDelegateControlC _ = return () +stopDelegateControlC :: IO () +stopDelegateControlC = return () + foreign import ccall unsafe "runInteractiveProcess" c_runInteractiveProcess :: CWString From git at git.haskell.org Thu Mar 19 11:37:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:52 +0000 (UTC) Subject: [commit: packages/directory] improve-tests-for-real: Fix testsuite/update-extra-source-files (492169c) Message-ID: <20150319113752.843A73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : improve-tests-for-real Link : http://ghc.haskell.org/trac/ghc/changeset/492169cca7f2e3b5c4d26f2e31481ff7904906e8/directory >--------------------------------------------------------------- commit 492169cca7f2e3b5c4d26f2e31481ff7904906e8 Author: Phil Ruffwind Date: Mon Mar 2 08:51:59 2015 -0500 Fix testsuite/update-extra-source-files >--------------------------------------------------------------- 492169cca7f2e3b5c4d26f2e31481ff7904906e8 testsuite/update-extra-source-files | 15 +++++++++------ 1 file changed, 9 insertions(+), 6 deletions(-) diff --git a/testsuite/update-extra-source-files b/testsuite/update-extra-source-files index 4711734..3857aff 100755 --- a/testsuite/update-extra-source-files +++ b/testsuite/update-extra-source-files @@ -16,7 +16,7 @@ def ensure_str(string): return string if not ensure_str_encoding: import locale - ensure_str_encoding[0] = locale.getpreferredencoding(False) + ensure_str_encoding.append(locale.getpreferredencoding(False)) return string.decode(ensure_str_encoding[0]) if isinstance(string, str): return string @@ -69,8 +69,8 @@ def write_file(filename, contents, binary=False): def find_cabal_fn(): '''Obtain the filename of the `*.cabal` file.''' - fns = [fn for fn in os.listdir() - if re.match(r"[\w-]+.cabal", fn) and os.path.isfile(fn)] + fns = [fn for fn in os.listdir(".") + if re.match(r"[\w-]+.cabal$", fn) and os.path.isfile(fn)] if len(fns) < 1: raise Exception("can't find .cabal file in current directory") elif len(fns) > 1: @@ -113,7 +113,10 @@ src_patterns = [indent + dir_name + "/*" + ext + "\n" # update the .cabal file cabal_fn = find_cabal_fn() contents = read_file(cabal_fn) -write_file(cabal_fn, - re.sub(r"\n(\s*" + dir_name + "/\S*\n)+", +contents = re.sub(r"\n(\s*" + dir_name + "/\S*\n)+", "\n" + "".join(src_patterns + srcs), - contents, count=1)) + contents, count=1) +write_file(cabal_fn, + contents.encode("utf8"), + # don't use Windows line-endings + binary=True) From git at git.haskell.org Thu Mar 19 11:37:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:53 +0000 (UTC) Subject: [commit: packages/filepath] master: Tighten the QuickCheck lower bound on the test suite, shrinkList was only introduced in 2.7 (7ea9235) Message-ID: <20150319113753.3ACCB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/7ea92355c0c7b73b505517217445d46bb01b9abb >--------------------------------------------------------------- commit 7ea92355c0c7b73b505517217445d46bb01b9abb Author: Neil Mitchell Date: Mon Mar 9 21:48:44 2015 +0000 Tighten the QuickCheck lower bound on the test suite, shrinkList was only introduced in 2.7 >--------------------------------------------------------------- 7ea92355c0c7b73b505517217445d46bb01b9abb filepath.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/filepath.cabal b/filepath.cabal index e3260e4..394bd31 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -58,7 +58,7 @@ test-suite filepath-tests build-depends: filepath, base, - QuickCheck >= 2.6 && < 2.8, + QuickCheck >= 2.7 && < 2.8, random == 1.0.* source-repository head From git at git.haskell.org Thu Mar 19 11:37:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:54 +0000 (UTC) Subject: [commit: packages/process] master: Add comment why no-op function for issue #21 (7ca2448) Message-ID: <20150319113754.584403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7ca24488f44ad4fd45b0e27fe1d21708db4b48d4/process >--------------------------------------------------------------- commit 7ca24488f44ad4fd45b0e27fe1d21708db4b48d4 Author: Takenobu Tani Date: Wed Feb 18 23:20:27 2015 +0900 Add comment why no-op function for issue #21 >--------------------------------------------------------------- 7ca24488f44ad4fd45b0e27fe1d21708db4b48d4 System/Process/Internals.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index 23e92a2..87d1d46 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -463,6 +463,9 @@ createProcess_ fun CreateProcess{ cmdspec = cmdsp, runInteractiveProcess_lock :: MVar () runInteractiveProcess_lock = unsafePerformIO $ newMVar () +-- Following functions are always exported in export list. +-- It should be a no-op function on Windows. +-- see the startDelegateControlC :: IO () startDelegateControlC = return () From git at git.haskell.org Thu Mar 19 11:37:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:54 +0000 (UTC) Subject: [commit: packages/directory] improve-tests-for-real: Fix dependency cycle problem (c9a879b) Message-ID: <20150319113754.8A0433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : improve-tests-for-real Link : http://ghc.haskell.org/trac/ghc/changeset/c9a879bc362da2be31da018b62bcfd50a5802cb7/directory >--------------------------------------------------------------- commit c9a879bc362da2be31da018b62bcfd50a5802cb7 Author: Phil Ruffwind Date: Mon Mar 2 17:57:03 2015 -0500 Fix dependency cycle problem >--------------------------------------------------------------- c9a879bc362da2be31da018b62bcfd50a5802cb7 directory.cabal | 5 ++++- testsuite/Main.hs | 41 +++++++++++++++++++++++++++++++++++++---- 2 files changed, 41 insertions(+), 5 deletions(-) diff --git a/directory.cabal b/directory.cabal index ad62a8b..36e1b39 100644 --- a/directory.cabal +++ b/directory.cabal @@ -83,9 +83,12 @@ Library test-suite test default-language: Haskell2010 + other-extensions: + CPP + ForeignFunctionInterface + ghc-options: -Wall hs-source-dirs: testsuite main-is: Main.hs type: exitcode-stdio-1.0 build-depends: base , directory - , process diff --git a/testsuite/Main.hs b/testsuite/Main.hs index 052add8..bee6bc7 100644 --- a/testsuite/Main.hs +++ b/testsuite/Main.hs @@ -1,9 +1,42 @@ +{-# LANGUAGE CPP, ForeignFunctionInterface #-} module Main (main) where -import System.Directory () +import Foreign (Ptr) +import Foreign.C (CChar(..), CInt(..), withCString) +import Data.Functor ((<$>)) +import System.Directory () -- make sure `directory` is built beforehand import System.Environment (getArgs) -import System.Process (callProcess) +import System.Exit (ExitCode(ExitSuccess, ExitFailure), exitWith) main :: IO () main = - -- execute in the Cabal sandbox environment - callProcess "cabal" . (["exec", "--", "sh", "testsuite/run"] ++) =<< getArgs + exitWith =<< + rawSystem "cabal" . -- execute in the Cabal sandbox environment + (["exec", "--", "sh", "testsuite/run"] ++) =<< + getArgs + +-- we can't use the `process` library as it causes a dependency cycle with +-- Cabal, so we reinvent the wheel here in a simplistic way; this will +-- probably break with non-ASCII characters on Windows +rawSystem :: String -> [String] -> IO ExitCode +rawSystem cmd args = + withCString (unwords (quoteArgument <$> cmd : args)) $ \ c_command -> + makeExitCode . fromIntegral <$> c_system c_command + +makeExitCode :: Int -> ExitCode +makeExitCode 0 = ExitSuccess +makeExitCode e = ExitFailure e + +-- handle the different quoting rules in CMD.EXE vs POSIX shells +quoteArgument :: String -> String +#ifdef mingw32_HOST_OS +quoteArgument s = "\"" ++ replaceElem '"' "\"\"" s ++ "\"" +#else +quoteArgument s = "'" ++ replaceElem '\'' "'\\''" s ++ "'" +#endif + +replaceElem :: Eq a => a -> [a] -> [a] -> [a] +replaceElem match repl = concat . (replace <$>) + where replace c | c == match = repl + | otherwise = [c] + +foreign import ccall safe "stdlib.h system" c_system :: Ptr CChar -> IO CInt From git at git.haskell.org Thu Mar 19 11:37:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:55 +0000 (UTC) Subject: [commit: packages/filepath] master: Delete the random constraint, was not required (fa66f58) Message-ID: <20150319113755.419B03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/fa66f583b2998dded1af04e0cebedbe606cee7d3 >--------------------------------------------------------------- commit fa66f583b2998dded1af04e0cebedbe606cee7d3 Author: Neil Mitchell Date: Mon Mar 9 21:48:58 2015 +0000 Delete the random constraint, was not required >--------------------------------------------------------------- fa66f583b2998dded1af04e0cebedbe606cee7d3 filepath.cabal | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/filepath.cabal b/filepath.cabal index 394bd31..3023f9d 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -58,8 +58,7 @@ test-suite filepath-tests build-depends: filepath, base, - QuickCheck >= 2.7 && < 2.8, - random == 1.0.* + QuickCheck >= 2.7 && < 2.8 source-repository head type: git From git at git.haskell.org Thu Mar 19 11:37:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:56 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #21 from takenobu-hs/patch-1 (8321c6d) Message-ID: <20150319113756.60DF33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8321c6df9571015140046acb7583b93d6caecf06/process >--------------------------------------------------------------- commit 8321c6df9571015140046acb7583b93d6caecf06 Merge: 0fb914a 7ca2448 Author: Michael Snoyman Date: Wed Feb 18 16:30:18 2015 +0200 Merge pull request #21 from takenobu-hs/patch-1 Add stopDelegateControlC for MinGW32 >--------------------------------------------------------------- 8321c6df9571015140046acb7583b93d6caecf06 System/Process/Internals.hs | 6 ++++++ 1 file changed, 6 insertions(+) From git at git.haskell.org Thu Mar 19 11:37:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:56 +0000 (UTC) Subject: [commit: packages/directory] improve-tests-for-real: Fix .travis.yml (0974721) Message-ID: <20150319113756.91AF93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : improve-tests-for-real Link : http://ghc.haskell.org/trac/ghc/changeset/09747218f5b464db74dbad318c84a23783fd67b4/directory >--------------------------------------------------------------- commit 09747218f5b464db74dbad318c84a23783fd67b4 Author: Phil Ruffwind Date: Mon Mar 2 18:57:03 2015 -0500 Fix .travis.yml >--------------------------------------------------------------- 09747218f5b464db74dbad318c84a23783fd67b4 .travis.yml | 22 ++++++++++++++++++++-- 1 file changed, 20 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 3848906..a932e54 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,3 +1,4 @@ +language: haskell env: # we have to use CABALVER=1.16 for GHC<7.6 as well, as there's # no package for earlier cabal versions in the PPA @@ -23,11 +24,28 @@ install: - cabal install --enable-tests --only-dependencies - ghc --version +before_script: + - # check if 'streaming' is supported (didn't exist until 1.20) + if cabal 2>&1 test --show-details=streaming __dummy | + grep >/dev/null 2>&1 "cabal: --show-details flags expects" + then streaming=always + else streaming=streaming + fi + export streaming + script: - autoreconf -i - cabal configure -v2 --enable-tests - cabal build - cabal check - cabal sdist - - cabal test --show-details=streaming --test-options=WAY= - - cabal install --force-reinstalls --run-tests dist/*-*.tar.gz + - cabal test --show-details=$streaming --test-options=WAY= + - | + # in the future, use '--run-tests' (didn't exist until 1.20) + cabal install --force-reinstalls dist/*-*.tar.gz + mkdir install-tmp + cd install-tmp + tar xzf ../dist/*-*.tar.gz + cd *-* + cabal configure --enable-tests + cabal test From git at git.haskell.org Thu Mar 19 11:37:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:57 +0000 (UTC) Subject: [commit: packages/filepath] master: Update version to 1.4.0.0 in preparation for GHC 7.10 release (Edward Kmett recommends a 0.1 version bump) (d039d5a) Message-ID: <20150319113757.47BE43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/d039d5ae7c070452a443219fdb7df65508567338 >--------------------------------------------------------------- commit d039d5ae7c070452a443219fdb7df65508567338 Author: Neil Mitchell Date: Tue Mar 10 21:15:28 2015 +0000 Update version to 1.4.0.0 in preparation for GHC 7.10 release (Edward Kmett recommends a 0.1 version bump) >--------------------------------------------------------------- d039d5ae7c070452a443219fdb7df65508567338 changelog.md | 2 +- filepath.cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md index 2d4aa01..6c36406 100644 --- a/changelog.md +++ b/changelog.md @@ -2,7 +2,7 @@ _Note: below all `FilePath` values are unquoted, so `\\` really means two backslashes._ -## 1.3.1.0 *TBA* +## 1.4.0.0 *Mar 2015* * Bundled with GHC 7.10.1 diff --git a/filepath.cabal b/filepath.cabal index 3023f9d..cb24f69 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -1,5 +1,5 @@ name: filepath -version: 1.3.1.0 +version: 1.4.0.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE From git at git.haskell.org Thu Mar 19 11:37:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:58 +0000 (UTC) Subject: [commit: packages/directory] master: Drop trailing path separators in `getPermissions` on Windows (3e56351) Message-ID: <20150319113758.98CBC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3e5635133c9ee42596ac0353f6856cef69dd09ff/directory >--------------------------------------------------------------- commit 3e5635133c9ee42596ac0353f6856cef69dd09ff Author: Phil Ruffwind Date: Mon Mar 2 20:21:13 2015 -0500 Drop trailing path separators in `getPermissions` on Windows This fixes the issue #9 where Windows fails to recognize paths that contain trailing path separators. >--------------------------------------------------------------- 3e5635133c9ee42596ac0353f6856cef69dd09ff System/Directory.hs | 3 ++- tests/getPermissions001.hs | 14 +++++++++----- 2 files changed, 11 insertions(+), 6 deletions(-) diff --git a/System/Directory.hs b/System/Directory.hs index 7cbaa50..695db9c 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -197,7 +197,8 @@ The operation may fail with: getPermissions :: FilePath -> IO Permissions getPermissions name = do #ifdef mingw32_HOST_OS - withFilePath name $ \s -> do + -- issue #9: Windows doesn't like trailing path separators + withFilePath (dropTrailingPathSeparator name) $ \s -> do -- stat() does a better job of guessing the permissions on Windows -- than access() does. e.g. for execute permission, it looks at the -- filename extension :-) diff --git a/tests/getPermissions001.hs b/tests/getPermissions001.hs index 5e9adf2..8290d3f 100644 --- a/tests/getPermissions001.hs +++ b/tests/getPermissions001.hs @@ -1,13 +1,17 @@ import System.Directory main = do +#ifndef mingw32_HOST_OS + let exe = ".exe" +#else + let exe = "" +#endif p <- getPermissions "." print p p <- getPermissions "getPermissions001.hs" print p -#ifndef mingw32_HOST_OS - p <- getPermissions "getPermissions001" -#else - p <- getPermissions "getPermissions001.exe" -#endif + p <- getPermissions ("getPermissions001" ++ exe) print p + + -- issue #9: Windows doesn't like trailing path separators + _ <- getPermissions "../tests/" From git at git.haskell.org Thu Mar 19 11:37:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:58 +0000 (UTC) Subject: [commit: packages/process] master: Slight documentation cleanup (10a0db2) Message-ID: <20150319113758.67E1B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/10a0db27adfdf61e644d3d97f3224fb1930fae05/process >--------------------------------------------------------------- commit 10a0db27adfdf61e644d3d97f3224fb1930fae05 Author: Michael Snoyman Date: Wed Feb 18 16:31:54 2015 +0200 Slight documentation cleanup >--------------------------------------------------------------- 10a0db27adfdf61e644d3d97f3224fb1930fae05 System/Process/Internals.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index 87d1d46..9d2be0a 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -463,9 +463,10 @@ createProcess_ fun CreateProcess{ cmdspec = cmdsp, runInteractiveProcess_lock :: MVar () runInteractiveProcess_lock = unsafePerformIO $ newMVar () --- Following functions are always exported in export list. --- It should be a no-op function on Windows. --- see the +-- The following functions are always present in the export list. For +-- compatibility with the non-Windows code, we provide the same functions with +-- matching type signatures, but implemented as no-ops. For details, see: +-- startDelegateControlC :: IO () startDelegateControlC = return () @@ -475,6 +476,8 @@ endDelegateControlC _ = return () stopDelegateControlC :: IO () stopDelegateControlC = return () +-- End no-op functions + foreign import ccall unsafe "runInteractiveProcess" c_runInteractiveProcess :: CWString From git at git.haskell.org Thu Mar 19 11:37:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:37:59 +0000 (UTC) Subject: [commit: packages/filepath] master: Refer to `makeAbsolute` instead of `canonicalizePath` in docs (b2e69c0) Message-ID: <20150319113759.50C373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/b2e69c0dfb63e956a0f57d83895caf05c7ea986f >--------------------------------------------------------------- commit b2e69c0dfb63e956a0f57d83895caf05c7ea986f Author: Phil Ruffwind Date: Wed Mar 11 01:58:09 2015 -0400 Refer to `makeAbsolute` instead of `canonicalizePath` in docs >--------------------------------------------------------------- b2e69c0dfb63e956a0f57d83895caf05c7ea986f System/FilePath/Internal.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index f7b3469..051e44c 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -729,8 +729,8 @@ equalFilePath a b = f a == f b -- | Contract a filename, based on a relative path. -- --- There is no corresponding @makeAbsolute@ function, instead use --- @System.Directory.canonicalizePath@ which has the same effect. +-- The corresponding @makeAbsolute@ function can be found in +-- @System.Directory at . -- -- > makeRelative "/directory" "/directory/file.ext" == "file.ext" -- > Valid x => makeRelative (takeDirectory x) x `equalFilePath` takeFileName x From git at git.haskell.org Thu Mar 19 11:38:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:00 +0000 (UTC) Subject: [commit: packages/process] master: Add readCreateProcess function (8c92d7d) Message-ID: <20150319113800.725FF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8c92d7dfd9f6ebba07b35ae1d0da0c2e66bc6c18/process >--------------------------------------------------------------- commit 8c92d7dfd9f6ebba07b35ae1d0da0c2e66bc6c18 Author: Bartosz Nitka Date: Wed Feb 25 09:42:50 2015 -0800 Add readCreateProcess function This function is more flexible then readProcess, for example it allows you to change the working directory before running the command. >--------------------------------------------------------------- 8c92d7dfd9f6ebba07b35ae1d0da0c2e66bc6c18 System/Process.hsc | 29 +++++++++++++++++++++++++---- 1 file changed, 25 insertions(+), 4 deletions(-) diff --git a/System/Process.hsc b/System/Process.hsc index fe3e8fc..6270fe3 100644 --- a/System/Process.hsc +++ b/System/Process.hsc @@ -40,6 +40,7 @@ module System.Process ( callCommand, spawnProcess, spawnCommand, + readCreateProcess, readProcess, readProcessWithExitCode, @@ -413,13 +414,25 @@ readProcess -> [String] -- ^ any arguments -> String -- ^ standard input -> IO String -- ^ stdout -readProcess cmd args input = do - let cp_opts = (proc cmd args) { +readProcess cmd args = readCreateProcess $ proc cmd args + +-- | @readCreateProcess@ works exactly like 'readProcess' except that it +-- lets you pass 'CreateProcess' giving better flexibility. +-- +-- > > readCreateProcess (shell "pwd" { cwd = "/etc/" }) "" +-- > "/etc\n" + +readCreateProcess + :: CreateProcess + -> String -- ^ standard input + -> IO String -- ^ stdout +readCreateProcess cp input = do + let cp_opts = cp { std_in = CreatePipe, std_out = CreatePipe, std_err = Inherit } - (ex, output) <- withCreateProcess_ "readProcess" cp_opts $ + (ex, output) <- withCreateProcess_ "readCreateProcess" cp_opts $ \(Just inh) (Just outh) _ ph -> do -- fork off a thread to start consuming the output @@ -442,7 +455,15 @@ readProcess cmd args input = do case ex of ExitSuccess -> return output - ExitFailure r -> processFailedException "readProcess" cmd args r + ExitFailure r -> processFailedException "readCreateProcess" cmd args r + where + cmd = case cp of + CreateProcess { cmdspec = ShellCommand sc } -> sc + CreateProcess { cmdspec = RawCommand fp _ } -> fp + args = case cp of + CreateProcess { cmdspec = ShellCommand _ } -> [] + CreateProcess { cmdspec = RawCommand _ args' } -> args' + -- | @readProcessWithExitCode@ is like @readProcess@ but with two differences: -- From git at git.haskell.org Thu Mar 19 11:38:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:00 +0000 (UTC) Subject: [commit: packages/directory] master: Update changelog.md: issue #9 is now fixed (8428a55) Message-ID: <20150319113800.A33D03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8428a55c0f51548e32c37f9d1a46b511c9976617/directory >--------------------------------------------------------------- commit 8428a55c0f51548e32c37f9d1a46b511c9976617 Author: Phil Ruffwind Date: Mon Mar 2 23:31:30 2015 -0500 Update changelog.md: issue #9 is now fixed >--------------------------------------------------------------- 8428a55c0f51548e32c37f9d1a46b511c9976617 changelog.md | 3 +++ 1 file changed, 3 insertions(+) diff --git a/changelog.md b/changelog.md index bc2d62a..d5e12f0 100644 --- a/changelog.md +++ b/changelog.md @@ -18,6 +18,9 @@ circumstances, fixing the inconsistency as noted in [#15](https://github.com/haskell/directory/issues/15) + * Allow trailing path separators in `getPermissions` on Windows + (fixes [#9](https://github.com/haskell/directory/issues/9)) + ## 1.2.1.0 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 11:38:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:01 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge pull request #41 from Rufflewind/master (4206435) Message-ID: <20150319113801.5910D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/4206435bda0929d7a65fc42e5c8629212328120c >--------------------------------------------------------------- commit 4206435bda0929d7a65fc42e5c8629212328120c Merge: d039d5a b2e69c0 Author: Neil Mitchell Date: Wed Mar 11 06:52:19 2015 +0000 Merge pull request #41 from Rufflewind/master Refer to `makeAbsolute` instead of `canonicalizePath` in docs >--------------------------------------------------------------- 4206435bda0929d7a65fc42e5c8629212328120c System/FilePath/Internal.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) From git at git.haskell.org Thu Mar 19 11:38:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:02 +0000 (UTC) Subject: [commit: packages/process] master: Fix reported function name in callProcess (24918b8) Message-ID: <20150319113802.798CE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/24918b8acb6a65d134838ae243abf9fa7e467ef0/process >--------------------------------------------------------------- commit 24918b8acb6a65d134838ae243abf9fa7e467ef0 Author: Bartosz Nitka Date: Wed Feb 25 14:45:19 2015 +0000 Fix reported function name in callProcess >--------------------------------------------------------------- 24918b8acb6a65d134838ae243abf9fa7e467ef0 System/Process.hsc | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Process.hsc b/System/Process.hsc index fe3e8fc..960b49d 100644 --- a/System/Process.hsc +++ b/System/Process.hsc @@ -298,7 +298,7 @@ spawnCommand cmd = do -- /Since: 1.2.0.0/ callProcess :: FilePath -> [String] -> IO () callProcess cmd args = do - exit_code <- withCreateProcess_ "callCommand" + exit_code <- withCreateProcess_ "callProcess" (proc cmd args) { delegate_ctlc = True } $ \_ _ _ p -> waitForProcess p case exit_code of From git at git.haskell.org Thu Mar 19 11:38:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:02 +0000 (UTC) Subject: [commit: packages/directory] master: Fix broken tests/getPermissions001.hs (8ec9e1a) Message-ID: <20150319113802.AADBF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8ec9e1a99bc5e8be58887e0f3aff6e0d9cbbc57e/directory >--------------------------------------------------------------- commit 8ec9e1a99bc5e8be58887e0f3aff6e0d9cbbc57e Author: Phil Ruffwind Date: Tue Mar 3 02:49:36 2015 -0500 Fix broken tests/getPermissions001.hs >--------------------------------------------------------------- 8ec9e1a99bc5e8be58887e0f3aff6e0d9cbbc57e tests/getPermissions001.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/tests/getPermissions001.hs b/tests/getPermissions001.hs index 8290d3f..6582928 100644 --- a/tests/getPermissions001.hs +++ b/tests/getPermissions001.hs @@ -1,7 +1,8 @@ +{-# LANGUAGE CPP #-} import System.Directory main = do -#ifndef mingw32_HOST_OS +#ifdef mingw32_HOST_OS let exe = ".exe" #else let exe = "" @@ -15,3 +16,5 @@ main = do -- issue #9: Windows doesn't like trailing path separators _ <- getPermissions "../tests/" + + return () From git at git.haskell.org Thu Mar 19 11:38:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:03 +0000 (UTC) Subject: [commit: packages/filepath] master: GHC 7.8.4 (1a72008) Message-ID: <20150319113803.613863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/1a7200820c76b2bab9e59cdfa55d66515712ff29 >--------------------------------------------------------------- commit 1a7200820c76b2bab9e59cdfa55d66515712ff29 Author: Neil Mitchell Date: Thu Mar 12 18:56:10 2015 +0000 GHC 7.8.4 >--------------------------------------------------------------- 1a7200820c76b2bab9e59cdfa55d66515712ff29 .travis.yml | 2 +- filepath.cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 274cc53..ebae307 100644 --- a/.travis.yml +++ b/.travis.yml @@ -2,7 +2,7 @@ env: - GHCVER=7.2.2 - GHCVER=7.4.2 - GHCVER=7.6.3 - - GHCVER=7.8.3 + - GHCVER=7.8.4 - GHCVER=7.10.1 - GHCVER=head diff --git a/filepath.cabal b/filepath.cabal index cb24f69..0841a0d 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -12,7 +12,7 @@ category: System build-type: Simple synopsis: Library for manipulating FilePaths in a cross platform way. cabal-version: >=1.10 -tested-with: GHC==7.10.1, GHC==7.8.3, GHC==7.6.3, GHC==7.4.2, GHC==7.2.2 +tested-with: GHC==7.10.1, GHC==7.8.4, GHC==7.6.3, GHC==7.4.2, GHC==7.2.2 description: This package provides functionality for manipulating @FilePath@ values, and is shipped with both and the . It provides three modules: . From git at git.haskell.org Thu Mar 19 11:38:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:04 +0000 (UTC) Subject: [commit: packages/process] master: Add @since annotation and update changelog.md (cdfce9f) Message-ID: <20150319113804.80FD13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cdfce9ff33429cfde3772b39cb17749805b9b838/process >--------------------------------------------------------------- commit cdfce9ff33429cfde3772b39cb17749805b9b838 Author: Bartosz Nitka Date: Thu Feb 26 01:45:24 2015 -0800 Add @since annotation and update changelog.md >--------------------------------------------------------------- cdfce9ff33429cfde3772b39cb17749805b9b838 System/Process.hsc | 2 ++ changelog.md | 2 ++ 2 files changed, 4 insertions(+) diff --git a/System/Process.hsc b/System/Process.hsc index 6270fe3..13c36ad 100644 --- a/System/Process.hsc +++ b/System/Process.hsc @@ -421,6 +421,8 @@ readProcess cmd args = readCreateProcess $ proc cmd args -- -- > > readCreateProcess (shell "pwd" { cwd = "/etc/" }) "" -- > "/etc\n" +-- +-- /Since: 1.2.3.0/ readCreateProcess :: CreateProcess diff --git a/changelog.md b/changelog.md index cb3a55f..0d46f3b 100644 --- a/changelog.md +++ b/changelog.md @@ -5,6 +5,8 @@ * [Meaningful error message when exe not found on close\_fds is True](https://ghc.haskell.org/trac/ghc/ticket/3649#comment:10) + * New function `readCreateProcess` + ## 1.2.2.0 *Jan 2015* * Fix delegated CTRL-C handling in `createProcess` in case of failed From git at git.haskell.org Thu Mar 19 11:38:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:04 +0000 (UTC) Subject: [commit: packages/directory] master: Ignore test executable (canonicalizePath001) (0c201fa) Message-ID: <20150319113804.B15923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0c201fa3e6b5f928674c4cd8cc36885f6a71d694/directory >--------------------------------------------------------------- commit 0c201fa3e6b5f928674c4cd8cc36885f6a71d694 Author: Phil Ruffwind Date: Tue Mar 3 19:15:15 2015 -0500 Ignore test executable (canonicalizePath001) >--------------------------------------------------------------- 0c201fa3e6b5f928674c4cd8cc36885f6a71d694 tests/.gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/tests/.gitignore b/tests/.gitignore index e675d35..d2fe0ee 100644 --- a/tests/.gitignore +++ b/tests/.gitignore @@ -9,6 +9,7 @@ # specific files /T4113 +/canonicalizePath001 /copyFile001 /copyFile002 /createDirectory001 From git at git.haskell.org Thu Mar 19 11:38:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:05 +0000 (UTC) Subject: [commit: packages/filepath] master: Merge branch 'master' of https://github.com/haskell/filepath (81375ae) Message-ID: <20150319113805.662713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/81375ae0c892b5951f2c1184c655a8f3a5193c9c >--------------------------------------------------------------- commit 81375ae0c892b5951f2c1184c655a8f3a5193c9c Merge: 1a72008 4206435 Author: Neil Mitchell Date: Thu Mar 12 18:56:22 2015 +0000 Merge branch 'master' of https://github.com/haskell/filepath >--------------------------------------------------------------- 81375ae0c892b5951f2c1184c655a8f3a5193c9c System/FilePath/Internal.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) From git at git.haskell.org Thu Mar 19 11:38:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:06 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #25 from niteria/errorReporting (9312797) Message-ID: <20150319113806.883C33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/93127978a33bf8863023383b01c752c5a1eb4a3a/process >--------------------------------------------------------------- commit 93127978a33bf8863023383b01c752c5a1eb4a3a Merge: 10a0db2 24918b8 Author: Michael Snoyman Date: Thu Feb 26 13:40:13 2015 +0200 Merge pull request #25 from niteria/errorReporting Fix reported function name in callProcess >--------------------------------------------------------------- 93127978a33bf8863023383b01c752c5a1eb4a3a System/Process.hsc | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Thu Mar 19 11:38:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:06 +0000 (UTC) Subject: [commit: packages/directory] master: Merge pull request #8 from gintas/master (021cc5d) Message-ID: <20150319113806.BE8553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/021cc5d4cbd164e53897f417e8c21dab99f7c8c9/directory >--------------------------------------------------------------- commit 021cc5d4cbd164e53897f417e8c21dab99f7c8c9 Merge: 0c201fa 60667c8 Author: Phil Ruffwind Date: Tue Mar 3 19:16:45 2015 -0500 Merge pull request #8 from gintas/master >--------------------------------------------------------------- 021cc5d4cbd164e53897f417e8c21dab99f7c8c9 System/Directory.hs | 26 ++++++++++++++++++++------ tests/.gitignore | 1 + tests/T8482.hs | 16 ++++++++++++++++ tests/T8482.stdout | 3 +++ tests/all.T | 2 ++ 5 files changed, 42 insertions(+), 6 deletions(-) diff --cc System/Directory.hs index 695db9c,14b89ff..0e2c071 --- a/System/Directory.hs +++ b/System/Directory.hs @@@ -678,18 -637,33 +678,32 @@@ Either path refers to an existing direc -} renameFile :: FilePath -> FilePath -> IO () -renameFile opath npath = do - -- XXX the isDirectory tests are not performed atomically with the rename +renameFile opath npath = (`ioeSetLocation` "renameFile") `modifyIOError` do - -- XXX this test isn't performed atomically with the following rename - dirType <- getDirectoryType opath - case dirType of - Directory -> ioError . (`ioeSetErrorString` "is a directory") $ - mkIOError InappropriateType "" Nothing (Just opath) - _ -> return () ++ -- XXX the tests are not performed atomically with the rename + checkNotDir opath - doRename `E.catch` renameExcHandler - where checkNotDir path = do - isdir <- pathIsDir path `E.catch` ((\ _ -> return False) :: IOException -> IO Bool) - when isdir $ dirIoError path - dirIoError path = ioError $ ioeSetErrorString (mkIOError InappropriateType "renameFile" Nothing (Just path)) "is a directory" - renameExcHandler :: IOException -> IO () - renameExcHandler exc = do - -- The underlying rename implementation throws odd exceptions - -- sometimes when the destination is a directory. For example, - -- Windows throws a permission error. In those cases check - -- if the cause is actually the destination being a directory - -- and throw InapprioriateType in that case. - checkNotDir npath - throw exc - doRename :: IO () - pathIsDir :: FilePath -> IO (Bool) #ifdef mingw32_HOST_OS - -- ToDo: use Win32 API - pathIsDir path = withFileOrSymlinkStatus "renameFile" path isDirectory - doRename = Win32.moveFileEx opath npath Win32.mOVEFILE_REPLACE_EXISTING + Win32.moveFileEx opath npath Win32.mOVEFILE_REPLACE_EXISTING #else - pathIsDir path = Posix.isDirectory `fmap` Posix.getSymbolicLinkStatus path - doRename = Posix.rename opath npath + Posix.rename opath npath #endif ++ -- The underlying rename implementation can throw odd exceptions when the ++ -- destination is a directory. For example, Windows typically throws a ++ -- permission error, while POSIX systems may throw a resource busy error ++ -- if one of the paths refers to the current directory. In these cases, ++ -- we check if the destination is a directory and, if so, throw an ++ -- InappropriateType error. ++ `catchIOError` \ err -> do ++ checkNotDir npath ++ ioError err ++ where checkNotDir path = do ++ dirType <- getDirectoryType path ++ `catchIOError` \ _ -> return NotDirectory ++ case dirType of ++ Directory -> errIsDir path ++ DirectoryLink -> errIsDir path ++ NotDirectory -> return () ++ errIsDir path = ioError . (`ioeSetErrorString` "is a directory") $ ++ mkIOError InappropriateType "" Nothing (Just path) #endif /* __GLASGOW_HASKELL__ */ diff --cc tests/.gitignore index d2fe0ee,e675d35..9abd17e --- a/tests/.gitignore +++ b/tests/.gitignore @@@ -23,3 -22,3 +23,4 @@@ /getPermissions001 /renameFile001 /renameFile001.tmp1 ++/T8482 diff --cc tests/all.T index bdde734,ac6c909..3279e5d --- a/tests/all.T +++ b/tests/all.T @@@ -26,3 -25,6 +26,5 @@@ test('createDirectoryIfMissing001', no # No sane way to tell whether the output is reasonable here... test('getHomeDirectory001', ignore_output, compile_and_run, ['']) + -test('T4113', when(platform('i386-apple-darwin'), expect_broken(7604)), compile_and_run, ['']) + test('T8482', normal, compile_and_run, ['']) From git at git.haskell.org Thu Mar 19 11:38:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:08 +0000 (UTC) Subject: [commit: packages/process] master: Version bump (pinging @hvr) (160bdd1) Message-ID: <20150319113808.8E98B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/160bdd16722d85c2644bd2353121d8eb5e1597e4/process >--------------------------------------------------------------- commit 160bdd16722d85c2644bd2353121d8eb5e1597e4 Author: Michael Snoyman Date: Fri Feb 27 09:36:13 2015 +0200 Version bump (pinging @hvr) >--------------------------------------------------------------- 160bdd16722d85c2644bd2353121d8eb5e1597e4 changelog.md | 2 +- process.cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md index cb3a55f..8347b8f 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`process` package](http://hackage.haskell.org/package/process) -## Unreleased +## 1.2.3.0 *unreleased* * [Meaningful error message when exe not found on close\_fds is True](https://ghc.haskell.org/trac/ghc/ticket/3649#comment:10) diff --git a/process.cabal b/process.cabal index d33e7bc..26b280f 100644 --- a/process.cabal +++ b/process.cabal @@ -1,5 +1,5 @@ name: process -version: 1.2.2.0 +version: 1.2.3.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE From git at git.haskell.org Thu Mar 19 11:38:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:08 +0000 (UTC) Subject: [commit: packages/directory] master: Update changelog for PR #8 (7020082) Message-ID: <20150319113808.C53DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/70200828492728f6bb051bccf2c50bb21bf30b77/directory >--------------------------------------------------------------- commit 70200828492728f6bb051bccf2c50bb21bf30b77 Author: Phil Ruffwind Date: Tue Mar 3 22:31:10 2015 -0500 Update changelog for PR #8 >--------------------------------------------------------------- 70200828492728f6bb051bccf2c50bb21bf30b77 changelog.md | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/changelog.md b/changelog.md index d5e12f0..6e4ef5f 100644 --- a/changelog.md +++ b/changelog.md @@ -21,6 +21,11 @@ * Allow trailing path separators in `getPermissions` on Windows (fixes [#9](https://github.com/haskell/directory/issues/9)) + * `renameFile` now always throws the correct error type + (`InappropriateType`) when the destination is a directory (as long as the + filesystem is not being modified concurrently). See + [pull request #8](https://github.com/haskell/directory/pull/8). + ## 1.2.1.0 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 11:38:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:10 +0000 (UTC) Subject: [commit: packages/process] master: Don't overwrite `std_err` in the CreateProcess record and add a note which handles are ignored. (049e8e3) Message-ID: <20150319113810.963823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/049e8e3f416dc8a418035e891cca319eb056f403/process >--------------------------------------------------------------- commit 049e8e3f416dc8a418035e891cca319eb056f403 Author: Bartosz Nitka Date: Fri Feb 27 06:20:57 2015 -0800 Don't overwrite `std_err` in the CreateProcess record and add a note which handles are ignored. >--------------------------------------------------------------- 049e8e3f416dc8a418035e891cca319eb056f403 System/Process.hsc | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/System/Process.hsc b/System/Process.hsc index 13c36ad..e9d470f 100644 --- a/System/Process.hsc +++ b/System/Process.hsc @@ -422,6 +422,8 @@ readProcess cmd args = readCreateProcess $ proc cmd args -- > > readCreateProcess (shell "pwd" { cwd = "/etc/" }) "" -- > "/etc\n" -- +-- Note that @Handle at s provided for @std_in@ or @std_out@ via the CreateProcess +-- record will be ignored. -- /Since: 1.2.3.0/ readCreateProcess @@ -432,7 +434,6 @@ readCreateProcess cp input = do let cp_opts = cp { std_in = CreatePipe, std_out = CreatePipe, - std_err = Inherit } (ex, output) <- withCreateProcess_ "readCreateProcess" cp_opts $ \(Just inh) (Just outh) _ ph -> do From git at git.haskell.org Thu Mar 19 11:38:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:10 +0000 (UTC) Subject: [commit: packages/directory] master: Add regression test for removeDirectoryRecursive bug (issue #15) (23b416f) Message-ID: <20150319113810.CCA1C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/23b416fdca01737223395f1cd243e67e31293101/directory >--------------------------------------------------------------- commit 23b416fdca01737223395f1cd243e67e31293101 Author: Phil Ruffwind Date: Wed Feb 18 03:22:49 2015 -0500 Add regression test for removeDirectoryRecursive bug (issue #15) >--------------------------------------------------------------- 23b416fdca01737223395f1cd243e67e31293101 tests/.gitignore | 1 + tests/TestUtils.hs | 88 ++++++++++++++++++++++++++++++ tests/all.T | 2 + tests/removeDirectoryRecursive001.hs | 93 ++++++++++++++++++++++++++++++++ tests/removeDirectoryRecursive001.stdout | 19 +++++++ 5 files changed, 203 insertions(+) diff --git a/tests/.gitignore b/tests/.gitignore index 9abd17e..4a62c19 100644 --- a/tests/.gitignore +++ b/tests/.gitignore @@ -23,4 +23,5 @@ /getPermissions001 /renameFile001 /renameFile001.tmp1 +/removeDirectoryRecursive001 /T8482 diff --git a/tests/TestUtils.hs b/tests/TestUtils.hs new file mode 100644 index 0000000..36c357e --- /dev/null +++ b/tests/TestUtils.hs @@ -0,0 +1,88 @@ +{-# LANGUAGE CPP, ForeignFunctionInterface #-} +module TestUtils + ( copyPathRecursive + , createSymbolicLink + , modifyPermissions + , tryCreateSymbolicLink + ) where +import System.Directory +import System.FilePath (()) +import System.IO.Error (ioeSetLocation, modifyIOError) +#ifdef mingw32_HOST_OS +import Foreign (Ptr) +import Foreign.C (CUChar(..), CULong(..), CWchar(..), withCWString) +import System.FilePath (takeDirectory) +import System.IO (hPutStrLn, stderr) +import System.IO.Error (catchIOError, ioeSetErrorString, isPermissionError, + mkIOError, permissionErrorType) +import System.Win32.Types (failWith, getLastError) +#else +import System.Posix.Files (createSymbolicLink) +#endif + +#ifdef mingw32_HOST_OS +# if defined i386_HOST_ARCH +# define WINAPI stdcall +# elif defined x86_64_HOST_ARCH +# define WINAPI ccall +# else +# error unknown architecture +# endif +foreign import WINAPI unsafe "windows.h CreateSymbolicLinkW" + c_CreateSymbolicLink :: Ptr CWchar -> Ptr CWchar -> CULong -> IO CUChar +#endif + +-- | @'copyPathRecursive' path@ copies an existing file or directory at +-- /path/ together with its contents and subdirectories. +-- +-- Warning: mostly untested and might not handle symlinks correctly. +copyPathRecursive :: FilePath -> FilePath -> IO () +copyPathRecursive source dest = + (`ioeSetLocation` "copyPathRecursive") `modifyIOError` do + dirExists <- doesDirectoryExist source + if dirExists + then do + contents <- getDirectoryContents source + createDirectory dest + mapM_ (uncurry copyPathRecursive) + [(source x, dest x) | x <- contents, x /= "." && x /= ".."] + else copyFile source dest + +modifyPermissions :: FilePath -> (Permissions -> Permissions) -> IO () +modifyPermissions path modify = do + permissions <- getPermissions path + setPermissions path (modify permissions) + +#if mingw32_HOST_OS +createSymbolicLink :: String -> String -> IO () +createSymbolicLink target link = + (`ioeSetLocation` "createSymbolicLink") `modifyIOError` do + isDir <- (fromIntegral . fromEnum) `fmap` + doesDirectoryExist (takeDirectory link target) + withCWString target $ \ target' -> + withCWString link $ \ link' -> do + status <- c_CreateSymbolicLink link' target' isDir + if status == 0 + then do + errCode <- getLastError + if errCode == c_ERROR_PRIVILEGE_NOT_HELD + then ioError . (`ioeSetErrorString` permissionErrorMsg) $ + mkIOError permissionErrorType "" Nothing (Just link) + else failWith "createSymbolicLink" errCode + else return () + where c_ERROR_PRIVILEGE_NOT_HELD = 0x522 + permissionErrorMsg = "no permission to create symbolic links" +#endif + +-- | Attempt to create a symbolic link. On Windows, this falls back to +-- copying if forbidden due to Group Policies. +tryCreateSymbolicLink :: FilePath -> FilePath -> IO () +tryCreateSymbolicLink target link = createSymbolicLink target link +#ifdef mingw32_HOST_OS + `catchIOError` \ e -> + if isPermissionError e + then do + copyPathRecursive (takeDirectory link target) link + hPutStrLn stderr "warning: didn't test symlinks due to Group Policy" + else ioError e +#endif diff --git a/tests/all.T b/tests/all.T index 3279e5d..d2a8440 100644 --- a/tests/all.T +++ b/tests/all.T @@ -28,3 +28,5 @@ test('createDirectoryIfMissing001', normal, compile_and_run, ['']) test('getHomeDirectory001', ignore_output, compile_and_run, ['']) test('T8482', normal, compile_and_run, ['']) + +test('removeDirectoryRecursive001', normal, compile_and_run, ['']) diff --git a/tests/removeDirectoryRecursive001.hs b/tests/removeDirectoryRecursive001.hs new file mode 100644 index 0000000..fbd38e7 --- /dev/null +++ b/tests/removeDirectoryRecursive001.hs @@ -0,0 +1,93 @@ +{-# LANGUAGE CPP #-} +module Main (main) where +import Data.List (sort) +import System.Directory +import System.FilePath ((), normalise) +import System.IO.Error (catchIOError) +import TestUtils + +testName :: String +testName = "removeDirectoryRecursive001" + +tmpD :: String +tmpD = testName ++ ".tmp" + +tmp :: String -> String +tmp s = tmpD normalise s + +main :: IO () +main = do + + ------------------------------------------------------------ + -- clean up junk from previous invocations + + modifyPermissions (tmp "c") (\ p -> p { writable = True }) + `catchIOError` \ _ -> return () + removeDirectoryRecursive tmpD + `catchIOError` \ _ -> return () + + ------------------------------------------------------------ + -- set up + + createDirectoryIfMissing True (tmp "a/x/w") + createDirectoryIfMissing True (tmp "a/y") + createDirectoryIfMissing True (tmp "a/z") + createDirectoryIfMissing True (tmp "b") + createDirectoryIfMissing True (tmp "c") + writeFile (tmp "a/x/w/u") "foo" + writeFile (tmp "a/t") "bar" + tryCreateSymbolicLink (normalise "../a") (tmp "b/g") + tryCreateSymbolicLink (normalise "../b") (tmp "c/h") + tryCreateSymbolicLink (normalise "a") (tmp "d") + modifyPermissions (tmp "c") (\ p -> p { writable = False }) + + ------------------------------------------------------------ + -- tests + + getDirectoryContents tmpD >>= putStrLn . unwords . sort + getDirectoryContents (tmp "a") >>= putStrLn . unwords . sort + getDirectoryContents (tmp "b") >>= putStrLn . unwords . sort + getDirectoryContents (tmp "c") >>= putStrLn . unwords . sort + getDirectoryContents (tmp "d") >>= putStrLn . unwords . sort + + putStrLn "" + + removeDirectoryRecursive (tmp "d") + `catchIOError` \ _ -> removeFile (tmp "d") +#ifdef mingw32_HOST_OS + `catchIOError` \ _ -> removeDirectory (tmp "d") +#endif + + getDirectoryContents tmpD >>= putStrLn . unwords . sort + getDirectoryContents (tmp "a") >>= putStrLn . unwords . sort + getDirectoryContents (tmp "b") >>= putStrLn . unwords . sort + getDirectoryContents (tmp "c") >>= putStrLn . unwords . sort + + putStrLn "" + + removeDirectoryRecursive (tmp "c") + `catchIOError` \ _ -> do + modifyPermissions (tmp "c") (\ p -> p { writable = True }) + removeDirectoryRecursive (tmp "c") + + getDirectoryContents tmpD >>= putStrLn . unwords . sort + getDirectoryContents (tmp "a") >>= putStrLn . unwords . sort + getDirectoryContents (tmp "b") >>= putStrLn . unwords . sort + + putStrLn "" + + removeDirectoryRecursive (tmp "b") + + getDirectoryContents tmpD >>= putStrLn . unwords . sort + getDirectoryContents (tmp "a") >>= putStrLn . unwords . sort + + putStrLn "" + + removeDirectoryRecursive (tmp "a") + + getDirectoryContents tmpD >>= putStrLn . unwords . sort + + ------------------------------------------------------------ + -- clean up + + removeDirectoryRecursive tmpD diff --git a/tests/removeDirectoryRecursive001.stdout b/tests/removeDirectoryRecursive001.stdout new file mode 100644 index 0000000..0967014 --- /dev/null +++ b/tests/removeDirectoryRecursive001.stdout @@ -0,0 +1,19 @@ +. .. a b c d +. .. t x y z +. .. g +. .. h +. .. t x y z + +. .. a b c +. .. t x y z +. .. g +. .. h + +. .. a b +. .. t x y z +. .. g + +. .. a +. .. t x y z + +. .. From git at git.haskell.org Thu Mar 19 11:38:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:12 +0000 (UTC) Subject: [commit: packages/process] master: Don't overwrite `std_err` in the CreateProcess record and add a note which handles are ignored. (650fadf) Message-ID: <20150319113812.9EF7B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/650fadfb7e80897c6ceb759d223ca5703e7df994/process >--------------------------------------------------------------- commit 650fadfb7e80897c6ceb759d223ca5703e7df994 Author: Bartosz Nitka Date: Fri Feb 27 06:20:57 2015 -0800 Don't overwrite `std_err` in the CreateProcess record and add a note which handles are ignored. >--------------------------------------------------------------- 650fadfb7e80897c6ceb759d223ca5703e7df994 System/Process.hsc | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/System/Process.hsc b/System/Process.hsc index 13c36ad..e9d470f 100644 --- a/System/Process.hsc +++ b/System/Process.hsc @@ -422,6 +422,8 @@ readProcess cmd args = readCreateProcess $ proc cmd args -- > > readCreateProcess (shell "pwd" { cwd = "/etc/" }) "" -- > "/etc\n" -- +-- Note that @Handle at s provided for @std_in@ or @std_out@ via the CreateProcess +-- record will be ignored. -- /Since: 1.2.3.0/ readCreateProcess @@ -432,7 +434,6 @@ readCreateProcess cp input = do let cp_opts = cp { std_in = CreatePipe, std_out = CreatePipe, - std_err = Inherit } (ex, output) <- withCreateProcess_ "readCreateProcess" cp_opts $ \(Just inh) (Just outh) _ ph -> do From git at git.haskell.org Thu Mar 19 11:38:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:12 +0000 (UTC) Subject: [commit: packages/directory] master: Add script to run the GHC test framework (47335ad) Message-ID: <20150319113812.D96FC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/47335adef0e5d801d9a1f323aaf5c50f186609e5/directory >--------------------------------------------------------------- commit 47335adef0e5d801d9a1f323aaf5c50f186609e5 Author: Phil Ruffwind Date: Sun Mar 1 16:02:42 2015 -0500 Add script to run the GHC test framework The script automatically clones the GHC repo and invokes the test framework with the correct arguments. A patch for the GHC repo is also included to work around bugs/incompatbilities. Note that it requires an existing Cabal project to work, due to the need for Cabal-specific files and configuration. Coupling the tests to Cabal allows them to be run using the version of project that is in the current working tree rather than whatever that's installed. Note that the project must still be built beforehand. Also, if a sandbox is used, the script must be run under `cabal exec`. >--------------------------------------------------------------- 47335adef0e5d801d9a1f323aaf5c50f186609e5 tools/ghc.patch | 62 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++ tools/run-tests | 50 ++++++++++++++++++++++++++++++++++++++++++++++ 2 files changed, 112 insertions(+) diff --git a/tools/ghc.patch b/tools/ghc.patch new file mode 100644 index 0000000..61ce567 --- /dev/null +++ b/tools/ghc.patch @@ -0,0 +1,62 @@ +# allow ghc and its tools to be located in different directories +--- testsuite/mk/boilerplate.mk ++++ testsuite/mk/boilerplate.mk +@@ -56,6 +56,7 @@ TEST_HC := $(STAGE2_GHC) + endif + + else ++implicit_compiler = YES + IN_TREE_COMPILER = NO + TEST_HC := $(shell which ghc) + endif +@@ -87,24 +88,30 @@ endif + # containing spaces + BIN_ROOT = $(shell dirname '$(TEST_HC)') + ++ifeq "$(implicit_compiler)" "YES" ++find_tool = $(shell which $(1)) ++else ++find_tool = $(BIN_ROOT)/$(1) ++endif ++ + ifeq "$(GHC_PKG)" "" +-GHC_PKG := $(BIN_ROOT)/ghc-pkg ++GHC_PKG := $(call find_tool,ghc-pkg) + endif + + ifeq "$(RUNGHC)" "" +-RUNGHC := $(BIN_ROOT)/runghc ++RUNGHC := $(call find_tool,runghc) + endif + + ifeq "$(HSC2HS)" "" +-HSC2HS := $(BIN_ROOT)/hsc2hs ++HSC2HS := $(call find_tool,hsc2hs) + endif + + ifeq "$(HP2PS_ABS)" "" +-HP2PS_ABS := $(BIN_ROOT)/hp2ps ++HP2PS_ABS := $(call find_tool,hp2ps) + endif + + ifeq "$(HPC)" "" +-HPC := $(BIN_ROOT)/hpc ++HPC := $(call find_tool,hpc) + endif + + $(eval $(call canonicaliseExecutable,TEST_HC)) + +# 'die' is not available until GHC 7.10 +--- testsuite/timeout/timeout.hs ++++ testsuite/timeout/timeout.hs +@@ -30,8 +30,8 @@ main = do + [secs,cmd] -> + case reads secs of + [(secs', "")] -> run secs' cmd +- _ -> die ("Can't parse " ++ show secs ++ " as a number of seconds") +- _ -> die ("Bad arguments " ++ show args) ++ _ -> ((>> exitFailure) . hPutStrLn stderr) ("Can't parse " ++ show secs ++ " as a number of seconds") ++ _ -> ((>> exitFailure) . hPutStrLn stderr) ("Bad arguments " ++ show args) + + timeoutMsg :: String + timeoutMsg = "Timeout happened...killing process..." diff --git a/tools/run-tests b/tools/run-tests new file mode 100755 index 0000000..c71b958 --- /dev/null +++ b/tools/run-tests @@ -0,0 +1,50 @@ +#!/bin/sh +# run all of the tests under the `tests` directory using the GHC test +# framework; for more info about this framework, see: +# https://ghc.haskell.org/trac/ghc/wiki/Building/RunningTests +# +# arguments received by this script are passed as arguments to the `make` +# invocation that initiates the tests +set -e + +# check if `-package-db` is supported (didn't exist until 1.20) +# note that we don't use `-package-db` directly because older versions will +# interpret it as `-package -db` +if ghc 2>&1 -no-user-package-db | + grep >/dev/null 2>&1 "ghc: unrecognised flags: -no-user-package-db" +then db=conf +else db=db +fi + +[ -z "$HSFLAGS" ] || HSFLAGS=\ $HSFLAGS +HSFLAGS="-package-$db ../dist/package.conf.inplace$HSFLAGS" +HSFLAGS="-optP-include -optP../dist/build/autogen/cabal_macros.h $HSFLAGS" +export HSFLAGS + +# download the GHC repository +[ -f dist/testsuite/ghc.ok ] || { + rm -fr dist/testsuite/ghc + git clone --depth 1 https://github.com/ghc/ghc dist/testsuite/ghc + patch dist/testsuite/Makefile \ + "s|^TOP=.*$|TOP=../dist/testsuite/ghc/testsuite|" \ + tests/Makefile + +cd tests +make -f ../dist/testsuite/Makefile WAY=normal EXTRA_HC_OPTS="$HSFLAGS" "$@" | + tee ../dist/testsuite/test.out + +# since the test framework doesn't report an exit status, we need to manually +# find out whether the test had any failures> +{ + grep '^ *0 had missing libraries$' ../dist/testsuite/test.out + grep '^ *0 caused framework failures$' ../dist/testsuite/test.out + grep '^ *0 unexpected passes$' ../dist/testsuite/test.out + grep '^ *0 unexpected failures$' ../dist/testsuite/test.out + grep '^ *0 unexpected stat failures$' ../dist/testsuite/test.out +} >/dev/null 2>/dev/null From git at git.haskell.org Thu Mar 19 11:38:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:14 +0000 (UTC) Subject: [commit: packages/process] master: Fix a syntax error (cac4d84) Message-ID: <20150319113814.A5D2C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cac4d8495bdbedf6900605b624f647aca5182421/process >--------------------------------------------------------------- commit cac4d8495bdbedf6900605b624f647aca5182421 Author: Bartosz Nitka Date: Fri Feb 27 07:28:44 2015 -0800 Fix a syntax error >--------------------------------------------------------------- cac4d8495bdbedf6900605b624f647aca5182421 System/Process.hsc | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Process.hsc b/System/Process.hsc index e9d470f..cbefb2c 100644 --- a/System/Process.hsc +++ b/System/Process.hsc @@ -433,7 +433,7 @@ readCreateProcess readCreateProcess cp input = do let cp_opts = cp { std_in = CreatePipe, - std_out = CreatePipe, + std_out = CreatePipe } (ex, output) <- withCreateProcess_ "readCreateProcess" cp_opts $ \(Just inh) (Just outh) _ ph -> do From git at git.haskell.org Thu Mar 19 11:38:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:14 +0000 (UTC) Subject: [commit: packages/directory] master: Hook test suite to `cabal test` (b80a204) Message-ID: <20150319113814.E08DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b80a2041a72d0408f774fa05f7b0685a927d2c71/directory >--------------------------------------------------------------- commit b80a2041a72d0408f774fa05f7b0685a927d2c71 Author: Phil Ruffwind Date: Mon Mar 2 05:09:03 2015 -0500 Hook test suite to `cabal test` `cabal test` now invokes the GHC test framework to run the tests. In effect, it's just a wrapper that runs `tools/run-tests` with the correct environment. This is somewhat complicated by the fact that we cannot add `process` as a dependency, so we have to reinvent the wheel just to launch the shell script. >--------------------------------------------------------------- b80a2041a72d0408f774fa05f7b0685a927d2c71 directory.cabal | 14 +++++------ test/main.hs | 20 ---------------- tools/dispatch-tests.hs | 63 +++++++++++++++++++++++++++++++++++++++++++++++++ 3 files changed, 70 insertions(+), 27 deletions(-) diff --git a/directory.cabal b/directory.cabal index c648e0d..d134c05 100644 --- a/directory.cabal +++ b/directory.cabal @@ -64,10 +64,10 @@ Library ghc-options: -Wall test-suite test - default-language: Haskell2010 - hs-source-dirs: test - main-is: main.hs - type: exitcode-stdio-1.0 - build-depends: base - , directory - , containers + default-language: Haskell2010 + other-extensions: CPP ForeignFunctionInterface + ghc-options: -Wall + hs-source-dirs: tools + main-is: dispatch-tests.hs + type: exitcode-stdio-1.0 + build-depends: base, directory diff --git a/test/main.hs b/test/main.hs deleted file mode 100644 index 7a9fcb3..0000000 --- a/test/main.hs +++ /dev/null @@ -1,20 +0,0 @@ -{-# LANGUAGE NoImplicitPrelude #-} --- Simplistic test suite for now. Worthwhile to add a dependency on a --- test framework at some point. -module Main (main) where - -import qualified Data.Set as Set -import Prelude (IO, error, fmap, return, show, (==)) -import System.Directory (getDirectoryContents) - -main :: IO () -main = do - let expected = Set.fromList - [ "." - , ".." - , "main.hs" - ] - actual <- fmap Set.fromList (getDirectoryContents "test") - if expected == actual - then return () - else error (show (expected, actual)) diff --git a/tools/dispatch-tests.hs b/tools/dispatch-tests.hs new file mode 100644 index 0000000..598cd8b --- /dev/null +++ b/tools/dispatch-tests.hs @@ -0,0 +1,63 @@ +{-# LANGUAGE CPP, ForeignFunctionInterface #-} +module Main (main) where +import Foreign (Ptr) +import Foreign.C (CChar(..), CInt(..), withCString) +import Data.Functor ((<$>)) +import System.Directory () -- to make sure `directory` is built beforehand +import System.Environment (getArgs) +import System.Exit (ExitCode(ExitSuccess, ExitFailure), exitWith) + +main :: IO () +main = do + + -- check if 'cabal exec' is supported (didn't exist until 1.20) + cabalExecTest <- rawSystem "sh" ["-c", "cabal >/dev/null 2>&1 exec true"] + + -- execute in the Cabal sandbox environment if possible + let prefix = case cabalExecTest of + ExitSuccess -> ["cabal", "exec", "--"] + ExitFailure _ -> [] + + args <- getArgs + let command : arguments = prefix ++ ["sh", "tools/run-tests"] ++ args + exitWith =<< normalizeExitCode <$> rawSystem command arguments + +makeExitCode :: Int -> ExitCode +makeExitCode 0 = ExitSuccess +makeExitCode e = ExitFailure e + +-- on Linux the exit code is right-shifted by 8 bits, causing exit codes to be +-- rather large; older versions of GHC don't seem to handle that well in +-- `exitWith` +normalizeExitCode :: ExitCode -> ExitCode +normalizeExitCode ExitSuccess = ExitSuccess +normalizeExitCode (ExitFailure _) = ExitFailure 1 + +-- we can't use the `process` library as it causes a dependency cycle with +-- Cabal, so we reinvent the wheel here in a simplistic way; this will +-- probably break with non-ASCII characters on Windows +rawSystem :: String -> [String] -> IO ExitCode +rawSystem cmd args = + withCString (quoteCmdArgs (cmd : args)) $ \ c_command -> + makeExitCode . fromIntegral <$> c_system c_command + +-- handle the different quoting rules in CMD.EXE vs POSIX shells +quoteCmdArgs :: [String] -> String +quoteCmdArgs cmdArgs = +#ifdef mingw32_HOST_OS + -- the arcane quoting rules require us to add an extra set of quotes + -- around the entire thing: see `help cmd` or look at + -- https://superuser.com/a/238813 + "\"" ++ unwords (quote <$> cmdArgs) ++ "\"" + where quote s = "\"" ++ replaceElem '"' "\"\"" s ++ "\"" +#else + unwords (quote <$> cmdArgs) + where quote s = "'" ++ replaceElem '\'' "'\\''" s ++ "'" +#endif + +replaceElem :: Eq a => a -> [a] -> [a] -> [a] +replaceElem match repl = concat . (replace <$>) + where replace c | c == match = repl + | otherwise = [c] + +foreign import ccall safe "stdlib.h system" c_system :: Ptr CChar -> IO CInt From git at git.haskell.org Thu Mar 19 11:38:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:16 +0000 (UTC) Subject: [commit: packages/process] master: Merge branch 'readCreateProcess' of github.com:niteria/process into readCreateProcess (c421397) Message-ID: <20150319113816.ABAFF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c421397dde9c9b93aaa07c1a195c230c2950df0b/process >--------------------------------------------------------------- commit c421397dde9c9b93aaa07c1a195c230c2950df0b Merge: cac4d84 049e8e3 Author: Bartosz Nitka Date: Fri Feb 27 07:30:52 2015 -0800 Merge branch 'readCreateProcess' of github.com:niteria/process into readCreateProcess Conflicts: System/Process.hsc >--------------------------------------------------------------- c421397dde9c9b93aaa07c1a195c230c2950df0b From git at git.haskell.org Thu Mar 19 11:38:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:16 +0000 (UTC) Subject: [commit: packages/directory] master: Add test-related files to source distribution (a6de021) Message-ID: <20150319113816.E82EC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a6de02181e646ef7eed0dd52a6c112c84a5275de/directory >--------------------------------------------------------------- commit a6de02181e646ef7eed0dd52a6c112c84a5275de Author: Phil Ruffwind Date: Mon Mar 2 08:34:59 2015 -0500 Add test-related files to source distribution A script was also added to make updating `directory.cabal` easier when new tests are added. >--------------------------------------------------------------- a6de02181e646ef7eed0dd52a6c112c84a5275de directory.cabal | 17 ++++++ tools/update-extra-source-files | 123 ++++++++++++++++++++++++++++++++++++++++ 2 files changed, 140 insertions(+) diff --git a/directory.cabal b/directory.cabal index d134c05..4ee4012 100644 --- a/directory.cabal +++ b/directory.cabal @@ -29,6 +29,23 @@ extra-source-files: directory.buildinfo include/HsDirectoryConfig.h.in install-sh + tests/*.hs + tests/*.stderr + tests/*.stdout + tests/Makefile + tests/all.T + tests/copyFile001dir/source + tests/copyFile002dir/source + tests/createDirectory001.stdout-mingw32 + tests/createDirectoryIfMissing001.stdout-mingw32 + tests/getDirContents002.stderr-mingw32 + tests/getPermissions001.stdout-alpha-dec-osf3 + tests/getPermissions001.stdout-i386-unknown-freebsd + tests/getPermissions001.stdout-i386-unknown-openbsd + tests/getPermissions001.stdout-mingw + tests/getPermissions001.stdout-x86_64-unknown-openbsd + tools/ghc.patch + tools/run-tests source-repository head type: git diff --git a/tools/update-extra-source-files b/tools/update-extra-source-files new file mode 100755 index 0000000..a7af432 --- /dev/null +++ b/tools/update-extra-source-files @@ -0,0 +1,123 @@ +#!/usr/bin/env python +# since cabal is rather picky about wildcards in 'extra-source-files', +# we have to fill this in ourselves; this script automates that +import os, re, subprocess + +ensure_str_encoding = [] +def ensure_str(string): + '''Ensure that the argument is in fact a Unicode string. If it isn't, + then: + + - on Python 2, it will be decoded using the preferred encoding; + - on Python 3, it will trigger a `TypeError`. + ''' + # Python 2 + if getattr(str, "decode", None) and getattr(str, "encode", None): + if isinstance(string, unicode): + return string + if not ensure_str_encoding: + import locale + ensure_str_encoding.append(locale.getpreferredencoding(False)) + return string.decode(ensure_str_encoding[0]) + # Python 3 + if isinstance(string, str): + return string + raise TypeError("not an instance of 'str': " + repr(string)) + +def rename(src_filename, dest_filename): + '''Rename a file (allows overwrites on Windows).''' + import os + if os.name == "nt": + import ctypes + success = ctypes.windll.kernel32.MoveFileExW( + ensure_str(src_filename), + ensure_str(dest_filename), + ctypes.c_ulong(0x1), + ) + if not success: + raise ctypes.WinError() + return + os.rename(src_filename, dest_filename) + +def read_file(filename, binary=False): + '''Read the contents of a file.''' + with open(filename, "rb" if binary else "rt") as file: + contents = file.read() + if not binary: + contents = ensure_str(contents) + return contents + +def write_file(filename, contents, binary=False, safe=True): + '''Write the contents to a file. Unless `safe` is false, it is performed + as atomically as possible. A temporary directory is used to store the + file while it is being written.''' + if not safe: + if not binary: + contents = ensure_str(contents) + with open(filename, "wb" if binary else "wt") as file: + file.write(contents) + return + import os, shutil, tempfile + try: + tmp_dir = tempfile.mkdtemp( + suffix=".tmp", + prefix="." + os.path.basename(filename) + ".", + dir=os.path.dirname(filename), + ) + tmp_filename = os.path.join(tmp_dir, "file.tmp") + write_file(tmp_filename, contents, binary, safe=False) + rename(tmp_filename, filename) + finally: + try: + shutil.rmtree(tmp_dir) + except Exception: + pass + +def find_cabal_fn(): + '''Obtain the filename of the `*.cabal` file.''' + fns = [fn for fn in os.listdir(".") + if re.match(r"[\w-]+.cabal$", fn) and os.path.isfile(fn)] + if len(fns) < 1: + raise Exception("can't find .cabal file in current directory") + elif len(fns) > 1: + raise Exception("too many .cabal files in current directory") + return fns[0] + +def git_tracked_files(): + '''Obtain the list of file tracked by Git.''' + return subprocess.check_output( + ["git", "ls-tree", "-r", "--name-only", "HEAD"] + ).decode("utf-8").split("\n") + +indent = " " * 4 + +dir_name = "tests" + +# extensions that are always included by default +src_extensions = [ + ".hs", + ".stderr", + ".stdout", +] + +# additional source files not covered by 'src_extensions' +srcs = [indent + fn + "\n" for fn in git_tracked_files() + if os.path.basename(fn) != ".gitignore" + and fn.startswith(dir_name + "/") + and (os.path.dirname(fn) != dir_name or + os.path.splitext(fn)[1] not in src_extensions)] + +# convert the extensions into patterns +src_patterns = [indent + dir_name + "/*" + ext + "\n" + for ext in src_extensions] + +# update the .cabal file +cabal_fn = find_cabal_fn() +contents = read_file(cabal_fn) +contents = re.sub(r"\n(\s*" + dir_name + "/.*\n)+", + "\n" + "".join(src_patterns + srcs), + contents, count=1) +write_file(cabal_fn, + contents.encode("utf8"), + # don't use Windows line-endings + binary=True) From git at git.haskell.org Thu Mar 19 11:38:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:18 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #24 from niteria/readCreateProcess (dd3ff59) Message-ID: <20150319113818.B3BB63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dd3ff59b2662e270b7ae5bdaee1edeefaccf375f/process >--------------------------------------------------------------- commit dd3ff59b2662e270b7ae5bdaee1edeefaccf375f Merge: 160bdd1 c421397 Author: Michael Snoyman Date: Sun Mar 1 16:54:59 2015 +0200 Merge pull request #24 from niteria/readCreateProcess Add readCreateProcess function >--------------------------------------------------------------- dd3ff59b2662e270b7ae5bdaee1edeefaccf375f System/Process.hsc | 36 ++++++++++++++++++++++++++++++------ changelog.md | 2 ++ 2 files changed, 32 insertions(+), 6 deletions(-) From git at git.haskell.org Thu Mar 19 11:38:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:18 +0000 (UTC) Subject: [commit: packages/directory] master: Update `.travis.yml` for new test system (eaf7236) Message-ID: <20150319113818.EF1643A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eaf72360d99cb99b864af271d49b631f08877cf9/directory >--------------------------------------------------------------- commit eaf72360d99cb99b864af271d49b631f08877cf9 Author: Phil Ruffwind Date: Tue Mar 3 02:23:00 2015 -0500 Update `.travis.yml` for new test system Travis CI will now run the entire test suite using the GHC test framework. Tweaks were made to work around missing features in older versions of Cabal. >--------------------------------------------------------------- eaf72360d99cb99b864af271d49b631f08877cf9 .travis.yml | 34 +++++++++++++++++++++++----------- 1 file changed, 23 insertions(+), 11 deletions(-) diff --git a/.travis.yml b/.travis.yml index 05ed4e4..bc3fe44 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,3 +1,6 @@ +# we want to use our custom environment, but the Travis YAML validator +# requires this field to be specified, so we'll just use 'c' +language: c env: # we have to use CABALVER=1.16 for GHC<7.6 as well, as there's # no package for earlier cabal versions in the PPA @@ -20,22 +23,31 @@ before_install: install: - travis_retry cabal update - - cabal install --only-dependencies + - cabal install --enable-tests --only-dependencies - ghc --version +before_script: + - | # check if 'streaming' is supported (didn't exist until 1.20) + if cabal 2>&1 test --show-details=streaming __dummy | + grep >/dev/null 2>&1 "cabal: --show-details flag expects" + then streaming=always + else streaming=streaming + fi + export streaming + script: - autoreconf -i - cabal configure -v2 --enable-tests - cabal build - cabal check - cabal sdist - - cabal test -# The following scriptlet checks that the resulting source distribution can be built & installed - - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; - cd dist/; - if [ -f "$SRC_TGZ" ]; then - cabal install --force-reinstalls "$SRC_TGZ"; - else - echo "expected '$SRC_TGZ' not found"; - exit 1; - fi + - cabal test --show-details=$streaming + - | # in the future, use '--run-tests' (didn't exist until 1.20) + cabal install --force-reinstalls dist/*-*.tar.gz + mkdir install-tmp + cd install-tmp + tar xzf ../dist/*-*.tar.gz + cd *-* + cabal configure --enable-tests + cabal build + cabal test From git at git.haskell.org Thu Mar 19 11:38:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:20 +0000 (UTC) Subject: [commit: packages/process] master: readCreateProcessWithExitCode (d0a62be) Message-ID: <20150319113820.BDC893A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d0a62be4d7d5867676da285540c21e2e2d8cd0c7/process >--------------------------------------------------------------- commit d0a62be4d7d5867676da285540c21e2e2d8cd0c7 Author: Michael Snoyman Date: Sun Mar 1 17:07:24 2015 +0200 readCreateProcessWithExitCode >--------------------------------------------------------------- d0a62be4d7d5867676da285540c21e2e2d8cd0c7 System/Process.hsc | 21 ++++++++++++++++++--- changelog.md | 2 +- 2 files changed, 19 insertions(+), 4 deletions(-) diff --git a/System/Process.hsc b/System/Process.hsc index c73326a..32ad6af 100644 --- a/System/Process.hsc +++ b/System/Process.hsc @@ -42,6 +42,7 @@ module System.Process ( spawnCommand, readCreateProcess, readProcess, + readCreateProcessWithExitCode, readProcessWithExitCode, -- ** Related utilities @@ -484,13 +485,27 @@ readProcessWithExitCode -> [String] -- ^ any arguments -> String -- ^ standard input -> IO (ExitCode,String,String) -- ^ exitcode, stdout, stderr -readProcessWithExitCode cmd args input = do - let cp_opts = (proc cmd args) { +readProcessWithExitCode cmd args = + readCreateProcessWithExitCode $ proc cmd args + +-- | @readCreateProcessWithExitCode@ works exactly like 'readProcessWithExitCode' except that it +-- lets you pass 'CreateProcess' giving better flexibility. +-- +-- Note that @Handle at s provided for @std_in@, @std_out@, or @std_err@ via the CreateProcess +-- record will be ignored. +-- +-- /Since: 1.2.3.0/ +readCreateProcessWithExitCode + :: CreateProcess + -> String -- ^ standard input + -> IO (ExitCode,String,String) -- ^ exitcode, stdout, stderr +readCreateProcessWithExitCode cp input = do + let cp_opts = cp { std_in = CreatePipe, std_out = CreatePipe, std_err = CreatePipe } - withCreateProcess_ "readProcessWithExitCode" cp_opts $ + withCreateProcess_ "readCreateProcessWithExitCode" cp_opts $ \(Just inh) (Just outh) (Just errh) ph -> do out <- hGetContents outh diff --git a/changelog.md b/changelog.md index e5a7faa..7d27d6c 100644 --- a/changelog.md +++ b/changelog.md @@ -5,7 +5,7 @@ * [Meaningful error message when exe not found on close\_fds is True](https://ghc.haskell.org/trac/ghc/ticket/3649#comment:10) - * New function `readCreateProcess` + * New functions `readCreateProcess` and `readCreateProcessWithExitCode` ## 1.2.2.0 *Jan 2015* From git at git.haskell.org Thu Mar 19 11:38:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:21 +0000 (UTC) Subject: [commit: packages/directory] master: Fix the tests for older versions of GHC (e856866) Message-ID: <20150319113821.0160B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e856866d6a46a910c3b297ca8c5e6198860f9fec/directory >--------------------------------------------------------------- commit e856866d6a46a910c3b297ca8c5e6198860f9fec Author: Phil Ruffwind Date: Tue Mar 3 06:10:50 2015 -0500 Fix the tests for older versions of GHC >--------------------------------------------------------------- e856866d6a46a910c3b297ca8c5e6198860f9fec tests/canonicalizePath001.hs | 8 +++----- tests/createDirectoryIfMissing001.hs | 6 +++--- 2 files changed, 6 insertions(+), 8 deletions(-) diff --git a/tests/canonicalizePath001.hs b/tests/canonicalizePath001.hs index dc21cd8..2c66a71 100644 --- a/tests/canonicalizePath001.hs +++ b/tests/canonicalizePath001.hs @@ -1,10 +1,8 @@ -module Main(main) where - -import Control.Exception +module Main (main) where import System.Directory +import System.IO.Error (catchIOError) main = do dot <- canonicalizePath "." - nul <- (canonicalizePath "") - `catch` ((\_ -> return "") :: IOException -> IO String) + nul <- canonicalizePath "" `catchIOError` \ _ -> return "" print (dot == nul) diff --git a/tests/createDirectoryIfMissing001.hs b/tests/createDirectoryIfMissing001.hs index bd80761..b99e5a1 100644 --- a/tests/createDirectoryIfMissing001.hs +++ b/tests/createDirectoryIfMissing001.hs @@ -2,7 +2,7 @@ module Main(main) where import Control.Concurrent import Control.Monad -import Control.Exception +import Control.Exception as E import System.Directory import System.FilePath import System.IO.Error @@ -66,14 +66,14 @@ cleanup = ignore $ removeDirectoryRecursive testdir report :: Show a => IO a -> IO () report io = do - r <- try io + r <- E.try io case r of Left e -> print (e :: SomeException) Right a -> print a ignore :: IO a -> IO () ignore io = do - r <- try io + r <- E.try io case r of Left e -> let _ = e :: SomeException in return () Right a -> return () From git at git.haskell.org Thu Mar 19 11:38:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:22 +0000 (UTC) Subject: [commit: packages/process] master: Fix GHC test process006 (ae10a33) Message-ID: <20150319113822.C50123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ae10a33cd16d9ac9238a193e5355c5c2e05ef0a2/process >--------------------------------------------------------------- commit ae10a33cd16d9ac9238a193e5355c5c2e05ef0a2 Author: Thomas Miedema Date: Sun Mar 8 21:40:45 2015 +0100 Fix GHC test process006 >--------------------------------------------------------------- ae10a33cd16d9ac9238a193e5355c5c2e05ef0a2 tests/process006.stdout | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/process006.stdout b/tests/process006.stdout index 5e2e409..1e1186b 100644 --- a/tests/process006.stdout +++ b/tests/process006.stdout @@ -1,4 +1,4 @@ "yan\ntan\tether\n" (ExitSuccess,"yan\ntan\tether\n","") (ExitFailure 3,"stdout\n","stderr\n") -Left readProcess: sh "-c" "echo stdout; echo stderr 1>&2; exit 3" (exit 3): failed +Left readCreateProcess: sh "-c" "echo stdout; echo stderr 1>&2; exit 3" (exit 3): failed From git at git.haskell.org Thu Mar 19 11:38:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:23 +0000 (UTC) Subject: [commit: packages/directory] master: Fix confusing (& wrong) release date for 1.2.2.0 (e04430d) Message-ID: <20150319113823.06F1C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e04430d2e65baa28ab4fd8c0c044b5819d63006a/directory >--------------------------------------------------------------- commit e04430d2e65baa28ab4fd8c0c044b5819d63006a Author: Herbert Valerio Riedel Date: Tue Mar 10 10:53:20 2015 +0100 Fix confusing (& wrong) release date for 1.2.2.0 >--------------------------------------------------------------- e04430d2e65baa28ab4fd8c0c044b5819d63006a changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index 6e4ef5f..e0cd786 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`directory` package](http://hackage.haskell.org/package/directory) -## 1.2.2.0 *Jan 2014* +## 1.2.2.0 *Mar 2015* * Bundled with GHC 7.10.1 From git at git.haskell.org Thu Mar 19 11:38:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:24 +0000 (UTC) Subject: [commit: packages/process] master: Use Python format string for GHC test T4198 (acfb062) Message-ID: <20150319113824.CA0573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/acfb062c05d12c31d49b06eaa093f8068788c7a8/process >--------------------------------------------------------------- commit acfb062c05d12c31d49b06eaa093f8068788c7a8 Author: Thomas Miedema Date: Sun Mar 8 12:11:11 2015 +0100 Use Python format string for GHC test T4198 The ghc test framework calls `cmd.format(**config.__dict__)` before running `cmd`, and `config.compiler` is already quoted. >--------------------------------------------------------------- acfb062c05d12c31d49b06eaa093f8068788c7a8 tests/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/all.T b/tests/all.T index 292f730..ee9d7c7 100644 --- a/tests/all.T +++ b/tests/all.T @@ -22,7 +22,7 @@ test('T3231', compile_and_run, ['']) test('T4198', - [pre_cmd('\'' + config.compiler + '\'' + ' exitminus1.c -no-hs-main -o exitminus1'), + [pre_cmd('{compiler} exitminus1.c -no-hs-main -o exitminus1'), extra_clean(['exitminus1.o', 'exitminus1', 'exitminus1.exe'])], compile_and_run, ['']) From git at git.haskell.org Thu Mar 19 11:38:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:25 +0000 (UTC) Subject: [commit: packages/directory] master: Disable warning in `TestUtils.tryCreateSymbolicLink` (087dbc3) Message-ID: <20150319113825.0E8983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/087dbc3d7ca0e792770bafd153a8a815763e124b/directory >--------------------------------------------------------------- commit 087dbc3d7ca0e792770bafd153a8a815763e124b Author: Phil Ruffwind Date: Sun Mar 8 14:17:02 2015 -0400 Disable warning in `TestUtils.tryCreateSymbolicLink` This is to prevent the test from failing on Windows due to the lack of privileges to create symbolic links. >--------------------------------------------------------------- 087dbc3d7ca0e792770bafd153a8a815763e124b tests/TestUtils.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/tests/TestUtils.hs b/tests/TestUtils.hs index 36c357e..a6faea0 100644 --- a/tests/TestUtils.hs +++ b/tests/TestUtils.hs @@ -81,8 +81,6 @@ tryCreateSymbolicLink target link = createSymbolicLink target link #ifdef mingw32_HOST_OS `catchIOError` \ e -> if isPermissionError e - then do - copyPathRecursive (takeDirectory link target) link - hPutStrLn stderr "warning: didn't test symlinks due to Group Policy" + then copyPathRecursive (takeDirectory link target) link else ioError e #endif From git at git.haskell.org Thu Mar 19 11:38:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:26 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #26 from thomie/fix-ghc-test (51d3f71) Message-ID: <20150319113826.D0FAF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/51d3f716bbc0491d552fa265278fe724f93471bc/process >--------------------------------------------------------------- commit 51d3f716bbc0491d552fa265278fe724f93471bc Merge: d0a62be acfb062 Author: Michael Snoyman Date: Mon Mar 9 07:35:15 2015 +0200 Merge pull request #26 from thomie/fix-ghc-test Update 2 GHC tests >--------------------------------------------------------------- 51d3f716bbc0491d552fa265278fe724f93471bc tests/all.T | 2 +- tests/process006.stdout | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) From git at git.haskell.org Thu Mar 19 11:38:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:27 +0000 (UTC) Subject: [commit: packages/directory] master: Update `README.md` (7f8fed1) Message-ID: <20150319113827.156F93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7f8fed1c688cdc3ed3b9c6954fc744ea15b8d9fc/directory >--------------------------------------------------------------- commit 7f8fed1c688cdc3ed3b9c6954fc744ea15b8d9fc Author: Phil Ruffwind Date: Tue Mar 3 16:53:52 2015 -0500 Update `README.md` >--------------------------------------------------------------- 7f8fed1c688cdc3ed3b9c6954fc744ea15b8d9fc README.md | 32 ++++++++++++++++++++------------ 1 file changed, 20 insertions(+), 12 deletions(-) diff --git a/README.md b/README.md index 2b1cedc..5eb5566 100644 --- a/README.md +++ b/README.md @@ -1,15 +1,23 @@ -The `directory` Package [![Hackage](https://img.shields.io/hackage/v/directory.svg)](https://hackage.haskell.org/package/directory) [![Build Status](https://travis-ci.org/haskell/directory.svg?branch=master)](https://travis-ci.org/haskell/directory) -======================= +`directory` [![Hackage][1]][2] [![Build Status][3]][4] +=========== -See [`directory` on Hackage](http://hackage.haskell.org/package/directory) for -more information. +Documentation can be found on [Hackage][2]. -Installing from Git -------------------- +Building from Git repository +---------------------------- -To build this package using Cabal directly from Git, you must run -`autoreconf -i` before the usual Cabal build steps (`cabal -{configure,build,install}`). The program `autoreconf` is part of -[GNU autoconf](http://www.gnu.org/software/autoconf/). There is no -need to run the `configure` script: `cabal configure` will do this for -you. +When building this package directly from the Git repository, one must run +`autoreconf -i` to generate the `configure` script needed by `cabal +configure`. This requires [Autoconf][5] to be installed. + + autoreconf -i + cabal install + +There is no need to run the `configure` script manually however, as `cabal +configure` does that automatically. + +[1]: https://img.shields.io/hackage/v/directory.svg +[2]: https://hackage.haskell.org/package/directory +[3]: https://travis-ci.org/haskell/directory.svg?branch=master +[4]: https://travis-ci.org/haskell/directory +[5]: https://gnu.org/software/autoconf From git at git.haskell.org Thu Mar 19 11:38:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:28 +0000 (UTC) Subject: [commit: packages/process] master: Allow filepath-1.4 (c8cdaef) Message-ID: <20150319113828.D8FDE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c8cdaef5585717089a53be61cb6f08b3120f18b4/process >--------------------------------------------------------------- commit c8cdaef5585717089a53be61cb6f08b3120f18b4 Author: Herbert Valerio Riedel Date: Wed Mar 11 08:50:45 2015 +0100 Allow filepath-1.4 See haskell/filepath at d039d5ae7c070452a443219fdb7df65508567338 >--------------------------------------------------------------- c8cdaef5585717089a53be61cb6f08b3120f18b4 process.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/process.cabal b/process.cabal index 26b280f..9898648 100644 --- a/process.cabal +++ b/process.cabal @@ -61,7 +61,7 @@ library build-depends: base >= 4.4 && < 4.9, directory >= 1.1 && < 1.3, - filepath >= 1.2 && < 1.4, + filepath >= 1.2 && < 1.5, deepseq >= 1.1 && < 1.5 if os(windows) build-depends: Win32 >=2.2 && < 2.4 From git at git.haskell.org Thu Mar 19 11:38:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:29 +0000 (UTC) Subject: [commit: packages/directory] master: Formatting and date changes in `changelog.md` (7d4a98e) Message-ID: <20150319113829.1D5743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7d4a98ef9af86dd4c7e16498a53f5fcefdea4f18/directory >--------------------------------------------------------------- commit 7d4a98ef9af86dd4c7e16498a53f5fcefdea4f18 Author: Phil Ruffwind Date: Tue Mar 3 06:28:22 2015 -0500 Formatting and date changes in `changelog.md` >--------------------------------------------------------------- 7d4a98ef9af86dd4c7e16498a53f5fcefdea4f18 changelog.md | 35 ++++++++++++++++++++--------------- 1 file changed, 20 insertions(+), 15 deletions(-) diff --git a/changelog.md b/changelog.md index e0cd786..ecc6838 100644 --- a/changelog.md +++ b/changelog.md @@ -1,32 +1,35 @@ -# Changelog for [`directory` package](http://hackage.haskell.org/package/directory) +Changelog for the [`directory`][1] package +========================================== -## 1.2.2.0 *Mar 2015* +## 1.2.2.0 (Mar 2015) * Bundled with GHC 7.10.1 - * make `getModificationTime` support sub-second resolution on windows + * Make `getModificationTime` support sub-second resolution on Windows * Fix silent failure in `createDirectoryIfMissing` * Replace `throw` by better defined `throwIO`s - * Avoid stack overflow in `getDirectoryContents` [#17](https://github.com/haskell/directory/pull/17) + * [#17](https://github.com/haskell/directory/pull/17): + Avoid stack overflow in `getDirectoryContents` - * Expose `findExecutables` [#14](https://github.com/haskell/directory/issues/14) + * [#14](https://github.com/haskell/directory/issues/14): + Expose `findExecutables` - * `removeDirectoryRecursive` no longer follows symlinks under any - circumstances, fixing the inconsistency as noted in - [#15](https://github.com/haskell/directory/issues/15) + * [#15](https://github.com/haskell/directory/issues/15): + `removeDirectoryRecursive` no longer follows symlinks under any + circumstances - * Allow trailing path separators in `getPermissions` on Windows - (fixes [#9](https://github.com/haskell/directory/issues/9)) + * [#9](https://github.com/haskell/directory/issues/9): + Allow trailing path separators in `getPermissions` on Windows - * `renameFile` now always throws the correct error type - (`InappropriateType`) when the destination is a directory (as long as the - filesystem is not being modified concurrently). See - [pull request #8](https://github.com/haskell/directory/pull/8). + * [#8](https://github.com/haskell/directory/pull/8): + `renameFile` now always throws the correct error type + (`InappropriateType`) when the destination is a directory, as long as the + filesystem is not being modified concurrently -## 1.2.1.0 *Mar 2014* +## 1.2.1.0 (Mar 2014) * Bundled with GHC 7.8.1 @@ -45,3 +48,5 @@ * Fix `findExecutable` to check that file permissions indicate executable * New convenience functions `findFiles` and `findFilesWith` + +[1]: https://hackage.haskell.org/package/directory From git at git.haskell.org Thu Mar 19 11:38:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:30 +0000 (UTC) Subject: [commit: packages/process] master: Fix changelog (unreleased => March 2015) (67efaf5) Message-ID: <20150319113830.E0DBE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/67efaf599a03f454a98a3905820ce40aa80825c7/process >--------------------------------------------------------------- commit 67efaf599a03f454a98a3905820ce40aa80825c7 Author: Michael Snoyman Date: Tue Mar 17 11:33:10 2015 +0200 Fix changelog (unreleased => March 2015) Pinging @hvr >--------------------------------------------------------------- 67efaf599a03f454a98a3905820ce40aa80825c7 changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index 7d27d6c..25f19ab 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`process` package](http://hackage.haskell.org/package/process) -## 1.2.3.0 *unreleased* +## 1.2.3.0 *March 2015* * [Meaningful error message when exe not found on close\_fds is True](https://ghc.haskell.org/trac/ghc/ticket/3649#comment:10) From git at git.haskell.org Thu Mar 19 11:38:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:31 +0000 (UTC) Subject: [commit: packages/directory] master: Update `directory.cabal` with new info (e561278) Message-ID: <20150319113831.250D53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e561278ca4950d4aa19dbcdfa568c32cbaedddf8/directory >--------------------------------------------------------------- commit e561278ca4950d4aa19dbcdfa568c32cbaedddf8 Author: Phil Ruffwind Date: Tue Mar 3 16:34:18 2015 -0500 Update `directory.cabal` with new info >--------------------------------------------------------------- e561278ca4950d4aa19dbcdfa568c32cbaedddf8 directory.cabal | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/directory.cabal b/directory.cabal index 4ee4012..0a041c1 100644 --- a/directory.cabal +++ b/directory.cabal @@ -4,10 +4,11 @@ version: 1.2.2.0 license: BSD3 license-file: LICENSE maintainer: libraries at haskell.org -bug-reports: http://ghc.haskell.org/trac/ghc/newticket?component=libraries/directory -synopsis: library for directory handling +bug-reports: https://github.com/haskell/directory/issues +synopsis: Platform-agnostic library for filesystem operations description: - This package provides a library for handling directories. + This library provides a basic set of operations for manipulating files and + directories in a portable way. category: System build-type: Configure cabal-version: >= 1.10 From git at git.haskell.org Thu Mar 19 11:38:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:33 +0000 (UTC) Subject: [commit: packages/directory] master: Add `makeAbsolute` function (87530fc) Message-ID: <20150319113833.2C4A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/87530fce17b5a5dc131af13aa0bedcd9eea793f5/directory >--------------------------------------------------------------- commit 87530fce17b5a5dc131af13aa0bedcd9eea793f5 Author: Phil Ruffwind Date: Fri Mar 6 04:40:18 2015 -0500 Add `makeAbsolute` function The function makes a path absolute by prepending the current directory and normalising the result. >--------------------------------------------------------------- 87530fce17b5a5dc131af13aa0bedcd9eea793f5 System/Directory.hs | 13 +++++++++++++ changelog.md | 3 +++ 2 files changed, 16 insertions(+) diff --git a/System/Directory.hs b/System/Directory.hs index 0e2c071..32dc453 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -44,6 +44,7 @@ module System.Directory , copyFile , canonicalizePath + , makeAbsolute , makeRelativeToCurrentDirectory , findExecutable , findExecutables @@ -778,6 +779,18 @@ foreign import ccall unsafe "realpath" -> IO CString #endif +-- | Make a path absolute by prepending the current directory (if it isn't +-- already absolute) and applying @'normalise'@ to the result. +-- +-- The operation may fail with the same exceptions as @'getCurrentDirectory'@. +-- +-- /Since: 1.2.2.0/ +makeAbsolute :: FilePath -> IO FilePath +makeAbsolute = fmap normalise . absolutize + where absolutize path -- avoid the call to `getCurrentDirectory` if we can + | isRelative path = fmap ( path) getCurrentDirectory + | otherwise = return path + -- | 'makeRelative' the current directory. makeRelativeToCurrentDirectory :: FilePath -> IO FilePath makeRelativeToCurrentDirectory x = do diff --git a/changelog.md b/changelog.md index ecc6838..31c8393 100644 --- a/changelog.md +++ b/changelog.md @@ -29,6 +29,9 @@ Changelog for the [`directory`][1] package (`InappropriateType`) when the destination is a directory, as long as the filesystem is not being modified concurrently + * Add `makeAbsolute`, which should be preferred over `canonicalizePath` + unless one requires symbolic links to be resolved + ## 1.2.1.0 (Mar 2014) * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 11:38:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:35 +0000 (UTC) Subject: [commit: packages/directory] master: Update documentation of `canonicalizePath` (e87edde) Message-ID: <20150319113835.342683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e87eddebece7d67dc0276fa71eeb3b49aea46a92/directory >--------------------------------------------------------------- commit e87eddebece7d67dc0276fa71eeb3b49aea46a92 Author: Phil Ruffwind Date: Wed Mar 11 02:24:33 2015 -0400 Update documentation of `canonicalizePath` >--------------------------------------------------------------- e87eddebece7d67dc0276fa71eeb3b49aea46a92 System/Directory.hs | 33 ++++++++++++++++++--------------- 1 file changed, 18 insertions(+), 15 deletions(-) diff --git a/System/Directory.hs b/System/Directory.hs index 32dc453..be8379d 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -737,24 +737,27 @@ copyFile fromFPath toFPath = ignoreIOExceptions io = io `catchIOError` (\_ -> return ()) --- | Given a path referring to a file or directory, returns a --- canonicalized path. The intent is that two paths referring --- to the same file\/directory will map to the same canonicalized --- path. +-- | Canonicalize the path of an existing file or directory. The intent is +-- that two paths referring to the same file\/directory will map to the same +-- canonicalized path. -- --- Note that it is impossible to guarantee that the --- implication (same file\/dir \<=\> same canonicalizedPath) holds --- in either direction: this function can make only a best-effort --- attempt. +-- __Note__: if you only require an absolute path, consider using +-- @'makeAbsolute'@ instead, which is more reliable and does not have +-- unspecified behavior on nonexistent paths. -- --- The precise behaviour is that of the C realpath function --- GetFullPathNameW on Windows). In particular, the behaviour --- on paths that do not exist is known to vary from platform --- to platform. Some platforms do not alter the input, some --- do, and on some an exception will be thrown. +-- It is impossible to guarantee that the implication (same file\/dir \<=\> +-- same canonicalized path) holds in either direction: this function can make +-- only a best-effort attempt. +-- +-- The precise behaviour is that of the POSIX @realpath@ function (or +-- @GetFullPathNameW@ on Windows). In particular, the behaviour on paths that +-- don't exist can vary from platform to platform. Some platforms do not +-- alter the input, some do, and some throw an exception. +-- +-- An empty path is considered to be equivalent to the current directory. +-- +-- /Known bug(s)/: on Windows, this function does not resolve symbolic links. -- --- If passed an empty string, behaviour is equivalent to --- calling canonicalizePath on the current directory. canonicalizePath :: FilePath -> IO FilePath canonicalizePath "" = canonicalizePath "." canonicalizePath fpath = From git at git.haskell.org Thu Mar 19 11:38:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 11:38:37 +0000 (UTC) Subject: [commit: packages/directory] master: Allow filepath-1.4 (7233248) Message-ID: <20150319113837.3A0E23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7233248952648ed4dd213f91ed52af2317a3f23b/directory >--------------------------------------------------------------- commit 7233248952648ed4dd213f91ed52af2317a3f23b Author: Herbert Valerio Riedel Date: Wed Mar 11 08:49:43 2015 +0100 Allow filepath-1.4 See haskell/filepath at d039d5ae7c070452a443219fdb7df65508567338 >--------------------------------------------------------------- 7233248952648ed4dd213f91ed52af2317a3f23b directory.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/directory.cabal b/directory.cabal index 0a041c1..52e0116 100644 --- a/directory.cabal +++ b/directory.cabal @@ -73,7 +73,7 @@ Library build-depends: base >= 4.5 && < 4.9, time >= 1.4 && < 1.6, - filepath >= 1.3 && < 1.4 + filepath >= 1.3 && < 1.5 if os(windows) build-depends: Win32 >= 2.2.2 && < 2.4 else From git at git.haskell.org Thu Mar 19 12:56:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 12:56:21 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Major rewrite: Pt 3: General fixes + added some smart constructors (b6943e6) Message-ID: <20150319125621.DA1AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/b6943e620008dbca1fec9222590a14416f1d9aa4/ghc >--------------------------------------------------------------- commit b6943e620008dbca1fec9222590a14416f1d9aa4 Author: George Karachalias Date: Thu Mar 19 13:52:53 2015 +0100 Major rewrite: Pt 3: General fixes + added some smart constructors >--------------------------------------------------------------- b6943e620008dbca1fec9222590a14416f1d9aa4 compiler/deSugar/Check.hs | 68 +++++++++++++++++++++++------------------------ 1 file changed, 34 insertions(+), 34 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 84f6272..b5b8890 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -728,12 +728,8 @@ data PmConstraint = TmConstraint Id (HsExpr Id) data Abstraction = P -- Pattern abstraction | V -- Value abstraction -{- COMEHERE: Replace PmPat2 with simple PmPat when the time comes -} -{- COMEHERE: Ignore lazy and strict patterns for now -} - data PmPat2 :: Abstraction -> * where --- GLetAbs :: PmPat2 P -> HsExpr Id -> PmPat2 P -- Guard: let P = e (lazy) - GBindAbs :: PmPat2 P -> HsExpr Id -> PmPat2 P -- Guard: P <- e (strict) + GBindAbs :: [PmPat2 P] -> HsExpr Id -> PmPat2 P -- Guard: P <- e (strict be default) Instead of a single P use a list [AsPat] ConAbs :: DataCon -> [PmPat2 abs] -> PmPat2 abs -- Constructor: K ps VarAbs :: Id -> PmPat2 abs -- Variable: x @@ -759,9 +755,9 @@ translatePat usupply pat = case pat of ParPat p -> translatePat usupply (unLoc p) LazyPat p -> translatePat usupply (unLoc p) -- COMEHERE: We ignore laziness for now BangPat p -> translatePat usupply (unLoc p) -- COMEHERE: We ignore strictness for now - AsPat lid p -> translatePat usupply (unLoc p) -- COMEHERE: FIXME: `lid' may appear in view patterns etc. - SigPatOut p ty -> translatePat usupply (unLoc p) -- COMEHERE: FIXME: What to do with the ty?? - CoPat wrapper p ty -> error "COMEHERE: FIXME: CoPat" -- CAREFUL WITH THIS + AsPat lid p -> VarAbs (unLoc lid) : translatePat usupply (unLoc p) + SigPatOut p ty -> translatePat usupply (unLoc p) -- COMEHERE: FIXME: Exploit the signature? + CoPat wrapper p ty -> translatePat usupply p -- COMEHERE: Make sure the coercion is not useful NPlusKPat n k ge minus -> error "COMEHERE" ViewPat lexpr lpat arg_ty -> error "COMEHERE" ListPat _ _ (Just (_,_)) -> error "COMEHERE: FIXME: Overloaded List" @@ -772,12 +768,10 @@ translatePat usupply pat = case pat of NPat lit mb_neg eq -> -- COMEHERE: Double check this. Also do something with the fixity? let var = mkPmId usupply (hsPatType pat) - var_pat = VarAbs var - hs_var = noLoc (HsVar var) - pattern = ConAbs trueDataCon [] -- COMEHERE: I do not like the noLoc thing + hs_var = noLoc (HsVar var) -- COMEHERE: I do not like the noLoc thing expr_lit = noLoc (negateOrNot mb_neg lit) -- COMEHERE: I do not like the noLoc thing expr = OpApp hs_var (noLoc eq) no_fixity expr_lit -- COMEHERE: I do not like the noLoc thing - in [VarAbs var, GBindAbs pattern expr] + in [VarAbs var, eqTrueExpr expr] LitPat lit -> [mkPmVar usupply (hsPatType pat)] -- COMEHERE: Wrong. Should be like NPat (which eq to use?) @@ -803,6 +797,9 @@ translatePat usupply pat = case pat of QuasiQuotePat {} -> panic "Check.translatePat: QuasiQuotePat" SigPatIn {} -> panic "Check.translatePat: SigPatIn" +eqTrueExpr :: HsExpr Id -> PatAbs +eqTrueExpr expr = GBindAbs [ConAbs trueDataCon []] expr + no_fixity :: a no_fixity = panic "COMEHERE: no fixity!!" @@ -848,13 +845,9 @@ tailValSetAbs :: ValSetAbs -> ValSetAbs tailValSetAbs Empty = Empty tailValSetAbs Singleton = panic "tailValSetAbs: Singleton" tailValSetAbs (Union vsa1 vsa2) = Union (tailValSetAbs vsa1) (tailValSetAbs vsa2) -tailValSetAbs (Constraint cs vsa) = Constraint cs (tailValSetAbs vsa) -- [1] +tailValSetAbs (Constraint cs vsa) = cs `addConstraints` tailValSetAbs vsa tailValSetAbs (Cons _ vsa) = vsa -- actual work --- COMEHERE: Optimisation for [1]: --- tailValSetAbs (Constraint cs vsa) | vsa' <- tailValSetAbs vsa --- = cs `addConstraints` vsa' -- In case more cs emerge at the head of vsa' - wrapK :: DataCon -> ValSetAbs -> ValSetAbs wrapK con = wrapK_aux (dataConSourceArity con) emptylist where @@ -904,31 +897,20 @@ covered usupply vec (Constraint cs vsa) = Constraint cs (covered usupply vec vsa -- CGuard covered usupply (GBindAbs p e : ps) vsa - = Constraint cs $ tailValSetAbs $ covered usupply2 (p:ps) (Cons (VarAbs y) vsa) -- [3] + | vsa' <- tailValSetAbs $ covered usupply2 (p++ps) (Cons (VarAbs y) vsa) + = cs `addConstraints` vsa' where (usupply1, usupply2) = splitUniqSupply usupply y = mkPmId usupply1 undefined -- COMEHERE: WHAT TYPE?? cs = [TmConstraint y e] --- COMEHERE: Optimisation for [3]: --- covered usupply (GBindAbs p e : ps) vsa --- | vsa' <- tailValSetAbs $ covered usupply2 (p:ps) (Cons (VarAbs y) vsa) --- = cs `addConstraints` vsa' --- where --- (usupply1, usupply2) = splitUniqSupply usupply --- y = mkPmVar usupply1 undefined -- COMEHERE: WHAT TYPE?? --- cs = [TmConstraint y e] - -- CVar covered usupply (VarAbs x : ps) (Cons va vsa) - = Cons va $ Constraint cs $ covered usupply ps vsa -- [2] + | vsa' <- covered usupply ps vsa + = Cons va $ cs `addConstraints` vsa' -- [2] where cs = [TmConstraint x (valAbsToHsExpr va)] --- COMEHERE: Optimisation for [2]: --- covered usupply (VarAbs x : ps) (Cons va vsa) --- | vsa' <- covered ps vsa --- = Cons va $ cs `addConstraints` vsa' --- where cs = [TmConstraint x (valAbsToHsExpr va)] +-- [2] COMEHERE: Maybe generate smart constructors for all, so that empty has only one representation (Empty) -- CConCon covered usupply (ConAbs c1 args1 : ps) (Cons (ConAbs c2 args2) vsa) @@ -966,7 +948,7 @@ uncovered usupply vec (Constraint cs vsa) = Constraint cs (uncovered usupply vec -- UGuard uncovered usupply (GBindAbs p e : ps) vsa - = Constraint cs $ tailValSetAbs $ uncovered usupply2 (p:ps) (Cons (VarAbs y) vsa) -- [3] + = Constraint cs $ tailValSetAbs $ uncovered usupply2 (p++ps) (Cons (VarAbs y) vsa) -- [3] where (usupply1, usupply2) = splitUniqSupply usupply y = mkPmId usupply1 undefined -- COMEHERE: WHAT TYPE?? @@ -1054,3 +1036,21 @@ valAbsToHsExpr (ConAbs c ps) = foldl lHsApp cexpr psexprs psexprs = map valAbsToHsExpr ps lHsApp le re = noLoc le `HsApp` noLoc re -- add locations (useless) to arguments +-- ---------------------------------------------------------------------------- +-- | Smart constructors +-- NB: The only representation of an empty value set is `Empty' + +addConstraints :: [PmConstraint] -> ValSetAbs -> ValSetAbs +addConstraints _cs Empty = Empty -- No point in adding constraints in an empty set. Maybe make it an invariant? (I mean that if empty(vsa) => vsa==Empty, like the bags) +addConstraints cs1 (Constraint cs2 vsa) = Constraint (cs1++cs2) vsa -- careful about associativity +addConstraints cs other_vsa = Constraint cs other_vsa + +unionValSetAbs :: ValSetAbs -> ValSetAbs -> ValSetAbs +unionValSetAbs Empty vsa = vsa +unionValSetAbs vsa Empty = vsa +unionValSetAbs vsa1 vsa2 = Union vsa1 vsa2 + +consValSetAbs :: ValAbs -> ValSetAbs -> ValSetAbs +consValSetAbs _ Empty = Empty +consValSetAbs va vsa = Cons va vsa + From git at git.haskell.org Thu Mar 19 14:18:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 14:18:27 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: Integrate jstolarek’s wording improvements (537ddb0) Message-ID: <20150319141827.2A7E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/537ddb011de858990aadab4ea6a08f10ec2cbd05/ghc >--------------------------------------------------------------- commit 537ddb011de858990aadab4ea6a08f10ec2cbd05 Author: Joachim Breitner Date: Thu Mar 19 15:18:17 2015 +0100 CmmSwitch: Integrate jstolarek?s wording improvements >--------------------------------------------------------------- 537ddb011de858990aadab4ea6a08f10ec2cbd05 ...{CmmCreateSwitchPlans.hs => CmmImplementSwitchPlans.hs} | 8 ++++---- compiler/cmm/CmmPipeline.hs | 4 ++-- compiler/cmm/CmmSwitch.hs | 14 +++++++------- compiler/codeGen/StgCmmUtils.hs | 2 +- compiler/ghc.cabal.in | 2 +- 5 files changed, 15 insertions(+), 15 deletions(-) diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmImplementSwitchPlans.hs similarity index 94% rename from compiler/cmm/CmmCreateSwitchPlans.hs rename to compiler/cmm/CmmImplementSwitchPlans.hs index 1ca0cd4..a321489 100644 --- a/compiler/cmm/CmmCreateSwitchPlans.hs +++ b/compiler/cmm/CmmImplementSwitchPlans.hs @@ -1,6 +1,6 @@ {-# LANGUAGE GADTs #-} -module CmmCreateSwitchPlans - ( cmmCreateSwitchPlans +module CmmImplementSwitchPlans + ( cmmImplementSwitchPlans ) where @@ -28,8 +28,8 @@ import DynFlags -- | Traverses the 'CmmGraph', making sure that 'CmmSwitch' are suitable for -- code generation. -cmmCreateSwitchPlans :: DynFlags -> CmmGraph -> UniqSM CmmGraph -cmmCreateSwitchPlans dflags g +cmmImplementSwitchPlans :: DynFlags -> CmmGraph -> UniqSM CmmGraph +cmmImplementSwitchPlans dflags g | targetSupportsSwitch (hscTarget dflags) = return g | otherwise = do blocks' <- concat `fmap` mapM (visitSwitches dflags) (toBlockList g) diff --git a/compiler/cmm/CmmPipeline.hs b/compiler/cmm/CmmPipeline.hs index eb89325..37dbd12 100644 --- a/compiler/cmm/CmmPipeline.hs +++ b/compiler/cmm/CmmPipeline.hs @@ -11,7 +11,7 @@ import Cmm import CmmLint import CmmBuildInfoTables import CmmCommonBlockElim -import CmmCreateSwitchPlans +import CmmImplementSwitchPlans import CmmProcPoint import CmmContFlowOpt import CmmLayoutStack @@ -73,7 +73,7 @@ cpsTop hsc_env proc = -- elimCommonBlocks g <- {-# SCC "createSwitchPlans" #-} - runUniqSM $ cmmCreateSwitchPlans dflags g + runUniqSM $ cmmImplementSwitchPlans dflags g dump Opt_D_dump_cmm_switch "Post switch plan" g ----------- Proc points ------------------------------------------------- diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs index e58b049..e96b64b 100644 --- a/compiler/cmm/CmmSwitch.hs +++ b/compiler/cmm/CmmSwitch.hs @@ -32,7 +32,7 @@ import qualified Data.Map as M -- * The Stg ? Cmm transformation creates a single `SwitchTargets` in -- emitSwitch and emitCmmLitSwitch in StgCmmUtils.hs. -- At this stage, they are unsuitable for code generation. --- * A dedicated Cmm transformation (CmmCreateSwitchPlans) replaces these +-- * A dedicated Cmm transformation (CmmImplementSwitchPlans) replaces these -- switch statements with code that is suitable for code generation, i.e. -- a nice balanced tree of decisions with dense jump tables in the leafs. -- The actual planning of this tree is performed in pure code in createSwitchPlan @@ -40,11 +40,11 @@ import qualified Data.Map as M -- * The actual code generation will not do any further processing and -- implement each CmmSwitch with a jump tables. -- --- When compiling to LLVM or C, CmmCreateSwitchPlans leaves the switch +-- When compiling to LLVM or C, CmmImplementSwitchPlans leaves the switch -- statements alone, as we can turn a SwitchTargets value into a nice -- switch-statement in LLVM resp. C, and leave the rest to the compiler. -- --- See Note [CmmSwitch vs. CmmCreateSwitchPlans] why the two module are +-- See Note [CmmSwitch vs. CmmImplementSwitchPlans] why the two module are -- separated. ----------------------------------------------------------------------------- @@ -393,23 +393,23 @@ reassocTuples initial [] last reassocTuples initial ((a,b):tuples) last = (initial,a) : reassocTuples b tuples last --- Note [CmmSwitch vs. CmmCreateSwitchPlans] +-- Note [CmmSwitch vs. CmmImplementSwitchPlans] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -- I (Joachim) separated the two somewhat closely related modules -- -- - CmmSwitch, which provides the CmmSwitchTargets type and contains the strategy -- for implementing a Cmm switch (createSwitchPlan), and --- - CmmCreateSwitchPlans, which contains the actuall Cmm graph modification, +-- - CmmImplementSwitchPlans, which contains the actuall Cmm graph modification, -- -- for these reasons: -- -- * CmmSwitch is very low in the dependency tree, i.e. does not depend on any -- GHC specific modules at all (with the exception of Output and Hoople --- (Literal)). CmmCreateSwitchPlans is the Cmm transformation and hence very +-- (Literal)). CmmImplementSwitchPlans is the Cmm transformation and hence very -- high in the dependency tree. -- * CmmSwitch provides the CmmSwitchTargets data type, which is abstract, but -- used in CmmNodes. -- * Because CmmSwitch is low in the dependency tree, the separation allows -- for more parallelism when building GHC. -- * The interaction between the modules is very explicit and easy to --- understande, due to the small and simple interface. +-- understand, due to the small and simple interface. diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index b9b8016..9e05658 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -494,7 +494,7 @@ mk_discrete_switch _ _tag_expr [(_tag,lbl)] Nothing _ -- In that situation we can be sure the (:) case -- can't happen, so no need to test --- SOMETHING MORE COMPLICATED: defer to CmmCreateSwitchPlans +-- SOMETHING MORE COMPLICATED: defer to CmmImplementSwitchPlans -- See Note [Cmm Switches, the general plan] in CmmSwitch mk_discrete_switch signed tag_expr branches mb_deflt range = mkSwitch tag_expr $ mkSwitchTargets signed range mb_deflt (M.fromList branches) diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index 9bbaed7..11c366d 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -197,7 +197,7 @@ Library CmmPipeline CmmCallConv CmmCommonBlockElim - CmmCreateSwitchPlans + CmmImplementSwitchPlans CmmContFlowOpt CmmExpr CmmInfo From git at git.haskell.org Thu Mar 19 15:23:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:23:09 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Major rewrite: Pt 5: Fixing and cleaning stuff (c32e111) Message-ID: <20150319152309.5656C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/c32e1114a7788d39221429da552b8865949550dd/ghc >--------------------------------------------------------------- commit c32e1114a7788d39221429da552b8865949550dd Author: George Karachalias Date: Thu Mar 19 14:42:50 2015 +0100 Major rewrite: Pt 5: Fixing and cleaning stuff * Only smart constructors used * Added some pretty printing * Fixed an ugly bug in UConVar >--------------------------------------------------------------- c32e1114a7788d39221429da552b8865949550dd compiler/deSugar/Check.hs | 56 +++++++++++++++++++++++++++++------------------ 1 file changed, 35 insertions(+), 21 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index b5b8890..fdac5c7 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -744,6 +744,24 @@ data ValSetAbs | Constraint [PmConstraint] ValSetAbs -- Extend Delta | Cons ValAbs ValSetAbs -- map (ucon u) vs +-- ---------------------------------------------------------------------------- +-- | Pretty printing + +instance Outputable PmConstraint where + ppr (TmConstraint x expr) = ppr x <+> ptext (sLit "~~") <+> ppr expr + ppr (TyConstraint thetas) = pprSet (map idType thetas) + +instance Outputable (PmPat2 abs) where + ppr (GBindAbs pats expr) = ppr pats <+> ptext (sLit "<-") <+> ppr expr + ppr (ConAbs con args) = sep [ppr con, pprWithParens2 args] + ppr (VarAbs x) = ppr x + +pprWithParens2 :: [PmPat2 abs] -> SDoc +pprWithParens2 pats = sep (map paren_if_needed pats) + where paren_if_needed p | ConAbs _ args <- p, not (null args) = parens (ppr p) + | GBindAbs ps _ <- p, not (null ps) = parens (ppr p) + | otherwise = ppr p + -- ----------------------------------------------------------------------- -- | Transform a Pat Id into a list of (PmPat Id) -- Note [Translation to PmPat] @@ -844,7 +862,7 @@ mkPmId usupply ty = mkLocalId name ty tailValSetAbs :: ValSetAbs -> ValSetAbs tailValSetAbs Empty = Empty tailValSetAbs Singleton = panic "tailValSetAbs: Singleton" -tailValSetAbs (Union vsa1 vsa2) = Union (tailValSetAbs vsa1) (tailValSetAbs vsa2) +tailValSetAbs (Union vsa1 vsa2) = tailValSetAbs vsa1 `unionValSetAbs` tailValSetAbs vsa2 tailValSetAbs (Constraint cs vsa) = cs `addConstraints` tailValSetAbs vsa tailValSetAbs (Cons _ vsa) = vsa -- actual work @@ -853,11 +871,11 @@ wrapK con = wrapK_aux (dataConSourceArity con) emptylist where wrapK_aux :: Int -> DList ValAbs -> ValSetAbs -> ValSetAbs wrapK_aux _ _ Empty = Empty - wrapK_aux 0 args vsa = Cons (ConAbs con (toList args)) vsa + wrapK_aux 0 args vsa = ConAbs con (toList args) `consValSetAbs` vsa wrapK_aux _ _ Singleton = panic "wrapK: Singleton" wrapK_aux n args (Cons vs vsa) = wrapK_aux (n-1) (args `snoc` vs) vsa - wrapK_aux n args (Constraint cs vsa) = Constraint cs (wrapK_aux n args vsa) - wrapK_aux n args (Union vsa1 vsa2) = Union (wrapK_aux n args vsa1) (wrapK_aux n args vsa2) + wrapK_aux n args (Constraint cs vsa) = cs `addConstraints` wrapK_aux n args vsa + wrapK_aux n args (Union vsa1 vsa2) = wrapK_aux n args vsa1 `unionValSetAbs` wrapK_aux n args vsa2 -- ---------------------------------------------------------------------------- -- | Some difference lists stuff for efficiency @@ -889,11 +907,11 @@ covered _usupply _vec Empty = Empty covered _usupply [] Singleton = Singleton -- Pure induction (New case because of representation) -covered usupply vec (Union vsa1 vsa2) = Union (covered usupply1 vec vsa1) (covered usupply2 vec vsa2) +covered usupply vec (Union vsa1 vsa2) = covered usupply1 vec vsa1 `unionValSetAbs` covered usupply2 vec vsa2 where (usupply1, usupply2) = splitUniqSupply usupply -- Pure induction (New case because of representation) -covered usupply vec (Constraint cs vsa) = Constraint cs (covered usupply vec vsa) +covered usupply vec (Constraint cs vsa) = cs `addConstraints` covered usupply vec vsa -- CGuard covered usupply (GBindAbs p e : ps) vsa @@ -906,12 +924,9 @@ covered usupply (GBindAbs p e : ps) vsa -- CVar covered usupply (VarAbs x : ps) (Cons va vsa) - | vsa' <- covered usupply ps vsa - = Cons va $ cs `addConstraints` vsa' -- [2] + = va `consValSetAbs` (cs `addConstraints` covered usupply ps vsa) where cs = [TmConstraint x (valAbsToHsExpr va)] --- [2] COMEHERE: Maybe generate smart constructors for all, so that empty has only one representation (Empty) - -- CConCon covered usupply (ConAbs c1 args1 : ps) (Cons (ConAbs c2 args2) vsa) | c1 /= c2 = Empty @@ -919,7 +934,7 @@ covered usupply (ConAbs c1 args1 : ps) (Cons (ConAbs c2 args2) vsa) -- CConVar covered usupply (ConAbs con args : ps) (Cons (VarAbs x) vsa) - = covered usupply2 (ConAbs con args : ps) (Cons con_abs (Constraint all_cs vsa)) -- [4] + = covered usupply2 (ConAbs con args : ps) (con_abs `consValSetAbs` (all_cs `addConstraints` vsa)) where (usupply1, usupply2) = splitUniqSupply usupply (con_abs, all_cs) = mkOneConFull x usupply1 con @@ -940,15 +955,15 @@ uncovered _usupply _vec Empty = Empty uncovered _usupply [] Singleton = Empty -- Pure induction (New case because of representation) -uncovered usupply vec (Union vsa1 vsa2) = Union (uncovered usupply1 vec vsa1) (uncovered usupply2 vec vsa2) +uncovered usupply vec (Union vsa1 vsa2) = uncovered usupply1 vec vsa1 `unionValSetAbs` uncovered usupply2 vec vsa2 where (usupply1, usupply2) = splitUniqSupply usupply -- Pure induction (New case because of representation) -uncovered usupply vec (Constraint cs vsa) = Constraint cs (uncovered usupply vec vsa) +uncovered usupply vec (Constraint cs vsa) = cs `addConstraints` uncovered usupply vec vsa -- UGuard uncovered usupply (GBindAbs p e : ps) vsa - = Constraint cs $ tailValSetAbs $ uncovered usupply2 (p++ps) (Cons (VarAbs y) vsa) -- [3] + = cs `addConstraints` (tailValSetAbs $ uncovered usupply2 (p++ps) (VarAbs y `consValSetAbs` vsa)) where (usupply1, usupply2) = splitUniqSupply usupply y = mkPmId usupply1 undefined -- COMEHERE: WHAT TYPE?? @@ -956,17 +971,16 @@ uncovered usupply (GBindAbs p e : ps) vsa -- UVar uncovered usupply (VarAbs x : ps) (Cons va vsa) - = Cons va $ Constraint cs $ uncovered usupply ps vsa -- [2] + = va `consValSetAbs` (cs `addConstraints` uncovered usupply ps vsa) where cs = [TmConstraint x (valAbsToHsExpr va)] -- UConCon uncovered usupply (ConAbs c1 args1 : ps) (Cons (ConAbs c2 args2) vsa) - | c1 /= c2 = Cons (ConAbs c2 args2) vsa - | otherwise = wrapK c1 (uncovered usupply (args1 ++ ps) (foldr Cons vsa args2)) + | c1 /= c2 = ConAbs c2 args2 `consValSetAbs` vsa + | otherwise = wrapK c1 (uncovered usupply (args1 ++ ps) (foldr consValSetAbs vsa args2)) --- CConVar +-- UConVar uncovered usupply (ConAbs con args : ps) (Cons (VarAbs x) vsa) - -- = Constraint all_cs $ covered usupply4 (ConAbs con args : ps) (Cons con_abs vsa) = covered usupply2 (ConAbs con args : ps) inst_vsa -- instantiated vsa [x \mapsto K_j ys] where -- Some more uniqSupplies @@ -975,8 +989,8 @@ uncovered usupply (ConAbs con args : ps) (Cons (VarAbs x) vsa) -- Unfold the variable to all possible constructor patterns uniqs_cons = listSplitUniqSupply usupply1 `zip` allConstructors con cons_cs = map (uncurry (mkOneConFull x)) uniqs_cons - add_one (va,cs) valset = Cons va $ Constraint cs valset - inst_vsa = foldr add_one vsa cons_cs + add_one (va,cs) valset = valset `unionValSetAbs` (va `consValSetAbs` (cs `addConstraints` vsa)) + inst_vsa = foldr add_one Empty cons_cs uncovered _usupply (ConAbs _ _ : _) Singleton = panic "uncovered: length mismatch: constructor-sing" uncovered _usupply (VarAbs _ : _) Singleton = panic "uncovered: length mismatch: variable-sing" From git at git.haskell.org Thu Mar 19 15:23:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:23:12 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Fixed AsPat, NPlusKPat, ViewPat and ListPat translation (b9ed6e8) Message-ID: <20150319152312.22CEF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/b9ed6e8cdfba8c02e8e02cf274b89e8776a08407/ghc >--------------------------------------------------------------- commit b9ed6e8cdfba8c02e8e02cf274b89e8776a08407 Author: George Karachalias Date: Thu Mar 19 16:22:23 2015 +0100 Fixed AsPat, NPlusKPat, ViewPat and ListPat translation >--------------------------------------------------------------- b9ed6e8cdfba8c02e8e02cf274b89e8776a08407 compiler/deSugar/Check.hs | 47 +++++++++++++++++++++++++++++++++++++++++------ 1 file changed, 41 insertions(+), 6 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index fdac5c7..7fc22e7 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -729,7 +729,7 @@ data Abstraction = P -- Pattern abstraction | V -- Value abstraction data PmPat2 :: Abstraction -> * where - GBindAbs :: [PmPat2 P] -> HsExpr Id -> PmPat2 P -- Guard: P <- e (strict be default) Instead of a single P use a list [AsPat] + GBindAbs :: [PmPat2 P] -> HsExpr Id -> PmPat2 P -- Guard: P <- e (strict by default) Instead of a single P use a list [AsPat] ConAbs :: DataCon -> [PmPat2 abs] -> PmPat2 abs -- Constructor: K ps VarAbs :: Id -> PmPat2 abs -- Variable: x @@ -773,12 +773,47 @@ translatePat usupply pat = case pat of ParPat p -> translatePat usupply (unLoc p) LazyPat p -> translatePat usupply (unLoc p) -- COMEHERE: We ignore laziness for now BangPat p -> translatePat usupply (unLoc p) -- COMEHERE: We ignore strictness for now - AsPat lid p -> VarAbs (unLoc lid) : translatePat usupply (unLoc p) + AsPat lid p -> + let ps = translatePat usupply (unLoc p) + idp = VarAbs (unLoc lid) + g = GBindAbs ps (HsVar (unLoc lid)) + in [idp, g] SigPatOut p ty -> translatePat usupply (unLoc p) -- COMEHERE: FIXME: Exploit the signature? CoPat wrapper p ty -> translatePat usupply p -- COMEHERE: Make sure the coercion is not useful - NPlusKPat n k ge minus -> error "COMEHERE" - ViewPat lexpr lpat arg_ty -> error "COMEHERE" - ListPat _ _ (Just (_,_)) -> error "COMEHERE: FIXME: Overloaded List" + NPlusKPat n k ge minus -> + let x = mkPmId usupply (idType (unLoc n)) -- x as Id + xe = noLoc (HsVar x) -- x as located expression + ke = noLoc (HsOverLit k) -- k as located expression + np = [VarAbs (unLoc n)] -- n as a list of value abstractions + + xp = VarAbs x -- x + g1 = eqTrueExpr $ OpApp xe (noLoc ge) no_fixity ke -- True <- (x >= k) + g2 = GBindAbs np $ OpApp xe (noLoc minus) no_fixity ke -- n <- (x - k) + in [xp, g1, g2] + + ViewPat lexpr lpat arg_ty -> + let (usupply1, usupply2) = splitUniqSupply usupply + + x = mkPmId usupply1 arg_ty -- x as Id + xe = noLoc (HsVar x) -- x as located expression + ps = translatePat usupply2 (unLoc lpat) -- p translated recursively + + xp = VarAbs x -- x + g = GBindAbs ps (HsApp lexpr xe) -- p <- f x + in [xp,g] + + ListPat lpats elem_ty (Just (pat_ty, to_list)) -> + let (usupply1, usupply2) = splitUniqSupply usupply + + x = mkPmId usupply1 (hsPatType pat) -- x as Id + xe = noLoc (HsVar x) -- x as located expression + ps = translatePats usupply2 (map unLoc lpats) -- list as value abstraction + + xp = VarAbs x -- x + g = GBindAbs (concat ps) $ HsApp (noLoc to_list) xe -- [...] <- toList x + in [xp,g] + + ConPatOut { pat_con = L _ (PatSynCon _) } -> error "COMEHERE: FIXME: Pattern Synonym" -- PATTERN SYNONYM - WHAT TO DO WITH IT? ConPatOut { pat_con = L _ (RealDataCon con), pat_args = ps } -> -- DO WE NEED OTHER STUFF FROM IT? @@ -791,7 +826,7 @@ translatePat usupply pat = case pat of expr = OpApp hs_var (noLoc eq) no_fixity expr_lit -- COMEHERE: I do not like the noLoc thing in [VarAbs var, eqTrueExpr expr] - LitPat lit -> [mkPmVar usupply (hsPatType pat)] -- COMEHERE: Wrong. Should be like NPat (which eq to use?) + LitPat lit -> error "COMEHERE" -- [mkPmVar usupply (hsPatType pat)] -- COMEHERE: Wrong. Should be like NPat (which eq to use?) ListPat ps ty Nothing -> -- WHAT TO DO WITH TY?? let tidy_ps = translatePats usupply (map unLoc ps) From git at git.haskell.org Thu Mar 19 15:26:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:26:30 +0000 (UTC) Subject: [commit: packages/hpc] tag 'v0.6.0.2' created Message-ID: <20150319152630.0E4DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc New tag : v0.6.0.2 Referencing: 2f0c4cd807b6a0858d9ae5411583e5874f72919e From git at git.haskell.org Thu Mar 19 15:34:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:34:07 +0000 (UTC) Subject: [commit: packages/array] tag 'v0.5.1.0' created Message-ID: <20150319153407.31A9A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array New tag : v0.5.1.0 Referencing: 1c62892f5ad636f9a14493f827a9432aef912042 From git at git.haskell.org Thu Mar 19 15:43:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:43:45 +0000 (UTC) Subject: [commit: packages/random] branch 'new_api' created Message-ID: <20150319154345.B184C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random New branch : new_api Referencing: 5541f8cdca26657cfc18bd6d101870e7c3a913a2 From git at git.haskell.org Thu Mar 19 15:43:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:43:47 +0000 (UTC) Subject: [commit: packages/random] branch 'ghc-head' deleted Message-ID: <20150319154347.B1DCC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random Deleted branch: ghc-head From git at git.haskell.org Thu Mar 19 15:43:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:43:49 +0000 (UTC) Subject: [commit: packages/random] tag 'v1.1' created Message-ID: <20150319154349.B1F723A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random New tag : v1.1 Referencing: 7f2e02a3e38b2171c4887ed9adfbe170fd2ff08b From git at git.haskell.org Thu Mar 19 15:43:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:43:51 +0000 (UTC) Subject: [commit: packages/random] new_api: Added randomBits based on genBits. This yields a performance improvement across most Random types. (38cab93) Message-ID: <20150319154351.BDDEF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/38cab934e948684144657083a41aad5fef99d440 >--------------------------------------------------------------- commit 38cab934e948684144657083a41aad5fef99d440 Author: Ryan Newton Date: Mon Jun 27 01:36:42 2011 -0400 Added randomBits based on genBits. This yields a performance improvement across most Random types. >--------------------------------------------------------------- 38cab934e948684144657083a41aad5fef99d440 Benchmark/SimpleRNGBench.hs | 2 ++ DEVLOG.md | 81 +++++++++++++++++++++++++++++++++++++++++++-- System/Random.hs | 69 ++++++++++++++++++++++++++++---------- 3 files changed, 133 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 38cab934e948684144657083a41aad5fef99d440 From git at git.haskell.org Thu Mar 19 15:43:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:43:53 +0000 (UTC) Subject: [commit: packages/random] new_api: Intermediate checkin. First draft of randomIvalBits replacement for randomIvalIntegral. It's unfinished but shows promise. (10add1b) Message-ID: <20150319154353.C79433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/10add1b4773b20f1fa9afdc5c7be75f457255f34 >--------------------------------------------------------------- commit 10add1b4773b20f1fa9afdc5c7be75f457255f34 Author: Ryan Newton Date: Mon Jun 27 11:59:49 2011 -0400 Intermediate checkin. First draft of randomIvalBits replacement for randomIvalIntegral. It's unfinished but shows promise. >--------------------------------------------------------------- 10add1b4773b20f1fa9afdc5c7be75f457255f34 DEVLOG.md | 34 +++++++++++++++++++ System/Random.hs | 102 +++++++++++++++++++++++++++++++++++++++++++++++-------- 2 files changed, 122 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 10add1b4773b20f1fa9afdc5c7be75f457255f34 From git at git.haskell.org Thu Mar 19 15:43:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:43:55 +0000 (UTC) Subject: [commit: packages/random] new_api: Intermediate checkin. Fixed one bug with the order of type conversion/shifting. Right now trying to fix randomIvalBits behavior on (signed) Ints. (7f44303) Message-ID: <20150319154355.CDC053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/7f44303fc009b282f940b986ab93feaaaba31489 >--------------------------------------------------------------- commit 7f44303fc009b282f940b986ab93feaaaba31489 Author: Ryan Newton Date: Mon Jun 27 13:05:25 2011 -0400 Intermediate checkin. Fixed one bug with the order of type conversion/shifting. Right now trying to fix randomIvalBits behavior on (signed) Ints. >--------------------------------------------------------------- 7f44303fc009b282f940b986ab93feaaaba31489 DEVLOG.md | 1 + System/Random.hs | 33 ++++++++++++++++++++++++--------- 2 files changed, 25 insertions(+), 9 deletions(-) diff --git a/DEVLOG.md b/DEVLOG.md index db1d12f..b482f1f 100644 --- a/DEVLOG.md +++ b/DEVLOG.md @@ -201,3 +201,4 @@ randomIvalBits uses a very inefficient bitScanReverse which can be improved. And in spite of that it didn't slow down TOO much. Also, randomIvalBits can fix the problems in tickets #5278 and #5280 having to do with uniformity and assumptions about the generators. + diff --git a/System/Random.hs b/System/Random.hs index eac2e1e..7a162ef 100644 --- a/System/Random.hs +++ b/System/Random.hs @@ -89,7 +89,14 @@ import Data.Char ( isSpace, chr, ord ) import System.IO.Unsafe ( unsafePerformIO ) import Data.IORef import Numeric ( readDec ) + + +#define DEBUGRAND +#ifdef DEBUGRAND +import Numeric ( showIntAtBase ) +import Data.Char ( intToDigit ) import Debug.Trace +#endif -- The standard nhc98 implementation of Time.ClockTime does not match -- the extended one expected in this module, so we lash-up a quick @@ -425,9 +432,13 @@ randomBits desired gen = if bits <= c then loop g' (acc `shiftL` bits .|. fromIntegral x) (c - bits) -- Otherwise we must make sure not to generate too many bits: - else let shft = min bits c in - (acc `shiftL` shft .|. (fromIntegral x `shiftR` fromIntegral (bits - shft)), - g') + else + let shifted = fromIntegral (x `shiftR` (bits - c)) in +#ifdef DEBUGRAND + trace (" Got random "++ showIntAtBase 16 intToDigit x "" ++ + ", shifted "++ show (bits-c)++": " ++ show shifted) $ +#endif + (acc `shiftL` c .|. shifted, g') in loop gen 0 desired Nothing -> error "TODO: IMPLEMENT ME" where @@ -450,7 +461,10 @@ randomIvalBits :: (RandomGen g, Integral a, Bits a) => (a, a) -> g -> (a, g) randomIvalBits (l,h) rng | l > h = randomIvalBits (h,l) rng | otherwise = - -- trace ("Got pow2: "++ show pow2 ++ " range " ++ show range ++ " cutoff "++ show cutoff) $ +#ifdef DEBUGRAND + trace (" Got pow2: "++show pow2++" bounding "++show bounding++" maxbits "++show maxbits++ + " range " ++ show range ++ " cutoff "++ show cutoff) $ +#endif (l + fin_x, fin_rng) where (fin_x,fin_rng) = @@ -462,14 +476,15 @@ randomIvalBits (l,h) rng -- range is the number of distinct values we wish to generate: -- If we are dealing with a signed type, range may be negative! --- range = h - l + 1 - range = h - l + range = h - l + 1 maxbits = bitSize l -- With randomBits we can only generate power-of-two ranges. We -- need to find the smallest power-of-two that is bigger than range. pow2 = findBoundingPow2 range - bounding = 1 `shiftL` pow2 + -- Bounding is the largest number we will generate with pow2 random bits: + -- bounding = (1 `shiftL` pow2) - 1 -- This could overflow! + bounding = complement 0 `shiftR` (maxbits - pow2) cutoff = --if pow2 == maxbits --then error "UNFINISHED" --else @@ -479,8 +494,8 @@ randomIvalBits (l,h) rng -- results, but usually it should be much much less. rollAndTrash g = case randomBits pow2 g of - (x,g') | x > cutoff -> rollAndTrash g' - pair -> pair + (x,g') | x >= cutoff -> rollAndTrash g' + pair -> pair -- Find the smallest power of two greater than or equal to the given number. -- findBoundingPow2 :: (Bits a, Ord a) => a -> Int From git at git.haskell.org Thu Mar 19 15:43:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:43:57 +0000 (UTC) Subject: [commit: packages/random] new_api: Intermediate checkin. Fixes for randomIvalBits. Still a couple corner cases to handle before its even a full candidate, however. (3581598) Message-ID: <20150319154357.D4ED93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/3581598e57ef995fa3d936fa321b201b7259d276 >--------------------------------------------------------------- commit 3581598e57ef995fa3d936fa321b201b7259d276 Author: Ryan Newton Date: Mon Jun 27 13:26:57 2011 -0400 Intermediate checkin. Fixes for randomIvalBits. Still a couple corner cases to handle before its even a full candidate, however. >--------------------------------------------------------------- 3581598e57ef995fa3d936fa321b201b7259d276 System/Random.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/System/Random.hs b/System/Random.hs index 7a162ef..4d4644b 100644 --- a/System/Random.hs +++ b/System/Random.hs @@ -91,7 +91,7 @@ import Data.IORef import Numeric ( readDec ) -#define DEBUGRAND +--define DEBUGRAND #ifdef DEBUGRAND import Numeric ( showIntAtBase ) import Data.Char ( intToDigit ) @@ -484,18 +484,19 @@ randomIvalBits (l,h) rng pow2 = findBoundingPow2 range -- Bounding is the largest number we will generate with pow2 random bits: -- bounding = (1 `shiftL` pow2) - 1 -- This could overflow! - bounding = complement 0 `shiftR` (maxbits - pow2) + -- Here we explicitly counter sign-extension in shiftR: + bounding = (clearBit (complement 0) (maxbits-1)) `shiftR` (maxbits - pow2 - 1) cutoff = --if pow2 == maxbits --then error "UNFINISHED" --else bounding - (bounding `rem` range) -- rollAndTrash rolls the dice repeatedly, trashing results it doesn't -- like. In the worst case, it can trash up to 50% of the - -- results, but usually it should be much much less. + -- results (but typically much much less). rollAndTrash g = case randomBits pow2 g of (x,g') | x >= cutoff -> rollAndTrash g' - pair -> pair + (x,g') -> (x `mod` range, g') -- Find the smallest power of two greater than or equal to the given number. -- findBoundingPow2 :: (Bits a, Ord a) => a -> Int From git at git.haskell.org Thu Mar 19 15:43:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:43:59 +0000 (UTC) Subject: [commit: packages/random] new_api: Merged patch from master. (f2088c9) Message-ID: <20150319154359.DC9B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/f2088c91c60b66147f40e078e89130a55cf49161 >--------------------------------------------------------------- commit f2088c91c60b66147f40e078e89130a55cf49161 Merge: 3581598 a837e1f Author: Ryan Newton Date: Mon Jun 27 13:41:10 2011 -0400 Merged patch from master. >--------------------------------------------------------------- f2088c91c60b66147f40e078e89130a55cf49161 System/Random.hs | 23 ++++++++++++++--------- 1 file changed, 14 insertions(+), 9 deletions(-) diff --cc System/Random.hs index 4d4644b,9f5a91b..0a6c82b --- a/System/Random.hs +++ b/System/Random.hs @@@ -382,26 -363,24 +389,27 @@@ instance Random Double wher mask53 = twoto53 - 1 instance Random Float where - randomR = randomIvalFrac + randomR = randomRFloating random rng = -- TODO: Faster to just use 'next' IF it generates enough bits of randomness. - case random rng of + case rand of (x,rng') -> -- We use 24 bits of randomness corresponding to the 24 bit significand: - ((fromIntegral (mask24 .&. (x::Int32)) :: Float) + ((fromIntegral (mask24 .&. (x::Int)) :: Float) / fromIntegral twoto24, rng') -- Note, encodeFloat is another option, but I'm not seeing slightly -- worse performance with the following [2011.06.25]: -- (encodeFloat rand (-24), rng') where + rand = case genBits rng of + Just n | n >= 24 -> next rng + _ -> random rng mask24 = twoto24 - 1 - twoto24 = (2::Int32) ^ (24::Int32) + twoto24 = (2::Int) ^ (24::Int) + -- CFloat/CDouble are basically the same as a Float/Double: instance Random CFloat where - randomR = randomIvalFrac + randomR = randomRFloating random rng = case random rng of (x,rng') -> (realToFrac (x::Float), rng') From git at git.haskell.org Thu Mar 19 15:44:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:01 +0000 (UTC) Subject: [commit: packages/random] new_api: Minor: comment tweak, DEVLOG notes, remved cruft. (797eb35) Message-ID: <20150319154401.E4E8F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/797eb35eb26f2fb18aadbdb757a1b6f0bbb099fe >--------------------------------------------------------------- commit 797eb35eb26f2fb18aadbdb757a1b6f0bbb099fe Author: Ryan Newton Date: Mon Jun 27 13:47:54 2011 -0400 Minor: comment tweak, DEVLOG notes, remved cruft. >--------------------------------------------------------------- 797eb35eb26f2fb18aadbdb757a1b6f0bbb099fe DEVLOG.md | 28 ++++++++++++++++++++++++++++ System/Random.hs | 44 ++++++++++++++------------------------------ 2 files changed, 42 insertions(+), 30 deletions(-) diff --git a/DEVLOG.md b/DEVLOG.md index b482f1f..24972cf 100644 --- a/DEVLOG.md +++ b/DEVLOG.md @@ -202,3 +202,31 @@ improved. And in spite of that it didn't slow down TOO much. Also, randomIvalBits can fix the problems in tickets #5278 and #5280 having to do with uniformity and assumptions about the generators. + +Oops, there were some bugs. Here are new times as of revision 3581598e57ef995f: + + Next timing range-restricted System.Random.randomR: + 3,738,614 randoms generated [System.Random Ints] ~ 892 cycles/int + 7,516,652 randoms generated [System.Random Word16s] ~ 444 cycles/int + 110,307 randoms generated [System.Random Floats] ~ 30,234 cycles/int + 110,507 randoms generated [System.Random CFloats] ~ 30,179 cycles/int + 2,538,000 randoms generated [System.Random Doubles] ~ 1,314 cycles/int + 108,386 randoms generated [System.Random CDoubles] ~ 30,770 cycles/int + 5,398,820 randoms generated [System.Random Integers] ~ 618 cycles/int + 4,758,575 randoms generated [System.Random Bools] ~ 701 cycles/int + +Finally, in revision a837e1ffb294234dc I tweaked the restricted +Float/Double instances to use the new versions: + + Next timing range-restricted System.Random.randomR: + 4,015,910 randoms generated [System.Random Ints] ~ 831 cycles/int + 7,572,249 randoms generated [System.Random Word16s] ~ 440 cycles/int + 12,768,688 randoms generated [System.Random Floats] ~ 261 cycles/int + 12,716,471 randoms generated [System.Random CFloats] ~ 262 cycles/int + 3,948,403 randoms generated [System.Random Doubles] ~ 845 cycles/int + 2,469,778 randoms generated [System.Random CDoubles] ~ 1,350 cycles/int + 4,542,423 randoms generated [System.Random Integers] ~ 734 cycles/int + 4,884,380 randoms generated [System.Random Bools] ~ 683 cycles/int + +Why would Floats be faster than Word16s though? Still some exploring left to do... + diff --git a/System/Random.hs b/System/Random.hs index 0a6c82b..0acbf9c 100644 --- a/System/Random.hs +++ b/System/Random.hs @@ -308,27 +308,24 @@ instance Random Integer where randomR ival g = randomIvalInteger ival g random g = randomR (toInteger (minBound::Int), toInteger (maxBound::Int)) g -#define TEMPTEST randomIvalBits --- define TEMPTEST randomIvalIntegral - -instance Random Int where randomR = TEMPTEST; random = randomBits WORD_SIZE_IN_BITS -instance Random Int8 where randomR = TEMPTEST; random = randomBits 8 -instance Random Int16 where randomR = TEMPTEST; random = randomBits 16 -instance Random Int32 where randomR = TEMPTEST; random = randomBits 32 -instance Random Int64 where randomR = TEMPTEST; random = randomBits 64 +instance Random Int where randomR = randomIvalBits; random = randomBits WORD_SIZE_IN_BITS +instance Random Int8 where randomR = randomIvalBits; random = randomBits 8 +instance Random Int16 where randomR = randomIvalBits; random = randomBits 16 +instance Random Int32 where randomR = randomIvalBits; random = randomBits 32 +instance Random Int64 where randomR = randomIvalBits; random = randomBits 64 #ifndef __NHC__ -- Word is a type synonym in nhc98. -instance Random Word where randomR = TEMPTEST; random = randomBounded +instance Random Word where randomR = randomIvalBits; random = randomBounded #endif -instance Random Word8 where randomR = TEMPTEST; random = randomBits 8 -instance Random Word16 where randomR = TEMPTEST; random = randomBits 16 -instance Random Word32 where randomR = TEMPTEST; random = randomBits 32 -instance Random Word64 where randomR = TEMPTEST; random = randomBits 64 +instance Random Word8 where randomR = randomIvalBits; random = randomBits 8 +instance Random Word16 where randomR = randomIvalBits; random = randomBits 16 +instance Random Word32 where randomR = randomIvalBits; random = randomBits 32 +instance Random Word64 where randomR = randomIvalBits; random = randomBits 64 -instance Random CChar where randomR = TEMPTEST; random = randomBits 8 -instance Random CSChar where randomR = TEMPTEST; random = randomBits 8 -instance Random CUChar where randomR = TEMPTEST; random = randomBits 8 +instance Random CChar where randomR = randomIvalBits; random = randomBits 8 +instance Random CSChar where randomR = randomIvalBits; random = randomBits 8 +instance Random CUChar where randomR = randomIvalBits; random = randomBits 8 -- TODO: Finish applying randomBits after I double check all the sizes: instance Random CShort where randomR = randomIvalIntegral; random = randomBounded @@ -391,7 +388,6 @@ instance Random Double where instance Random Float where randomR = randomRFloating random rng = - -- TODO: Faster to just use 'next' IF it generates enough bits of randomness. case rand of (x,rng') -> -- We use 24 bits of randomness corresponding to the 24 bit significand: @@ -449,10 +445,9 @@ randomBits desired gen = #endif (acc `shiftL` c .|. shifted, g') in loop gen 0 desired - Nothing -> error "TODO: IMPLEMENT ME" + Nothing -> error "TODO: IMPLEMENT ME - handle undesirable bit sources" where -#if 1 -------------------------------------------------------------------------------- -- TEMP: These should probably be in Data.Bits AND they shoul have hardware support: -- The number of leading zero bits: @@ -507,22 +502,11 @@ randomIvalBits (l,h) rng (x,g') | x >= cutoff -> rollAndTrash g' (x,g') -> (x `mod` range, g') --- Find the smallest power of two greater than or equal to the given number. --- findBoundingPow2 :: (Bits a, Ord a) => a -> Int --- findBoundingPow2 num | num <= 0 = error "findBoundingPow2 should not be given a non-positive number" --- findBoundingPow2 num = --- if num == bit (leadPos-1) --- then leadPos-1 --- else leadPos --- where --- leadPos = bitSize num - bitScanReverse num - -- Find the smallest power of two greater than the given number. -- Treat all numbers as unsigned irrespective of type: findBoundingPow2 :: (Bits a, Ord a) => a -> Int -- findBoundingPow2 num | num <= 0 = error "findBoundingPow2 should not be given a non-positive number" findBoundingPow2 num = bitSize num - bitScanReverse num -#endif randomBounded :: (RandomGen g, Random a, Bounded a) => g -> (a, g) From git at git.haskell.org Thu Mar 19 15:44:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:03 +0000 (UTC) Subject: [commit: packages/random] new_api: minor: DEVLOG notes (1271050) Message-ID: <20150319154403.EC0DD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/1271050b932dc1cb625eab37872dcd5c23cb0f0a >--------------------------------------------------------------- commit 1271050b932dc1cb625eab37872dcd5c23cb0f0a Author: Ryan Newton Date: Mon Jun 27 14:48:17 2011 -0400 minor: DEVLOG notes >--------------------------------------------------------------- 1271050b932dc1cb625eab37872dcd5c23cb0f0a DEVLOG.md | 46 ++++++++++++++++++++++++++++++++++------------ System/Random.hs | 8 ++++---- 2 files changed, 38 insertions(+), 16 deletions(-) diff --git a/DEVLOG.md b/DEVLOG.md index 24972cf..51264ec 100644 --- a/DEVLOG.md +++ b/DEVLOG.md @@ -216,17 +216,39 @@ Oops, there were some bugs. Here are new times as of revision 3581598e57ef995f: 4,758,575 randoms generated [System.Random Bools] ~ 701 cycles/int Finally, in revision a837e1ffb294234dc I tweaked the restricted -Float/Double instances to use the new versions: +Float/Double instances to use the new versions. Here are results from +what is currently the "new_api" branch: - Next timing range-restricted System.Random.randomR: - 4,015,910 randoms generated [System.Random Ints] ~ 831 cycles/int - 7,572,249 randoms generated [System.Random Word16s] ~ 440 cycles/int - 12,768,688 randoms generated [System.Random Floats] ~ 261 cycles/int - 12,716,471 randoms generated [System.Random CFloats] ~ 262 cycles/int - 3,948,403 randoms generated [System.Random Doubles] ~ 845 cycles/int - 2,469,778 randoms generated [System.Random CDoubles] ~ 1,350 cycles/int - 4,542,423 randoms generated [System.Random Integers] ~ 734 cycles/int - 4,884,380 randoms generated [System.Random Bools] ~ 683 cycles/int - -Why would Floats be faster than Word16s though? Still some exploring left to do... + Second, timing System.Random.random at different types: + 4,346,075 randoms generated [System.Random Ints] ~ 767 cycles/int + 12,162,421 randoms generated [System.Random Word16] ~ 274 cycles/int + 6,615,428 randoms generated [System.Random Word32] ~ 504 cycles/int + 13,371,440 randoms generated [System.Random Floats] ~ 249 cycles/int + 13,393,200 randoms generated [System.Random CFloats] ~ 249 cycles/int + 4,334,003 randoms generated [System.Random Doubles] ~ 770 cycles/int + 2,462,703 randoms generated [System.Random CDoubles] ~ 1,354 cycles/int + 855,408 randoms generated [System.Random Integers] ~ 3,899 cycles/int + 5,088,025 randoms generated [System.Random Bools] ~ 656 cycles/int + Next timing range-restricted System.Random.randomR: + 4,015,910 randoms generated [System.Random Ints] ~ 831 cycles/int + 7,572,249 randoms generated [System.Random Word16s] ~ 440 cycles/int + 12,768,688 randoms generated [System.Random Floats] ~ 261 cycles/int + 12,716,471 randoms generated [System.Random CFloats] ~ 262 cycles/int + 3,948,403 randoms generated [System.Random Doubles] ~ 845 cycles/int + 2,469,778 randoms generated [System.Random CDoubles] ~ 1,350 cycles/int + 4,542,423 randoms generated [System.Random Integers] ~ 734 cycles/int + 4,884,380 randoms generated [System.Random Bools] ~ 683 cycles/int + +Why would Floats be faster than Word16s though? Why did Word16 takes +such a hit for the range-restricted version? Still some exploring +left to do... + +As a mock-up I made bitScanReverse return an incorrect constant +result, which should approximate the cost of a cheap, BSR-based version. +Surprisingly, it doesn't do very much better! + + Second, timing System.Random.random at different types: + 12,383,682 randoms generated [System.Random Word16] ~ 269 cycles/int + Next timing range-restricted System.Random.randomR: + 8,265,744 randoms generated [System.Random Word16s] ~ 404 cycles/int diff --git a/System/Random.hs b/System/Random.hs index 0acbf9c..e58f083 100644 --- a/System/Random.hs +++ b/System/Random.hs @@ -90,8 +90,7 @@ import System.IO.Unsafe ( unsafePerformIO ) import Data.IORef import Numeric ( readDec ) - ---define DEBUGRAND +-- #define DEBUGRAND #ifdef DEBUGRAND import Numeric ( showIntAtBase ) import Data.Char ( intToDigit ) @@ -449,7 +448,9 @@ randomBits desired gen = where -------------------------------------------------------------------------------- --- TEMP: These should probably be in Data.Bits AND they shoul have hardware support: +-- TEMP: These should probably be in Data.Bits AND they should have hardware support. +-- (See trac ticket #4102.) + -- The number of leading zero bits: bitScanReverse :: Bits a => a -> Int bitScanReverse num = loop (size - 1) @@ -487,7 +488,6 @@ randomIvalBits (l,h) rng -- need to find the smallest power-of-two that is bigger than range. pow2 = findBoundingPow2 range -- Bounding is the largest number we will generate with pow2 random bits: - -- bounding = (1 `shiftL` pow2) - 1 -- This could overflow! -- Here we explicitly counter sign-extension in shiftR: bounding = (clearBit (complement 0) (maxbits-1)) `shiftR` (maxbits - pow2 - 1) cutoff = --if pow2 == maxbits From git at git.haskell.org Thu Mar 19 15:44:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:06 +0000 (UTC) Subject: [commit: packages/random] new_api: Merge branch 'master' into new_api (352e7d6) Message-ID: <20150319154406.02C793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/352e7d6788b463ff87c9881e0a0d83ae3dc40901 >--------------------------------------------------------------- commit 352e7d6788b463ff87c9881e0a0d83ae3dc40901 Merge: 1271050 c48cdb9 Author: Ryan Newton Date: Tue Jun 28 00:11:48 2011 -0400 Merge branch 'master' into new_api >--------------------------------------------------------------- 352e7d6788b463ff87c9881e0a0d83ae3dc40901 Benchmark/SimpleRNGBench.hs | 18 ------ System/Random.hs | 4 +- tests/all.T | 10 +++- tests/random1283.hs | 2 + tests/rangeTest.hs | 132 ++++++++++++++++++++++++++++++++++++++++++++ tests/rangeTest.stdout | 64 +++++++++++++++++++++ 6 files changed, 209 insertions(+), 21 deletions(-) From git at git.haskell.org Thu Mar 19 15:44:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:08 +0000 (UTC) Subject: [commit: packages/random] new_api: Converted the rest of the numeric types to use randomBits. Fixed randomIvalBits so that it can handle large ranges within a signed type. (6191716) Message-ID: <20150319154408.0D7193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/6191716f814c286c69ed7358858d4b060d2169f6 >--------------------------------------------------------------- commit 6191716f814c286c69ed7358858d4b060d2169f6 Author: Ryan Newton Date: Tue Jun 28 01:04:00 2011 -0400 Converted the rest of the numeric types to use randomBits. Fixed randomIvalBits so that it can handle large ranges within a signed type. >--------------------------------------------------------------- 6191716f814c286c69ed7358858d4b060d2169f6 Benchmark/SimpleRNGBench.hs | 13 ++----- System/Random.hs | 82 ++++++++++++++++++++++++--------------------- 2 files changed, 46 insertions(+), 49 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6191716f814c286c69ed7358858d4b060d2169f6 From git at git.haskell.org Thu Mar 19 15:44:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:10 +0000 (UTC) Subject: [commit: packages/random] new_api: Merge branch 'master' into new_api (56e6dd0) Message-ID: <20150319154410.174713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/56e6dd0372e204f3272a8738c1e8b833bba3d043 >--------------------------------------------------------------- commit 56e6dd0372e204f3272a8738c1e8b833bba3d043 Merge: 6191716 6d60652 Author: Ryan Newton Date: Tue Jun 28 01:06:31 2011 -0400 Merge branch 'master' into new_api >--------------------------------------------------------------- 56e6dd0372e204f3272a8738c1e8b833bba3d043 tests/rangeTest.hs | 14 ++++++++------ tests/rangeTest.stdout | 3 +++ 2 files changed, 11 insertions(+), 6 deletions(-) From git at git.haskell.org Thu Mar 19 15:44:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:12 +0000 (UTC) Subject: [commit: packages/random] new_api: Merge branch 'master' into new_api (321776e) Message-ID: <20150319154412.1F9D73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/321776e8833bf7c207a76e997da1dc258b4a7519 >--------------------------------------------------------------- commit 321776e8833bf7c207a76e997da1dc258b4a7519 Merge: 56e6dd0 f2a3d60 Author: Ryan Newton Date: Tue Jun 28 01:10:47 2011 -0400 Merge branch 'master' into new_api >--------------------------------------------------------------- 321776e8833bf7c207a76e997da1dc258b4a7519 README.md | 11 +++++++++++ 1 file changed, 11 insertions(+) From git at git.haskell.org Thu Mar 19 15:44:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:14 +0000 (UTC) Subject: [commit: packages/random] new_api: Consolidating. Moving last types over to randomBits based. Only Integer is left. (bdc4d46) Message-ID: <20150319154414.27C003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/bdc4d46f0f265bdc26716db12c1887f0c73e1d51 >--------------------------------------------------------------- commit bdc4d46f0f265bdc26716db12c1887f0c73e1d51 Author: Ryan Newton Date: Tue Jun 28 01:33:00 2011 -0400 Consolidating. Moving last types over to randomBits based. Only Integer is left. >--------------------------------------------------------------- bdc4d46f0f265bdc26716db12c1887f0c73e1d51 Benchmark/SimpleRNGBench.hs | 6 ++-- DEVLOG.md | 36 +++++++++++++++++++++++ System/Random.hs | 71 ++++++++++----------------------------------- 3 files changed, 55 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 bdc4d46f0f265bdc26716db12c1887f0c73e1d51 From git at git.haskell.org Thu Mar 19 15:44:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:16 +0000 (UTC) Subject: [commit: packages/random] new_api: Converted Integer generation over to randomBits approach and deleted randomIvalInteger. (12e8fbb) Message-ID: <20150319154416.3184F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/12e8fbb046a6a1312c5058ae83ff460dc52ab131 >--------------------------------------------------------------- commit 12e8fbb046a6a1312c5058ae83ff460dc52ab131 Author: Ryan Newton Date: Tue Jun 28 10:02:14 2011 -0400 Converted Integer generation over to randomBits approach and deleted randomIvalInteger. >--------------------------------------------------------------- 12e8fbb046a6a1312c5058ae83ff460dc52ab131 DEVLOG.md | 16 +++++++++- System/Random.hs | 92 +++++++++++++++++++++++++++----------------------------- 2 files changed, 59 insertions(+), 49 deletions(-) diff --git a/DEVLOG.md b/DEVLOG.md index c5f910c..cf6fc84 100644 --- a/DEVLOG.md +++ b/DEVLOG.md @@ -284,7 +284,21 @@ This should slow down the range versions. Now there are several more Maybe coalescing those three branches into one would help. -Also, I'm eliminating the last uses of randomIvalInteger. This speeds up Bools: +Also, I'm eliminating the last uses of randomIvalInteger & co. This speeds up Bools: 11,159,027 randoms generated [System.Random Bools] ~ 298 cycles/int +And CDoubles: + 4,327,409 randoms generated [System.Random CDoubles] ~ 771 cycles/int +(I don't know why I had the opposite result before from CDouble where randomFrac was better.) + + +Finally, converting Integer over to the randomBits approach gives me +an odd reversal of the above situation. Now random is quicker but +randomR is SLOWER: + + random: + 4,370,660 randoms generated [System.Random Integers] ~ 763 cycles/int + randomR: + 922,702 randoms generated [System.Random Integers] ~ 3,615 cycles/int + diff --git a/System/Random.hs b/System/Random.hs index 45e0f5d..931f2bd 100644 --- a/System/Random.hs +++ b/System/Random.hs @@ -304,7 +304,9 @@ class Random a where instance Random Integer where -- randomR cannot use the "Bits" version here: - randomR ival g = randomIvalInteger ival g + randomR ival@(lo,hi) = + let bits = (1 + max (bitOccupancy lo) (bitOccupancy hi)) in + randomIvalBits_raw bits ival random g = case random g of (x,g') -> (toInteger (x::Int), g') instance Random Int where randomR = randomIvalBits; random = randomBits WORD_SIZE_IN_BITS @@ -354,13 +356,6 @@ instance Random Bool where random g = case random g of (x,g') -> (testBit (x::Word8) 0, g') -{-# INLINE randomRFloating #-} -randomRFloating :: (Num a, Ord a, Random a, RandomGen g) => (a, a) -> g -> (a, g) -randomRFloating (l,h) g - | l>h = randomRFloating (h,l) g - | otherwise = let (coef,g') = random g in - (l + coef * (h-l), g') - instance Random Double where randomR = randomRFloating random rng = @@ -381,9 +376,6 @@ instance Random Float where -- We use 24 bits of randomness corresponding to the 24 bit significand: ((fromIntegral (mask24 .&. (x::Int)) :: Float) / fromIntegral twoto24, rng') - -- Note, encodeFloat is another option, but I'm not seeing slightly - -- worse performance with the following [2011.06.25]: --- (encodeFloat rand (-24), rng') where rand = case genBits rng of Just n | n >= 24 -> next rng @@ -408,6 +400,14 @@ mkStdRNG o = do (sec, psec) <- getTime return (createStdGen (sec * 12345 + psec + ct + o)) +{-# INLINE randomRFloating #-} +randomRFloating :: (Num a, Ord a, Random a, RandomGen g) => (a, a) -> g -> (a, g) +randomRFloating (l,h) g + | l>h = randomRFloating (h,l) g + | otherwise = let (coef,g') = random g in + (l + coef * (h-l), g') + + -- Create a specific number of random bits. randomBits :: (RandomGen g, Bits a) => Int -> g -> (a,g) randomBits desired gen = @@ -433,14 +433,13 @@ randomBits desired gen = where -------------------------------------------------------------------------------- --- TEMP: These should probably be in Data.Bits AND they should have hardware support. +-- TEMP: This should probably be in Data.Bits AND they should have hardware support. -- (See trac ticket #4102.) --- The number of leading zero bits: -bitScanReverse :: Bits a => a -> Int -bitScanReverse num = loop (size - 1) +-- Determine the number of leading zero bits: +bitScanReverse :: Bits a => Int -> a -> Int +bitScanReverse size num = loop (size - 1) where - size = bitSize num loop i | i < 0 = size | testBit num i = size - 1 - i | otherwise = loop (i-1) @@ -448,39 +447,49 @@ bitScanReverse num = loop (size - 1) -- This new version uses randomBits to generate a number in an interval. randomIvalBits :: (RandomGen g, Integral a, Bits a) => (a, a) -> g -> (a, g) -randomIvalBits (l,h) rng +randomIvalBits bounds@(lo,_) rng = + randomIvalBits_raw (bitSize lo) bounds rng + +randomIvalBits_raw :: (RandomGen g, Integral a, Bits a) => + Int -> (a, a) -> g -> (a, g) +randomIvalBits_raw maxbits (l,h) rng | l > h = randomIvalBits (h,l) rng | otherwise = #ifdef DEBUGRAND trace (" Got pow2: "++show pow2++" bounding "++show bounding++" maxbits "++show maxbits++ " range " ++ show range ++ " cutoff "++ show cutoff) $ #endif - -- In the special case we don't offset from l: if special_case + -- In the special case we don't offset from the lower bound: then (h - cutoff + fin_x + 1, fin_rng) else (l + fin_x, fin_rng) where + +-- TODO - USE IS_SIGNED!!! + (fin_x,fin_rng) = - -- If we have a power-of-two-sized interval matters are simple. if range == bit (pow2 - 1) + -- If we have a power-of-two-sized interval life is easy! then randomBits (pow2 - 1) rng else rollAndTrash rng -- range is the number of distinct values we wish to generate: -- If we are dealing with a signed type, range may be negative! range = h - l + 1 - maxbits = bitSize l -- With randomBits we can only generate power-of-two ranges. We -- need to find the smallest power-of-two that is bigger than range. - pow2 = findBoundingPow2 range + pow2 = findBoundingPow2 maxbits range -- Bounding is the largest number we will generate with pow2 random bits: -- Here we explicitly counter sign-extension in shiftR: special_case = range < 0 -- Special case for signed numbers and range overflow. - bounding = - if special_case - then clearBit (complement 0) (maxbits-1) - else (clearBit (complement 0) (maxbits-1)) `shiftR` (maxbits - pow2 - 1) +-- bounding = let pow = if isSigned l then pow2-2 else pow2-1 + bounding = let pow = if special_case then pow2-2 else pow2-1 + n = 1 `shiftL` pow in + n - 1 + n + -- if special_case + -- then bnd -- clearBit (complement 0) (maxbits-1) + -- else bnd `shiftR` (maxbits - pow2 - 1) cutoff = if special_case then bounding - (bounding - h) - (l - complement bounding) + 1 @@ -495,31 +504,18 @@ randomIvalBits (l,h) rng (x,g') -> (if special_case then x else x `mod` range, g') --- Find the smallest power of two greater than the given number. +-- Find the smallest power of two greater than the given number, that +-- is, the number of bits needed to represent the number. -- Treat all numbers as unsigned irrespective of type: -findBoundingPow2 :: (Bits a, Ord a) => a -> Int +findBoundingPow2 :: (Bits a, Ord a) => Int -> a -> Int -- findBoundingPow2 num | num <= 0 = error "findBoundingPow2 should not be given a non-positive number" -findBoundingPow2 num = bitSize num - bitScanReverse num - --- These integer functions take an [inclusive,inclusive] range. -randomIvalInteger :: (RandomGen g, Num a) => (Integer, Integer) -> g -> (a, g) -randomIvalInteger (l,h) rng - | l > h = randomIvalInteger (h,l) rng - | otherwise = case (f n 1 rng) of (v, rng') -> (fromInteger (l + v `mod` k), rng') - where - k = h - l + 1 - b = 2147483561 - n = iLogBase b k - - f 0 acc g = (acc, g) - f n' acc g = - let - (x,g') = next g - in - f (n' - 1) (fromIntegral x + acc * b) g' - -iLogBase :: Integer -> Integer -> Integer -iLogBase b i = if i < b then 1 else 1 + iLogBase b (i `div` b) +findBoundingPow2 bitsize num = bitsize - bitScanReverse bitsize num + +-- How many bits does it take to represent this integer? +-- NOT counting the sign bit. +bitOccupancy :: Integer -> Int +bitOccupancy i | i < 0 = bitOccupancy (-i) +bitOccupancy i = if i == 0 then 0 else 1 + bitOccupancy (i `shiftR` 1) stdRange :: (Int,Int) stdRange = (0, 2147483562) From git at git.haskell.org Thu Mar 19 15:44:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:18 +0000 (UTC) Subject: [commit: packages/random] new_api: merge (6789310) Message-ID: <20150319154418.38A463A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/678931040d617920c947716d67fba1da730bd6ce >--------------------------------------------------------------- commit 678931040d617920c947716d67fba1da730bd6ce Merge: 12e8fbb 327401e Author: Ryan Newton Date: Tue Jun 28 10:11:18 2011 -0400 merge >--------------------------------------------------------------- Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 678931040d617920c947716d67fba1da730bd6ce From git at git.haskell.org Thu Mar 19 15:44:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:20 +0000 (UTC) Subject: [commit: packages/random] new_api: Removed ifdefd debugging trace messages. (08b60a4) Message-ID: <20150319154420.40C753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/08b60a4e49c6cab5c0f04f200bcfbba02e03feae >--------------------------------------------------------------- commit 08b60a4e49c6cab5c0f04f200bcfbba02e03feae Author: Ryan Newton Date: Tue Jun 28 10:36:48 2011 -0400 Removed ifdefd debugging trace messages. >--------------------------------------------------------------- 08b60a4e49c6cab5c0f04f200bcfbba02e03feae System/Random.hs | 15 --------------- 1 file changed, 15 deletions(-) diff --git a/System/Random.hs b/System/Random.hs index 931f2bd..4ef2090 100644 --- a/System/Random.hs +++ b/System/Random.hs @@ -90,13 +90,6 @@ import System.IO.Unsafe ( unsafePerformIO ) import Data.IORef import Numeric ( readDec ) --- #define DEBUGRAND -#ifdef DEBUGRAND -import Numeric ( showIntAtBase ) -import Data.Char ( intToDigit ) -import Debug.Trace -#endif - -- The standard nhc98 implementation of Time.ClockTime does not match -- the extended one expected in this module, so we lash-up a quick -- replacement here. @@ -423,10 +416,6 @@ randomBits desired gen = -- Otherwise we must make sure not to generate too many bits: else let shifted = fromIntegral (x `shiftR` (bits - c)) in -#ifdef DEBUGRAND - trace (" Got random "++ showIntAtBase 16 intToDigit x "" ++ - ", shifted "++ show (bits-c)++": " ++ show shifted) $ -#endif (acc `shiftL` c .|. shifted, g') in loop gen 0 desired Nothing -> error "TODO: IMPLEMENT ME - handle undesirable bit sources" @@ -455,10 +444,6 @@ randomIvalBits_raw :: (RandomGen g, Integral a, Bits a) => randomIvalBits_raw maxbits (l,h) rng | l > h = randomIvalBits (h,l) rng | otherwise = -#ifdef DEBUGRAND - trace (" Got pow2: "++show pow2++" bounding "++show bounding++" maxbits "++show maxbits++ - " range " ++ show range ++ " cutoff "++ show cutoff) $ -#endif if special_case -- In the special case we don't offset from the lower bound: then (h - cutoff + fin_x + 1, fin_rng) From git at git.haskell.org Thu Mar 19 15:44:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:22 +0000 (UTC) Subject: [commit: packages/random] new_api: Fix trac #5280 #5278. Actually this has been a gradual fix over many revs. But in this revision I make a stronger assumption about genBits and do away with unimplemented cases. So this is the first candidate full replacement for the master branch with the old (incorrect) function definitions completely removed and replaced. (f85c6a5) Message-ID: <20150319154422.4AEDC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/f85c6a55b731d5e380c1d6e880105c9933aa9d48 >--------------------------------------------------------------- commit f85c6a55b731d5e380c1d6e880105c9933aa9d48 Author: Ryan Newton Date: Tue Jun 28 10:37:28 2011 -0400 Fix trac #5280 #5278. Actually this has been a gradual fix over many revs. But in this revision I make a stronger assumption about genBits and do away with unimplemented cases. So this is the first candidate full replacement for the master branch with the old (incorrect) function definitions completely removed and replaced. >--------------------------------------------------------------- f85c6a55b731d5e380c1d6e880105c9933aa9d48 DEVLOG.md | 93 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++ System/Random.hs | 46 ++++++++++++++-------------- random.cabal | 2 +- 3 files changed, 118 insertions(+), 23 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f85c6a55b731d5e380c1d6e880105c9933aa9d48 From git at git.haskell.org Thu Mar 19 15:44:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:24 +0000 (UTC) Subject: [commit: packages/random] new_api: Merge branch 'master' into new_api (280f978) Message-ID: <20150319154424.540BC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/280f97885da4409dd7d8833cf6d9435bc5294efa >--------------------------------------------------------------- commit 280f97885da4409dd7d8833cf6d9435bc5294efa Merge: f85c6a5 dfeff47 Author: Ryan Newton Date: Tue Jun 28 14:57:19 2011 -0400 Merge branch 'master' into new_api >--------------------------------------------------------------- 280f97885da4409dd7d8833cf6d9435bc5294efa tests/TestRandomRs.hs | 24 ++++++++++++++++++++++ tests/rangeTest.hs | 4 ++-- tests/rangeTest.stdout | 2 -- tests/slowness.hs | 55 ++++++++++++++++++++++++++++++++++++++++++++++++++ 4 files changed, 81 insertions(+), 4 deletions(-) From git at git.haskell.org Thu Mar 19 15:44:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:26 +0000 (UTC) Subject: [commit: packages/random] new_api: Reactivated big Integer tests that were deactivated on the master branch. (5541f8c) Message-ID: <20150319154426.5A5813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : new_api Link : http://git.haskell.org/packages/random.git/commitdiff/5541f8cdca26657cfc18bd6d101870e7c3a913a2 >--------------------------------------------------------------- commit 5541f8cdca26657cfc18bd6d101870e7c3a913a2 Author: Ryan Newton Date: Wed Jun 29 13:28:46 2011 -0400 Reactivated big Integer tests that were deactivated on the master branch. >--------------------------------------------------------------- 5541f8cdca26657cfc18bd6d101870e7c3a913a2 tests/rangeTest.hs | 4 ++-- tests/rangeTest.stdout | 2 ++ 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/tests/rangeTest.hs b/tests/rangeTest.hs index 704a36c..88f736d 100644 --- a/tests/rangeTest.hs +++ b/tests/rangeTest.hs @@ -58,8 +58,8 @@ main = do checkBounds "Int" (intRange nb) (approxBounds random trials (undefined::Int)) checkBounds "Integer" (intRange nb) (approxBounds random trials (undefined::Integer)) --- checkBounds "Integer Rbig" (False,-(2^500), 2^500) (approxBounds (randomR (-(2^500), 2^500)) trials (undefined::Integer)) --- checkBounds "Integer RbigPos" (False,1,2^5000) (approxBounds (randomR (1,2^5000)) trials (undefined::Integer)) + checkBounds "Integer Rbig" (False,-(2^500), 2^500) (approxBounds (randomR (-(2^500), 2^500)) trials (undefined::Integer)) + checkBounds "Integer RbigPos" (False,1,2^5000) (approxBounds (randomR (1,2^5000)) trials (undefined::Integer)) checkBounds "Int8" (intRange 8) (approxBounds random trials (undefined::Int8)) checkBounds "Int16" (intRange 16) (approxBounds random trials (undefined::Int16)) checkBounds "Int32" (intRange 32) (approxBounds random trials (undefined::Int32)) diff --git a/tests/rangeTest.stdout b/tests/rangeTest.stdout index 55ccaff..f9d9479 100644 --- a/tests/rangeTest.stdout +++ b/tests/rangeTest.stdout @@ -1,5 +1,7 @@ Int: Passed Integer: Passed +Integer Rbig: Passed +Integer RbigPos: Passed Int8: Passed Int16: Passed Int32: Passed From git at git.haskell.org Thu Mar 19 15:44:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:28 +0000 (UTC) Subject: [commit: packages/random] master: Add .gitignore. (613224a) Message-ID: <20150319154428.620383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/613224a9d8a6c97bbf9f79255835251927176217 >--------------------------------------------------------------- commit 613224a9d8a6c97bbf9f79255835251927176217 Author: Paolo Capriotti Date: Tue Mar 6 10:57:35 2012 +0000 Add .gitignore. >--------------------------------------------------------------- 613224a9d8a6c97bbf9f79255835251927176217 .gitignore | 3 +++ 1 file changed, 3 insertions(+) diff --git a/.gitignore b/.gitignore new file mode 100644 index 0000000..8f4d267 --- /dev/null +++ b/.gitignore @@ -0,0 +1,3 @@ +GNUmakefile +dist-install +ghc.mk From git at git.haskell.org Thu Mar 19 15:44:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:30 +0000 (UTC) Subject: [commit: packages/random] master: Updated link (b185c4e) Message-ID: <20150319154430.6A1A83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/b185c4e6440c2a6ac74a001b4b4b025bfab352a9 >--------------------------------------------------------------- commit b185c4e6440c2a6ac74a001b4b4b025bfab352a9 Author: Krishna Thapa Date: Mon Apr 29 01:12:25 2013 -0500 Updated link >--------------------------------------------------------------- b185c4e6440c2a6ac74a001b4b4b025bfab352a9 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 325f8db..8c32bea 100644 --- a/README.md +++ b/README.md @@ -8,7 +8,7 @@ provides a basic interface for (splittable) random number generators. The API documentation can be found here: - http://www.haskell.org/ghc/docs/latest/html/libraries/random/System-Random.html + http://www.haskell.org/ghc/docs/7.6.2/html/libraries/haskell98-2.0.0.2/Random.html A module supplying this interface is required for Haskell 98. From git at git.haskell.org Thu Mar 19 15:44:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:32 +0000 (UTC) Subject: [commit: packages/random] master: Merge pull request #2 from pcapriotti/master (9519072) Message-ID: <20150319154432.7282F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/9519072ebcc92a6cf9bc120c2a8a98338403afc9 >--------------------------------------------------------------- commit 9519072ebcc92a6cf9bc120c2a8a98338403afc9 Merge: 69bfde2 613224a Author: Ryan Newton Date: Tue Feb 4 13:16:24 2014 -0800 Merge pull request #2 from pcapriotti/master Add .gitignore >--------------------------------------------------------------- 9519072ebcc92a6cf9bc120c2a8a98338403afc9 .gitignore | 3 +++ 1 file changed, 3 insertions(+) From git at git.haskell.org Thu Mar 19 15:44:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:34 +0000 (UTC) Subject: [commit: packages/random] master: Merge pull request #3 from thapakrish/master (c5e5af6) Message-ID: <20150319154434.797813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/c5e5af65c773bd2eb4fb3abd1ebd030e720b838b >--------------------------------------------------------------- commit c5e5af65c773bd2eb4fb3abd1ebd030e720b838b Merge: 9519072 b185c4e Author: Ryan Newton Date: Tue Feb 4 13:17:01 2014 -0800 Merge pull request #3 from thapakrish/master Edited readme >--------------------------------------------------------------- c5e5af65c773bd2eb4fb3abd1ebd030e720b838b README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Thu Mar 19 15:44:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:36 +0000 (UTC) Subject: [commit: packages/random] master: Use GHC.Exts.build in randoms, randomRs to achieve fusion (4695ffa) Message-ID: <20150319154436.808683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/4695ffa366f659940369f05e419a4f2249c3a776 >--------------------------------------------------------------- commit 4695ffa366f659940369f05e419a4f2249c3a776 Author: Johan Kiviniemi Date: Sun Jan 26 14:59:55 2014 +0200 Use GHC.Exts.build in randoms, randomRs to achieve fusion >--------------------------------------------------------------- 4695ffa366f659940369f05e419a4f2249c3a776 System/Random.hs | 27 +++++++++++++++++++++++++-- 1 file changed, 25 insertions(+), 2 deletions(-) diff --git a/System/Random.hs b/System/Random.hs index 9a970c4..844dea8 100644 --- a/System/Random.hs +++ b/System/Random.hs @@ -96,6 +96,15 @@ import System.IO.Unsafe ( unsafePerformIO ) import Data.IORef import Numeric ( readDec ) +#ifdef __GLASGOW_HASKELL__ +import GHC.Exts ( build ) +#else +-- | A dummy variant of build without fusion. +{-# INLINE build #-} +build :: ((a -> [a] -> [a]) -> [a] -> [a]) -> [a] +build g = g (:) [] +#endif + -- The standard nhc98 implementation of Time.ClockTime does not match -- the extended one expected in this module, so we lash-up a quick -- replacement here. @@ -279,13 +288,15 @@ class Random a where -- | Plural variant of 'randomR', producing an infinite list of -- random values instead of returning a new generator. + {-# INLINE randomRs #-} randomRs :: RandomGen g => (a,a) -> g -> [a] - randomRs ival g = x : randomRs ival g' where (x,g') = randomR ival g + randomRs ival g = build (\cons _nil -> buildRandoms cons (randomR ival) g) -- | Plural variant of 'random', producing an infinite list of -- random values instead of returning a new generator. + {-# INLINE randoms #-} randoms :: RandomGen g => g -> [a] - randoms g = (\(x,g') -> x : randoms g') (random g) + randoms g = build (\cons _nil -> buildRandoms cons random g) -- | A variant of 'randomR' that uses the global random number generator -- (see "System.Random#globalrng"). @@ -297,6 +308,18 @@ class Random a where randomIO :: IO a randomIO = getStdRandom random +-- | Produce an infinite list-equivalent of random values. +{-# INLINE buildRandoms #-} +buildRandoms :: RandomGen g + => (a -> as -> as) -- ^ E.g. '(:)' but subject to fusion + -> (g -> (a,g)) -- ^ E.g. 'random' + -> g -- ^ A 'RandomGen' instance + -> as +buildRandoms cons rand = go + where + -- The seq fixes part of #4218 and also makes fused Core simpler. + go g = x `seq` (x `cons` go g') where (x,g') = rand g + instance Random Integer where randomR ival g = randomIvalInteger ival g From git at git.haskell.org Thu Mar 19 15:44:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:38 +0000 (UTC) Subject: [commit: packages/random] master: Merge branch 'master' of github.com:haskell/random (42851d3) Message-ID: <20150319154438.874B33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/42851d3e4fbf6e29e8339ff28862f21e61cd9685 >--------------------------------------------------------------- commit 42851d3e4fbf6e29e8339ff28862f21e61cd9685 Merge: 4695ffa c5e5af6 Author: Ryan Newton Date: Tue Feb 4 16:25:26 2014 -0500 Merge branch 'master' of github.com:haskell/random >--------------------------------------------------------------- 42851d3e4fbf6e29e8339ff28862f21e61cd9685 .gitignore | 3 +++ README.md | 2 +- 2 files changed, 4 insertions(+), 1 deletion(-) From git at git.haskell.org Thu Mar 19 15:44:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:40 +0000 (UTC) Subject: [commit: packages/random] master: Version bump to go with prev (a42da67) Message-ID: <20150319154440.8DB153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/a42da67186e942243b2190ca2a34b2b3d76efcc7 >--------------------------------------------------------------- commit a42da67186e942243b2190ca2a34b2b3d76efcc7 Author: Ryan Newton Date: Wed Feb 5 01:17:13 2014 -0500 Version bump to go with prev >--------------------------------------------------------------- a42da67186e942243b2190ca2a34b2b3d76efcc7 random.cabal | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/random.cabal b/random.cabal index 9c7b63f..fe7099f 100644 --- a/random.cabal +++ b/random.cabal @@ -1,8 +1,9 @@ name: random -version: 1.0.1.1 +version: 1.0.1.2 -- 1.0.1.0 -- bump for bug fixes, but no SplittableGen yet -- 1.0.1.1 -- bump for overflow bug fixes +-- 1.0.1.2 -- bump for ticket 8704, build fusion license: BSD3 license-file: LICENSE From git at git.haskell.org Thu Mar 19 15:44:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:42 +0000 (UTC) Subject: [commit: packages/random] master: fix for randomIvalInteger, ghc #8898 (031a557) Message-ID: <20150319154442.954F43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/031a5574ebf31d956f077a16f3fc38c39ca284a3 >--------------------------------------------------------------- commit 031a5574ebf31d956f077a16f3fc38c39ca284a3 Author: Ken Bateman Date: Sat Mar 22 20:42:44 2014 +0000 fix for randomIvalInteger, ghc #8898 >--------------------------------------------------------------- 031a5574ebf31d956f077a16f3fc38c39ca284a3 System/Random.hs | 42 ++++++++++++++++++++++-------------------- 1 file changed, 22 insertions(+), 20 deletions(-) diff --git a/System/Random.hs b/System/Random.hs index 844dea8..665dd78 100644 --- a/System/Random.hs +++ b/System/Random.hs @@ -444,24 +444,33 @@ randomBounded = randomR (minBound, maxBound) randomIvalIntegral :: (RandomGen g, Integral a) => (a, a) -> g -> (a, g) randomIvalIntegral (l,h) = randomIvalInteger (toInteger l, toInteger h) +{-# SPECIALIZE randomIvalInteger :: (Num a) => + (Integer, Integer) -> StdGen -> (a, StdGen) #-} + randomIvalInteger :: (RandomGen g, Num a) => (Integer, Integer) -> g -> (a, g) randomIvalInteger (l,h) rng | l > h = randomIvalInteger (h,l) rng - | otherwise = case (f n 1 rng) of (v, rng') -> (fromInteger (l + v `mod` k), rng') + | otherwise = case (f 1 0 rng) of (v, rng') -> (fromInteger (l + v `mod` k), rng') where + (genlo, genhi) = genRange rng + b = fromIntegral genhi - fromIntegral genlo + 1 + + -- Probabilities of the most likely and least likely result + -- will differ at most by a factor of (1 +- 1/q). Assuming the RandomGen + -- is uniform, of course + + -- On average, log q / log b more random values will be generated + -- than the minimum + q = 1000 k = h - l + 1 - -- ERROR: b here (2^31-87) represents a baked-in assumption about genRange: - b = 2147483561 - n = iLogBase b k - - -- Here we loop until we've generated enough randomness to cover the range: - f 0 acc g = (acc, g) - f n' acc g = - let - (x,g') = next g - in - -- We shift over the random bits generated thusfar (* b) and add in the new ones. - f (n' - 1) (fromIntegral x + acc * b) g' + magtgt = k * q + + -- generate random values until we exceed the target magnitude + f mag v g | mag >= magtgt = (v, g) + | otherwise = v' `seq`f (mag*b) v' g' where + (x,g') = next g + v' = (v * b + (fromIntegral x - fromIntegral genlo)) + -- The continuous functions on the other hand take an [inclusive,exclusive) range. randomFrac :: (RandomGen g, Fractional a) => g -> (a, g) @@ -484,13 +493,6 @@ randomIvalDouble (l,h) fromDouble rng int32Count :: Integer int32Count = toInteger (maxBound::Int32) - toInteger (minBound::Int32) + 1 --- Perform an expensive logarithm on arbitrary-size integers by repeated division. --- --- (NOTE: This actually returns ceiling(log(i) base b) except with an --- incorrect result at iLogBase b b = 2.) -iLogBase :: Integer -> Integer -> Integer -iLogBase b i = if i < b then 1 else 1 + iLogBase b (i `div` b) - stdRange :: (Int,Int) stdRange = (0, 2147483562) From git at git.haskell.org Thu Mar 19 15:44:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:44 +0000 (UTC) Subject: [commit: packages/random] master: Merge remote-tracking branch 'remotes/downstream/master' (dcb3972) Message-ID: <20150319154444.9E8653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/dcb39721a9f9e3bc946b12fc1adc0085e402c1d5 >--------------------------------------------------------------- commit dcb39721a9f9e3bc946b12fc1adc0085e402c1d5 Merge: a42da67 180aa65 Author: Ryan Newton Date: Fri Mar 28 15:53:29 2014 -0400 Merge remote-tracking branch 'remotes/downstream/master' Conflicts: .gitignore >--------------------------------------------------------------- dcb39721a9f9e3bc946b12fc1adc0085e402c1d5 .gitignore | 7 ++++++- random.cabal | 2 +- tests/all.T | 2 +- 3 files changed, 8 insertions(+), 3 deletions(-) From git at git.haskell.org Thu Mar 19 15:44:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:46 +0000 (UTC) Subject: [commit: packages/random] master: Merge pull request #4 from NovaDenizen/master (b1cb6e5) Message-ID: <20150319154446.A4FEF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/b1cb6e55d31efd67535b57748c28c9c1668ad3b8 >--------------------------------------------------------------- commit b1cb6e55d31efd67535b57748c28c9c1668ad3b8 Merge: dcb3972 031a557 Author: Ryan Newton Date: Fri Mar 28 16:01:01 2014 -0400 Merge pull request #4 from NovaDenizen/master fix for randomIvalInteger, ghc #8898 >--------------------------------------------------------------- b1cb6e55d31efd67535b57748c28c9c1668ad3b8 System/Random.hs | 42 ++++++++++++++++++++++-------------------- 1 file changed, 22 insertions(+), 20 deletions(-) From git at git.haskell.org Thu Mar 19 15:44:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:48 +0000 (UTC) Subject: [commit: packages/random] master: Update README + issue tracker link in cabal file (fecc2d7) Message-ID: <20150319154448.AF64C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/fecc2d7674f8a5c844594e3c5a645ebfaecfed51 >--------------------------------------------------------------- commit fecc2d7674f8a5c844594e3c5a645ebfaecfed51 Author: Thomas Miedema Date: Fri Jun 27 15:38:24 2014 +0200 Update README + issue tracker link in cabal file >--------------------------------------------------------------- fecc2d7674f8a5c844594e3c5a645ebfaecfed51 README.md | 13 +++++++++---- random.cabal | 2 +- 2 files changed, 10 insertions(+), 5 deletions(-) diff --git a/README.md b/README.md index 8c32bea..24669f7 100644 --- a/README.md +++ b/README.md @@ -3,12 +3,17 @@ The Haskell Standard Library -- Random Number Generation ======================================================== -This core library is (was) shipped with the Glasgow Haskell Compiler and -provides a basic interface for (splittable) random number generators. +This library provides a basic interface for (splittable) random number generators. The API documentation can be found here: - http://www.haskell.org/ghc/docs/7.6.2/html/libraries/haskell98-2.0.0.2/Random.html + http://hackage.haskell.org/package/random/docs/System-Random.html -A module supplying this interface is required for Haskell 98. +A module supplying this interface is required for Haskell 98 (but not Haskell +2010). An older [version] +(http://www.haskell.org/ghc/docs/latest/html/libraries/haskell98/Random.html) +of this library is included with GHC in the haskell98 package. This newer +version, with compatible api, is included in the [Haskell Platform] +(http://www.haskell.org/platform/contents.html). +Please report bugs in the Github [issue tracker] (https://github.com/haskell/random/issues) (no longer in the GHC trac). diff --git a/random.cabal b/random.cabal index b0115de..f8dc6f8 100644 --- a/random.cabal +++ b/random.cabal @@ -8,7 +8,7 @@ version: 1.0.1.2 license: BSD3 license-file: LICENSE maintainer: rrnewton at gmail.com -bug-reports: http://hackage.haskell.org/trac/ghc/newticket?component=libraries/random +bug-reports: https://github.com/haskell/random/issues synopsis: random number library category: System description: From git at git.haskell.org Thu Mar 19 15:44:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:50 +0000 (UTC) Subject: [commit: packages/random] master: The lowest int generated by StdGen is 1. Fixes ghc #8899. (485cbf1) Message-ID: <20150319154450.BBE593A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/485cbf1ab6ba08a014a470e7109221f91a5e321a >--------------------------------------------------------------- commit 485cbf1ab6ba08a014a470e7109221f91a5e321a Author: Thomas Miedema Date: Tue Jul 8 14:06:40 2014 +0200 The lowest int generated by StdGen is 1. Fixes ghc #8899. This follows from the following line in the function stdNext (z' is the next generated Int): z' = if z < 1 then z + 2147483562 else z >--------------------------------------------------------------- 485cbf1ab6ba08a014a470e7109221f91a5e321a System/Random.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Random.hs b/System/Random.hs index 665dd78..defb8e4 100644 --- a/System/Random.hs +++ b/System/Random.hs @@ -494,7 +494,7 @@ int32Count :: Integer int32Count = toInteger (maxBound::Int32) - toInteger (minBound::Int32) + 1 stdRange :: (Int,Int) -stdRange = (0, 2147483562) +stdRange = (1, 2147483562) stdNext :: StdGen -> (Int, StdGen) -- Returns values in the range stdRange From git at git.haskell.org Thu Mar 19 15:44:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:52 +0000 (UTC) Subject: [commit: packages/random] master: Cleanup + add comments (a3a70df) Message-ID: <20150319154452.C4CEB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/a3a70df88018e8b7fd82c3feec91bf9087fb239e >--------------------------------------------------------------- commit a3a70df88018e8b7fd82c3feec91bf9087fb239e Author: Thomas Miedema Date: Tue Jul 8 14:32:26 2014 +0200 Cleanup + add comments Fixme reverred to formatting of comments, which was done in 24260b389852ab109de6b62822d889d0e66ae723 >--------------------------------------------------------------- a3a70df88018e8b7fd82c3feec91bf9087fb239e System/Random.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/System/Random.hs b/System/Random.hs index defb8e4..cebcccf 100644 --- a/System/Random.hs +++ b/System/Random.hs @@ -244,6 +244,11 @@ should be likely to produce distinct generators. mkStdGen :: Int -> StdGen -- why not Integer ? mkStdGen s = mkStdGen32 $ fromIntegral s +{- +From ["System.Random\#LEcuyer"]: "The integer variables s1 and s2 ... must be +initialized to values in the range [1, 2147483562] and [1, 2147483398] +respectively." +-} mkStdGen32 :: Int32 -> StdGen mkStdGen32 sMaybeNegative = StdGen (s1+1) (s2+1) where @@ -256,8 +261,6 @@ mkStdGen32 sMaybeNegative = StdGen (s1+1) (s2+1) createStdGen :: Integer -> StdGen createStdGen s = mkStdGen32 $ fromIntegral s --- FIXME: 1/2/3 below should be ** (vs at 30082002) XXX - {- | With a source of random number supply in hand, the 'Random' class allows the programmer to extract random values of a variety of types. @@ -491,7 +494,7 @@ randomIvalDouble (l,h) fromDouble rng (scaled_x, rng') int32Count :: Integer -int32Count = toInteger (maxBound::Int32) - toInteger (minBound::Int32) + 1 +int32Count = toInteger (maxBound::Int32) - toInteger (minBound::Int32) + 1 -- GHC ticket #3982 stdRange :: (Int,Int) stdRange = (1, 2147483562) From git at git.haskell.org Thu Mar 19 15:44:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:54 +0000 (UTC) Subject: [commit: packages/random] master: Make TestRandomRs (GHC #4218) fast and add to cabal file (bba3db1) Message-ID: <20150319154454.CC29B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/bba3db1dfd172790f9a6182d32e4034c42def6cb >--------------------------------------------------------------- commit bba3db1dfd172790f9a6182d32e4034c42def6cb Author: Thomas Miedema Date: Tue Jul 1 16:28:57 2014 +0200 Make TestRandomRs (GHC #4218) fast and add to cabal file >--------------------------------------------------------------- bba3db1dfd172790f9a6182d32e4034c42def6cb random.cabal | 16 +++++++++++++++- tests/TestRandomRs.hs | 38 ++++++++++++++++++-------------------- 2 files changed, 33 insertions(+), 21 deletions(-) diff --git a/random.cabal b/random.cabal index b0115de..511ce29 100644 --- a/random.cabal +++ b/random.cabal @@ -16,7 +16,9 @@ description: library, including the ability to split random number generators. build-type: Simple -Cabal-Version: >= 1.6 +-- cabal-version 1.8 needed because "the field 'build-depends: random' refers +-- to a library which is defined within the same package" +cabal-version: >= 1.8 @@ -31,3 +33,15 @@ source-repository head type: git location: http://git.haskell.org/packages/random.git +-- To run the Test-Suite: +-- $ cabal configure --enable-tests +-- $ cabal test --show-details=always --test-options="+RTS -M1M -RTS" + +Test-Suite TestRandomRs + type: exitcode-stdio-1.0 + main-is: TestRandomRs.hs + hs-source-dirs: tests + build-depends: base >= 3 && < 5, random + ghc-options: -rtsopts -O2 + -- TODO. Why does the following not work? + --test-options: +RTS -M1M -RTS diff --git a/tests/TestRandomRs.hs b/tests/TestRandomRs.hs index 74e319d..cdae106 100644 --- a/tests/TestRandomRs.hs +++ b/tests/TestRandomRs.hs @@ -1,24 +1,22 @@ - --- Test from ticket #4218: --- http://hackage.haskell.org/trac/ghc/ticket/4218 +-- Test for ticket #4218 (TestRandomRs): +-- https://ghc.haskell.org/trac/ghc/ticket/4218 +-- +-- Fixed together with ticket #8704 +-- https://ghc.haskell.org/trac/ghc/ticket/8704 +-- Commit 4695ffa366f659940369f05e419a4f2249c3a776 +-- +-- Used to fail with: +-- +-- $ cabal test TestRandomRs --test-options="+RTS -M1M -RTS" +-- TestRandomRs: Heap exhausted; module Main where -import Control.Monad -import System.Random -import Data.List - -force = foldr (\x r -> x `seq` (x:r)) [] - --- Ten million random numbers: -blowsTheHeap :: IO Integer -blowsTheHeap = (last . take 10000000 . randomRs (0, 1000000)) `liftM` getStdGen - -works :: IO Integer -works = (last . take 10000000 . force . randomRs (0, 1000000)) `liftM` getStdGen - - -main = - do n <- blowsTheHeap - print n +import Control.Monad (liftM, replicateM) +import System.Random (randomRs, getStdGen) +-- Return the five-thousandth random number: +-- Should run in constant space (< 1Mb heap). +main = do + n <- (last . take 5000 . randomRs (0, 1000000)) `liftM` getStdGen + print (n::Integer) From git at git.haskell.org Thu Mar 19 15:44:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:56 +0000 (UTC) Subject: [commit: packages/random] master: Use atomicModifyIORef' (strict) (GHC #4218) (8a4dedd) Message-ID: <20150319154456.D3C183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/8a4dedd12e26cacacd971d1334be95f1e3860515 >--------------------------------------------------------------- commit 8a4dedd12e26cacacd971d1334be95f1e3860515 Author: Thomas Miedema Date: Thu Jul 10 21:01:44 2014 +0200 Use atomicModifyIORef' (strict) (GHC #4218) >--------------------------------------------------------------- 8a4dedd12e26cacacd971d1334be95f1e3860515 System/Random.hs | 4 ++-- random.cabal | 7 +++++++ tests/TestRandomIOs.hs | 20 ++++++++++++++++++++ 3 files changed, 29 insertions(+), 2 deletions(-) diff --git a/System/Random.hs b/System/Random.hs index 665dd78..7522499 100644 --- a/System/Random.hs +++ b/System/Random.hs @@ -553,7 +553,7 @@ theStdGen = unsafePerformIO $ do -- |Applies 'split' to the current global random generator, -- updates it with one of the results, and returns the other. newStdGen :: IO StdGen -newStdGen = atomicModifyIORef theStdGen split +newStdGen = atomicModifyIORef' theStdGen split {- |Uses the supplied function to get a value from the current global random generator, and updates the global generator with the new generator @@ -566,7 +566,7 @@ between 1 and 6: -} getStdRandom :: (StdGen -> (a,StdGen)) -> IO a -getStdRandom f = atomicModifyIORef theStdGen (swap . f) +getStdRandom f = atomicModifyIORef' theStdGen (swap . f) where swap (v,g) = (g,v) {- $references diff --git a/random.cabal b/random.cabal index 511ce29..1039057 100644 --- a/random.cabal +++ b/random.cabal @@ -45,3 +45,10 @@ Test-Suite TestRandomRs ghc-options: -rtsopts -O2 -- TODO. Why does the following not work? --test-options: +RTS -M1M -RTS + +Test-Suite TestRandomIOs + type: exitcode-stdio-1.0 + main-is: TestRandomIOs.hs + hs-source-dirs: tests + build-depends: base >= 3 && < 5, random + ghc-options: -rtsopts -O2 diff --git a/tests/TestRandomIOs.hs b/tests/TestRandomIOs.hs new file mode 100644 index 0000000..d8a00cc --- /dev/null +++ b/tests/TestRandomIOs.hs @@ -0,0 +1,20 @@ +-- Test for ticket #4218 (TestRandomIOs): +-- https://ghc.haskell.org/trac/ghc/ticket/4218 +-- +-- Used to fail with: +-- +-- $ cabal test TestRandomIOs --test-options="+RTS -M1M -RTS" +-- TestRandomIOs: Heap exhausted; + +module Main where + +import Control.Monad (replicateM) +import System.Random (randomIO) + +-- Build a list of 5000 random ints in memory (IO Monad is strict), and print +-- the last one. +-- Should use less than 1Mb of heap space, or we are generating a list of +-- unevaluated thunks. +main = do + rs <- replicateM 5000 randomIO :: IO [Int] + print $ last rs From git at git.haskell.org Thu Mar 19 15:44:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:44:58 +0000 (UTC) Subject: [commit: packages/random] master: Use strict fields for StdGen (GHC #7936) (9721b7c) Message-ID: <20150319154458.DD07C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/9721b7c09278479a763a9a187fbd91fa4faacc98 >--------------------------------------------------------------- commit 9721b7c09278479a763a9a187fbd91fa4faacc98 Author: Thomas Miedema Date: Thu Jul 10 20:56:17 2014 +0200 Use strict fields for StdGen (GHC #7936) >--------------------------------------------------------------- 9721b7c09278479a763a9a187fbd91fa4faacc98 System/Random.hs | 2 +- random.cabal | 7 +++++++ tests/T7936.hs | 14 ++++++++++++++ 3 files changed, 22 insertions(+), 1 deletion(-) diff --git a/System/Random.hs b/System/Random.hs index 7522499..1d0ec42 100644 --- a/System/Random.hs +++ b/System/Random.hs @@ -198,7 +198,7 @@ instance of 'StdGen' has the following properties: -} data StdGen - = StdGen Int32 Int32 + = StdGen !Int32 !Int32 instance RandomGen StdGen where next = stdNext diff --git a/random.cabal b/random.cabal index 1039057..8353685 100644 --- a/random.cabal +++ b/random.cabal @@ -37,6 +37,13 @@ source-repository head -- $ cabal configure --enable-tests -- $ cabal test --show-details=always --test-options="+RTS -M1M -RTS" +Test-Suite T7936 + type: exitcode-stdio-1.0 + main-is: T7936.hs + hs-source-dirs: tests + build-depends: base >= 3 && < 5, random + ghc-options: -rtsopts -O2 + Test-Suite TestRandomRs type: exitcode-stdio-1.0 main-is: TestRandomRs.hs diff --git a/tests/T7936.hs b/tests/T7936.hs new file mode 100644 index 0000000..cfea911 --- /dev/null +++ b/tests/T7936.hs @@ -0,0 +1,14 @@ +-- Test for ticket #7936: +-- https://ghc.haskell.org/trac/ghc/ticket/7936 +-- +-- Used to fail with: +-- +-- $ cabal test T7936 --test-options="+RTS -M1M -RTS" +-- T7936: Heap exhausted; + +module Main where + +import System.Random (newStdGen) +import Control.Monad (replicateM_) + +main = replicateM_ 100000 newStdGen From git at git.haskell.org Thu Mar 19 15:45:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:00 +0000 (UTC) Subject: [commit: packages/random] master: rangeTest: Fix signed-ness of types (80df82a) Message-ID: <20150319154500.E82D03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/80df82aa70f8ad7c260603bc1578106982b50745 >--------------------------------------------------------------- commit 80df82aa70f8ad7c260603bc1578106982b50745 Author: Ben Gamari Date: Sat Mar 22 15:29:45 2014 +0100 rangeTest: Fix signed-ness of types On some architectures types like CChar are signed whereas the use previously assumed they were unsigned. Fix this by relying on Bounded instances where possible. >--------------------------------------------------------------- 80df82aa70f8ad7c260603bc1578106982b50745 tests/rangeTest.hs | 87 +++++++++++++++++++++++++++--------------------------- 1 file changed, 43 insertions(+), 44 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 80df82aa70f8ad7c260603bc1578106982b50745 From git at git.haskell.org Thu Mar 19 15:45:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:02 +0000 (UTC) Subject: [commit: packages/random] master: Revert "rangeTest fails on Windows (#7379)" (8e379a7) Message-ID: <20150319154502.F08073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/8e379a72306a1d9c082d0a728930fa197d61e8ba >--------------------------------------------------------------- commit 8e379a72306a1d9c082d0a728930fa197d61e8ba Author: Ben Gamari Date: Tue Aug 19 16:02:23 2014 -0400 Revert "rangeTest fails on Windows (#7379)" This reverts commit 2117e38729adaa4f465f3c5b7a8c5c4d77702d3f. We no longer assume that C types are unsigned. >--------------------------------------------------------------- 8e379a72306a1d9c082d0a728930fa197d61e8ba tests/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/all.T b/tests/all.T index 5fb2645..f1675ed 100644 --- a/tests/all.T +++ b/tests/all.T @@ -1,6 +1,6 @@ test('rangeTest', - when(opsys('mingw32'), expect_broken(7379)), + normal, compile_and_run, ['']) From git at git.haskell.org Thu Mar 19 15:45:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:05 +0000 (UTC) Subject: [commit: packages/random] master: Merge pull request #8 from thomie/memory-leaks (5ee25dc) Message-ID: <20150319154505.05CA23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/5ee25dca1fe22c8e22b5862bb79dcd72182ba62b >--------------------------------------------------------------- commit 5ee25dca1fe22c8e22b5862bb79dcd72182ba62b Merge: b1cb6e5 9721b7c Author: Ryan Newton Date: Fri Aug 22 15:48:56 2014 -0400 Merge pull request #8 from thomie/memory-leaks Fix for memory leaks (GHC #7936 and #4218) >--------------------------------------------------------------- 5ee25dca1fe22c8e22b5862bb79dcd72182ba62b System/Random.hs | 6 +++--- random.cabal | 30 +++++++++++++++++++++++++++++- tests/T7936.hs | 14 ++++++++++++++ tests/TestRandomIOs.hs | 20 ++++++++++++++++++++ tests/TestRandomRs.hs | 38 ++++++++++++++++++-------------------- 5 files changed, 84 insertions(+), 24 deletions(-) From git at git.haskell.org Thu Mar 19 15:45:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:07 +0000 (UTC) Subject: [commit: packages/random] master: Merge pull request #7 from thomie/T8899 (8570176) Message-ID: <20150319154507.0E7543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/8570176d5836279939710ebf7b34eb1ba0cdf797 >--------------------------------------------------------------- commit 8570176d5836279939710ebf7b34eb1ba0cdf797 Merge: 5ee25dc a3a70df Author: Ryan Newton Date: Fri Aug 22 15:49:01 2014 -0400 Merge pull request #7 from thomie/T8899 Fix for ghc ticket #8899: StdGen does not generate 0 >--------------------------------------------------------------- 8570176d5836279939710ebf7b34eb1ba0cdf797 System/Random.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) From git at git.haskell.org Thu Mar 19 15:45:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:09 +0000 (UTC) Subject: [commit: packages/random] master: Merge pull request #6 from thomie/master (cc9372d) Message-ID: <20150319154509.141793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/cc9372d00d2e1c66f8e7587698bc9bd6052d6e4d >--------------------------------------------------------------- commit cc9372d00d2e1c66f8e7587698bc9bd6052d6e4d Merge: 8570176 fecc2d7 Author: Ryan Newton Date: Fri Aug 22 15:49:08 2014 -0400 Merge pull request #6 from thomie/master Update README + issue tracker link in cabal file >--------------------------------------------------------------- cc9372d00d2e1c66f8e7587698bc9bd6052d6e4d README.md | 13 +++++++++---- random.cabal | 2 +- 2 files changed, 10 insertions(+), 5 deletions(-) From git at git.haskell.org Thu Mar 19 15:45:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:11 +0000 (UTC) Subject: [commit: packages/random] master: Merge pull request #5 from bgamari/master (dedcb54) Message-ID: <20150319154511.1C59C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/dedcb54955952d42ae3989e913be35b564b9f929 >--------------------------------------------------------------- commit dedcb54955952d42ae3989e913be35b564b9f929 Merge: cc9372d 8e379a7 Author: Ryan Newton Date: Fri Aug 22 15:50:01 2014 -0400 Merge pull request #5 from bgamari/master rangeTest: Fix signed-ness of types >--------------------------------------------------------------- dedcb54955952d42ae3989e913be35b564b9f929 tests/all.T | 2 +- tests/rangeTest.hs | 87 +++++++++++++++++++++++++++--------------------------- 2 files changed, 44 insertions(+), 45 deletions(-) From git at git.haskell.org Thu Mar 19 15:45:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:13 +0000 (UTC) Subject: [commit: packages/random] master: Bump version for various bugfixes (d05a606) Message-ID: <20150319154513.2888B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/d05a606f13889652f8aa1e2153564d18a5c343fe >--------------------------------------------------------------- commit d05a606f13889652f8aa1e2153564d18a5c343fe Author: Ryan Newton Date: Fri Aug 22 15:52:30 2014 -0400 Bump version for various bugfixes >--------------------------------------------------------------- d05a606f13889652f8aa1e2153564d18a5c343fe random.cabal | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/random.cabal b/random.cabal index 98d2aab..c9a645a 100644 --- a/random.cabal +++ b/random.cabal @@ -1,9 +1,10 @@ name: random -version: 1.0.1.2 +version: 1.0.1.3 -- 1.0.1.0 -- bump for bug fixes, but no SplittableGen yet -- 1.0.1.1 -- bump for overflow bug fixes -- 1.0.1.2 -- bump for ticket 8704, build fusion +-- 1.0.1.3 -- bump for various bug fixes license: BSD3 license-file: LICENSE From git at git.haskell.org Thu Mar 19 15:45:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:15 +0000 (UTC) Subject: [commit: packages/random] master: rangeTest: Fix type for "CSigAtomic R" test (3000397) Message-ID: <20150319154515.358EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/3000397a8a60ac9f744171a1b30e60b6aa3720d7 >--------------------------------------------------------------- commit 3000397a8a60ac9f744171a1b30e60b6aa3720d7 Author: Ben Gamari Date: Fri Aug 22 17:41:42 2014 -0400 rangeTest: Fix type for "CSigAtomic R" test >--------------------------------------------------------------- 3000397a8a60ac9f744171a1b30e60b6aa3720d7 tests/rangeTest.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/rangeTest.hs b/tests/rangeTest.hs index e59f0d6..ac62c71 100644 --- a/tests/rangeTest.hs +++ b/tests/rangeTest.hs @@ -121,7 +121,7 @@ main = checkBounds "CPtrdiff R" (False,-100,100) (approxBounds (randomR (-100,100)) trials (undefined:: CPtrdiff)) checkBounds "CSize R" (False,0,200) (approxBounds (randomR (0,200)) trials (undefined:: CSize)) checkBounds "CWchar R" (False,0,100) (approxBounds (randomR (0,100)) trials (undefined:: CWchar)) - checkBounds "CSigAtomic R" (False,0,100) (approxBounds (randomR (0,100)) trials (undefined:: CWchar)) + checkBounds "CSigAtomic R" (False,0,100) (approxBounds (randomR (0,100)) trials (undefined:: CSigAtomic)) checkBounds "CLLong R" (False,-100,100) (approxBounds (randomR (-100,100)) trials (undefined:: CLLong)) checkBounds "CULLong R" (False,0,200) (approxBounds (randomR (0,200)) trials (undefined:: CULLong)) checkBounds "CIntPtr R" (False,-100,100) (approxBounds (randomR (-100,100)) trials (undefined:: CIntPtr)) From git at git.haskell.org Thu Mar 19 15:45:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:17 +0000 (UTC) Subject: [commit: packages/random] master: Add .travis.yml. (94791c8) Message-ID: <20150319154517.3D74D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/94791c817422c71020d2f3265742a265ac674130 >--------------------------------------------------------------- commit 94791c817422c71020d2f3265742a265ac674130 Author: Mikhail Glushenkov Date: Sat Aug 23 21:15:48 2014 +0200 Add .travis.yml. >--------------------------------------------------------------- 94791c817422c71020d2f3265742a265ac674130 .travis.yml | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/.travis.yml b/.travis.yml new file mode 100644 index 0000000..6a03bcb --- /dev/null +++ b/.travis.yml @@ -0,0 +1,5 @@ +language: haskell +ghc: + - 7.4 + - 7.6 + - 7.8 From git at git.haskell.org Thu Mar 19 15:45:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:19 +0000 (UTC) Subject: [commit: packages/random] master: Update .gitignore. (04692d0) Message-ID: <20150319154519.46FAC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/04692d0e2c8307a1de138cee8afa41e6f04a78e7 >--------------------------------------------------------------- commit 04692d0e2c8307a1de138cee8afa41e6f04a78e7 Author: Mikhail Glushenkov Date: Sat Aug 23 21:16:43 2014 +0200 Update .gitignore. >--------------------------------------------------------------- 04692d0e2c8307a1de138cee8afa41e6f04a78e7 .gitignore | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/.gitignore b/.gitignore index 29f4f08..41c6d8c 100644 --- a/.gitignore +++ b/.gitignore @@ -6,3 +6,7 @@ Thumbs.db GNUmakefile dist-install/ ghc.mk + +dist +.cabal-sandbox +cabal.sandbox.config From git at git.haskell.org Thu Mar 19 15:45:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:21 +0000 (UTC) Subject: [commit: packages/random] master: Add Travis icon. (7743967) Message-ID: <20150319154521.4C72E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/7743967bf243025e82c4e063895683f728181a75 >--------------------------------------------------------------- commit 7743967bf243025e82c4e063895683f728181a75 Author: Mikhail Glushenkov Date: Sat Aug 23 21:19:50 2014 +0200 Add Travis icon. >--------------------------------------------------------------- 7743967bf243025e82c4e063895683f728181a75 README.md | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/README.md b/README.md index 24669f7..9d5bb51 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,6 @@ - - The Haskell Standard Library -- Random Number Generation ======================================================== +[![Build Status](https://secure.travis-ci.org/haskell/random.svg?branch=master)](http://travis-ci.org/haskell/random) This library provides a basic interface for (splittable) random number generators. From git at git.haskell.org Thu Mar 19 15:45:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:23 +0000 (UTC) Subject: [commit: packages/random] master: Support base < 4.6 / GHC 7.4. (e6a0a92) Message-ID: <20150319154523.57DA53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/e6a0a92594d4c90cebc5806febd01d1c5ab23b18 >--------------------------------------------------------------- commit e6a0a92594d4c90cebc5806febd01d1c5ab23b18 Author: Mikhail Glushenkov Date: Sat Aug 23 20:55:31 2014 +0200 Support base < 4.6 / GHC 7.4. Fixes #10. >--------------------------------------------------------------- e6a0a92594d4c90cebc5806febd01d1c5ab23b18 System/Random.hs | 15 ++++++++++++++- 1 file changed, 14 insertions(+), 1 deletion(-) diff --git a/System/Random.hs b/System/Random.hs index 97e98a5..4efcad6 100644 --- a/System/Random.hs +++ b/System/Random.hs @@ -93,7 +93,11 @@ import Data.Ratio ( numerator, denominator ) #endif import Data.Char ( isSpace, chr, ord ) import System.IO.Unsafe ( unsafePerformIO ) -import Data.IORef +import Data.IORef ( IORef, atomicModifyIORef, newIORef, readIORef + , writeIORef ) +#if MIN_VERSION_base (4,6,0) +import Data.IORef ( atomicModifyIORef' ) +#endif import Numeric ( readDec ) #ifdef __GLASGOW_HASKELL__ @@ -105,6 +109,15 @@ build :: ((a -> [a] -> [a]) -> [a] -> [a]) -> [a] build g = g (:) [] #endif +#if !MIN_VERSION_base (4,6,0) +atomicModifyIORef' :: IORef a -> (a -> (a,b)) -> IO b +atomicModifyIORef' ref f = do + b <- atomicModifyIORef ref + (\x -> let (a, b) = f x + in (a, a `seq` b)) + b `seq` return b +#endif + -- The standard nhc98 implementation of Time.ClockTime does not match -- the extended one expected in this module, so we lash-up a quick -- replacement here. From git at git.haskell.org Thu Mar 19 15:45:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:25 +0000 (UTC) Subject: [commit: packages/random] master: Merge pull request #12 from 23Skidoo/unbreak-ghc-7.4 (ad4de49) Message-ID: <20150319154525.613B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/ad4de49833895cd07b3207d9dbfacb318e3bc652 >--------------------------------------------------------------- commit ad4de49833895cd07b3207d9dbfacb318e3bc652 Merge: 7743967 e6a0a92 Author: Edward Kmett Date: Mon Aug 25 11:25:49 2014 -0400 Merge pull request #12 from 23Skidoo/unbreak-ghc-7.4 Support base < 4.6 / GHC 7.4. >--------------------------------------------------------------- ad4de49833895cd07b3207d9dbfacb318e3bc652 System/Random.hs | 15 ++++++++++++++- 1 file changed, 14 insertions(+), 1 deletion(-) From git at git.haskell.org Thu Mar 19 15:45:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:27 +0000 (UTC) Subject: [commit: packages/random] master: prepping for the 1.1 fixup release (673ac33) Message-ID: <20150319154527.6CC6A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/673ac3336ed1bf7b3e4d27ed613d2f71dbc52703 >--------------------------------------------------------------- commit 673ac3336ed1bf7b3e4d27ed613d2f71dbc52703 Author: Carter Tazio Schonwald Date: Mon Sep 15 14:42:59 2014 -0400 prepping for the 1.1 fixup release 1) still need to merge in https://github.com/haskell/random/pull/9 2) should we force -O2 in the ghcoptions? (its currently set that way, but is that a good idea/needed here?) >--------------------------------------------------------------- 673ac3336ed1bf7b3e4d27ed613d2f71dbc52703 CHANGELOG.md | 24 ++++++++++++++++++++++++ CHANGELOG.txt | 4 ---- random.cabal | 10 +++++----- 3 files changed, 29 insertions(+), 9 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md new file mode 100644 index 0000000..6bcfe81 --- /dev/null +++ b/CHANGELOG.md @@ -0,0 +1,24 @@ +# 1.1 + * breaking change to `randomIValInteger` to improve RNG quality and performance + see https://github.com/haskell/random/pull/4 and + ghc https://ghc.haskell.org/trac/ghc/ticket/8898 + * correct documentation about generated range of Int32 sized values of type Int + https://github.com/haskell/random/pull/7 + * fix memory leaks by using strict fields and strict atomicModifyIORef' + https://github.com/haskell/random/pull/8 + * support for base < 4.6 (which doesnt provide strict atomicModifyIORef') + and integrating Travis CI support. + https://github.com/haskell/random/pull/12 + +# 1.0.1.1 +bump for overflow bug fixes + +# 1.0.1.2 +bump for ticket 8704, build fusion + +# 1.0.1.0 +bump for bug fixes, + +# 1.0.0.4 +bumped version for float/double range bugfix + diff --git a/CHANGELOG.txt b/CHANGELOG.txt deleted file mode 100644 index bb4f39a..0000000 --- a/CHANGELOG.txt +++ /dev/null @@ -1,4 +0,0 @@ - - -1.0.0.4 -- bumped version for float/double range bugfix - diff --git a/random.cabal b/random.cabal index c9a645a..72b182a 100644 --- a/random.cabal +++ b/random.cabal @@ -1,10 +1,8 @@ name: random -version: 1.0.1.3 +version: 1.1 + + --- 1.0.1.0 -- bump for bug fixes, but no SplittableGen yet --- 1.0.1.1 -- bump for overflow bug fixes --- 1.0.1.2 -- bump for ticket 8704, build fusion --- 1.0.1.3 -- bump for various bug fixes license: BSD3 license-file: LICENSE @@ -16,6 +14,8 @@ description: This package provides a basic random number generation library, including the ability to split random number generators. + + build-type: Simple -- cabal-version 1.8 needed because "the field 'build-depends: random' refers -- to a library which is defined within the same package" From git at git.haskell.org Thu Mar 19 15:45:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:29 +0000 (UTC) Subject: [commit: packages/random] master: Merge pull request #9 from bgamari/master (f2a3544) Message-ID: <20150319154529.735B83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/f2a3544b537f987ba7f2f311109b3f97a0281cfe >--------------------------------------------------------------- commit f2a3544b537f987ba7f2f311109b3f97a0281cfe Merge: ad4de49 3000397 Author: Edward Kmett Date: Mon Sep 15 14:53:25 2014 -0400 Merge pull request #9 from bgamari/master rangeTest: Fix type for "CSigAtomic R" test >--------------------------------------------------------------- f2a3544b537f987ba7f2f311109b3f97a0281cfe tests/rangeTest.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Thu Mar 19 15:45:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:31 +0000 (UTC) Subject: [commit: packages/random] master: Merge pull request #15 from cartazio/master (537599b) Message-ID: <20150319154531.7A4F23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/537599bcf9365da3b6b6554ffa4be145192f3d68 >--------------------------------------------------------------- commit 537599bcf9365da3b6b6554ffa4be145192f3d68 Merge: f2a3544 673ac33 Author: Edward Kmett Date: Mon Sep 15 15:50:07 2014 -0400 Merge pull request #15 from cartazio/master prepping for the 1.1 fixup release >--------------------------------------------------------------- 537599bcf9365da3b6b6554ffa4be145192f3d68 CHANGELOG.md | 24 ++++++++++++++++++++++++ CHANGELOG.txt | 4 ---- random.cabal | 10 +++++----- 3 files changed, 29 insertions(+), 9 deletions(-) From git at git.haskell.org Thu Mar 19 15:45:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:33 +0000 (UTC) Subject: [commit: packages/random] master: adding more changes to the change log (53f8c21) Message-ID: <20150319154533.863603A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/53f8c213da6e79c146319838d6efcb25f37d4240 >--------------------------------------------------------------- commit 53f8c213da6e79c146319838d6efcb25f37d4240 Author: Carter Tazio Schonwald Date: Mon Sep 15 17:46:04 2014 -0400 adding more changes to the change log >--------------------------------------------------------------- 53f8c213da6e79c146319838d6efcb25f37d4240 CHANGELOG.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/CHANGELOG.md b/CHANGELOG.md index 6bcfe81..15c882a 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -6,9 +6,11 @@ https://github.com/haskell/random/pull/7 * fix memory leaks by using strict fields and strict atomicModifyIORef' https://github.com/haskell/random/pull/8 + related to ghc trac tickets #7936 and #4218 * support for base < 4.6 (which doesnt provide strict atomicModifyIORef') and integrating Travis CI support. https://github.com/haskell/random/pull/12 + * fix C type in test suite https://github.com/haskell/random/pull/9 # 1.0.1.1 bump for overflow bug fixes From git at git.haskell.org Thu Mar 19 15:45:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:35 +0000 (UTC) Subject: [commit: packages/random] master: Merge pull request #16 from cartazio/master (4dfda2a) Message-ID: <20150319154535.8DD173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/4dfda2aa2ef1bcad33acfb9152d55847b76bbaa3 >--------------------------------------------------------------- commit 4dfda2aa2ef1bcad33acfb9152d55847b76bbaa3 Merge: 537599b 53f8c21 Author: Edward Kmett Date: Mon Sep 15 18:02:41 2014 -0400 Merge pull request #16 from cartazio/master adding more changes to the change log >--------------------------------------------------------------- 4dfda2aa2ef1bcad33acfb9152d55847b76bbaa3 CHANGELOG.md | 2 ++ 1 file changed, 2 insertions(+) From git at git.haskell.org Thu Mar 19 15:45:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:37 +0000 (UTC) Subject: [commit: packages/random] master: naive extra files bits (17462c1) Message-ID: <20150319154537.94CDA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/17462c14cb6a2c604bc0711daba2f05b9f587c9a >--------------------------------------------------------------- commit 17462c14cb6a2c604bc0711daba2f05b9f587c9a Author: Carter Tazio Schonwald Date: Mon Sep 15 21:53:10 2014 -0400 naive extra files bits >--------------------------------------------------------------- 17462c14cb6a2c604bc0711daba2f05b9f587c9a random.cabal | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/random.cabal b/random.cabal index 72b182a..ac00f60 100644 --- a/random.cabal +++ b/random.cabal @@ -15,6 +15,14 @@ description: library, including the ability to split random number generators. +extra-source-files: + .travis.yml + README.md + CHANGELOG.md + .gitignore + .darcs-boring + + build-type: Simple -- cabal-version 1.8 needed because "the field 'build-depends: random' refers From git at git.haskell.org Thu Mar 19 15:45:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:39 +0000 (UTC) Subject: [commit: packages/random] master: Hide empty when importing Control.Monad. (23f7d4e) Message-ID: <20150319154539.9B1443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/23f7d4e4c745a9c5d2769cccdc2025c6a66af1c7 >--------------------------------------------------------------- commit 23f7d4e4c745a9c5d2769cccdc2025c6a66af1c7 Author: Geoffrey Mainland Date: Tue Sep 16 11:56:31 2014 -0400 Hide empty when importing Control.Monad. This is need for compatibility with AMP since Control.Monad now exports empty. >--------------------------------------------------------------- 23f7d4e4c745a9c5d2769cccdc2025c6a66af1c7 tests/random1283.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/random1283.hs b/tests/random1283.hs index 2ad3530..33fc488 100644 --- a/tests/random1283.hs +++ b/tests/random1283.hs @@ -1,5 +1,5 @@ import Control.Concurrent -import Control.Monad +import Control.Monad hiding (empty) import Data.Sequence (ViewL(..), empty, fromList, viewl, (<|), (|>), (><)) import System.Random From git at git.haskell.org Thu Mar 19 15:45:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:41 +0000 (UTC) Subject: [commit: packages/random] master: Fix unused import warning. (7476569) Message-ID: <20150319154541.A4C6B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/74765698fc6e1ec50ae4bd986b796cc20081ce0b >--------------------------------------------------------------- commit 74765698fc6e1ec50ae4bd986b796cc20081ce0b Author: Geoffrey Mainland Date: Tue Sep 16 11:57:35 2014 -0400 Fix unused import warning. >--------------------------------------------------------------- 74765698fc6e1ec50ae4bd986b796cc20081ce0b System/Random.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/System/Random.hs b/System/Random.hs index 4efcad6..ab77274 100644 --- a/System/Random.hs +++ b/System/Random.hs @@ -93,10 +93,11 @@ import Data.Ratio ( numerator, denominator ) #endif import Data.Char ( isSpace, chr, ord ) import System.IO.Unsafe ( unsafePerformIO ) -import Data.IORef ( IORef, atomicModifyIORef, newIORef, readIORef - , writeIORef ) +import Data.IORef ( IORef, newIORef, readIORef, writeIORef ) #if MIN_VERSION_base (4,6,0) import Data.IORef ( atomicModifyIORef' ) +#else +import Data.IORef ( atomicModifyIORef ) #endif import Numeric ( readDec ) From git at git.haskell.org Thu Mar 19 15:45:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:43 +0000 (UTC) Subject: [commit: packages/random] master: Merge pull request #18 from cartazio/master (922855f) Message-ID: <20150319154543.ABCD03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/922855f9e97ca1f8406959ef7d4b4ad535bcc0a9 >--------------------------------------------------------------- commit 922855f9e97ca1f8406959ef7d4b4ad535bcc0a9 Merge: 4dfda2a 17462c1 Author: Edward Kmett Date: Tue Sep 16 16:25:35 2014 -0400 Merge pull request #18 from cartazio/master naive extra-files bits >--------------------------------------------------------------- 922855f9e97ca1f8406959ef7d4b4ad535bcc0a9 random.cabal | 8 ++++++++ 1 file changed, 8 insertions(+) From git at git.haskell.org Thu Mar 19 15:45:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:45 +0000 (UTC) Subject: [commit: packages/random] master: Merge pull request #19 from mainland/master (279163e) Message-ID: <20150319154545.B4C883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/279163ead86fb0bbaa7f33a4aa5176d8a9658543 >--------------------------------------------------------------- commit 279163ead86fb0bbaa7f33a4aa5176d8a9658543 Merge: 922855f 7476569 Author: Edward Kmett Date: Tue Sep 16 17:03:24 2014 -0400 Merge pull request #19 from mainland/master Fix compilation with GHC HEAD. >--------------------------------------------------------------- 279163ead86fb0bbaa7f33a4aa5176d8a9658543 System/Random.hs | 5 +++-- tests/random1283.hs | 2 +- 2 files changed, 4 insertions(+), 3 deletions(-) From git at git.haskell.org Thu Mar 19 15:45:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:47 +0000 (UTC) Subject: [commit: packages/random] master: set maintainer (cfdfe6f) Message-ID: <20150319154547.BE6323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random On branch : master Link : http://git.haskell.org/packages/random.git/commitdiff/cfdfe6f09ad414fde5b855cc5f90207533413241 >--------------------------------------------------------------- commit cfdfe6f09ad414fde5b855cc5f90207533413241 Author: Edward Kmett Date: Tue Sep 16 17:34:25 2014 -0400 set maintainer >--------------------------------------------------------------- cfdfe6f09ad414fde5b855cc5f90207533413241 random.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/random.cabal b/random.cabal index ac00f60..fd29840 100644 --- a/random.cabal +++ b/random.cabal @@ -6,7 +6,7 @@ version: 1.1 license: BSD3 license-file: LICENSE -maintainer: rrnewton at gmail.com +maintainer: core-libraries-committee at haskell.org bug-reports: https://github.com/haskell/random/issues synopsis: random number library category: System From git at git.haskell.org Thu Mar 19 15:45:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:45:50 +0000 (UTC) Subject: [commit: packages/random] master's head updated: set maintainer (cfdfe6f) Message-ID: <20150319154550.0D78E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random Branch 'master' now includes: 613224a Add .gitignore. 2117e38 rangeTest fails on Windows (#7379) 0531d37 Follow changes in the testsuite 4b68afd Add .gitignore b185c4e Updated link 180aa65 Update Git repo URL in `.cabal` file 9519072 Merge pull request #2 from pcapriotti/master c5e5af6 Merge pull request #3 from thapakrish/master 4695ffa Use GHC.Exts.build in randoms, randomRs to achieve fusion 42851d3 Merge branch 'master' of github.com:haskell/random a42da67 Version bump to go with prev 031a557 fix for randomIvalInteger, ghc #8898 dcb3972 Merge remote-tracking branch 'remotes/downstream/master' b1cb6e5 Merge pull request #4 from NovaDenizen/master fecc2d7 Update README + issue tracker link in cabal file 485cbf1 The lowest int generated by StdGen is 1. Fixes ghc #8899. a3a70df Cleanup + add comments bba3db1 Make TestRandomRs (GHC #4218) fast and add to cabal file 8a4dedd Use atomicModifyIORef' (strict) (GHC #4218) 9721b7c Use strict fields for StdGen (GHC #7936) 80df82a rangeTest: Fix signed-ness of types 8e379a7 Revert "rangeTest fails on Windows (#7379)" 5ee25dc Merge pull request #8 from thomie/memory-leaks 8570176 Merge pull request #7 from thomie/T8899 cc9372d Merge pull request #6 from thomie/master dedcb54 Merge pull request #5 from bgamari/master d05a606 Bump version for various bugfixes 3000397 rangeTest: Fix type for "CSigAtomic R" test 94791c8 Add .travis.yml. 04692d0 Update .gitignore. 7743967 Add Travis icon. e6a0a92 Support base < 4.6 / GHC 7.4. ad4de49 Merge pull request #12 from 23Skidoo/unbreak-ghc-7.4 673ac33 prepping for the 1.1 fixup release f2a3544 Merge pull request #9 from bgamari/master 537599b Merge pull request #15 from cartazio/master 53f8c21 adding more changes to the change log 4dfda2a Merge pull request #16 from cartazio/master 17462c1 naive extra files bits 23f7d4e Hide empty when importing Control.Monad. 7476569 Fix unused import warning. 922855f Merge pull request #18 from cartazio/master 279163e Merge pull request #19 from mainland/master cfdfe6f set maintainer From git at git.haskell.org Thu Mar 19 15:46:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:46:18 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update filepath/hpc/process submodules (72b114a) Message-ID: <20150319154618.E34E33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/72b114a537e581f4ce488b169b8d5a7a801dc090/ghc >--------------------------------------------------------------- commit 72b114a537e581f4ce488b169b8d5a7a801dc090 Author: Herbert Valerio Riedel Date: Thu Mar 19 16:44:51 2015 +0100 Update filepath/hpc/process submodules These updates these 3 submodules to their respective released tagged commits. No source-code changes are involved with this update. >--------------------------------------------------------------- 72b114a537e581f4ce488b169b8d5a7a801dc090 libraries/filepath | 2 +- libraries/hpc | 2 +- libraries/process | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/filepath b/libraries/filepath index 4206435..81375ae 160000 --- a/libraries/filepath +++ b/libraries/filepath @@ -1 +1 @@ -Subproject commit 4206435bda0929d7a65fc42e5c8629212328120c +Subproject commit 81375ae0c892b5951f2c1184c655a8f3a5193c9c diff --git a/libraries/hpc b/libraries/hpc index f601495..154eecf 160000 --- a/libraries/hpc +++ b/libraries/hpc @@ -1 +1 @@ -Subproject commit f601495ac5f93f24cbcaa95f45b1bc26ad644ac9 +Subproject commit 154eecf3ca10f9252bf75213d091221ee3c551d6 diff --git a/libraries/process b/libraries/process index c8cdaef..67efaf5 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit c8cdaef5585717089a53be61cb6f08b3120f18b4 +Subproject commit 67efaf599a03f454a98a3905820ce40aa80825c7 From git at git.haskell.org Thu Mar 19 15:49:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:25 +0000 (UTC) Subject: [commit: packages/unix] branch 'safe710fixes' created Message-ID: <20150319154925.25DCA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix New branch : safe710fixes Referencing: 1eda33a96c513f7957f082798a97c291a36cc2d6 From git at git.haskell.org Thu Mar 19 15:49:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:27 +0000 (UTC) Subject: [commit: packages/unix] branch 'safefixes710again' created Message-ID: <20150319154927.252223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix New branch : safefixes710again Referencing: e0bc46b891608f7e50223443d03a849fd16ac84d From git at git.haskell.org Thu Mar 19 15:49:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:29 +0000 (UTC) Subject: [commit: packages/unix] branch 'safe710fixes-again' created Message-ID: <20150319154929.25B173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix New branch : safe710fixes-again Referencing: eafa4372bd0d9fc61e15f7c587bf495a4f277b7e From git at git.haskell.org Thu Mar 19 15:49:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:31 +0000 (UTC) Subject: [commit: packages/unix] tag 'v2.7.1.0' created Message-ID: <20150319154931.275CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix New tag : v2.7.1.0 Referencing: 280ff4ebb80ede715929b1b691c8eddec4de2b13 From git at git.haskell.org Thu Mar 19 15:49:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:33 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Enable test for getLoginName (cad1ef2) Message-ID: <20150319154933.321023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/cad1ef27bb0a51bc68ebadb1297de1ae05bee9db/unix >--------------------------------------------------------------- commit cad1ef27bb0a51bc68ebadb1297de1ae05bee9db Author: Thomas Miedema Date: Thu Jun 26 23:23:15 2014 +0200 Enable test for getLoginName Fixes #1487. Make use of no_stdin test option, introduced explictly for this purpose in fa52a8c9d8eae5e3fc4c0cf0e5672875e161e05c >--------------------------------------------------------------- cad1ef27bb0a51bc68ebadb1297de1ae05bee9db tests/all.T | 14 +++++++++++++- tests/user001.hs | 4 ++-- tests/user001.stdout | 2 ++ 3 files changed, 17 insertions(+), 3 deletions(-) diff --git a/tests/all.T b/tests/all.T index 6b9fa15..b6bd433 100644 --- a/tests/all.T +++ b/tests/all.T @@ -11,7 +11,19 @@ test('forkprocess01', [ only_compiler_types(['ghc']), # user001 may fail due to this bug in glibc: # http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=466647 # -test('user001', normal, compile_and_run, ['-package unix']) +# user001 may also fail on GNU/Linux when using a terminal emulator that doesn't +# write login records to /var/run/utmp. Running: +# $ logname +# should print your login name. If it doesn't, the getLoginName test in user001 +# will fail, and that's why you are here. Try xterm. +# +# Ticket #1487. The glibc implementation of getlogin, which is called by +# getLoginName, requires that a terminal is connected to filedescriptor 0. +# See: https://sourceware.org/git/?p=glibc.git;a=blob;f=sysdeps/unix/getlogin.c +# Therefore, we use the no_stdin option, and have to omit the 'ghci' way, +# because it relies on redirecting stdin from file. +# +test('user001', [no_stdin, omit_ways(['ghci'])], compile_and_run, ['-package unix']) test('resourceLimit', normal, compile_and_run, ['-package unix']) x86FreeBsdFail = when(platform('i386-unknown-freebsd'), expect_fail) diff --git a/tests/user001.hs b/tests/user001.hs index ebbb464..f4c44fc 100644 --- a/tests/user001.hs +++ b/tests/user001.hs @@ -17,11 +17,11 @@ main = do p "getRealUserID" $ getRealUserID p "getEffectiveUserID" $ getEffectiveUserID p "getEffectiveGroupID" $ getEffectiveGroupID p "getGroups" $ getGroups - -- p "getLoginName" $ getLoginName + p "getLoginName" $ getLoginName p "getEffectiveUserName" $ getEffectiveUserName p "getGroupEntryForID" $ getRealGroupID >>= getGroupEntryForID p "getGroupEntryForName" $ getRealGroupID >>= getGroupEntryForID >>= getGroupEntryForName . groupName p "getAllGroupEntries" $ getAllGroupEntries p "getUserEntryForID" $ getRealUserID >>= getUserEntryForID - -- p "getUserEntryForName" $ getLoginName >>= getUserEntryForName + p "getUserEntryForName" $ getLoginName >>= getUserEntryForName p "getAllUserEntries" $ getAllUserEntries diff --git a/tests/user001.stdout b/tests/user001.stdout index e2e03df..48c0cfd 100644 --- a/tests/user001.stdout +++ b/tests/user001.stdout @@ -3,9 +3,11 @@ getRealGroupID: OK getEffectiveUserID: OK getEffectiveGroupID: OK getGroups: OK +getLoginName: OK getEffectiveUserName: OK getGroupEntryForID: OK getGroupEntryForName: OK getAllGroupEntries: OK getUserEntryForID: OK +getUserEntryForName: OK getAllUserEntries: OK From git at git.haskell.org Thu Mar 19 15:49:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:35 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Remove unnecessary checks for RTLD_NOW and RTLD_GLOBAL (827e675) Message-ID: <20150319154935.388FD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/827e67570db8cdcb0af8a2108c562b7b51fbf244/unix >--------------------------------------------------------------- commit 827e67570db8cdcb0af8a2108c562b7b51fbf244 Author: Thomas Miedema Date: Fri Jul 4 17:23:58 2014 +0200 Remove unnecessary checks for RTLD_NOW and RTLD_GLOBAL These checks were introduced for OpenBSD on July 16 2002 in GHC commit 03e9edb3094fd3bb38ed886b96ee9f61f39e9b53. According to http://www.openbsd.org/cgi-bin/cvsweb/src/include/dlfcn.h RTLD_NOW, RTLD_GLOBAL and RTLD_LOCAL have been available on OpenBSD since Revision 1.8 (September 2 2003). This is merely code cleanup. >--------------------------------------------------------------- 827e67570db8cdcb0af8a2108c562b7b51fbf244 System/Posix/DynamicLinker/Prim.hsc | 10 ---------- configure.ac | 32 +------------------------------- 2 files changed, 1 insertion(+), 41 deletions(-) diff --git a/System/Posix/DynamicLinker/Prim.hsc b/System/Posix/DynamicLinker/Prim.hsc index 2fe67b4..646e4fe 100644 --- a/System/Posix/DynamicLinker/Prim.hsc +++ b/System/Posix/DynamicLinker/Prim.hsc @@ -96,18 +96,8 @@ packRTLDFlags flags = foldl (\ s f -> (packRTLDFlag f) .|. s) 0 flags packRTLDFlag :: RTLDFlags -> CInt packRTLDFlag RTLD_LAZY = #const RTLD_LAZY - -#ifdef HAVE_RTLDNOW packRTLDFlag RTLD_NOW = #const RTLD_NOW -#else /* HAVE_RTLDNOW */ -packRTLDFlag RTLD_NOW = error "RTLD_NOW not available" -#endif /* HAVE_RTLDNOW */ - -#ifdef HAVE_RTLDGLOBAL packRTLDFlag RTLD_GLOBAL = #const RTLD_GLOBAL -#else /* HAVE_RTLDGLOBAL */ -packRTLDFlag RTLD_GLOBAL = error "RTLD_GLOBAL not available" -#endif #ifdef HAVE_RTLDLOCAL packRTLDFlag RTLD_LOCAL = #const RTLD_LOCAL diff --git a/configure.ac b/configure.ac index 57b7cf7..ccb627b 100644 --- a/configure.ac +++ b/configure.ac @@ -155,7 +155,7 @@ AC_EGREP_CPP(yes, AC_MSG_RESULT(no) ]) -dnl ** RTLD_LOCAL isn't available on cygwin or openbsd +dnl ** RTLD_LOCAL isn't available on cygwin AC_MSG_CHECKING(for RTLD_LOCAL from dlfcn.h) AC_EGREP_CPP(yes, [ @@ -170,36 +170,6 @@ AC_EGREP_CPP(yes, AC_MSG_RESULT(no) ]) -dnl ** RTLD_GLOBAL isn't available on openbsd -AC_MSG_CHECKING(for RTLD_GLOBAL from dlfcn.h) -AC_EGREP_CPP(yes, -[ - #include - #ifdef RTLD_GLOBAL - yes - #endif -], [ - AC_MSG_RESULT(yes) - AC_DEFINE([HAVE_RTLDGLOBAL], [1], [Define to 1 if RTLD_GLOBAL is available.]) -], [ - AC_MSG_RESULT(no) - ]) - -dnl ** RTLD_NOW isn't available on openbsd -AC_MSG_CHECKING(for RTLD_NOW from dlfcn.h) -AC_EGREP_CPP(yes, -[ - #include - #ifdef RTLD_NOW - yes - #endif -], [ - AC_MSG_RESULT(yes) - AC_DEFINE([HAVE_RTLDNOW], [1], [Define to 1 if we can see RTLD_NOW in dlfcn.h]) -], [ - AC_MSG_RESULT(no) - ]) - AC_CHECK_FUNCS(openpty,, AC_CHECK_LIB(util,openpty, [AC_DEFINE(HAVE_OPENPTY) EXTRA_LIBS="$EXTRA_LIBS util"], From git at git.haskell.org Thu Mar 19 15:49:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:37 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Add haddock comments on RTLD_NEXT and RTLD_DEFAULT (4c32cd4) Message-ID: <20150319154937.3F8E63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/4c32cd4444270c94249f0f161951c4e9465e7c3e/unix >--------------------------------------------------------------- commit 4c32cd4444270c94249f0f161951c4e9465e7c3e Author: Thomas Miedema Date: Fri Jul 4 16:42:21 2014 +0200 Add haddock comments on RTLD_NEXT and RTLD_DEFAULT Related ticket: #8902. >--------------------------------------------------------------- 4c32cd4444270c94249f0f161951c4e9465e7c3e System/Posix/DynamicLinker/Prim.hsc | 37 ++++++++++++++++++++++++------------- configure.ac | 5 +++-- 2 files changed, 27 insertions(+), 15 deletions(-) diff --git a/System/Posix/DynamicLinker/Prim.hsc b/System/Posix/DynamicLinker/Prim.hsc index a111e3a..2fe67b4 100644 --- a/System/Posix/DynamicLinker/Prim.hsc +++ b/System/Posix/DynamicLinker/Prim.hsc @@ -41,25 +41,25 @@ import Foreign.Ptr ( Ptr, FunPtr, nullPtr ) import Foreign.C.Types import Foreign.C.String ( CString ) --- RTLD_NEXT madness --- On some host (e.g. SuSe Linux 7.2) RTLD_NEXT is not visible --- without setting _GNU_SOURCE. Since we don't want to set this --- flag, here's a different solution: You can use the Haskell --- function 'haveRtldNext' to check wether the flag is available --- to you. Ideally, this will be optimized by the compiler so --- that it should be as efficient as an #ifdef. --- If you fail to test the flag and use it although it is --- undefined, 'packOneModuleFlag' will bomb. --- The same applies to RTLD_LOCAL which isn't available on + +-- |On some hosts (e.g. SuSe and Ubuntu Linux) 'RTLD_NEXT' (and +-- 'RTLD_DEFAULT') are not visible without setting the macro +-- '_GNU_SOURCE'. Since we don't want to define this macro, you can use +-- the function 'haveRtldNext' to check wether the flag `Next` is +-- available. Ideally, this will be optimized by the compiler so that it +-- should be as efficient as an #ifdef. +-- +-- If you fail to test the flag and use it although it is undefined, +-- 'packDL' will throw an error. +-- +-- The same applies to RTLD_LOCAL which isn't available on -- cygwin. haveRtldNext :: Bool #ifdef HAVE_RTLDNEXT haveRtldNext = True - foreign import ccall unsafe "__hsunix_rtldNext" rtldNext :: Ptr a - #else /* HAVE_RTLDNEXT */ haveRtldNext = False #endif /* HAVE_RTLDNEXT */ @@ -76,6 +76,9 @@ haveRtldLocal = True haveRtldLocal = False #endif /* HAVE_RTLDLOCAL */ + +-- |Flags for 'System.Posix.DynamicLinker.dlopen'. + data RTLDFlags = RTLD_LAZY | RTLD_NOW @@ -112,21 +115,29 @@ packRTLDFlag RTLD_LOCAL = #const RTLD_LOCAL packRTLDFlag RTLD_LOCAL = error "RTLD_LOCAL not available" #endif /* HAVE_RTLDLOCAL */ + -- |Flags for 'System.Posix.DynamicLinker.dlsym'. Notice that 'Next' --- might not be available on your particular platform! +-- might not be available on your particular platform! Use +-- `haveRtldNext`. +-- +-- If 'RTLD_DEFAULT' is not defined on your platform, `packDL` `Default` +-- reduces to 'nullPtr'. data DL = Null | Next | Default | DLHandle (Ptr ()) deriving (Show) packDL :: DL -> Ptr () packDL Null = nullPtr + #ifdef HAVE_RTLDNEXT packDL Next = rtldNext #else packDL Next = error "RTLD_NEXT not available" #endif + #ifdef HAVE_RTLDDEFAULT packDL Default = rtldDefault #else packDL Default = nullPtr #endif + packDL (DLHandle h) = h diff --git a/configure.ac b/configure.ac index f295061..57b7cf7 100644 --- a/configure.ac +++ b/configure.ac @@ -124,7 +124,9 @@ case "$fptools_cv_func_unsetenv_return_type" in ;; esac -dnl ** sometimes RTLD_NEXT is hidden in #ifdefs we really don't wan to set +dnl On some hosts (e.g. SuSe and Ubuntu Linux) RTLD_NEXT and RTLD_DEFAULT are +dnl not visible without setting _GNU_SOURCE, which we really don't want to. +dnl Also see comments in System/Posix/DynamicLinker/Prim.hsc. AC_MSG_CHECKING(for RTLD_NEXT from dlfcn.h) AC_EGREP_CPP(yes, [ @@ -139,7 +141,6 @@ AC_EGREP_CPP(yes, AC_MSG_RESULT(no) ]) -dnl ** RTLD_DEFAULT isn't available on cygwin AC_MSG_CHECKING(for RTLD_DEFAULT from dlfcn.h) AC_EGREP_CPP(yes, [ From git at git.haskell.org Thu Mar 19 15:49:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:39 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Deprecate function `haveRtldLocal` (5e72506) Message-ID: <20150319154939.4787B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/5e7250642bfbef066daf8fe7336f0f09bea030b3/unix >--------------------------------------------------------------- commit 5e7250642bfbef066daf8fe7336f0f09bea030b3 Author: Thomas Miedema Date: Fri Jul 4 17:53:07 2014 +0200 Deprecate function `haveRtldLocal` The function haveRtldLocal was introduced for compatibility with Cygwin on Mar 28 2002 in GHC commit 4740cf56c774b92e02d31b4666158d70c2e85a8f. According to https://cygwin.com/viewvc/src/winsup/cygwin/include/dlfcn.h RTLD_LOCAL has been available on Cygwin since Revision 1.4 (August 9 2010). >--------------------------------------------------------------- 5e7250642bfbef066daf8fe7336f0f09bea030b3 System/Posix/DynamicLinker/Prim.hsc | 14 +------------- configure.ac | 15 --------------- 2 files changed, 1 insertion(+), 28 deletions(-) diff --git a/System/Posix/DynamicLinker/Prim.hsc b/System/Posix/DynamicLinker/Prim.hsc index 646e4fe..0bef60b 100644 --- a/System/Posix/DynamicLinker/Prim.hsc +++ b/System/Posix/DynamicLinker/Prim.hsc @@ -51,9 +51,6 @@ import Foreign.C.String ( CString ) -- -- If you fail to test the flag and use it although it is undefined, -- 'packDL' will throw an error. --- --- The same applies to RTLD_LOCAL which isn't available on --- cygwin. haveRtldNext :: Bool @@ -69,12 +66,8 @@ foreign import ccall unsafe "__hsunix_rtldDefault" rtldDefault :: Ptr a #endif /* HAVE_RTLDDEFAULT */ haveRtldLocal :: Bool - -#ifdef HAVE_RTLDLOCAL haveRtldLocal = True -#else /* HAVE_RTLDLOCAL */ -haveRtldLocal = False -#endif /* HAVE_RTLDLOCAL */ +{-# DEPRECATED haveRtldLocal "defaults to True" #-} -- |Flags for 'System.Posix.DynamicLinker.dlopen'. @@ -98,12 +91,7 @@ packRTLDFlag :: RTLDFlags -> CInt packRTLDFlag RTLD_LAZY = #const RTLD_LAZY packRTLDFlag RTLD_NOW = #const RTLD_NOW packRTLDFlag RTLD_GLOBAL = #const RTLD_GLOBAL - -#ifdef HAVE_RTLDLOCAL packRTLDFlag RTLD_LOCAL = #const RTLD_LOCAL -#else /* HAVE_RTLDLOCAL */ -packRTLDFlag RTLD_LOCAL = error "RTLD_LOCAL not available" -#endif /* HAVE_RTLDLOCAL */ -- |Flags for 'System.Posix.DynamicLinker.dlsym'. Notice that 'Next' diff --git a/configure.ac b/configure.ac index ccb627b..41274dc 100644 --- a/configure.ac +++ b/configure.ac @@ -155,21 +155,6 @@ AC_EGREP_CPP(yes, AC_MSG_RESULT(no) ]) -dnl ** RTLD_LOCAL isn't available on cygwin -AC_MSG_CHECKING(for RTLD_LOCAL from dlfcn.h) -AC_EGREP_CPP(yes, -[ - #include - #ifdef RTLD_LOCAL - yes - #endif -], [ - AC_MSG_RESULT(yes) - AC_DEFINE([HAVE_RTLDLOCAL], [1], [Define to 1 if RTLD_LOCAL is available.]) -], [ - AC_MSG_RESULT(no) - ]) - AC_CHECK_FUNCS(openpty,, AC_CHECK_LIB(util,openpty, [AC_DEFINE(HAVE_OPENPTY) EXTRA_LIBS="$EXTRA_LIBS util"], From git at git.haskell.org Thu Mar 19 15:49:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:41 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Merge pull request #2 from thomie/T8902 (c566040) Message-ID: <20150319154941.506993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/c566040bf3a31bc83e7ecc29d819e058d6077625/unix >--------------------------------------------------------------- commit c566040bf3a31bc83e7ecc29d819e058d6077625 Merge: 54fbbde 5e72506 Author: Bryan O'Sullivan Date: Fri Jul 11 16:39:07 2014 +0100 Merge pull request #2 from thomie/T8902 Add haddock comments on RTLD_NEXT and RTLD_DEFAULT >--------------------------------------------------------------- c566040bf3a31bc83e7ecc29d819e058d6077625 System/Posix/DynamicLinker/Prim.hsc | 57 +++++++++++++++---------------------- configure.ac | 50 ++------------------------------ 2 files changed, 26 insertions(+), 81 deletions(-) From git at git.haskell.org Thu Mar 19 15:49:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:43 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Merge pull request #1 from thomie/master (30248d7) Message-ID: <20150319154943.5A40B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/30248d77d87ac7ec69b71cb3075d3ec64fa389fa/unix >--------------------------------------------------------------- commit 30248d77d87ac7ec69b71cb3075d3ec64fa389fa Merge: c566040 cad1ef2 Author: Gregory Collins Date: Tue Jul 15 13:16:07 2014 +0200 Merge pull request #1 from thomie/master Enable test for getLoginName (Fixes #1487) >--------------------------------------------------------------- 30248d77d87ac7ec69b71cb3075d3ec64fa389fa tests/all.T | 14 +++++++++++++- tests/user001.hs | 4 ++-- tests/user001.stdout | 2 ++ 3 files changed, 17 insertions(+), 3 deletions(-) From git at git.haskell.org Thu Mar 19 15:49:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:45 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Ignore test output created by GHC test suite. (fa1a859) Message-ID: <20150319154945.610BE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/fa1a859ee40bdeadb5144c910e57225d71d1dddf/unix >--------------------------------------------------------------- commit fa1a859ee40bdeadb5144c910e57225d71d1dddf Author: Edward Z. Yang Date: Fri Aug 22 14:20:06 2014 +0100 Ignore test output created by GHC test suite. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- fa1a859ee40bdeadb5144c910e57225d71d1dddf .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index 6023241..b67c37a 100644 --- a/.gitignore +++ b/.gitignore @@ -15,4 +15,5 @@ tests/*.eventlog tests/*.genscript tests/*.o tests/*.hi +tests/*.normalised *~ From git at git.haskell.org Thu Mar 19 15:49:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:47 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Merge pull request #10 from ezyang/ezyang-dev (6378c16) Message-ID: <20150319154947.682FD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/6378c16a4f830141149f804cda2948b190d8a93a/unix >--------------------------------------------------------------- commit 6378c16a4f830141149f804cda2948b190d8a93a Merge: 30248d7 fa1a859 Author: Herbert Valerio Riedel Date: Sat Aug 23 00:05:29 2014 +0200 Merge pull request #10 from ezyang/ezyang-dev Ignore test output created by GHC test suite. >--------------------------------------------------------------- 6378c16a4f830141149f804cda2948b190d8a93a .gitignore | 1 + 1 file changed, 1 insertion(+) From git at git.haskell.org Thu Mar 19 15:49:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:49 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Bump `base` constraint for AMP (8afe57f) Message-ID: <20150319154949.705EB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/8afe57ff808499584f43a5cfeb1a3bb42602df8b/unix >--------------------------------------------------------------- commit 8afe57ff808499584f43a5cfeb1a3bb42602df8b Author: Herbert Valerio Riedel Date: Tue Sep 9 17:32:01 2014 +0200 Bump `base` constraint for AMP >--------------------------------------------------------------- 8afe57ff808499584f43a5cfeb1a3bb42602df8b changelog.md | 8 ++++++++ unix.cabal | 4 ++-- 2 files changed, 10 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md index 9d587ab..4440892 100644 --- a/changelog.md +++ b/changelog.md @@ -1,3 +1,11 @@ +# Changelog for [`unix` package](http://hackage.haskell.org/package/unix) + +## 2.7.0.2 *TBA* + + * Add support for `base-4.8.0.0` + * Add haddock comments on `RTLD_NEXT` and `RTLD_DEFAULT` + * Deprecate function `haveRtldLocal` + ## 2.7.0.1 *Mar 2014* * Bundled with GHC 7.8.1 diff --git a/unix.cabal b/unix.cabal index 8d0b16f..61de701 100644 --- a/unix.cabal +++ b/unix.cabal @@ -1,6 +1,6 @@ name: unix version: 2.7.0.2 --- GHC 7.8.2 released with 2.7.0.1 +-- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE maintainer: libraries at haskell.org @@ -58,7 +58,7 @@ library Trustworthy build-depends: - base >= 4.5 && < 4.8, + base >= 4.5 && < 4.9, bytestring >= 0.9.2 && < 0.11, time >= 1.2 && < 1.5 From git at git.haskell.org Thu Mar 19 15:49:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:51 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: fix getGroupEntryForID/Name on Solaris (3c28bc8) Message-ID: <20150319154951.782283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/3c28bc83695cb5351d24920dac655b944a8abfba/unix >--------------------------------------------------------------- commit 3c28bc83695cb5351d24920dac655b944a8abfba Author: Karel Gardas Date: Mon Sep 8 20:17:47 2014 +0200 fix getGroupEntryForID/Name on Solaris This patch fixes getGroupEntryForID and getGroupEntryForName on Solaris The issue on Solaris is that it defines both required getgrgid_r and getgrnam_r functions as CPP macros which depending on configuration are mapped to real function implementations with different names. The issue is solved by using C API calling convention instead of platform C ABI calling convention. >--------------------------------------------------------------- 3c28bc83695cb5351d24920dac655b944a8abfba System/Posix/User.hsc | 6 +++--- changelog.md | 6 ++++++ 2 files changed, 9 insertions(+), 3 deletions(-) diff --git a/System/Posix/User.hsc b/System/Posix/User.hsc index ff7268f..50c9f41 100644 --- a/System/Posix/User.hsc +++ b/System/Posix/User.hsc @@ -1,5 +1,5 @@ #ifdef __GLASGOW_HASKELL__ -{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE Trustworthy, CApiFFI #-} #endif ----------------------------------------------------------------------------- -- | @@ -207,7 +207,7 @@ getGroupEntryForID gid = doubleAllocWhileERANGE "getGroupEntryForID" "group" grBufSize unpackGroupEntry $ c_getgrgid_r gid pgr -foreign import ccall unsafe "getgrgid_r" +foreign import capi unsafe "HsUnix.h getgrgid_r" c_getgrgid_r :: CGid -> Ptr CGroup -> CString -> CSize -> Ptr (Ptr CGroup) -> IO CInt #else @@ -226,7 +226,7 @@ getGroupEntryForName name = doubleAllocWhileERANGE "getGroupEntryForName" "group" grBufSize unpackGroupEntry $ c_getgrnam_r pstr pgr -foreign import ccall unsafe "getgrnam_r" +foreign import capi unsafe "HsUnix.h getgrnam_r" c_getgrnam_r :: CString -> Ptr CGroup -> CString -> CSize -> Ptr (Ptr CGroup) -> IO CInt #else diff --git a/changelog.md b/changelog.md index 9d587ab..e8632e2 100644 --- a/changelog.md +++ b/changelog.md @@ -1,3 +1,9 @@ + + * Fix `getGroupEntryForID/getGroupEntryForName' on Solaris. Solaris uses + CPP macros for required getgrgid_r and getgrnam_r functions definition + so the fix is to change from C ABI calling convention to C API calling + convention + ## 2.7.0.1 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 15:49:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:53 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Merge branch 'sol-fix-getgrgid_r-v3' of https://github.com/kgardas/unix into kgardas-sol-fix-getgrgid_r-v3 (b8e314a) Message-ID: <20150319154953.7FC1E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/b8e314a7f1304ebb4a80795b015f85e676b3e2bd/unix >--------------------------------------------------------------- commit b8e314a7f1304ebb4a80795b015f85e676b3e2bd Merge: 8afe57f 3c28bc8 Author: Herbert Valerio Riedel Date: Wed Sep 10 11:34:44 2014 +0200 Merge branch 'sol-fix-getgrgid_r-v3' of https://github.com/kgardas/unix into kgardas-sol-fix-getgrgid_r-v3 Conflicts: changelog.md >--------------------------------------------------------------- b8e314a7f1304ebb4a80795b015f85e676b3e2bd System/Posix/User.hsc | 6 +++--- changelog.md | 4 ++++ 2 files changed, 7 insertions(+), 3 deletions(-) diff --cc changelog.md index 4440892,e8632e2..ae5b726 --- a/changelog.md +++ b/changelog.md @@@ -1,10 -1,8 +1,14 @@@ +# Changelog for [`unix` package](http://hackage.haskell.org/package/unix) +## 2.7.0.2 *TBA* + + * Add support for `base-4.8.0.0` + * Add haddock comments on `RTLD_NEXT` and `RTLD_DEFAULT` + * Deprecate function `haveRtldLocal` + * Fix `getGroupEntryForID/getGroupEntryForName' on Solaris. Solaris uses + CPP macros for required getgrgid_r and getgrnam_r functions definition + so the fix is to change from C ABI calling convention to C API calling + convention ## 2.7.0.1 *Mar 2014* From git at git.haskell.org Thu Mar 19 15:49:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:55 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Relax upper bound to allow `time-1.5` (b2c8ae1) Message-ID: <20150319154955.883BE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/b2c8ae1cf231745c928fe51029d391681c1f0c20/unix >--------------------------------------------------------------- commit b2c8ae1cf231745c928fe51029d391681c1f0c20 Author: Herbert Valerio Riedel Date: Wed Sep 10 22:51:21 2014 +0200 Relax upper bound to allow `time-1.5` >--------------------------------------------------------------- b2c8ae1cf231745c928fe51029d391681c1f0c20 unix.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/unix.cabal b/unix.cabal index 61de701..ddd95de 100644 --- a/unix.cabal +++ b/unix.cabal @@ -60,7 +60,7 @@ library build-depends: base >= 4.5 && < 4.9, bytestring >= 0.9.2 && < 0.11, - time >= 1.2 && < 1.5 + time >= 1.2 && < 1.6 exposed-modules: System.Posix From git at git.haskell.org Thu Mar 19 15:49:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:57 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Use import list for `Data.Time.Clock.POSIX` (e865808) Message-ID: <20150319154957.91C923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/e865808ba41798889ea12b1bc056ef1c87f3f2e1/unix >--------------------------------------------------------------- commit e865808ba41798889ea12b1bc056ef1c87f3f2e1 Author: Herbert Valerio Riedel Date: Wed Sep 10 22:48:39 2014 +0200 Use import list for `Data.Time.Clock.POSIX` This makes it more obvious why `unix` depends on `time` in the first place, i.e. for the sole purpose of reusing the `POSIXTime` type. >--------------------------------------------------------------- e865808ba41798889ea12b1bc056ef1c87f3f2e1 System/Posix/Files.hsc | 2 +- System/Posix/Files/ByteString.hsc | 2 +- System/Posix/Files/Common.hsc | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/System/Posix/Files.hsc b/System/Posix/Files.hsc index a54443a..c8b5ddf 100644 --- a/System/Posix/Files.hsc +++ b/System/Posix/Files.hsc @@ -99,7 +99,7 @@ import System.Posix.Files.Common import System.Posix.Error import System.Posix.Internals -import Data.Time.Clock.POSIX +import Data.Time.Clock.POSIX (POSIXTime) -- ----------------------------------------------------------------------------- -- chmod() diff --git a/System/Posix/Files/ByteString.hsc b/System/Posix/Files/ByteString.hsc index 4f8a05f..80f0bea 100644 --- a/System/Posix/Files/ByteString.hsc +++ b/System/Posix/Files/ByteString.hsc @@ -104,7 +104,7 @@ import Foreign.C hiding ( import System.Posix.Files.Common import System.Posix.ByteString.FilePath -import Data.Time.Clock.POSIX +import Data.Time.Clock.POSIX (POSIXTime) -- ----------------------------------------------------------------------------- -- chmod() diff --git a/System/Posix/Files/Common.hsc b/System/Posix/Files/Common.hsc index 3056014..62fff6b 100644 --- a/System/Posix/Files/Common.hsc +++ b/System/Posix/Files/Common.hsc @@ -92,7 +92,7 @@ import Data.Bits import Data.Int import Data.Ratio #endif -import Data.Time.Clock.POSIX +import Data.Time.Clock.POSIX (POSIXTime) import System.Posix.Internals import Foreign.C import Foreign.ForeignPtr From git at git.haskell.org Thu Mar 19 15:49:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:49:59 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Update config.{guess, sub} to GNU automake 1.14.1 (832ac1d) Message-ID: <20150319154959.9ADD33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/832ac1d654762876c811ca5fd7e04c01badaa754/unix >--------------------------------------------------------------- commit 832ac1d654762876c811ca5fd7e04c01badaa754 Author: Herbert Valerio Riedel Date: Tue Sep 16 12:05:40 2014 +0200 Update config.{guess,sub} to GNU automake 1.14.1 >--------------------------------------------------------------- 832ac1d654762876c811ca5fd7e04c01badaa754 config.guess | 192 +++++++++-------------------------------------------------- config.sub | 23 +++---- 2 files changed, 40 insertions(+), 175 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 832ac1d654762876c811ca5fd7e04c01badaa754 From git at git.haskell.org Thu Mar 19 15:50:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:01 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Unify whitespace in System/Posix/Files/ByteString (03cc926) Message-ID: <20150319155001.A31913A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/03cc92646d3b2c49b850de0952aeaaf1ef863d7d/unix >--------------------------------------------------------------- commit 03cc92646d3b2c49b850de0952aeaaf1ef863d7d Author: Clemens Lang Date: Sun Sep 21 17:45:01 2014 +0200 Unify whitespace in System/Posix/Files/ByteString >--------------------------------------------------------------- 03cc92646d3b2c49b850de0952aeaaf1ef863d7d System/Posix/Files/ByteString.hsc | 24 ++++++++++++------------ 1 file changed, 12 insertions(+), 12 deletions(-) diff --git a/System/Posix/Files/ByteString.hsc b/System/Posix/Files/ByteString.hsc index 80f0bea..9430779 100644 --- a/System/Posix/Files/ByteString.hsc +++ b/System/Posix/Files/ByteString.hsc @@ -145,22 +145,22 @@ fileExist name = withFilePath name $ \s -> do r <- c_access s (#const F_OK) if (r == 0) - then return True - else do err <- getErrno - if (err == eNOENT) - then return False - else throwErrnoPath "fileExist" name + then return True + else do err <- getErrno + if (err == eNOENT) + then return False + else throwErrnoPath "fileExist" name access :: RawFilePath -> CMode -> IO Bool access name flags = withFilePath name $ \s -> do r <- c_access s (fromIntegral flags) if (r == 0) - then return True - else do err <- getErrno - if (err == eACCES) - then return False - else throwErrnoPath "fileAccess" name + then return True + else do err <- getErrno + if (err == eACCES) + then return False + else throwErrnoPath "fileAccess" name -- | @getFileStatus path@ calls gets the @FileStatus@ information (user ID, @@ -276,7 +276,7 @@ readSymbolicLink file = allocaArray0 (#const PATH_MAX) $ \buf -> do withFilePath file $ \s -> do len <- throwErrnoPathIfMinus1 "readSymbolicLink" file $ - c_readlink s buf (#const PATH_MAX) + c_readlink s buf (#const PATH_MAX) peekFilePathLen (buf,fromIntegral len) foreign import ccall unsafe "readlink" @@ -323,7 +323,7 @@ setSymbolicLinkOwnerAndGroup :: RawFilePath -> UserID -> GroupID -> IO () setSymbolicLinkOwnerAndGroup name uid gid = do withFilePath name $ \s -> throwErrnoPathIfMinus1_ "setSymbolicLinkOwnerAndGroup" name - (c_lchown s uid gid) + (c_lchown s uid gid) foreign import ccall unsafe "lchown" c_lchown :: CString -> CUid -> CGid -> IO CInt From git at git.haskell.org Thu Mar 19 15:50:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:03 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Unify accepted errno flags for access (5c5484c) Message-ID: <20150319155003.ABB2B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/5c5484c8006f3df63d4cfb640f947f6391ea192f/unix >--------------------------------------------------------------- commit 5c5484c8006f3df63d4cfb640f947f6391ea192f Author: Clemens Lang Date: Sun Sep 21 17:45:56 2014 +0200 Unify accepted errno flags for access The ByteString variant of the access function didn't accept the same flags as the non-ByteString one, but it makes sense that the OS doesn't care about which one is being used and returns all error codes for both variants. >--------------------------------------------------------------- 5c5484c8006f3df63d4cfb640f947f6391ea192f System/Posix/Files/ByteString.hsc | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Posix/Files/ByteString.hsc b/System/Posix/Files/ByteString.hsc index 9430779..1b346a7 100644 --- a/System/Posix/Files/ByteString.hsc +++ b/System/Posix/Files/ByteString.hsc @@ -158,7 +158,7 @@ access name flags = if (r == 0) then return True else do err <- getErrno - if (err == eACCES) + if (err == eACCES || err == eROFS || err == eTXTBSY) then return False else throwErrnoPath "fileAccess" name From git at git.haskell.org Thu Mar 19 15:50:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:05 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Accept EPERM as valid error code for access(2) (3a0c0fe) Message-ID: <20150319155005.B39383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/3a0c0fe1c8b2242250735675b64114fadbfc0aee/unix >--------------------------------------------------------------- commit 3a0c0fe1c8b2242250735675b64114fadbfc0aee Author: Clemens Lang Date: Sun Sep 21 17:49:16 2014 +0200 Accept EPERM as valid error code for access(2) This is useful on OS X when its sandboxing mechanism is used, because that will set errno = EPERM when a file can't be written due to sandboxing (as opposed to setting it to EACCES when file permissions deny writing). >--------------------------------------------------------------- 3a0c0fe1c8b2242250735675b64114fadbfc0aee System/Posix/Files.hsc | 3 ++- System/Posix/Files/ByteString.hsc | 3 ++- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/System/Posix/Files.hsc b/System/Posix/Files.hsc index c8b5ddf..7c20987 100644 --- a/System/Posix/Files.hsc +++ b/System/Posix/Files.hsc @@ -152,7 +152,8 @@ access name flags = if (r == 0) then return True else do err <- getErrno - if (err == eACCES || err == eROFS || err == eTXTBSY) + if (err == eACCES || err == eROFS || err == eTXTBSY || + err == ePERM) then return False else throwErrnoPath "fileAccess" name diff --git a/System/Posix/Files/ByteString.hsc b/System/Posix/Files/ByteString.hsc index 1b346a7..dc1a3f8 100644 --- a/System/Posix/Files/ByteString.hsc +++ b/System/Posix/Files/ByteString.hsc @@ -158,7 +158,8 @@ access name flags = if (r == 0) then return True else do err <- getErrno - if (err == eACCES || err == eROFS || err == eTXTBSY) + if (err == eACCES || err == eROFS || err == eTXTBSY || + err == ePERM) then return False else throwErrnoPath "fileAccess" name From git at git.haskell.org Thu Mar 19 15:50:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:07 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Disable getlogin tests for the moment (#1487) (e7ce4a6) Message-ID: <20150319155007.B990D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/e7ce4a66113a910af6327b3192e9ce4879a453cc/unix >--------------------------------------------------------------- commit e7ce4a66113a910af6327b3192e9ce4879a453cc Author: Thomas Miedema Date: Fri Sep 26 19:03:05 2014 +0200 Disable getlogin tests for the moment (#1487) >--------------------------------------------------------------- e7ce4a66113a910af6327b3192e9ce4879a453cc tests/user001.hs | 4 ++-- tests/user001.stdout | 2 -- 2 files changed, 2 insertions(+), 4 deletions(-) diff --git a/tests/user001.hs b/tests/user001.hs index f4c44fc..4b4dd8b 100644 --- a/tests/user001.hs +++ b/tests/user001.hs @@ -17,11 +17,11 @@ main = do p "getRealUserID" $ getRealUserID p "getEffectiveUserID" $ getEffectiveUserID p "getEffectiveGroupID" $ getEffectiveGroupID p "getGroups" $ getGroups - p "getLoginName" $ getLoginName + --p "getLoginName" $ getLoginName p "getEffectiveUserName" $ getEffectiveUserName p "getGroupEntryForID" $ getRealGroupID >>= getGroupEntryForID p "getGroupEntryForName" $ getRealGroupID >>= getGroupEntryForID >>= getGroupEntryForName . groupName p "getAllGroupEntries" $ getAllGroupEntries p "getUserEntryForID" $ getRealUserID >>= getUserEntryForID - p "getUserEntryForName" $ getLoginName >>= getUserEntryForName + --p "getUserEntryForName" $ getLoginName >>= getUserEntryForName p "getAllUserEntries" $ getAllUserEntries diff --git a/tests/user001.stdout b/tests/user001.stdout index 48c0cfd..e2e03df 100644 --- a/tests/user001.stdout +++ b/tests/user001.stdout @@ -3,11 +3,9 @@ getRealGroupID: OK getEffectiveUserID: OK getEffectiveGroupID: OK getGroups: OK -getLoginName: OK getEffectiveUserName: OK getGroupEntryForID: OK getGroupEntryForName: OK getAllGroupEntries: OK getUserEntryForID: OK -getUserEntryForName: OK getAllUserEntries: OK From git at git.haskell.org Thu Mar 19 15:50:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:09 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Merge pull request #19 from thomie/master (49dda44) Message-ID: <20150319155009.C25E23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/49dda44ebcc669751892e5b62b5230807947fa6e/unix >--------------------------------------------------------------- commit 49dda44ebcc669751892e5b62b5230807947fa6e Merge: 832ac1d e7ce4a6 Author: Herbert Valerio Riedel Date: Fri Sep 26 19:32:15 2014 +0200 Merge pull request #19 from thomie/master Disable getlogin tests for the moment (#1487) >--------------------------------------------------------------- 49dda44ebcc669751892e5b62b5230807947fa6e tests/user001.hs | 4 ++-- tests/user001.stdout | 2 -- 2 files changed, 2 insertions(+), 4 deletions(-) From git at git.haskell.org Thu Mar 19 15:50:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:11 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Replace obsolete `defaultUserHooks` by `autoconfUserHooks` (c46a7fe) Message-ID: <20150319155011.CB2C53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/c46a7fecc212573cc7864a25a762e9e6849f7257/unix >--------------------------------------------------------------- commit c46a7fecc212573cc7864a25a762e9e6849f7257 Author: Herbert Valerio Riedel Date: Sat Sep 27 09:52:28 2014 +0200 Replace obsolete `defaultUserHooks` by `autoconfUserHooks` >--------------------------------------------------------------- c46a7fecc212573cc7864a25a762e9e6849f7257 Setup.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Setup.hs b/Setup.hs index 7cf9bfd..54f57d6 100644 --- a/Setup.hs +++ b/Setup.hs @@ -3,4 +3,4 @@ module Main (main) where import Distribution.Simple main :: IO () -main = defaultMainWithHooks defaultUserHooks +main = defaultMainWithHooks autoconfUserHooks From git at git.haskell.org Thu Mar 19 15:50:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:13 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: fix _FILE_OFFSET_BITS redefined warning on Solaris/x86 (1b53296) Message-ID: <20150319155013.D43AD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/1b53296fba0d36f6144c7797e96bf95b33a4cd7e/unix >--------------------------------------------------------------- commit 1b53296fba0d36f6144c7797e96bf95b33a4cd7e Author: Karel Gardas Date: Fri Jul 25 23:42:00 2014 +0200 fix _FILE_OFFSET_BITS redefined warning on Solaris/x86 The issue is that sys/types.h header on Solaris includes somehow /usr/include/sys/feature_tests.h which tests if _FILE_OFFSET_BITS is defined and if not, then it defines it to 32 if we're compiling 32 bit code (x86). This is simply wrong since we'd like to have it defined to 64. The issue is solved by including HsUnixConfig.h first which defines _FILE_OFFSET_BITS to 64 and feature_tests.h is later OK with that. >--------------------------------------------------------------- 1b53296fba0d36f6144c7797e96bf95b33a4cd7e System/Posix/SharedMem.hsc | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/System/Posix/SharedMem.hsc b/System/Posix/SharedMem.hsc index 1d7a80a..c85e4b7 100644 --- a/System/Posix/SharedMem.hsc +++ b/System/Posix/SharedMem.hsc @@ -19,12 +19,12 @@ module System.Posix.SharedMem (ShmOpenFlags(..), shmOpen, shmUnlink) where +#include "HsUnix.h" + #include #include #include -#include "HsUnix.h" - import System.Posix.Types #if defined(HAVE_SHM_OPEN) || defined(HAVE_SHM_UNLINK) import Foreign.C From git at git.haskell.org Thu Mar 19 15:50:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:15 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Use CAPI FFI imports for `truncate` (bc4bd17) Message-ID: <20150319155015.DC67F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/bc4bd179bda49b615a1c40df7402ddf80bf775b2/unix >--------------------------------------------------------------- commit bc4bd179bda49b615a1c40df7402ddf80bf775b2 Author: Herbert Valerio Riedel Date: Thu Aug 7 12:33:51 2014 +0200 Use CAPI FFI imports for `truncate` This makes sure we pick up the LFS version of `truncate` in case `off_t` is affected by CPP defines such as `_FILE_OFFSET_BITS`. >--------------------------------------------------------------- bc4bd179bda49b615a1c40df7402ddf80bf775b2 System/Posix/Files.hsc | 4 +++- System/Posix/Files/ByteString.hsc | 4 +++- changelog.md | 2 ++ configure.ac | 3 +++ 4 files changed, 11 insertions(+), 2 deletions(-) diff --git a/System/Posix/Files.hsc b/System/Posix/Files.hsc index c8b5ddf..1822294 100644 --- a/System/Posix/Files.hsc +++ b/System/Posix/Files.hsc @@ -1,6 +1,8 @@ #ifdef __GLASGOW_HASKELL__ {-# LANGUAGE Trustworthy #-} #endif +{-# LANGUAGE CApiFFI #-} + ----------------------------------------------------------------------------- -- | -- Module : System.Posix.Files @@ -420,7 +422,7 @@ setFileSize file off = withFilePath file $ \s -> throwErrnoPathIfMinus1_ "setFileSize" file (c_truncate s off) -foreign import ccall unsafe "truncate" +foreign import capi unsafe "HsUnix.h truncate" c_truncate :: CString -> COff -> IO CInt -- ----------------------------------------------------------------------------- diff --git a/System/Posix/Files/ByteString.hsc b/System/Posix/Files/ByteString.hsc index 80f0bea..cb68668 100644 --- a/System/Posix/Files/ByteString.hsc +++ b/System/Posix/Files/ByteString.hsc @@ -1,6 +1,8 @@ #ifdef __GLASGOW_HASKELL__ {-# LANGUAGE Trustworthy #-} #endif +{-# LANGUAGE CApiFFI #-} + ----------------------------------------------------------------------------- -- | -- Module : System.Posix.Files.ByteString @@ -420,7 +422,7 @@ setFileSize file off = withFilePath file $ \s -> throwErrnoPathIfMinus1_ "setFileSize" file (c_truncate s off) -foreign import ccall unsafe "truncate" +foreign import capi unsafe "HsUnix.h truncate" c_truncate :: CString -> COff -> IO CInt -- ----------------------------------------------------------------------------- diff --git a/changelog.md b/changelog.md index c481922..66caaeb 100644 --- a/changelog.md +++ b/changelog.md @@ -12,6 +12,8 @@ convention * Fix potential type-mismatch in `telldir`/`seekdir` FFI imports + * Use CAPI FFI import for `truncate` to make sure the LFS-version is used. + ## 2.7.0.1 *Mar 2014* * Bundled with GHC 7.8.1 diff --git a/configure.ac b/configure.ac index 41274dc..c10bf89 100644 --- a/configure.ac +++ b/configure.ac @@ -18,6 +18,9 @@ AC_C_CONST dnl ** Enable large file support. NB. do this before testing the type of dnl off_t, because it will affect the result of that test. +dnl +dnl WARNING: It's essential this check agrees with HsBaseConfig.h as otherwise +dnl the definitions of COff/coff_t don't line up AC_SYS_LARGEFILE AC_CHECK_HEADERS([dirent.h fcntl.h grp.h limits.h pwd.h signal.h string.h]) From git at git.haskell.org Thu Mar 19 15:50:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:17 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Use correct POSIX offset-type for tell/seekdir (43343c1) Message-ID: <20150319155017.E38883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/43343c151f9824a44bd6e353610fdeb23f910c72/unix >--------------------------------------------------------------- commit 43343c151f9824a44bd6e353610fdeb23f910c72 Author: Herbert Valerio Riedel Date: Thu Aug 7 12:23:07 2014 +0200 Use correct POSIX offset-type for tell/seekdir This fixes the FFI imports to use the proper `CLong` type over the previous incorrect `COff` type, as using the wrong argument type can cause problems when the `long` and `off_t` types have different size. Historic note from the manual page: In glibc up to version 2.1.1, the return type of telldir() was off_t. POSIX.1-2001 specifies long, and this is the type used since glibc 2.1.2 (released in 1999). >--------------------------------------------------------------- 43343c151f9824a44bd6e353610fdeb23f910c72 System/Posix/Directory/Common.hsc | 8 ++++---- changelog.md | 2 ++ 2 files changed, 6 insertions(+), 4 deletions(-) diff --git a/System/Posix/Directory/Common.hsc b/System/Posix/Directory/Common.hsc index 86d87ca..7cc61af 100644 --- a/System/Posix/Directory/Common.hsc +++ b/System/Posix/Directory/Common.hsc @@ -62,20 +62,20 @@ newtype DirStreamOffset = DirStreamOffset COff #ifdef HAVE_SEEKDIR seekDirStream :: DirStream -> DirStreamOffset -> IO () seekDirStream (DirStream dirp) (DirStreamOffset off) = - c_seekdir dirp off + c_seekdir dirp (fromIntegral off) -- TODO: check for CLong/COff overflow foreign import ccall unsafe "seekdir" - c_seekdir :: Ptr CDir -> COff -> IO () + c_seekdir :: Ptr CDir -> CLong -> IO () #endif #ifdef HAVE_TELLDIR tellDirStream :: DirStream -> IO DirStreamOffset tellDirStream (DirStream dirp) = do off <- c_telldir dirp - return (DirStreamOffset off) + return (DirStreamOffset (fromIntegral off)) -- TODO: check for overflow foreign import ccall unsafe "telldir" - c_telldir :: Ptr CDir -> IO COff + c_telldir :: Ptr CDir -> IO CLong #endif changeWorkingDirectoryFd :: Fd -> IO () diff --git a/changelog.md b/changelog.md index ae5b726..c481922 100644 --- a/changelog.md +++ b/changelog.md @@ -1,3 +1,4 @@ +<<<<<<< HEAD # Changelog for [`unix` package](http://hackage.haskell.org/package/unix) ## 2.7.0.2 *TBA* @@ -9,6 +10,7 @@ CPP macros for required getgrgid_r and getgrnam_r functions definition so the fix is to change from C ABI calling convention to C API calling convention + * Fix potential type-mismatch in `telldir`/`seekdir` FFI imports ## 2.7.0.1 *Mar 2014* From git at git.haskell.org Thu Mar 19 15:50:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:19 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Merge pull request #5 from hvr/pr-LFS (5970f50) Message-ID: <20150319155019.EE7433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/5970f506e6f8baa125063c12cfe7cd2bb3747295/unix >--------------------------------------------------------------- commit 5970f506e6f8baa125063c12cfe7cd2bb3747295 Merge: c46a7fe 1b53296 Author: Herbert Valerio Riedel Date: Sat Oct 18 17:08:52 2014 +0200 Merge pull request #5 from hvr/pr-LFS Fix potential LFS related issues >--------------------------------------------------------------- 5970f506e6f8baa125063c12cfe7cd2bb3747295 System/Posix/Directory/Common.hsc | 8 ++++---- System/Posix/Files.hsc | 4 +++- System/Posix/Files/ByteString.hsc | 4 +++- System/Posix/SharedMem.hsc | 4 ++-- changelog.md | 4 ++++ configure.ac | 3 +++ 6 files changed, 19 insertions(+), 8 deletions(-) From git at git.haskell.org Thu Mar 19 15:50:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:21 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Add hackage-shield to README.md (f72e171) Message-ID: <20150319155021.F27F33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/f72e171587708782db4a0f82e9a2c5b76d16a927/unix >--------------------------------------------------------------- commit f72e171587708782db4a0f82e9a2c5b76d16a927 Author: Herbert Valerio Riedel Date: Thu Oct 23 09:36:57 2014 +0200 Add hackage-shield to README.md >--------------------------------------------------------------- f72e171587708782db4a0f82e9a2c5b76d16a927 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index dae5aaa..918cfc1 100644 --- a/README.md +++ b/README.md @@ -1,4 +1,4 @@ -The `unix` Package [![Build Status](https://travis-ci.org/haskell/unix.svg)](https://travis-ci.org/haskell/unix) +The `unix` Package [![Hackage](https://img.shields.io/hackage/v/unix.svg)](https://hackage.haskell.org/package/unix) [![Build Status](https://travis-ci.org/haskell/unix.svg)](https://travis-ci.org/haskell/unix) ================== See [`unix` on Hackage](http://hackage.haskell.org/package/unix) for From git at git.haskell.org Thu Mar 19 15:50:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:24 +0000 (UTC) Subject: [commit: packages/unix] master, safe710fixes, safe710fixes-again, safefixes710again: Merge pull request #18 from neverpanic/master (f5a08a9) Message-ID: <20150319155024.08C003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safe710fixes,safe710fixes-again,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/f5a08a97292fe2f17df7320e47dd0272c382d811/unix >--------------------------------------------------------------- commit f5a08a97292fe2f17df7320e47dd0272c382d811 Merge: f72e171 3a0c0fe Author: Herbert Valerio Riedel Date: Fri Nov 7 11:16:25 2014 +0100 Merge pull request #18 from neverpanic/master `System.Posix.Files.fileAccess` fails inside OS X sandbox >--------------------------------------------------------------- f5a08a97292fe2f17df7320e47dd0272c382d811 System/Posix/Files.hsc | 3 ++- System/Posix/Files/ByteString.hsc | 25 +++++++++++++------------ 2 files changed, 15 insertions(+), 13 deletions(-) From git at git.haskell.org Thu Mar 19 15:50:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:26 +0000 (UTC) Subject: [commit: packages/unix] safe710fixes: Tighten Safe Haskell bounds, fixes new warning in GHC 7.10. (1eda33a) Message-ID: <20150319155026.105AC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : safe710fixes Link : http://ghc.haskell.org/trac/ghc/changeset/1eda33a96c513f7957f082798a97c291a36cc2d6/unix >--------------------------------------------------------------- commit 1eda33a96c513f7957f082798a97c291a36cc2d6 Author: David Terei Date: Wed Nov 12 18:12:18 2014 -0800 Tighten Safe Haskell bounds, fixes new warning in GHC 7.10. >--------------------------------------------------------------- 1eda33a96c513f7957f082798a97c291a36cc2d6 System/Posix/DynamicLinker/Module.hsc | 4 +++- System/Posix/DynamicLinker/Prim.hsc | 1 + System/Posix/Env.hsc | 4 +++- System/Posix/IO.hsc | 4 +++- System/Posix/IO/ByteString.hsc | 4 +++- System/Posix/SharedMem.hsc | 4 +++- System/Posix/Temp.hsc | 4 +++- System/Posix/Temp/ByteString.hsc | 4 +++- 8 files changed, 22 insertions(+), 7 deletions(-) diff --git a/System/Posix/DynamicLinker/Module.hsc b/System/Posix/DynamicLinker/Module.hsc index aa83b6b..aa18d83 100644 --- a/System/Posix/DynamicLinker/Module.hsc +++ b/System/Posix/DynamicLinker/Module.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/DynamicLinker/Prim.hsc b/System/Posix/DynamicLinker/Prim.hsc index 0bef60b..1704f79 100644 --- a/System/Posix/DynamicLinker/Prim.hsc +++ b/System/Posix/DynamicLinker/Prim.hsc @@ -1,5 +1,6 @@ #ifdef __GLASGOW_HASKELL__ {-# LANGUAGE Trustworthy #-} +{-# OPTIONS_GHC -fno-warn-trustworthy-safe #-} #endif ----------------------------------------------------------------------------- -- | diff --git a/System/Posix/Env.hsc b/System/Posix/Env.hsc index 557bc57..95b7bc8 100644 --- a/System/Posix/Env.hsc +++ b/System/Posix/Env.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/IO.hsc b/System/Posix/IO.hsc index eeabb24..41e0b3b 100644 --- a/System/Posix/IO.hsc +++ b/System/Posix/IO.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/IO/ByteString.hsc b/System/Posix/IO/ByteString.hsc index 87dfad6..b8bc87a 100644 --- a/System/Posix/IO/ByteString.hsc +++ b/System/Posix/IO/ByteString.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/SharedMem.hsc b/System/Posix/SharedMem.hsc index c85e4b7..ff43b97 100644 --- a/System/Posix/SharedMem.hsc +++ b/System/Posix/SharedMem.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/Temp.hsc b/System/Posix/Temp.hsc index c27645f..349030b 100644 --- a/System/Posix/Temp.hsc +++ b/System/Posix/Temp.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/Temp/ByteString.hsc b/System/Posix/Temp/ByteString.hsc index 7323012..61bd7e9 100644 --- a/System/Posix/Temp/ByteString.hsc +++ b/System/Posix/Temp/ByteString.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- From git at git.haskell.org Thu Mar 19 15:50:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:28 +0000 (UTC) Subject: [commit: packages/unix] safe710fixes-again: Tighten Safe Haskell bounds, fixes new warning in GHC 7.10. (eafa437) Message-ID: <20150319155028.1C62F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : safe710fixes-again Link : http://ghc.haskell.org/trac/ghc/changeset/eafa4372bd0d9fc61e15f7c587bf495a4f277b7e/unix >--------------------------------------------------------------- commit eafa4372bd0d9fc61e15f7c587bf495a4f277b7e Author: David Terei Date: Wed Nov 12 18:12:18 2014 -0800 Tighten Safe Haskell bounds, fixes new warning in GHC 7.10. >--------------------------------------------------------------- eafa4372bd0d9fc61e15f7c587bf495a4f277b7e System/Posix/DynamicLinker/Module.hsc | 4 +++- System/Posix/DynamicLinker/Prim.hsc | 3 +++ System/Posix/Env.hsc | 4 +++- System/Posix/IO.hsc | 4 +++- System/Posix/IO/ByteString.hsc | 4 +++- System/Posix/SharedMem.hsc | 4 +++- System/Posix/Temp.hsc | 4 +++- System/Posix/Temp/ByteString.hsc | 4 +++- 8 files changed, 24 insertions(+), 7 deletions(-) diff --git a/System/Posix/DynamicLinker/Module.hsc b/System/Posix/DynamicLinker/Module.hsc index aa83b6b..aa18d83 100644 --- a/System/Posix/DynamicLinker/Module.hsc +++ b/System/Posix/DynamicLinker/Module.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/DynamicLinker/Prim.hsc b/System/Posix/DynamicLinker/Prim.hsc index 0bef60b..9e4dde7 100644 --- a/System/Posix/DynamicLinker/Prim.hsc +++ b/System/Posix/DynamicLinker/Prim.hsc @@ -1,5 +1,8 @@ #ifdef __GLASGOW_HASKELL__ {-# LANGUAGE Trustworthy #-} +#if __GLASGOW_HASKELL__ >= 709 +{-# OPTIONS_GHC -fno-warn-trustworthy-safe #-} +#endif #endif ----------------------------------------------------------------------------- -- | diff --git a/System/Posix/Env.hsc b/System/Posix/Env.hsc index 557bc57..95b7bc8 100644 --- a/System/Posix/Env.hsc +++ b/System/Posix/Env.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/IO.hsc b/System/Posix/IO.hsc index eeabb24..41e0b3b 100644 --- a/System/Posix/IO.hsc +++ b/System/Posix/IO.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/IO/ByteString.hsc b/System/Posix/IO/ByteString.hsc index 87dfad6..b8bc87a 100644 --- a/System/Posix/IO/ByteString.hsc +++ b/System/Posix/IO/ByteString.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/SharedMem.hsc b/System/Posix/SharedMem.hsc index c85e4b7..ff43b97 100644 --- a/System/Posix/SharedMem.hsc +++ b/System/Posix/SharedMem.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/Temp.hsc b/System/Posix/Temp.hsc index c27645f..349030b 100644 --- a/System/Posix/Temp.hsc +++ b/System/Posix/Temp.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/Temp/ByteString.hsc b/System/Posix/Temp/ByteString.hsc index 7323012..61bd7e9 100644 --- a/System/Posix/Temp/ByteString.hsc +++ b/System/Posix/Temp/ByteString.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- From git at git.haskell.org Thu Mar 19 15:50:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:30 +0000 (UTC) Subject: [commit: packages/unix] master, safefixes710again: Update Travis CI Job (a03d30d) Message-ID: <20150319155030.204303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/a03d30de8024a902c53cc6c82726bad64feeb4f8/unix >--------------------------------------------------------------- commit a03d30de8024a902c53cc6c82726bad64feeb4f8 Author: Herbert Valerio Riedel Date: Sat Dec 6 13:19:20 2014 +0100 Update Travis CI Job >--------------------------------------------------------------- a03d30de8024a902c53cc6c82726bad64feeb4f8 .travis.yml | 43 ++++++++++++++++++++++++++----------------- 1 file changed, 26 insertions(+), 17 deletions(-) diff --git a/.travis.yml b/.travis.yml index 2bab2ff..22d1b36 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,30 +1,39 @@ env: - - GHCVER=7.4.1 - - GHCVER=7.4.2 - - GHCVER=7.6.1 - - GHCVER=7.6.2 - - GHCVER=7.6.3 + - CABALVER=1.16 GHCVER=7.4.1 + - CABALVER=1.16 GHCVER=7.4.2 + - CABALVER=1.16 GHCVER=7.6.1 + - CABALVER=1.16 GHCVER=7.6.2 + - CABALVER=1.16 GHCVER=7.6.3 + - CABALVER=1.18 GHCVER=7.8.1 + - CABALVER=1.18 GHCVER=7.8.2 + - CABALVER=1.18 GHCVER=7.8.3 + - CABALVER=head GHCVER=head + +matrix: + allow_failures: + - env: CABALVER=head GHCVER=head before_install: - - sudo add-apt-repository -y ppa:hvr/ghc - - sudo apt-get update - - sudo apt-get install cabal-install-1.18 ghc-$GHCVER autoconf - - export PATH=/opt/ghc/$GHCVER/bin:$PATH + - travis_retry sudo add-apt-repository -y ppa:hvr/ghc + - travis_retry sudo apt-get update + - travis_retry sudo apt-get install cabal-install-$CABALVER ghc-$GHCVER autoconf + - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH install: - - cabal-1.18 update - - ghc --version + - cabal --version + - echo "$(ghc --version) [$(ghc --print-project-git-commit-id 2> /dev/null || echo '?')]" + - travis_retry cabal update script: - autoreconf -i - - cabal-1.18 configure -v2 - - cabal-1.18 build - - cabal-1.18 check - - cabal-1.18 sdist - - export SRC_TGZ=$(cabal-1.18 info . | awk '{print $2 ".tar.gz";exit}') ; + - cabal configure -v2 + - cabal build + - cabal check + - cabal sdist + - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; cd dist/; if [ -f "$SRC_TGZ" ]; then - cabal-1.18 install "$SRC_TGZ"; + cabal install --force-reinstalls "$SRC_TGZ"; else echo "expected '$SRC_TGZ' not found"; exit 1; From git at git.haskell.org Thu Mar 19 15:50:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:32 +0000 (UTC) Subject: [commit: packages/unix] master, safefixes710again: fixup Travis CI job (5dd47a6) Message-ID: <20150319155032.2760B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/5dd47a6de1e5b71b488ec86942bf9920ad1e6b19/unix >--------------------------------------------------------------- commit 5dd47a6de1e5b71b488ec86942bf9920ad1e6b19 Author: Herbert Valerio Riedel Date: Sat Dec 6 13:48:10 2014 +0100 fixup Travis CI job >--------------------------------------------------------------- 5dd47a6de1e5b71b488ec86942bf9920ad1e6b19 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 22d1b36..5b94c8c 100644 --- a/.travis.yml +++ b/.travis.yml @@ -28,7 +28,7 @@ script: - autoreconf -i - cabal configure -v2 - cabal build - - cabal check + - cabal check || [ "$CABALVER" == "1.16" ] - cabal sdist - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; cd dist/; From git at git.haskell.org Thu Mar 19 15:50:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:34 +0000 (UTC) Subject: [commit: packages/unix] master, safefixes710again: Kill spurious line from changelog (054df84) Message-ID: <20150319155034.2FD393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/054df8427dc6480bad1f782371a6b7c3ee199574/unix >--------------------------------------------------------------- commit 054df8427dc6480bad1f782371a6b7c3ee199574 Author: Herbert Valerio Riedel Date: Sat Dec 6 13:50:30 2014 +0100 Kill spurious line from changelog [skip ci] >--------------------------------------------------------------- 054df8427dc6480bad1f782371a6b7c3ee199574 changelog.md | 1 - 1 file changed, 1 deletion(-) diff --git a/changelog.md b/changelog.md index 66caaeb..6ef8de8 100644 --- a/changelog.md +++ b/changelog.md @@ -1,4 +1,3 @@ -<<<<<<< HEAD # Changelog for [`unix` package](http://hackage.haskell.org/package/unix) ## 2.7.0.2 *TBA* From git at git.haskell.org Thu Mar 19 15:50:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:36 +0000 (UTC) Subject: [commit: packages/unix] master, safefixes710again: Tighten Safe Haskell bounds, fixes new warning in GHC 7.10. (7222765) Message-ID: <20150319155036.3772F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/7222765c40868100e2527ec7c4a0832e68a786a0/unix >--------------------------------------------------------------- commit 7222765c40868100e2527ec7c4a0832e68a786a0 Author: David Terei Date: Wed Nov 12 18:12:18 2014 -0800 Tighten Safe Haskell bounds, fixes new warning in GHC 7.10. Closes #27 >--------------------------------------------------------------- 7222765c40868100e2527ec7c4a0832e68a786a0 System/Posix/DynamicLinker/Module.hsc | 4 +++- System/Posix/DynamicLinker/Prim.hsc | 3 +++ System/Posix/Env.hsc | 4 +++- System/Posix/IO.hsc | 4 +++- System/Posix/IO/ByteString.hsc | 4 +++- System/Posix/SharedMem.hsc | 4 +++- System/Posix/Temp.hsc | 4 +++- System/Posix/Temp/ByteString.hsc | 4 +++- changelog.md | 1 + 9 files changed, 25 insertions(+), 7 deletions(-) diff --git a/System/Posix/DynamicLinker/Module.hsc b/System/Posix/DynamicLinker/Module.hsc index aa83b6b..aa18d83 100644 --- a/System/Posix/DynamicLinker/Module.hsc +++ b/System/Posix/DynamicLinker/Module.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/DynamicLinker/Prim.hsc b/System/Posix/DynamicLinker/Prim.hsc index 0bef60b..9e4dde7 100644 --- a/System/Posix/DynamicLinker/Prim.hsc +++ b/System/Posix/DynamicLinker/Prim.hsc @@ -1,5 +1,8 @@ #ifdef __GLASGOW_HASKELL__ {-# LANGUAGE Trustworthy #-} +#if __GLASGOW_HASKELL__ >= 709 +{-# OPTIONS_GHC -fno-warn-trustworthy-safe #-} +#endif #endif ----------------------------------------------------------------------------- -- | diff --git a/System/Posix/Env.hsc b/System/Posix/Env.hsc index 557bc57..95b7bc8 100644 --- a/System/Posix/Env.hsc +++ b/System/Posix/Env.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/IO.hsc b/System/Posix/IO.hsc index eeabb24..41e0b3b 100644 --- a/System/Posix/IO.hsc +++ b/System/Posix/IO.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/IO/ByteString.hsc b/System/Posix/IO/ByteString.hsc index 87dfad6..b8bc87a 100644 --- a/System/Posix/IO/ByteString.hsc +++ b/System/Posix/IO/ByteString.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/SharedMem.hsc b/System/Posix/SharedMem.hsc index c85e4b7..ff43b97 100644 --- a/System/Posix/SharedMem.hsc +++ b/System/Posix/SharedMem.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/Temp.hsc b/System/Posix/Temp.hsc index c27645f..349030b 100644 --- a/System/Posix/Temp.hsc +++ b/System/Posix/Temp.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/System/Posix/Temp/ByteString.hsc b/System/Posix/Temp/ByteString.hsc index 7323012..61bd7e9 100644 --- a/System/Posix/Temp/ByteString.hsc +++ b/System/Posix/Temp/ByteString.hsc @@ -1,4 +1,6 @@ -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- diff --git a/changelog.md b/changelog.md index 6ef8de8..d5100cf 100644 --- a/changelog.md +++ b/changelog.md @@ -3,6 +3,7 @@ ## 2.7.0.2 *TBA* * Add support for `base-4.8.0.0` + * Tighten `SafeHaskell` bounds for GHC 7.10+ * Add haddock comments on `RTLD_NEXT` and `RTLD_DEFAULT` * Deprecate function `haveRtldLocal` * Fix `getGroupEntryForID/getGroupEntryForName' on Solaris. Solaris uses From git at git.haskell.org Thu Mar 19 15:50:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:38 +0000 (UTC) Subject: [commit: packages/unix] master, safefixes710again: Do not blindly add libdl to extra libraries (123fcba) Message-ID: <20150319155038.3E9503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/123fcba7125c3b94ad35c3d7dfe31c715a79a470/unix >--------------------------------------------------------------- commit 123fcba7125c3b94ad35c3d7dfe31c715a79a470 Author: Igor Pashev Date: Tue Aug 19 16:23:35 2014 +0400 Do not blindly add libdl to extra libraries On some systems dlopen() is available without libdl (illumos, solaris). Sometimes libdl.so cannot be loaded by runtime linker, see https://ghc.haskell.org/trac/ghc/ticket/8713 Closes #8 >--------------------------------------------------------------- 123fcba7125c3b94ad35c3d7dfe31c715a79a470 configure.ac | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index c10bf89..f519d19 100644 --- a/configure.ac +++ b/configure.ac @@ -186,7 +186,7 @@ else fi # Avoid adding dl if absent or unneeded -AC_CHECK_LIB(dl, dlopen, [EXTRA_LIBS="$EXTRA_LIBS dl"]) +AC_SEARCH_LIBS([dlopen], [dl], [EXTRA_LIBS="$EXTRA_LIBS $ac_lib"]) # -{l,}pthread goo AC_CANONICAL_TARGET From git at git.haskell.org Thu Mar 19 15:50:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:40 +0000 (UTC) Subject: [commit: packages/unix] master, safefixes710again: Refactor local `execvpe(3)` implementation (f24ba78) Message-ID: <20150319155040.492E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/f24ba78f68b2cbc4f4afadc8dd60fc2935357255/unix >--------------------------------------------------------------- commit f24ba78f68b2cbc4f4afadc8dd60fc2935357255 Author: Herbert Valerio Riedel Date: Sat Dec 6 15:39:12 2014 +0100 Refactor local `execvpe(3)` implementation The previous code was prone to conflicts with when the platform happens to expose a `execvpe(3)` implementation in its libc. This commit renames the internal implementation to `__hsunix_execvpe` as well as adding an autoconf-detection for the presence of `execvpe(3)`, in which case `__hsunix_execvpe()` forwards the call to `execvpe(3)`. Moreover, the code has been cleaned up to remove likely bitrotted CPP conditionals. This should fix #22 (This also partially addresses #11 on platforms which have a libc-provided `execvpe(3)`) >--------------------------------------------------------------- f24ba78f68b2cbc4f4afadc8dd60fc2935357255 System/Posix/Process/Internals.hs | 2 +- cbits/execvpe.c | 44 +++++++++++++++++++-------------------- cbits/ghcrts.c | 14 +++++++++++++ configure.ac | 3 +++ include/execvpe.h | 24 ++++----------------- unix.cabal | 1 + 6 files changed, 44 insertions(+), 44 deletions(-) diff --git a/System/Posix/Process/Internals.hs b/System/Posix/Process/Internals.hs index bd3dd31..b320dc7 100644 --- a/System/Posix/Process/Internals.hs +++ b/System/Posix/Process/Internals.hs @@ -30,7 +30,7 @@ data ProcessStatus foreign import ccall unsafe "pPrPr_disableITimers" pPrPr_disableITimers :: IO () -foreign import ccall unsafe "execvpe" +foreign import ccall unsafe "__hsunix_execvpe" c_execvpe :: CString -> Ptr CString -> Ptr CString -> IO CInt decipherWaitStatus :: CInt -> IO ProcessStatus diff --git a/cbits/execvpe.c b/cbits/execvpe.c index 6ce1e9d..8c9d52d 100644 --- a/cbits/execvpe.c +++ b/cbits/execvpe.c @@ -2,19 +2,25 @@ (c) The University of Glasgow 1995-2004 Our low-level exec() variant. + + Note: __hsunix_execvpe() is very similiar to the function + execvpe(3) as provided by glibc 2.11 and later. However, if + execvpe(3) is available, we use that instead. + -------------------------------------------------------------------------- */ #include "execvpe.h" -#ifdef __GLASGOW_HASKELL__ -#include "Rts.h" -#endif +#include "HsUnixConfig.h" -#if !(defined(_MSC_VER) || defined(__MINGW32__) || defined(_WIN32)) /* to the end */ -#ifndef __QNXNTO__ - -/* Evidently non-Posix. */ -/* #include "PosixSource.h" */ +#if HAVE_EXECVPE +# define _GNU_SOURCE +#endif +#include +#include +#if HAVE_SYS_WAIT_H +# include +#endif #include #include #include @@ -59,8 +65,11 @@ */ int -execvpe(char *name, char *const argv[], char **envp) +__hsunix_execvpe(const char *name, char *const argv[], char *const envp[]) { +#if HAVE_EXECVPE + return execvpe(name, argv, envp); +#else register int lp, ln; register char *p; int eacces=0, etxtbsy=0; @@ -75,18 +84,18 @@ execvpe(char *name, char *const argv[], char **envp) /* Get the path we're searching. */ if (!(path = getenv("PATH"))) { -#ifdef HAVE_CONFSTR +# ifdef HAVE_CONFSTR ln = confstr(_CS_PATH, NULL, 0); if ((cur = path = malloc(ln + 1)) != NULL) { path[0] = ':'; (void) confstr (_CS_PATH, path + 1, ln); } -#else +# else if ((cur = path = malloc(1 + 1)) != NULL) { path[0] = ':'; path[1] = '\0'; } -#endif +# endif } else cur = path = strdup(path); @@ -157,16 +166,5 @@ execvpe(char *name, char *const argv[], char **envp) if (buf) free(buf); return (-1); -} -#endif - - -/* Copied verbatim from ghc/lib/std/cbits/system.c. */ -void pPrPr_disableITimers (void) -{ -#ifdef __GLASGOW_HASKELL__ - stopTimer(); #endif } - -#endif diff --git a/cbits/ghcrts.c b/cbits/ghcrts.c new file mode 100644 index 0000000..1e0dc1c --- /dev/null +++ b/cbits/ghcrts.c @@ -0,0 +1,14 @@ +#include "execvpe.h" + +#ifdef __GLASGOW_HASKELL__ +// for 'void StopTimer(void)' prototype +# include "Rts.h" +#endif + +/* Copied verbatim from ghc/lib/std/cbits/system.c. */ +void pPrPr_disableITimers (void) +{ +#ifdef __GLASGOW_HASKELL__ + stopTimer(); +#endif +} diff --git a/configure.ac b/configure.ac index f519d19..cf5a1fd 100644 --- a/configure.ac +++ b/configure.ac @@ -39,6 +39,9 @@ AC_CHECK_FUNCS([readdir_r]) dnl not available on android so check for it AC_CHECK_FUNCS([telldir seekdir]) +dnl This is e.g. available as a GNU extension in glibc 2.11+ +AC_CHECK_FUNCS([execvpe]) + AC_CHECK_MEMBERS([struct stat.st_atim]) AC_CHECK_MEMBERS([struct stat.st_mtim]) AC_CHECK_MEMBERS([struct stat.st_ctim]) diff --git a/include/execvpe.h b/include/execvpe.h index c3b2dd3..1d49e35 100644 --- a/include/execvpe.h +++ b/include/execvpe.h @@ -1,27 +1,11 @@ /* ---------------------------------------------------------------------------- (c) The University of Glasgow 2004 - Interface for code in execvpe.c + Interface for code in cbits/execvpe.c ------------------------------------------------------------------------- */ -#include "HsUnixConfig.h" -// Otherwise these clash with similar definitions from other packages: -#undef PACKAGE_BUGREPORT -#undef PACKAGE_NAME -#undef PACKAGE_STRING -#undef PACKAGE_TARNAME -#undef PACKAGE_VERSION +extern int +__hsunix_execvpe(const char *name, char *const argv[], char *const envp[]); -#include -#include -#if HAVE_SYS_WAIT_H -#include -#endif - -#if !defined(_MSC_VER) && !defined(__MINGW32__) && !defined(_WIN32) -#ifndef __QNXNTO__ -extern int execvpe(char *name, char *const argv[], char **envp); -#endif +// implemented in cbits/ghcrts.c extern void pPrPr_disableITimers (void); -#endif - diff --git a/unix.cabal b/unix.cabal index ddd95de..69470ba 100644 --- a/unix.cabal +++ b/unix.cabal @@ -127,3 +127,4 @@ library cbits/HsUnix.c cbits/dirUtils.c cbits/execvpe.c + cbits/ghcrts.c From git at git.haskell.org Thu Mar 19 15:50:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:42 +0000 (UTC) Subject: [commit: packages/unix] master, safefixes710again: Retry process execution in case of ENOTDIR (558b0fb) Message-ID: <20150319155042.51B403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/558b0fb4eaa4aebc823022b3e1d560da3faad658/unix >--------------------------------------------------------------- commit 558b0fb4eaa4aebc823022b3e1d560da3faad658 Author: Iku Iwasa Date: Sat Aug 2 22:02:23 2014 +0900 Retry process execution in case of ENOTDIR If `PATH` environment variable contains non directory component, `__hsunix_execvpe()` failed by `ENOTDIR`. This fixes #11 for all platforms. >--------------------------------------------------------------- 558b0fb4eaa4aebc823022b3e1d560da3faad658 cbits/execvpe.c | 1 + changelog.md | 3 +++ 2 files changed, 4 insertions(+) diff --git a/cbits/execvpe.c b/cbits/execvpe.c index 8c9d52d..b4f9472 100644 --- a/cbits/execvpe.c +++ b/cbits/execvpe.c @@ -129,6 +129,7 @@ __hsunix_execvpe(const char *name, char *const argv[], char *const envp[]) case EACCES: eacces = 1; break; + case ENOTDIR: case ENOENT: break; case ENOEXEC: diff --git a/changelog.md b/changelog.md index d5100cf..b7dafcd 100644 --- a/changelog.md +++ b/changelog.md @@ -14,6 +14,9 @@ * Use CAPI FFI import for `truncate` to make sure the LFS-version is used. + * `executeFile`: Fix `ENOTDIR` error for entries with non-directory + components in `PATH` (and instead skip over non-directory `PATH`-elements) + ## 2.7.0.1 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Thu Mar 19 15:50:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:44 +0000 (UTC) Subject: [commit: packages/unix] master, safefixes710again: `M-x untabify` && `M-x delete-trailing-whitespace` (078666f) Message-ID: <20150319155044.693633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/078666f4399f368e2f3dd82b5081dc1ad9b9fdc2/unix >--------------------------------------------------------------- commit 078666f4399f368e2f3dd82b5081dc1ad9b9fdc2 Author: Herbert Valerio Riedel Date: Sat Dec 6 17:08:06 2014 +0100 `M-x untabify` && `M-x delete-trailing-whitespace` >--------------------------------------------------------------- 078666f4399f368e2f3dd82b5081dc1ad9b9fdc2 System/Posix/ByteString/FilePath.hsc | 0 System/Posix/Directory.hsc | 48 ++++----- System/Posix/Directory/ByteString.hsc | 44 ++++----- System/Posix/Directory/Common.hsc | 0 System/Posix/DynamicLinker.hsc | 2 +- System/Posix/DynamicLinker/ByteString.hsc | 2 +- System/Posix/DynamicLinker/Common.hsc | 0 System/Posix/DynamicLinker/Module.hsc | 26 ++--- System/Posix/DynamicLinker/Module/ByteString.hsc | 14 +-- System/Posix/DynamicLinker/Prim.hsc | 6 +- System/Posix/Env/ByteString.hsc | 12 +-- System/Posix/Error.hs | 14 +-- System/Posix/Files/ByteString.hsc | 0 System/Posix/Files/Common.hsc | 66 ++++++------- System/Posix/Process.hsc | 28 +++--- System/Posix/Process/Internals.hs | 20 ++-- System/Posix/Resource.hsc | 26 ++--- System/Posix/Semaphore.hsc | 0 System/Posix/Terminal/ByteString.hsc | 0 System/Posix/Terminal/Common.hsc | 118 +++++++++++------------ System/Posix/Time.hsc | 6 +- System/Posix/Unistd.hsc | 24 ++--- System/Posix/User.hsc | 8 +- 23 files changed, 232 insertions(+), 232 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 078666f4399f368e2f3dd82b5081dc1ad9b9fdc2 From git at git.haskell.org Thu Mar 19 15:50:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:46 +0000 (UTC) Subject: [commit: packages/unix] master, safefixes710again: Have "execvpe.h" provide execvpe() again (7bad9d7) Message-ID: <20150319155046.6D44D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/7bad9d7d52d24cc4246646e5af3116c2dd8c25c4/unix >--------------------------------------------------------------- commit 7bad9d7d52d24cc4246646e5af3116c2dd8c25c4 Author: Herbert Valerio Riedel Date: Sat Dec 6 21:11:59 2014 +0100 Have "execvpe.h" provide execvpe() again Turns out `process` reuses `unix`'s execvpe() implementation, and the refactoring in f24ba78f68b2cbc4f4afadc8dd60fc2935357255 broke process. >--------------------------------------------------------------- 7bad9d7d52d24cc4246646e5af3116c2dd8c25c4 cbits/execvpe.c | 5 +++-- include/execvpe.h | 15 +++++++++++++++ 2 files changed, 18 insertions(+), 2 deletions(-) diff --git a/cbits/execvpe.c b/cbits/execvpe.c index b4f9472..9599836 100644 --- a/cbits/execvpe.c +++ b/cbits/execvpe.c @@ -8,12 +8,13 @@ execvpe(3) is available, we use that instead. -------------------------------------------------------------------------- */ -#include "execvpe.h" -#include "HsUnixConfig.h" +#include "execvpe.h" #if HAVE_EXECVPE # define _GNU_SOURCE +#else +# undef execvpe #endif #include diff --git a/include/execvpe.h b/include/execvpe.h index 1d49e35..d4b6521 100644 --- a/include/execvpe.h +++ b/include/execvpe.h @@ -4,8 +4,23 @@ Interface for code in cbits/execvpe.c ------------------------------------------------------------------------- */ +#ifndef HSUNIX_EXECVPE_H +#define HSUNIX_EXECVPE_H + +#include "HsUnixConfig.h" + extern int __hsunix_execvpe(const char *name, char *const argv[], char *const envp[]); +// this hack is needed for `process`; to be removed in unix-2.8 +#if HAVE_EXECVPE +# define _GNU_SOURCE +# include +#else +# define execvpe(name,argv,envp) __hsunix_execvpe(name,argv,envp) +#endif + // implemented in cbits/ghcrts.c extern void pPrPr_disableITimers (void); + +#endif From git at git.haskell.org Thu Mar 19 15:50:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:48 +0000 (UTC) Subject: [commit: packages/unix] master, safefixes710again: Repeat execvpe(3) prototype (fup to 7bad9d7d52d) (256b191) Message-ID: <20150319155048.7457A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/256b19184bcb05c3cd9a6061730b7d67d61c0763/unix >--------------------------------------------------------------- commit 256b19184bcb05c3cd9a6061730b7d67d61c0763 Author: Herbert Valerio Riedel Date: Sat Dec 6 22:29:51 2014 +0100 Repeat execvpe(3) prototype (fup to 7bad9d7d52d) This is needed in case `` was included before "execvpe.h" w/o `_GNU_SOURCE` set (on Glibc systems) >--------------------------------------------------------------- 256b19184bcb05c3cd9a6061730b7d67d61c0763 include/execvpe.h | 2 ++ 1 file changed, 2 insertions(+) diff --git a/include/execvpe.h b/include/execvpe.h index d4b6521..7faa0df 100644 --- a/include/execvpe.h +++ b/include/execvpe.h @@ -16,6 +16,8 @@ __hsunix_execvpe(const char *name, char *const argv[], char *const envp[]); #if HAVE_EXECVPE # define _GNU_SOURCE # include +extern int +execvpe(const char *name, char *const argv[], char *const envp[]); #else # define execvpe(name,argv,envp) __hsunix_execvpe(name,argv,envp) #endif From git at git.haskell.org Thu Mar 19 15:50:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:50 +0000 (UTC) Subject: [commit: packages/unix] master, safefixes710again: Wrap fsync(2) and fdatasync(2) (98eced8) Message-ID: <20150319155050.7C5743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/98eced86549def54dfb5057ef984a02c720be763/unix >--------------------------------------------------------------- commit 98eced86549def54dfb5057ef984a02c720be763 Author: Herbert Valerio Riedel Date: Sun Dec 7 15:29:10 2014 +0100 Wrap fsync(2) and fdatasync(2) This adds two new functions in `System.Posix.Unistd` - `fileSynchronise` (aka `fsync(2)`), and - `fileSynchroniseDataOnly` (aka `fdatasync(2)`) This is based on part of #7 and has been heavily refactored from its original patch submission by Ricardo Catalinas Jim?nez. This also bumps version to 2.7.1.0 as a minor version bump is now needed. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 98eced86549def54dfb5057ef984a02c720be763 System/Posix/Unistd.hsc | 52 +++++++++++++++++++++++++++++++++++++++++++++++++ changelog.md | 6 +++++- configure.ac | 3 +++ unix.cabal | 2 +- 4 files changed, 61 insertions(+), 2 deletions(-) diff --git a/System/Posix/Unistd.hsc b/System/Posix/Unistd.hsc index 0a13d6d..afb8c08 100644 --- a/System/Posix/Unistd.hsc +++ b/System/Posix/Unistd.hsc @@ -1,3 +1,4 @@ +{-# LANGUAGE CApiFFI #-} {-# LANGUAGE NondecreasingIndentation #-} #ifdef __GLASGOW_HASKELL__ {-# LANGUAGE Trustworthy #-} @@ -27,6 +28,10 @@ module System.Posix.Unistd ( -- * Sleeping sleep, usleep, nanosleep, + -- * File synchronisation + fileSynchronise, + fileSynchroniseDataOnly, + {- ToDo from unistd.h: confstr, @@ -55,8 +60,14 @@ import Foreign.C.Error import Foreign.C.String ( peekCString ) import Foreign.C.Types import Foreign +import System.Posix.Types import System.Posix.Internals +#if !(HAVE_FSYNC && HAVE_FDATASYNC) +import System.IO.Error ( ioeSetLocation ) +import GHC.IO.Exception ( unsupportedOperation ) +#endif + -- ----------------------------------------------------------------------------- -- System environment (uname()) @@ -206,3 +217,44 @@ sysconf n = do foreign import ccall unsafe "sysconf" c_sysconf :: CInt -> IO CLong + +-- ----------------------------------------------------------------------------- +-- File synchronization + +-- | Performs @fsync(2)@ operation on file-descriptor. +-- +-- Throws 'IOError' (\"unsupported operation\") if platform does not +-- provide @fsync(2)@ (use @#if HAVE_FSYNC@ CPP guard to +-- detect availability). +fileSynchronise :: Fd -> IO () +#if HAVE_FSYNC +fileSynchronise fd = do + throwErrnoIfMinus1_ "fileSynchronise" (c_fsync fd) + +foreign import capi safe "unistd.h fsync" + c_fsync :: Fd -> IO CInt +#else +{-# WARNING fileSynchronise + "operation will throw exception (CPP guard: @#if HAVE_FSYNC@)" #-} +fileSynchronise _ = ioError (ioeSetLocation unsupportedOperation + "fileSynchronise") +#endif + +-- | Performs @fdatasync(2)@ operation on file-descriptor. +-- +-- Throws 'IOError' (\"unsupported operation\") if platform does not +-- provide @fdatasync(2)@ (use @#if HAVE_FDATASYNC@ CPP guard to +-- detect availability). +fileSynchroniseDataOnly :: Fd -> IO () +#if HAVE_FDATASYNC +fileSynchroniseDataOnly fd = do + throwErrnoIfMinus1_ "fileSynchroniseDataOnly" (c_fdatasync fd) + +foreign import capi safe "unistd.h fdatasync" + c_fdatasync :: Fd -> IO CInt +#else +{-# WARNING fileSynchroniseDataOnly + "operation will throw exception (CPP guard: @#if HAVE_FDATASYNC@)" #-} +fileSynchroniseDataOnly _ = ioError (ioeSetLocation unsupportedOperation + "fileSynchroniseDataOnly") +#endif diff --git a/changelog.md b/changelog.md index b7dafcd..1be0f35 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`unix` package](http://hackage.haskell.org/package/unix) -## 2.7.0.2 *TBA* +## 2.7.1.0 *Dec 2014* * Add support for `base-4.8.0.0` * Tighten `SafeHaskell` bounds for GHC 7.10+ @@ -17,6 +17,10 @@ * `executeFile`: Fix `ENOTDIR` error for entries with non-directory components in `PATH` (and instead skip over non-directory `PATH`-elements) + * New functions in `System.Posix.Unistd`: + - `fileSynchronise` (aka `fsync(2)`), and + - `fileSynchroniseDataOnly` (aka `fdatasync(2)`) + ## 2.7.0.1 *Mar 2014* * Bundled with GHC 7.8.1 diff --git a/configure.ac b/configure.ac index cf5a1fd..94d9d77 100644 --- a/configure.ac +++ b/configure.ac @@ -67,6 +67,9 @@ AC_CHECK_FUNCS([lutimes futimes]) # Additional temp functions AC_CHECK_FUNCS([mkstemps mkdtemp]) +# Functions for file synchronization and allocation control +AC_CHECK_FUNCS([fsync fdatasync]) + # Avoid adding rt if absent or unneeded # shm_open needs -lrt on linux AC_SEARCH_LIBS(shm_open, rt, [AC_CHECK_FUNCS([shm_open shm_unlink])]) diff --git a/unix.cabal b/unix.cabal index 69470ba..7bcf0d9 100644 --- a/unix.cabal +++ b/unix.cabal @@ -1,5 +1,5 @@ name: unix -version: 2.7.0.2 +version: 2.7.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE From git at git.haskell.org Thu Mar 19 15:50:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:50 +0000 (UTC) Subject: [commit: ghc] wip/T10137: CmmSwitch: T783 regresses a lot (1495ed5) Message-ID: <20150319155050.CD4B53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10137 Link : http://ghc.haskell.org/trac/ghc/changeset/1495ed521601affcd6e2a7a2bf9d579dc6b6486f/ghc >--------------------------------------------------------------- commit 1495ed521601affcd6e2a7a2bf9d579dc6b6486f Author: Joachim Breitner Date: Thu Mar 19 16:45:46 2015 +0100 CmmSwitch: T783 regresses a lot but it is the only one exhibiting that. The cause is the changed order of branches in an if-then-else tree, which makes the hoople data flow analysis traverse the blocks in a suboptimal order. Reverting that gets rid of this regression, but has a consistent, if only very small (+0.2%), negative effect on runtime. So I conclude that this test is an extreme outlier and no reason to change the code. >--------------------------------------------------------------- 1495ed521601affcd6e2a7a2bf9d579dc6b6486f testsuite/tests/perf/compiler/all.T | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index a874866..d20d676 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -390,7 +390,7 @@ test('T783', # 2014-09-03: 223377364 (Windows) better specialisation, raft of core-to-core optimisations # 2014-12-22: 235002220 (Windows) not sure why - (wordsize(64), 441932632, 10)]), + (wordsize(64), 719814352, 10)]), # prev: 349263216 (amd64/Linux) # 07/08/2012: 384479856 (amd64/Linux) # 29/08/2012: 436927840 (amd64/Linux) @@ -405,6 +405,10 @@ test('T783', # (general round of updates) # 2014-08-29: 441932632 (amd64/Linux) # (better specialisation, raft of core-to-core optimisations) + # 2014-08-29: 719814352 (amd64/Linux) + # (changed order of cmm block causes analyses to allocate much more, + # but the changed order is slighly better in terms of runtime, and + # this test seems to be an extreme outlier.) extra_hc_opts('-static') ], compile,['']) From git at git.haskell.org Thu Mar 19 15:50:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:52 +0000 (UTC) Subject: [commit: packages/unix] master, safefixes710again: Tweak execvpe.h hack (see 256b19184bcb) some more (5986106) Message-ID: <20150319155052.886653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/59861061f2ab1d3f4b28e83d2dcc3adf0f9acb04/unix >--------------------------------------------------------------- commit 59861061f2ab1d3f4b28e83d2dcc3adf0f9acb04 Author: Herbert Valerio Riedel Date: Sun Dec 7 16:01:51 2014 +0100 Tweak execvpe.h hack (see 256b19184bcb) some more >--------------------------------------------------------------- 59861061f2ab1d3f4b28e83d2dcc3adf0f9acb04 cbits/execvpe.c | 7 ++++--- cbits/ghcrts.c | 5 +++-- include/execvpe.h | 5 +++-- 3 files changed, 10 insertions(+), 7 deletions(-) diff --git a/cbits/execvpe.c b/cbits/execvpe.c index 9599836..c27bca9 100644 --- a/cbits/execvpe.c +++ b/cbits/execvpe.c @@ -9,12 +9,10 @@ -------------------------------------------------------------------------- */ -#include "execvpe.h" +#include "HsUnixConfig.h" #if HAVE_EXECVPE # define _GNU_SOURCE -#else -# undef execvpe #endif #include @@ -28,6 +26,9 @@ #include #include +#define HSUNIX_EXECVPE_H_NO_COMPAT +#include "execvpe.h" + /* * We want the search semantics of execvp, but we want to provide our * own environment, like execve. The following copyright applies to diff --git a/cbits/ghcrts.c b/cbits/ghcrts.c index 1e0dc1c..9003675 100644 --- a/cbits/ghcrts.c +++ b/cbits/ghcrts.c @@ -1,10 +1,11 @@ -#include "execvpe.h" - #ifdef __GLASGOW_HASKELL__ // for 'void StopTimer(void)' prototype # include "Rts.h" #endif +#define HSUNIX_EXECVPE_H_NO_COMPAT +#include "execvpe.h" + /* Copied verbatim from ghc/lib/std/cbits/system.c. */ void pPrPr_disableITimers (void) { diff --git a/include/execvpe.h b/include/execvpe.h index 7faa0df..1fd2fbb 100644 --- a/include/execvpe.h +++ b/include/execvpe.h @@ -7,12 +7,12 @@ #ifndef HSUNIX_EXECVPE_H #define HSUNIX_EXECVPE_H -#include "HsUnixConfig.h" - extern int __hsunix_execvpe(const char *name, char *const argv[], char *const envp[]); // this hack is needed for `process`; to be removed in unix-2.8 +#ifndef HSUNIX_EXECVPE_H_NO_COMPAT +#include "HsUnixConfig.h" #if HAVE_EXECVPE # define _GNU_SOURCE # include @@ -21,6 +21,7 @@ execvpe(const char *name, char *const argv[], char *const envp[]); #else # define execvpe(name,argv,envp) __hsunix_execvpe(name,argv,envp) #endif +#endif // implemented in cbits/ghcrts.c extern void pPrPr_disableITimers (void); From git at git.haskell.org Thu Mar 19 15:50:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:54 +0000 (UTC) Subject: [commit: packages/unix] master, safefixes710again: More fixes for Safe Haskell bounds under GHC 7.10 (e0bc46b) Message-ID: <20150319155054.9616D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branches: master,safefixes710again Link : http://ghc.haskell.org/trac/ghc/changeset/e0bc46b891608f7e50223443d03a849fd16ac84d/unix >--------------------------------------------------------------- commit e0bc46b891608f7e50223443d03a849fd16ac84d Author: David Terei Date: Mon Dec 8 22:03:15 2014 -0800 More fixes for Safe Haskell bounds under GHC 7.10 >--------------------------------------------------------------- e0bc46b891608f7e50223443d03a849fd16ac84d System/Posix/ByteString/FilePath.hsc | 5 ++++- System/Posix/Directory/Common.hsc | 4 +++- System/Posix/DynamicLinker.hsc | 4 +++- System/Posix/DynamicLinker/ByteString.hsc | 5 ++++- System/Posix/DynamicLinker/Common.hsc | 4 +++- System/Posix/DynamicLinker/Module/ByteString.hsc | 5 ++++- System/Posix/Env/ByteString.hsc | 4 ++++ System/Posix/Error.hs | 4 +++- System/Posix/Files.hsc | 4 +++- System/Posix/Files/ByteString.hsc | 4 +++- System/Posix/IO/Common.hsc | 5 ++++- System/Posix/Process.hsc | 4 +++- System/Posix/Process/ByteString.hsc | 5 ++++- System/Posix/Resource.hsc | 4 +++- System/Posix/Semaphore.hsc | 4 +++- System/Posix/Signals/Exts.hsc | 5 +++++ System/Posix/Terminal.hsc | 4 +++- System/Posix/Terminal/ByteString.hsc | 4 +++- System/Posix/Time.hsc | 4 +++- System/Posix/Unistd.hsc | 4 +++- 20 files changed, 68 insertions(+), 18 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e0bc46b891608f7e50223443d03a849fd16ac84d From git at git.haskell.org Thu Mar 19 15:50:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:56 +0000 (UTC) Subject: [commit: packages/unix] master: Merge pull request #29 from haskell/safefixes710again (cbe8af7) Message-ID: <20150319155056.9F02A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cbe8af7a60c9350dda479fd3539d639a59ffb85a/unix >--------------------------------------------------------------- commit cbe8af7a60c9350dda479fd3539d639a59ffb85a Merge: 5986106 e0bc46b Author: Herbert Valerio Riedel Date: Tue Dec 9 17:46:41 2014 +0100 Merge pull request #29 from haskell/safefixes710again More fixes for Safe Haskell bounds under GHC 7.10 >--------------------------------------------------------------- cbe8af7a60c9350dda479fd3539d639a59ffb85a System/Posix/ByteString/FilePath.hsc | 5 ++++- System/Posix/Directory/Common.hsc | 4 +++- System/Posix/DynamicLinker.hsc | 4 +++- System/Posix/DynamicLinker/ByteString.hsc | 5 ++++- System/Posix/DynamicLinker/Common.hsc | 4 +++- System/Posix/DynamicLinker/Module/ByteString.hsc | 5 ++++- System/Posix/Env/ByteString.hsc | 4 ++++ System/Posix/Error.hs | 4 +++- System/Posix/Files.hsc | 4 +++- System/Posix/Files/ByteString.hsc | 4 +++- System/Posix/IO/Common.hsc | 5 ++++- System/Posix/Process.hsc | 4 +++- System/Posix/Process/ByteString.hsc | 5 ++++- System/Posix/Resource.hsc | 4 +++- System/Posix/Semaphore.hsc | 4 +++- System/Posix/Signals/Exts.hsc | 5 +++++ System/Posix/Terminal.hsc | 4 +++- System/Posix/Terminal/ByteString.hsc | 4 +++- System/Posix/Time.hsc | 4 +++- System/Posix/Unistd.hsc | 4 +++- 20 files changed, 68 insertions(+), 18 deletions(-) From git at git.haskell.org Thu Mar 19 15:50:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:50:58 +0000 (UTC) Subject: [commit: packages/unix] master: Wrap posix_fadvise(2) and posix_fallocate(2) (e14fbe2) Message-ID: <20150319155058.AECFB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e14fbe2cb3bbd604dadcc3847882ca37edf548b3/unix >--------------------------------------------------------------- commit e14fbe2cb3bbd604dadcc3847882ca37edf548b3 Author: Herbert Valerio Riedel Date: Mon Dec 15 23:25:26 2014 +0100 Wrap posix_fadvise(2) and posix_fallocate(2) This adds two new functions in `System.Posix.Unistd` - `fileAdvise` (aka `posix_fadvise(2)`), and - `fileAllocate` (aka `posix_fallocate(2)`) This is based in part on #7 and has been heavily refactored from its original patch submission by Ricardo Catalinas Jim?nez. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- e14fbe2cb3bbd604dadcc3847882ca37edf548b3 System/Posix/Fcntl.hsc | 99 ++++++++++++++++++++++++++++++++++++++++++++++++++ changelog.md | 4 ++ configure.ac | 1 + unix.cabal | 2 + 4 files changed, 106 insertions(+) diff --git a/System/Posix/Fcntl.hsc b/System/Posix/Fcntl.hsc new file mode 100644 index 0000000..a45f559 --- /dev/null +++ b/System/Posix/Fcntl.hsc @@ -0,0 +1,99 @@ +{-# LANGUAGE CApiFFI #-} +#ifdef __GLASGOW_HASKELL__ +{-# LANGUAGE Trustworthy #-} +#endif +----------------------------------------------------------------------------- +-- | +-- Module : System.Posix.Fcntl +-- Copyright : (c) The University of Glasgow 2014 +-- License : BSD-style (see the file LICENSE) +-- +-- Maintainer : libraries at haskell.org +-- Stability : provisional +-- Portability : non-portable (requires POSIX) +-- +-- POSIX file control support +-- +----------------------------------------------------------------------------- + +#include "HsUnix.h" + +module System.Posix.Fcntl ( + -- * File allocation + Advice(..), fileAdvise, + fileAllocate, + ) where + +#if HAVE_POSIX_FALLOCATE || HAVE_POSIX_FADVISE +import Foreign.C +#endif +import System.Posix.Types + +#if !HAVE_POSIX_FALLOCATE +import System.IO.Error ( ioeSetLocation ) +import GHC.IO.Exception ( unsupportedOperation ) +#endif + +-- ----------------------------------------------------------------------------- +-- File control + +-- | Advice parameter for 'fileAdvise' operation. +-- +-- For more details, see documentation of @posix_fadvise(2)@. +data Advice + = AdviceNormal + | AdviceRandom + | AdviceSequential + | AdviceWillNeed + | AdviceDontNeed + | AdviceNoReuse + deriving Eq + +-- | Performs @posix_fadvise(2)@ operation on file-descriptor. +-- +-- If platform does not provide @posix_fadvise(2)@ 'fileAdvise' +-- becomes a no-op. +-- +-- (use @#if HAVE_POSIX_FADVISE@ CPP guard to detect availability) +-- +-- /Since: 2.7.1.0/ +fileAdvise :: Fd -> FileOffset -> FileOffset -> Advice -> IO () +#if HAVE_POSIX_FADVISE +fileAdvise fd off len adv = do + throwErrnoIfMinus1_ "fileAdvise" (c_posix_fadvise (fromIntegral fd) (fromIntegral off) (fromIntegral len) (packAdvice adv)) + +foreign import capi safe "fcntl.h posix_fadvise" + c_posix_fadvise :: CInt -> COff -> COff -> CInt -> IO CInt + +packAdvice :: Advice -> CInt +packAdvice AdviceNormal = (#const POSIX_FADV_NORMAL) +packAdvice AdviceRandom = (#const POSIX_FADV_RANDOM) +packAdvice AdviceSequential = (#const POSIX_FADV_SEQUENTIAL) +packAdvice AdviceWillNeed = (#const POSIX_FADV_WILLNEED) +packAdvice AdviceDontNeed = (#const POSIX_FADV_DONTNEED) +packAdvice AdviceNoReuse = (#const POSIX_FADV_NOREUSE) +#else +fileAdvise _ _ _ _ = return () +#endif + +-- | Performs @posix_fallocate(2)@ operation on file-descriptor. +-- +-- Throws 'IOError' (\"unsupported operation\") if platform does not +-- provide @posix_fallocate(2)@. +-- +-- (use @#if HAVE_POSIX_FALLOCATE@ CPP guard to detect availability). +-- +-- /Since: 2.7.1.0/ +fileAllocate :: Fd -> FileOffset -> FileOffset -> IO () +#if HAVE_POSIX_FALLOCATE +fileAllocate fd off len = do + throwErrnoIfMinus1_ "fileAllocate" (c_posix_fallocate (fromIntegral fd) (fromIntegral off) (fromIntegral len)) + +foreign import capi safe "fcntl.h posix_fallocate" + c_posix_fallocate :: CInt -> COff -> COff -> IO CInt +#else +{-# WARNING fileAllocate + "operation will throw 'IOError' \"unsupported operation\" (CPP guard: @#if HAVE_POSIX_FALLOCATE@)" #-} +fileAllocate _ _ _ = ioError (ioeSetLocation unsupportedOperation + "fileAllocate") +#endif diff --git a/changelog.md b/changelog.md index 1be0f35..db6bb48 100644 --- a/changelog.md +++ b/changelog.md @@ -21,6 +21,10 @@ - `fileSynchronise` (aka `fsync(2)`), and - `fileSynchroniseDataOnly` (aka `fdatasync(2)`) + * New module `System.Posix.Fcntl` providing + - `fileAdvise` (aka `posix_fadvise(2)`), and + - `fileAllocate` (aka `posix_fallocate(2)`) + ## 2.7.0.1 *Mar 2014* * Bundled with GHC 7.8.1 diff --git a/configure.ac b/configure.ac index 94d9d77..1c82c36 100644 --- a/configure.ac +++ b/configure.ac @@ -69,6 +69,7 @@ AC_CHECK_FUNCS([mkstemps mkdtemp]) # Functions for file synchronization and allocation control AC_CHECK_FUNCS([fsync fdatasync]) +AC_CHECK_FUNCS([posix_fadvise posix_fallocate]) # Avoid adding rt if absent or unneeded # shm_open needs -lrt on linux diff --git a/unix.cabal b/unix.cabal index 7bcf0d9..cc9c646 100644 --- a/unix.cabal +++ b/unix.cabal @@ -96,6 +96,8 @@ library System.Posix.Env System.Posix.Env.ByteString + System.Posix.Fcntl + System.Posix.Process System.Posix.Process.Internals System.Posix.Process.ByteString From git at git.haskell.org Thu Mar 19 15:51:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:51:00 +0000 (UTC) Subject: [commit: packages/unix] master: Add since-annotations to new fileSync ops (dbec02c) Message-ID: <20150319155100.B92A63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dbec02cc26afd39a35a932dc013175664e3a47eb/unix >--------------------------------------------------------------- commit dbec02cc26afd39a35a932dc013175664e3a47eb Author: Herbert Valerio Riedel Date: Mon Dec 15 23:28:20 2014 +0100 Add since-annotations to new fileSync ops >--------------------------------------------------------------- dbec02cc26afd39a35a932dc013175664e3a47eb System/Posix/Unistd.hsc | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/System/Posix/Unistd.hsc b/System/Posix/Unistd.hsc index 2cbfaa2..3b8d2e4 100644 --- a/System/Posix/Unistd.hsc +++ b/System/Posix/Unistd.hsc @@ -228,6 +228,8 @@ foreign import ccall unsafe "sysconf" -- Throws 'IOError' (\"unsupported operation\") if platform does not -- provide @fsync(2)@ (use @#if HAVE_FSYNC@ CPP guard to -- detect availability). +-- +-- /Since: 2.7.1.0/ fileSynchronise :: Fd -> IO () #if HAVE_FSYNC fileSynchronise fd = do @@ -247,6 +249,8 @@ fileSynchronise _ = ioError (ioeSetLocation unsupportedOperation -- Throws 'IOError' (\"unsupported operation\") if platform does not -- provide @fdatasync(2)@ (use @#if HAVE_FDATASYNC@ CPP guard to -- detect availability). +-- +-- /Since: 2.7.1.0/ fileSynchroniseDataOnly :: Fd -> IO () #if HAVE_FDATASYNC fileSynchroniseDataOnly fd = do From git at git.haskell.org Thu Mar 19 15:51:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:51:02 +0000 (UTC) Subject: [commit: packages/unix] master: Be more explicit in WARNING what will be thrown (757bf44) Message-ID: <20150319155102.C25353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/757bf44bb4895fc561a2e5dd2f602168478741ec/unix >--------------------------------------------------------------- commit 757bf44bb4895fc561a2e5dd2f602168478741ec Author: Herbert Valerio Riedel Date: Mon Dec 15 23:33:15 2014 +0100 Be more explicit in WARNING what will be thrown >--------------------------------------------------------------- 757bf44bb4895fc561a2e5dd2f602168478741ec System/Posix/Unistd.hsc | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/System/Posix/Unistd.hsc b/System/Posix/Unistd.hsc index 3b8d2e4..3f2d115 100644 --- a/System/Posix/Unistd.hsc +++ b/System/Posix/Unistd.hsc @@ -239,7 +239,7 @@ foreign import capi safe "unistd.h fsync" c_fsync :: Fd -> IO CInt #else {-# WARNING fileSynchronise - "operation will throw exception (CPP guard: @#if HAVE_FSYNC@)" #-} + "operation will throw 'IOError' \"unsupported operation\" (CPP guard: @#if HAVE_FSYNC@)" #-} fileSynchronise _ = ioError (ioeSetLocation unsupportedOperation "fileSynchronise") #endif @@ -260,7 +260,7 @@ foreign import capi safe "unistd.h fdatasync" c_fdatasync :: Fd -> IO CInt #else {-# WARNING fileSynchroniseDataOnly - "operation will throw exception (CPP guard: @#if HAVE_FDATASYNC@)" #-} + "operation will throw 'IOError' \"unsupported operation\" (CPP guard: @#if HAVE_FDATASYNC@)" #-} fileSynchroniseDataOnly _ = ioError (ioeSetLocation unsupportedOperation "fileSynchroniseDataOnly") #endif From git at git.haskell.org Thu Mar 19 15:51:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:51:04 +0000 (UTC) Subject: [commit: packages/unix] master: Fix SIGINFO and SIGWINCH. (3c4ced4) Message-ID: <20150319155104.CC44C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3c4ced48d5d82bc3042fdd058e684e87e7036166/unix >--------------------------------------------------------------- commit 3c4ced48d5d82bc3042fdd058e684e87e7036166 Author: Erik de Castro Lopo Date: Fri Dec 19 14:47:43 2014 +1100 Fix SIGINFO and SIGWINCH. It seems these two signals have not been working since at least 2009. Detection of these signals seems to have never been added to the configure.ac script and the code guarded by #ifdef then bit-rotted (the idiom used to handle these signals seems to have been abandoned for something simpler/better in 2009). This fix simply handles these signals the same way the other signals are handled in System/Posix/Signals.hsc. Closes #30 and #31 >--------------------------------------------------------------- 3c4ced48d5d82bc3042fdd058e684e87e7036166 System/Posix/Signals/Exts.hsc | 49 +++++++++++++++---------------------------- cbits/HsUnix.c | 7 ------- changelog.md | 2 ++ configure.ac | 2 +- include/HsUnix.h | 7 ------- 5 files changed, 20 insertions(+), 47 deletions(-) diff --git a/System/Posix/Signals/Exts.hsc b/System/Posix/Signals/Exts.hsc index a889340..95796a2 100644 --- a/System/Posix/Signals/Exts.hsc +++ b/System/Posix/Signals/Exts.hsc @@ -1,10 +1,7 @@ +{-# LANGUAGE CPP #-} #ifdef __GLASGOW_HASKELL__ -#if defined(SIGINFO) || defined(SIGWINCH) -{-# LANGUAGE Trustworthy #-} -#else {-# LANGUAGE Safe #-} #endif -#endif ----------------------------------------------------------------------------- -- | @@ -20,45 +17,33 @@ -- ----------------------------------------------------------------------------- -#include "HsUnix.h" - -module System.Posix.Signals.Exts ( - module System.Posix.Signals +#include "HsUnixConfig.h" +##include "HsUnixConfig.h" -#ifdef SIGINFO - , infoEvent, sigINFO -#endif -#ifdef SIGWINCH - , windowChange, sigWINCH +#ifdef HAVE_SIGNAL_H +#include #endif +module System.Posix.Signals.Exts ( + module System.Posix.Signals + , sigINFO + , sigWINCH + , infoEvent + , windowChange ) where import Foreign.C import System.Posix.Signals -#ifdef __HUGS__ -# ifdef SIGINFO -sigINFO = (#const SIGINFO) :: CInt -# endif -# ifdef SIGWINCH -sigWINCH = (#const SIGWINCH) :: CInt -# endif -#else /* !HUGS */ -# ifdef SIGINFO -foreign import ccall unsafe "__hsunix_SIGINFO" sigINFO :: CInt -# endif -# ifdef SIGWINCH -foreign import ccall unsafe "__hsunix_SIGWINCH" sigWINCH :: CInt -# endif -#endif /* !HUGS */ +sigINFO :: CInt +sigINFO = CONST_SIGINFO + +sigWINCH :: CInt +sigWINCH = CONST_SIGWINCH + -#ifdef SIGINFO infoEvent :: Signal infoEvent = sigINFO -#endif -#ifdef SIGWINCH windowChange :: Signal windowChange = sigWINCH -#endif diff --git a/cbits/HsUnix.c b/cbits/HsUnix.c index db97de2..60f19bc 100644 --- a/cbits/HsUnix.c +++ b/cbits/HsUnix.c @@ -24,13 +24,6 @@ void *__hsunix_rtldNext (void) {return RTLD_NEXT;} void *__hsunix_rtldDefault (void) {return RTLD_DEFAULT;} #endif -#ifdef SIGINFO -int __hsunix_SIGINFO(void) { return SIGINFO; } -#endif -#ifdef SIGWINCH -int __hsunix_SIGWINCH(void) { return SIGWINCH; } -#endif - // lstat is a macro on some platforms, so we need a wrapper: int __hsunix_lstat(const char *path, struct stat *buf) { diff --git a/changelog.md b/changelog.md index db6bb48..5d682bc 100644 --- a/changelog.md +++ b/changelog.md @@ -25,6 +25,8 @@ - `fileAdvise` (aka `posix_fadvise(2)`), and - `fileAllocate` (aka `posix_fallocate(2)`) + * Fix SIGINFO and SIGWINCH definitions + ## 2.7.0.1 *Mar 2014* * Bundled with GHC 7.8.1 diff --git a/configure.ac b/configure.ac index 1c82c36..f7b1afb 100644 --- a/configure.ac +++ b/configure.ac @@ -76,7 +76,7 @@ AC_CHECK_FUNCS([posix_fadvise posix_fallocate]) AC_SEARCH_LIBS(shm_open, rt, [AC_CHECK_FUNCS([shm_open shm_unlink])]) AS_IF([test "x$ac_cv_search_shm_open" = x-lrt], [EXTRA_LIBS="$EXTRA_LIBS rt"]) -FP_CHECK_CONSTS([SIGABRT SIGALRM SIGBUS SIGCHLD SIGCONT SIGFPE SIGHUP SIGILL SIGINT SIGKILL SIGPIPE SIGQUIT SIGSEGV SIGSTOP SIGTERM SIGTSTP SIGTTIN SIGTTOU SIGUSR1 SIGUSR2 SIGPOLL SIGPROF SIGSYS SIGTRAP SIGURG SIGVTALRM SIGXCPU SIGXFSZ SIG_BLOCK SIG_SETMASK SIG_UNBLOCK], [ +FP_CHECK_CONSTS([SIGABRT SIGALRM SIGBUS SIGCHLD SIGCONT SIGFPE SIGHUP SIGILL SIGINT SIGKILL SIGPIPE SIGQUIT SIGSEGV SIGSTOP SIGTERM SIGTSTP SIGTTIN SIGTTOU SIGUSR1 SIGUSR2 SIGPOLL SIGPROF SIGSYS SIGTRAP SIGURG SIGVTALRM SIGXCPU SIGXFSZ SIG_BLOCK SIG_SETMASK SIG_UNBLOCK SIGINFO SIGWINCH], [ #if HAVE_SIGNAL_H #include #endif]) diff --git a/include/HsUnix.h b/include/HsUnix.h index a23f0f9..ba3e053 100644 --- a/include/HsUnix.h +++ b/include/HsUnix.h @@ -119,13 +119,6 @@ fall back to O_FSYNC, which should be the same */ #define O_SYNC O_FSYNC #endif -#ifdef SIGINFO -int __hsunix_SIGINFO(); -#endif -#ifdef SIGWINCH -int __hsunix_SIGWINCH(); -#endif - // lstat is a macro on some platforms, so we need a wrapper: int __hsunix_lstat(const char *path, struct stat *buf); From git at git.haskell.org Thu Mar 19 15:51:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:51:06 +0000 (UTC) Subject: [commit: packages/unix] master: Tighten SafeHaskell (e5a2411) Message-ID: <20150319155106.D5DE73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e5a24114f52d82d4405dfec0f294f39b13696ea3/unix >--------------------------------------------------------------- commit e5a24114f52d82d4405dfec0f294f39b13696ea3 Author: Herbert Valerio Riedel Date: Fri Dec 19 09:57:00 2014 +0100 Tighten SafeHaskell This was forgotten in e14fbe2cb3bbd604dadcc3847882ca37edf548b3 >--------------------------------------------------------------- e5a24114f52d82d4405dfec0f294f39b13696ea3 System/Posix/Fcntl.hsc | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/System/Posix/Fcntl.hsc b/System/Posix/Fcntl.hsc index a45f559..7760bb5 100644 --- a/System/Posix/Fcntl.hsc +++ b/System/Posix/Fcntl.hsc @@ -1,5 +1,7 @@ {-# LANGUAGE CApiFFI #-} -#ifdef __GLASGOW_HASKELL__ +#if __GLASGOW_HASKELL__ >= 709 +{-# LANGUAGE Safe #-} +#elif __GLASGOW_HASKELL__ >= 703 {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- From git at git.haskell.org Thu Mar 19 15:51:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:51:08 +0000 (UTC) Subject: [commit: packages/unix] master: Fix markdown markup [skip ci] (396d30e) Message-ID: <20150319155108.DC61F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/396d30ed26fd57b99dbb701ff6ee0c0d378f4600/unix >--------------------------------------------------------------- commit 396d30ed26fd57b99dbb701ff6ee0c0d378f4600 Author: Herbert Valerio Riedel Date: Fri Dec 19 09:59:44 2014 +0100 Fix markdown markup [skip ci] >--------------------------------------------------------------- 396d30ed26fd57b99dbb701ff6ee0c0d378f4600 changelog.md | 9 ++------- 1 file changed, 2 insertions(+), 7 deletions(-) diff --git a/changelog.md b/changelog.md index 5d682bc..68e750b 100644 --- a/changelog.md +++ b/changelog.md @@ -6,25 +6,20 @@ * Tighten `SafeHaskell` bounds for GHC 7.10+ * Add haddock comments on `RTLD_NEXT` and `RTLD_DEFAULT` * Deprecate function `haveRtldLocal` - * Fix `getGroupEntryForID/getGroupEntryForName' on Solaris. Solaris uses - CPP macros for required getgrgid_r and getgrnam_r functions definition + * Fix `getGroupEntryForID/getGroupEntryForName` on Solaris. Solaris uses + CPP macros for required `getgrgid_r` and `getgrnam_r` functions definition so the fix is to change from C ABI calling convention to C API calling convention * Fix potential type-mismatch in `telldir`/`seekdir` FFI imports - * Use CAPI FFI import for `truncate` to make sure the LFS-version is used. - * `executeFile`: Fix `ENOTDIR` error for entries with non-directory components in `PATH` (and instead skip over non-directory `PATH`-elements) - * New functions in `System.Posix.Unistd`: - `fileSynchronise` (aka `fsync(2)`), and - `fileSynchroniseDataOnly` (aka `fdatasync(2)`) - * New module `System.Posix.Fcntl` providing - `fileAdvise` (aka `posix_fadvise(2)`), and - `fileAllocate` (aka `posix_fallocate(2)`) - * Fix SIGINFO and SIGWINCH definitions ## 2.7.0.1 *Mar 2014* From git at git.haskell.org Thu Mar 19 15:51:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:51:10 +0000 (UTC) Subject: [commit: packages/unix] master: Tweak markdown markup again [skip ci] (9a9ea92) Message-ID: <20150319155110.E35F73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9a9ea9294c2cb201054cc554a1086045eeca15cf/unix >--------------------------------------------------------------- commit 9a9ea9294c2cb201054cc554a1086045eeca15cf Author: Herbert Valerio Riedel Date: Fri Dec 19 10:01:32 2014 +0100 Tweak markdown markup again [skip ci] >--------------------------------------------------------------- 9a9ea9294c2cb201054cc554a1086045eeca15cf changelog.md | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/changelog.md b/changelog.md index 68e750b..3a04bfc 100644 --- a/changelog.md +++ b/changelog.md @@ -3,23 +3,33 @@ ## 2.7.1.0 *Dec 2014* * Add support for `base-4.8.0.0` + * Tighten `SafeHaskell` bounds for GHC 7.10+ + * Add haddock comments on `RTLD_NEXT` and `RTLD_DEFAULT` + * Deprecate function `haveRtldLocal` + * Fix `getGroupEntryForID/getGroupEntryForName` on Solaris. Solaris uses CPP macros for required `getgrgid_r` and `getgrnam_r` functions definition so the fix is to change from C ABI calling convention to C API calling convention + * Fix potential type-mismatch in `telldir`/`seekdir` FFI imports + * Use CAPI FFI import for `truncate` to make sure the LFS-version is used. + * `executeFile`: Fix `ENOTDIR` error for entries with non-directory components in `PATH` (and instead skip over non-directory `PATH`-elements) + * New functions in `System.Posix.Unistd`: - `fileSynchronise` (aka `fsync(2)`), and - `fileSynchroniseDataOnly` (aka `fdatasync(2)`) + * New module `System.Posix.Fcntl` providing - `fileAdvise` (aka `posix_fadvise(2)`), and - `fileAllocate` (aka `posix_fallocate(2)`) + * Fix SIGINFO and SIGWINCH definitions ## 2.7.0.1 *Mar 2014* From git at git.haskell.org Thu Mar 19 15:51:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:51:12 +0000 (UTC) Subject: [commit: packages/unix] master: Prepare for 2.7.1.0 release (b3775fa) Message-ID: <20150319155112.EB0F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b3775fa5fd41b3c663ac60e3dc4f68433743ce94/unix >--------------------------------------------------------------- commit b3775fa5fd41b3c663ac60e3dc4f68433743ce94 Author: Herbert Valerio Riedel Date: Fri Dec 19 10:02:18 2014 +0100 Prepare for 2.7.1.0 release >--------------------------------------------------------------- b3775fa5fd41b3c663ac60e3dc4f68433743ce94 changelog.md | 2 ++ unix.cabal | 5 +++-- 2 files changed, 5 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md index 3a04bfc..a2ce61f 100644 --- a/changelog.md +++ b/changelog.md @@ -2,6 +2,8 @@ ## 2.7.1.0 *Dec 2014* + * Bundled with GHC 7.10.1 + * Add support for `base-4.8.0.0` * Tighten `SafeHaskell` bounds for GHC 7.10+ diff --git a/unix.cabal b/unix.cabal index cc9c646..cde94db 100644 --- a/unix.cabal +++ b/unix.cabal @@ -10,7 +10,7 @@ synopsis: POSIX functionality category: System build-type: Configure cabal-version: >= 1.10 -tested-with: GHC==7.6.3, GHC==7.6.2, GHC==7.6.1, GHC==7.4.2, GHC==7.4.1 +tested-with: GHC>=7.4.1 description: This package gives you access to the set of operating system services standardised by POSIX 1003.1b (or the IEEE Portable @@ -48,9 +48,10 @@ library CPP DeriveDataTypeable InterruptibleFFI - NoMonomorphismRestriction + NondecreasingIndentation OverloadedStrings RankNTypes + RecordWildCards if impl(ghc) other-extensions: From git at git.haskell.org Thu Mar 19 15:51:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:51:15 +0000 (UTC) Subject: [commit: packages/unix] master: Add /Since/ annotation to System.Posix.Fcntl (4260c25) Message-ID: <20150319155115.01FA43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4260c25687d3a4bc1ffacdacfbe7e47082ff2550/unix >--------------------------------------------------------------- commit 4260c25687d3a4bc1ffacdacfbe7e47082ff2550 Author: Herbert Valerio Riedel Date: Fri Dec 19 10:51:27 2014 +0100 Add /Since/ annotation to System.Posix.Fcntl >--------------------------------------------------------------- 4260c25687d3a4bc1ffacdacfbe7e47082ff2550 System/Posix/Fcntl.hsc | 3 +++ 1 file changed, 3 insertions(+) diff --git a/System/Posix/Fcntl.hsc b/System/Posix/Fcntl.hsc index 7760bb5..749826f 100644 --- a/System/Posix/Fcntl.hsc +++ b/System/Posix/Fcntl.hsc @@ -16,6 +16,7 @@ -- -- POSIX file control support -- +-- /Since: 2.7.1.0/ ----------------------------------------------------------------------------- #include "HsUnix.h" @@ -42,6 +43,8 @@ import GHC.IO.Exception ( unsupportedOperation ) -- | Advice parameter for 'fileAdvise' operation. -- -- For more details, see documentation of @posix_fadvise(2)@. +-- +-- /Since: 2.7.1.0/ data Advice = AdviceNormal | AdviceRandom From git at git.haskell.org Thu Mar 19 15:51:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:51:17 +0000 (UTC) Subject: [commit: packages/unix] master: rewrite getWorkingDirectory to use allocaBytes for exception safety (6479305) Message-ID: <20150319155117.09E7C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/64793053fbc9a37b5b7887e547f97a3f8c6ed7f6/unix >--------------------------------------------------------------- commit 64793053fbc9a37b5b7887e547f97a3f8c6ed7f6 Author: Marios Titas Date: Tue Dec 23 06:21:57 2014 +0000 rewrite getWorkingDirectory to use allocaBytes for exception safety >--------------------------------------------------------------- 64793053fbc9a37b5b7887e547f97a3f8c6ed7f6 System/Posix/Directory.hsc | 30 +++++++++++++++--------------- System/Posix/Directory/ByteString.hsc | 30 +++++++++++++++--------------- 2 files changed, 30 insertions(+), 30 deletions(-) diff --git a/System/Posix/Directory.hsc b/System/Posix/Directory.hsc index 9dbecb7..7518b4b 100644 --- a/System/Posix/Directory.hsc +++ b/System/Posix/Directory.hsc @@ -116,21 +116,21 @@ foreign import ccall unsafe "__hscore_d_name" -- | @getWorkingDirectory@ calls @getcwd@ to obtain the name -- of the current working directory. getWorkingDirectory :: IO FilePath -getWorkingDirectory = do - p <- mallocBytes long_path_size - go p long_path_size - where go p bytes = do - p' <- c_getcwd p (fromIntegral bytes) - if p' /= nullPtr - then do s <- peekFilePath p' - free p' - return s - else do errno <- getErrno - if errno == eRANGE - then do let bytes' = bytes * 2 - p'' <- reallocBytes p bytes' - go p'' bytes' - else throwErrno "getCurrentDirectory" +getWorkingDirectory = go long_path_size + where + go bytes = do + r <- allocaBytes bytes $ \buf -> do + buf' <- c_getcwd buf (fromIntegral bytes) + if buf' /= nullPtr + then do s <- peekFilePath buf + return (Just s) + else do errno <- getErrno + if errno == eRANGE + -- we use Nothing to indicate that we should + -- try again with a bigger buffer + then return Nothing + else throwErrno "getWorkingDirectory" + maybe (go (2 * bytes)) return r foreign import ccall unsafe "getcwd" c_getcwd :: Ptr CChar -> CSize -> IO (Ptr CChar) diff --git a/System/Posix/Directory/ByteString.hsc b/System/Posix/Directory/ByteString.hsc index 232427c..b1db079 100644 --- a/System/Posix/Directory/ByteString.hsc +++ b/System/Posix/Directory/ByteString.hsc @@ -117,21 +117,21 @@ foreign import ccall unsafe "__hscore_d_name" -- | @getWorkingDirectory@ calls @getcwd@ to obtain the name -- of the current working directory. getWorkingDirectory :: IO RawFilePath -getWorkingDirectory = do - p <- mallocBytes long_path_size - go p long_path_size - where go p bytes = do - p' <- c_getcwd p (fromIntegral bytes) - if p' /= nullPtr - then do s <- peekFilePath p' - free p' - return s - else do errno <- getErrno - if errno == eRANGE - then do let bytes' = bytes * 2 - p'' <- reallocBytes p bytes' - go p'' bytes' - else throwErrno "getCurrentDirectory" +getWorkingDirectory = go long_path_size + where + go bytes = do + r <- allocaBytes bytes $ \buf -> do + buf' <- c_getcwd buf (fromIntegral bytes) + if buf' /= nullPtr + then do s <- peekFilePath buf + return (Just s) + else do errno <- getErrno + if errno == eRANGE + -- we use Nothing to indicate that we should + -- try again with a bigger buffer + then return Nothing + else throwErrno "getWorkingDirectory" + maybe (go (2 * bytes)) return r foreign import ccall unsafe "getcwd" c_getcwd :: Ptr CChar -> CSize -> IO (Ptr CChar) From git at git.haskell.org Thu Mar 19 15:51:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:51:19 +0000 (UTC) Subject: [commit: packages/unix] master: Add GHC 7.10.1 to test-matrix (49aede1) Message-ID: <20150319155119.0FDC93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/49aede104bf3ed1f89f0c27652f913a91f3bc66e/unix >--------------------------------------------------------------- commit 49aede104bf3ed1f89f0c27652f913a91f3bc66e Author: Herbert Valerio Riedel Date: Tue Dec 23 11:17:22 2014 +0100 Add GHC 7.10.1 to test-matrix >--------------------------------------------------------------- 49aede104bf3ed1f89f0c27652f913a91f3bc66e .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index 5b94c8c..ae43717 100644 --- a/.travis.yml +++ b/.travis.yml @@ -7,6 +7,7 @@ env: - CABALVER=1.18 GHCVER=7.8.1 - CABALVER=1.18 GHCVER=7.8.2 - CABALVER=1.18 GHCVER=7.8.3 + - CABALVER=1.22 GHCVER=7.10.1 - CABALVER=head GHCVER=head matrix: From git at git.haskell.org Thu Mar 19 15:51:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:51:21 +0000 (UTC) Subject: [commit: packages/unix] master: Merge pull request #32 from redneb/getcwd-exn-safe (275a51a) Message-ID: <20150319155121.16E733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/275a51ac6fe3b56edd5b43d77a4ac5560ec469d0/unix >--------------------------------------------------------------- commit 275a51ac6fe3b56edd5b43d77a4ac5560ec469d0 Merge: 49aede1 6479305 Author: Gregory Collins Date: Tue Dec 23 19:51:17 2014 -0500 Merge pull request #32 from redneb/getcwd-exn-safe rewrite getWorkingDirectory to use allocaBytes for exception safety >--------------------------------------------------------------- 275a51ac6fe3b56edd5b43d77a4ac5560ec469d0 System/Posix/Directory.hsc | 30 +++++++++++++++--------------- System/Posix/Directory/ByteString.hsc | 30 +++++++++++++++--------------- 2 files changed, 30 insertions(+), 30 deletions(-) From git at git.haskell.org Thu Mar 19 15:51:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:51:23 +0000 (UTC) Subject: [commit: packages/unix] master: Add GHC 7.8.4 to test-matrix (fa24ceb) Message-ID: <20150319155123.1F36C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fa24cebd8246aabc0d590fc22561f90e6b1252df/unix >--------------------------------------------------------------- commit fa24cebd8246aabc0d590fc22561f90e6b1252df Author: Herbert Valerio Riedel Date: Sat Dec 27 19:18:50 2014 +0100 Add GHC 7.8.4 to test-matrix >--------------------------------------------------------------- fa24cebd8246aabc0d590fc22561f90e6b1252df .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index ae43717..19ac588 100644 --- a/.travis.yml +++ b/.travis.yml @@ -7,6 +7,7 @@ env: - CABALVER=1.18 GHCVER=7.8.1 - CABALVER=1.18 GHCVER=7.8.2 - CABALVER=1.18 GHCVER=7.8.3 + - CABALVER=1.18 GHCVER=7.8.4 - CABALVER=1.22 GHCVER=7.10.1 - CABALVER=head GHCVER=head From git at git.haskell.org Thu Mar 19 15:51:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:51:25 +0000 (UTC) Subject: [commit: packages/unix] master: Adds a more comprehensive check for fdatasync (b06446e) Message-ID: <20150319155125.26E283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b06446edd4753f964a46d27ddae864fad97adc13/unix >--------------------------------------------------------------- commit b06446edd4753f964a46d27ddae864fad97adc13 Author: Elliot Robinson Date: Sun Mar 8 15:55:05 2015 -0400 Adds a more comprehensive check for fdatasync Some versions of OS X have fdatasync in the headers but don't include implementations in the standard library. This leads to a compile failure in configure.ac when using AC_CHECK_FUNCS. This change explicitly attempts to compile a file containing a call to fdatasync and properly sets the AC_CHECK_FUNCS flags depending on the result of compilation. >--------------------------------------------------------------- b06446edd4753f964a46d27ddae864fad97adc13 configure.ac | 21 ++++++++++++++++++++- 1 file changed, 20 insertions(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index f7b1afb..c63b45b 100644 --- a/configure.ac +++ b/configure.ac @@ -68,7 +68,26 @@ AC_CHECK_FUNCS([lutimes futimes]) AC_CHECK_FUNCS([mkstemps mkdtemp]) # Functions for file synchronization and allocation control -AC_CHECK_FUNCS([fsync fdatasync]) +AC_CHECK_FUNCS([fsync]) + +# A more comprehensive check that fdatasync exits +# Necessary for platforms that have fdatasync in headers but have no +# implementation +dnl Originally provided by user copiousfreetime for the beanstalkd project +dnl {{{ make sure that fdatasync exits +AC_CACHE_CHECK([for fdatasync],[ac_cv_func_fdatasync],[ + AC_COMPILE_IFELSE([AC_LANG_PROGRAM([[ +#include +]],[[ +fdatasync(4); +]])], +[ac_cv_func_fdatasync=yes], +[ac_cv_func_fdatasync=no]) +]) +AS_IF([test "x${ac_cv_func_fdatasync}" = "xyes"], + [AC_DEFINE([HAVE_FDATASYNC],[1],[If the system defines fdatasync])]) +dnl }}} + AC_CHECK_FUNCS([posix_fadvise posix_fallocate]) # Avoid adding rt if absent or unneeded From git at git.haskell.org Thu Mar 19 15:51:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 15:51:27 +0000 (UTC) Subject: [commit: packages/unix] master: Merge pull request #42 from argiopetech/master (94d8824) Message-ID: <20150319155127.2FE5B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/94d8824bae10c9d91f56c1aee9c45a90136a1770/unix >--------------------------------------------------------------- commit 94d8824bae10c9d91f56c1aee9c45a90136a1770 Merge: fa24ceb b06446e Author: Elliot Robinson Date: Mon Mar 9 04:09:37 2015 -0400 Merge pull request #42 from argiopetech/master Adds a more comprehensive check for fdatasync >--------------------------------------------------------------- 94d8824bae10c9d91f56c1aee9c45a90136a1770 configure.ac | 21 ++++++++++++++++++++- 1 file changed, 20 insertions(+), 1 deletion(-) From git at git.haskell.org Thu Mar 19 16:21:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 16:21:01 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Major rewrite: Pt 7: Some cleanup and print to see current state of the impl (9bbe8f5) Message-ID: <20150319162101.491403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/9bbe8f5965a26b179e3d3c7d9577a639c54a4fc2/ghc >--------------------------------------------------------------- commit 9bbe8f5965a26b179e3d3c7d9577a639c54a4fc2 Author: George Karachalias Date: Thu Mar 19 17:19:42 2015 +0100 Major rewrite: Pt 7: Some cleanup and print to see current state of the impl >--------------------------------------------------------------- 9bbe8f5965a26b179e3d3c7d9577a639c54a4fc2 compiler/deSugar/Check.hs | 38 ++++++++++++++++++++++++++------------ 1 file changed, 26 insertions(+), 12 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 7fc22e7..9328660 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -47,6 +47,7 @@ import MonadUtils -- MonadIO import Var (EvVar) import Type +import TcRnTypes ( pprInTcRnIf ) import UniqSupply ( UniqSupply , splitUniqSupply -- :: UniqSupply -> (UniqSupply, UniqSupply) , listSplitUniqSupply -- :: UniqSupply -> [UniqSupply] @@ -146,6 +147,14 @@ checkpm tys eq_info checkpm' :: [Type] -> Uncovered -> [EquationInfo] -> PmM PmResult checkpm' _tys uncovered_set [] = return ([],[], bagToList uncovered_set) checkpm' tys uncovered_set (eq_info:eq_infos) = do + + -- --------------------------------------------------------------------- + -- Let's check how well we do at the moment + usupply <- getUniqueSupplyM + let translated = translateEqnInfo usupply eq_info + pprInTcRnIf (ppr translated) + -- --------------------------------------------------------------------- + invec <- preprocess_match eq_info (covers, us, forces) <- process_vector tys uncovered_set invec let (redundant, inaccessible) @@ -781,12 +790,10 @@ translatePat usupply pat = case pat of SigPatOut p ty -> translatePat usupply (unLoc p) -- COMEHERE: FIXME: Exploit the signature? CoPat wrapper p ty -> translatePat usupply p -- COMEHERE: Make sure the coercion is not useful NPlusKPat n k ge minus -> - let x = mkPmId usupply (idType (unLoc n)) -- x as Id - xe = noLoc (HsVar x) -- x as located expression + let (xp, xe) = mkPmId2Forms usupply (idType (unLoc n)) ke = noLoc (HsOverLit k) -- k as located expression np = [VarAbs (unLoc n)] -- n as a list of value abstractions - xp = VarAbs x -- x g1 = eqTrueExpr $ OpApp xe (noLoc ge) no_fixity ke -- True <- (x >= k) g2 = GBindAbs np $ OpApp xe (noLoc minus) no_fixity ke -- n <- (x - k) in [xp, g1, g2] @@ -794,27 +801,22 @@ translatePat usupply pat = case pat of ViewPat lexpr lpat arg_ty -> let (usupply1, usupply2) = splitUniqSupply usupply - x = mkPmId usupply1 arg_ty -- x as Id - xe = noLoc (HsVar x) -- x as located expression + (xp, xe) = mkPmId2Forms usupply1 arg_ty ps = translatePat usupply2 (unLoc lpat) -- p translated recursively - xp = VarAbs x -- x g = GBindAbs ps (HsApp lexpr xe) -- p <- f x in [xp,g] ListPat lpats elem_ty (Just (pat_ty, to_list)) -> let (usupply1, usupply2) = splitUniqSupply usupply - x = mkPmId usupply1 (hsPatType pat) -- x as Id - xe = noLoc (HsVar x) -- x as located expression + (xp, xe) = mkPmId2Forms usupply1 (hsPatType pat) ps = translatePats usupply2 (map unLoc lpats) -- list as value abstraction - xp = VarAbs x -- x g = GBindAbs (concat ps) $ HsApp (noLoc to_list) xe -- [...] <- toList x in [xp,g] - - ConPatOut { pat_con = L _ (PatSynCon _) } -> error "COMEHERE: FIXME: Pattern Synonym" -- PATTERN SYNONYM - WHAT TO DO WITH IT? + ConPatOut { pat_con = L _ (PatSynCon _) } -> [mkPmVar usupply (hsPatType pat)] -- ERROR ConPatOut { pat_con = L _ (RealDataCon con), pat_args = ps } -> -- DO WE NEED OTHER STUFF FROM IT? [ConAbs con (translateConPats usupply con ps)] @@ -826,7 +828,7 @@ translatePat usupply pat = case pat of expr = OpApp hs_var (noLoc eq) no_fixity expr_lit -- COMEHERE: I do not like the noLoc thing in [VarAbs var, eqTrueExpr expr] - LitPat lit -> error "COMEHERE" -- [mkPmVar usupply (hsPatType pat)] -- COMEHERE: Wrong. Should be like NPat (which eq to use?) + LitPat lit -> [mkPmVar usupply (hsPatType pat)] -- ERROR: Which eq to use?? ListPat ps ty Nothing -> -- WHAT TO DO WITH TY?? let tidy_ps = translatePats usupply (map unLoc ps) @@ -864,6 +866,12 @@ translatePats :: UniqSupply -> [Pat Id] -> [PatternVec] -- Do not concatenate th translatePats usupply pats = map (uncurry translatePat) uniqs_pats where uniqs_pats = listSplitUniqSupply usupply `zip` pats +-- ----------------------------------------------------------------------- +-- Temporary function +translateEqnInfo :: UniqSupply -> EquationInfo -> [PatternVec] +translateEqnInfo usupply (EqnInfo { eqn_pats = ps }) = translatePats usupply ps +-- ----------------------------------------------------------------------- + translateConPats :: UniqSupply -> DataCon -> HsConPatDetails Id -> PatternVec translateConPats usupply _ (PrefixCon ps) = concat (translatePats usupply (map unLoc ps)) translateConPats usupply _ (InfixCon p1 p2) = concat (translatePats usupply (map unLoc [p1,p2])) @@ -891,6 +899,12 @@ mkPmId usupply ty = mkLocalId name ty occname = mkVarOccFS (fsLit (show unique)) name = mkInternalName unique occname noSrcSpan +-- Generate a *fresh* Id using the given UniqSupply and Type. We often need it +-- in 2 different forms: Variable Abstraction and Variable Expression +mkPmId2Forms :: UniqSupply -> Type -> (PmPat2 abs, LHsExpr Id) +mkPmId2Forms usupply ty = (VarAbs x, noLoc (HsVar x)) + where x = mkPmId usupply ty + -- ---------------------------------------------------------------------------- -- | Utility function `tailValSetAbs' and `wrapK' From git at git.haskell.org Thu Mar 19 16:42:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 16:42:46 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Use the gold linker for linux/ARM and android/ARM targets. (a86fe8a) Message-ID: <20150319164246.E7BE63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/a86fe8a4602e8e57f3aff3f2bc78055a8fa8fe2e/ghc >--------------------------------------------------------------- commit a86fe8a4602e8e57f3aff3f2bc78055a8fa8fe2e Author: Erik de Castro Lopo Date: Thu Mar 12 14:36:50 2015 +1100 Use the gold linker for linux/ARM and android/ARM targets. Fixes #8976 and #9873 by making use of the Binutils ld.gold linker explicit whenever the target is linux/ARM or android/ARM. This does not affect iOS where Apple provides its own linker. In order to achieve this, we need to add `-fuse-ld=gold` to the SettingsCCompilerLinkFlags setting and set SettingsLdCommand to `ld.gold` (or `${target}-ld.gold` when cross-compiling). In addition, simplifying the use of `$(CONF_GCC_LINKER_OPTS_STAGEn)`. This patch was tested by ensuring that the following worked as expected: * Native builds on linux/x86_64 (nothing changed). * Native builds on linux/arm (and uses the gold linker). * Linux to linux/arm cross compiles (and uses the cross gold linker). Contributions by Ben Gamari, Joachim Breitner and Reid Barton. Reviewers: nomeata, bgamari, austin, rwbarton Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D715 GHC Trac Issues: #8976 #9873 (cherry picked from commit 71fcc4c096ec0b575522e4c2d0104ef7a71a13c5) >--------------------------------------------------------------- a86fe8a4602e8e57f3aff3f2bc78055a8fa8fe2e aclocal.m4 | 5 +++++ configure.ac | 13 ++++++++++++- libffi/ghc.mk | 2 +- mk/config.mk.in | 1 - rules/build-package-data.mk | 2 +- rules/distdir-opts.mk | 1 - 6 files changed, 19 insertions(+), 5 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 0cc9dcc..141a42d 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -565,6 +565,11 @@ AC_DEFUN([FPTOOLS_SET_C_LD_FLAGS], $3="$$3 -D_HPUX_SOURCE" $5="$$5 -D_HPUX_SOURCE" ;; + arm*linux*) + # On arm/linux and arm/android, tell gcc to link using the gold linker. + # Forcing LD to be ld.gold is done in configre.ac. + $3="$$3 -fuse-ld=gold" + ;; esac # If gcc knows about the stack protector, turn it off. diff --git a/configure.ac b/configure.ac index 689ebd8..b357f19 100644 --- a/configure.ac +++ b/configure.ac @@ -489,7 +489,18 @@ FP_CPP_CMD_WITH_ARGS(HaskellCPPCmd, HaskellCPPArgs) dnl ** Which ld to use? dnl -------------------------------------------------------------- FP_ARG_WITH_PATH_GNU_PROG([LD], [ld], [ld]) -LdCmd="$LD" +case $target in +arm*linux*) + # Arm requires use of the binutils ld.gold linker. + # This case should catch at least arm-unknown-linux-gnueabihf and + # arm-linux-androideabi. + FP_ARG_WITH_PATH_GNU_PROG([LD_GOLD], [ld.gold], [ld.gold]) + LdCmd="$LD_GOLD" + ;; +*) + LdCmd="$LD" + ;; +esac AC_SUBST([LdCmd]) dnl ** Which nm to use? diff --git a/libffi/ghc.mk b/libffi/ghc.mk index abbe87f..a5645de 100644 --- a/libffi/ghc.mk +++ b/libffi/ghc.mk @@ -100,7 +100,7 @@ $(libffi_STAMP_CONFIGURE): $(TOUCH_DEP) NM=$(NM) \ RANLIB=$(REAL_RANLIB_CMD) \ CFLAGS="$(SRC_CC_OPTS) $(CONF_CC_OPTS_STAGE1) -w" \ - LDFLAGS="$(SRC_LD_OPTS) $(CONF_GCC_LINKER_OPTS_STAGE1) -w" \ + LDFLAGS="$(SRC_LD_OPTS) -w" \ "$(SHELL)" ./configure \ --prefix=$(TOP)/libffi/build/inst \ --libdir=$(TOP)/libffi/build/inst/lib \ diff --git a/mk/config.mk.in b/mk/config.mk.in index 42720c8..49d8610 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -568,7 +568,6 @@ define set_stage_HSC2HS_OPTS # $1 = stage SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --cflag=,$$(filter-out -O,$$(SRC_CC_OPTS) $$(CONF_CC_OPTS_STAGE$1))) SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --cflag=,$$(CONF_CPP_OPTS_STAGE$1)) -SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --lflag=,$$(CONF_GCC_LINKER_OPTS_STAGE$1)) endef $(eval $(call set_stage_HSC2HS_OPTS,0)) $(eval $(call set_stage_HSC2HS_OPTS,1)) diff --git a/rules/build-package-data.mk b/rules/build-package-data.mk index 494b89a..817bf8d 100644 --- a/rules/build-package-data.mk +++ b/rules/build-package-data.mk @@ -50,7 +50,7 @@ endif # for a feature it may not generate warning-free C code, and thus may # think that the feature doesn't exist if -Werror is on. $1_$2_CONFIGURE_CFLAGS = $$(filter-out -Werror,$$(SRC_CC_OPTS)) $$(CONF_CC_OPTS_STAGE$3) $$($1_CC_OPTS) $$($1_$2_CC_OPTS) $$(SRC_CC_WARNING_OPTS) -$1_$2_CONFIGURE_LDFLAGS = $$(SRC_LD_OPTS) $$(CONF_GCC_LINKER_OPTS_STAGE$3) $$($1_LD_OPTS) $$($1_$2_LD_OPTS) +$1_$2_CONFIGURE_LDFLAGS = $$(SRC_LD_OPTS) $$($1_LD_OPTS) $$($1_$2_LD_OPTS) $1_$2_CONFIGURE_CPPFLAGS = $$(SRC_CPP_OPTS) $$(CONF_CPP_OPTS_STAGE$3) $$($1_CPP_OPTS) $$($1_$2_CPP_OPTS) $1_$2_CONFIGURE_OPTS += --configure-option=CFLAGS="$$($1_$2_CONFIGURE_CFLAGS)" diff --git a/rules/distdir-opts.mk b/rules/distdir-opts.mk index 3126a88..b2f0d1b 100644 --- a/rules/distdir-opts.mk +++ b/rules/distdir-opts.mk @@ -65,7 +65,6 @@ $1_$2_DIST_LD_LIB_DIRS := $$(subst $$(space)',$$(space)-L',$$(space)$$($1_$2_DEP endif $1_$2_DIST_LD_OPTS = \ - $$(CONF_GCC_LINKER_OPTS_STAGE$3) \ $$(SRC_LD_OPTS) \ $$($1_LD_OPTS) \ $$($1_$2_LD_OPTS) \ From git at git.haskell.org Thu Mar 19 16:42:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 16:42:49 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix build on amd64/solaris. (072cc76) Message-ID: <20150319164249.EED7E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/072cc766016bf4a09a477f98bb16cf55b253c4f6/ghc >--------------------------------------------------------------- commit 072cc766016bf4a09a477f98bb16cf55b253c4f6 Author: Erik de Castro Lopo Date: Fri Mar 13 20:38:13 2015 +0000 Fix build on amd64/solaris. Summary: Commit 71fcc4c096ec0 breaks the 64bit build on Solaris 11. Solaris is a multi-lib OS so both 32bit and 64bit binaries may be run, but by default it compiles to 32bit so that -m64 needs to be added in the appropriate place when compiling for 64 bits. Patch-from: Karel Gardas Reviewers: kgardas, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D733 (cherry picked from commit 83afcd174cdbf4fb770371da764f91ca9ad414a7) >--------------------------------------------------------------- 072cc766016bf4a09a477f98bb16cf55b253c4f6 mk/config.mk.in | 1 + 1 file changed, 1 insertion(+) diff --git a/mk/config.mk.in b/mk/config.mk.in index 49d8610..42720c8 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -568,6 +568,7 @@ define set_stage_HSC2HS_OPTS # $1 = stage SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --cflag=,$$(filter-out -O,$$(SRC_CC_OPTS) $$(CONF_CC_OPTS_STAGE$1))) SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --cflag=,$$(CONF_CPP_OPTS_STAGE$1)) +SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --lflag=,$$(CONF_GCC_LINKER_OPTS_STAGE$1)) endef $(eval $(call set_stage_HSC2HS_OPTS,0)) $(eval $(call set_stage_HSC2HS_OPTS,1)) From git at git.haskell.org Thu Mar 19 16:44:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 16:44:57 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update Cabal submodule to 1.22 branch tip (7c132c0) Message-ID: <20150319164457.2A8173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/7c132c02436fadaa70674bbfe38b21a67c4fed3a/ghc >--------------------------------------------------------------- commit 7c132c02436fadaa70674bbfe38b21a67c4fed3a Author: Herbert Valerio Riedel Date: Thu Mar 19 17:41:48 2015 +0100 Update Cabal submodule to 1.22 branch tip >--------------------------------------------------------------- 7c132c02436fadaa70674bbfe38b21a67c4fed3a libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index cbd9d53..b7b98fc 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit cbd9d53bc028717323417316a5ed10d65c704d87 +Subproject commit b7b98fc4a1603eec5af7efcab13afadee1da6c3a From git at git.haskell.org Thu Mar 19 17:10:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 17:10:30 +0000 (UTC) Subject: [commit: ghc] master: Update filepath/hpc/process submodules (6b3a7f4) Message-ID: <20150319171030.A94BC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6b3a7f43e88c78ff6cf71d2ef88d17626460fdbe/ghc >--------------------------------------------------------------- commit 6b3a7f43e88c78ff6cf71d2ef88d17626460fdbe Author: Herbert Valerio Riedel Date: Thu Mar 19 16:44:51 2015 +0100 Update filepath/hpc/process submodules These updates these 3 submodules to their respective released tagged commits. No source-code changes are involved with this update. >--------------------------------------------------------------- 6b3a7f43e88c78ff6cf71d2ef88d17626460fdbe libraries/filepath | 2 +- libraries/hpc | 2 +- libraries/process | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/filepath b/libraries/filepath index 4206435..81375ae 160000 --- a/libraries/filepath +++ b/libraries/filepath @@ -1 +1 @@ -Subproject commit 4206435bda0929d7a65fc42e5c8629212328120c +Subproject commit 81375ae0c892b5951f2c1184c655a8f3a5193c9c diff --git a/libraries/hpc b/libraries/hpc index f601495..154eecf 160000 --- a/libraries/hpc +++ b/libraries/hpc @@ -1 +1 @@ -Subproject commit f601495ac5f93f24cbcaa95f45b1bc26ad644ac9 +Subproject commit 154eecf3ca10f9252bf75213d091221ee3c551d6 diff --git a/libraries/process b/libraries/process index c8cdaef..67efaf5 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit c8cdaef5585717089a53be61cb6f08b3120f18b4 +Subproject commit 67efaf599a03f454a98a3905820ce40aa80825c7 From git at git.haskell.org Thu Mar 19 17:10:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 17:10:33 +0000 (UTC) Subject: [commit: ghc] master: Update Cabal submodule to 1.22 branch tip (c4aa959) Message-ID: <20150319171033.7391F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c4aa959bd771f7e69c7f0da1e857599f513d5331/ghc >--------------------------------------------------------------- commit c4aa959bd771f7e69c7f0da1e857599f513d5331 Author: Herbert Valerio Riedel Date: Thu Mar 19 17:41:48 2015 +0100 Update Cabal submodule to 1.22 branch tip >--------------------------------------------------------------- c4aa959bd771f7e69c7f0da1e857599f513d5331 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index cbd9d53..b7b98fc 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit cbd9d53bc028717323417316a5ed10d65c704d87 +Subproject commit b7b98fc4a1603eec5af7efcab13afadee1da6c3a From git at git.haskell.org Thu Mar 19 18:15:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 18:15:15 +0000 (UTC) Subject: [commit: ghc] master: Remove comments and flag for GranSim (9d81980) Message-ID: <20150319181515.F0D7C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9d819804bc0ccf1fed384a4145014c257e85e848/ghc >--------------------------------------------------------------- commit 9d819804bc0ccf1fed384a4145014c257e85e848 Author: Thomas Miedema Date: Thu Mar 19 19:11:09 2015 +0100 Remove comments and flag for GranSim The GranSim code was removed in dd56e9ab and 297b05a9 in 2009, and perhaps other commits I couldn't find. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D737 >--------------------------------------------------------------- 9d819804bc0ccf1fed384a4145014c257e85e848 compiler/cmm/CLabel.hs | 9 --------- compiler/cmm/cmm-notes | 1 - compiler/codeGen/StgCmmBind.hs | 5 +---- compiler/main/DynFlags.hs | 12 ------------ mk/ways.mk | 8 ++------ rts/RtsMain.c | 2 -- rts/Schedule.h | 2 -- rts/Sparks.h | 2 +- rts/Threads.c | 2 -- 9 files changed, 4 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 9d819804bc0ccf1fed384a4145014c257e85e848 From git at git.haskell.org Thu Mar 19 18:15:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 18:15:18 +0000 (UTC) Subject: [commit: ghc] master: Refactor Linker.hs: use System.Directory.findFile (c718bd8) Message-ID: <20150319181518.BCE243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c718bd85caffceb19707d4bacd63b2d3e405aaa9/ghc >--------------------------------------------------------------- commit c718bd85caffceb19707d4bacd63b2d3e405aaa9 Author: Thomas Miedema Date: Thu Mar 19 19:12:32 2015 +0100 Refactor Linker.hs: use System.Directory.findFile Use System.Directory.findFile instead of a custom implementation. Also change FilePath concatenation with ++ by . Refactoring only. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D738 >--------------------------------------------------------------- c718bd85caffceb19707d4bacd63b2d3e405aaa9 compiler/ghci/Linker.hs | 44 +++++++++++++++++--------------------------- 1 file changed, 17 insertions(+), 27 deletions(-) diff --git a/compiler/ghci/Linker.hs b/compiler/ghci/Linker.hs index a2e694e..cb24702 100644 --- a/compiler/ghci/Linker.hs +++ b/compiler/ghci/Linker.hs @@ -62,7 +62,7 @@ import Control.Concurrent.MVar import System.FilePath import System.IO -import System.Directory hiding (findFile) +import System.Directory import Exception @@ -1214,23 +1214,23 @@ locateLib dflags is_hs dirs lib -- we search for .so libraries first. = findHSDll `orElse` findDynObject `orElse` assumeDll where - mk_obj_path dir = dir (lib <.> "o") - mk_dyn_obj_path dir = dir (lib <.> "dyn_o") - mk_arch_path dir = dir ("lib" ++ lib <.> "a") + obj_file = lib <.> "o" + dyn_obj_file = lib <.> "dyn_o" + arch_file = "lib" ++ lib <.> "a" hs_dyn_lib_name = lib ++ '-':programName dflags ++ projectVersion dflags - mk_hs_dyn_lib_path dir = dir mkHsSOName platform hs_dyn_lib_name + hs_dyn_lib_file = mkHsSOName platform hs_dyn_lib_name so_name = mkSOName platform lib - mk_dyn_lib_path dir = case (arch, os) of - (ArchX86_64, OSSolaris2) -> dir ("64/" ++ so_name) - _ -> dir so_name - - findObject = liftM (fmap Object) $ findFile mk_obj_path dirs - findDynObject = liftM (fmap Object) $ findFile mk_dyn_obj_path dirs - findArchive = liftM (fmap Archive) $ findFile mk_arch_path dirs - findHSDll = liftM (fmap DLLPath) $ findFile mk_hs_dyn_lib_path dirs - findDll = liftM (fmap DLLPath) $ findFile mk_dyn_lib_path dirs + dyn_lib_file = case (arch, os) of + (ArchX86_64, OSSolaris2) -> "64" so_name + _ -> so_name + + findObject = liftM (fmap Object) $ findFile dirs obj_file + findDynObject = liftM (fmap Object) $ findFile dirs dyn_obj_file + findArchive = liftM (fmap Archive) $ findFile dirs arch_file + findHSDll = liftM (fmap DLLPath) $ findFile dirs hs_dyn_lib_file + findDll = liftM (fmap DLLPath) $ findFile dirs dyn_lib_file tryGcc = liftM (fmap DLLPath) $ searchForLibUsingGcc dflags so_name dirs assumeDll = return (DLL lib) @@ -1266,16 +1266,16 @@ loadFramework extraPaths rootname = do { either_dir <- tryIO getHomeDirectory ; let homeFrameworkPath = case either_dir of Left _ -> [] - Right dir -> [dir ++ "/Library/Frameworks"] + Right dir -> [dir "Library/Frameworks"] ps = extraPaths ++ homeFrameworkPath ++ defaultFrameworkPaths - ; mb_fwk <- findFile mk_fwk ps + ; mb_fwk <- findFile ps fwk_file ; case mb_fwk of Just fwk_path -> loadDLL fwk_path Nothing -> return (Just "not found") } -- Tried all our known library paths, but dlopen() -- has no built-in paths for frameworks: give up where - mk_fwk dir = dir (rootname ++ ".framework/" ++ rootname) + fwk_file = rootname <.> "framework" rootname -- sorry for the hardcoded paths, I hope they won't change anytime soon: defaultFrameworkPaths = ["/Library/Frameworks", "/System/Library/Frameworks"] @@ -1285,16 +1285,6 @@ loadFramework extraPaths rootname ********************************************************************* -} -findFile :: (FilePath -> FilePath) -- Maps a directory path to a file path - -> [FilePath] -- Directories to look in - -> IO (Maybe FilePath) -- The first file path to match -findFile _ [] = return Nothing -findFile mk_file_path (dir : dirs) - = do let file_path = mk_file_path dir - b <- doesFileExist file_path - if b then return (Just file_path) - else findFile mk_file_path dirs - maybePutStr :: DynFlags -> String -> IO () maybePutStr dflags s = when (verbosity dflags > 1) $ From git at git.haskell.org Thu Mar 19 18:15:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 18:15:21 +0000 (UTC) Subject: [commit: ghc] master: Refactor: follow hlint suggestions in Linker.hs (d832b6b) Message-ID: <20150319181521.923363A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d832b6b4e899b1ec2d1bec9687de821ba8d2b67e/ghc >--------------------------------------------------------------- commit d832b6b4e899b1ec2d1bec9687de821ba8d2b67e Author: Thomas Miedema Date: Thu Mar 19 19:13:09 2015 +0100 Refactor: follow hlint suggestions in Linker.hs Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D739 >--------------------------------------------------------------- d832b6b4e899b1ec2d1bec9687de821ba8d2b67e compiler/ghci/Linker.hs | 16 ++++++---------- 1 file changed, 6 insertions(+), 10 deletions(-) diff --git a/compiler/ghci/Linker.hs b/compiler/ghci/Linker.hs index cb24702..9446e3d 100644 --- a/compiler/ghci/Linker.hs +++ b/compiler/ghci/Linker.hs @@ -58,6 +58,7 @@ import Control.Monad import Data.IORef import Data.List +import Data.Maybe import Control.Concurrent.MVar import System.FilePath @@ -314,7 +315,7 @@ linkCmdLineLibs' dflags@(DynFlags { ldInputs = cmdline_ld_inputs else ([],[]) -- Finally do (c),(d),(e) - ; let cmdline_lib_specs = [ l | Just l <- classified_ld_inputs ] + ; let cmdline_lib_specs = catMaybes classified_ld_inputs ++ libspecs ++ map Framework frameworks ; if null cmdline_lib_specs then return pls @@ -368,7 +369,7 @@ classifyLdInput dflags f where platform = targetPlatform dflags preloadLib :: DynFlags -> [String] -> [String] -> PersistentLinkerState - -> LibrarySpec -> IO (PersistentLinkerState) + -> LibrarySpec -> IO PersistentLinkerState preloadLib dflags lib_paths framework_paths pls lib_spec = do maybePutStr dflags ("Loading object " ++ showLS lib_spec ++ " ... ") case lib_spec of @@ -428,7 +429,7 @@ preloadLib dflags lib_paths framework_paths pls lib_spec ++ sys_errmsg ++ ")\nWhilst trying to load: " ++ showLS spec ++ "\nAdditional directories searched:" ++ (if null paths then " (none)" else - (concat (intersperse "\n" (map (" "++) paths))))) + intercalate "\n" (map (" "++) paths))) -- Not interested in the paths in the static case. preload_static _paths name @@ -1173,9 +1174,7 @@ load_dyn dll = do r <- loadDLL dll loadFrameworks :: Platform -> PackageConfig -> IO () loadFrameworks platform pkg - = if platformUsesFrameworks platform - then mapM_ load frameworks - else return () + = when (platformUsesFrameworks platform) $ mapM_ load frameworks where fw_dirs = Packages.frameworkDirs pkg frameworks = Packages.frameworks pkg @@ -1235,10 +1234,7 @@ locateLib dflags is_hs dirs lib assumeDll = return (DLL lib) infixr `orElse` - f `orElse` g = do m <- f - case m of - Just x -> return x - Nothing -> g + f `orElse` g = f >>= maybe g return platform = targetPlatform dflags arch = platformArch platform From git at git.haskell.org Thu Mar 19 19:21:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 19:21:43 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: compiler: don't warn on -package-name for now (fb326db) Message-ID: <20150319192143.1E5A93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/fb326dba5141f8636cb0c0eb0639b8d0c0caa931/ghc >--------------------------------------------------------------- commit fb326dba5141f8636cb0c0eb0639b8d0c0caa931 Author: Austin Seipp Date: Thu Mar 19 14:21:02 2015 -0500 compiler: don't warn on -package-name for now This avoids the annoying conundrum explained in #9956 - for the 7.10 release, we'll keep (silently) supporting this flag so -Werror doesn't trip anything up. Really, we could just say 'deal with it' to users probably, but the fix is painless and does remove a sharp corner. Signed-off-by: Austin Seipp Reviewers: ezyang Differential Revision: https://phabricator.haskell.org/D742 GHC Trac Issues: #9956 >--------------------------------------------------------------- fb326dba5141f8636cb0c0eb0639b8d0c0caa931 compiler/main/DynFlags.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 4c93657..93c386c 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -2732,9 +2732,7 @@ package_flags = [ (NoArg $ do removeUserPkgConf deprecate "Use -no-user-package-db instead") - , defGhcFlag "package-name" (HasArg $ \name -> do - upd (setPackageKey name) - deprecate "Use -this-package-key instead") + , defGhcFlag "package-name" (hasArg setPackageKey) , defGhcFlag "this-package-key" (hasArg setPackageKey) , defFlag "package-id" (HasArg exposePackageId) , defFlag "package" (HasArg exposePackage) From git at git.haskell.org Thu Mar 19 21:00:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 21:00:02 +0000 (UTC) Subject: [commit: ghc] master: win32/base: Remove redundant import (48ba1e5) Message-ID: <20150319210002.C88E23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/48ba1e5378f908cd4a4c90592b388ae77cac302f/ghc >--------------------------------------------------------------- commit 48ba1e5378f908cd4a4c90592b388ae77cac302f Author: Austin Seipp Date: Thu Mar 19 15:59:20 2015 -0500 win32/base: Remove redundant import This causes ./validate to trip -Werror on Windows. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 48ba1e5378f908cd4a4c90592b388ae77cac302f libraries/base/GHC/Conc/Windows.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/libraries/base/GHC/Conc/Windows.hs b/libraries/base/GHC/Conc/Windows.hs index b77945f..16112cd 100644 --- a/libraries/base/GHC/Conc/Windows.hs +++ b/libraries/base/GHC/Conc/Windows.hs @@ -39,7 +39,6 @@ module GHC.Conc.Windows ) where import Data.Bits (shiftR) -import Data.Typeable import GHC.Base import GHC.Conc.Sync import GHC.Enum (Enum) From git at git.haskell.org Thu Mar 19 21:21:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 21:21:05 +0000 (UTC) Subject: [commit: ghc] master: libraries: update win32 submodule (2ff68c3) Message-ID: <20150319212105.AB1923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2ff68c3589af86811f65991c71f33282e0e50778/ghc >--------------------------------------------------------------- commit 2ff68c3589af86811f65991c71f33282e0e50778 Author: Austin Seipp Date: Thu Mar 19 16:20:26 2015 -0500 libraries: update win32 submodule This update fixes #10165. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 2ff68c3589af86811f65991c71f33282e0e50778 libraries/Win32 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Win32 b/libraries/Win32 index 8fc5486..3b573ee 160000 --- a/libraries/Win32 +++ b/libraries/Win32 @@ -1 +1 @@ -Subproject commit 8fc5486f4e31ddeacd46c6b07d62934c3ce8f378 +Subproject commit 3b573ee058560d1199a19efab10c016278dff252 From git at git.haskell.org Thu Mar 19 21:21:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 21:21:27 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: libraries: update win32 submodule (47cd08a) Message-ID: <20150319212127.05D693A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/47cd08ab94e0a9bae3d9e966777616230d4fb4ff/ghc >--------------------------------------------------------------- commit 47cd08ab94e0a9bae3d9e966777616230d4fb4ff Author: Austin Seipp Date: Thu Mar 19 16:20:26 2015 -0500 libraries: update win32 submodule This update fixes #10165. Signed-off-by: Austin Seipp (cherry picked from commit 2ff68c3589af86811f65991c71f33282e0e50778) >--------------------------------------------------------------- 47cd08ab94e0a9bae3d9e966777616230d4fb4ff libraries/Win32 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Win32 b/libraries/Win32 index 8fc5486..3b573ee 160000 --- a/libraries/Win32 +++ b/libraries/Win32 @@ -1 +1 @@ -Subproject commit 8fc5486f4e31ddeacd46c6b07d62934c3ce8f378 +Subproject commit 3b573ee058560d1199a19efab10c016278dff252 From git at git.haskell.org Thu Mar 19 21:35:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 21:35:57 +0000 (UTC) Subject: [commit: ghc] master: Improve `Typeable` solver. (3a0019e) Message-ID: <20150319213557.2C4C43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3a0019e3672097761e7ce09c811018f774febfd2/ghc >--------------------------------------------------------------- commit 3a0019e3672097761e7ce09c811018f774febfd2 Author: Iavor S. Diatchki Date: Thu Mar 19 13:40:34 2015 -0700 Improve `Typeable` solver. >--------------------------------------------------------------- 3a0019e3672097761e7ce09c811018f774febfd2 compiler/typecheck/TcInteract.hs | 32 ++++++++++++++------------------ 1 file changed, 14 insertions(+), 18 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 8f85dd3..5f54130 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1845,23 +1845,19 @@ isCallStackIP _ _ _ matchTypeableClass :: Class -> Kind -> Type -> CtLoc -> TcS LookupInstResult matchTypeableClass clas k t loc | isForAllTy k = return NoInstance - | Just (tc, ks_tys) <- splitTyConApp_maybe t = doTyConApp tc ks_tys + | Just (tc, ks) <- splitTyConApp_maybe t + , all isKind ks = doTyCon tc ks | Just (f,kt) <- splitAppTy_maybe t = doTyApp f kt - | Just _ <- isNumLitTy t = mkEv [] (EvTypeableTyLit t) - | Just _ <- isStrLitTy t = mkEv [] (EvTypeableTyLit t) + | Just _ <- isNumLitTy t = mkSimpEv (EvTypeableTyLit t) + | Just _ <- isStrLitTy t = mkSimpEv (EvTypeableTyLit t) | otherwise = return NoInstance where - -- Representation for type constructor applied to some kinds and some types. - doTyConApp tc ks_ts = + -- Representation for type constructor applied to some kinds + doTyCon tc ks = case mapM kindRep ks of - Nothing -> return NoInstance -- Not concrete kinds - Just kReps -> - do tCts <- mapM subGoal ts - mkEv tCts (EvTypeableTyCon tc kReps (map ctEvTerm tCts `zip` ts)) - where - (ks,ts) = span isKind ks_ts - + Nothing -> return NoInstance + Just kReps -> mkSimpEv (EvTypeableTyCon tc kReps []) {- Representation for an application of a type to a type-or-kind. This may happen when the type expression starts with a type variable. @@ -1876,7 +1872,9 @@ matchTypeableClass clas k t loc | otherwise = do ct1 <- subGoal f ct2 <- subGoal tk - mkEv [ct1,ct2] (EvTypeableTyApp (ctEvTerm ct1,f) (ctEvTerm ct2,tk)) + let realSubs = [ c | (c,Fresh) <- [ct1,ct2] ] + return $ GenInst realSubs + $ EvTypeable $ EvTypeableTyApp (getEv ct1,f) (getEv ct2,tk) -- Representation for concrete kinds. We just use the kind itself, @@ -1886,13 +1884,11 @@ matchTypeableClass clas k t loc mapM_ kindRep ks return ki + getEv (ct,_fresh) = ctEvTerm ct -- Emit a `Typeable` constraint for the given type. subGoal ty = do let goal = mkClassPred clas [ typeKind ty, ty ] - ev <- newWantedEvVarNC loc goal - return ev - - - mkEv subs ev = return (GenInst subs (EvTypeable ev)) + newWantedEvVar loc goal + mkSimpEv ev = return (GenInst [] (EvTypeable ev)) From git at git.haskell.org Thu Mar 19 21:36:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 21:36:00 +0000 (UTC) Subject: [commit: ghc] master: Merge branch 'master' of git://git.haskell.org/ghc (a07ff3b) Message-ID: <20150319213600.33AFB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a07ff3b0051b2607ef87d4601362e57798107ce4/ghc >--------------------------------------------------------------- commit a07ff3b0051b2607ef87d4601362e57798107ce4 Merge: 3a0019e 2ff68c3 Author: Iavor S. Diatchki Date: Thu Mar 19 14:35:30 2015 -0700 Merge branch 'master' of git://git.haskell.org/ghc >--------------------------------------------------------------- a07ff3b0051b2607ef87d4601362e57798107ce4 libraries/Win32 | 2 +- libraries/base/GHC/Conc/Windows.hs | 1 - 2 files changed, 1 insertion(+), 2 deletions(-) From git at git.haskell.org Thu Mar 19 22:33:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 22:33:50 +0000 (UTC) Subject: [commit: ghc] master: Remove unused parameter to `EvTypeableTyCon` (75ef8b3) Message-ID: <20150319223350.46CEC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/75ef8b3b56f0b33c6be782b59a55b853565ea5f4/ghc >--------------------------------------------------------------- commit 75ef8b3b56f0b33c6be782b59a55b853565ea5f4 Author: Iavor S. Diatchki Date: Thu Mar 19 15:33:50 2015 -0700 Remove unused parameter to `EvTypeableTyCon` >--------------------------------------------------------------- 75ef8b3b56f0b33c6be782b59a55b853565ea5f4 compiler/deSugar/DsBinds.hs | 7 +++---- compiler/typecheck/TcEvidence.hs | 7 +++---- compiler/typecheck/TcHsSyn.hs | 2 +- compiler/typecheck/TcInteract.hs | 2 +- 4 files changed, 8 insertions(+), 10 deletions(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index 079cfbf..488ffa3 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -894,7 +894,7 @@ dsEvTypeable ev = (ty, rep) <- case ev of - EvTypeableTyCon tc ks ts -> + EvTypeableTyCon tc ks -> do ctr <- dsLookupGlobalId mkPolyTyConAppName mkTyCon <- dsLookupGlobalId mkTyConName dflags <- getDynFlags @@ -913,10 +913,9 @@ dsEvTypeable ev = tcRep <- tyConRep dflags mkTyCon tc kReps <- mapM kindRep ks - tReps <- mapM (getRep tyCl) ts - return ( mkTyConApp tc (ks ++ map snd ts) - , mkRep tcRep kReps tReps + return ( mkTyConApp tc ks + , mkRep tcRep kReps [] ) EvTypeableTyApp t1 t2 -> diff --git a/compiler/typecheck/TcEvidence.hs b/compiler/typecheck/TcEvidence.hs index 3eb5a31..bec2415 100644 --- a/compiler/typecheck/TcEvidence.hs +++ b/compiler/typecheck/TcEvidence.hs @@ -735,7 +735,7 @@ data EvTerm -- | Instructions on how to make a 'Typeable' dictionary. data EvTypeable - = EvTypeableTyCon TyCon [Kind] [(EvTerm, Type)] + = EvTypeableTyCon TyCon [Kind] -- ^ Dicitionary for concrete type constructors. | EvTypeableTyApp (EvTerm,Type) (EvTerm,Type) @@ -1015,7 +1015,7 @@ evVarsOfCallStack cs = case cs of evVarsOfTypeable :: EvTypeable -> VarSet evVarsOfTypeable ev = case ev of - EvTypeableTyCon _ _ es -> evVarsOfTerms (map fst es) + EvTypeableTyCon _ _ -> emptyVarSet EvTypeableTyApp e1 e2 -> evVarsOfTerms (map fst [e1,e2]) EvTypeableTyLit _ -> emptyVarSet @@ -1102,8 +1102,7 @@ instance Outputable EvCallStack where instance Outputable EvTypeable where ppr ev = case ev of - EvTypeableTyCon tc ks ts -> parens (ppr tc <+> sep (map ppr ks) <+> - sep (map (ppr . fst) ts)) + EvTypeableTyCon tc ks -> parens (ppr tc <+> sep (map ppr ks)) EvTypeableTyApp t1 t2 -> parens (ppr (fst t1) <+> ppr (fst t2)) EvTypeableTyLit x -> ppr x diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs index e4fb33e..45f384a 100644 --- a/compiler/typecheck/TcHsSyn.hs +++ b/compiler/typecheck/TcHsSyn.hs @@ -1256,7 +1256,7 @@ zonkEvTerm _ (EvLit l) = return (EvLit l) zonkEvTerm env (EvTypeable ev) = fmap EvTypeable $ case ev of - EvTypeableTyCon tc ks ts -> EvTypeableTyCon tc ks `fmap` mapM zonk ts + EvTypeableTyCon tc ks -> return (EvTypeableTyCon tc ks) EvTypeableTyApp t1 t2 -> do e1 <- zonk t1 e2 <- zonk t2 return (EvTypeableTyApp e1 e2) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 5f54130..e83709c 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1857,7 +1857,7 @@ matchTypeableClass clas k t loc doTyCon tc ks = case mapM kindRep ks of Nothing -> return NoInstance - Just kReps -> mkSimpEv (EvTypeableTyCon tc kReps []) + Just kReps -> mkSimpEv (EvTypeableTyCon tc kReps) {- Representation for an application of a type to a type-or-kind. This may happen when the type expression starts with a type variable. From git at git.haskell.org Thu Mar 19 22:41:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 22:41:21 +0000 (UTC) Subject: [commit: ghc] master: testsuite: add a regression test for #10011 (e02ef0e) Message-ID: <20150319224121.53D263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e02ef0e6d4eefa5f065cc1c33795dfa2114cd58e/ghc >--------------------------------------------------------------- commit e02ef0e6d4eefa5f065cc1c33795dfa2114cd58e Author: Austin Seipp Date: Thu Mar 19 17:41:08 2015 -0500 testsuite: add a regression test for #10011 Signed-off-by: Austin Seipp >--------------------------------------------------------------- e02ef0e6d4eefa5f065cc1c33795dfa2114cd58e testsuite/.gitignore | 1 + testsuite/tests/numeric/should_run/T10011.hs | 14 ++++++++++++++ .../tests/numeric/should_run/T10011.stdout | 0 testsuite/tests/numeric/should_run/all.T | 1 + 4 files changed, 16 insertions(+) diff --git a/testsuite/.gitignore b/testsuite/.gitignore index 27ecc02..30188e2 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -1045,6 +1045,7 @@ mk/ghcconfig*_inplace_bin_ghc-stage2.exe.mk /tests/numeric/should_run/T7689 /tests/numeric/should_run/T8726 /tests/numeric/should_run/T9810 +/tests/numeric/should_run/T10011 /tests/numeric/should_run/add2 /tests/numeric/should_run/arith001 /tests/numeric/should_run/arith002 diff --git a/testsuite/tests/numeric/should_run/T10011.hs b/testsuite/tests/numeric/should_run/T10011.hs new file mode 100644 index 0000000..91a0ecd --- /dev/null +++ b/testsuite/tests/numeric/should_run/T10011.hs @@ -0,0 +1,14 @@ +{-# LANGUAGE ScopedTypeVariables, TypeOperators, GADTs #-} +module Main + ( main -- :: IO () + ) where +import Data.Data +import Data.Ratio + +main :: IO () +main = + let bad = gmapT (\(x :: b) -> + case eqT :: Maybe (b :~: Integer) of + Nothing -> x; + Just Refl -> x * 2) (1 % 2) :: Rational + in print (bad == numerator bad % denominator bad) diff --git a/libraries/base/tests/IO/IOError002.stdout b/testsuite/tests/numeric/should_run/T10011.stdout similarity index 100% copy from libraries/base/tests/IO/IOError002.stdout copy to testsuite/tests/numeric/should_run/T10011.stdout diff --git a/testsuite/tests/numeric/should_run/all.T b/testsuite/tests/numeric/should_run/all.T index 6262279..4369430 100644 --- a/testsuite/tests/numeric/should_run/all.T +++ b/testsuite/tests/numeric/should_run/all.T @@ -64,3 +64,4 @@ test('NumDecimals', normal, compile_and_run, ['']) test('T8726', normal, compile_and_run, ['']) test('CarryOverflow', omit_ways(['ghci']), compile_and_run, ['']) test('T9810', normal, compile_and_run, ['']) +test('T10011', normal, compile_and_run, ['']) From git at git.haskell.org Thu Mar 19 22:42:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 19 Mar 2015 22:42:20 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: testsuite: add a regression test for #10011 (111ff63) Message-ID: <20150319224220.5442D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/111ff6327c79b343f73ab640e33a42b3bf4e3943/ghc >--------------------------------------------------------------- commit 111ff6327c79b343f73ab640e33a42b3bf4e3943 Author: Austin Seipp Date: Thu Mar 19 17:41:08 2015 -0500 testsuite: add a regression test for #10011 Signed-off-by: Austin Seipp (cherry picked from commit e02ef0e6d4eefa5f065cc1c33795dfa2114cd58e) >--------------------------------------------------------------- 111ff6327c79b343f73ab640e33a42b3bf4e3943 testsuite/.gitignore | 1 + testsuite/tests/numeric/should_run/T10011.hs | 14 ++++++++++++++ .../tests/numeric/should_run/T10011.stdout | 0 testsuite/tests/numeric/should_run/all.T | 1 + 4 files changed, 16 insertions(+) diff --git a/testsuite/.gitignore b/testsuite/.gitignore index bbb2174..4750b04 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -1046,6 +1046,7 @@ mk/ghcconfig*_inplace_bin_ghc-stage2.exe.mk /tests/numeric/should_run/T7689 /tests/numeric/should_run/T8726 /tests/numeric/should_run/T9810 +/tests/numeric/should_run/T10011 /tests/numeric/should_run/add2 /tests/numeric/should_run/arith001 /tests/numeric/should_run/arith002 diff --git a/testsuite/tests/numeric/should_run/T10011.hs b/testsuite/tests/numeric/should_run/T10011.hs new file mode 100644 index 0000000..91a0ecd --- /dev/null +++ b/testsuite/tests/numeric/should_run/T10011.hs @@ -0,0 +1,14 @@ +{-# LANGUAGE ScopedTypeVariables, TypeOperators, GADTs #-} +module Main + ( main -- :: IO () + ) where +import Data.Data +import Data.Ratio + +main :: IO () +main = + let bad = gmapT (\(x :: b) -> + case eqT :: Maybe (b :~: Integer) of + Nothing -> x; + Just Refl -> x * 2) (1 % 2) :: Rational + in print (bad == numerator bad % denominator bad) diff --git a/libraries/base/tests/IO/IOError002.stdout b/testsuite/tests/numeric/should_run/T10011.stdout similarity index 100% copy from libraries/base/tests/IO/IOError002.stdout copy to testsuite/tests/numeric/should_run/T10011.stdout diff --git a/testsuite/tests/numeric/should_run/all.T b/testsuite/tests/numeric/should_run/all.T index 6262279..4369430 100644 --- a/testsuite/tests/numeric/should_run/all.T +++ b/testsuite/tests/numeric/should_run/all.T @@ -64,3 +64,4 @@ test('NumDecimals', normal, compile_and_run, ['']) test('T8726', normal, compile_and_run, ['']) test('CarryOverflow', omit_ways(['ghci']), compile_and_run, ['']) test('T9810', normal, compile_and_run, ['']) +test('T10011', normal, compile_and_run, ['']) From git at git.haskell.org Fri Mar 20 06:31:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 06:31:32 +0000 (UTC) Subject: [commit: packages/haskeline] tag '0.7.2.0' created Message-ID: <20150320063132.211743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline New tag : 0.7.2.0 Referencing: 31921c206f492a0f5a51a09aec0df0e98587da9f From git at git.haskell.org Fri Mar 20 06:31:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 06:31:34 +0000 (UTC) Subject: [commit: packages/haskeline] : Update changelog. (f977b4e) Message-ID: <20150320063134.27BE83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : Link : http://git.haskell.org/packages/haskeline.git/commitdiff/f977b4e22ed2e749c41e332ec771d68b3a47a523 >--------------------------------------------------------------- commit f977b4e22ed2e749c41e332ec771d68b3a47a523 Author: Judah Jacobson Date: Tue Jan 20 10:46:52 2015 -0800 Update changelog. >--------------------------------------------------------------- f977b4e22ed2e749c41e332ec771d68b3a47a523 Changelog | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/Changelog b/Changelog index aadc660..a2cf1f1 100644 --- a/Changelog +++ b/Changelog @@ -1,3 +1,11 @@ +Changed in version 0.7.2.0: + * Bump upper-bound on base library to accomodate GHC HEAD (7.10) + * Drop Cabal dependency to 1.10 + * Use explicit forall syntax to avoid warning + * Support Applicative/Monad proposal in Win32/Draw backend + * Add Eq/Ord instances to Completion + * Add a "forall" quantifier before rank-n types + Changed in version 0.7.1.3: * Add support for transformers-0.4.0.0. From git at git.haskell.org Fri Mar 20 06:31:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 06:31:36 +0000 (UTC) Subject: [commit: packages/haskeline] : Merge branch 'master' of github.com:judah/haskeline (b039cf8) Message-ID: <20150320063136.2E69D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : Link : http://git.haskell.org/packages/haskeline.git/commitdiff/b039cf8de476cb871938e4c344fdd2082b5b2e70 >--------------------------------------------------------------- commit b039cf8de476cb871938e4c344fdd2082b5b2e70 Merge: f977b4e 06679b7 Author: Judah Jacobson Date: Thu Mar 19 20:18:31 2015 -0700 Merge branch 'master' of github.com:judah/haskeline >--------------------------------------------------------------- b039cf8de476cb871938e4c344fdd2082b5b2e70 haskeline.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Fri Mar 20 06:31:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 06:31:38 +0000 (UTC) Subject: [commit: packages/haskeline] : Final update of Changelog for next release. (dbffdd9) Message-ID: <20150320063138.34CE83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : Link : http://git.haskell.org/packages/haskeline.git/commitdiff/dbffdd9fc601fc0b74e9e43d237dba0a10b1e0fe >--------------------------------------------------------------- commit dbffdd9fc601fc0b74e9e43d237dba0a10b1e0fe Author: Judah Jacobson Date: Thu Mar 19 20:23:22 2015 -0700 Final update of Changelog for next release. >--------------------------------------------------------------- dbffdd9fc601fc0b74e9e43d237dba0a10b1e0fe Changelog | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Changelog b/Changelog index a2cf1f1..5ca9601 100644 --- a/Changelog +++ b/Changelog @@ -1,5 +1,5 @@ Changed in version 0.7.2.0: - * Bump upper-bound on base library to accomodate GHC HEAD (7.10) + * Bump upper-bound on base and filepath libraries to accomodate GHC HEAD (7.10) * Drop Cabal dependency to 1.10 * Use explicit forall syntax to avoid warning * Support Applicative/Monad proposal in Win32/Draw backend From git at git.haskell.org Fri Mar 20 06:32:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 06:32:29 +0000 (UTC) Subject: [commit: packages/terminfo] tag '0.4.0.1' created Message-ID: <20150320063229.BB3733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/terminfo New tag : 0.4.0.1 Referencing: 6452d2cf91aa318720f46379b66143eda9f3adbf From git at git.haskell.org Fri Mar 20 06:35:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 06:35:23 +0000 (UTC) Subject: [commit: packages/haskeline] master's head updated: Final update of Changelog for next release. (dbffdd9) Message-ID: <20150320063523.CC8AD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline Branch 'master' now includes: f977b4e Update changelog. b039cf8 Merge branch 'master' of github.com:judah/haskeline dbffdd9 Final update of Changelog for next release. From git at git.haskell.org Fri Mar 20 06:40:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 06:40:35 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update haskeline submodule to tagged 0.7.2.0 commit (602a47a) Message-ID: <20150320064035.42BD23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/602a47af646cd7376deec9d04ede1c7a23aa0cc6/ghc >--------------------------------------------------------------- commit 602a47af646cd7376deec9d04ede1c7a23aa0cc6 Author: Herbert Valerio Riedel Date: Fri Mar 20 07:39:18 2015 +0100 Update haskeline submodule to tagged 0.7.2.0 commit >--------------------------------------------------------------- 602a47af646cd7376deec9d04ede1c7a23aa0cc6 libraries/haskeline | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/haskeline b/libraries/haskeline index 06679b7..dbffdd9 160000 --- a/libraries/haskeline +++ b/libraries/haskeline @@ -1 +1 @@ -Subproject commit 06679b723fc07ca805d0dc6b328a5762255e93ee +Subproject commit dbffdd9fc601fc0b74e9e43d237dba0a10b1e0fe From git at git.haskell.org Fri Mar 20 09:31:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 09:31:44 +0000 (UTC) Subject: [commit: packages/deepseq] tag 'v1.4.1.1' created Message-ID: <20150320093144.0CCF43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq New tag : v1.4.1.1 Referencing: 9d85a88d727c43a1216d01c789800d526e7119e9 From git at git.haskell.org Fri Mar 20 09:31:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 09:31:46 +0000 (UTC) Subject: [commit: packages/deepseq] master: Drop redundant `ghc-prim` dependency (cdfcdee) Message-ID: <20150320093146.11BFF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/cdfcdee14ce9071bbfbddf0007df8aee8015da48 >--------------------------------------------------------------- commit cdfcdee14ce9071bbfbddf0007df8aee8015da48 Author: Herbert Valerio Riedel Date: Thu Mar 19 23:39:36 2015 +0100 Drop redundant `ghc-prim` dependency >--------------------------------------------------------------- cdfcdee14ce9071bbfbddf0007df8aee8015da48 changelog.md | 6 +++++- deepseq.cabal | 4 +--- 2 files changed, 6 insertions(+), 4 deletions(-) diff --git a/changelog.md b/changelog.md index e21fb5d..0f8a14d 100644 --- a/changelog.md +++ b/changelog.md @@ -1,8 +1,12 @@ # Changelog for [`deepseq` package](http://hackage.haskell.org/package/deepseq) -## 1.4.1.0 *Mar 2015* +## 1.4.1.1 *Mar 2015* * Bundled with GHC 7.10.1 + * Drop redundant `ghc-prim` dependency + +## 1.4.1.0 *Mar 2015* + * Drop redundant constraints from a few `NFData` instances (if possible for a given `base` version) diff --git a/deepseq.cabal b/deepseq.cabal index ad07416..8c0a391 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -1,5 +1,5 @@ name: deepseq -version: 1.4.1.0 +version: 1.4.1.1 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE @@ -44,8 +44,6 @@ library Safe TypeOperators - build-depends: ghc-prim >= 0.2 && < 0.4 - build-depends: base >= 4.3 && < 4.9, array >= 0.3 && < 0.6 ghc-options: -Wall From git at git.haskell.org Fri Mar 20 09:31:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 09:31:48 +0000 (UTC) Subject: [commit: packages/deepseq] master: Fix compilation with GHC 7.2 (2af92b3) Message-ID: <20150320093148.170623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/2af92b376030c69c99fd6a47bbf91381d80fd91f >--------------------------------------------------------------- commit 2af92b376030c69c99fd6a47bbf91381d80fd91f Author: Herbert Valerio Riedel Date: Fri Mar 20 07:48:22 2015 +0100 Fix compilation with GHC 7.2 Follow-up to cdfcdee14ce9071bbfbddf0007df8aee8015da48 >--------------------------------------------------------------- 2af92b376030c69c99fd6a47bbf91381d80fd91f deepseq.cabal | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/deepseq.cabal b/deepseq.cabal index 8c0a391..dd32d4c 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -44,6 +44,10 @@ library Safe TypeOperators + -- GHC.Generics lived in `ghc-prim` for GHC 7.2 + if impl(ghc < 7.4) + build-depends: ghc-prim == 0.2.* + build-depends: base >= 4.3 && < 4.9, array >= 0.3 && < 0.6 ghc-options: -Wall From git at git.haskell.org Fri Mar 20 09:31:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 09:31:50 +0000 (UTC) Subject: [commit: packages/deepseq] master: Fix compilation with GHC 7.4 (c6cb196) Message-ID: <20150320093150.1C6D03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq On branch : master Link : http://git.haskell.org/packages/deepseq.git/commitdiff/c6cb196fb1bd5f16bb5945add2d6ece3f7910e90 >--------------------------------------------------------------- commit c6cb196fb1bd5f16bb5945add2d6ece3f7910e90 Author: Herbert Valerio Riedel Date: Fri Mar 20 07:58:17 2015 +0100 Fix compilation with GHC 7.4 Follow-up to cdfcdee14ce9071bbfbddf0007df8aee8015da48 >--------------------------------------------------------------- c6cb196fb1bd5f16bb5945add2d6ece3f7910e90 deepseq.cabal | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/deepseq.cabal b/deepseq.cabal index dd32d4c..7435b25 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -44,8 +44,8 @@ library Safe TypeOperators - -- GHC.Generics lived in `ghc-prim` for GHC 7.2 - if impl(ghc < 7.4) + -- GHC.Generics lived in `ghc-prim` for GHC 7.2 & GHC 7.4 + if impl(ghc < 7.6) build-depends: ghc-prim == 0.2.* build-depends: base >= 4.3 && < 4.9, From git at git.haskell.org Fri Mar 20 09:50:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 09:50:37 +0000 (UTC) Subject: [commit: ghc] master: Update deepseq submodule to 1.4.1.1 tag (c2833d6) Message-ID: <20150320095037.136973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c2833d60083dd6f4e13f8f58502e3bf2b0aacf5c/ghc >--------------------------------------------------------------- commit c2833d60083dd6f4e13f8f58502e3bf2b0aacf5c Author: Herbert Valerio Riedel Date: Fri Mar 20 10:37:33 2015 +0100 Update deepseq submodule to 1.4.1.1 tag This deepseq update drops the redundant ghc-prim dependency for GHC>=7.6 >--------------------------------------------------------------- c2833d60083dd6f4e13f8f58502e3bf2b0aacf5c libraries/deepseq | 2 +- testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout | 6 +++--- testsuite/tests/th/TH_Roles2.stderr | 2 +- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/libraries/deepseq b/libraries/deepseq index 5cbc7d1..c6cb196 160000 --- a/libraries/deepseq +++ b/libraries/deepseq @@ -1 +1 @@ -Subproject commit 5cbc7d1c1d51838b5a147b3fb2d4b6f87b0eda09 +Subproject commit c6cb196fb1bd5f16bb5945add2d6ece3f7910e90 diff --git a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout index 16be65e..700f3a3 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout +++ b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout @@ -29,17 +29,17 @@ trusted: safe require own pkg trusted: True M_SafePkg6 -package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.6.0* deepseq-1.4.1.0 ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 +package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.6.0* deepseq-1.4.1.1 ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 trusted: trustworthy require own pkg trusted: False M_SafePkg7 -package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.6.0* deepseq-1.4.1.0 ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 +package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.6.0* deepseq-1.4.1.1 ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 trusted: safe require own pkg trusted: False M_SafePkg8 -package dependencies: array-0.5.0.1 base-4.8.0.0 bytestring-0.10.6.0* deepseq-1.4.1.0 ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 +package dependencies: array-0.5.0.1 base-4.8.0.0 bytestring-0.10.6.0* deepseq-1.4.1.1 ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 trusted: trustworthy require own pkg trusted: False diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index 489064c..531a874 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -4,7 +4,7 @@ TYPE CONSTRUCTORS data T (a :: k) COERCION AXIOMS Dependent modules: [] -Dependent packages: [array-0.5.1.0, base-4.8.0.0, deepseq-1.4.1.0, +Dependent packages: [array-0.5.1.0, base-4.8.0.0, deepseq-1.4.1.1, ghc-prim-0.3.1.0, integer-gmp-1.0.0.0, pretty-1.1.2.0, template-haskell-2.10.0.0] From git at git.haskell.org Fri Mar 20 10:21:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 10:21:28 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Major rewrite: Pt 8: Just comment work (74e5832) Message-ID: <20150320102128.993A63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/74e5832527fe84c377beb5fad842e269fd18fd85/ghc >--------------------------------------------------------------- commit 74e5832527fe84c377beb5fad842e269fd18fd85 Author: George Karachalias Date: Fri Mar 20 11:21:05 2015 +0100 Major rewrite: Pt 8: Just comment work >--------------------------------------------------------------- 74e5832527fe84c377beb5fad842e269fd18fd85 compiler/deSugar/Check.hs | 46 ++++++++++++++++++++++------------------------ 1 file changed, 22 insertions(+), 24 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 9328660..bccdc76 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -343,9 +343,6 @@ alg_uncovered_many uncovered clause = do uncovered' <- mapBagM (\uvec -> alg_uncovered uvec clause) uncovered return (concatBag uncovered') - --- COMEHERE: ALL FUNCTIONS BELLOW SHOULD BE CHECKED FOR PROPER TYPING PROPAGATION - -- ----------------------------------------------------------------------- -- | Given an uncovered value vector and a clause, check whether the clause -- forces the evaluation of any arguments. @@ -682,7 +679,6 @@ pprWithParens pats = sep (map paren_if_needed pats) | otherwise = ppr p -- | Pretty print list [1,2,3] as the set {1,2,3} --- {COMEHERE: FRESH VARIABLE and "where .. not one of ..."} pprSet :: Outputable id => [id] -> SDoc pprSet lits = braces $ sep $ punctuate comma $ map ppr lits @@ -774,8 +770,7 @@ pprWithParens2 pats = sep (map paren_if_needed pats) -- ----------------------------------------------------------------------- -- | Transform a Pat Id into a list of (PmPat Id) -- Note [Translation to PmPat] --- Syntax only for now, NO TYPES USED -translatePat :: UniqSupply -> Pat Id -> PatternVec -- Do not return UniqSupply. It is just for us (we need laziness) +translatePat :: UniqSupply -> Pat Id -> PatternVec translatePat usupply pat = case pat of WildPat ty -> [mkPmVar usupply ty] VarPat id -> [VarAbs id] @@ -787,8 +782,8 @@ translatePat usupply pat = case pat of idp = VarAbs (unLoc lid) g = GBindAbs ps (HsVar (unLoc lid)) in [idp, g] - SigPatOut p ty -> translatePat usupply (unLoc p) -- COMEHERE: FIXME: Exploit the signature? - CoPat wrapper p ty -> translatePat usupply p -- COMEHERE: Make sure the coercion is not useful + SigPatOut p ty -> translatePat usupply (unLoc p) -- TODO: Use the signature? + CoPat wrapper p ty -> translatePat usupply p -- TODO: Check if we need the coercion NPlusKPat n k ge minus -> let (xp, xe) = mkPmId2Forms usupply (idType (unLoc n)) ke = noLoc (HsOverLit k) -- k as located expression @@ -816,31 +811,32 @@ translatePat usupply pat = case pat of g = GBindAbs (concat ps) $ HsApp (noLoc to_list) xe -- [...] <- toList x in [xp,g] - ConPatOut { pat_con = L _ (PatSynCon _) } -> [mkPmVar usupply (hsPatType pat)] -- ERROR + ConPatOut { pat_con = L _ (PatSynCon _) } -> -- CHECKME: Is there a way to unfold this into a normal pattern? + [mkPmVar usupply (hsPatType pat)] - ConPatOut { pat_con = L _ (RealDataCon con), pat_args = ps } -> -- DO WE NEED OTHER STUFF FROM IT? + ConPatOut { pat_con = L _ (RealDataCon con), pat_args = ps } -> [ConAbs con (translateConPats usupply con ps)] - NPat lit mb_neg eq -> -- COMEHERE: Double check this. Also do something with the fixity? + NPat lit mb_neg eq -> let var = mkPmId usupply (hsPatType pat) - hs_var = noLoc (HsVar var) -- COMEHERE: I do not like the noLoc thing - expr_lit = noLoc (negateOrNot mb_neg lit) -- COMEHERE: I do not like the noLoc thing - expr = OpApp hs_var (noLoc eq) no_fixity expr_lit -- COMEHERE: I do not like the noLoc thing + hs_var = noLoc (HsVar var) + expr_lit = noLoc (negateOrNot mb_neg lit) + expr = OpApp hs_var (noLoc eq) no_fixity expr_lit in [VarAbs var, eqTrueExpr expr] - LitPat lit -> [mkPmVar usupply (hsPatType pat)] -- ERROR: Which eq to use?? + LitPat lit -> [mkPmVar usupply (hsPatType pat)] -- CHECKME: Which eq function to use? - ListPat ps ty Nothing -> -- WHAT TO DO WITH TY?? + ListPat ps ty Nothing -> let tidy_ps = translatePats usupply (map unLoc ps) mkListPat x y = [ConAbs consDataCon (x++y)] in foldr mkListPat [ConAbs nilDataCon []] tidy_ps - PArrPat ps tys -> -- WHAT TO DO WITH TYS?? + PArrPat ps tys -> let tidy_ps = translatePats usupply (map unLoc ps) fake_con = parrFakeCon (length ps) in [ConAbs fake_con (concat tidy_ps)] - TuplePat ps boxity tys -> -- WHAT TO DO WITH TYS?? + TuplePat ps boxity tys -> let tidy_ps = translatePats usupply (map unLoc ps) tuple_con = tupleCon (boxityNormalTupleSort boxity) (length ps) in [ConAbs tuple_con (concat tidy_ps)] @@ -855,12 +851,14 @@ translatePat usupply pat = case pat of eqTrueExpr :: HsExpr Id -> PatAbs eqTrueExpr expr = GBindAbs [ConAbs trueDataCon []] expr +-- CHECKME: Can we retrieve the fixity from the operator name? +-- Do we even really need it? no_fixity :: a no_fixity = panic "COMEHERE: no fixity!!" negateOrNot :: Maybe (SyntaxExpr Id) -> HsOverLit Id -> HsExpr Id negateOrNot Nothing lit = HsOverLit lit -negateOrNot (Just neg) lit = NegApp (noLoc (HsOverLit lit)) neg -- COMEHERE: I do not like the noLoc thing +negateOrNot (Just neg) lit = NegApp (noLoc (HsOverLit lit)) neg translatePats :: UniqSupply -> [Pat Id] -> [PatternVec] -- Do not concatenate them (sometimes we need them separately) translatePats usupply pats = map (uncurry translatePat) uniqs_pats @@ -879,7 +877,7 @@ translateConPats usupply c (RecCon (HsRecFields fs _)) | null fs = map (uncurry mkPmVar) $ listSplitUniqSupply usupply `zip` dataConOrigArgTys c | otherwise = concat (translatePats usupply (map (unLoc . snd) all_pats)) where - -- COMEHERE: The functions below are ugly and they do not care much about types too + -- TODO: The functions below are ugly and they do not care much about types too field_pats = map (\lbl -> (lbl, noLoc (WildPat (dataConFieldType c lbl)))) (dataConFieldLabels c) all_pats = foldr (\(L _ (HsRecField id p _)) acc -> insertNm (getName (unLoc id)) p acc) field_pats fs @@ -968,7 +966,7 @@ covered usupply (GBindAbs p e : ps) vsa = cs `addConstraints` vsa' where (usupply1, usupply2) = splitUniqSupply usupply - y = mkPmId usupply1 undefined -- COMEHERE: WHAT TYPE?? + y = mkPmId usupply1 undefined -- CHECKME: Which type to use? cs = [TmConstraint y e] -- CVar @@ -1015,7 +1013,7 @@ uncovered usupply (GBindAbs p e : ps) vsa = cs `addConstraints` (tailValSetAbs $ uncovered usupply2 (p++ps) (VarAbs y `consValSetAbs` vsa)) where (usupply1, usupply2) = splitUniqSupply usupply - y = mkPmId usupply1 undefined -- COMEHERE: WHAT TYPE?? + y = mkPmId usupply1 undefined -- CHECKME: Which type to use? cs = [TmConstraint y e] -- UVar @@ -1095,7 +1093,7 @@ valAbsToHsExpr :: ValAbs -> HsExpr Id valAbsToHsExpr (VarAbs x) = HsVar x valAbsToHsExpr (ConAbs c ps) = foldl lHsApp cexpr psexprs where - cexpr = HsVar (dataConWrapId c) -- var representation of the constructor -- COMEHERE: Fishy. Ask Simon + cexpr = HsVar (dataConWrapId c) -- CHECKME: Representation of the constructor as an Id? psexprs = map valAbsToHsExpr ps lHsApp le re = noLoc le `HsApp` noLoc re -- add locations (useless) to arguments @@ -1104,7 +1102,7 @@ valAbsToHsExpr (ConAbs c ps) = foldl lHsApp cexpr psexprs -- NB: The only representation of an empty value set is `Empty' addConstraints :: [PmConstraint] -> ValSetAbs -> ValSetAbs -addConstraints _cs Empty = Empty -- No point in adding constraints in an empty set. Maybe make it an invariant? (I mean that if empty(vsa) => vsa==Empty, like the bags) +addConstraints _cs Empty = Empty addConstraints cs1 (Constraint cs2 vsa) = Constraint (cs1++cs2) vsa -- careful about associativity addConstraints cs other_vsa = Constraint cs other_vsa From git at git.haskell.org Fri Mar 20 10:23:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 10:23:13 +0000 (UTC) Subject: [commit: ghc] master: Modify test th/T10019 to wobble less (76f385b) Message-ID: <20150320102313.1205C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/76f385ba840fdb87ff4254cd838752ba161b0a8d/ghc >--------------------------------------------------------------- commit 76f385ba840fdb87ff4254cd838752ba161b0a8d Author: Simon Peyton Jones Date: Thu Mar 19 23:17:21 2015 +0000 Modify test th/T10019 to wobble less The TH output contains uniques which change too much. So I took the length of the string instead. Crude, perhaps too crude, but it'll still show up most significant output changes >--------------------------------------------------------------- 76f385ba840fdb87ff4254cd838752ba161b0a8d testsuite/tests/th/T10019.script | 9 ++++++++- testsuite/tests/th/T10019.stdout | 2 +- 2 files changed, 9 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/th/T10019.script b/testsuite/tests/th/T10019.script index eef5fe7..97ecbe1 100644 --- a/testsuite/tests/th/T10019.script +++ b/testsuite/tests/th/T10019.script @@ -1,4 +1,11 @@ :set -XTemplateHaskell import Language.Haskell.TH data Option a = Some a | None -$(reify 'Some >>= stringE . show) +$(reify 'Some >>= litE . integerL . toInteger . length . show) +-- By taking the length we avoid wobbling when the exact uniques +-- chosen by TH change +-- +-- This was the original +-- $(reify 'Some >>= stringE . show) +-- which yields +-- "DataConI Ghci1.Some (ForallT [KindedTV a_1627391549 StarT] [] (AppT (AppT ArrowT (VarT a_1627391549)) (AppT (ConT Ghci1.Option) (VarT a_1627391549)))) Ghci1.Option (Fixity 9 InfixL)" \ No newline at end of file diff --git a/testsuite/tests/th/T10019.stdout b/testsuite/tests/th/T10019.stdout index 350338c..d65e8e3 100644 --- a/testsuite/tests/th/T10019.stdout +++ b/testsuite/tests/th/T10019.stdout @@ -1 +1 @@ -"DataConI Ghci1.Some (ForallT [KindedTV a_1627391549 StarT] [] (AppT (AppT ArrowT (VarT a_1627391549)) (AppT (ConT Ghci1.Option) (VarT a_1627391549)))) Ghci1.Option (Fixity 9 InfixL)" +181 From git at git.haskell.org Fri Mar 20 11:27:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 11:27:19 +0000 (UTC) Subject: [commit: ghc] master: Bump ghc-prim to 0.4.0.0 (9dfdd16) Message-ID: <20150320112719.D25373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9dfdd16a61e79cb03c633d442190a81fe5c0b6b8/ghc >--------------------------------------------------------------- commit 9dfdd16a61e79cb03c633d442190a81fe5c0b6b8 Author: Herbert Valerio Riedel Date: Fri Mar 20 12:23:41 2015 +0100 Bump ghc-prim to 0.4.0.0 This major version bump was made necessary by f44333eae7bc7dc7b6003b75874a02445f6b633b which changed the type signatures of prefetch primops, as well as other changes such as 051d694fc978ad28ac3043d296cafddd3c2a7050 turning `Any` into an abstract closed type family. Reviewed By: ekmett Differential Revision: https://phabricator.haskell.org/D743 >--------------------------------------------------------------- 9dfdd16a61e79cb03c633d442190a81fe5c0b6b8 libraries/base/base.cabal | 2 +- libraries/ghc-prim/ghc-prim.cabal | 4 ++-- libraries/integer-gmp/integer-gmp.cabal | 2 +- .../tests/indexed-types/should_compile/T3017.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/ADT.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr1.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr2.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr3.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr4.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr5.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr6.stderr | 2 +- .../tests/partial-sigs/should_compile/BoolToBool.stderr | 2 +- .../partial-sigs/should_compile/Defaulting1MROn.stderr | 2 +- .../partial-sigs/should_compile/Defaulting2MROff.stderr | 2 +- .../partial-sigs/should_compile/Defaulting2MROn.stderr | 2 +- .../tests/partial-sigs/should_compile/Either.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Every.stderr | 2 +- .../tests/partial-sigs/should_compile/EveryNamed.stderr | 2 +- .../partial-sigs/should_compile/ExpressionSig.stderr | 2 +- .../should_compile/ExpressionSigNamed.stderr | 2 +- .../partial-sigs/should_compile/ExtraConstraints1.stderr | 2 +- .../partial-sigs/should_compile/ExtraConstraints2.stderr | 2 +- .../partial-sigs/should_compile/ExtraConstraints3.stderr | 2 +- .../partial-sigs/should_compile/ExtraNumAMROff.stderr | 2 +- .../tests/partial-sigs/should_compile/Forall1.stderr | 2 +- .../tests/partial-sigs/should_compile/GenNamed.stderr | 2 +- .../tests/partial-sigs/should_compile/HigherRank1.stderr | 2 +- .../tests/partial-sigs/should_compile/HigherRank2.stderr | 2 +- .../should_compile/LocalDefinitionBug.stderr | 2 +- .../tests/partial-sigs/should_compile/Meltdown.stderr | 2 +- .../partial-sigs/should_compile/MonoLocalBinds.stderr | 4 ++-- .../tests/partial-sigs/should_compile/NamedTyVar.stderr | 2 +- .../should_compile/ParensAroundContext.stderr | 2 +- .../tests/partial-sigs/should_compile/PatBind.stderr | 4 ++-- .../tests/partial-sigs/should_compile/PatternSig.stderr | 2 +- .../tests/partial-sigs/should_compile/Recursive.stderr | 2 +- .../should_compile/ScopedNamedWildcards.stderr | 2 +- .../should_compile/ScopedNamedWildcardsGood.stderr | 2 +- .../tests/partial-sigs/should_compile/ShowNamed.stderr | 2 +- .../tests/partial-sigs/should_compile/SimpleGen.stderr | 2 +- .../tests/partial-sigs/should_compile/SkipMany.stderr | 2 +- .../partial-sigs/should_compile/SomethingShowable.stderr | 2 +- .../tests/partial-sigs/should_compile/Uncurry.stderr | 2 +- .../partial-sigs/should_compile/UncurryNamed.stderr | 2 +- .../should_compile/WarningWildcardInstantiations.stderr | 2 +- testsuite/tests/roles/should_compile/Roles1.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles14.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles2.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles3.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles4.stderr | 4 ++-- testsuite/tests/roles/should_compile/T8958.stderr | 4 ++-- testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout | 16 ++++++++-------- testsuite/tests/typecheck/should_compile/tc231.stderr | 4 ++-- 53 files changed, 71 insertions(+), 71 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9dfdd16a61e79cb03c633d442190a81fe5c0b6b8 From git at git.haskell.org Fri Mar 20 12:01:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 12:01:47 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update deepseq submodule to 1.4.1.1 tag (038bdb2) Message-ID: <20150320120147.098703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/038bdb286ddaf7fc7b18d1fb0c92173fa7854a22/ghc >--------------------------------------------------------------- commit 038bdb286ddaf7fc7b18d1fb0c92173fa7854a22 Author: Herbert Valerio Riedel Date: Fri Mar 20 10:37:33 2015 +0100 Update deepseq submodule to 1.4.1.1 tag This deepseq update drops the redundant ghc-prim dependency for GHC>=7.6 (cherry picked from commit c2833d60083dd6f4e13f8f58502e3bf2b0aacf5c) >--------------------------------------------------------------- 038bdb286ddaf7fc7b18d1fb0c92173fa7854a22 libraries/deepseq | 2 +- testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout | 6 +++--- testsuite/tests/th/TH_Roles2.stderr | 2 +- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/libraries/deepseq b/libraries/deepseq index 56809c3..c6cb196 160000 --- a/libraries/deepseq +++ b/libraries/deepseq @@ -1 +1 @@ -Subproject commit 56809c3e45c3a266564672b968817ca8b6d496c1 +Subproject commit c6cb196fb1bd5f16bb5945add2d6ece3f7910e90 diff --git a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout index 134ad6f..636a243 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout +++ b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout @@ -29,17 +29,17 @@ trusted: safe require own pkg trusted: True M_SafePkg6 -package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.5.0* deepseq-1.4.1.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.6.0* deepseq-1.4.1.1 ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 trusted: trustworthy require own pkg trusted: False M_SafePkg7 -package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.5.0* deepseq-1.4.1.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: array-0.5.0.1 base-4.8.0.0* bytestring-0.10.6.0* deepseq-1.4.1.1 ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 trusted: safe require own pkg trusted: False M_SafePkg8 -package dependencies: array-0.5.0.1 base-4.8.0.0 bytestring-0.10.5.0* deepseq-1.4.1.0 ghc-prim-0.3.1.0 integer-gmp-0.5.1.0 +package dependencies: array-0.5.0.1 base-4.8.0.0 bytestring-0.10.6.0* deepseq-1.4.1.1 ghc-prim-0.3.1.0 integer-gmp-1.0.0.0 trusted: trustworthy require own pkg trusted: False diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index 489064c..531a874 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -4,7 +4,7 @@ TYPE CONSTRUCTORS data T (a :: k) COERCION AXIOMS Dependent modules: [] -Dependent packages: [array-0.5.1.0, base-4.8.0.0, deepseq-1.4.1.0, +Dependent packages: [array-0.5.1.0, base-4.8.0.0, deepseq-1.4.1.1, ghc-prim-0.3.1.0, integer-gmp-1.0.0.0, pretty-1.1.2.0, template-haskell-2.10.0.0] From git at git.haskell.org Fri Mar 20 12:01:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 12:01:49 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Bump ghc-prim to 0.4.0.0 (49c4678) Message-ID: <20150320120149.E96663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/49c4678f061ba5fd3db74c67395979d40b3bbf1c/ghc >--------------------------------------------------------------- commit 49c4678f061ba5fd3db74c67395979d40b3bbf1c Author: Herbert Valerio Riedel Date: Fri Mar 20 12:23:41 2015 +0100 Bump ghc-prim to 0.4.0.0 This major version bump was made necessary by f44333eae7bc7dc7b6003b75874a02445f6b633b which changed the type signatures of prefetch primops, as well as other changes such as 051d694fc978ad28ac3043d296cafddd3c2a7050 turning `Any` into an abstract closed type family. (cherry picked from commit 9dfdd16a61e79cb03c633d442190a81fe5c0b6b8) >--------------------------------------------------------------- 49c4678f061ba5fd3db74c67395979d40b3bbf1c libraries/base/base.cabal | 2 +- libraries/ghc-prim/ghc-prim.cabal | 4 ++-- libraries/integer-gmp/integer-gmp.cabal | 2 +- .../tests/indexed-types/should_compile/T3017.stderr | 4 ++-- testsuite/tests/partial-sigs/should_compile/ADT.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr1.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr2.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr3.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr4.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr5.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr6.stderr | 2 +- .../tests/partial-sigs/should_compile/BoolToBool.stderr | 2 +- .../partial-sigs/should_compile/Defaulting1MROn.stderr | 2 +- .../partial-sigs/should_compile/Defaulting2MROff.stderr | 2 +- .../partial-sigs/should_compile/Defaulting2MROn.stderr | 2 +- .../tests/partial-sigs/should_compile/Either.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Every.stderr | 2 +- .../tests/partial-sigs/should_compile/EveryNamed.stderr | 2 +- .../partial-sigs/should_compile/ExpressionSig.stderr | 2 +- .../should_compile/ExpressionSigNamed.stderr | 2 +- .../partial-sigs/should_compile/ExtraConstraints1.stderr | 2 +- .../partial-sigs/should_compile/ExtraConstraints2.stderr | 2 +- .../partial-sigs/should_compile/ExtraConstraints3.stderr | 2 +- .../partial-sigs/should_compile/ExtraNumAMROff.stderr | 2 +- .../tests/partial-sigs/should_compile/Forall1.stderr | 2 +- .../tests/partial-sigs/should_compile/GenNamed.stderr | 2 +- .../tests/partial-sigs/should_compile/HigherRank1.stderr | 2 +- .../tests/partial-sigs/should_compile/HigherRank2.stderr | 2 +- .../should_compile/LocalDefinitionBug.stderr | 2 +- .../tests/partial-sigs/should_compile/Meltdown.stderr | 2 +- .../partial-sigs/should_compile/MonoLocalBinds.stderr | 4 ++-- .../tests/partial-sigs/should_compile/NamedTyVar.stderr | 2 +- .../should_compile/ParensAroundContext.stderr | 2 +- .../tests/partial-sigs/should_compile/PatBind.stderr | 4 ++-- .../tests/partial-sigs/should_compile/PatternSig.stderr | 2 +- .../tests/partial-sigs/should_compile/Recursive.stderr | 2 +- .../should_compile/ScopedNamedWildcards.stderr | 2 +- .../should_compile/ScopedNamedWildcardsGood.stderr | 2 +- .../tests/partial-sigs/should_compile/ShowNamed.stderr | 2 +- .../tests/partial-sigs/should_compile/SimpleGen.stderr | 2 +- .../tests/partial-sigs/should_compile/SkipMany.stderr | 2 +- .../partial-sigs/should_compile/SomethingShowable.stderr | 2 +- .../tests/partial-sigs/should_compile/Uncurry.stderr | 2 +- .../partial-sigs/should_compile/UncurryNamed.stderr | 2 +- .../should_compile/WarningWildcardInstantiations.stderr | 2 +- testsuite/tests/roles/should_compile/Roles1.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles14.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles2.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles3.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles4.stderr | 4 ++-- testsuite/tests/roles/should_compile/T8958.stderr | 4 ++-- testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout | 16 ++++++++-------- testsuite/tests/th/TH_Roles2.stderr | 2 +- testsuite/tests/typecheck/should_compile/tc231.stderr | 4 ++-- 54 files changed, 72 insertions(+), 72 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 49c4678f061ba5fd3db74c67395979d40b3bbf1c From git at git.haskell.org Fri Mar 20 12:34:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 12:34:20 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Try to reconstruct a changelog for TH 2.10 (9d15af8) Message-ID: <20150320123420.7C22C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/9d15af88b9b5cbf9dd4a4d072aa94540074cc4b3/ghc >--------------------------------------------------------------- commit 9d15af88b9b5cbf9dd4a4d072aa94540074cc4b3 Author: Herbert Valerio Riedel Date: Fri Mar 20 13:33:19 2015 +0100 Try to reconstruct a changelog for TH 2.10 >--------------------------------------------------------------- 9d15af88b9b5cbf9dd4a4d072aa94540074cc4b3 libraries/template-haskell/changelog.md | 19 ++++++++++++++++++- 1 file changed, 18 insertions(+), 1 deletion(-) diff --git a/libraries/template-haskell/changelog.md b/libraries/template-haskell/changelog.md index 7d39d35..f205ed5 100644 --- a/libraries/template-haskell/changelog.md +++ b/libraries/template-haskell/changelog.md @@ -1,5 +1,22 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) -## 2.10.0.0 *TBA* +## 2.10.0.0 *Mar 2015* * Bundled with GHC 7.10.1 + * Remove build-dependency on `containers` package + * Make `Pred` a type synonym of `Type`, and deprecate `classP`/`equalP` (#7021) + * Add support for `LINE` pragma via `prageLineD` and `LineP` + * Replace `Int#` with `!Int` in `NameFlavour` constructors + * Derive `Generic` for TH types (#9527) + * Add `standaloneDerivD` (#8100) + * Add support for generic default signatures via `defaultSigD` (#9064) + * Add `Lift` instances for `()` and `Rational` + * Derive new `Show` and `Data` instances for `Loc` + * Derive `Eq` instances for `Loc`, `Info`, and `ModuleInfo` + * Make calling conventions available in template haskell consistent + with those from GHC (#9703) + * Add support for `-XStaticValues` via `staticE` + * Add `Ord` instances to TH types + * Merge some instances from `th-orphans` (`Ppr` instances for `Lit` + and `Loc` as well as `Lift` instances for numeric types + * Put parens around `(ty :: kind)` when pretty-printing TH syntax From git at git.haskell.org Fri Mar 20 12:35:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 12:35:29 +0000 (UTC) Subject: [commit: ghc] master: Try to reconstruct a changelog for TH 2.10 (6da18b8) Message-ID: <20150320123529.CCACB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6da18b88a7b4de9f55da82904a4e555c5e956723/ghc >--------------------------------------------------------------- commit 6da18b88a7b4de9f55da82904a4e555c5e956723 Author: Herbert Valerio Riedel Date: Fri Mar 20 13:33:19 2015 +0100 Try to reconstruct a changelog for TH 2.10 [skip ci] (cherry picked from commit 9d15af88b9b5cbf9dd4a4d072aa94540074cc4b3) >--------------------------------------------------------------- 6da18b88a7b4de9f55da82904a4e555c5e956723 libraries/template-haskell/changelog.md | 19 ++++++++++++++++++- 1 file changed, 18 insertions(+), 1 deletion(-) diff --git a/libraries/template-haskell/changelog.md b/libraries/template-haskell/changelog.md index 7d39d35..f205ed5 100644 --- a/libraries/template-haskell/changelog.md +++ b/libraries/template-haskell/changelog.md @@ -1,5 +1,22 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) -## 2.10.0.0 *TBA* +## 2.10.0.0 *Mar 2015* * Bundled with GHC 7.10.1 + * Remove build-dependency on `containers` package + * Make `Pred` a type synonym of `Type`, and deprecate `classP`/`equalP` (#7021) + * Add support for `LINE` pragma via `prageLineD` and `LineP` + * Replace `Int#` with `!Int` in `NameFlavour` constructors + * Derive `Generic` for TH types (#9527) + * Add `standaloneDerivD` (#8100) + * Add support for generic default signatures via `defaultSigD` (#9064) + * Add `Lift` instances for `()` and `Rational` + * Derive new `Show` and `Data` instances for `Loc` + * Derive `Eq` instances for `Loc`, `Info`, and `ModuleInfo` + * Make calling conventions available in template haskell consistent + with those from GHC (#9703) + * Add support for `-XStaticValues` via `staticE` + * Add `Ord` instances to TH types + * Merge some instances from `th-orphans` (`Ppr` instances for `Lit` + and `Loc` as well as `Lift` instances for numeric types + * Put parens around `(ty :: kind)` when pretty-printing TH syntax From git at git.haskell.org Fri Mar 20 17:52:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 17:52:43 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update integer-gmp2's changelog for release (7bd3efe) Message-ID: <20150320175243.F053A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/7bd3efe3ccc6dc0a3ec84008285b4e03b48d8f41/ghc >--------------------------------------------------------------- commit 7bd3efe3ccc6dc0a3ec84008285b4e03b48d8f41 Author: Herbert Valerio Riedel Date: Fri Mar 20 18:52:28 2015 +0100 Update integer-gmp2's changelog for release [skip ci] >--------------------------------------------------------------- 7bd3efe3ccc6dc0a3ec84008285b4e03b48d8f41 libraries/integer-gmp2/changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/integer-gmp2/changelog.md b/libraries/integer-gmp2/changelog.md index af3ac83..cb55b80 100644 --- a/libraries/integer-gmp2/changelog.md +++ b/libraries/integer-gmp2/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`integer-gmp` package](http://hackage.haskell.org/package/integer-gmp) -## 1.0.0.0 **TBA** +## 1.0.0.0 *Mar 2015* * Bundled with GHC 7.10.1 From git at git.haskell.org Fri Mar 20 19:36:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 19:36:36 +0000 (UTC) Subject: [commit: packages/bytestring] tag '0.10.6.0' created Message-ID: <20150320193637.010653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring New tag : 0.10.6.0 Referencing: 3830359c966aee3484c2b417b886000c274ec1c3 From git at git.haskell.org Fri Mar 20 19:36:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 19:36:39 +0000 (UTC) Subject: [commit: packages/bytestring] master: Fix build for ghc 6.12 (87c994d) Message-ID: <20150320193639.100F33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/87c994d8f2d5d9db9f6ad164243bd2870d2bb999 >--------------------------------------------------------------- commit 87c994d8f2d5d9db9f6ad164243bd2870d2bb999 Author: Duncan Coutts Date: Fri Mar 20 16:45:19 2015 +0000 Fix build for ghc 6.12 >--------------------------------------------------------------- 87c994d8f2d5d9db9f6ad164243bd2870d2bb999 Data/ByteString/Short/Internal.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Data/ByteString/Short/Internal.hs b/Data/ByteString/Short/Internal.hs index 01630ef..6c0bf20 100644 --- a/Data/ByteString/Short/Internal.hs +++ b/Data/ByteString/Short/Internal.hs @@ -108,7 +108,7 @@ import Prelude ( Eq(..), Ord(..), Ordering(..), Read(..), Show(..) -- data ShortByteString = SBS ByteArray# #if !(MIN_VERSION_base(4,3,0)) - Int -- ^ Prior to ghc-7.0.x, 'ByteArray#'s reported + {-# UNPACK #-} !Int -- ^ Prior to ghc-7.0.x, 'ByteArray#'s reported -- their length rounded up to the nearest word. -- This means we have to store the true length -- separately, wasting a word. @@ -137,7 +137,7 @@ instance Monoid ShortByteString where mconcat = concat instance NFData ShortByteString where - rnf (SBS !_) = () + rnf (SBS {}) = () instance Show ShortByteString where showsPrec p ps r = showsPrec p (unpackChars ps) r From git at git.haskell.org Fri Mar 20 19:36:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 19:36:41 +0000 (UTC) Subject: [commit: packages/bytestring] master: Fix warnings for ghc-7.10 (02381c3) Message-ID: <20150320193641.1D8E63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/02381c3bfe37b974deb27e107ee0c868ddd3b0c9 >--------------------------------------------------------------- commit 02381c3bfe37b974deb27e107ee0c868ddd3b0c9 Author: Duncan Coutts Date: Fri Mar 20 16:45:38 2015 +0000 Fix warnings for ghc-7.10 >--------------------------------------------------------------- 02381c3bfe37b974deb27e107ee0c868ddd3b0c9 Data/ByteString.hs | 2 ++ Data/ByteString/Builder.hs | 4 +++- Data/ByteString/Builder/ASCII.hs | 5 +++++ Data/ByteString/Builder/Internal.hs | 7 +++++-- Data/ByteString/Internal.hs | 2 ++ Data/ByteString/Lazy.hs | 2 ++ Data/ByteString/Lazy/Internal.hs | 2 ++ 7 files changed, 21 insertions(+), 3 deletions(-) diff --git a/Data/ByteString.hs b/Data/ByteString.hs index bf33a99..42263a6 100644 --- a/Data/ByteString.hs +++ b/Data/ByteString.hs @@ -254,7 +254,9 @@ import System.IO (stdin,stdout,hClose,hFileSize ,IOMode(..)) import System.IO.Error (mkIOError, illegalOperationErrorType) +#if !(MIN_VERSION_base(4,8,0)) import Data.Monoid (Monoid(..)) +#endif #if !defined(__GLASGOW_HASKELL__) import System.IO.Unsafe diff --git a/Data/ByteString/Builder.hs b/Data/ByteString/Builder.hs index 9307872..dccc88c 100644 --- a/Data/ByteString/Builder.hs +++ b/Data/ByteString/Builder.hs @@ -266,7 +266,9 @@ import Foreign -- HADDOCK only imports import qualified Data.ByteString as S (concat) -import Data.Monoid +#if !(MIN_VERSION_base(4,8,0)) +import Data.Monoid (Monoid(..)) +#endif import Data.Foldable (foldMap) import Data.List (intersperse) diff --git a/Data/ByteString/Builder/ASCII.hs b/Data/ByteString/Builder/ASCII.hs index e0d6bdf..e5370fa 100644 --- a/Data/ByteString/Builder/ASCII.hs +++ b/Data/ByteString/Builder/ASCII.hs @@ -86,14 +86,19 @@ import Foreign #if defined(__GLASGOW_HASKELL__) && defined(INTEGER_GMP) + +#if !(MIN_VERSION_base(4,8,0)) import Data.Monoid (mappend) +# endif import Foreign.C.Types import qualified Data.ByteString.Builder.Prim.Internal as P import Data.ByteString.Builder.Prim.Internal.UncheckedShifts ( caseWordSize_32_64 ) +# if __GLASGOW_HASKELL__ < 710 import GHC.Num (quotRemInteger) +# endif import GHC.Types (Int(..)) diff --git a/Data/ByteString/Builder/Internal.hs b/Data/ByteString/Builder/Internal.hs index d52c626..838ec9f 100644 --- a/Data/ByteString/Builder/Internal.hs +++ b/Data/ByteString/Builder/Internal.hs @@ -129,10 +129,13 @@ module Data.ByteString.Builder.Internal ( ) where import Control.Arrow (second) -import Control.Applicative (Applicative(..), (<$>)) --- import Control.Exception (return) +#if !(MIN_VERSION_base(4,8,0)) import Data.Monoid +import Control.Applicative (Applicative(..)) +#endif +import Control.Applicative ((<$>)) + import qualified Data.ByteString as S import qualified Data.ByteString.Internal as S import qualified Data.ByteString.Lazy.Internal as L diff --git a/Data/ByteString/Internal.hs b/Data/ByteString/Internal.hs index 90e2424..0346d01 100644 --- a/Data/ByteString/Internal.hs +++ b/Data/ByteString/Internal.hs @@ -93,7 +93,9 @@ import Foreign.C.Types (CInt, CSize, CULong) #endif import Foreign.C.String (CString) +#if !(MIN_VERSION_base(4,8,0)) import Data.Monoid (Monoid(..)) +#endif import Control.DeepSeq (NFData(rnf)) #if MIN_VERSION_base(3,0,0) diff --git a/Data/ByteString/Lazy.hs b/Data/ByteString/Lazy.hs index b001d7c..ad8938b 100644 --- a/Data/ByteString/Lazy.hs +++ b/Data/ByteString/Lazy.hs @@ -222,7 +222,9 @@ import qualified Data.ByteString.Internal as S import qualified Data.ByteString.Unsafe as S import Data.ByteString.Lazy.Internal +#if !(MIN_VERSION_base(4,8,0)) import Data.Monoid (Monoid(..)) +#endif import Control.Monad (mplus) import Data.Word (Word8) diff --git a/Data/ByteString/Lazy/Internal.hs b/Data/ByteString/Lazy/Internal.hs index 9ed6d05..550e90f 100644 --- a/Data/ByteString/Lazy/Internal.hs +++ b/Data/ByteString/Lazy/Internal.hs @@ -53,7 +53,9 @@ import qualified Data.ByteString as S (length, take, drop) import Data.Word (Word8) import Foreign.Storable (Storable(sizeOf)) +#if !(MIN_VERSION_base(4,8,0)) import Data.Monoid (Monoid(..)) +#endif import Control.DeepSeq (NFData, rnf) #if MIN_VERSION_base(3,0,0) From git at git.haskell.org Fri Mar 20 19:36:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 19:36:43 +0000 (UTC) Subject: [commit: packages/bytestring] master: Fix the testsuite (c2ddcf9) Message-ID: <20150320193643.2B0583A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/c2ddcf96cdc6bf83206457a781801f6ff45a1aa6 >--------------------------------------------------------------- commit c2ddcf96cdc6bf83206457a781801f6ff45a1aa6 Author: Duncan Coutts Date: Fri Mar 20 18:45:38 2015 +0000 Fix the testsuite >--------------------------------------------------------------- c2ddcf96cdc6bf83206457a781801f6ff45a1aa6 tests/Properties.hs | 20 ++++++++++---------- tests/QuickCheckUtils.hs | 35 ----------------------------------- tests/bytestring-tests.cabal | 6 +++--- 3 files changed, 13 insertions(+), 48 deletions(-) diff --git a/tests/Properties.hs b/tests/Properties.hs index a42a86d..7d86e27 100644 --- a/tests/Properties.hs +++ b/tests/Properties.hs @@ -77,7 +77,7 @@ prop_allCC = D.all `eq2` C.all prop_anyCC = D.any `eq2` C.any prop_appendCC = D.append `eq2` C.append prop_breakCC = D.break `eq2` C.break -prop_concatMapCC = adjustSize (min 50) $ +prop_concatMapCC = forAll (sized $ \n -> resize (min 50 n) arbitrary) $ D.concatMap `eq2` C.concatMap prop_consCC = D.cons `eq2` C.cons prop_consCC' = D.cons' `eq2` C.cons @@ -147,7 +147,7 @@ prop_mapAccumLCC = eq3 -- ByteString.Lazy <=> ByteString -- -prop_concatBP = adjustSize (`div` 2) $ +prop_concatBP = forAll (sized $ \n -> resize (n `div` 2) arbitrary) $ L.concat `eq1` P.concat prop_nullBP = L.null `eq1` P.null prop_reverseBP = L.reverse `eq1` P.reverse @@ -161,7 +161,7 @@ prop_allBP = L.all `eq2` P.all prop_anyBP = L.any `eq2` P.any prop_appendBP = L.append `eq2` P.append prop_breakBP = L.break `eq2` P.break -prop_concatMapBP = adjustSize (`div` 4) $ +prop_concatMapBP = forAll (sized $ \n -> resize (n `div` 4) arbitrary) $ L.concatMap `eq2` P.concatMap prop_consBP = L.cons `eq2` P.cons prop_consBP' = L.cons' `eq2` P.cons @@ -332,7 +332,7 @@ prop_repeatL = -- properties comparing ByteString.Lazy `eq1` List -- -prop_concatBL = adjustSize (`div` 2) $ +prop_concatBL = forAll (sized $ \n -> resize (n `div` 2) arbitrary) $ L.concat `eq1` (concat :: [[W]] -> [W]) prop_lengthBL = L.length `eq1` (toInt64 . length :: [W] -> Int64) prop_nullBL = L.null `eq1` (null :: [W] -> Bool) @@ -346,7 +346,7 @@ prop_allBL = L.all `eq2` (all :: (W -> Bool) -> prop_anyBL = L.any `eq2` (any :: (W -> Bool) -> [W] -> Bool) prop_appendBL = L.append `eq2` ((++) :: [W] -> [W] -> [W]) prop_breakBL = L.break `eq2` (break :: (W -> Bool) -> [W] -> ([W],[W])) -prop_concatMapBL = adjustSize (`div` 2) $ +prop_concatMapBL = forAll (sized $ \n -> resize (n `div` 2) arbitrary) $ L.concatMap `eq2` (concatMap :: (W -> [W]) -> [W] -> [W]) prop_consBL = L.cons `eq2` ((:) :: W -> [W] -> [W]) prop_dropBL = (L.drop . toInt64) `eq2` (drop :: Int -> [W] -> [W]) @@ -431,13 +431,13 @@ prop_groupPL = P.group `eq1` (group :: [W] -> [[W]]) prop_groupByPL = P.groupBy `eq2` (groupBy :: (W -> W -> Bool) -> [W] -> [[W]]) prop_initsPL = P.inits `eq1` (inits :: [W] -> [[W]]) prop_tailsPL = P.tails `eq1` (tails :: [W] -> [[W]]) -prop_concatPL = adjustSize (`div` 2) $ +prop_concatPL = forAll (sized $ \n -> resize (n `div` 2) arbitrary) $ P.concat `eq1` (concat :: [[W]] -> [W]) prop_allPL = P.all `eq2` (all :: (W -> Bool) -> [W] -> Bool) prop_anyPL = P.any `eq2` (any :: (W -> Bool) -> [W] -> Bool) prop_appendPL = P.append `eq2` ((++) :: [W] -> [W] -> [W]) prop_breakPL = P.break `eq2` (break :: (W -> Bool) -> [W] -> ([W],[W])) -prop_concatMapPL = adjustSize (`div` 2) $ +prop_concatMapPL = forAll (sized $ \n -> resize (n `div` 2) arbitrary) $ P.concatMap `eq2` (concatMap :: (W -> [W]) -> [W] -> [W]) prop_consPL = P.cons `eq2` ((:) :: W -> [W] -> [W]) prop_dropPL = P.drop `eq2` (drop :: Int -> [W] -> [W]) @@ -655,8 +655,8 @@ prop_foldr1_3 xs = prop_concat1 xs = (concat [xs,xs]) == (unpack $ L.concat [pack xs, pack xs]) prop_concat2 xs = (concat [xs,[]]) == (unpack $ L.concat [pack xs, pack []]) -prop_concat3 xss = adjustSize (`div` 2) $ - L.concat (map pack xss) == pack (concat xss) +prop_concat3 = forAll (sized $ \n -> resize (n `div` 2) arbitrary) $ \xss -> + L.concat (map pack xss) == pack (concat xss) prop_concatMap xs = L.concatMap L.singleton xs == (pack . concatMap (:[]) . unpack) xs @@ -667,7 +667,7 @@ prop_maximum xs = (not (null xs)) ==> (maximum xs) == (L.maximum ( pack xs )) prop_minimum xs = (not (null xs)) ==> (minimum xs) == (L.minimum ( pack xs )) prop_replicate1 c = - forAll arbitrarySizedIntegral $ \(Positive n) -> + forAll arbitrary $ \(Positive n) -> unpack (L.replicate (fromIntegral n) c) == replicate n c prop_replicate2 c = unpack (L.replicate 0 c) == replicate 0 c diff --git a/tests/QuickCheckUtils.hs b/tests/QuickCheckUtils.hs index 959ea86..55730a1 100644 --- a/tests/QuickCheckUtils.hs +++ b/tests/QuickCheckUtils.hs @@ -27,41 +27,6 @@ import qualified Data.ByteString.Lazy.Char8 as LC ------------------------------------------------------------------------ -adjustSize :: Testable prop => (Int -> Int) -> prop -> Property -adjustSize f p = sized $ \sz -> resize (f sz) (property p) - ------------------------------------------------------------------------- - -{- - --- HUGS needs: - -instance Functor ((->) r) where - fmap = (.) - -instance (Arbitrary a) => Arbitrary (Maybe a) where - arbitrary = sized arbMaybe - where - arbMaybe 0 = return Nothing - arbMaybe n = fmap Just (resize (n-1) arbitrary) - coarbitrary Nothing = variant 0 - coarbitrary (Just x) = variant 1 . coarbitrary x - -instance Monad ((->) r) where - return = const - f >>= k = \ r -> k (f r) r - -instance Functor ((,) a) where - fmap f (x,y) = (x, f y) - -instance Functor (Either a) where - fmap _ (Left x) = Left x - fmap f (Right y) = Right (f y) - --} - ------------------------------------------------------------------------- - integralRandomR :: (Integral a, RandomGen g) => (a,a) -> g -> (a,g) integralRandomR (a,b) g = case randomR (fromIntegral a :: Integer, fromIntegral b :: Integer) g of diff --git a/tests/bytestring-tests.cabal b/tests/bytestring-tests.cabal index d84fc6b..79f7686 100644 --- a/tests/bytestring-tests.cabal +++ b/tests/bytestring-tests.cabal @@ -27,7 +27,7 @@ executable prop-compiled hs-source-dirs: . .. build-depends: base, ghc-prim, deepseq, random, directory, test-framework, test-framework-quickcheck2, - QuickCheck >= 2.3 && < 2.7 + QuickCheck >= 2.3 && < 2.8 c-sources: ../cbits/fpstring.c include-dirs: ../include cpp-options: -DHAVE_TEST_FRAMEWORK=1 @@ -72,9 +72,9 @@ executable test-builder deepseq, QuickCheck >= 2.4 && < 3, byteorder == 1.0.*, - dlist == 0.5.*, + dlist >= 0.5 && < 0.8, directory, - mtl >= 2.0 && < 2.2, + mtl >= 2.0 && < 2.3, HUnit, test-framework, test-framework-hunit, From git at git.haskell.org Fri Mar 20 19:36:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 19:36:45 +0000 (UTC) Subject: [commit: packages/bytestring] master: Update builds with list, dates and drop old TODO (5bc593b) Message-ID: <20150320193645.3536B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/5bc593ba36acafdeb2f3f0c59d498be179b185da >--------------------------------------------------------------- commit 5bc593ba36acafdeb2f3f0c59d498be179b185da Author: Duncan Coutts Date: Fri Mar 20 16:50:57 2015 +0000 Update builds with list, dates and drop old TODO >--------------------------------------------------------------- 5bc593ba36acafdeb2f3f0c59d498be179b185da LICENSE | 2 +- bytestring.cabal | 6 +++--- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/LICENSE b/LICENSE index 2a41eb9..20827fa 100644 --- a/LICENSE +++ b/LICENSE @@ -1,5 +1,5 @@ Copyright (c) Don Stewart 2005-2009 - (c) Duncan Coutts 2006-2011 + (c) Duncan Coutts 2006-2015 (c) David Roundy 2003-2005 (c) Simon Meier 2010-2011 diff --git a/bytestring.cabal b/bytestring.cabal index 40fa4ad..a742667 100644 --- a/bytestring.cabal +++ b/bytestring.cabal @@ -44,7 +44,7 @@ License: BSD3 License-file: LICENSE Category: Data Copyright: Copyright (c) Don Stewart 2005-2009, - (c) Duncan Coutts 2006-2013, + (c) Duncan Coutts 2006-2015, (c) David Roundy 2003-2005, (c) Jasper Van der Jeugt 2010, (c) Simon Meier 2010-2013. @@ -54,10 +54,10 @@ Author: Don Stewart, Maintainer: Duncan Coutts Homepage: https://github.com/haskell/bytestring Bug-reports: https://github.com/haskell/bytestring/issues -Tested-With: GHC==7.8.1, GHC==7.6.3, GHC==7.4.2, GHC==7.0.4, GHC==6.12.3 +Tested-With: GHC==7.10.1, GHC==7.8.4, GHC==7.6.3, GHC==7.4.2, GHC==6.12.3 Build-Type: Simple Cabal-Version: >= 1.10 -extra-source-files: README.md TODO +extra-source-files: README.md source-repository head type: git From git at git.haskell.org Fri Mar 20 19:36:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 19:36:47 +0000 (UTC) Subject: [commit: packages/bytestring] master: Update changelog and add it to the tarball (3ce8218) Message-ID: <20150320193647.42F453A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring On branch : master Link : http://git.haskell.org/packages/bytestring.git/commitdiff/3ce82181141cb053bb4d25b428cf2539258b709a >--------------------------------------------------------------- commit 3ce82181141cb053bb4d25b428cf2539258b709a Author: Duncan Coutts Date: Fri Mar 20 16:54:35 2015 +0000 Update changelog and add it to the tarball >--------------------------------------------------------------- 3ce82181141cb053bb4d25b428cf2539258b709a Changelog.md | 4 +++- bytestring.cabal | 2 +- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/Changelog.md b/Changelog.md index 731256e..5f4e644 100644 --- a/Changelog.md +++ b/Changelog.md @@ -1,11 +1,13 @@ -0.10.5.x (current development version) +0.10.6.0 Duncan Coutts Mar 2015 * Rename inlinePerformIO so people don't misuse it * Fix a corner case in unfoldrN * Export isSuffixOf from D.B.Lazy.Char8 * Add D.B.Lazy.elemIndexEnd * Fix readFile for files with incorrectly reported file size + * Fix for builder performance with ghc 7.10 + * Fix building with ghc 6.12 0.10.4.1 Duncan Coutts Nov 2014 diff --git a/bytestring.cabal b/bytestring.cabal index a742667..6f6d68d 100644 --- a/bytestring.cabal +++ b/bytestring.cabal @@ -57,7 +57,7 @@ Bug-reports: https://github.com/haskell/bytestring/issues Tested-With: GHC==7.10.1, GHC==7.8.4, GHC==7.6.3, GHC==7.4.2, GHC==6.12.3 Build-Type: Simple Cabal-Version: >= 1.10 -extra-source-files: README.md +extra-source-files: README.md Changelog.md source-repository head type: git From git at git.haskell.org Fri Mar 20 19:37:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 19:37:59 +0000 (UTC) Subject: [commit: ghc] master: Update bytestring submodule to 0.10.6.0 release tag (c746f01) Message-ID: <20150320193759.D9A9A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c746f016fa68b2b0b539f3c8e126d0c9a4f3e5e2/ghc >--------------------------------------------------------------- commit c746f016fa68b2b0b539f3c8e126d0c9a4f3e5e2 Author: Herbert Valerio Riedel Date: Fri Mar 20 20:37:41 2015 +0100 Update bytestring submodule to 0.10.6.0 release tag >--------------------------------------------------------------- c746f016fa68b2b0b539f3c8e126d0c9a4f3e5e2 libraries/bytestring | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/bytestring b/libraries/bytestring index 08d5c3a..c2ddcf9 160000 --- a/libraries/bytestring +++ b/libraries/bytestring @@ -1 +1 @@ -Subproject commit 08d5c3a80be94a9d7ef7731317dea79aaadbd2c4 +Subproject commit c2ddcf96cdc6bf83206457a781801f6ff45a1aa6 From git at git.haskell.org Fri Mar 20 19:39:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 20 Mar 2015 19:39:05 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update bytestring submodule to 0.10.6.0 release tag (acbfc19) Message-ID: <20150320193905.30F8D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/acbfc19a6d27b51aaec5177e4b64ea9b45f74c84/ghc >--------------------------------------------------------------- commit acbfc19a6d27b51aaec5177e4b64ea9b45f74c84 Author: Herbert Valerio Riedel Date: Fri Mar 20 20:37:41 2015 +0100 Update bytestring submodule to 0.10.6.0 release tag (cherry picked from commit c746f016fa68b2b0b539f3c8e126d0c9a4f3e5e2) >--------------------------------------------------------------- acbfc19a6d27b51aaec5177e4b64ea9b45f74c84 libraries/bytestring | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/bytestring b/libraries/bytestring index 08d5c3a..c2ddcf9 160000 --- a/libraries/bytestring +++ b/libraries/bytestring @@ -1 +1 @@ -Subproject commit 08d5c3a80be94a9d7ef7731317dea79aaadbd2c4 +Subproject commit c2ddcf96cdc6bf83206457a781801f6ff45a1aa6 From git at git.haskell.org Sat Mar 21 09:05:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 21 Mar 2015 09:05:29 +0000 (UTC) Subject: [commit: ghc] master: Update Cabal submodule to Cabal-v1.22.2.0 rls tag (d9e0e16) Message-ID: <20150321090529.BB3AD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d9e0e165804cb97273bc88372c5429619d74636f/ghc >--------------------------------------------------------------- commit d9e0e165804cb97273bc88372c5429619d74636f Author: Herbert Valerio Riedel Date: Sat Mar 21 10:04:02 2015 +0100 Update Cabal submodule to Cabal-v1.22.2.0 rls tag this submdoule updates pulls in only meta-data changes >--------------------------------------------------------------- d9e0e165804cb97273bc88372c5429619d74636f libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index b7b98fc..5386dd5 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit b7b98fc4a1603eec5af7efcab13afadee1da6c3a +Subproject commit 5386dd5c167a7fe7c3d17ba93803e1f477360df3 From git at git.haskell.org Sat Mar 21 09:06:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 21 Mar 2015 09:06:44 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update Cabal submodule to Cabal-v1.22.2.0 rls tag (6153d16) Message-ID: <20150321090644.AFD5A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/6153d16c755f45845b8911dd4562e5f999d15846/ghc >--------------------------------------------------------------- commit 6153d16c755f45845b8911dd4562e5f999d15846 Author: Herbert Valerio Riedel Date: Sat Mar 21 10:04:02 2015 +0100 Update Cabal submodule to Cabal-v1.22.2.0 rls tag this submdoule updates pulls in only meta-data changes (cherry picked from commit d9e0e165804cb97273bc88372c5429619d74636f) >--------------------------------------------------------------- 6153d16c755f45845b8911dd4562e5f999d15846 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index b7b98fc..5386dd5 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit b7b98fc4a1603eec5af7efcab13afadee1da6c3a +Subproject commit 5386dd5c167a7fe7c3d17ba93803e1f477360df3 From git at git.haskell.org Sat Mar 21 12:00:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 21 Mar 2015 12:00:24 +0000 (UTC) Subject: [commit: ghc] master: Correct documentation in `Parser`. (1cc46b1) Message-ID: <20150321120024.4A7F63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1cc46b1fd5ce794d3a1519c65dcf4aded317598b/ghc >--------------------------------------------------------------- commit 1cc46b1fd5ce794d3a1519c65dcf4aded317598b Author: Matthew Pickering Date: Sat Mar 21 12:57:18 2015 +0100 Correct documentation in `Parser`. Removed a trailing `in` from the final line which caused a compilation error. [skip ci] Reviewed by: thomie Differential Revision: https://phabricator.haskell.org/D744 >--------------------------------------------------------------- 1cc46b1fd5ce794d3a1519c65dcf4aded317598b compiler/parser/Parser.y | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 832b6c9..9389708 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -28,7 +28,7 @@ -- filename = "\" -- location = mkRealSrcLoc (mkFastString filename) 1 1 -- buffer = stringToStringBuffer str --- parseState = mkPState flags buffer location in +-- parseState = mkPState flags buffer location -- @ module Parser (parseModule, parseImport, parseStatement, parseDeclaration, parseExpression, parseTypeSignature, From git at git.haskell.org Sat Mar 21 22:30:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 21 Mar 2015 22:30:23 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Remove unused parameter to `EvTypeableTyCon` (4631675) Message-ID: <20150321223023.0AE443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/463167577b8d621369df91a0b845acdd1d027db1/ghc >--------------------------------------------------------------- commit 463167577b8d621369df91a0b845acdd1d027db1 Author: Iavor S. Diatchki Date: Thu Mar 19 15:33:50 2015 -0700 Remove unused parameter to `EvTypeableTyCon` (cherry picked from commit 75ef8b3b56f0b33c6be782b59a55b853565ea5f4) >--------------------------------------------------------------- 463167577b8d621369df91a0b845acdd1d027db1 compiler/deSugar/DsBinds.hs | 7 +++---- compiler/typecheck/TcEvidence.hs | 7 +++---- compiler/typecheck/TcHsSyn.hs | 2 +- compiler/typecheck/TcInteract.hs | 2 +- 4 files changed, 8 insertions(+), 10 deletions(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index 0031040..76b53ac 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -919,7 +919,7 @@ dsEvTypeable ev = (ty, rep) <- case ev of - EvTypeableTyCon tc ks ts -> + EvTypeableTyCon tc ks -> do ctr <- dsLookupGlobalId mkPolyTyConAppName mkTyCon <- dsLookupGlobalId mkTyConName dflags <- getDynFlags @@ -938,10 +938,9 @@ dsEvTypeable ev = tcRep <- tyConRep dflags mkTyCon tc kReps <- mapM kindRep ks - tReps <- mapM (getRep tyCl) ts - return ( mkTyConApp tc (ks ++ map snd ts) - , mkRep tcRep kReps tReps + return ( mkTyConApp tc ks + , mkRep tcRep kReps [] ) EvTypeableTyApp t1 t2 -> diff --git a/compiler/typecheck/TcEvidence.hs b/compiler/typecheck/TcEvidence.hs index 5bfd209..a5a727b 100644 --- a/compiler/typecheck/TcEvidence.hs +++ b/compiler/typecheck/TcEvidence.hs @@ -711,7 +711,7 @@ data EvTerm -- | Instructions on how to make a 'Typeable' dictionary. data EvTypeable - = EvTypeableTyCon TyCon [Kind] [(EvTerm, Type)] + = EvTypeableTyCon TyCon [Kind] -- ^ Dicitionary for concrete type constructors. | EvTypeableTyApp (EvTerm,Type) (EvTerm,Type) @@ -859,7 +859,7 @@ evVarsOfTerms = mapUnionVarSet evVarsOfTerm evVarsOfTypeable :: EvTypeable -> VarSet evVarsOfTypeable ev = case ev of - EvTypeableTyCon _ _ es -> evVarsOfTerms (map fst es) + EvTypeableTyCon _ _ -> emptyVarSet EvTypeableTyApp e1 e2 -> evVarsOfTerms (map fst [e1,e2]) EvTypeableTyLit _ -> emptyVarSet @@ -933,7 +933,6 @@ instance Outputable EvLit where instance Outputable EvTypeable where ppr ev = case ev of - EvTypeableTyCon tc ks ts -> parens (ppr tc <+> sep (map ppr ks) <+> - sep (map (ppr . fst) ts)) + EvTypeableTyCon tc ks -> parens (ppr tc <+> sep (map ppr ks)) EvTypeableTyApp t1 t2 -> parens (ppr (fst t1) <+> ppr (fst t2)) EvTypeableTyLit x -> ppr x diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs index 01b1cf7..4dfd5e9 100644 --- a/compiler/typecheck/TcHsSyn.hs +++ b/compiler/typecheck/TcHsSyn.hs @@ -1250,7 +1250,7 @@ zonkEvTerm _ (EvLit l) = return (EvLit l) zonkEvTerm env (EvTypeable ev) = fmap EvTypeable $ case ev of - EvTypeableTyCon tc ks ts -> EvTypeableTyCon tc ks `fmap` mapM zonk ts + EvTypeableTyCon tc ks -> return (EvTypeableTyCon tc ks) EvTypeableTyApp t1 t2 -> do e1 <- zonk t1 e2 <- zonk t2 return (EvTypeableTyApp e1 e2) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index bd0a5dc..7569d56 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -2133,7 +2133,7 @@ matchTypeableClass clas k t loc doTyCon tc ks = case mapM kindRep ks of Nothing -> return NoInstance - Just kReps -> mkSimpEv (EvTypeableTyCon tc kReps []) + Just kReps -> mkSimpEv (EvTypeableTyCon tc kReps) {- Representation for an application of a type to a type-or-kind. This may happen when the type expression starts with a type variable. From git at git.haskell.org Sat Mar 21 22:30:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 21 Mar 2015 22:30:25 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Improve `Typeable` solver. (32a5d95) Message-ID: <20150321223025.B5B3D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/32a5d959ea47f0ebd3231d41d77c4dd13c138658/ghc >--------------------------------------------------------------- commit 32a5d959ea47f0ebd3231d41d77c4dd13c138658 Author: Iavor S. Diatchki Date: Thu Mar 19 13:40:34 2015 -0700 Improve `Typeable` solver. (cherry picked from commit 3a0019e3672097761e7ce09c811018f774febfd2) >--------------------------------------------------------------- 32a5d959ea47f0ebd3231d41d77c4dd13c138658 compiler/typecheck/TcInteract.hs | 31 ++++++++++++++----------------- 1 file changed, 14 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 9e7fe43..bd0a5dc 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -2121,23 +2121,19 @@ constraint solving. matchTypeableClass :: Class -> Kind -> Type -> CtLoc -> TcS LookupInstResult matchTypeableClass clas k t loc | isForAllTy k = return NoInstance - | Just (tc, ks_tys) <- splitTyConApp_maybe t = doTyConApp tc ks_tys + | Just (tc, ks) <- splitTyConApp_maybe t + , all isKind ks = doTyCon tc ks | Just (f,kt) <- splitAppTy_maybe t = doTyApp f kt - | Just _ <- isNumLitTy t = mkEv [] (EvTypeableTyLit t) - | Just _ <- isStrLitTy t = mkEv [] (EvTypeableTyLit t) + | Just _ <- isNumLitTy t = mkSimpEv (EvTypeableTyLit t) + | Just _ <- isStrLitTy t = mkSimpEv (EvTypeableTyLit t) | otherwise = return NoInstance where - -- Representation for type constructor applied to some kinds and some types. - doTyConApp tc ks_ts = + -- Representation for type constructor applied to some kinds + doTyCon tc ks = case mapM kindRep ks of - Nothing -> return NoInstance -- Not concrete kinds - Just kReps -> - do tCts <- mapM subGoal ts - mkEv tCts (EvTypeableTyCon tc kReps (map ctEvTerm tCts `zip` ts)) - where - (ks,ts) = span isKind ks_ts - + Nothing -> return NoInstance + Just kReps -> mkSimpEv (EvTypeableTyCon tc kReps []) {- Representation for an application of a type to a type-or-kind. This may happen when the type expression starts with a type variable. @@ -2152,7 +2148,9 @@ matchTypeableClass clas k t loc | otherwise = do ct1 <- subGoal f ct2 <- subGoal tk - mkEv [ct1,ct2] (EvTypeableTyApp (ctEvTerm ct1,f) (ctEvTerm ct2,tk)) + let realSubs = [ c | (c,Fresh) <- [ct1,ct2] ] + return $ GenInst realSubs + $ EvTypeable $ EvTypeableTyApp (getEv ct1,f) (getEv ct2,tk) -- Representation for concrete kinds. We just use the kind itself, @@ -2162,11 +2160,10 @@ matchTypeableClass clas k t loc mapM_ kindRep ks return ki + getEv (ct,_fresh) = ctEvTerm ct -- Emit a `Typeable` constraint for the given type. subGoal ty = do let goal = mkClassPred clas [ typeKind ty, ty ] - ev <- newWantedEvVarNC loc goal - return ev - + newWantedEvVar loc goal - mkEv subs ev = return (GenInst subs (EvTypeable ev)) + mkSimpEv ev = return (GenInst [] (EvTypeable ev)) From git at git.haskell.org Sat Mar 21 23:07:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 21 Mar 2015 23:07:14 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update haddock submodule to 'master' tip (04ae20c) Message-ID: <20150321230714.1CBF83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/04ae20cc4968524b7a18900ac3c6e4611a2ed8f2/ghc >--------------------------------------------------------------- commit 04ae20cc4968524b7a18900ac3c6e4611a2ed8f2 Author: Herbert Valerio Riedel Date: Thu Mar 19 23:33:50 2015 +0100 Update haddock submodule to 'master' tip >--------------------------------------------------------------- 04ae20cc4968524b7a18900ac3c6e4611a2ed8f2 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 89fc560..0fc494f 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 89fc5605c865d0e0ce5ed7e396102e678426533b +Subproject commit 0fc494f2015b7d9cc2cd80e87d67c430e9842777 From git at git.haskell.org Sun Mar 22 01:13:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 01:13:37 +0000 (UTC) Subject: [commit: ghc] master: testsuite: add test for #10177 (854fd12) Message-ID: <20150322011337.1A1EC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/854fd12358fef51848c2eb5e7e08d9c8cec43e16/ghc >--------------------------------------------------------------- commit 854fd12358fef51848c2eb5e7e08d9c8cec43e16 Author: Austin Seipp Date: Sat Mar 21 20:12:55 2015 -0500 testsuite: add test for #10177 Signed-off-by: Austin Seipp >--------------------------------------------------------------- 854fd12358fef51848c2eb5e7e08d9c8cec43e16 testsuite/tests/typecheck/should_compile/T10177.hs | 10 ++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 11 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T10177.hs b/testsuite/tests/typecheck/should_compile/T10177.hs new file mode 100644 index 0000000..fd84396 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T10177.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE FlexibleContexts #-} +module T10177 where + +import Data.Typeable + +newtype V n a = V [a] + +class Typeable a => C a +instance (Typeable (V n), Typeable a) => C (V n a) diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index a4b497e..d4e71c7 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -444,3 +444,4 @@ test('T10031', normal, compile, ['']) test('T10072', normal, compile_fail, ['']) test('T10100', normal, compile, ['']) test('T10156', normal, compile, ['']) +test('T10177', normal, compile, ['']) From git at git.haskell.org Sun Mar 22 01:16:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 01:16:47 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: testsuite: add test for #10177 (0926edc) Message-ID: <20150322011647.0AF253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/0926edc66bc36d075037f0e455fdaef43c052fae/ghc >--------------------------------------------------------------- commit 0926edc66bc36d075037f0e455fdaef43c052fae Author: Austin Seipp Date: Sat Mar 21 20:12:55 2015 -0500 testsuite: add test for #10177 Signed-off-by: Austin Seipp (cherry picked from commit 854fd12358fef51848c2eb5e7e08d9c8cec43e16) >--------------------------------------------------------------- 0926edc66bc36d075037f0e455fdaef43c052fae testsuite/tests/typecheck/should_compile/T10177.hs | 10 ++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 11 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T10177.hs b/testsuite/tests/typecheck/should_compile/T10177.hs new file mode 100644 index 0000000..fd84396 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T10177.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE FlexibleContexts #-} +module T10177 where + +import Data.Typeable + +newtype V n a = V [a] + +class Typeable a => C a +instance (Typeable (V n), Typeable a) => C (V n a) diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 87d217f..258aa7f 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -440,3 +440,4 @@ test('T9892', normal, compile, ['']) test('T9971', normal, compile, ['']) test('T10031', normal, compile, ['']) test('T10072', normal, compile_fail, ['']) +test('T10177', normal, compile, ['']) From git at git.haskell.org Sun Mar 22 07:17:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 07:17:50 +0000 (UTC) Subject: [commit: packages/haskeline] tag '0.7.1.3' created Message-ID: <20150322071750.7F3B13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline New tag : 0.7.1.3 Referencing: ee562d9ff68564ffbf4adcad969381d9ecfcdb98 From git at git.haskell.org Sun Mar 22 07:17:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 07:17:58 +0000 (UTC) Subject: [commit: packages/haskeline] tag '0.7.2.1' created Message-ID: <20150322071758.484E43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline New tag : 0.7.2.1 Referencing: 59243538439eb5b90da46c3fffec78c068c9189b From git at git.haskell.org Sun Mar 22 07:18:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 07:18:00 +0000 (UTC) Subject: [commit: packages/haskeline] : Fix build on Win32: missing import of Applicative. (c5d6e57) Message-ID: <20150322071800.533B43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : Link : http://git.haskell.org/packages/haskeline.git/commitdiff/c5d6e578856abbf1825f2abb3b86d7d8e4bddbb9 >--------------------------------------------------------------- commit c5d6e578856abbf1825f2abb3b86d7d8e4bddbb9 Author: Judah Jacobson Date: Sat Mar 21 18:51:45 2015 -0700 Fix build on Win32: missing import of Applicative. >--------------------------------------------------------------- c5d6e578856abbf1825f2abb3b86d7d8e4bddbb9 System/Console/Haskeline/Backend/Win32.hsc | 1 + 1 file changed, 1 insertion(+) diff --git a/System/Console/Haskeline/Backend/Win32.hsc b/System/Console/Haskeline/Backend/Win32.hsc index d0a594f..61c9ab2 100644 --- a/System/Console/Haskeline/Backend/Win32.hsc +++ b/System/Console/Haskeline/Backend/Win32.hsc @@ -14,6 +14,7 @@ import Data.List(intercalate) import Control.Concurrent hiding (throwTo) import Data.Char(isPrint) import Data.Maybe(mapMaybe) +import Control.Applicative import Control.Monad import System.Console.Haskeline.Key From git at git.haskell.org Sun Mar 22 07:18:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 07:18:02 +0000 (UTC) Subject: [commit: packages/haskeline] : Bump version to 0.7.2.1 and add changelog. (7a72748) Message-ID: <20150322071802.5A6563A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : Link : http://git.haskell.org/packages/haskeline.git/commitdiff/7a72748b3898e68c99e3d5ae7d06c58dd190b149 >--------------------------------------------------------------- commit 7a72748b3898e68c99e3d5ae7d06c58dd190b149 Author: Judah Jacobson Date: Sat Mar 21 18:53:27 2015 -0700 Bump version to 0.7.2.1 and add changelog. >--------------------------------------------------------------- 7a72748b3898e68c99e3d5ae7d06c58dd190b149 Changelog | 3 +++ haskeline.cabal | 2 +- 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/Changelog b/Changelog index 5ca9601..5cb7cc5 100644 --- a/Changelog +++ b/Changelog @@ -1,3 +1,6 @@ +Changed in version 0.7.2.1: + * Fix build on Windows. + Changed in version 0.7.2.0: * Bump upper-bound on base and filepath libraries to accomodate GHC HEAD (7.10) * Drop Cabal dependency to 1.10 diff --git a/haskeline.cabal b/haskeline.cabal index c37129c..b709ee3 100644 --- a/haskeline.cabal +++ b/haskeline.cabal @@ -1,6 +1,6 @@ Name: haskeline Cabal-Version: >=1.10 -Version: 0.7.2.0 +Version: 0.7.2.1 Category: User Interfaces License: BSD3 License-File: LICENSE From git at git.haskell.org Sun Mar 22 07:21:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 07:21:33 +0000 (UTC) Subject: [commit: packages/haskeline] master's head updated: Bump version to 0.7.2.1 and add changelog. (7a72748) Message-ID: <20150322072133.4D7803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline Branch 'master' now includes: c5d6e57 Fix build on Win32: missing import of Applicative. 7a72748 Bump version to 0.7.2.1 and add changelog. From git at git.haskell.org Sun Mar 22 07:23:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 07:23:59 +0000 (UTC) Subject: [commit: ghc] master: Update haskeline submodule to 0.7.2.1 release tag (899cb3e) Message-ID: <20150322072359.4AAE23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/899cb3e768bf495b396f59dc2b49b7b10eb4ad8c/ghc >--------------------------------------------------------------- commit 899cb3e768bf495b396f59dc2b49b7b10eb4ad8c Author: Herbert Valerio Riedel Date: Sun Mar 22 08:22:03 2015 +0100 Update haskeline submodule to 0.7.2.1 release tag This fixes compilation under windows with pre-AMP GHCs although it's not clear if bootstrapping GHC was affected. (see https://github.com/judah/haskeline/issues/20 for details) >--------------------------------------------------------------- 899cb3e768bf495b396f59dc2b49b7b10eb4ad8c libraries/haskeline | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/haskeline b/libraries/haskeline index 06679b7..7a72748 160000 --- a/libraries/haskeline +++ b/libraries/haskeline @@ -1 +1 @@ -Subproject commit 06679b723fc07ca805d0dc6b328a5762255e93ee +Subproject commit 7a72748b3898e68c99e3d5ae7d06c58dd190b149 From git at git.haskell.org Sun Mar 22 07:26:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 07:26:58 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update haskeline submodule to 0.7.2.1 release tag (507c968) Message-ID: <20150322072659.00ED13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/507c9683dafd9c237ea735a846352b0ea55dc3fb/ghc >--------------------------------------------------------------- commit 507c9683dafd9c237ea735a846352b0ea55dc3fb Author: Herbert Valerio Riedel Date: Sun Mar 22 08:22:03 2015 +0100 Update haskeline submodule to 0.7.2.1 release tag This fixes compilation under windows with pre-AMP GHCs although it's not clear if bootstrapping GHC was affected. (see https://github.com/judah/haskeline/issues/20 for details) (cherry picked from commit 899cb3e768bf495b396f59dc2b49b7b10eb4ad8c) >--------------------------------------------------------------- 507c9683dafd9c237ea735a846352b0ea55dc3fb libraries/haskeline | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/haskeline b/libraries/haskeline index dbffdd9..7a72748 160000 --- a/libraries/haskeline +++ b/libraries/haskeline @@ -1 +1 @@ -Subproject commit dbffdd9fc601fc0b74e9e43d237dba0a10b1e0fe +Subproject commit 7a72748b3898e68c99e3d5ae7d06c58dd190b149 From git at git.haskell.org Sun Mar 22 11:13:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 11:13:13 +0000 (UTC) Subject: [commit: ghc] master: Clarify meaning of the RTS `taskCount` variable (5449b25) Message-ID: <20150322111313.654083A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5449b25d02cca0c4ae706c9152f5f2c6107fe711/ghc >--------------------------------------------------------------- commit 5449b25d02cca0c4ae706c9152f5f2c6107fe711 Author: Thomas Miedema Date: Sun Mar 22 12:04:18 2015 +0100 Clarify meaning of the RTS `taskCount` variable In #9261, there was some confusion about the meaning of the taskCount stats variable in the rts. It turns out that taskCount is not decremented when a worker task is stopped (i.e. from workerTaskStop), but only when freeMyTask is called, which frees the task bound to the current thread. So taskCount is the current number of bound tasks + the total number of worker tasks. This makes the calculation of the current number of bound tasks in rts/Stats.c correct _as is_. [skip ci] Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D746 >--------------------------------------------------------------- 5449b25d02cca0c4ae706c9152f5f2c6107fe711 rts/Task.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/Task.c b/rts/Task.c index 42893fe..be72c1b 100644 --- a/rts/Task.c +++ b/rts/Task.c @@ -27,7 +27,7 @@ // Locks required: all_tasks_mutex. Task *all_tasks = NULL; -nat taskCount; +nat taskCount; // current number of bound tasks + total number of worker tasks. nat workerCount; nat currentWorkerCount; nat peakWorkerCount; From git at git.haskell.org Sun Mar 22 16:22:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 16:22:36 +0000 (UTC) Subject: [commit: ghc] master: Test case for #10176 (5119e09) Message-ID: <20150322162236.B13963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5119e097b5cc08d1e6e94529d8c6d7c654a28829/ghc >--------------------------------------------------------------- commit 5119e097b5cc08d1e6e94529d8c6d7c654a28829 Author: Joachim Breitner Date: Sat Mar 21 15:08:16 2015 +0100 Test case for #10176 originally provided by Neil Mitchell. Despite what he observed, I can observe the bug even with all in one module. >--------------------------------------------------------------- 5119e097b5cc08d1e6e94529d8c6d7c654a28829 testsuite/tests/simplCore/should_compile/T10176.hs | 34 ++++++++++++++++++++++ testsuite/tests/simplCore/should_compile/all.T | 1 + 2 files changed, 35 insertions(+) diff --git a/testsuite/tests/simplCore/should_compile/T10176.hs b/testsuite/tests/simplCore/should_compile/T10176.hs new file mode 100644 index 0000000..e91ccda --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T10176.hs @@ -0,0 +1,34 @@ + +module T10176(buggy) where + +{-# NOINLINE error2Args #-} +error2Args :: () -> () -> a +error2Args _ _ = error "here" + +newtype ReaderT r a = ReaderT { runReaderT :: r -> IO a } + +instance Functor (ReaderT r) where + fmap = undefined + +instance Applicative (ReaderT r) where + pure = liftReaderT . pure + f <*> v = undefined + +instance Monad (ReaderT r) where + return = liftReaderT . return + m >>= k = undefined + m >> k = ReaderT $ \r -> do runReaderT m r; runReaderT k r + +liftReaderT :: IO a -> ReaderT r a +liftReaderT m = ReaderT (const m) + +{-# NOINLINE buggy #-} +buggy fun unit bool = + runReaderT (do + if bool then liftReaderT $ print () else pure () + case fun unit of + True -> do + error2Args unit unit + pure () + _ -> pure () + ) () :: IO () diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index bc1ed26..5520b40 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -211,3 +211,4 @@ test('T9400', only_ways(['optasm']), compile, ['-O0 -ddump-simpl -dsuppress-uniq test('T9583', only_ways(['optasm']), compile, ['']) test('T9565', only_ways(['optasm']), compile, ['']) test('T5821', only_ways(['optasm']), compile, ['']) +test('T10176', [only_ways(['optasm']), expect_broken(10176)], compile, ['']) From git at git.haskell.org Sun Mar 22 16:22:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 16:22:39 +0000 (UTC) Subject: [commit: ghc] master: New lint check: exprIsHNF = True and alts = [] is bogus (29f7c10) Message-ID: <20150322162239.624613A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/29f7c1030260f6efce108f1e8461bb6cd4e6f585/ghc >--------------------------------------------------------------- commit 29f7c1030260f6efce108f1e8461bb6cd4e6f585 Author: Joachim Breitner Date: Sat Mar 21 15:02:07 2015 +0100 New lint check: exprIsHNF = True and alts = [] is bogus >--------------------------------------------------------------- 29f7c1030260f6efce108f1e8461bb6cd4e6f585 compiler/coreSyn/CoreLint.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index 5338359..690836a 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -637,6 +637,9 @@ lintCoreExpr e@(Case scrut var alt_ty alts) = ; alt_ty <- lintInTy alt_ty ; var_ty <- lintInTy (idType var) + ; checkL (not (null alts && exprIsHNF scrut)) + (ptext (sLit "No alternatives for a case scrutinee in head-normal form:") <+> ppr scrut) + ; case tyConAppTyCon_maybe (idType var) of Just tycon | debugIsOn && From git at git.haskell.org Sun Mar 22 16:22:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 16:22:42 +0000 (UTC) Subject: [commit: ghc] master: Trim Call Arity (b4efac5) Message-ID: <20150322162242.154323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b4efac59ef5aac74d382d1fd57652982edddbe75/ghc >--------------------------------------------------------------- commit b4efac59ef5aac74d382d1fd57652982edddbe75 Author: Joachim Breitner Date: Sat Mar 21 15:58:38 2015 +0100 Trim Call Arity to not accidentially invalidate a strictness signature with a Diverges result info. This seems to fix #10176. Differential Revision: https://phabricator.haskell.org/D747 >--------------------------------------------------------------- b4efac59ef5aac74d382d1fd57652982edddbe75 compiler/simplCore/CallArity.hs | 51 +++++++++++++++++++++++--- testsuite/tests/simplCore/should_compile/all.T | 2 +- 2 files changed, 47 insertions(+), 6 deletions(-) diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs index 36a8b96..4a0b8ee 100644 --- a/compiler/simplCore/CallArity.hs +++ b/compiler/simplCore/CallArity.hs @@ -18,6 +18,7 @@ import CoreArity ( typeArity ) import CoreUtils ( exprIsHNF ) --import Outputable import UnVarGraph +import Demand import Control.Arrow ( first, second ) @@ -360,6 +361,28 @@ to them. The plan is as follows: Treat the top-level binds as nested lets around a body representing ?all external calls?, which returns a pessimistic CallArityRes (the co-call graph is the complete graph, all arityies 0). +Note [Trimming arity] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +In the Call Arity papers, we are working on an untyped lambda calculus with no +other id annotations, where eta-expansion is always possible. But this is not +the case for Core! + 1. We need to ensure the invariant + callArity e <= typeArity (exprType e) + for the same reasons that exprArity needs this invariant (see Note + [exprArity invariant] in CoreArity). + + If we are not doing that, a too-high arity annotation will be stored with + the id, confusing the simplifier later on. + + 2. Eta-expanding a right hand side might invalidate existing annotations. In + particular, if an id has a strictness annotation of <...><...>b, then + passing one argument to it will definitely bottom out, so the simplifier + will throw away additional parameters. This conflicts with Call Arity! So + we ensure that we never eta-expand such a value beyond the number of + arguments mentioned in the strictness signature. + See #10176 for a real-world-example. + -} -- Main entry point @@ -506,15 +529,19 @@ callArityBind ae_body int (NonRec v rhs) safe_arity | called_once = arity | is_thunk = 0 -- A thunk! Do not eta-expand | otherwise = arity - (ae_rhs, rhs') = callArityAnal safe_arity int rhs + + -- See Note [Trimming arity] + trimmed_arity = trimArity v safe_arity + + (ae_rhs, rhs') = callArityAnal trimmed_arity int rhs + ae_rhs'| called_once = ae_rhs | safe_arity == 0 = ae_rhs -- If it is not a function, its body is evaluated only once | otherwise = calledMultipleTimes ae_rhs final_ae = callArityNonRecEnv v ae_rhs' ae_body - v' = v `setIdCallArity` safe_arity - + v' = v `setIdCallArity` trimmed_arity -- Recursive let. See Note [Recursion and fixpointing] @@ -558,19 +585,33 @@ callArityBind ae_body int b@(Rec binds) safe_arity | is_thunk = 0 -- See Note [Thunks in recursive groups] | otherwise = new_arity - (ae_rhs, rhs') = callArityAnal safe_arity int_body rhs + -- See Note [Trimming arity] + trimmed_arity = trimArity i safe_arity + + (ae_rhs, rhs') = callArityAnal trimmed_arity int_body rhs ae_rhs' | called_once = ae_rhs | safe_arity == 0 = ae_rhs -- If it is not a function, its body is evaluated only once | otherwise = calledMultipleTimes ae_rhs - in (True, (i `setIdCallArity` safe_arity, Just (called_once, new_arity, ae_rhs'), rhs')) + in (True, (i `setIdCallArity` trimmed_arity, Just (called_once, new_arity, ae_rhs'), rhs')) where (new_arity, called_once) = lookupCallArityRes ae i (changes, ann_binds') = unzip $ map rerun ann_binds any_change = or changes +-- See Note [Trimming arity] +trimArity :: Id -> Arity -> Arity +trimArity v a = minimum [a, max_arity_by_type, max_arity_by_strsig] + where + max_arity_by_type = length (typeArity (idType v)) + max_arity_by_strsig + | isBotRes result_info = length demands + | otherwise = a + + (demands, result_info) = splitStrictSig (idStrictness v) + -- Combining the results from body and rhs, non-recursive case -- See Note [Analysis II: The Co-Called analysis] callArityNonRecEnv :: Var -> CallArityRes -> CallArityRes -> CallArityRes diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 5520b40..6c000d3 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -211,4 +211,4 @@ test('T9400', only_ways(['optasm']), compile, ['-O0 -ddump-simpl -dsuppress-uniq test('T9583', only_ways(['optasm']), compile, ['']) test('T9565', only_ways(['optasm']), compile, ['']) test('T5821', only_ways(['optasm']), compile, ['']) -test('T10176', [only_ways(['optasm']), expect_broken(10176)], compile, ['']) +test('T10176', only_ways(['optasm']), compile, ['']) From git at git.haskell.org Sun Mar 22 17:03:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 17:03:51 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Test case for #10176 (7e1758a) Message-ID: <20150322170351.63F143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/7e1758a9cf86c28440834d3e3d44737186e5ca5f/ghc >--------------------------------------------------------------- commit 7e1758a9cf86c28440834d3e3d44737186e5ca5f Author: Joachim Breitner Date: Sat Mar 21 15:08:16 2015 +0100 Test case for #10176 originally provided by Neil Mitchell. Despite what he observed, I can observe the bug even with all in one module. (cherry picked from commit 5119e097b5cc08d1e6e94529d8c6d7c654a28829) >--------------------------------------------------------------- 7e1758a9cf86c28440834d3e3d44737186e5ca5f testsuite/tests/simplCore/should_compile/T10176.hs | 34 ++++++++++++++++++++++ testsuite/tests/simplCore/should_compile/all.T | 1 + 2 files changed, 35 insertions(+) diff --git a/testsuite/tests/simplCore/should_compile/T10176.hs b/testsuite/tests/simplCore/should_compile/T10176.hs new file mode 100644 index 0000000..e91ccda --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T10176.hs @@ -0,0 +1,34 @@ + +module T10176(buggy) where + +{-# NOINLINE error2Args #-} +error2Args :: () -> () -> a +error2Args _ _ = error "here" + +newtype ReaderT r a = ReaderT { runReaderT :: r -> IO a } + +instance Functor (ReaderT r) where + fmap = undefined + +instance Applicative (ReaderT r) where + pure = liftReaderT . pure + f <*> v = undefined + +instance Monad (ReaderT r) where + return = liftReaderT . return + m >>= k = undefined + m >> k = ReaderT $ \r -> do runReaderT m r; runReaderT k r + +liftReaderT :: IO a -> ReaderT r a +liftReaderT m = ReaderT (const m) + +{-# NOINLINE buggy #-} +buggy fun unit bool = + runReaderT (do + if bool then liftReaderT $ print () else pure () + case fun unit of + True -> do + error2Args unit unit + pure () + _ -> pure () + ) () :: IO () diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index bbdadbf..998894a 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -209,3 +209,4 @@ test('T6056', only_ways(['optasm']), multimod_compile, ['T6056', '-v0 -ddump-rul test('T9400', only_ways(['optasm']), compile, ['-O0 -ddump-simpl -dsuppress-uniques']) test('T9583', only_ways(['optasm']), compile, ['']) test('T9565', only_ways(['optasm']), compile, ['']) +test('T10176', [only_ways(['optasm']), expect_broken(10176)], compile, ['']) From git at git.haskell.org Sun Mar 22 17:03:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 17:03:54 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Trim Call Arity (011f691) Message-ID: <20150322170354.41BA93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/011f691333aff2833acc900ee3911885e488cf1b/ghc >--------------------------------------------------------------- commit 011f691333aff2833acc900ee3911885e488cf1b Author: Joachim Breitner Date: Sat Mar 21 15:58:38 2015 +0100 Trim Call Arity to not accidentially invalidate a strictness signature with a Diverges result info. This seems to fix #10176. (cherry picked from commit b4efac59ef5aac74d382d1fd57652982edddbe75) >--------------------------------------------------------------- 011f691333aff2833acc900ee3911885e488cf1b compiler/simplCore/CallArity.hs | 51 +++++++++++++++++++++++--- testsuite/tests/simplCore/should_compile/all.T | 2 +- 2 files changed, 47 insertions(+), 6 deletions(-) diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs index 5ee5fe2..2f4f107 100644 --- a/compiler/simplCore/CallArity.hs +++ b/compiler/simplCore/CallArity.hs @@ -18,6 +18,7 @@ import CoreArity ( typeArity ) import CoreUtils ( exprIsHNF ) --import Outputable import UnVarGraph +import Demand import Control.Arrow ( first, second ) @@ -360,6 +361,28 @@ to them. The plan is as follows: Treat the top-level binds as nested lets around a body representing ?all external calls?, which returns a pessimistic CallArityRes (the co-call graph is the complete graph, all arityies 0). +Note [Trimming arity] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +In the Call Arity papers, we are working on an untyped lambda calculus with no +other id annotations, where eta-expansion is always possible. But this is not +the case for Core! + 1. We need to ensure the invariant + callArity e <= typeArity (exprType e) + for the same reasons that exprArity needs this invariant (see Note + [exprArity invariant] in CoreArity). + + If we are not doing that, a too-high arity annotation will be stored with + the id, confusing the simplifier later on. + + 2. Eta-expanding a right hand side might invalidate existing annotations. In + particular, if an id has a strictness annotation of <...><...>b, then + passing one argument to it will definitely bottom out, so the simplifier + will throw away additional parameters. This conflicts with Call Arity! So + we ensure that we never eta-expand such a value beyond the number of + arguments mentioned in the strictness signature. + See #10176 for a real-world-example. + -} -- Main entry point @@ -508,15 +531,19 @@ callArityBind ae_body int (NonRec v rhs) safe_arity | called_once = arity | is_thunk = 0 -- A thunk! Do not eta-expand | otherwise = arity - (ae_rhs, rhs') = callArityAnal safe_arity int rhs + + -- See Note [Trimming arity] + trimmed_arity = trimArity v safe_arity + + (ae_rhs, rhs') = callArityAnal trimmed_arity int rhs + ae_rhs'| called_once = ae_rhs | safe_arity == 0 = ae_rhs -- If it is not a function, its body is evaluated only once | otherwise = calledMultipleTimes ae_rhs final_ae = callArityNonRecEnv v ae_rhs' ae_body - v' = v `setIdCallArity` safe_arity - + v' = v `setIdCallArity` trimmed_arity -- Recursive let. See Note [Recursion and fixpointing] @@ -560,19 +587,33 @@ callArityBind ae_body int b@(Rec binds) safe_arity | is_thunk = 0 -- See Note [Thunks in recursive groups] | otherwise = new_arity - (ae_rhs, rhs') = callArityAnal safe_arity int_body rhs + -- See Note [Trimming arity] + trimmed_arity = trimArity i safe_arity + + (ae_rhs, rhs') = callArityAnal trimmed_arity int_body rhs ae_rhs' | called_once = ae_rhs | safe_arity == 0 = ae_rhs -- If it is not a function, its body is evaluated only once | otherwise = calledMultipleTimes ae_rhs - in (True, (i `setIdCallArity` safe_arity, Just (called_once, new_arity, ae_rhs'), rhs')) + in (True, (i `setIdCallArity` trimmed_arity, Just (called_once, new_arity, ae_rhs'), rhs')) where (new_arity, called_once) = lookupCallArityRes ae i (changes, ann_binds') = unzip $ map rerun ann_binds any_change = or changes +-- See Note [Trimming arity] +trimArity :: Id -> Arity -> Arity +trimArity v a = minimum [a, max_arity_by_type, max_arity_by_strsig] + where + max_arity_by_type = length (typeArity (idType v)) + max_arity_by_strsig + | isBotRes result_info = length demands + | otherwise = a + + (demands, result_info) = splitStrictSig (idStrictness v) + -- Combining the results from body and rhs, non-recursive case -- See Note [Analysis II: The Co-Called analysis] callArityNonRecEnv :: Var -> CallArityRes -> CallArityRes -> CallArityRes diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 998894a..32aa8ea 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -209,4 +209,4 @@ test('T6056', only_ways(['optasm']), multimod_compile, ['T6056', '-v0 -ddump-rul test('T9400', only_ways(['optasm']), compile, ['-O0 -ddump-simpl -dsuppress-uniques']) test('T9583', only_ways(['optasm']), compile, ['']) test('T9565', only_ways(['optasm']), compile, ['']) -test('T10176', [only_ways(['optasm']), expect_broken(10176)], compile, ['']) +test('T10176', only_ways(['optasm']), compile, ['']) From git at git.haskell.org Sun Mar 22 17:53:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 17:53:41 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T10181' created Message-ID: <20150322175341.B3C163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T10181 Referencing: fe42a82e46a8f28ece1ac6d541232f58cb45dec1 From git at git.haskell.org Sun Mar 22 17:53:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 17:53:44 +0000 (UTC) Subject: [commit: ghc] wip/T10181: New lint check: Check idArity invariants (#10181) (fe42a82) Message-ID: <20150322175344.9230C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10181 Link : http://ghc.haskell.org/trac/ghc/changeset/fe42a82e46a8f28ece1ac6d541232f58cb45dec1/ghc >--------------------------------------------------------------- commit fe42a82e46a8f28ece1ac6d541232f58cb45dec1 Author: Joachim Breitner Date: Sun Mar 22 17:51:51 2015 +0100 New lint check: Check idArity invariants (#10181) The arity of an id should not be larger than what the type allows, and it should also not contradict the strictness signature. This adds a lint check for that. >--------------------------------------------------------------- fe42a82e46a8f28ece1ac6d541232f58cb45dec1 compiler/coreSyn/CoreLint.hs | 20 ++++++++++++++++++++ 1 file changed, 20 insertions(+) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index 690836a..a81c9c3 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -56,6 +56,8 @@ import Util import InstEnv ( instanceDFunId ) import OptCoercion ( checkAxInstCo ) import UniqSupply +import CoreArity ( typeArity ) +import Demand ( splitStrictSig, isBotRes ) import HscTypes import DynFlags @@ -487,6 +489,24 @@ lintSingleBinding top_lvl_flag rec_flag (binder,rhs) -- StrictSig dmd_ty -> idArity binder >= dmdTypeDepth dmd_ty || exprIsTrivial rhs) -- (mkArityMsg binder) + -- Check that the binder's arity is within the bounds imposed by + -- the type and the strictness signature. See Note [exprArity invariant] + -- and Note [Trimming arity] + ; checkL (idArity binder <= length (typeArity (idType binder))) + (ptext (sLit "idArity") <+> ppr (idArity binder) <+> + ptext (sLit "exceeds typeArity") <+> + ppr (length (typeArity (idType binder))) <> colon <+> + ppr binder) + + ; case splitStrictSig (idStrictness binder) of + (demands, result_info) | isBotRes result_info -> + checkL (idArity binder <= length demands) + (ptext (sLit "idArity") <+> ppr (idArity binder) <+> + ptext (sLit "exceeds arity imposed by the strictness signature") <+> + ppr (idStrictness binder) <> colon <+> + ppr binder) + _ -> return () + ; lintIdUnfolding binder binder_ty (idUnfolding binder) } -- We should check the unfolding, if any, but this is tricky because From git at git.haskell.org Sun Mar 22 17:53:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 17:53:57 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T10180' created Message-ID: <20150322175357.AEB1D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T10180 Referencing: b3fc549eef9e5e15941e597dfa8c669ea33ff0cc From git at git.haskell.org Sun Mar 22 17:54:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 17:54:00 +0000 (UTC) Subject: [commit: ghc] wip/T10180: New Lint check: no alternatives implies exprIsBottom (b3fc549) Message-ID: <20150322175400.A24113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10180 Link : http://ghc.haskell.org/trac/ghc/changeset/b3fc549eef9e5e15941e597dfa8c669ea33ff0cc/ghc >--------------------------------------------------------------- commit b3fc549eef9e5e15941e597dfa8c669ea33ff0cc Author: Joachim Breitner Date: Sun Mar 22 17:32:26 2015 +0100 New Lint check: no alternatives implies exprIsBottom as suggested by SPJ. This fixes #10180. >--------------------------------------------------------------- b3fc549eef9e5e15941e597dfa8c669ea33ff0cc compiler/coreSyn/CoreLint.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index 690836a..5ff2f92 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -637,8 +637,12 @@ lintCoreExpr e@(Case scrut var alt_ty alts) = ; alt_ty <- lintInTy alt_ty ; var_ty <- lintInTy (idType var) - ; checkL (not (null alts && exprIsHNF scrut)) + ; when (null alts) $ + do { checkL (not (exprIsHNF scrut)) (ptext (sLit "No alternatives for a case scrutinee in head-normal form:") <+> ppr scrut) + ; checkL (exprIsBottom scrut) + (ptext (sLit "No alternatives for a case scrutinee not known to diverge for sure:") <+> ppr scrut) + } ; case tyConAppTyCon_maybe (idType var) of Just tycon From git at git.haskell.org Sun Mar 22 19:11:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 19:11:43 +0000 (UTC) Subject: [commit: ghc] master: docs: make gen_contents_index --verbose more verbose (e25ad04) Message-ID: <20150322191143.CF6263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e25ad0424019e9727a49a88ebea0092fdf17b467/ghc >--------------------------------------------------------------- commit e25ad0424019e9727a49a88ebea0092fdf17b467 Author: Austin Seipp Date: Sun Mar 22 14:11:22 2015 -0500 docs: make gen_contents_index --verbose more verbose Signed-off-by: Austin Seipp >--------------------------------------------------------------- e25ad0424019e9727a49a88ebea0092fdf17b467 libraries/gen_contents_index | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/libraries/gen_contents_index b/libraries/gen_contents_index index 34e51f3..b583b88 100644 --- a/libraries/gen_contents_index +++ b/libraries/gen_contents_index @@ -75,7 +75,9 @@ fi # Now create the combined contents and index pages if [ -n "$VERBOSE" ] then - echo $HADDOCK_ARGS + echo $HADDOCK --gen-index --gen-contents -o . \ + -t "Haskell Hierarchical Libraries" \ + $HADDOCK_ARGS fi $HADDOCK --gen-index --gen-contents -o . \ -t "Haskell Hierarchical Libraries" \ From git at git.haskell.org Sun Mar 22 19:12:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 19:12:26 +0000 (UTC) Subject: [commit: ghc] wip/T10180: New Lint check: no alternatives implies bottoming expression (a7d24cd) Message-ID: <20150322191226.38C583A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10180 Link : http://ghc.haskell.org/trac/ghc/changeset/a7d24cd9c100655b487f1911cb014fea738cd36c/ghc >--------------------------------------------------------------- commit a7d24cd9c100655b487f1911cb014fea738cd36c Author: Joachim Breitner Date: Sun Mar 22 17:32:26 2015 +0100 New Lint check: no alternatives implies bottoming expression detected either by exprIsBottom or by an empty type. This was suggested by SPJ and fixes #10180. >--------------------------------------------------------------- a7d24cd9c100655b487f1911cb014fea738cd36c compiler/coreSyn/CoreLint.hs | 6 +++++- compiler/types/TyCon.hs | 10 ++++++++++ compiler/types/Type.hs | 12 +++++++++++- 3 files changed, 26 insertions(+), 2 deletions(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index 690836a..c615ea6 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -637,8 +637,12 @@ lintCoreExpr e@(Case scrut var alt_ty alts) = ; alt_ty <- lintInTy alt_ty ; var_ty <- lintInTy (idType var) - ; checkL (not (null alts && exprIsHNF scrut)) + ; when (null alts) $ + do { checkL (not (exprIsHNF scrut)) (ptext (sLit "No alternatives for a case scrutinee in head-normal form:") <+> ppr scrut) + ; checkL (exprIsBottom scrut || isEmptyTy (exprType scrut)) + (ptext (sLit "No alternatives for a case scrutinee not known to diverge for sure:") <+> ppr scrut) + } ; case tyConAppTyCon_maybe (idType var) of Just tycon diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index 8e0175a..c3723c4 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -42,6 +42,7 @@ module TyCon( promotableTyCon_maybe, promoteTyCon, isDataTyCon, isProductTyCon, isDataProductTyCon_maybe, + isEmptyDataTyCon, isEnumerationTyCon, isNewTyCon, isAbstractTyCon, isFamilyTyCon, isOpenFamilyTyCon, @@ -1286,6 +1287,15 @@ isDataProductTyCon_maybe (TupleTyCon { dataCon = con }) = Just con isDataProductTyCon_maybe _ = Nothing +-- | True of datatypes with no constructors +isEmptyDataTyCon :: TyCon -> Bool +isEmptyDataTyCon tc + | AlgTyCon {algTcRhs = rhs} <- tc + , [] <- data_cons rhs + = True + | otherwise + = False + -- | Is this a 'TyCon' representing a regular H98 type synonym (@type@)? isTypeSynonymTyCon :: TyCon -> Bool isTypeSynonymTyCon (SynonymTyCon {}) = True diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index a2d3392..9cec0bd 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -66,7 +66,7 @@ module Type ( -- (Lifting and boxity) isUnLiftedType, isUnboxedTupleType, isAlgType, isClosedAlgType, - isPrimitiveType, isStrictType, + isPrimitiveType, isStrictType, isEmptyTy, -- * Main data types representing Kinds -- $kind_subtyping @@ -1184,6 +1184,16 @@ isPrimitiveType ty = case splitTyConApp_maybe ty of isPrimTyCon tc _ -> False +-- | True if the type has no non-bottom elements +isEmptyTy :: Type -> Bool +isEmptyTy ty + -- Data types with no constructors are empty + | Just (tc, _) <- splitTyConApp_maybe ty + , isEmptyDataTyCon tc + = True + | otherwise + = False + {- ************************************************************************ * * From git at git.haskell.org Sun Mar 22 21:11:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 21:11:20 +0000 (UTC) Subject: [commit: ghc] master: fix bus error (misaligned data access) on SPARC in __decodeDouble_Int64 (12a03c4) Message-ID: <20150322211120.235723A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/12a03c44c006f142f93980e0dbdfab0f73db042c/ghc >--------------------------------------------------------------- commit 12a03c44c006f142f93980e0dbdfab0f73db042c Author: Karel Gardas Date: Sun Mar 22 21:58:03 2015 +0100 fix bus error (misaligned data access) on SPARC in __decodeDouble_Int64 Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D749 >--------------------------------------------------------------- 12a03c44c006f142f93980e0dbdfab0f73db042c rts/StgPrimFloat.c | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/rts/StgPrimFloat.c b/rts/StgPrimFloat.c index e2eeee5..277ae66 100644 --- a/rts/StgPrimFloat.c +++ b/rts/StgPrimFloat.c @@ -182,9 +182,9 @@ __decodeDouble_Int64 (StgInt64 *const mantissa, const StgDouble dbl) I_ exp = 0; __decodeDouble_2Int (&man_sign, &man_high, &man_low, &exp, dbl); - - *mantissa = ((((StgInt64)man_high << 32) | (StgInt64)man_low) - * (StgInt64)man_sign); + ASSIGN_Int64((W_*)mantissa, ((((StgInt64)man_high << 32) + | (StgInt64)man_low) + * (StgInt64)man_sign)); return exp; #endif } From git at git.haskell.org Sun Mar 22 23:57:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 22 Mar 2015 23:57:37 +0000 (UTC) Subject: [commit: ghc] master: rts: check arguments to flags that don't have any (a20cc3d) Message-ID: <20150322235737.8A3E83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a20cc3d00c4ca0753fcdcb16199f173b3af44fe4/ghc >--------------------------------------------------------------- commit a20cc3d00c4ca0753fcdcb16199f173b3af44fe4 Author: Carlos Tom? Date: Mon Mar 23 00:53:42 2015 +0100 rts: check arguments to flags that don't have any There were some flags of the RTS that when given an argument (which they don't have) were not firing an error. e.g -Targument when the flag -T has no argument. Now this is an error and affects the following flags: -B -w -T -Z -P -Pa -c -t Signed-off-by: Carlos Tom? Reviewed By: austin, thomie, hvr Differential Revision: https://phabricator.haskell.org/D748 GHC Trac Issues: #9839 >--------------------------------------------------------------- a20cc3d00c4ca0753fcdcb16199f173b3af44fe4 rts/RtsFlags.c | 35 +++++++++++++++++----- .../tests/{ghc-api/T7478/C.hs => rts/T9839_02.hs} | 0 .../tests/{ghc-api/T7478/C.hs => rts/T9839_03.hs} | 0 testsuite/tests/rts/all.T | 13 ++++++++ 4 files changed, 41 insertions(+), 7 deletions(-) diff --git a/rts/RtsFlags.c b/rts/RtsFlags.c index 6866700..d7114bf 100644 --- a/rts/RtsFlags.c +++ b/rts/RtsFlags.c @@ -791,7 +791,7 @@ error = rtsTrue; case 'B': OPTION_UNSAFE; RtsFlags.GcFlags.ringBell = rtsTrue; - break; + goto check_rest; case 'c': OPTION_UNSAFE; @@ -806,7 +806,7 @@ error = rtsTrue; case 'w': OPTION_UNSAFE; RtsFlags.GcFlags.sweep = rtsTrue; - break; + goto check_rest; case 'F': OPTION_UNSAFE; @@ -957,7 +957,7 @@ error = rtsTrue; case 'T': OPTION_SAFE; RtsFlags.GcFlags.giveStats = COLLECT_GC_STATS; - break; /* Don't initialize statistics file. */ + goto check_rest; /* Don't initialize statistics file. */ case 'S': OPTION_SAFE; /* but see below */ @@ -989,7 +989,7 @@ error = rtsTrue; case 'Z': OPTION_UNSAFE; RtsFlags.GcFlags.squeezeUpdFrames = rtsFalse; - break; + goto check_rest; /* =========== PROFILING ========================== */ @@ -1000,8 +1000,14 @@ error = rtsTrue; switch (rts_argv[arg][2]) { case 'a': RtsFlags.CcFlags.doCostCentres = COST_CENTRES_ALL; + if (rts_argv[arg][3] != '\0') { + errorBelch("flag -Pa given an argument" + " when none was expected: %s" + ,rts_argv[arg]); + error = rtsTrue; + } break; - default: + case '\0': if (rts_argv[arg][1] == 'P') { RtsFlags.CcFlags.doCostCentres = COST_CENTRES_VERBOSE; @@ -1010,6 +1016,8 @@ error = rtsTrue; COST_CENTRES_SUMMARY; } break; + default: + goto check_rest; } ) break; @@ -1362,14 +1370,14 @@ error = rtsTrue; PROFILING_BUILD_ONLY( RtsFlags.ProfFlags.showCCSOnException = rtsTrue; ); - break; + goto check_rest; case 't': /* Include memory used by TSOs in a heap profile */ OPTION_SAFE; PROFILING_BUILD_ONLY( RtsFlags.ProfFlags.includeTSOs = rtsTrue; ); - break; + goto check_rest; /* The option prefix '-xx' is reserved for future extension. KSW 1999-11. */ @@ -1388,6 +1396,19 @@ error = rtsTrue; } break; /* defensive programming */ + /* check the rest to be sure there is nothing afterwards.*/ + /* see Trac #9839 */ + check_rest: + { + if (rts_argv[arg][2] != '\0') { + errorBelch("flag -%c given an argument" + " when none was expected: %s", + rts_argv[arg][1],rts_argv[arg]); + error = rtsTrue; + } + break; + } + /* =========== OH DEAR ============================ */ default: OPTION_SAFE; diff --git a/testsuite/tests/ghc-api/T7478/C.hs b/testsuite/tests/rts/T9839_02.hs old mode 100644 new mode 100755 similarity index 100% copy from testsuite/tests/ghc-api/T7478/C.hs copy to testsuite/tests/rts/T9839_02.hs diff --git a/testsuite/tests/ghc-api/T7478/C.hs b/testsuite/tests/rts/T9839_03.hs old mode 100644 new mode 100755 similarity index 100% copy from testsuite/tests/ghc-api/T7478/C.hs copy to testsuite/tests/rts/T9839_03.hs diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index 86b1bcf..05253fe 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -281,3 +281,16 @@ test('linker_error3', ignore_output ], run_command, ['$MAKE -s --no-print-directory linker_error3']) + +test('T9839_01', [ no_stdin, ignore_output], + run_command, + ['{compiler} -e 1 +RTS -T-s 2>&1 | \ + grep "flag -T given an argument when none was expected: -T-s"']) + +test('T9839_02', [ only_ways(prof_ways), ignore_output, exit_code(1), extra_run_opts('+RTS -Pax')], + compile_and_run, + ['']) + +test('T9839_03', [ only_ways(prof_ways), ignore_output, exit_code(1), extra_run_opts('+RTS -Px')], + compile_and_run, + ['']) From git at git.haskell.org Mon Mar 23 07:15:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 07:15:12 +0000 (UTC) Subject: [commit: ghc] master: Fix integer-gmp source tarball distribution (cab5b3a) Message-ID: <20150323071512.93A063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cab5b3acc514dc7beafc3527625c687c8a5116a0/ghc >--------------------------------------------------------------- commit cab5b3acc514dc7beafc3527625c687c8a5116a0 Author: Herbert Valerio Riedel Date: Mon Mar 23 08:11:32 2015 +0100 Fix integer-gmp source tarball distribution The `configure` script checks for presence of `install-sh` even if it's not used, so we simply add it to the distribution to make `configure` happy. >--------------------------------------------------------------- cab5b3acc514dc7beafc3527625c687c8a5116a0 install-sh => libraries/integer-gmp2/install-sh | 0 libraries/integer-gmp2/integer-gmp.cabal | 1 + 2 files changed, 1 insertion(+) diff --git a/install-sh b/libraries/integer-gmp2/install-sh similarity index 100% copy from install-sh copy to libraries/integer-gmp2/install-sh diff --git a/libraries/integer-gmp2/integer-gmp.cabal b/libraries/integer-gmp2/integer-gmp.cabal index a76e622..4833704 100644 --- a/libraries/integer-gmp2/integer-gmp.cabal +++ b/libraries/integer-gmp2/integer-gmp.cabal @@ -19,6 +19,7 @@ extra-source-files: configure.ac gmp/config.mk.in include/HsIntegerGmp.h.in + install-sh integer-gmp.buildinfo.in extra-tmp-files: From git at git.haskell.org Mon Mar 23 07:15:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 07:15:15 +0000 (UTC) Subject: [commit: ghc] master: Update integer-gmp2's changelog for release (5ef5a18) Message-ID: <20150323071515.573A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5ef5a18de3422479c46663b3858fed16c8954900/ghc >--------------------------------------------------------------- commit 5ef5a18de3422479c46663b3858fed16c8954900 Author: Herbert Valerio Riedel Date: Fri Mar 20 18:52:28 2015 +0100 Update integer-gmp2's changelog for release [skip ci] (cherry picked from commit 7bd3efe3ccc6dc0a3ec84008285b4e03b48d8f41) >--------------------------------------------------------------- 5ef5a18de3422479c46663b3858fed16c8954900 libraries/integer-gmp2/changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/integer-gmp2/changelog.md b/libraries/integer-gmp2/changelog.md index af3ac83..cb55b80 100644 --- a/libraries/integer-gmp2/changelog.md +++ b/libraries/integer-gmp2/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`integer-gmp` package](http://hackage.haskell.org/package/integer-gmp) -## 1.0.0.0 **TBA** +## 1.0.0.0 *Mar 2015* * Bundled with GHC 7.10.1 From git at git.haskell.org Mon Mar 23 07:32:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 07:32:05 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix integer-gmp source tarball distribution (b618d01) Message-ID: <20150323073205.E16423A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/b618d01ef14f56fab65ddb028330148b2a2a47ce/ghc >--------------------------------------------------------------- commit b618d01ef14f56fab65ddb028330148b2a2a47ce Author: Herbert Valerio Riedel Date: Mon Mar 23 08:11:32 2015 +0100 Fix integer-gmp source tarball distribution The `configure` script checks for presence of `install-sh` even if it's not used, so we simply add it to the distribution to make `configure` happy. (cherry picked from commit cab5b3acc514dc7beafc3527625c687c8a5116a0) >--------------------------------------------------------------- b618d01ef14f56fab65ddb028330148b2a2a47ce install-sh => libraries/integer-gmp2/install-sh | 0 libraries/integer-gmp2/integer-gmp.cabal | 1 + 2 files changed, 1 insertion(+) diff --git a/install-sh b/libraries/integer-gmp2/install-sh similarity index 100% copy from install-sh copy to libraries/integer-gmp2/install-sh diff --git a/libraries/integer-gmp2/integer-gmp.cabal b/libraries/integer-gmp2/integer-gmp.cabal index a76e622..4833704 100644 --- a/libraries/integer-gmp2/integer-gmp.cabal +++ b/libraries/integer-gmp2/integer-gmp.cabal @@ -19,6 +19,7 @@ extra-source-files: configure.ac gmp/config.mk.in include/HsIntegerGmp.h.in + install-sh integer-gmp.buildinfo.in extra-tmp-files: From git at git.haskell.org Mon Mar 23 07:49:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 07:49:16 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Set release date for base-4.8.0.0 in changelog (f2c7686) Message-ID: <20150323074916.923633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/f2c76865244c5caeeb5c376b9e1493d59b067320/ghc >--------------------------------------------------------------- commit f2c76865244c5caeeb5c376b9e1493d59b067320 Author: Herbert Valerio Riedel Date: Mon Mar 23 08:49:03 2015 +0100 Set release date for base-4.8.0.0 in changelog [skip ci] >--------------------------------------------------------------- f2c76865244c5caeeb5c376b9e1493d59b067320 libraries/base/changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index e2318a8..4facf0c 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`base` package](http://hackage.haskell.org/package/base) -## 4.8.0.0 *TBA* +## 4.8.0.0 *Mar 2015* * Bundled with GHC 7.10.1 From git at git.haskell.org Mon Mar 23 09:13:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 09:13:08 +0000 (UTC) Subject: [commit: ghc] master: Minor fix to Note [Trimming arity] (992040e) Message-ID: <20150323091308.13B3A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/992040e9abbeaffecc4bbe9d9475da69d9427f82/ghc >--------------------------------------------------------------- commit 992040e9abbeaffecc4bbe9d9475da69d9427f82 Author: Joachim Breitner Date: Mon Mar 23 10:12:34 2015 +0100 Minor fix to Note [Trimming arity] [ci skip] >--------------------------------------------------------------- 992040e9abbeaffecc4bbe9d9475da69d9427f82 compiler/simplCore/CallArity.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs index 4a0b8ee..a635f7c 100644 --- a/compiler/simplCore/CallArity.hs +++ b/compiler/simplCore/CallArity.hs @@ -377,7 +377,7 @@ the case for Core! 2. Eta-expanding a right hand side might invalidate existing annotations. In particular, if an id has a strictness annotation of <...><...>b, then - passing one argument to it will definitely bottom out, so the simplifier + passing two arguments to it will definitely bottom out, so the simplifier will throw away additional parameters. This conflicts with Call Arity! So we ensure that we never eta-expand such a value beyond the number of arguments mentioned in the strictness signature. From git at git.haskell.org Mon Mar 23 09:42:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 09:42:33 +0000 (UTC) Subject: [commit: ghc] master: Fix quasiquotation test (#4150) (f72074e) Message-ID: <20150323094233.265DF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f72074ec85edd06867587698be4f3db48d0658d0/ghc >--------------------------------------------------------------- commit f72074ec85edd06867587698be4f3db48d0658d0 Author: Thomas Miedema Date: Mon Mar 23 10:41:22 2015 +0100 Fix quasiquotation test (#4150) >--------------------------------------------------------------- f72074ec85edd06867587698be4f3db48d0658d0 testsuite/tests/quasiquotation/T4150.stderr | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/quasiquotation/T4150.stderr b/testsuite/tests/quasiquotation/T4150.stderr index 9e0f4c2..689c808 100644 --- a/testsuite/tests/quasiquotation/T4150.stderr +++ b/testsuite/tests/quasiquotation/T4150.stderr @@ -1,3 +1,3 @@ T4150.hs:11:18: - Not in scope: type constructor or class `NoSuchType' + Not in scope: type constructor or class ?NoSuchType? From git at git.haskell.org Mon Mar 23 09:59:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 09:59:20 +0000 (UTC) Subject: [commit: ghc] wip/T10180: New Lint check: no alternatives implies bottoming expression (13384c1) Message-ID: <20150323095920.F3D0F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10180 Link : http://ghc.haskell.org/trac/ghc/changeset/13384c1aeb061b555f3860b3482949a729b7cfbe/ghc >--------------------------------------------------------------- commit 13384c1aeb061b555f3860b3482949a729b7cfbe Author: Joachim Breitner Date: Sun Mar 22 17:32:26 2015 +0100 New Lint check: no alternatives implies bottoming expression detected either by exprIsBottom or by an empty type. This was suggested by SPJ and fixes #10180. >--------------------------------------------------------------- 13384c1aeb061b555f3860b3482949a729b7cfbe compiler/coreSyn/CoreLint.hs | 6 +++++- compiler/types/TyCon.hs | 10 ++++++++++ compiler/types/Type.hs | 12 +++++++++++- 3 files changed, 26 insertions(+), 2 deletions(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index 690836a..c615ea6 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -637,8 +637,12 @@ lintCoreExpr e@(Case scrut var alt_ty alts) = ; alt_ty <- lintInTy alt_ty ; var_ty <- lintInTy (idType var) - ; checkL (not (null alts && exprIsHNF scrut)) + ; when (null alts) $ + do { checkL (not (exprIsHNF scrut)) (ptext (sLit "No alternatives for a case scrutinee in head-normal form:") <+> ppr scrut) + ; checkL (exprIsBottom scrut || isEmptyTy (exprType scrut)) + (ptext (sLit "No alternatives for a case scrutinee not known to diverge for sure:") <+> ppr scrut) + } ; case tyConAppTyCon_maybe (idType var) of Just tycon diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index 8e0175a..c3723c4 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -42,6 +42,7 @@ module TyCon( promotableTyCon_maybe, promoteTyCon, isDataTyCon, isProductTyCon, isDataProductTyCon_maybe, + isEmptyDataTyCon, isEnumerationTyCon, isNewTyCon, isAbstractTyCon, isFamilyTyCon, isOpenFamilyTyCon, @@ -1286,6 +1287,15 @@ isDataProductTyCon_maybe (TupleTyCon { dataCon = con }) = Just con isDataProductTyCon_maybe _ = Nothing +-- | True of datatypes with no constructors +isEmptyDataTyCon :: TyCon -> Bool +isEmptyDataTyCon tc + | AlgTyCon {algTcRhs = rhs} <- tc + , [] <- data_cons rhs + = True + | otherwise + = False + -- | Is this a 'TyCon' representing a regular H98 type synonym (@type@)? isTypeSynonymTyCon :: TyCon -> Bool isTypeSynonymTyCon (SynonymTyCon {}) = True diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index a2d3392..9cec0bd 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -66,7 +66,7 @@ module Type ( -- (Lifting and boxity) isUnLiftedType, isUnboxedTupleType, isAlgType, isClosedAlgType, - isPrimitiveType, isStrictType, + isPrimitiveType, isStrictType, isEmptyTy, -- * Main data types representing Kinds -- $kind_subtyping @@ -1184,6 +1184,16 @@ isPrimitiveType ty = case splitTyConApp_maybe ty of isPrimTyCon tc _ -> False +-- | True if the type has no non-bottom elements +isEmptyTy :: Type -> Bool +isEmptyTy ty + -- Data types with no constructors are empty + | Just (tc, _) <- splitTyConApp_maybe ty + , isEmptyDataTyCon tc + = True + | otherwise + = False + {- ************************************************************************ * * From git at git.haskell.org Mon Mar 23 09:59:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 09:59:23 +0000 (UTC) Subject: [commit: ghc] wip/T10180: exprIsBottom should look through type lambdas (b32e049) Message-ID: <20150323095923.9D34D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10180 Link : http://ghc.haskell.org/trac/ghc/changeset/b32e0495fc144a8d76229bff6becc7f40520effd/ghc >--------------------------------------------------------------- commit b32e0495fc144a8d76229bff6becc7f40520effd Author: Joachim Breitner Date: Mon Mar 23 10:17:25 2015 +0100 exprIsBottom should look through type lambdas as evaluting (\ (@ a) -> e) diverges if and only if evaluating e diverges. This was found in the context of #10180. >--------------------------------------------------------------- b32e0495fc144a8d76229bff6becc7f40520effd compiler/coreSyn/CoreUtils.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index 08f4fcd..b385576 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -702,6 +702,7 @@ exprIsBottom e go n (Tick _ e) = go n e go n (Cast e _) = go n e go n (Let _ e) = go n e + go n (Lam v e) | isTyVar v = go n e go _ _ = False {- From git at git.haskell.org Mon Mar 23 09:59:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 09:59:25 +0000 (UTC) Subject: [commit: ghc] wip/T10180's head updated: New Lint check: no alternatives implies bottoming expression (13384c1) Message-ID: <20150323095925.B6FFD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T10180' now includes: e25ad04 docs: make gen_contents_index --verbose more verbose 12a03c4 fix bus error (misaligned data access) on SPARC in __decodeDouble_Int64 a20cc3d rts: check arguments to flags that don't have any 5ef5a18 Update integer-gmp2's changelog for release cab5b3a Fix integer-gmp source tarball distribution 992040e Minor fix to Note [Trimming arity] b32e049 exprIsBottom should look through type lambdas 13384c1 New Lint check: no alternatives implies bottoming expression From git at git.haskell.org Mon Mar 23 10:29:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 10:29:18 +0000 (UTC) Subject: [commit: ghc] master: Update base changelog regarding 4.8.1 changes (1a72886) Message-ID: <20150323102918.BDFA93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1a7288696afec8ea3dbb39a3c2df3cc42bf379bd/ghc >--------------------------------------------------------------- commit 1a7288696afec8ea3dbb39a3c2df3cc42bf379bd Author: Herbert Valerio Riedel Date: Mon Mar 23 11:19:50 2015 +0100 Update base changelog regarding 4.8.1 changes Turns out we've been a bit too lazy and quite a few undocumented changes have accumulated in `base` relative to GHC 7.10's `base-4.8.0.0`... [skip ci] >--------------------------------------------------------------- 1a7288696afec8ea3dbb39a3c2df3cc42bf379bd libraries/base/changelog.md | 30 +++++++++++++++++++++++++++--- 1 file changed, 27 insertions(+), 3 deletions(-) diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 2ebad45..849a7ad 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -1,10 +1,34 @@ # Changelog for [`base` package](http://hackage.haskell.org/package/base) -## FUTURE VERSION *TBA* +## 4.8.1.0 *TBA* - * `Alt` now has `MonadZip` and `MonadFix` instances. + * Bundled with GHC 7.12.1 -## 4.8.0.0 *TBA* + * `Alt`, `Dual`, `First`, `Last`, `Product`, and `Sum` now have `Data`, + `MonadZip`, and `MonadFix` instances + + * `Maybe` now has a `MonadZip` instance + + * `All` and `Any` now have `Data` instances + + * `Dual`, `First`, `Last`, `Product`, and `Sum` now have `Foldable` and + `Traversable` instances + + * `Dual`, `Product`, and `Sum` now have `Functor`, `Applicative`, and + `Monad` instances + + * Redundant typeclass constraints have been removed: + - `Data.Ratio.{denominator,numerator}` have no `Integral` constraint anymore + - **TODO** + + * New module `GHC.SrcLoc` + + * New `GHC.Generics.packageName` operation + + * New `GHC.Stack.CallStack` data type + + +## 4.8.0.0 *Mar 2015* * Bundled with GHC 7.10.1 From git at git.haskell.org Mon Mar 23 10:29:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 10:29:21 +0000 (UTC) Subject: [commit: ghc] master: Minor bump `base` version to 4.8.1.0 (7035ff8) Message-ID: <20150323102921.6CF0A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7035ff872450855c449c53554b6fe7b1e95ef50d/ghc >--------------------------------------------------------------- commit 7035ff872450855c449c53554b6fe7b1e95ef50d Author: Herbert Valerio Riedel Date: Mon Mar 23 11:22:36 2015 +0100 Minor bump `base` version to 4.8.1.0 We've accumulated enough to justify a minor version bump to 4.8.1.0, but not enough to justify a major version bump yet as far as I can see. >--------------------------------------------------------------- 7035ff872450855c449c53554b6fe7b1e95ef50d libraries/base/base.cabal | 2 +- testsuite/tests/cabal/cabal06/q/q-1.0.conf | 2 +- testsuite/tests/ghci/scripts/ghci008.stdout | 4 ++-- .../tests/indexed-types/should_compile/T3017.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/ADT.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr1.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr2.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr3.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr4.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr5.stderr | 2 +- .../tests/partial-sigs/should_compile/AddAndOr6.stderr | 2 +- .../tests/partial-sigs/should_compile/BoolToBool.stderr | 2 +- .../partial-sigs/should_compile/Defaulting1MROn.stderr | 2 +- .../partial-sigs/should_compile/Defaulting2MROff.stderr | 2 +- .../partial-sigs/should_compile/Defaulting2MROn.stderr | 2 +- .../tests/partial-sigs/should_compile/Either.stderr | 2 +- .../should_compile/EqualityConstraint.stderr | 2 +- testsuite/tests/partial-sigs/should_compile/Every.stderr | 2 +- .../tests/partial-sigs/should_compile/EveryNamed.stderr | 2 +- .../partial-sigs/should_compile/ExpressionSig.stderr | 2 +- .../should_compile/ExpressionSigNamed.stderr | 2 +- .../partial-sigs/should_compile/ExtraConstraints1.stderr | 2 +- .../partial-sigs/should_compile/ExtraConstraints2.stderr | 2 +- .../partial-sigs/should_compile/ExtraConstraints3.stderr | 2 +- .../partial-sigs/should_compile/ExtraNumAMROff.stderr | 2 +- .../partial-sigs/should_compile/ExtraNumAMROn.stderr | 2 +- .../tests/partial-sigs/should_compile/Forall1.stderr | 2 +- .../tests/partial-sigs/should_compile/GenNamed.stderr | 2 +- .../tests/partial-sigs/should_compile/HigherRank1.stderr | 2 +- .../tests/partial-sigs/should_compile/HigherRank2.stderr | 2 +- .../should_compile/LocalDefinitionBug.stderr | 2 +- .../tests/partial-sigs/should_compile/Meltdown.stderr | 2 +- .../partial-sigs/should_compile/MonoLocalBinds.stderr | 2 +- .../tests/partial-sigs/should_compile/NamedTyVar.stderr | 2 +- .../should_compile/ParensAroundContext.stderr | 2 +- .../tests/partial-sigs/should_compile/PatBind.stderr | 2 +- .../tests/partial-sigs/should_compile/PatBind2.stderr | 2 +- .../tests/partial-sigs/should_compile/PatternSig.stderr | 2 +- .../tests/partial-sigs/should_compile/Recursive.stderr | 2 +- .../should_compile/ScopedNamedWildcards.stderr | 2 +- .../should_compile/ScopedNamedWildcardsGood.stderr | 2 +- .../tests/partial-sigs/should_compile/ShowNamed.stderr | 2 +- .../tests/partial-sigs/should_compile/SimpleGen.stderr | 2 +- .../tests/partial-sigs/should_compile/SkipMany.stderr | 2 +- .../partial-sigs/should_compile/SomethingShowable.stderr | 2 +- .../tests/partial-sigs/should_compile/Uncurry.stderr | 2 +- .../partial-sigs/should_compile/UncurryNamed.stderr | 2 +- .../should_compile/WarningWildcardInstantiations.stderr | 2 +- testsuite/tests/rename/should_fail/rnfail040.stderr | 2 +- testsuite/tests/roles/should_compile/Roles1.stderr | 2 +- testsuite/tests/roles/should_compile/Roles14.stderr | 2 +- testsuite/tests/roles/should_compile/Roles2.stderr | 2 +- testsuite/tests/roles/should_compile/Roles3.stderr | 2 +- testsuite/tests/roles/should_compile/Roles4.stderr | 2 +- testsuite/tests/roles/should_compile/T8958.stderr | 2 +- testsuite/tests/safeHaskell/check/Check01.stderr | 2 +- testsuite/tests/safeHaskell/check/Check06.stderr | 2 +- testsuite/tests/safeHaskell/check/Check08.stderr | 2 +- testsuite/tests/safeHaskell/check/Check09.stderr | 2 +- testsuite/tests/safeHaskell/check/pkg01/ImpSafe01.stderr | 2 +- testsuite/tests/safeHaskell/check/pkg01/ImpSafe04.stderr | 2 +- .../tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr | 2 +- .../tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr | 2 +- testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout | 16 ++++++++-------- testsuite/tests/safeHaskell/flags/SafeFlags17.stderr | 2 +- testsuite/tests/th/TH_Roles2.stderr | 2 +- testsuite/tests/typecheck/should_compile/tc231.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail182.stderr | 2 +- utils/ghc-cabal/cabal_macros_boot.h | 8 +++++++- 69 files changed, 83 insertions(+), 77 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7035ff872450855c449c53554b6fe7b1e95ef50d From git at git.haskell.org Mon Mar 23 12:41:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 12:41:55 +0000 (UTC) Subject: [commit: ghc] wip/T10181: New lint check: Check idArity invariants (#10181) (f6f1e92) Message-ID: <20150323124155.905C93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10181 Link : http://ghc.haskell.org/trac/ghc/changeset/f6f1e9258453bd94a132eab641d4db74c6961e26/ghc >--------------------------------------------------------------- commit f6f1e9258453bd94a132eab641d4db74c6961e26 Author: Joachim Breitner Date: Sun Mar 22 17:51:51 2015 +0100 New lint check: Check idArity invariants (#10181) The arity of an id should not be larger than what the type allows, and it should also not contradict the strictness signature. This adds a lint check for that. This broke test T8743, uncovering a bug in the SOURCE import machinery, which is now filed as #10182. >--------------------------------------------------------------- f6f1e9258453bd94a132eab641d4db74c6961e26 compiler/coreSyn/CoreLint.hs | 20 ++++++++++++++++++++ testsuite/tests/stranal/should_compile/all.T | 2 +- 2 files changed, 21 insertions(+), 1 deletion(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index 690836a..a81c9c3 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -56,6 +56,8 @@ import Util import InstEnv ( instanceDFunId ) import OptCoercion ( checkAxInstCo ) import UniqSupply +import CoreArity ( typeArity ) +import Demand ( splitStrictSig, isBotRes ) import HscTypes import DynFlags @@ -487,6 +489,24 @@ lintSingleBinding top_lvl_flag rec_flag (binder,rhs) -- StrictSig dmd_ty -> idArity binder >= dmdTypeDepth dmd_ty || exprIsTrivial rhs) -- (mkArityMsg binder) + -- Check that the binder's arity is within the bounds imposed by + -- the type and the strictness signature. See Note [exprArity invariant] + -- and Note [Trimming arity] + ; checkL (idArity binder <= length (typeArity (idType binder))) + (ptext (sLit "idArity") <+> ppr (idArity binder) <+> + ptext (sLit "exceeds typeArity") <+> + ppr (length (typeArity (idType binder))) <> colon <+> + ppr binder) + + ; case splitStrictSig (idStrictness binder) of + (demands, result_info) | isBotRes result_info -> + checkL (idArity binder <= length demands) + (ptext (sLit "idArity") <+> ppr (idArity binder) <+> + ptext (sLit "exceeds arity imposed by the strictness signature") <+> + ppr (idStrictness binder) <> colon <+> + ppr binder) + _ -> return () + ; lintIdUnfolding binder binder_ty (idUnfolding binder) } -- We should check the unfolding, if any, but this is tricky because diff --git a/testsuite/tests/stranal/should_compile/all.T b/testsuite/tests/stranal/should_compile/all.T index 184ff1e..eae3ba0 100644 --- a/testsuite/tests/stranal/should_compile/all.T +++ b/testsuite/tests/stranal/should_compile/all.T @@ -18,7 +18,7 @@ test('newtype', req_profiling, compile, ['-prof -auto-all']) test('T1988', normal, compile, ['']) test('T8467', normal, compile, ['']) test('T8037', normal, compile, ['']) -test('T8743', [ extra_clean(['T8743.o-boot', 'T8743.hi-boot']) ], multimod_compile, ['T8743', '-v0']) +test('T8743', [ extra_clean(['T8743.o-boot', 'T8743.hi-boot']), expect_broken(10182) ], multimod_compile, ['T8743', '-v0']) test('T9208', when(compiler_debugged(), expect_broken(9208)), compile, ['']) # T9208 fails (and should do so) if you have assertion checking on in the compiler From git at git.haskell.org Mon Mar 23 12:57:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 12:57:25 +0000 (UTC) Subject: [commit: ghc] master: Make testsuite driver Python 2.6 compatible again (0f03a84) Message-ID: <20150323125726.0040B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0f03a843e7e740218f3ce3853f80de99b0ed6236/ghc >--------------------------------------------------------------- commit 0f03a843e7e740218f3ce3853f80de99b0ed6236 Author: Thomas Miedema Date: Mon Mar 23 13:56:22 2015 +0100 Make testsuite driver Python 2.6 compatible again Another bug in the #10164 series. Only Python 2.7 and up allow you to omit the positional argument specifiers in format strings. Test Plan: this fixes the Solaris builders Reviewed By: kgardas Differential Revision: https://phabricator.haskell.org/D750 GHC Trac Issues: #10164 >--------------------------------------------------------------- 0f03a843e7e740218f3ce3853f80de99b0ed6236 testsuite/driver/testlib.py | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 961f545..d3b9b20 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1306,11 +1306,11 @@ def simple_run( name, way, prog, args ): stdin_comes_from = ' <' + use_stdin if opts.combined_output: - redirection = ' > {} 2>&1'.format(run_stdout) - redirection_append = ' >> {} 2>&1'.format(run_stdout) + redirection = ' > {0} 2>&1'.format(run_stdout) + redirection_append = ' >> {0} 2>&1'.format(run_stdout) else: - redirection = ' > {} 2> {}'.format(run_stdout, run_stderr) - redirection_append = ' >> {} 2>> {}'.format(run_stdout, run_stderr) + redirection = ' > {0} 2> {1}'.format(run_stdout, run_stderr) + redirection_append = ' >> {0} 2>> {1}'.format(run_stdout, run_stderr) cmd = prog + ' ' + args + ' ' \ + my_rts_flags + ' ' \ @@ -1418,11 +1418,11 @@ def interpreter_run( name, way, extra_hc_opts, compile_only, top_mod ): config.way_flags(name)[way]) if getTestOpts().combined_output: - redirection = ' > {} 2>&1'.format(outname) - redirection_append = ' >> {} 2>&1'.format(outname) + redirection = ' > {0} 2>&1'.format(outname) + redirection_append = ' >> {0} 2>&1'.format(outname) else: - redirection = ' > {} 2> {}'.format(outname, errname) - redirection_append = ' >> {} 2>> {}'.format(outname, errname) + redirection = ' > {0} 2> {1}'.format(outname, errname) + redirection_append = ' >> {0} 2>> {1}'.format(outname, errname) cmd = ('{{compiler}} {srcname} {flags} {extra_hc_opts} ' '< {scriptname} {redirection}' From git at git.haskell.org Mon Mar 23 16:26:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 16:26:33 +0000 (UTC) Subject: [commit: ghc] master: Do proper depth checking in the flattener to avoid looping. (c1edbdf) Message-ID: <20150323162633.8A3D93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c1edbdfd9148ad9f74bfe41e76c524f3e775aaaa/ghc >--------------------------------------------------------------- commit c1edbdfd9148ad9f74bfe41e76c524f3e775aaaa Author: Richard Eisenberg Date: Mon Mar 23 10:30:19 2015 -0400 Do proper depth checking in the flattener to avoid looping. This implements (roughly) the plan put forward in comment:14:ticket:7788, fixing #7788, #8550, #9554, #10139, and addressing concerns raised in #10079. There are some regressions w.r.t. GHC 7.8, but only with pathological type families (like F a = F a). This also (hopefully -- don't have a test case) fixes #10158. Unsolved problems include #10184 and #10185, which are both known deficiencies of the approach used here. As part of this change, the plumbing around detecting infinite loops has changed. Instead of -fcontext-stack and -ftype-function-depth, we now have one combined -freduction-depth parameter. Setting it to 0 disbales the check, which is now the recommended way to get (terminating) code to typecheck in releases. (The number of reduction steps may well change between minor GHC releases!) This commit also introduces a new IntWithInf type in BasicTypes that represents an integer+infinity. This type is used in a few places throughout the code. Tests in indexed-types/should_fail/T7788 indexed-types/should_fail/T8550 indexed-types/should_fail/T9554 indexed-types/should_compile/T10079 indexed-types/should_compile/T10139 typecheck/should_compile/T10184 (expected broken) typecheck/should_compile/T10185 (expected broken) This commit also changes performance testsuite numbers, for the better. >--------------------------------------------------------------- c1edbdfd9148ad9f74bfe41e76c524f3e775aaaa compiler/basicTypes/BasicTypes.hs | 69 ++- compiler/main/Constants.hs | 11 +- compiler/main/DynFlags.hs | 20 +- compiler/simplCore/SimplMonad.hs | 17 +- compiler/typecheck/FamInst.hs | 6 +- compiler/typecheck/TcCanonical.hs | 520 ++++++++------------- compiler/typecheck/TcErrors.hs | 30 +- compiler/typecheck/TcEvidence.hs | 2 +- compiler/typecheck/TcExpr.hs | 2 +- compiler/typecheck/TcFlatten.hs | 478 ++++++++++++------- compiler/typecheck/TcInteract.hs | 60 +-- compiler/typecheck/TcRnTypes.hs | 125 ++--- compiler/typecheck/TcSMonad.hs | 151 ++---- compiler/typecheck/TcValidity.hs | 29 +- docs/users_guide/flags.xml | 10 +- docs/users_guide/glasgow_exts.xml | 8 +- testsuite/tests/deriving/should_fail/T4846.stderr | 4 +- .../tests/indexed-types/should_compile/T10139.hs | 39 ++ .../indexed-types/should_compile/T3208b.stderr | 7 +- testsuite/tests/indexed-types/should_compile/all.T | 2 + .../indexed-types/should_fail/NoMatchErr.stderr | 2 +- .../tests/indexed-types/should_fail/T1897b.stderr | 2 +- .../tests/indexed-types/should_fail/T2664.stderr | 6 +- .../tests/indexed-types/should_fail/T4179.stderr | 6 +- .../tests/indexed-types/should_fail/T5439.stderr | 4 +- .../tests/indexed-types/should_fail/T7010.stderr | 2 +- .../tests/indexed-types/should_fail/T7729.stderr | 2 +- testsuite/tests/indexed-types/should_fail/T7788.hs | 19 + .../tests/indexed-types/should_fail/T7788.stderr | 10 + .../tests/indexed-types/should_fail/T7967.stderr | 2 +- testsuite/tests/indexed-types/should_fail/T8550.hs | 16 + .../tests/indexed-types/should_fail/T8550.stderr | 11 + .../tests/indexed-types/should_fail/T9036.stderr | 2 +- testsuite/tests/indexed-types/should_fail/T9554.hs | 13 + .../tests/indexed-types/should_fail/T9554.stderr | 22 + .../tests/indexed-types/should_fail/T9580.stderr | 4 +- testsuite/tests/indexed-types/should_fail/all.T | 4 +- testsuite/tests/perf/compiler/T5321FD.hs | 2 +- testsuite/tests/perf/compiler/T5321Fun.hs | 2 +- testsuite/tests/perf/compiler/T5837.stderr | 92 +--- testsuite/tests/perf/compiler/T9872a.hs | 2 +- testsuite/tests/perf/compiler/T9872b.hs | 2 +- testsuite/tests/perf/compiler/T9872c.hs | 2 +- testsuite/tests/perf/compiler/T9872d.hs | 1 + testsuite/tests/perf/compiler/all.T | 15 +- testsuite/tests/roles/should_fail/Roles10.stderr | 2 +- testsuite/tests/typecheck/should_compile/T10184.hs | 9 + testsuite/tests/typecheck/should_compile/T10185.hs | 7 + .../typecheck/should_compile/TcCoercibleCompile.hs | 43 +- testsuite/tests/typecheck/should_compile/all.T | 4 +- .../typecheck/should_fail/ContextStack1.stderr | 9 +- .../typecheck/should_fail/ContextStack2.stderr | 13 +- .../typecheck/should_fail/FrozenErrorTests.stderr | 4 +- testsuite/tests/typecheck/should_fail/T9318.stderr | 2 +- .../typecheck/should_fail/TcCoercibleFail.stderr | 27 +- .../typecheck/should_fail/TcCoercibleFail3.stderr | 2 +- testsuite/tests/typecheck/should_fail/all.T | 4 +- testsuite/tests/typecheck/should_fail/tcfail201.hs | 2 +- .../tests/typecheck/should_fail/tcfail201.stderr | 17 +- 59 files changed, 1034 insertions(+), 946 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c1edbdfd9148ad9f74bfe41e76c524f3e775aaaa From git at git.haskell.org Mon Mar 23 19:14:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 19:14:36 +0000 (UTC) Subject: [commit: ghc] wip/T10180: exprIsBottom should look through type lambdas (6ab5bc4) Message-ID: <20150323191436.03C923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10180 Link : http://ghc.haskell.org/trac/ghc/changeset/6ab5bc4ca9b3afb5862079cd8e3922fdd8cbf1ff/ghc >--------------------------------------------------------------- commit 6ab5bc4ca9b3afb5862079cd8e3922fdd8cbf1ff Author: Joachim Breitner Date: Mon Mar 23 10:17:25 2015 +0100 exprIsBottom should look through type lambdas as evaluting (\ (@ a) -> e) diverges if and only if evaluating e diverges. This was found in the context of #10180. >--------------------------------------------------------------- 6ab5bc4ca9b3afb5862079cd8e3922fdd8cbf1ff compiler/coreSyn/CoreUtils.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index 08f4fcd..b385576 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -702,6 +702,7 @@ exprIsBottom e go n (Tick _ e) = go n e go n (Cast e _) = go n e go n (Let _ e) = go n e + go n (Lam v e) | isTyVar v = go n e go _ _ = False {- From git at git.haskell.org Mon Mar 23 19:14:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 19:14:38 +0000 (UTC) Subject: [commit: ghc] wip/T10180: New Lint check: no alternatives implies bottoming expression (69ec2ad) Message-ID: <20150323191438.BACD23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10180 Link : http://ghc.haskell.org/trac/ghc/changeset/69ec2ad157794621a1161862f9954d670fe58646/ghc >--------------------------------------------------------------- commit 69ec2ad157794621a1161862f9954d670fe58646 Author: Joachim Breitner Date: Sun Mar 22 17:32:26 2015 +0100 New Lint check: no alternatives implies bottoming expression detected either by exprIsBottom or by an empty type. This was suggested by SPJ and fixes #10180. >--------------------------------------------------------------- 69ec2ad157794621a1161862f9954d670fe58646 compiler/coreSyn/CoreLint.hs | 6 +++++- compiler/coreSyn/CoreUtils.hs | 20 ++++++++++++++++++++ 2 files changed, 25 insertions(+), 1 deletion(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index 690836a..c615ea6 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -637,8 +637,12 @@ lintCoreExpr e@(Case scrut var alt_ty alts) = ; alt_ty <- lintInTy alt_ty ; var_ty <- lintInTy (idType var) - ; checkL (not (null alts && exprIsHNF scrut)) + ; when (null alts) $ + do { checkL (not (exprIsHNF scrut)) (ptext (sLit "No alternatives for a case scrutinee in head-normal form:") <+> ppr scrut) + ; checkL (exprIsBottom scrut || isEmptyTy (exprType scrut)) + (ptext (sLit "No alternatives for a case scrutinee not known to diverge for sure:") <+> ppr scrut) + } ; case tyConAppTyCon_maybe (idType var) of Just tycon diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index b385576..46d4f58 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -42,6 +42,7 @@ module CoreUtils ( -- * Manipulating data constructors and types applyTypeToArgs, applyTypeToArg, dataConRepInstPat, dataConRepFSInstPat, + isEmptyTy, -- * Working with ticks stripTicksTop, stripTicksTopE, stripTicksTopT, @@ -2098,3 +2099,22 @@ rhsIsStatic platform is_dynamic_name cvt_integer rhs = is_static False rhs = case isDataConWorkId_maybe f of Just dc -> n_val_args == dataConRepArity dc Nothing -> False + +{- +************************************************************************ +* * +\subsection{Type utilities} +* * +************************************************************************ +-} + +-- | True if the type has no non-bottom elements +isEmptyTy :: Type -> Bool +isEmptyTy ty + -- Data types with no constructors are empty + | Just (tc, inst_tys) <- splitTyConApp_maybe ty + , Just dcs <- tyConDataCons_maybe tc + , all (dataConCannotMatch inst_tys) dcs + = True + | otherwise + = False From git at git.haskell.org Mon Mar 23 19:33:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 19:33:39 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T10180' deleted Message-ID: <20150323193339.19FD73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T10180 From git at git.haskell.org Mon Mar 23 19:34:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 19:34:26 +0000 (UTC) Subject: [commit: ghc] master: exprIsBottom should look through type lambdas (5673bfc) Message-ID: <20150323193426.A57EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5673bfc49ec1e54a1540197078041a9da9754fa3/ghc >--------------------------------------------------------------- commit 5673bfc49ec1e54a1540197078041a9da9754fa3 Author: Joachim Breitner Date: Mon Mar 23 10:17:25 2015 +0100 exprIsBottom should look through type lambdas as evaluting (\ (@ a) -> e) diverges if and only if evaluating e diverges. This was found in the context of #10180. >--------------------------------------------------------------- 5673bfc49ec1e54a1540197078041a9da9754fa3 compiler/coreSyn/CoreUtils.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index 08f4fcd..b385576 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -702,6 +702,7 @@ exprIsBottom e go n (Tick _ e) = go n e go n (Cast e _) = go n e go n (Let _ e) = go n e + go n (Lam v e) | isTyVar v = go n e go _ _ = False {- From git at git.haskell.org Mon Mar 23 19:34:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 19:34:29 +0000 (UTC) Subject: [commit: ghc] master: New Lint check: no alternatives implies bottoming expression (a0678f1) Message-ID: <20150323193429.757AE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a0678f1f0e62496c108491e1c80d5eef3936474a/ghc >--------------------------------------------------------------- commit a0678f1f0e62496c108491e1c80d5eef3936474a Author: Joachim Breitner Date: Sun Mar 22 17:32:26 2015 +0100 New Lint check: no alternatives implies bottoming expression detected either by exprIsBottom or by an empty type. This was suggested by SPJ and fixes #10180. >--------------------------------------------------------------- a0678f1f0e62496c108491e1c80d5eef3936474a compiler/coreSyn/CoreLint.hs | 6 +++++- compiler/coreSyn/CoreUtils.hs | 20 ++++++++++++++++++++ 2 files changed, 25 insertions(+), 1 deletion(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index 690836a..c615ea6 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -637,8 +637,12 @@ lintCoreExpr e@(Case scrut var alt_ty alts) = ; alt_ty <- lintInTy alt_ty ; var_ty <- lintInTy (idType var) - ; checkL (not (null alts && exprIsHNF scrut)) + ; when (null alts) $ + do { checkL (not (exprIsHNF scrut)) (ptext (sLit "No alternatives for a case scrutinee in head-normal form:") <+> ppr scrut) + ; checkL (exprIsBottom scrut || isEmptyTy (exprType scrut)) + (ptext (sLit "No alternatives for a case scrutinee not known to diverge for sure:") <+> ppr scrut) + } ; case tyConAppTyCon_maybe (idType var) of Just tycon diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index b385576..46d4f58 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -42,6 +42,7 @@ module CoreUtils ( -- * Manipulating data constructors and types applyTypeToArgs, applyTypeToArg, dataConRepInstPat, dataConRepFSInstPat, + isEmptyTy, -- * Working with ticks stripTicksTop, stripTicksTopE, stripTicksTopT, @@ -2098,3 +2099,22 @@ rhsIsStatic platform is_dynamic_name cvt_integer rhs = is_static False rhs = case isDataConWorkId_maybe f of Just dc -> n_val_args == dataConRepArity dc Nothing -> False + +{- +************************************************************************ +* * +\subsection{Type utilities} +* * +************************************************************************ +-} + +-- | True if the type has no non-bottom elements +isEmptyTy :: Type -> Bool +isEmptyTy ty + -- Data types with no constructors are empty + | Just (tc, inst_tys) <- splitTyConApp_maybe ty + , Just dcs <- tyConDataCons_maybe tc + , all (dataConCannotMatch inst_tys) dcs + = True + | otherwise + = False From git at git.haskell.org Mon Mar 23 19:46:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 19:46:50 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T10181' deleted Message-ID: <20150323194650.3A5093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T10181 From git at git.haskell.org Mon Mar 23 19:46:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 19:46:53 +0000 (UTC) Subject: [commit: ghc] master: New lint check: Check idArity invariants (#10181) (567db32) Message-ID: <20150323194653.1A3953A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/567db32b074860723e2b7c38f119b1880a803775/ghc >--------------------------------------------------------------- commit 567db32b074860723e2b7c38f119b1880a803775 Author: Joachim Breitner Date: Sun Mar 22 17:51:51 2015 +0100 New lint check: Check idArity invariants (#10181) The arity of an id should not be larger than what the type allows, and it should also not contradict the strictness signature. This adds a lint check for that. This broke test T8743, uncovering a bug in the SOURCE import machinery, which is now filed as #10182. >--------------------------------------------------------------- 567db32b074860723e2b7c38f119b1880a803775 compiler/coreSyn/CoreLint.hs | 20 ++++++++++++++++++++ testsuite/tests/stranal/should_compile/all.T | 2 +- 2 files changed, 21 insertions(+), 1 deletion(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index c615ea6..c454334 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -56,6 +56,8 @@ import Util import InstEnv ( instanceDFunId ) import OptCoercion ( checkAxInstCo ) import UniqSupply +import CoreArity ( typeArity ) +import Demand ( splitStrictSig, isBotRes ) import HscTypes import DynFlags @@ -487,6 +489,24 @@ lintSingleBinding top_lvl_flag rec_flag (binder,rhs) -- StrictSig dmd_ty -> idArity binder >= dmdTypeDepth dmd_ty || exprIsTrivial rhs) -- (mkArityMsg binder) + -- Check that the binder's arity is within the bounds imposed by + -- the type and the strictness signature. See Note [exprArity invariant] + -- and Note [Trimming arity] + ; checkL (idArity binder <= length (typeArity (idType binder))) + (ptext (sLit "idArity") <+> ppr (idArity binder) <+> + ptext (sLit "exceeds typeArity") <+> + ppr (length (typeArity (idType binder))) <> colon <+> + ppr binder) + + ; case splitStrictSig (idStrictness binder) of + (demands, result_info) | isBotRes result_info -> + checkL (idArity binder <= length demands) + (ptext (sLit "idArity") <+> ppr (idArity binder) <+> + ptext (sLit "exceeds arity imposed by the strictness signature") <+> + ppr (idStrictness binder) <> colon <+> + ppr binder) + _ -> return () + ; lintIdUnfolding binder binder_ty (idUnfolding binder) } -- We should check the unfolding, if any, but this is tricky because diff --git a/testsuite/tests/stranal/should_compile/all.T b/testsuite/tests/stranal/should_compile/all.T index 184ff1e..eae3ba0 100644 --- a/testsuite/tests/stranal/should_compile/all.T +++ b/testsuite/tests/stranal/should_compile/all.T @@ -18,7 +18,7 @@ test('newtype', req_profiling, compile, ['-prof -auto-all']) test('T1988', normal, compile, ['']) test('T8467', normal, compile, ['']) test('T8037', normal, compile, ['']) -test('T8743', [ extra_clean(['T8743.o-boot', 'T8743.hi-boot']) ], multimod_compile, ['T8743', '-v0']) +test('T8743', [ extra_clean(['T8743.o-boot', 'T8743.hi-boot']), expect_broken(10182) ], multimod_compile, ['T8743', '-v0']) test('T9208', when(compiler_debugged(), expect_broken(9208)), compile, ['']) # T9208 fails (and should do so) if you have assertion checking on in the compiler From git at git.haskell.org Mon Mar 23 21:16:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 21:16:30 +0000 (UTC) Subject: [commit: ghc] master: Add Note [No alternatives lint check] (8f08069) Message-ID: <20150323211630.00F493A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8f08069668f12ce019be3277bc4baacb477a77ed/ghc >--------------------------------------------------------------- commit 8f08069668f12ce019be3277bc4baacb477a77ed Author: Joachim Breitner Date: Mon Mar 23 22:16:08 2015 +0100 Add Note [No alternatives lint check] in a follow up to #10180. >--------------------------------------------------------------- 8f08069668f12ce019be3277bc4baacb477a77ed compiler/coreSyn/CoreLint.hs | 13 +++++++++++++ compiler/coreSyn/CoreUtils.hs | 5 ++++- 2 files changed, 17 insertions(+), 1 deletion(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index c454334..d5b031a 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -657,6 +657,7 @@ lintCoreExpr e@(Case scrut var alt_ty alts) = ; alt_ty <- lintInTy alt_ty ; var_ty <- lintInTy (idType var) + -- See Note [No alternatives lint check] ; when (null alts) $ do { checkL (not (exprIsHNF scrut)) (ptext (sLit "No alternatives for a case scrutinee in head-normal form:") <+> ppr scrut) @@ -715,6 +716,18 @@ kind coercions and produce the following substitution which is to be applied in the type variables: k_ag ~~> * -> * +Note [No alternatives lint check] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +Case expressions with no alternatives are odd beasts, and worth looking at +in the linter. + +Certainly, it would be terribly wrong if the scrutinee was already in head +normal form. That is the first check. + +Furthermore, we should be able to see why GHC believes the scrutinee is +diverging for sure. That is the second check. see #10180. + ************************************************************************ * * \subsection[lintCoreArgs]{lintCoreArgs} diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index 46d4f58..e0d94c4 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -2108,7 +2108,10 @@ rhsIsStatic platform is_dynamic_name cvt_integer rhs = is_static False rhs ************************************************************************ -} --- | True if the type has no non-bottom elements +-- | True if the type has no non-bottom elements, e.g. when it is an empty +-- datatype, or a GADT with non-satisfiable type parameters, e.g. Int :~: Bool. +-- +-- See Note [No alternatives lint check] for one use of this function. isEmptyTy :: Type -> Bool isEmptyTy ty -- Data types with no constructors are empty From git at git.haskell.org Mon Mar 23 21:20:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 21:20:31 +0000 (UTC) Subject: [commit: ghc] master: isEmptyTy: Improve comment (aef4de4) Message-ID: <20150323212031.AD94E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aef4de4765187ba85b8a08de83c245c6bc8e372e/ghc >--------------------------------------------------------------- commit aef4de4765187ba85b8a08de83c245c6bc8e372e Author: Joachim Breitner Date: Mon Mar 23 22:19:21 2015 +0100 isEmptyTy: Improve comment [skip ci] >--------------------------------------------------------------- aef4de4765187ba85b8a08de83c245c6bc8e372e compiler/coreSyn/CoreUtils.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index e0d94c4..ba40f25 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -2114,7 +2114,9 @@ rhsIsStatic platform is_dynamic_name cvt_integer rhs = is_static False rhs -- See Note [No alternatives lint check] for one use of this function. isEmptyTy :: Type -> Bool isEmptyTy ty - -- Data types with no constructors are empty + -- Data types where, given the particular type parameters, no data + -- constructor matches, are empty. + -- This includes data types with no constructors, e.g. Data.Void.Void. | Just (tc, inst_tys) <- splitTyConApp_maybe ty , Just dcs <- tyConDataCons_maybe tc , all (dataConCannotMatch inst_tys) dcs From git at git.haskell.org Mon Mar 23 21:35:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 21:35:54 +0000 (UTC) Subject: [commit: ghc] branch 'typeable-with-kinds' deleted Message-ID: <20150323213554.AC17F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: typeable-with-kinds From git at git.haskell.org Mon Mar 23 21:57:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 23 Mar 2015 21:57:11 +0000 (UTC) Subject: [commit: ghc] master: Do version specific detection of LLVM tools (#10170). (42448e3) Message-ID: <20150323215711.780043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/42448e3757f25735a0a5b5e2b7ee456b5e8b0039/ghc >--------------------------------------------------------------- commit 42448e3757f25735a0a5b5e2b7ee456b5e8b0039 Author: Erik de Castro Lopo Date: Fri Mar 20 12:16:23 2015 +1100 Do version specific detection of LLVM tools (#10170). The LLVM developers seem to make breaking changes in the LLVM IR language between major releases. As a consumer of the LLVM tools GHC now needs to be locked more tightly to a single version of the LLVM tools. GHC HEAD currently only supports LLVM version 3.6. This commit changes the configure script to look for `llc-3.6` and `opt-3.6` before looking for `llc` and `opt`. If the former are not found, but the later are, check that they actually are version 3.6. At the same time, when detecting known problems with the LLVM tools (ie #9439) test for it using the versions of the LLVM tools retrieved from the bootstrap compiler's settings file. Test Plan: Manual testing. Reviewers: thomie, rwbarton, nomeata, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D745 GHC Trac Issues: #10170 >--------------------------------------------------------------- 42448e3757f25735a0a5b5e2b7ee456b5e8b0039 aclocal.m4 | 55 ++++++++++++++++++++++++++++++------------------------- configure.ac | 27 ++++++++++++++++++++++----- 2 files changed, 52 insertions(+), 30 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 871dacc..5726a3f 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2096,38 +2096,43 @@ AC_DEFUN([XCODE_VERSION],[ # $1 = the variable to set # $2 = the with option name # $3 = the command to look for +# $4 = the version of the command to look for # AC_DEFUN([FIND_LLVM_PROG],[ - FP_ARG_WITH_PATH_GNU_PROG_OPTIONAL_NOTARGET([$1], [$2], [$3]) + # Test for program with version name. + FP_ARG_WITH_PATH_GNU_PROG_OPTIONAL_NOTARGET([$1], [$2], [$3-$4]) if test "$$1" = ""; then - echo -n "checking for $3-x.x... " - save_IFS=$IFS - IFS=":;" - if test "$windows" = YES; then - PERM= - MODE= + # Test for program without version name. + FP_ARG_WITH_PATH_GNU_PROG_OPTIONAL_NOTARGET([$1], [$2], [$3]) + AC_MSG_CHECKING([$$1 is version $4]) + if test `$$1 --version | grep -c "version $4"` -gt 0 ; then + AC_MSG_RESULT(yes) else - # Search for executables. - PERM="-perm" - MODE="/+x" - fi - for p in ${PATH}; do - if test -d "${p}"; then - $1=`${FindCmd} "${p}" -maxdepth 1 \( -type f -o -type l \) ${PERM} ${MODE} -regex ".*/$3-[[0-9]]\.[[0-9]]" | ${SortCmd} -n | tail -1` - if test -n "$$1"; then - break - fi - fi - done - IFS=$save_IFS - if test -n "$$1"; then - echo "$$1" - else - echo "no" - fi + AC_MSG_RESULT(no) + $1="" + fi fi ]) +# FIND_GHC_BOOTSTRAP_PROG() +# -------------------------------- +# Parse the bootstrap GHC's compier settings file for the location of things +# like the `llc` and `opt` commands. +# +# $1 = the variable to set +# $2 = The bootstrap compiler. +# $3 = The string to grep for to find the correct line. +# +AC_DEFUN([FIND_GHC_BOOTSTRAP_PROG],[ + BootstrapTmpCmd=`grep $3 $($2 --print-libdir)/settings 2>/dev/null | sed 's/.*", "//;s/".*//'` + if test -n "$BootstrapTmpCmd" && test `basename $BootstrapTmpCmd` = $BootstrapTmpCmd ; then + AC_PATH_PROG([$1], [$BootstrapTmpCmd], "") + else + $1=$BootstrapTmpCmd + fi +]) + + # FIND_GCC() # -------------------------------- # Finds where gcc is diff --git a/configure.ac b/configure.ac index e7d467f..fc6b3c2 100644 --- a/configure.ac +++ b/configure.ac @@ -483,15 +483,21 @@ cygwin32|mingw32) ;; esac +# Here is where we re-target which specific version of the LLVM +# tools we are looking for. In the past, GHC supported a number of +# versions of LLVM simultaneously, but that stopped working around +# 3.5/3.6 release of LLVM. +llvm_version=3.6 + dnl ** Which LLVM llc to use? dnl -------------------------------------------------------------- -FIND_LLVM_PROG([LLC], [llc], [llc]) +FIND_LLVM_PROG([LLC], [llc], [llc], [$llvm_version]) LlcCmd="$LLC" AC_SUBST([LlcCmd]) dnl ** Which LLVM opt to use? dnl -------------------------------------------------------------- -FIND_LLVM_PROG([OPT], [opt], [opt]) +FIND_LLVM_PROG([OPT], [opt], [opt], [$llvm_version]) OptCmd="$OPT" AC_SUBST([OptCmd]) @@ -513,13 +519,24 @@ dnl whether -fllvm is the stage 0 compiler's default. If so we dnl fail. If not, we check whether -fllvm is affected explicitly and dnl if so set a flag. The build system will later check this flag dnl after the desired build flags are known. -if test -n "$LlcCmd" && test -n "$OptCmd" + +dnl This problem is further complicated by the fact that the llvm +dnl version used by the bootstrap compiler may be different from the +dnl version we arre trying to compile GHC against. Therefore, we need +dnl to find the boostrap compiler's `settings` file then check to see +dnl if the `opt` and `llc` command strings are non-empty and if these +dnl programs exist. Only if they exist to we test for bug #9439. + +FIND_GHC_BOOTSTRAP_PROG([BootstrapLlcCmd], [${WithGhc}], "LLVM llc command") +FIND_GHC_BOOTSTRAP_PROG([BootstrapOptCmd], [${WithGhc}], "LLVM opt command") + +if test -n "$BootstrapLlcCmd" && test -n "$BootstrapOptCmd" then AC_MSG_CHECKING(whether bootstrap compiler is affected by bug 9439) echo "main = putStrLn \"%function\"" > conftestghc.hs # Check whether LLVM backend is default for this platform - "${WithGhc}" -pgmlc="${LlcCmd}" -pgmlo="${OptCmd}" conftestghc.hs 2>&1 >/dev/null + "${WithGhc}" -pgmlc="${BootstrapLlcCmd}" -pgmlo="${BootstrapOptCmd}" conftestghc.hs 2>&1 >/dev/null res=`./conftestghc` if test "x$res" = "x%object" then @@ -536,7 +553,7 @@ then # -fllvm is not the default, but set a flag so the Makefile can check # -for it in the build flags later on - "${WithGhc}" -fforce-recomp -pgmlc="${LlcCmd}" -pgmlo="${OptCmd}" -fllvm conftestghc.hs 2>&1 >/dev/null + "${WithGhc}" -fforce-recomp -pgmlc="${BootstrapLlcCmd}" -pgmlo="${BootstrapOptCmd}" -fllvm conftestghc.hs 2>&1 >/dev/null if test $? = 0 then res=`./conftestghc` From git at git.haskell.org Tue Mar 24 02:09:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Mar 2015 02:09:44 +0000 (UTC) Subject: [commit: ghc] master: Fix bug in hs-libraries field munging. (fd17651) Message-ID: <20150324020944.6C4D03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fd176515f5259d9793d08299dd3b03f384fb504c/ghc >--------------------------------------------------------------- commit fd176515f5259d9793d08299dd3b03f384fb504c Author: Edward Z. Yang Date: Wed Mar 18 15:28:29 2015 -0700 Fix bug in hs-libraries field munging. Signed-off-by: Edward Z. Yang Test Plan: validate with 7.8 stage0 and HEAD stage0 Reviewers: austin, kgardas Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D740 >--------------------------------------------------------------- fd176515f5259d9793d08299dd3b03f384fb504c compiler/ghc.mk | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index b692891..132a4dd 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -727,11 +727,12 @@ endif # Note [munge-stage1-package-config] # Strip the date/patchlevel from the version of stage1. See Note # [fiddle-stage1-version] above. +# NB: The sed expression for hs-libraries is a bit weird to be POSIX-compliant. ifeq "$(compiler_stage1_VERSION_MUNGED)" "YES" compiler/stage1/inplace-pkg-config-munged: compiler/stage1/inplace-pkg-config sed -e 's/^\(version: .*\)\.$(ProjectPatchLevel)$$/\1/' \ -e 's/^\(id: .*\)\.$(ProjectPatchLevel)$$/\1/' \ - -e 's/^\(hs-libraries: HSghc-.*\)\.$(ProjectPatchLevel)$$/\1/' \ + -e 's/^\(hs-libraries: HSghc-.*\)\.$(ProjectPatchLevel)\(-[A-Za-z0-9][A-Za-z0-9]*\)*$$/\1\2/' \ < $< > $@ "$(compiler_stage1_GHC_PKG)" update --force $(compiler_stage1_GHC_PKG_OPTS) $@ From git at git.haskell.org Tue Mar 24 08:26:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Mar 2015 08:26:18 +0000 (UTC) Subject: [commit: ghc] master: exprIsBottom: Make use of isEmptyTy (#10186) (7062ebe) Message-ID: <20150324082618.E2DDB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7062ebe0ce92c191d87e993bd2497275976b9452/ghc >--------------------------------------------------------------- commit 7062ebe0ce92c191d87e993bd2497275976b9452 Author: Joachim Breitner Date: Mon Mar 23 22:25:24 2015 +0100 exprIsBottom: Make use of isEmptyTy (#10186) Any expression with of empty type is necessary bottom, so we can use that here. No effects known, but it is the right thing to do and validate, so lets do it. Differential Revision: https://phabricator.haskell.org/D754 >--------------------------------------------------------------- 7062ebe0ce92c191d87e993bd2497275976b9452 compiler/coreSyn/CoreLint.hs | 2 +- compiler/coreSyn/CoreUtils.hs | 4 ++++ 2 files changed, 5 insertions(+), 1 deletion(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index d5b031a..81e5618 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -661,7 +661,7 @@ lintCoreExpr e@(Case scrut var alt_ty alts) = ; when (null alts) $ do { checkL (not (exprIsHNF scrut)) (ptext (sLit "No alternatives for a case scrutinee in head-normal form:") <+> ppr scrut) - ; checkL (exprIsBottom scrut || isEmptyTy (exprType scrut)) + ; checkL (exprIsBottom scrut) (ptext (sLit "No alternatives for a case scrutinee not known to diverge for sure:") <+> ppr scrut) } diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index ba40f25..f400ebc 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -694,6 +694,10 @@ expensive. -} exprIsBottom :: CoreExpr -> Bool +-- If the type only contains no elements besides bottom, then this expressions, +-- well, bottom. +exprIsBottom e | isEmptyTy (exprType e) = True +-- Otherwise see if this is a bottoming id applied to enough arguments exprIsBottom e = go 0 e where From git at git.haskell.org Tue Mar 24 08:38:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Mar 2015 08:38:15 +0000 (UTC) Subject: [commit: ghc] master: Empty alternative lint check: Explain why there are two checks (9cdd2e6) Message-ID: <20150324083815.1308B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9cdd2e643cad099864a9c1e8218fb645d5989310/ghc >--------------------------------------------------------------- commit 9cdd2e643cad099864a9c1e8218fb645d5989310 Author: Joachim Breitner Date: Tue Mar 24 09:37:31 2015 +0100 Empty alternative lint check: Explain why there are two checks This addresses https://ghc.haskell.org/trac/ghc/ticket/10180#comment:6 [skip ci] >--------------------------------------------------------------- 9cdd2e643cad099864a9c1e8218fb645d5989310 compiler/coreSyn/CoreLint.hs | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index 81e5618..c0ca270 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -728,6 +728,15 @@ normal form. That is the first check. Furthermore, we should be able to see why GHC believes the scrutinee is diverging for sure. That is the second check. see #10180. +In principle, the first check is redundant: exprIsBottom == True will always +imply exprIsHNF == False. +But the first check is reliable: If exprIsHNF == True, then there definitely is +a problem (exprIsHNF errs on the right side). +If the second check triggers then it may be the case that the compiler got +smarter elsewhere, and the empty case is correct, but that exprIsBottom is +unable to see it. Therefore, this check is not fully reliable, and we keep +both around. + ************************************************************************ * * \subsection[lintCoreArgs]{lintCoreArgs} From git at git.haskell.org Tue Mar 24 09:44:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Mar 2015 09:44:04 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Fixed a copy-paste-bug in uncovered (fcf2c28) Message-ID: <20150324094404.F18943A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/fcf2c2872a1698a2fd9cece11e98b5b98f771ba2/ghc >--------------------------------------------------------------- commit fcf2c2872a1698a2fd9cece11e98b5b98f771ba2 Author: George Karachalias Date: Sun Mar 22 04:53:23 2015 +0100 Fixed a copy-paste-bug in uncovered Also: * Call the algorithm to see the results * Improved pretty-printing >--------------------------------------------------------------- fcf2c2872a1698a2fd9cece11e98b5b98f771ba2 compiler/deSugar/Check.hs | 114 ++++++++++++++++++++++++++++++++++++++-------- 1 file changed, 95 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 fcf2c2872a1698a2fd9cece11e98b5b98f771ba2 From git at git.haskell.org Tue Mar 24 09:44:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Mar 2015 09:44:07 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Major rewrite: Pt 10: Lifted (HsExpr Id) to PmExpr in term-constraints (0447d5a) Message-ID: <20150324094407.ABE423A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/0447d5af067f35aca14302f7c60f4094a67dd40e/ghc >--------------------------------------------------------------- commit 0447d5af067f35aca14302f7c60f4094a67dd40e Author: George Karachalias Date: Mon Mar 23 22:01:27 2015 +0100 Major rewrite: Pt 10: Lifted (HsExpr Id) to PmExpr in term-constraints >--------------------------------------------------------------- 0447d5af067f35aca14302f7c60f4094a67dd40e compiler/deSugar/Check.hs | 103 +++++++++++++++++++++++++++------------------- 1 file changed, 61 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 0447d5af067f35aca14302f7c60f4094a67dd40e From git at git.haskell.org Tue Mar 24 09:44:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Mar 2015 09:44:10 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Major rewrite: Pt 11: Implemented a (rather naive) term solver (2caa3e3) Message-ID: <20150324094410.68E733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/2caa3e3acd253a2d01b36ce969625e16090e9c24/ghc >--------------------------------------------------------------- commit 2caa3e3acd253a2d01b36ce969625e16090e9c24 Author: George Karachalias Date: Tue Mar 24 03:19:35 2015 +0100 Major rewrite: Pt 11: Implemented a (rather naive) term solver >--------------------------------------------------------------- 2caa3e3acd253a2d01b36ce969625e16090e9c24 compiler/deSugar/Check.hs | 471 +++++++++++++++++++++++++++++++++++++++++++++- 1 file changed, 464 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 2caa3e3acd253a2d01b36ce969625e16090e9c24 From git at git.haskell.org Tue Mar 24 09:44:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Mar 2015 09:44:13 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Major rewrite: Pt 12: Improved (performance) term oracle and respective text (bda52c2) Message-ID: <20150324094413.3955C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/bda52c276246caa04191b031b95f1ad8aef0c1b0/ghc >--------------------------------------------------------------- commit bda52c276246caa04191b031b95f1ad8aef0c1b0 Author: George Karachalias Date: Tue Mar 24 05:33:08 2015 +0100 Major rewrite: Pt 12: Improved (performance) term oracle and respective text Last Important TODO: * Implement typing THE RIGHT WAY (as described in paper) Other TODOs: * Make pretty-printing as it should be * Improve performance where possible * Fully document code * Follow GHC's coding conventions When all (most of) the above are done, erase previous implementation (which is actually active at the moment) and fully activate new. Don't forget to rename functions that end in '2'. >--------------------------------------------------------------- bda52c276246caa04191b031b95f1ad8aef0c1b0 compiler/deSugar/Check.hs | 149 +++++++++++++++++++--------------------------- 1 file changed, 62 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 bda52c276246caa04191b031b95f1ad8aef0c1b0 From git at git.haskell.org Tue Mar 24 09:53:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Mar 2015 09:53:03 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Avoid redundant-import warning (w/o CPP) (252953f) Message-ID: <20150324095303.C62A83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/252953f5a0eaa7fd31e8aa61fbb26143c1496810/ghc >--------------------------------------------------------------- commit 252953f5a0eaa7fd31e8aa61fbb26143c1496810 Author: Herbert Valerio Riedel Date: Sat Dec 27 23:43:20 2014 +0100 Avoid redundant-import warning (w/o CPP) (cherry picked from commit c55fefc0f25ecd754db3f274cba3f972d603f117) >--------------------------------------------------------------- 252953f5a0eaa7fd31e8aa61fbb26143c1496810 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 Tue Mar 24 10:12:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Mar 2015 10:12:00 +0000 (UTC) Subject: [commit: ghc] master: Delete DynFlag for NDP way (484d2b1) Message-ID: <20150324101200.3A1B63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/484d2b1655b877e065f91ccedece53d6291089a0/ghc >--------------------------------------------------------------- commit 484d2b1655b877e065f91ccedece53d6291089a0 Author: Thomas Miedema Date: Tue Mar 24 11:09:43 2015 +0100 Delete DynFlag for NDP way The last trace of NDP was removed in 2008 in commit: 44ee866e5bc20fcdf29ab13ea050816da9faf915 NDP stood for 'Nested Data Parallelism'. It was superseded by Data Parallel Haskell (DPH). Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D752 >--------------------------------------------------------------- 484d2b1655b877e065f91ccedece53d6291089a0 compiler/main/DynFlags.hs | 13 ------------- 1 file changed, 13 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index eea16dd..8e3733f 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -1194,7 +1194,6 @@ data Way | WayProf | WayEventLog | WayPar - | WayNDP | WayDyn deriving (Eq, Ord, Show) @@ -1215,7 +1214,6 @@ allowed_combination way = and [ x `allowedWith` y WayDebug `allowedWith` _ = True (WayCustom {}) `allowedWith` _ = True - WayProf `allowedWith` WayNDP = True WayThreaded `allowedWith` WayProf = True WayThreaded `allowedWith` WayEventLog = True _ `allowedWith` _ = False @@ -1231,7 +1229,6 @@ wayTag WayDyn = "dyn" wayTag WayProf = "p" wayTag WayEventLog = "l" wayTag WayPar = "mp" -wayTag WayNDP = "ndp" wayRTSOnly :: Way -> Bool wayRTSOnly (WayCustom {}) = False @@ -1241,7 +1238,6 @@ wayRTSOnly WayDyn = False wayRTSOnly WayProf = False wayRTSOnly WayEventLog = True wayRTSOnly WayPar = False -wayRTSOnly WayNDP = False wayDesc :: Way -> String wayDesc (WayCustom xs) = xs @@ -1251,7 +1247,6 @@ wayDesc WayDyn = "Dynamic" wayDesc WayProf = "Profiling" wayDesc WayEventLog = "RTS Event Logging" wayDesc WayPar = "Parallel" -wayDesc WayNDP = "Nested data parallelism" -- Turn these flags on when enabling this way wayGeneralFlags :: Platform -> Way -> [GeneralFlag] @@ -1269,7 +1264,6 @@ wayGeneralFlags _ WayDyn = [Opt_PIC] wayGeneralFlags _ WayProf = [Opt_SccProfilingOn] wayGeneralFlags _ WayEventLog = [] wayGeneralFlags _ WayPar = [Opt_Parallel] -wayGeneralFlags _ WayNDP = [] -- Turn these flags off when enabling this way wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag] @@ -1284,7 +1278,6 @@ wayUnsetGeneralFlags _ WayDyn = [-- There's no point splitting objects wayUnsetGeneralFlags _ WayProf = [] wayUnsetGeneralFlags _ WayEventLog = [] wayUnsetGeneralFlags _ WayPar = [] -wayUnsetGeneralFlags _ WayNDP = [] wayExtras :: Platform -> Way -> DynFlags -> DynFlags wayExtras _ (WayCustom {}) dflags = dflags @@ -1294,8 +1287,6 @@ wayExtras _ WayDyn dflags = dflags wayExtras _ WayProf dflags = dflags wayExtras _ WayEventLog dflags = dflags wayExtras _ WayPar dflags = exposePackage' "concurrent" dflags -wayExtras _ WayNDP dflags = setExtensionFlag' Opt_ParallelArrays - $ setGeneralFlag' Opt_Vectorise dflags wayOptc :: Platform -> Way -> [String] wayOptc _ (WayCustom {}) = [] @@ -1308,7 +1299,6 @@ wayOptc _ WayDyn = [] wayOptc _ WayProf = ["-DPROFILING"] wayOptc _ WayEventLog = ["-DTRACING"] wayOptc _ WayPar = ["-DPAR", "-w"] -wayOptc _ WayNDP = [] wayOptl :: Platform -> Way -> [String] wayOptl _ (WayCustom {}) = [] @@ -1329,7 +1319,6 @@ wayOptl _ WayEventLog = [] wayOptl _ WayPar = ["-L${PVM_ROOT}/lib/${PVM_ARCH}", "-lpvm3", "-lgpvm3"] -wayOptl _ WayNDP = [] wayOptP :: Platform -> Way -> [String] wayOptP _ (WayCustom {}) = [] @@ -1339,7 +1328,6 @@ wayOptP _ WayDyn = [] wayOptP _ WayProf = ["-DPROFILING"] wayOptP _ WayEventLog = ["-DTRACING"] wayOptP _ WayPar = ["-D__PARALLEL_HASKELL__"] -wayOptP _ WayNDP = [] whenGeneratingDynamicToo :: MonadIO m => DynFlags -> m () -> m () whenGeneratingDynamicToo dflags f = ifGeneratingDynamicToo dflags f (return ()) @@ -2265,7 +2253,6 @@ dynamic_flags = [ , defGhcFlag "smp" (NoArg (addWay WayThreaded >> deprecate "Use -threaded instead")) , defGhcFlag "debug" (NoArg (addWay WayDebug)) - , defGhcFlag "ndp" (NoArg (addWay WayNDP)) , defGhcFlag "threaded" (NoArg (addWay WayThreaded)) , defGhcFlag "ticky" From git at git.haskell.org Tue Mar 24 10:31:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Mar 2015 10:31:14 +0000 (UTC) Subject: [commit: ghc] master: Some stress tests for the empty case linter (6cf0c79) Message-ID: <20150324103114.6C6133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6cf0c7962c582eefb84cdf2735504d034fb16314/ghc >--------------------------------------------------------------- commit 6cf0c7962c582eefb84cdf2735504d034fb16314 Author: Joachim Breitner Date: Tue Mar 24 11:28:55 2015 +0100 Some stress tests for the empty case linter This is a variation of T2431 where the emptyness of the type is hidden behind a newtype, a type family and a closed type family. In all cases, it would be sound for the compiler to determine that the equality type is empty and the case alternatives may be dropped. At the moment, GHC does _not_ determine that. But if it ever does, this test ensures that we do not forget to make the lint from #10180 smarter as well. >--------------------------------------------------------------- 6cf0c7962c582eefb84cdf2735504d034fb16314 testsuite/tests/simplCore/should_compile/T10180.hs | 27 ++++++++++++++++++++++ testsuite/tests/simplCore/should_compile/all.T | 1 + 2 files changed, 28 insertions(+) diff --git a/testsuite/tests/simplCore/should_compile/T10180.hs b/testsuite/tests/simplCore/should_compile/T10180.hs new file mode 100644 index 0000000..55c52f0 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T10180.hs @@ -0,0 +1,27 @@ +{-# LANGUAGE TypeOperators, TypeFamilies, GADTs, EmptyCase #-} +module T10180 where + +newtype Foo = Foo Int + +type family Bar a +type instance Bar Int = Int + +type family Baz a where + Baz Int = Int + Baz Char = Int + +data a :~: b where + Refl :: a :~: a + +absurd0 :: Int :~: Bool -> a +absurd0 x = case x of {} + +absurd1 :: Foo :~: Bool -> a +absurd1 x = case x of {} + +absurd2 :: Bar Int :~: Bool -> a +absurd2 x = case x of {} + +absurd3 :: Baz a :~: Bool -> a +absurd3 x = case x of {} + diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 6c000d3..daf038a 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -212,3 +212,4 @@ test('T9583', only_ways(['optasm']), compile, ['']) test('T9565', only_ways(['optasm']), compile, ['']) test('T5821', only_ways(['optasm']), compile, ['']) test('T10176', only_ways(['optasm']), compile, ['']) +test('T10180', only_ways(['optasm']), compile, ['']) From git at git.haskell.org Tue Mar 24 13:52:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Mar 2015 13:52:26 +0000 (UTC) Subject: [commit: ghc] master: Improve environment handling in TcBinds (8eaa70a) Message-ID: <20150324135226.24D5D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8eaa70a6b973f2a76f51a0d073a953fe696ddda1/ghc >--------------------------------------------------------------- commit 8eaa70a6b973f2a76f51a0d073a953fe696ddda1 Author: Simon Peyton Jones Date: Tue Mar 24 12:52:29 2015 +0000 Improve environment handling in TcBinds This is a minor refactoring, but it simplifies the code quite a bit * Decrease the number of variants of tcExtend in TcEnv * Remove "not_actually_free" from TcEnv.tc_extend_local_env2 * Simplify plumbingof the "closed" flag * Remove redundant scoping of wild-card variables >--------------------------------------------------------------- 8eaa70a6b973f2a76f51a0d073a953fe696ddda1 compiler/typecheck/TcBinds.hs | 177 +++++++++++---------- compiler/typecheck/TcClassDcl.hs | 2 +- compiler/typecheck/TcEnv.hs | 113 +++++++------ compiler/typecheck/TcInstDcls.hs | 4 +- compiler/typecheck/TcPat.hs | 7 +- compiler/typecheck/TcPatSyn.hs | 2 +- compiler/typecheck/TcRnTypes.hs | 45 +++--- .../should_fail/Defaulting1MROff.stderr | 2 +- .../ExtraConstraintsWildcardNotPresent.stderr | 2 +- .../partial-sigs/should_fail/Trac10045.stderr | 2 +- 10 files changed, 187 insertions(+), 169 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8eaa70a6b973f2a76f51a0d073a953fe696ddda1 From git at git.haskell.org Tue Mar 24 13:52:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Mar 2015 13:52:28 +0000 (UTC) Subject: [commit: ghc] master: More comments (related to Trac #10180) (33cfa5f) Message-ID: <20150324135228.EB2833A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/33cfa5ff9db4e7886b3e7c2eed5ac1c75436bc4c/ghc >--------------------------------------------------------------- commit 33cfa5ff9db4e7886b3e7c2eed5ac1c75436bc4c Author: Simon Peyton Jones Date: Tue Mar 24 13:52:20 2015 +0000 More comments (related to Trac #10180) >--------------------------------------------------------------- 33cfa5ff9db4e7886b3e7c2eed5ac1c75436bc4c compiler/coreSyn/CoreLint.hs | 33 ++++++++++++++++----------------- compiler/coreSyn/CoreSyn.hs | 31 +++++++++++++------------------ compiler/coreSyn/CoreUtils.hs | 42 ++++++++++++++++++++++++++++++++++++------ 3 files changed, 65 insertions(+), 41 deletions(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index c0ca270..256a682 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -718,24 +718,23 @@ applied in the type variables: Note [No alternatives lint check] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ - Case expressions with no alternatives are odd beasts, and worth looking at -in the linter. - -Certainly, it would be terribly wrong if the scrutinee was already in head -normal form. That is the first check. - -Furthermore, we should be able to see why GHC believes the scrutinee is -diverging for sure. That is the second check. see #10180. - -In principle, the first check is redundant: exprIsBottom == True will always -imply exprIsHNF == False. -But the first check is reliable: If exprIsHNF == True, then there definitely is -a problem (exprIsHNF errs on the right side). -If the second check triggers then it may be the case that the compiler got -smarter elsewhere, and the empty case is correct, but that exprIsBottom is -unable to see it. Therefore, this check is not fully reliable, and we keep -both around. +in the linter (cf Trac #10180). We check two things: + +* exprIsHNF is false: certainly, it would be terribly wrong if the + scrutinee was already in head normal form. + +* exprIsBottom is true: we should be able to see why GHC believes the + scrutinee is diverging for sure. + +In principle, the first check is redundant: exprIsBottom == True will +always imply exprIsHNF == False. But the first check is reliable: If +exprIsHNF == True, then there definitely is a problem (exprIsHNF errs +on the right side). If the second check triggers then it may be the +case that the compiler got smarter elsewhere, and the empty case is +correct, but that exprIsBottom is unable to see it. In particular, the +empty-type check in exprIsBottom is an approximation. Therefore, this +check is not fully reliable, and we keep both around. ************************************************************************ * * diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index b744ea2..e614c93 100644 --- a/compiler/coreSyn/CoreSyn.hs +++ b/compiler/coreSyn/CoreSyn.hs @@ -379,25 +379,20 @@ See #type_let# Note [Empty case alternatives] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -The alternatives of a case expression should be exhaustive. A case expression -can have empty alternatives if (and only if) the scrutinee is bound to raise -an exception or diverge. So: - Case (error Int "Hello") b Bool [] -is fine, and has type Bool. This is one reason we need a type on -the case expression: if the alternatives are empty we can't get the type -from the alternatives! I'll write this - case (error Int "Hello") of Bool {} -with the return type just before the alternatives. - -Here's another example: +The alternatives of a case expression should be exhaustive. + +A case expression can have empty alternatives if (and only if) the +scrutinee is bound to raise an exception or diverge. When do we know +this? See Note [Bottoming expressions] in CoreUtils. + +The possiblity of empty alternatives is one reason we need a type on +the case expression: if the alternatives are empty we can't get the +type from the alternatives! + +In the case of empty types (see Note [Bottoming expressions]), say data T - f :: T -> Bool - f = \(x:t). case x of Bool {} -Since T has no data constructors, the case alternatives are of course -empty. However note that 'x' is not bound to a visibly-bottom value; -it's the *type* that tells us it's going to diverge. Its a bit of a -degnerate situation but we do NOT want to replace - case x of Bool {} --> error Bool "Inaccessible case" +we do NOT want to replace + case (x::T) of Bool {} --> error Bool "Inaccessible case" because x might raise an exception, and *that*'s what we want to see! (Trac #6067 is an example.) To preserve semantics we'd have to say x `seq` error Bool "Inaccessible case" diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index f400ebc..d7344e1 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -694,11 +694,11 @@ expensive. -} exprIsBottom :: CoreExpr -> Bool --- If the type only contains no elements besides bottom, then this expressions, --- well, bottom. -exprIsBottom e | isEmptyTy (exprType e) = True --- Otherwise see if this is a bottoming id applied to enough arguments +-- See Note [Bottoming expressions] exprIsBottom e + | isEmptyTy (exprType e) + = True + | otherwise = go 0 e where go n (Var v) = isBottomingId v && n >= idArity v @@ -710,7 +710,36 @@ exprIsBottom e go n (Lam v e) | isTyVar v = go n e go _ _ = False -{- +{- Note [Bottoming expressions] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +A bottoming expression is guaranteed to diverge, or raise an +exception. We can test for it in two different ways, and exprIsBottom +checks for both of these situations: + +* Visibly-bottom computations. For example + (error Int "Hello") + is visibly bottom. The strictness analyser also finds out if + a function diverges or raises an exception, and puts that info + in its strictness signature. + +* Empty types. If a type is empty, its only inhabitant is bottom. + For example: + data T + f :: T -> Bool + f = \(x:t). case x of Bool {} + Since T has no data constructors, the case alternatives are of course + empty. However note that 'x' is not bound to a visibly-bottom value; + it's the *type* that tells us it's going to diverge. + +A GADT may also be empty even though it has constructors: + data T a where + T1 :: a -> T Bool + T2 :: T Int + ...(case (x::T Char) of {})... +Here (T Char) is uninhabited. A more realistic case is (Int ~ Bool), +which is likewise uninhabited. + + ************************************************************************ * * exprIsDupable @@ -2114,8 +2143,9 @@ rhsIsStatic platform is_dynamic_name cvt_integer rhs = is_static False rhs -- | True if the type has no non-bottom elements, e.g. when it is an empty -- datatype, or a GADT with non-satisfiable type parameters, e.g. Int :~: Bool. +-- See Note [Bottoming expressions] -- --- See Note [No alternatives lint check] for one use of this function. +-- See Note [No alternatives lint check] for another use of this function. isEmptyTy :: Type -> Bool isEmptyTy ty -- Data types where, given the particular type parameters, no data From git at git.haskell.org Tue Mar 24 15:27:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Mar 2015 15:27:48 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Make testsuite driver Python 2.6 compatible again (b189a5a) Message-ID: <20150324152748.CCC9F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/b189a5a3fb33caf8e23f6cdb329901f0675946ad/ghc >--------------------------------------------------------------- commit b189a5a3fb33caf8e23f6cdb329901f0675946ad Author: Thomas Miedema Date: Mon Mar 23 13:56:22 2015 +0100 Make testsuite driver Python 2.6 compatible again Another bug in the #10164 series. Only Python 2.7 and up allow you to omit the positional argument specifiers in format strings. Test Plan: this fixes the Solaris builders Reviewed By: kgardas Differential Revision: https://phabricator.haskell.org/D750 GHC Trac Issues: #10164 (cherry picked from commit 0f03a843e7e740218f3ce3853f80de99b0ed6236) >--------------------------------------------------------------- b189a5a3fb33caf8e23f6cdb329901f0675946ad testsuite/driver/testlib.py | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 29ceedb..af1dcdf 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1294,11 +1294,11 @@ def simple_run( name, way, prog, args ): stdin_comes_from = ' <' + use_stdin if opts.combined_output: - redirection = ' > {} 2>&1'.format(run_stdout) - redirection_append = ' >> {} 2>&1'.format(run_stdout) + redirection = ' > {0} 2>&1'.format(run_stdout) + redirection_append = ' >> {0} 2>&1'.format(run_stdout) else: - redirection = ' > {} 2> {}'.format(run_stdout, run_stderr) - redirection_append = ' >> {} 2>> {}'.format(run_stdout, run_stderr) + redirection = ' > {0} 2> {1}'.format(run_stdout, run_stderr) + redirection_append = ' >> {0} 2>> {1}'.format(run_stdout, run_stderr) cmd = prog + ' ' + args + ' ' \ + my_rts_flags + ' ' \ @@ -1406,11 +1406,11 @@ def interpreter_run( name, way, extra_hc_opts, compile_only, top_mod ): config.way_flags(name)[way]) if getTestOpts().combined_output: - redirection = ' > {} 2>&1'.format(outname) - redirection_append = ' >> {} 2>&1'.format(outname) + redirection = ' > {0} 2>&1'.format(outname) + redirection_append = ' >> {0} 2>&1'.format(outname) else: - redirection = ' > {} 2> {}'.format(outname, errname) - redirection_append = ' >> {} 2>> {}'.format(outname, errname) + redirection = ' > {0} 2> {1}'.format(outname, errname) + redirection_append = ' >> {0} 2>> {1}'.format(outname, errname) cmd = ('{{compiler}} {srcname} {flags} {extra_hc_opts} ' '< {scriptname} {redirection}' From git at git.haskell.org Tue Mar 24 15:27:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 24 Mar 2015 15:27:51 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Rearrange order of the release note highlights (d4ae21a) Message-ID: <20150324152751.DD2C33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/d4ae21ae7c1f8c198c5cccb1132db65f8c9bd8b6/ghc >--------------------------------------------------------------- commit d4ae21ae7c1f8c198c5cccb1132db65f8c9bd8b6 Author: Douglas Burke Date: Tue Mar 24 10:26:45 2015 -0500 Rearrange order of the release note highlights Summary: I noticed that the highlights do not highlight the breaking changes first, so I re-ordered them to what - to me, as a general and not power-user of ghc - seems a more sensible order. Should I have opened a ticket for this? Test Plan: This is a doc change. Reviewers: ezyang, austin Reviewed By: ezyang, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D736 GHC Trac Issues: #10038 >--------------------------------------------------------------- d4ae21ae7c1f8c198c5cccb1132db65f8c9bd8b6 docs/users_guide/7.10.1-notes.xml | 83 ++++++++++++++++++++++----------------- 1 file changed, 46 insertions(+), 37 deletions(-) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index df7359e..7669d2c 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -18,24 +18,14 @@ - GHC now has support for plugins which modify the type - checker. This allows external users to interface with - GHC and write type-checking plugins to solve - constraints and equalities generated by the - typechecker. - - - This feature is experimental and will likely change in - the future. - - - - GHC has implemented "The Applicative Monad Proposal", meaning the Applicative typeclass is now a superclass of Monad. This is a breaking change and your programs will need to be updated. + Please see the GHC + 7.10 Migration Guide on the GHC wiki. @@ -47,6 +37,9 @@ Data.Traversable), rather than exporting custom, less-generic versions. This is a change that may require updates to your program. + Please see the GHC + 7.10 Migration Guide on the GHC wiki. @@ -59,6 +52,40 @@ + The integer-gmp package has been + completely rewritten from the ground up. The primary + change in this rewrite is that GHC-compiled programs + that link to GMP no longer 'hook' GMP allocation + routines, to create an Integer on + the raw Haskell heap. Instead, + integer-gmp now allocates all + memory in Haskell code, and talks to GMP via normal + FFI imports like other C code. + + + The practical side effect of this is that C libraries + which bind to GMP (such as MPFR or FLINT) no longer + need careful (or impossible) hacks to be used inside a + GHC-compiled program via the FFI; GMP is treated just + like any other C library, with no special + accomodations. + + + + + GHC now has support for plugins which modify the type + checker. This allows external users to interface with + GHC and write type-checking plugins to solve + constraints and equalities generated by the + typechecker. + + + This feature is experimental and will likely change in + the future. + + + + GHC now has support for a new extension, -XStaticPointers, that allows you to (de)reference and serialize pointers to known, @@ -87,27 +114,6 @@ should still be useful today. - - - The integer-gmp package has been - completely rewritten from the ground up. The primary - change in this rewrite is that GHC-compiled programs - that link to GMP no longer 'hook' GMP allocation - routines, to create an Integer on - the raw Haskell heap. Instead, - integer-gmp now allocates all - memory in Haskell code, and talks to GMP via normal - FFI imports like other C code. - - - The practical side effect of this is that C libraries - which bind to GMP (such as MPFR or FLINT) no longer - need careful (or impossible) hacks to be used inside a - GHC-compiled program via the FFI; GMP is treated just - like any other C library, with no special - accomodations. - - @@ -881,19 +887,22 @@ echo "[]" > package.conf On Mac OS X, the -threaded Garbage Collector currently suffers from a large performance penalty due to a lack of system-specific optimization - (issue #7602). + (issue #7602). GHC's LLVM backend is currently incompatible with LLVM - 3.4 (issue #9929). + 3.4 (issue #9929). GHCi fails to appropriately load - .dyn_o files (issue #8736). + .dyn_o files (issue #8736). From git at git.haskell.org Wed Mar 25 13:51:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 25 Mar 2015 13:51:25 +0000 (UTC) Subject: [commit: ghc] master: Add Monad instance for `((, ) a)` (#10190) (9db005a) Message-ID: <20150325135125.BABE63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9db005a444722e31aca1956b058e069bcf3cacbd/ghc >--------------------------------------------------------------- commit 9db005a444722e31aca1956b058e069bcf3cacbd Author: Fumiaki Kinoshita Date: Wed Mar 25 13:30:25 2015 +0900 Add Monad instance for `((,) a)` (#10190) This was proposed a couple of times in the past, e.g. - https://mail.haskell.org/pipermail/libraries/2011-November/017153.html - https://mail.haskell.org/pipermail/libraries/2013-July/020446.html but its implementation had been blocked by the fact that `Monoid` wasn't in scope where the `Monad` class was defined. Since the AMP/FTP restructuring this is no longer the case. >--------------------------------------------------------------- 9db005a444722e31aca1956b058e069bcf3cacbd libraries/base/GHC/Base.hs | 3 +++ libraries/base/changelog.md | 2 ++ testsuite/tests/ghci/scripts/T7627.stdout | 1 + testsuite/tests/ghci/scripts/ghci011.stdout | 1 + testsuite/tests/typecheck/should_fail/tcfail181.stderr | 2 +- 5 files changed, 8 insertions(+), 1 deletion(-) diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index 7e04ab4..d9192d7 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -308,6 +308,9 @@ instance Monoid a => Applicative ((,) a) where pure x = (mempty, x) (u, f) <*> (v, x) = (u `mappend` v, f x) +instance Monoid a => Monad ((,) a) where + return x = (mempty, x) + (u, a) >>= k = case k a of (v, b) -> (u `mappend` v, b) {- | The 'Functor' class is used for types that can be mapped over. Instances of 'Functor' should satisfy the following laws: diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 849a7ad..f402189 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -17,6 +17,8 @@ * `Dual`, `Product`, and `Sum` now have `Functor`, `Applicative`, and `Monad` instances + * `(,) a` now has a `Monad` instance + * Redundant typeclass constraints have been removed: - `Data.Ratio.{denominator,numerator}` have no `Integral` constraint anymore - **TODO** diff --git a/testsuite/tests/ghci/scripts/T7627.stdout b/testsuite/tests/ghci/scripts/T7627.stdout index 2713566..158672c 100644 --- a/testsuite/tests/ghci/scripts/T7627.stdout +++ b/testsuite/tests/ghci/scripts/T7627.stdout @@ -15,6 +15,7 @@ data (,) a b = (,) a b -- Defined in ?GHC.Tuple? instance (Bounded a, Bounded b) => Bounded (a, b) -- Defined in ?GHC.Enum? instance (Eq a, Eq b) => Eq (a, b) -- Defined in ?GHC.Classes? +instance Monoid a => Monad ((,) a) -- Defined in ?GHC.Base? instance Functor ((,) a) -- Defined in ?GHC.Base? instance (Ord a, Ord b) => Ord (a, b) -- Defined in ?GHC.Classes? instance (Read a, Read b) => Read (a, b) -- Defined in ?GHC.Read? diff --git a/testsuite/tests/ghci/scripts/ghci011.stdout b/testsuite/tests/ghci/scripts/ghci011.stdout index a608f07..8042757 100644 --- a/testsuite/tests/ghci/scripts/ghci011.stdout +++ b/testsuite/tests/ghci/scripts/ghci011.stdout @@ -21,6 +21,7 @@ data (,) a b = (,) a b -- Defined in ?GHC.Tuple? instance (Bounded a, Bounded b) => Bounded (a, b) -- Defined in ?GHC.Enum? instance (Eq a, Eq b) => Eq (a, b) -- Defined in ?GHC.Classes? +instance Monoid a => Monad ((,) a) -- Defined in ?GHC.Base? instance Functor ((,) a) -- Defined in ?GHC.Base? instance (Ord a, Ord b) => Ord (a, b) -- Defined in ?GHC.Classes? instance (Read a, Read b) => Read (a, b) -- Defined in ?GHC.Read? diff --git a/testsuite/tests/typecheck/should_fail/tcfail181.stderr b/testsuite/tests/typecheck/should_fail/tcfail181.stderr index e638099..787b62e 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail181.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail181.stderr @@ -10,7 +10,7 @@ tcfail181.hs:17:9: instance Monad Maybe -- Defined in ?GHC.Base? instance Monad IO -- Defined in ?GHC.Base? instance Monad ((->) r) -- Defined in ?GHC.Base? - ...plus one other + ...plus two others In the expression: foo In the expression: foo {bar = return True} In an equation for ?wog?: wog x = foo {bar = return True} From git at git.haskell.org Thu Mar 26 12:41:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Mar 2015 12:41:00 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T9858-typeable-spj' created Message-ID: <20150326124100.B611B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T9858-typeable-spj Referencing: fcd18c42b6ae2e73a9f4c67dbe6d994b0f8468c8 From git at git.haskell.org Thu Mar 26 12:41:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Mar 2015 12:41:03 +0000 (UTC) Subject: [commit: ghc] wip/T9858-typeable-spj: Improve the error messages for class instance errors (48512df) Message-ID: <20150326124103.896723A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9858-typeable-spj Link : http://ghc.haskell.org/trac/ghc/changeset/48512df5751a07fd503f0ba523e5504d09ee258d/ghc >--------------------------------------------------------------- commit 48512df5751a07fd503f0ba523e5504d09ee258d Author: Simon Peyton Jones Date: Fri Mar 20 12:27:59 2015 +0000 Improve the error messages for class instance errors See Note [Displaying potential instances]. >--------------------------------------------------------------- 48512df5751a07fd503f0ba523e5504d09ee258d compiler/main/DynFlags.hs | 2 + compiler/typecheck/TcErrors.hs | 106 ++++++++++++++++++++++++++++++++++------- docs/users_guide/flags.xml | 6 +++ docs/users_guide/using.xml | 11 +++++ 4 files changed, 107 insertions(+), 18 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 48512df5751a07fd503f0ba523e5504d09ee258d From git at git.haskell.org Thu Mar 26 12:41:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Mar 2015 12:41:06 +0000 (UTC) Subject: [commit: ghc] wip/T9858-typeable-spj: Comments and white space (7078a11) Message-ID: <20150326124106.484F43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9858-typeable-spj Link : http://ghc.haskell.org/trac/ghc/changeset/7078a11f50e3af9139dd5ceef032e89047677833/ghc >--------------------------------------------------------------- commit 7078a11f50e3af9139dd5ceef032e89047677833 Author: Simon Peyton Jones Date: Fri Mar 20 12:36:22 2015 +0000 Comments and white space >--------------------------------------------------------------- 7078a11f50e3af9139dd5ceef032e89047677833 compiler/basicTypes/Id.hs | 7 +++---- compiler/coreSyn/MkCore.hs | 1 + compiler/iface/LoadIface.hs | 3 ++- 3 files changed, 6 insertions(+), 5 deletions(-) diff --git a/compiler/basicTypes/Id.hs b/compiler/basicTypes/Id.hs index 2a97445..ea2ef49 100644 --- a/compiler/basicTypes/Id.hs +++ b/compiler/basicTypes/Id.hs @@ -307,9 +307,8 @@ mkTemplateLocals = mkTemplateLocalsNum 1 mkTemplateLocalsNum :: Int -> [Type] -> [Id] mkTemplateLocalsNum n tys = zipWith mkTemplateLocal [n..] tys -{- -Note [Exported LocalIds] -~~~~~~~~~~~~~~~~~~~~~~~~ +{- Note [Exported LocalIds] +~~~~~~~~~~~~~~~~~~~~~~~~~~~ We use mkExportedLocalId for things like - Dictionary functions (DFunId) - Wrapper and matcher Ids for pattern synonyms @@ -323,7 +322,7 @@ code by the occurrence analyser. (But "exported" here does not mean "brought into lexical scope by an import declaration". Indeed these things are always internal Ids that the user never sees.) -It's very important that they are *LocalIds*, not GlobalIs, for lots +It's very important that they are *LocalIds*, not GlobalIds, for lots of reasons: * We want to treat them as free variables for the purpose of diff --git a/compiler/coreSyn/MkCore.hs b/compiler/coreSyn/MkCore.hs index 6905641..915188a 100644 --- a/compiler/coreSyn/MkCore.hs +++ b/compiler/coreSyn/MkCore.hs @@ -274,6 +274,7 @@ mkCharExpr c = mkConApp charDataCon [mkCharLit c] -- | Create a 'CoreExpr' which will evaluate to the given @String@ mkStringExpr :: MonadThings m => String -> m CoreExpr -- Result :: String + -- | Create a 'CoreExpr' which will evaluate to a string morally equivalent to the given @FastString@ mkStringExprFS :: MonadThings m => FastString -> m CoreExpr -- Result :: String diff --git a/compiler/iface/LoadIface.hs b/compiler/iface/LoadIface.hs index 169e929..b1d7556 100644 --- a/compiler/iface/LoadIface.hs +++ b/compiler/iface/LoadIface.hs @@ -190,6 +190,7 @@ checkWiredInTyCon tc = return () | otherwise = do { mod <- getModule + ; traceIf (text "checkWiredInTyCon" <+> ppr tc_name $$ ppr mod) ; ASSERT( isExternalName tc_name ) when (mod /= nameModule tc_name) (initIfaceTcRn (loadWiredInHomeIface tc_name)) @@ -354,7 +355,7 @@ loadInterfaceForModule doc m -- | An 'IfM' function to load the home interface for a wired-in thing, -- so that we're sure that we see its instance declarations and rules --- See Note [Loading instances for wired-in things] in TcIface +-- See Note [Loading instances for wired-in things] loadWiredInHomeIface :: Name -> IfM lcl () loadWiredInHomeIface name = ASSERT( isWiredInName name ) From git at git.haskell.org Thu Mar 26 12:41:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Mar 2015 12:41:09 +0000 (UTC) Subject: [commit: ghc] wip/T9858-typeable-spj: Implement lookupGlobal in TcEnv, and use it (6473d11) Message-ID: <20150326124109.007F33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9858-typeable-spj Link : http://ghc.haskell.org/trac/ghc/changeset/6473d110ab1aa22a5933e405b59e3f597562ce02/ghc >--------------------------------------------------------------- commit 6473d110ab1aa22a5933e405b59e3f597562ce02 Author: Simon Peyton Jones Date: Fri Mar 20 12:38:42 2015 +0000 Implement lookupGlobal in TcEnv, and use it This localises the (revolting) initTcForLookup function, exposing instead the more civilised interface for lookupGlobal >--------------------------------------------------------------- 6473d110ab1aa22a5933e405b59e3f597562ce02 compiler/coreSyn/CorePrep.hs | 20 ++++++++++++-------- compiler/simplCore/CoreMonad.hs | 9 ++++----- compiler/typecheck/TcEnv.hs | 20 +++++++++++++++++++- 3 files changed, 35 insertions(+), 14 deletions(-) diff --git a/compiler/coreSyn/CorePrep.hs b/compiler/coreSyn/CorePrep.hs index 87b7d16..1e99e80 100644 --- a/compiler/coreSyn/CorePrep.hs +++ b/compiler/coreSyn/CorePrep.hs @@ -30,7 +30,6 @@ import Type import Literal import Coercion import TcEnv -import TcRnMonad import TyCon import Demand import Var @@ -57,9 +56,14 @@ import Config import Name ( NamedThing(..), nameSrcSpan ) import SrcLoc ( SrcSpan(..), realSrcLocSpan, mkRealSrcLoc ) import Data.Bits +import MonadUtils ( mapAccumLM ) import Data.List ( mapAccumL ) import Control.Monad +#if __GLASGOW_HASKELL__ < 711 +import Control.Applicative +#endif + {- -- --------------------------------------------------------------------------- -- Overview @@ -1153,23 +1157,23 @@ data CorePrepEnv = CPE { lookupMkIntegerName :: DynFlags -> HscEnv -> IO Id lookupMkIntegerName dflags hsc_env = guardIntegerUse dflags $ liftM tyThingId $ - initTcForLookup hsc_env (tcLookupGlobal mkIntegerName) + lookupGlobal hsc_env mkIntegerName lookupIntegerSDataConName :: DynFlags -> HscEnv -> IO (Maybe DataCon) lookupIntegerSDataConName dflags hsc_env = case cIntegerLibraryType of - IntegerGMP -> guardIntegerUse dflags $ liftM Just $ - initTcForLookup hsc_env (tcLookupDataCon integerSDataConName) - IntegerGMP2-> guardIntegerUse dflags $ liftM Just $ - initTcForLookup hsc_env (tcLookupDataCon integerSDataConName) + IntegerGMP -> guardIntegerUse dflags $ liftM (Just . tyThingDataCon) $ + lookupGlobal hsc_env integerSDataConName + IntegerGMP2-> guardIntegerUse dflags $ liftM (Just . tyThingDataCon) $ + lookupGlobal hsc_env integerSDataConName IntegerSimple -> return Nothing -- | Helper for 'lookupMkIntegerName' and 'lookupIntegerSDataConName' guardIntegerUse :: DynFlags -> IO a -> IO a guardIntegerUse dflags act | thisPackage dflags == primPackageKey - = return $ panic "Can't use Integer in ghc-prim" + = return $ panic "Can't use Integer in ghc-prim" | thisPackage dflags == integerPackageKey - = return $ panic "Can't use Integer in integer-*" + = return $ panic "Can't use Integer in integer-*" | otherwise = act mkInitialCorePrepEnv :: DynFlags -> HscEnv -> IO CorePrepEnv diff --git a/compiler/simplCore/CoreMonad.hs b/compiler/simplCore/CoreMonad.hs index dec41bb..ae36557 100644 --- a/compiler/simplCore/CoreMonad.hs +++ b/compiler/simplCore/CoreMonad.hs @@ -56,6 +56,7 @@ module CoreMonad ( #ifdef GHCI import Name( Name ) +import TcRnMonad ( initTcForLookup ) #endif import CoreSyn import HscTypes @@ -67,8 +68,7 @@ import Annotations import IOEnv hiding ( liftIO, failM, failWithM ) import qualified IOEnv ( liftIO ) -import TcEnv ( tcLookupGlobal ) -import TcRnMonad ( initTcForLookup ) +import TcEnv ( lookupGlobal ) import Var import Outputable import FastString @@ -853,9 +853,8 @@ dumpIfSet_dyn flag str = msg (\dflags -> Err.dumpIfSet_dyn dflags flag str) -} instance MonadThings CoreM where - lookupThing name = do - hsc_env <- getHscEnv - liftIO $ initTcForLookup hsc_env (tcLookupGlobal name) + lookupThing name = do { hsc_env <- getHscEnv + ; liftIO $ lookupGlobal hsc_env name } {- ************************************************************************ diff --git a/compiler/typecheck/TcEnv.hs b/compiler/typecheck/TcEnv.hs index e31ce86..b8324b8 100644 --- a/compiler/typecheck/TcEnv.hs +++ b/compiler/typecheck/TcEnv.hs @@ -1,5 +1,4 @@ -- (c) The University of Glasgow 2006 - {-# LANGUAGE CPP, FlexibleInstances #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -- instance MonadThings is necessarily an orphan @@ -19,6 +18,7 @@ module TcEnv( tcLookupDataCon, tcLookupPatSyn, tcLookupConLike, tcLookupLocatedGlobalId, tcLookupLocatedTyCon, tcLookupLocatedClass, tcLookupAxiom, + lookupGlobal, -- Local environment tcExtendKindEnv, tcExtendKindEnv2, @@ -97,6 +97,23 @@ import Maybes( MaybeErr(..) ) import Data.IORef import Data.List + +{- ********************************************************************* +* * + An IO interface to looking up globals +* * +********************************************************************* -} + +lookupGlobal :: HscEnv -> Name -> IO TyThing +-- An IO version, used outside the typechecker +-- It's more complicated than it looks, because it may +-- need to suck in an interface file +lookupGlobal hsc_env name + = initTcForLookup hsc_env (tcLookupGlobal name) + -- This initTcForLookup stuff is massive overkill + -- but that's how it is right now, and at least + -- this function localises it + {- ************************************************************************ * * @@ -109,6 +126,7 @@ unless you know that the SrcSpan in the monad is already set to the span of the Name. -} + tcLookupLocatedGlobal :: Located Name -> TcM TyThing -- c.f. IfaceEnvEnv.tcIfaceGlobal tcLookupLocatedGlobal name From git at git.haskell.org Thu Mar 26 12:41:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Mar 2015 12:41:11 +0000 (UTC) Subject: [commit: ghc] wip/T9858-typeable-spj: tcRnDeclsi can use tcRnSrcDecls (021e6f5) Message-ID: <20150326124111.B6AE33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9858-typeable-spj Link : http://ghc.haskell.org/trac/ghc/changeset/021e6f583a1159b0a3581ab1713d560cadc2bdf7/ghc >--------------------------------------------------------------- commit 021e6f583a1159b0a3581ab1713d560cadc2bdf7 Author: Simon Peyton Jones Date: Mon Mar 23 14:32:31 2015 +0000 tcRnDeclsi can use tcRnSrcDecls I'm not sure why tcRnDeclsi didn't call tcRnSrcDecls before, but now it does. About 20 lines of code vanish. Hooray. >--------------------------------------------------------------- 021e6f583a1159b0a3581ab1713d560cadc2bdf7 compiler/typecheck/TcRnDriver.hs | 42 +++------------------------------------- 1 file changed, 3 insertions(+), 39 deletions(-) diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index dca128e..821fa7a 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -1850,45 +1850,9 @@ tcRnDeclsi exists to allow class, data, and other declarations in GHCi. tcRnDeclsi :: HscEnv -> [LHsDecl RdrName] -> IO (Messages, Maybe TcGblEnv) - -tcRnDeclsi hsc_env local_decls = - runTcInteractive hsc_env $ do - - ((tcg_env, tclcl_env), lie) <- - captureConstraints $ tc_rn_src_decls emptyModDetails local_decls - setEnvs (tcg_env, tclcl_env) $ do - - -- wanted constraints from static forms - stWC <- tcg_static_wc <$> getGblEnv >>= readTcRef - - new_ev_binds <- simplifyTop (andWC stWC lie) - - failIfErrsM - let TcGblEnv { tcg_type_env = type_env, - tcg_binds = binds, - tcg_sigs = sig_ns, - tcg_ev_binds = cur_ev_binds, - tcg_imp_specs = imp_specs, - tcg_rules = rules, - tcg_vects = vects, - tcg_fords = fords } = tcg_env - all_ev_binds = cur_ev_binds `unionBags` new_ev_binds - - (bind_ids, ev_binds', binds', fords', imp_specs', rules', vects') - <- zonkTopDecls all_ev_binds binds Nothing sig_ns rules vects - imp_specs fords - - let --global_ids = map globaliseAndTidyId bind_ids - final_type_env = extendTypeEnvWithIds type_env bind_ids --global_ids - tcg_env' = tcg_env { tcg_binds = binds', - tcg_ev_binds = ev_binds', - tcg_imp_specs = imp_specs', - tcg_rules = rules', - tcg_vects = vects', - tcg_fords = fords' } - - setGlobalTypeEnv tcg_env' final_type_env - +tcRnDeclsi hsc_env local_decls + = runTcInteractive hsc_env $ + tcRnSrcDecls emptyModDetails emptyBag local_decls #endif /* GHCi */ {- From git at git.haskell.org Thu Mar 26 12:41:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Mar 2015 12:41:15 +0000 (UTC) Subject: [commit: ghc] wip/T9858-typeable-spj: Generate Typeble info at definition sites (fe510d9) Message-ID: <20150326124115.9E2C23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9858-typeable-spj Link : http://ghc.haskell.org/trac/ghc/changeset/fe510d911b6cf61d6884b8b42d8771d4aea3229f/ghc >--------------------------------------------------------------- commit fe510d911b6cf61d6884b8b42d8771d4aea3229f Author: Simon Peyton Jones Date: Mon Mar 23 14:50:23 2015 +0000 Generate Typeble info at definition sites This patch implements the idea floated in #9858, namely that we should generate type-representation information at the data type declaration site, rather than when solving a Typeable constraint. However, this turned out quite a bit harder than I expected. I still think it's the right thing to do, and it's done now, but it was quite a struggle. See particularly * Note [Grand plan for Typeable] in TcTypeable (which is a new module) * Note [The overall promotion story] in DataCon (clarifies existing stuff) The most painful bit was that to generate Typeable instances (ie TyConRepName bindings) for every TyCon is tricky for types in ghc-prim etc: - we need to have enough data types around to *define* a TyCon - many of these types are wired-in Also, to minimise the code generated for each data type, I wanted to generate pure data, not CAFs with unpackCString# stuff floating about. Performance ~~~~~~~~~~~ Three perf/compiler tests start to allocate quite a bit more. This isn't surprising, because they all allocate zillions of data types, with practically no other code, esp T1969 T1969: GHC allocates 30% more T5642: GHC allocates 14% more T9872d: GHC allocates 5% more I'm treating this as acceptable. The payoff comes in Typeable-heavy code. Remaining to do ~~~~~~~~~~~~~~~ * I think that "TyCon" and "Module" are over-generic names to use for the runtime type representations used in GHC.Typeable. Better might be "TrTyCon" and "TrModule". But I have not yet done this * Add more info the the "TyCon" e.g. source location where it was defined * Use the new "Module" type to help with Trac #10068 * It would be possible to generate TyConRepName (ie Typeable instances) selectively rather than all the time. We'd need to persist the information in interface files. Lacking a motivating reason I have not done this, but it would not be difficult. Refactoring ~~~~~~~~~~~ As is so often the case, I ended up refactoring more than I intended. In particular * In TyCon, - a type *family* (whether type or data) is repesented by a FamilyTyCon - a algebraic data type (including data/newtype instances) is represented by AlgTyCon This wasn't true before; a data family was represented as an AlgTyCon. There are some corresponding changes in IfaceSyn. Also get rid of the (unhelpfully named) tyConParent. * In TyCon define 'Promoted', isomorphic to Maybe, used when things are optionally promoted; and use it elsewhere in GHC. * Each TyCon, including promoted TyCons, contains its TyConRepName, if it has one. This is, in effect, the name of its Typeable instance. * I added PatSynId, DefMethId, and ReflectionId to the IdInfo.IdDetails type. They are used for debugging only, namely to suppress excessive output in -ddump-types. * Tidy up the generation of PrelInfo.knownKeyNames * Move newImplicitBinder from IfaceEnv to BuildTyCl * PrelNames.conName renamed to dcQual for consistency with varQual, tcQual * Move mkDefaultMethodIds, mkRecSelBinds from TcTyClsDecls to TcTyDecls >--------------------------------------------------------------- fe510d911b6cf61d6884b8b42d8771d4aea3229f compiler/basicTypes/DataCon.hs | 256 +++++++++++----- compiler/basicTypes/IdInfo.hs | 19 +- compiler/basicTypes/OccName.hs | 19 +- compiler/basicTypes/Unique.hs | 59 ++-- compiler/deSugar/DsBinds.hs | 270 ++++++++-------- compiler/ghc.cabal.in | 1 + compiler/hsSyn/HsUtils.hs | 6 +- compiler/iface/BinIface.hs | 10 +- compiler/iface/BuildTyCl.hs | 73 +++-- compiler/iface/IfaceEnv.hs | 33 +- compiler/iface/IfaceSyn.hs | 86 +++--- compiler/iface/MkIface.hs | 25 +- compiler/iface/TcIface.hs | 67 ++-- compiler/main/HscMain.hs | 10 +- compiler/main/HscTypes.hs | 20 +- compiler/prelude/PrelInfo.hs | 66 ++-- compiler/prelude/PrelNames.hs | 122 +++++--- compiler/prelude/TysPrim.hs | 42 +-- compiler/prelude/TysWiredIn.hs | 188 ++++++------ compiler/typecheck/TcBinds.hs | 35 ++- compiler/typecheck/TcDeriv.hs | 86 +----- compiler/typecheck/TcEvidence.hs | 37 +-- compiler/typecheck/TcGenGenerics.hs | 38 ++- compiler/typecheck/TcHsSyn.hs | 28 +- compiler/typecheck/TcHsType.hs | 8 +- compiler/typecheck/TcInstDcls.hs | 26 +- compiler/typecheck/TcInteract.hs | 203 +++++++----- compiler/typecheck/TcPatSyn.hs | 4 +- compiler/typecheck/TcRnDriver.hs | 43 +-- compiler/typecheck/TcRnMonad.hs | 2 +- compiler/typecheck/TcRnTypes.hs | 7 +- compiler/typecheck/TcTyClsDecls.hs | 324 ++++---------------- compiler/typecheck/TcTyDecls.hs | 325 ++++++++++++++++---- compiler/typecheck/TcType.hs | 0 compiler/typecheck/TcTypeNats.hs | 10 +- compiler/typecheck/TcTypeable.hs | 202 ++++++++++++ compiler/types/TyCon.hs | 407 ++++++++++++++----------- compiler/types/Type.hs | 12 + compiler/utils/Binary.hs | 11 +- compiler/vectorise/Vectorise/Generic/PData.hs | 4 +- compiler/vectorise/Vectorise/Type/Env.hs | 4 +- compiler/vectorise/Vectorise/Type/TyConDecl.hs | 7 +- libraries/base/Data/Typeable.hs | 3 +- libraries/base/Data/Typeable/Internal.hs | 331 +++++++++++++------- libraries/base/GHC/Show.hs | 10 + libraries/ghc-prim/GHC/Classes.hs | 46 ++- libraries/ghc-prim/GHC/IntWord64.hs | 3 + libraries/ghc-prim/GHC/Magic.hs | 2 + libraries/ghc-prim/GHC/Tuple.hs | 3 + libraries/ghc-prim/GHC/TyCon.hs | 15 + libraries/ghc-prim/GHC/Types.hs | 51 +++- 51 files changed, 2177 insertions(+), 1482 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fe510d911b6cf61d6884b8b42d8771d4aea3229f From git at git.haskell.org Thu Mar 26 12:41:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Mar 2015 12:41:18 +0000 (UTC) Subject: [commit: ghc] wip/T9858-typeable-spj: Error message wibbles (a620075) Message-ID: <20150326124118.6382C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9858-typeable-spj Link : http://ghc.haskell.org/trac/ghc/changeset/a6200759fd2f3f0e901cb2092e148bf31abb08b4/ghc >--------------------------------------------------------------- commit a6200759fd2f3f0e901cb2092e148bf31abb08b4 Author: Simon Peyton Jones Date: Mon Mar 23 14:53:53 2015 +0000 Error message wibbles These are associated with - new instance reporting - typeable changes in -ddump-simpl output - -ddump-types being a bit less verbose - some renaming of type variables in debugger output (no idea why this happens) >--------------------------------------------------------------- a6200759fd2f3f0e901cb2092e148bf31abb08b4 .../tests/annotations/should_fail/annfail10.stderr | 29 ++++---- .../tests/deSugar/should_compile/T2431.stderr | 24 ++++++- testsuite/tests/deriving/should_fail/T9687.hs | 1 + testsuite/tests/deriving/should_fail/T9687.stderr | 4 +- testsuite/tests/ghci.debugger/scripts/T2740.stdout | 2 +- .../tests/ghci.debugger/scripts/break006.stderr | 26 ++++--- .../tests/ghci.debugger/scripts/break009.stdout | 2 +- .../tests/ghci.debugger/scripts/break010.stdout | 4 +- .../tests/ghci.debugger/scripts/break011.stdout | 8 +-- .../tests/ghci.debugger/scripts/break012.stdout | 16 ++--- .../tests/ghci.debugger/scripts/break018.stdout | 4 +- .../ghci.debugger/scripts/break022/break022.stdout | 2 +- .../tests/ghci.debugger/scripts/break028.stdout | 6 +- .../tests/ghci.debugger/scripts/print018.stdout | 6 +- .../tests/ghci.debugger/scripts/print019.stderr | 6 +- .../tests/ghci.debugger/scripts/print031.stdout | 2 +- testsuite/tests/ghci/scripts/Defer02.stderr | 3 +- testsuite/tests/ghci/scripts/T4175.stdout | 4 +- testsuite/tests/ghci/scripts/T5417.stdout | 2 - testsuite/tests/ghci/scripts/T8674.stdout | 4 +- testsuite/tests/ghci/scripts/T9181.stdout | 28 ++++---- .../tests/indexed-types/should_fail/T4485.stderr | 2 +- .../tests/numeric/should_compile/T7116.stdout | 27 +++++++- .../should_fail/overloadedlistsfail01.stderr | 18 ++--- testsuite/tests/polykinds/T8132.stderr | 2 +- testsuite/tests/quasiquotation/T7918.stdout | 3 + testsuite/tests/rebindable/rebindable6.stderr | 6 +- testsuite/tests/roles/should_compile/Roles1.stderr | 3 - .../tests/roles/should_compile/Roles13.stderr | 29 ++++---- .../tests/roles/should_compile/Roles14.stderr | 3 - testsuite/tests/roles/should_compile/Roles2.stderr | 3 - testsuite/tests/roles/should_compile/Roles3.stderr | 3 - testsuite/tests/roles/should_compile/Roles4.stderr | 3 - testsuite/tests/roles/should_compile/T8958.stderr | 16 ----- testsuite/tests/roles/should_compile/all.T | 14 ++-- .../tests/simplCore/should_compile/T3234.stderr | 4 +- .../tests/simplCore/should_compile/T3717.stderr | 27 +++++++- .../tests/simplCore/should_compile/T3772.stdout | 27 +++++++- .../tests/simplCore/should_compile/T4908.stderr | 27 +++++++- .../tests/simplCore/should_compile/T4930.stderr | 27 +++++++- .../tests/simplCore/should_compile/T7360.stderr | 44 +++++++++++- .../tests/simplCore/should_compile/T8274.stdout | 8 +++ .../tests/simplCore/should_compile/T9400.stderr | 14 +++- .../tests/simplCore/should_compile/rule2.stderr | 3 +- .../simplCore/should_compile/spec-inline.stderr | 27 +++++++- .../stranal/sigs/BottomFromInnerLambda.stderr | 1 + testsuite/tests/stranal/sigs/DmdAnalGADTs.stderr | 2 + testsuite/tests/stranal/sigs/HyperStrUse.stderr | 1 + testsuite/tests/stranal/sigs/StrAnalExample.stderr | 1 + testsuite/tests/stranal/sigs/T8569.stderr | 2 + testsuite/tests/stranal/sigs/T8598.stderr | 1 + testsuite/tests/stranal/sigs/UnsatFun.stderr | 1 + testsuite/tests/th/TH_Roles2.stderr | 3 - testsuite/tests/th/all.T | 2 +- .../tests/typecheck/should_compile/holes2.stderr | 4 +- testsuite/tests/typecheck/should_fail/T4921.stderr | 4 +- testsuite/tests/typecheck/should_fail/T5095.stderr | 81 ++-------------------- testsuite/tests/typecheck/should_fail/T5858.stderr | 2 +- testsuite/tests/typecheck/should_fail/T7857.stderr | 2 +- testsuite/tests/typecheck/should_fail/T9999.hs | 16 ++++- testsuite/tests/typecheck/should_fail/T9999.stderr | 11 --- testsuite/tests/typecheck/should_fail/all.T | 2 +- .../tests/typecheck/should_fail/tcfail008.stderr | 3 +- .../tests/typecheck/should_fail/tcfail040.stderr | 2 +- .../tests/typecheck/should_fail/tcfail043.stderr | 4 +- .../tests/typecheck/should_fail/tcfail072.stderr | 8 ++- .../tests/typecheck/should_fail/tcfail128.stderr | 6 +- .../tests/typecheck/should_fail/tcfail133.stderr | 4 +- .../tests/typecheck/should_fail/tcfail181.stderr | 3 +- 69 files changed, 413 insertions(+), 276 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a6200759fd2f3f0e901cb2092e148bf31abb08b4 From git at git.haskell.org Thu Mar 26 12:41:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Mar 2015 12:41:21 +0000 (UTC) Subject: [commit: ghc] wip/T9858-typeable-spj: Remove a redndant 'return' (fcd18c4) Message-ID: <20150326124121.5A3353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9858-typeable-spj Link : http://ghc.haskell.org/trac/ghc/changeset/fcd18c42b6ae2e73a9f4c67dbe6d994b0f8468c8/ghc >--------------------------------------------------------------- commit fcd18c42b6ae2e73a9f4c67dbe6d994b0f8468c8 Author: Simon Peyton Jones Date: Thu Mar 26 11:06:12 2015 +0000 Remove a redndant 'return' >--------------------------------------------------------------- fcd18c42b6ae2e73a9f4c67dbe6d994b0f8468c8 libraries/base/Foreign/Marshal/Array.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/libraries/base/Foreign/Marshal/Array.hs b/libraries/base/Foreign/Marshal/Array.hs index 0aea67b..5e10341 100644 --- a/libraries/base/Foreign/Marshal/Array.hs +++ b/libraries/base/Foreign/Marshal/Array.hs @@ -211,8 +211,7 @@ withArrayLen :: Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b withArrayLen vals f = allocaArray len $ \ptr -> do pokeArray ptr vals - res <- f len ptr - return res + f len ptr where len = length vals From git at git.haskell.org Thu Mar 26 21:42:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 26 Mar 2015 21:42:49 +0000 (UTC) Subject: [commit: ghc] master: Fix Git-commit-id detection for RELEASE=YES (5aa57d0) Message-ID: <20150326214249.256FF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5aa57d0137e7626a2ed2b3656d24d7a1aac74e58/ghc >--------------------------------------------------------------- commit 5aa57d0137e7626a2ed2b3656d24d7a1aac74e58 Author: Herbert Valerio Riedel Date: Thu Mar 26 22:39:52 2015 +0100 Fix Git-commit-id detection for RELEASE=YES By mistake, the Git-commit-id detection was only enabled for `RELEASE=NO` (since the date-based GHC version computation is only active in that case). With this commit the commit-id detection is active regardless of the `RELEASE`-setting. This is a follow-up to 73e5e2f8bade2d8b2b1ecae958fe12d0b24591ef >--------------------------------------------------------------- 5aa57d0137e7626a2ed2b3656d24d7a1aac74e58 aclocal.m4 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index 5726a3f..f5456ae 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1586,6 +1586,7 @@ if test "$RELEASE" = "NO"; then dnl less likely to go wrong. PACKAGE_VERSION=${PACKAGE_VERSION}.`date +%Y%m%d` fi +fi AC_MSG_CHECKING([for GHC Git commit id]) if test -d .git; then @@ -1603,7 +1604,6 @@ if test "$RELEASE" = "NO"; then PACKAGE_GIT_COMMIT_ID="0000000000000000000000000000000000000000" fi -fi # Some renamings AC_SUBST([ProjectName], [$PACKAGE_NAME]) From git at git.haskell.org Fri Mar 27 15:26:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:26:23 +0000 (UTC) Subject: [commit: ghc] master: Remove some unimplemented GranSim primops (90dd11b) Message-ID: <20150327152623.78C243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/90dd11bf1918485f0f19bb2fb764f1675c0f0dd5/ghc >--------------------------------------------------------------- commit 90dd11bf1918485f0f19bb2fb764f1675c0f0dd5 Author: Reid Barton Date: Fri Mar 27 11:25:19 2015 -0400 Remove some unimplemented GranSim primops Summary: An attempt to use these resulted in an error like: [1 of 1] Compiling Main ( p.hs, p.o ) ghc: panic! (the 'impossible' happened) (GHC version 7.8.4 for x86_64-unknown-linux): emitPrimOp: can't translate PrimOp parAt#{v} Test Plan: validate Reviewers: thomie, austin Reviewed By: thomie, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D758 >--------------------------------------------------------------- 90dd11bf1918485f0f19bb2fb764f1675c0f0dd5 compiler/prelude/PrimOp.hs | 6 ----- compiler/prelude/primops.txt.pp | 49 ----------------------------------------- 2 files changed, 55 deletions(-) diff --git a/compiler/prelude/PrimOp.hs b/compiler/prelude/PrimOp.hs index 1c9b49e..de6d49b 100644 --- a/compiler/prelude/PrimOp.hs +++ b/compiler/prelude/PrimOp.hs @@ -278,12 +278,6 @@ Invariants: stable name. --- HWL: The first 4 Int# in all par... annotations denote: --- name, granularity info, size of result, degree of parallelism --- Same structure as _seq_ i.e. returns Int# --- KSW: v, the second arg in parAt# and parAtForNow#, is used only to determine --- `the processor containing the expression v'; it is not evaluated - These primops are pretty weird. dataToTag# :: a -> Int (arg must be an evaluated data type) diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp index 909b17b..162063e 100644 --- a/compiler/prelude/primops.txt.pp +++ b/compiler/prelude/primops.txt.pp @@ -2421,55 +2421,6 @@ primop NumSparks "numSparks#" GenPrimOp has_side_effects = True out_of_line = True --- HWL: The first 4 Int# in all par... annotations denote: --- name, granularity info, size of result, degree of parallelism --- Same structure as _seq_ i.e. returns Int# --- KSW: v, the second arg in parAt# and parAtForNow#, is used only to determine --- `the processor containing the expression v'; it is not evaluated - -primop ParGlobalOp "parGlobal#" GenPrimOp - a -> Int# -> Int# -> Int# -> Int# -> b -> Int# - with - has_side_effects = True - -primop ParLocalOp "parLocal#" GenPrimOp - a -> Int# -> Int# -> Int# -> Int# -> b -> Int# - with - has_side_effects = True - -primop ParAtOp "parAt#" GenPrimOp - b -> a -> Int# -> Int# -> Int# -> Int# -> c -> Int# - with - has_side_effects = True - -primop ParAtAbsOp "parAtAbs#" GenPrimOp - a -> Int# -> Int# -> Int# -> Int# -> Int# -> b -> Int# - with - has_side_effects = True - -primop ParAtRelOp "parAtRel#" GenPrimOp - a -> Int# -> Int# -> Int# -> Int# -> Int# -> b -> Int# - with - has_side_effects = True - -primop ParAtForNowOp "parAtForNow#" GenPrimOp - b -> a -> Int# -> Int# -> Int# -> Int# -> c -> Int# - with - has_side_effects = True - --- copyable# and noFollow# are yet to be implemented (for GpH) --- ---primop CopyableOp "copyable#" GenPrimOp --- a -> Int# --- with --- has_side_effects = True --- ---primop NoFollowOp "noFollow#" GenPrimOp --- a -> Int# --- with --- has_side_effects = True - - ------------------------------------------------------------------------ section "Tag to enum stuff" {Convert back and forth between values of enumerated types From git at git.haskell.org Fri Mar 27 15:39:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:39:58 +0000 (UTC) Subject: [commit: ghc] master: Update list of primops that don't get wrappers (#10191) (af45feb) Message-ID: <20150327153958.01F8F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/af45feba476af0b5a12f3a1ac36854f2cf44f993/ghc >--------------------------------------------------------------- commit af45feba476af0b5a12f3a1ac36854f2cf44f993 Author: Reid Barton Date: Fri Mar 27 00:09:23 2015 -0400 Update list of primops that don't get wrappers (#10191) Summary: The list was 14 years old, and there don't seem to be any problems with seq# or par#; the other par*# primops were not actually implemented at all and were removed in D758. Test Plan: validate; will also try to locally validate an unregisterised build in case there was some truth to the deleted comment Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D759 GHC Trac Issues: #10191 >--------------------------------------------------------------- af45feba476af0b5a12f3a1ac36854f2cf44f993 utils/genprimopcode/Main.hs | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/utils/genprimopcode/Main.hs b/utils/genprimopcode/Main.hs index 7ade0b1..803323f 100644 --- a/utils/genprimopcode/Main.hs +++ b/utils/genprimopcode/Main.hs @@ -567,12 +567,10 @@ gen_wrappers (Info _ entries) dodgy spec = name spec `elem` - [-- C code generator can't handle these - "seq#", - "tagToEnum#", - -- not interested in parallel support - "par#", "parGlobal#", "parLocal#", "parAt#", - "parAtAbs#", "parAtRel#", "parAtForNow#" + [-- tagToEnum# is really magical, and can't have + -- a wrapper since its implementation depends on + -- the type of its result + "tagToEnum#" ] is_llvm_only :: Entry -> Bool From git at git.haskell.org Fri Mar 27 15:45:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:45:43 +0000 (UTC) Subject: [commit: ghc] branch 'wip/orf-reboot' created Message-ID: <20150327154543.D802F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/orf-reboot Referencing: 3c3e1dc7e2fce256cdd786fe119774386ff76cd5 From git at git.haskell.org Fri Mar 27 15:45:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:45:47 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: WIP rebuilding ORF (40ce4b3) Message-ID: <20150327154547.A1C4D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/40ce4b35d4ecd87485ec37ced35126a47b060fb0/ghc >--------------------------------------------------------------- commit 40ce4b35d4ecd87485ec37ced35126a47b060fb0 Author: Adam Gundry Date: Fri Feb 20 08:17:15 2015 +0000 WIP rebuilding ORF >--------------------------------------------------------------- 40ce4b35d4ecd87485ec37ced35126a47b060fb0 compiler/basicTypes/Avail.hs | 149 +- compiler/basicTypes/DataCon.hs | 21 +- compiler/basicTypes/DataCon.hs-boot | 2 + compiler/basicTypes/FieldLabel.lhs | 145 ++ compiler/basicTypes/Id.hs | 12 +- compiler/basicTypes/MkId.hs | 2 +- compiler/basicTypes/OccName.hs | 31 +- compiler/basicTypes/RdrName.hs | 151 +- compiler/basicTypes/SrcLoc.hs | 8 +- compiler/deSugar/Check.hs | 5 +- compiler/deSugar/Coverage.hs | 4 +- compiler/deSugar/Desugar.hs | 2 + compiler/deSugar/DsExpr.hs | 19 +- compiler/deSugar/DsMeta.hs | 4 +- compiler/deSugar/DsMonad.hs | 1 + compiler/deSugar/MatchCon.hs | 5 +- compiler/ghc.cabal.in | 3 + compiler/ghc.mk | 7 + compiler/hsSyn/Convert.hs | 29 +- compiler/hsSyn/HsDecls.hs | 15 +- compiler/hsSyn/HsExpr.hs | 8 + compiler/hsSyn/HsImpExp.hs | 50 +- compiler/hsSyn/HsPat.hs | 73 +- compiler/hsSyn/HsTypes.hs | 79 +- compiler/hsSyn/HsUtils.hs | 126 +- compiler/iface/BuildTyCl.hs | 2 +- compiler/iface/IfaceSyn.hs | 47 +- compiler/iface/LoadIface.hs | 14 +- compiler/iface/MkIface.hs | 31 +- compiler/iface/TcIface.hs | 30 +- compiler/main/DynFlags.hs | 10 + compiler/main/GHC.hs | 19 +- compiler/main/HscMain.hs | 8 +- compiler/main/HscTypes.hs | 27 +- compiler/main/InteractiveEval.hs | 1 + compiler/main/TidyPgm.hs | 5 +- compiler/parser/Parser.y | 6 +- compiler/parser/RdrHsSyn.hs | 6 +- compiler/prelude/PrelInfo.hs | 2 +- compiler/prelude/PrelNames.hs | 37 +- compiler/prelude/TysWiredIn.hs | 2 +- compiler/rename/RnEnv.hs | 307 ++- compiler/rename/RnExpr.hs | 20 +- compiler/rename/RnNames.hs | 490 ++++- compiler/rename/RnPat.hs | 75 +- compiler/rename/RnSource.hs | 175 +- compiler/rename/RnTypes.hs | 63 +- compiler/typecheck/FamInst.hs | 56 +- compiler/typecheck/Inst.hs | 3 +- compiler/typecheck/TcEnv.hs | 57 +- compiler/typecheck/TcErrors.hs | 56 +- compiler/typecheck/TcExpr.hs | 329 ++- compiler/typecheck/TcFldInsts.lhs | 473 +++++ compiler/typecheck/TcGenDeriv.hs | 11 +- compiler/typecheck/TcGenGenerics.hs | 13 +- compiler/typecheck/TcHsSyn.hs | 5 +- compiler/typecheck/TcHsType.hs | 17 +- compiler/typecheck/TcInstDcls.hs | 2 +- compiler/typecheck/TcInteract.lhs | 2194 ++++++++++++++++++++ compiler/typecheck/TcPat.hs | 32 +- compiler/typecheck/TcRnDriver.hs | 22 +- compiler/typecheck/TcRnMonad.hs | 5 +- compiler/typecheck/TcRnTypes.hs | 31 +- compiler/typecheck/TcSMonad.lhs | 1963 +++++++++++++++++ compiler/typecheck/TcSplice.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 125 +- compiler/typecheck/TcType.hs | 9 + compiler/typecheck/TcValidity.hs | 19 +- compiler/types/TyCon.hs | 53 +- compiler/types/Type.hs | 30 +- compiler/types/Type.hs-boot | 2 + compiler/types/TypeRep.hs | 44 +- compiler/utils/FastStringEnv.lhs | 75 + docs/users_guide/glasgow_exts.xml | 307 +++ libraries/base/GHC/Base.hs | 1 + libraries/base/GHC/Records.hs | 249 +++ libraries/base/GHC/TypeLits.hs | 8 +- libraries/base/base.cabal | 1 + testsuite/tests/driver/T4437.hs | 1 + testsuite/tests/ghci/scripts/ghci042.stdout | 2 +- testsuite/tests/module/mod176.stderr | 2 +- .../{annotations => overloadedrecflds}/Makefile | 0 .../ghci}/Makefile | 0 testsuite/tests/overloadedrecflds/ghci/all.T | 3 + .../ghci/overloadedrecfldsghci01.script | 13 + .../ghci/overloadedrecfldsghci01.stdout | 11 + .../should_fail}/Makefile | 0 .../should_fail/OverloadedRecFldsFail04_A.hs | 9 + .../should_fail/OverloadedRecFldsFail06_A.hs | 16 + .../should_fail/OverloadedRecFldsFail08_A.hs | 14 + .../tests/overloadedrecflds/should_fail/all.T | 16 + .../should_fail/overloadedrecfldsfail01.hs | 17 + .../should_fail/overloadedrecfldsfail01.stderr | 16 + .../should_fail/overloadedrecfldsfail02.hs | 19 + .../should_fail/overloadedrecfldsfail02.stderr | 50 + .../should_fail/overloadedrecfldsfail03.hs | 7 + .../should_fail/overloadedrecfldsfail03.stderr | 5 + .../should_fail/overloadedrecfldsfail04.hs | 9 + .../should_fail/overloadedrecfldsfail04.stderr | 5 + .../should_fail/overloadedrecfldsfail05.hs | 10 + .../should_fail/overloadedrecfldsfail05.stderr | 10 + .../should_fail/overloadedrecfldsfail06.hs | 10 + .../should_fail/overloadedrecfldsfail06.stderr | 15 + .../should_fail/overloadedrecfldsfail07.hs | 11 + .../should_fail/overloadedrecfldsfail07.stderr | 6 + .../should_fail/overloadedrecfldsfail08.hs | 13 + .../should_fail/overloadedrecfldsfail08.stderr | 47 + .../should_fail/overloadedrecfldsfail09.hs | 9 + .../should_fail/overloadedrecfldsfail09.stderr | 20 + .../should_fail/overloadedrecfldsfail10.hs | 11 + .../should_fail/overloadedrecfldsfail10.stderr | 9 + .../should_run}/Makefile | 0 .../should_run/OverloadedRecFldsRun01_A.hs | 9 + .../should_run/OverloadedRecFldsRun02_A.hs | 9 + .../should_run/OverloadedRecFldsRun07_A.hs | 11 + .../should_run/OverloadedRecFldsRun07_B.hs | 7 + .../should_run/OverloadedRecFldsRun08_A.hs | 11 + .../should_run/OverloadedRecFldsRun08_B.hs | 7 + .../should_run/OverloadedRecFldsRun08_C.hs | 7 + .../should_run/OverloadedRecFldsRun11_A.hs | 9 + .../should_run/OverloadedRecFldsRun11_A.hs-boot | 5 + .../should_run/OverloadedRecFldsRun11_B.hs | 7 + .../should_run/OverloadedRecFldsRun12_A.hs | 11 + .../should_run/OverloadedRecFldsRun12_B.hs | 7 + testsuite/tests/overloadedrecflds/should_run/all.T | 26 + .../should_run/overloadedrecfldsrun01.hs | 70 + .../should_run/overloadedrecfldsrun01.stdout | 13 + .../should_run/overloadedrecfldsrun02.hs | 6 + .../should_run/overloadedrecfldsrun02.stdout | 0 .../should_run/overloadedrecfldsrun03.hs | 18 + .../should_run/overloadedrecfldsrun03.stdout | 4 + .../should_run/overloadedrecfldsrun04.hs | 18 + .../should_run/overloadedrecfldsrun04.stdout | 3 + .../should_run/overloadedrecfldsrun05.hs | 34 + .../should_run/overloadedrecfldsrun05.stdout | 2 + .../should_run/overloadedrecfldsrun06.hs | 28 + .../should_run/overloadedrecfldsrun06.stdout | 1 + .../should_run/overloadedrecfldsrun07.hs | 7 + .../should_run/overloadedrecfldsrun07.stdout} | 0 .../should_run/overloadedrecfldsrun08.hs | 7 + .../should_run/overloadedrecfldsrun08.stdout | 2 + .../should_run/overloadedrecfldsrun09.hs | 8 + .../should_run/overloadedrecfldsrun09.stdout | 2 + .../should_run/overloadedrecfldsrun10.hs | 12 + .../should_run/overloadedrecfldsrun10.stderr | 2 + .../should_run/overloadedrecfldsrun11.hs | 5 + .../should_run/overloadedrecfldsrun11.stdout} | 0 .../should_run/overloadedrecfldsrun12.hs | 6 + .../should_run/overloadedrecfldsrun12.stdout | 2 + .../should_run/overloadedrecfldsrun13.hs | 9 + .../should_run/overloadedrecfldsrun13.stdout} | 0 .../tests/typecheck/should_fail/tcfail102.stderr | 7 +- utils/ghctags/Main.hs | 2 +- 153 files changed, 8611 insertions(+), 691 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 40ce4b35d4ecd87485ec37ced35126a47b060fb0 From git at git.haskell.org Fri Mar 27 15:45:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:45:51 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Very rough removal of magical typeclasses (dbf9a8c) Message-ID: <20150327154551.BF8E93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/dbf9a8cc14757302cc91d252a200d33abd909a75/ghc >--------------------------------------------------------------- commit dbf9a8cc14757302cc91d252a200d33abd909a75 Author: Adam Gundry Date: Fri Feb 20 08:47:42 2015 +0000 Very rough removal of magical typeclasses >--------------------------------------------------------------- dbf9a8cc14757302cc91d252a200d33abd909a75 .../basicTypes/{FieldLabel.lhs => FieldLabel.hs} | 63 +- compiler/basicTypes/OccName.hs | 8 +- compiler/deSugar/Desugar.hs | 2 - compiler/deSugar/DsExpr.hs | 3 +- compiler/ghc.cabal.in | 1 - compiler/hsSyn/HsExpr.hs | 4 - compiler/main/DynFlags.hs | 7 +- compiler/main/HscMain.hs | 8 +- compiler/main/HscTypes.hs | 16 +- compiler/main/TidyPgm.hs | 5 +- compiler/prelude/PrelNames.hs | 28 - compiler/rename/RnEnv.hs | 98 - compiler/rename/RnExpr.hs | 20 +- compiler/rename/RnNames.hs | 11 +- compiler/typecheck/TcExpr.hs | 38 - compiler/typecheck/TcFldInsts.lhs | 473 ----- compiler/typecheck/TcHsType.hs | 17 +- compiler/typecheck/TcInteract.lhs | 2194 -------------------- compiler/typecheck/TcRnDriver.hs | 18 +- compiler/typecheck/TcRnMonad.hs | 1 - compiler/typecheck/TcRnTypes.hs | 2 - compiler/typecheck/TcSMonad.lhs | 1963 ----------------- compiler/typecheck/TcValidity.hs | 19 +- compiler/types/Type.hs | 30 +- compiler/types/TypeRep.hs | 44 +- .../utils/{FastStringEnv.lhs => FastStringEnv.hs} | 4 +- 26 files changed, 43 insertions(+), 5034 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc dbf9a8cc14757302cc91d252a200d33abd909a75 From git at git.haskell.org Fri Mar 27 15:45:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:45:54 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Very rough conflict resolution (32e5ce5) Message-ID: <20150327154554.BFC153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/32e5ce580b58295c5fd36ea44d858169c741a2b5/ghc >--------------------------------------------------------------- commit 32e5ce580b58295c5fd36ea44d858169c741a2b5 Author: Adam Gundry Date: Fri Feb 20 10:19:18 2015 +0000 Very rough conflict resolution >--------------------------------------------------------------- 32e5ce580b58295c5fd36ea44d858169c741a2b5 compiler/hsSyn/Convert.hs | 31 +++------- compiler/hsSyn/HsDecls.hs | 2 +- compiler/rename/RnSource.hs | 72 ++--------------------- compiler/rename/RnTypes.hs | 66 ++++----------------- compiler/typecheck/TcPat.hs | 26 ++------- compiler/typecheck/TcTyClsDecls.hs | 117 ++++++++----------------------------- 6 files changed, 52 insertions(+), 262 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 32e5ce580b58295c5fd36ea44d858169c741a2b5 From git at git.haskell.org Fri Mar 27 15:45:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:45:57 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Get rid of GHC.Records (9cea576) Message-ID: <20150327154557.BEB343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/9cea576b081135f5aadf9dcf709b60ecce141588/ghc >--------------------------------------------------------------- commit 9cea576b081135f5aadf9dcf709b60ecce141588 Author: Adam Gundry Date: Fri Feb 20 10:29:19 2015 +0000 Get rid of GHC.Records >--------------------------------------------------------------- 9cea576b081135f5aadf9dcf709b60ecce141588 compiler/basicTypes/MkId.hs | 2 +- compiler/prelude/PrelNames.hs | 11 +- compiler/prelude/TysWiredIn.hs | 2 +- libraries/base/GHC/Base.hs | 1 - libraries/base/GHC/Records.hs | 249 ----------------------------------------- libraries/base/GHC/TypeLits.hs | 8 +- libraries/base/base.cabal | 1 - 7 files changed, 7 insertions(+), 267 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9cea576b081135f5aadf9dcf709b60ecce141588 From git at git.haskell.org Fri Mar 27 15:46:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:00 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Successfully compiling stage 1 (a35adba) Message-ID: <20150327154600.C4D3B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/a35adbabd3b6a83bb9e60aff0986d7e64cad616c/ghc >--------------------------------------------------------------- commit a35adbabd3b6a83bb9e60aff0986d7e64cad616c Author: Adam Gundry Date: Fri Feb 20 10:59:00 2015 +0000 Successfully compiling stage 1 >--------------------------------------------------------------- a35adbabd3b6a83bb9e60aff0986d7e64cad616c compiler/basicTypes/FieldLabel.hs | 2 +- compiler/hsSyn/HsTypes.hs | 4 +-- compiler/rename/RnEnv.hs | 1 - compiler/rename/RnPat.hs | 4 +-- compiler/rename/RnSource.hs | 4 +-- compiler/rename/RnTypes.hs | 9 +++--- compiler/typecheck/FamInst.hs | 56 ++----------------------------------- compiler/typecheck/TcErrors.hs | 56 +++---------------------------------- compiler/typecheck/TcExpr.hs | 26 ++++++++--------- compiler/typecheck/TcGenGenerics.hs | 13 +++++---- compiler/typecheck/TcTyClsDecls.hs | 4 +-- 11 files changed, 40 insertions(+), 139 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a35adbabd3b6a83bb9e60aff0986d7e64cad616c From git at git.haskell.org Fri Mar 27 15:46:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:03 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Successfully compiling stage 2 (f8efbff) Message-ID: <20150327154603.C6CD93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/f8efbffeb293eaed322b021b5c1a589dee46af79/ghc >--------------------------------------------------------------- commit f8efbffeb293eaed322b021b5c1a589dee46af79 Author: Adam Gundry Date: Fri Feb 20 12:57:41 2015 +0000 Successfully compiling stage 2 >--------------------------------------------------------------- f8efbffeb293eaed322b021b5c1a589dee46af79 compiler/deSugar/DsMeta.hs | 6 +++--- compiler/ghc.mk | 5 ----- compiler/hsSyn/Convert.hs | 4 ++-- compiler/typecheck/TcTyClsDecls.hs | 19 +++++-------------- 4 files changed, 10 insertions(+), 24 deletions(-) diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs index a496b78..72d765c 100644 --- a/compiler/deSugar/DsMeta.hs +++ b/compiler/deSugar/DsMeta.hs @@ -1864,9 +1864,9 @@ repConstr con (RecCon (L _ ips)) ; rep2 recCName [unC con, unC arg_vtys] } where rep_ip (L _ ip) = mapM (rep_one_ip (cd_fld_type ip)) (cd_fld_names ip) - rep_one_ip t n = do { MkC v <- lookupLOcc n - ; MkC ty <- repBangTy t - ; rep2 varStrictTypeName [v,ty] } + rep_one_ip t (L l _, Just n) = do { MkC v <- lookupLOcc $ L l n -- AMG TODO ? + ; MkC ty <- repBangTy t + ; rep2 varStrictTypeName [v,ty] } repConstr con (InfixCon st1 st2) = do arg1 <- repBangTy st1 diff --git a/compiler/ghc.mk b/compiler/ghc.mk index b520fec..c8e9e4a 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -562,17 +562,12 @@ compiler_stage2_dll0_MODULES = \ Pretty \ PrimOp \ RdrName \ - RnEnv \ - RnHsDoc \ - RnNames \ Rules \ Serialized \ SrcLoc \ StaticFlags \ StringBuffer \ - TcEnv \ TcEvidence \ - TcMType \ TcRnTypes \ TcType \ TrieMap \ diff --git a/compiler/hsSyn/Convert.hs b/compiler/hsSyn/Convert.hs index 2ec1f71..629f891 100644 --- a/compiler/hsSyn/Convert.hs +++ b/compiler/hsSyn/Convert.hs @@ -724,7 +724,7 @@ which we don't want. cvtFld :: (TH.Name, TH.Exp) -> CvtM (LHsRecField RdrName (LHsExpr RdrName)) cvtFld (v,e) = do { v' <- vNameL v; e' <- cvtl e - ; return (noLoc $ HsRecField { hsRecFieldId = v' + ; return (noLoc $ HsRecField { hsRecFieldLbl = v' , hsRecFieldSel = hsRecFieldSelMissing -- AMG TODO , hsRecFieldArg = e' , hsRecPun = False}) } @@ -943,7 +943,7 @@ cvtp (ViewP e p) = do { e' <- cvtl e; p' <- cvtPat p cvtPatFld :: (TH.Name, TH.Pat) -> CvtM (LHsRecField RdrName (LPat RdrName)) cvtPatFld (s,p) = do { s' <- vNameL s; p' <- cvtPat p - ; return (noLoc $ HsRecField { hsRecFieldId = s' + ; return (noLoc $ HsRecField { hsRecFieldLbl = s' , hsRecFieldSel = hsRecFieldSelMissing -- AMG TODO , hsRecFieldArg = p' , hsRecPun = False}) } diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 3dfc354..70da3ad 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1242,21 +1242,12 @@ tcConArgs new_or_data (InfixCon bty1 bty2) tcConArgs new_or_data (RecCon fields) = mapM (tcConArg new_or_data) btys where --- <<<<<<< HEAD:compiler/typecheck/TcTyClsDecls.lhs - btys = map (cd_fld_type . unLoc) $ unLoc fields -{- --- AMG TODO -||||||| merged common ancestors - field_names = map (unLoc . cd_fld_name) fields - btys = map cd_fld_type fields -======= -- We need a one-to-one mapping from field_names to btys combined = map (\(L _ f) -> (cd_fld_names f,cd_fld_type f)) (unLoc fields) - explode (ns,ty) = zip (map unLoc ns) (repeat ty) + explode (ns,ty) = zip ns (repeat ty) exploded = concatMap explode combined - (field_names,btys) = unzip exploded ->>>>>>> origin/master:compiler/typecheck/TcTyClsDecls.hs --} + (_,btys) = unzip exploded + tcConArg :: NewOrData -> LHsType Name -> TcM (TcType, HsSrcBang) tcConArg new_or_data bty @@ -1936,10 +1927,10 @@ mkRecSelBind :: (TyCon, FieldLabel) -> (LSig Name, LHsBinds Name) mkRecSelBind (tycon, fl) = (L loc (IdSig sel_id), unitBag (L loc sel_bind)) where + loc = getSrcSpan sel_name + sel_id = mkExportedLocalId rec_details sel_name sel_ty lbl = flLabel fl sel_name = flSelector fl - loc = getSrcSpan sel_name - sel_id = mkExportedLocalId rec_details sel_name sel_ty rec_details = RecSelId { sel_tycon = tycon, sel_naughty = is_naughty } -- Find a representative constructor, con1 From git at git.haskell.org Fri Mar 27 15:46:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:06 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Handle missing case in pprExport (1f0dc01) Message-ID: <20150327154606.ACBD43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/1f0dc017284c759f22358855e56bed40d1762c6c/ghc >--------------------------------------------------------------- commit 1f0dc017284c759f22358855e56bed40d1762c6c Author: Adam Gundry Date: Fri Feb 20 13:49:31 2015 +0000 Handle missing case in pprExport >--------------------------------------------------------------- 1f0dc017284c759f22358855e56bed40d1762c6c compiler/iface/LoadIface.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/iface/LoadIface.hs b/compiler/iface/LoadIface.hs index f50fb0c..01f59f4 100644 --- a/compiler/iface/LoadIface.hs +++ b/compiler/iface/LoadIface.hs @@ -961,9 +961,9 @@ When printing export lists, we print like this: pprExport :: IfaceExport -> SDoc pprExport (Avail n) = ppr n pprExport (AvailTC _ [] []) = Outputable.empty -pprExport (AvailTC n (n':ns) fs) - | n==n' = ppr n <> pp_export ns fs - | otherwise = ppr n <> char '|' <> pp_export (n':ns) fs +pprExport (AvailTC n ns0 fs) = case ns0 of + (n':ns) | n==n' -> ppr n <> pp_export ns fs + _ -> ppr n <> char '|' <> pp_export ns0 fs where pp_export [] [] = Outputable.empty pp_export names fs = braces (hsep (map ppr names ++ map pprAvailField fs)) From git at git.haskell.org Fri Mar 27 15:46:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:09 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Prune testsuite for minimal OverloadedRecordFields implementation (fe22f12) Message-ID: <20150327154609.B75DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/fe22f1273c94d346720f1157da2e4b3b9010e90d/ghc >--------------------------------------------------------------- commit fe22f1273c94d346720f1157da2e4b3b9010e90d Author: Adam Gundry Date: Mon Feb 23 13:33:27 2015 +0000 Prune testsuite for minimal OverloadedRecordFields implementation >--------------------------------------------------------------- fe22f1273c94d346720f1157da2e4b3b9010e90d .../ghci/overloadedrecfldsghci01.script | 5 +- .../ghci/overloadedrecfldsghci01.stdout | 19 ++++++- .../should_fail/OverloadedRecFldsFail06_A.hs | 6 +- .../tests/overloadedrecflds/should_fail/all.T | 6 -- .../should_fail/overloadedrecfldsfail01.hs | 2 + .../should_fail/overloadedrecfldsfail01.stderr | 6 +- .../should_fail/overloadedrecfldsfail02.hs | 22 ++------ .../should_fail/overloadedrecfldsfail02.stderr | 54 ++---------------- .../should_fail/overloadedrecfldsfail03.hs | 3 + .../should_fail/overloadedrecfldsfail03.stderr | 6 +- .../should_fail/overloadedrecfldsfail04.hs | 3 + .../should_fail/overloadedrecfldsfail04.stderr | 10 +++- .../should_fail/overloadedrecfldsfail05.hs | 14 ++--- .../should_fail/overloadedrecfldsfail05.stderr | 12 ++-- .../should_fail/overloadedrecfldsfail06.hs | 11 +++- .../should_fail/overloadedrecfldsfail06.stderr | 5 +- .../should_fail/overloadedrecfldsfail07.hs | 11 ---- .../should_fail/overloadedrecfldsfail07.stderr | 6 -- .../should_fail/overloadedrecfldsfail08.hs | 13 ----- .../should_fail/overloadedrecfldsfail08.stderr | 47 --------------- .../should_fail/overloadedrecfldsfail09.hs | 9 --- .../should_fail/overloadedrecfldsfail09.stderr | 20 ------- .../should_fail/overloadedrecfldsfail10.hs | 11 ---- .../should_fail/overloadedrecfldsfail10.stderr | 9 --- .../should_run/OverloadedRecFldsRun01_A.hs | 9 --- .../should_run/OverloadedRecFldsRun07_A.hs | 11 ---- .../should_run/OverloadedRecFldsRun07_B.hs | 7 --- .../should_run/OverloadedRecFldsRun08_A.hs | 11 ---- .../should_run/OverloadedRecFldsRun08_B.hs | 7 --- .../should_run/OverloadedRecFldsRun08_C.hs | 7 --- .../should_run/OverloadedRecFldsRun11_A.hs | 9 --- .../should_run/OverloadedRecFldsRun11_A.hs-boot | 5 -- .../should_run/OverloadedRecFldsRun11_B.hs | 7 --- .../should_run/OverloadedRecFldsRun12_A.hs | 11 ---- .../should_run/OverloadedRecFldsRun12_B.hs | 7 --- testsuite/tests/overloadedrecflds/should_run/all.T | 18 ------ .../should_run/overloadedrecfldsrun01.hs | 66 ++++------------------ .../should_run/overloadedrecfldsrun01.stdout | 12 ---- .../should_run/overloadedrecfldsrun03.hs | 17 ++++-- .../should_run/overloadedrecfldsrun03.stdout | 2 - .../should_run/overloadedrecfldsrun04.hs | 5 +- .../should_run/overloadedrecfldsrun04.stdout | 3 +- .../should_run/overloadedrecfldsrun05.hs | 34 ----------- .../should_run/overloadedrecfldsrun05.stdout | 2 - .../should_run/overloadedrecfldsrun06.hs | 28 --------- .../should_run/overloadedrecfldsrun06.stdout | 1 - .../should_run/overloadedrecfldsrun07.hs | 7 --- .../should_run/overloadedrecfldsrun07.stdout | 3 - .../should_run/overloadedrecfldsrun08.hs | 7 --- .../should_run/overloadedrecfldsrun08.stdout | 2 - .../should_run/overloadedrecfldsrun09.hs | 8 --- .../should_run/overloadedrecfldsrun09.stdout | 2 - .../should_run/overloadedrecfldsrun10.hs | 12 ---- .../should_run/overloadedrecfldsrun10.stderr | 2 - .../should_run/overloadedrecfldsrun11.hs | 5 -- .../should_run/overloadedrecfldsrun11.stdout | 1 - .../should_run/overloadedrecfldsrun12.hs | 6 -- .../should_run/overloadedrecfldsrun12.stdout | 2 - .../should_run/overloadedrecfldsrun13.hs | 9 --- .../should_run/overloadedrecfldsrun13.stdout | 1 - 60 files changed, 107 insertions(+), 549 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fe22f1273c94d346720f1157da2e4b3b9010e90d From git at git.haskell.org Fri Mar 27 15:46:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:12 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Minor fixes (7c15c73) Message-ID: <20150327154612.C64883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/7c15c739ad9c6ede500192d6316df8463f91124e/ghc >--------------------------------------------------------------- commit 7c15c739ad9c6ede500192d6316df8463f91124e Author: Adam Gundry Date: Mon Feb 23 14:09:30 2015 +0000 Minor fixes >--------------------------------------------------------------- 7c15c739ad9c6ede500192d6316df8463f91124e compiler/typecheck/TcGenDeriv.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 5 ++--- 2 files changed, 3 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcGenDeriv.hs b/compiler/typecheck/TcGenDeriv.hs index 3764cab..366a9db 100644 --- a/compiler/typecheck/TcGenDeriv.hs +++ b/compiler/typecheck/TcGenDeriv.hs @@ -1357,7 +1357,7 @@ gen_Data_binds dflags loc rep_tc nlList labels, -- Field labels nlHsVar fixity] -- Fixity - labels = map (nlHsLit . HsString "AMG TODO" . flLabel) + labels = map (nlHsLit . mkHsString . unpackFS . flLabel) (dataConFieldLabels dc) dc_occ = getOccName dc is_infix = isDataSymOcc dc_occ diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 70da3ad..1c85505 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1164,11 +1164,10 @@ tcConDecl new_or_data rep_tycon tmpl_tvs res_tmpl -- Data types ; (ctxt, arg_tys, res_ty, field_lbls, stricts) <- tcHsTyVarBndrs hs_tvs $ \ _ -> do { ctxt <- tcHsContext hs_ctxt - ; details <- tcConArgs new_or_data hs_details + ; btys <- tcConArgs new_or_data hs_details ; res_ty <- tcConRes hs_res_ty ; field_lbls <- lookupConstructorFields (unLoc $ head names) -- AMG TODO ??? - ; let btys = details -- AMG TODO - (arg_tys, stricts) = unzip btys + ; let (arg_tys, stricts) = unzip btys ; return (ctxt, arg_tys, res_ty, field_lbls, stricts) } From git at git.haskell.org Fri Mar 27 15:46:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:15 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Use PlaceHolder for cd_fld_names (419d8c8) Message-ID: <20150327154616.007293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/419d8c878d1eb3b530054e447a6617e3fdfab62c/ghc >--------------------------------------------------------------- commit 419d8c878d1eb3b530054e447a6617e3fdfab62c Author: Adam Gundry Date: Mon Feb 23 14:22:50 2015 +0000 Use PlaceHolder for cd_fld_names >--------------------------------------------------------------- 419d8c878d1eb3b530054e447a6617e3fdfab62c compiler/deSugar/DsMeta.hs | 6 +++--- compiler/hsSyn/Convert.hs | 2 +- compiler/hsSyn/HsTypes.hs | 8 +------- compiler/hsSyn/HsUtils.hs | 27 +++++++++++++-------------- compiler/hsSyn/PlaceHolder.hs | 1 + compiler/parser/Parser.y | 2 +- compiler/rename/RnTypes.hs | 4 ++-- 7 files changed, 22 insertions(+), 28 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 419d8c878d1eb3b530054e447a6617e3fdfab62c From git at git.haskell.org Fri Mar 27 15:46:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:18 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Get rid of hsRecFieldSel landmine, the stupid way (282a23d) Message-ID: <20150327154618.EA55D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/282a23d250e349574067bdbb787027214a828d29/ghc >--------------------------------------------------------------- commit 282a23d250e349574067bdbb787027214a828d29 Author: Adam Gundry Date: Mon Feb 23 14:57:17 2015 +0000 Get rid of hsRecFieldSel landmine, the stupid way >--------------------------------------------------------------- 282a23d250e349574067bdbb787027214a828d29 compiler/hsSyn/Convert.hs | 4 ++-- compiler/hsSyn/HsPat.hs | 7 +++++-- 2 files changed, 7 insertions(+), 4 deletions(-) diff --git a/compiler/hsSyn/Convert.hs b/compiler/hsSyn/Convert.hs index 33a1165..6202703 100644 --- a/compiler/hsSyn/Convert.hs +++ b/compiler/hsSyn/Convert.hs @@ -725,7 +725,7 @@ cvtFld :: (TH.Name, TH.Exp) -> CvtM (LHsRecField RdrName (LHsExpr RdrName)) cvtFld (v,e) = do { v' <- vNameL v; e' <- cvtl e ; return (noLoc $ HsRecField { hsRecFieldLbl = v' - , hsRecFieldSel = hsRecFieldSelMissing -- AMG TODO + , hsRecFieldSel = hsRecFieldSelMissing , hsRecFieldArg = e' , hsRecPun = False}) } @@ -944,7 +944,7 @@ cvtPatFld :: (TH.Name, TH.Pat) -> CvtM (LHsRecField RdrName (LPat RdrName)) cvtPatFld (s,p) = do { s' <- vNameL s; p' <- cvtPat p ; return (noLoc $ HsRecField { hsRecFieldLbl = s' - , hsRecFieldSel = hsRecFieldSelMissing -- AMG TODO + , hsRecFieldSel = hsRecFieldSelMissing , hsRecFieldArg = p' , hsRecPun = False}) } diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs index e2baac1..2c72855 100644 --- a/compiler/hsSyn/HsPat.hs +++ b/compiler/hsSyn/HsPat.hs @@ -309,10 +309,13 @@ data HsRecField id arg = HsRecField { -- hsRecFieldSel = Right [(S, $sel:x:S), (T, $sel:x:T)] -- -- and the typechecker will determine that $sel:x:S is meant. - +-- +-- AMG TODO: it would be nice if we could enforce in the types that +-- ambiguous fields occur only in record updates, and only between the +-- renamer and the typechecker. hsRecFieldSelMissing :: Either id [(id, id)] -hsRecFieldSelMissing = error "hsRecFieldSelMissing" +hsRecFieldSelMissing = Right [] hsRecFields :: HsRecFields id arg -> [(FieldLabelString, Either id [(id, id)])] hsRecFields rbinds = map (toFld . unLoc) (rec_flds rbinds) From git at git.haskell.org Fri Mar 27 15:46:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:21 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Accept test output wibbles (bc988f8) Message-ID: <20150327154621.E9E293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/bc988f83bf83bd39dff8ebac18e575d36b80e319/ghc >--------------------------------------------------------------- commit bc988f83bf83bd39dff8ebac18e575d36b80e319 Author: Adam Gundry Date: Mon Feb 23 15:07:53 2015 +0000 Accept test output wibbles >--------------------------------------------------------------- bc988f83bf83bd39dff8ebac18e575d36b80e319 testsuite/tests/rename/should_fail/T5892a.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail102.stderr | 7 +++---- 2 files changed, 4 insertions(+), 5 deletions(-) diff --git a/testsuite/tests/rename/should_fail/T5892a.stderr b/testsuite/tests/rename/should_fail/T5892a.stderr index 5e9e4d3..f382cd3 100644 --- a/testsuite/tests/rename/should_fail/T5892a.stderr +++ b/testsuite/tests/rename/should_fail/T5892a.stderr @@ -1,6 +1,6 @@ T5892a.hs:12:8: Warning: - Fields of ?Node? not initialised: Data.Tree.subForest + Fields of ?Node? not initialised: subForest In the expression: Node {..} In the expression: let rootLabel = [] in Node {..} In an equation for ?foo?: diff --git a/testsuite/tests/typecheck/should_fail/tcfail102.stderr b/testsuite/tests/typecheck/should_fail/tcfail102.stderr index 495ddc0..6bd3750 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail102.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail102.stderr @@ -3,11 +3,10 @@ tcfail102.hs:1:14: Warning: -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language. tcfail102.hs:9:15: - Could not deduce (Integral (Ratio a)) - arising from a use of the record selector ?p? + Could not deduce (Integral (Ratio a)) arising from a use of ?p? from the context: Integral a - bound by the type signature for - f :: Integral a => P (Ratio a) -> P (Ratio a) + bound by the type signature for: + f :: Integral a => P (Ratio a) -> P (Ratio a) at tcfail102.hs:8:6-45 In the ?p? field of a record In the expression: x {p = p x} From git at git.haskell.org Fri Mar 27 15:46:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:24 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Update a comment (385b6fd) Message-ID: <20150327154624.E53D53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/385b6fd4aa8c6fd38a9dfc50da19d081d420a203/ghc >--------------------------------------------------------------- commit 385b6fd4aa8c6fd38a9dfc50da19d081d420a203 Author: Adam Gundry Date: Mon Feb 23 15:12:11 2015 +0000 Update a comment >--------------------------------------------------------------- 385b6fd4aa8c6fd38a9dfc50da19d081d420a203 compiler/hsSyn/HsTypes.hs | 18 ++++++++---------- 1 file changed, 8 insertions(+), 10 deletions(-) diff --git a/compiler/hsSyn/HsTypes.hs b/compiler/hsSyn/HsTypes.hs index 732cb30..3e3a41d 100644 --- a/compiler/hsSyn/HsTypes.hs +++ b/compiler/hsSyn/HsTypes.hs @@ -516,7 +516,7 @@ type LConDeclField name = Located (ConDeclField name) -- For details on above see note [Api annotations] in ApiAnnotation data ConDeclField name -- Record fields have Haddoc docs on them = ConDeclField { cd_fld_names :: [(Located RdrName, PostRn name Name)], - -- ^ See Note [ConDeclField selector] + -- ^ See Note [ConDeclField names] cd_fld_type :: LBangType name, cd_fld_doc :: Maybe LHsDocString } -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon' @@ -526,15 +526,13 @@ data ConDeclField name -- Record fields have Haddoc docs on them deriving instance (DataId name) => Data (ConDeclField name) {- -AMG TODO update note +Note [ConDeclField names] +~~~~~~~~~~~~~~~~~~~~~~~~~ -Note [ConDeclField selector] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~ - -A ConDeclField always contains the field label as the user wrote it in -cd_fld_lbl. After the renamer, it will additionally contain the Name -of the selector function in cd_fld_sel. (Before the renamer, -cd_fld_sel contains an error thunk.) +A ConDeclField contains a list of field names: these always include +the field label as the user wrote it in the first component of the +pair. After the renamer, it will additionally contain the Name of the +selector function in the second component. Due to OverloadedRecordFields, the OccName of the selector function may have been mangled, which is why we keep the original field label @@ -544,7 +542,7 @@ separately. For example, when OverloadedRecordFields is enabled gives - ConDeclField { cd_fld_lbl = "x", cd_fld_sel = $sel:x:T, ... }. + ConDeclField { cd_fld_names = [("x", $sel:x:T)], ... }. -} ----------------------- From git at git.haskell.org Fri Mar 27 15:46:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:27 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Clean up hsGroupBinders and friends (924cbec) Message-ID: <20150327154627.E9F663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/924cbec63013228a8b2835131767259cab535d8e/ghc >--------------------------------------------------------------- commit 924cbec63013228a8b2835131767259cab535d8e Author: Adam Gundry Date: Mon Feb 23 15:32:08 2015 +0000 Clean up hsGroupBinders and friends >--------------------------------------------------------------- 924cbec63013228a8b2835131767259cab535d8e compiler/deSugar/DsMeta.hs | 2 +- compiler/hsSyn/HsUtils.hs | 63 ++++++++++----------------------------------- compiler/rename/RnSource.hs | 2 +- 3 files changed, 15 insertions(+), 52 deletions(-) diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs index a21b196..b6ea0fe 100644 --- a/compiler/deSugar/DsMeta.hs +++ b/compiler/deSugar/DsMeta.hs @@ -127,7 +127,7 @@ repTopDs group@(HsGroup { hs_valds = valds , hs_vects = vects , hs_docs = docs }) = do { let { tv_bndrs = hsSigTvBinders valds - ; bndrs = tv_bndrs ++ fst (hsGroupBinders group) } ; + ; bndrs = tv_bndrs ++ hsGroupBinders group } ; ss <- mkGenSyms bndrs ; -- Bind all the names mainly to avoid repeated use of explicit strings. diff --git a/compiler/hsSyn/HsUtils.hs b/compiler/hsSyn/HsUtils.hs index 5dba62a..2580844 100644 --- a/compiler/hsSyn/HsUtils.hs +++ b/compiler/hsSyn/HsUtils.hs @@ -740,39 +740,22 @@ variables bound by the lazy pattern are n,m, *not* the dictionary d. So in mkSelectorBinds in DsUtils, we want just m,n as the variables bound. -} --- AMG TODO: what's going on with all these? - -hsGroupBinders :: HsGroup Name -> ([Name], [(RdrName, Name, Name)]) +hsGroupBinders :: HsGroup Name -> [Name] hsGroupBinders (HsGroup { hs_valds = val_decls, hs_tyclds = tycl_decls, hs_instds = inst_decls, hs_fords = foreign_decls }) --- Collect the binders of a Group - = (collectHsValBinders val_decls, []) - `mappend` hsTyClForeignBinders tycl_decls inst_decls foreign_decls + = collectHsValBinders val_decls + ++ hsTyClForeignBinders tycl_decls inst_decls foreign_decls --- <<<<<<< HEAD:compiler/hsSyn/HsUtils.lhs hsTyClForeignBinders :: [TyClGroup Name] -> [LInstDecl Name] - -> [LForeignDecl Name] -> ([Name], [(RdrName, Name, Name)]) + -> [LForeignDecl Name] -> [Name] -- We need to look at instance declarations too, -- because their associated types may bind data constructors hsTyClForeignBinders tycl_decls inst_decls foreign_decls - = unLocs ((hsForeignDeclsBinders foreign_decls, []) `mappend` - foldMap (foldMap hsLTyClDeclBinders . group_tyclds) tycl_decls `mappend` - foldMap hsLInstDeclBinders inst_decls) - where unLocs (xs, ys) = (map unLoc xs, map (\ (x, y, z) -> (unLoc x, y, unLoc z)) ys) --- ||||||| merged common ancestors --- hsTyClDeclsBinders :: [TyClGroup Name] -> [Located (InstDecl Name)] -> [Name] --- hsTyClDeclsBinders tycl_decls inst_decls --- = map unLoc (concatMap (concatMap hsLTyClDeclBinders . group_tyclds) tycl_decls ++ --- concatMap (hsInstDeclBinders . unLoc) inst_decls) --- ======= --- hsTyClForeignBinders :: [TyClGroup Name] -> [LInstDecl Name] --- -> [LForeignDecl Name] -> [Name] --- hsTyClForeignBinders tycl_decls inst_decls foreign_decls --- = map unLoc $ --- hsForeignDeclsBinders foreign_decls ++ --- concatMap (concatMap hsLTyClDeclBinders . group_tyclds) tycl_decls ++ --- concatMap hsLInstDeclBinders inst_decls --- >>>>>>> origin/master:compiler/hsSyn/HsUtils.hs + = map unLoc (hsForeignDeclsBinders foreign_decls) + ++ getSelectorNames (foldMap (foldMap hsLTyClDeclBinders . group_tyclds) tycl_decls + `mappend` foldMap hsLInstDeclBinders inst_decls) + where + getSelectorNames (ns, fs) = map unLoc ns ++ map (\ (_, x, _) -> x) fs ------------------- hsLTyClDeclBinders :: Located (TyClDecl name) -> @@ -862,36 +845,16 @@ hsConDeclsBinders cons = go id cons case r of -- remove only the first occurrence of any seen field in order to -- avoid circumventing detection of duplicate fields (#9156) --- <<<<<<< HEAD:compiler/hsSyn/HsUtils.lhs - L loc (ConDecl { con_names = names , con_details = RecCon flds }) -> + L loc (ConDecl { con_names = names, con_details = RecCon flds }) -> (map (L loc . unLoc) names ++ ns, r' ++ fs) - where r' = remSeen (concatMap (cd_fld_names . unLoc) (unLoc flds)) - -- AMG TODO what on earth happens here - -- cd_fld_lflds cdfld = (cd_fld_lbl x, cd_fld_sel x) + where r' = remSeen (concatMap (cd_fld_names . unLoc) + (unLoc flds)) remSeen' = foldr (.) remSeen [deleteBy ((==) `on` unLoc . fst) v | v <- r'] (ns, fs) = go remSeen' rs L loc (ConDecl { con_names = names }) -> - (map (L loc . unLoc) names ++ ns, fs) + (map (L loc . unLoc) names ++ ns, fs) where (ns, fs) = go remSeen rs --- ||||||| merged common ancestors --- L loc (ConDecl { con_name = L _ name , con_details = RecCon flds }) -> --- (L loc name) : r' ++ go remSeen' rs --- where r' = remSeen (map cd_fld_name flds) --- remSeen' = foldr (.) remSeen [deleteBy ((==) `on` unLoc) v | v <- r'] --- L loc (ConDecl { con_name = L _ name }) -> --- (L loc name) : go remSeen rs --- ======= --- L loc (ConDecl { con_names = names, con_details = RecCon flds }) -> --- (map (L loc . unLoc) names) ++ r' ++ go remSeen' rs --- where r' = remSeen (concatMap (cd_fld_names . unLoc) --- (unLoc flds)) --- remSeen' = foldr (.) remSeen [deleteBy ((==) `on` unLoc) v | v <- r'] --- L loc (ConDecl { con_names = names }) -> --- (map (L loc . unLoc) names) ++ go remSeen rs - --- >>>>>>> origin/master:compiler/hsSyn/HsUtils.hs - withTyCon :: name' -> (a, [(r, name)]) -> (a, [(r, name, name')]) withTyCon tycon_name (xs, ys) = (xs, map (\ (r, n) -> (r, n, tycon_name)) ys) diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index c02823d..356f799 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -205,7 +205,7 @@ rnSrcDecls extra_deps group0@(HsGroup { hs_valds = val_decls, hs_docs = rn_docs } ; tcf_bndrs = hsTyClForeignBinders rn_tycl_decls rn_inst_decls rn_foreign_decls ; - other_def = (Just (mkNameSet $ fst tcf_bndrs), emptyNameSet) ; -- AMG TODO tcf_bndrs? + other_def = (Just (mkNameSet tcf_bndrs), emptyNameSet) ; other_fvs = plusFVs [src_fvs1, src_fvs2, src_fvs3, src_fvs4, src_fvs5, src_fvs6, src_fvs7, src_fvs8, src_fvs9] ; From git at git.haskell.org Fri Mar 27 15:46:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:30 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Clean up RnNames (13168ff) Message-ID: <20150327154630.E2C5F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/13168ff78c3b6af3cf1d9f6c891ecf8c2ef61f0b/ghc >--------------------------------------------------------------- commit 13168ff78c3b6af3cf1d9f6c891ecf8c2ef61f0b Author: Adam Gundry Date: Mon Feb 23 15:58:58 2015 +0000 Clean up RnNames >--------------------------------------------------------------- 13168ff78c3b6af3cf1d9f6c891ecf8c2ef61f0b compiler/rename/RnNames.hs | 59 +++++++--------------------------------------- 1 file changed, 8 insertions(+), 51 deletions(-) diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs index 4956a8e..ade177e 100644 --- a/compiler/rename/RnNames.hs +++ b/compiler/rename/RnNames.hs @@ -1021,14 +1021,7 @@ mkChildEnv gres = foldr add emptyNameEnv gres findChildren :: NameEnv [ChildName] -> Name -> [ChildName] findChildren env n = lookupNameEnv env n `orElse` [] --- AMG TODO --- <<<<<<< HEAD:compiler/rename/RnNames.lhs lookupChildren :: [ChildName] -> [Located RdrName] -> [Maybe (Located ChildName)] --- ||||||| merged common ancestors --- lookupChildren :: [Name] -> [RdrName] -> [Maybe Name] --- ======= --- lookupChildren :: [Name] -> [Located RdrName] -> [Maybe (Located Name)] --- >>>>>>> origin/master:compiler/rename/RnNames.hs -- (lookupChildren all_kids rdr_items) maps each rdr_item to its -- corresponding Name all_kids, if the former exists -- The matching is done by FastString, not OccName, so that @@ -1044,31 +1037,8 @@ lookupChildren all_kids rdr_items Just n -> Just (L l n) Nothing -> Nothing --- kid_env = mkFsEnv [(occNameFS (nameOccName n), n) | n <- all_kids] - - kid_env = extendFsEnvList_C plusChildName emptyFsEnv - [(occNameFS (childOccName n), n) | n <- all_kids] - - plusChildName (OverloadedFldChild lbl xs) (OverloadedFldChild _ ys) - = OverloadedFldChild lbl (xs ++ ys) - plusChildName (OverloadedFldChild lbl xs) (FldChild n) - = OverloadedFldChild lbl (n:xs) - plusChildName (FldChild n) (OverloadedFldChild lbl xs) - = OverloadedFldChild lbl (n:xs) - plusChildName (FldChild m) (FldChild n) - = OverloadedFldChild (occNameFS (nameOccName m)) [m, n] - plusChildName _ y = y -- This can happen if we have both - -- Example{tc} and Example{d} in all_kids; - -- take the second because it will be the - -- data constructor (AvailTC invariant) - - -{- - -- AMG TODO figure out - where -<<<<<<< HEAD:compiler/rename/RnNames.lhs kid_env = extendFsEnvList_C plusChildName emptyFsEnv - [(occNameFS (childOccName n), n) | n <- all_kids] + [(occNameFS (childOccName n), n) | n <- all_kids] plusChildName (OverloadedFldChild lbl xs) (OverloadedFldChild _ ys) = OverloadedFldChild lbl (xs ++ ys) @@ -1083,16 +1053,6 @@ lookupChildren all_kids rdr_items -- take the second because it will be the -- data constructor (AvailTC invariant) -||||||| merged common ancestors - kid_env = mkFsEnv [(occNameFS (nameOccName n), n) | n <- all_kids] -======= - doOne (L l r) = case (lookupFsEnv kid_env . occNameFS . rdrNameOcc) r of - Just n -> Just (L l n) - Nothing -> Nothing - - kid_env = mkFsEnv [(occNameFS (nameOccName n), n) | n <- all_kids] ->>>>>>> origin/master:compiler/rename/RnNames.hs --} childrenNamesFlds :: [Located ChildName] -> ([Located Name], AvailFields) childrenNamesFlds xs = mconcat (map bisect xs) @@ -1344,14 +1304,12 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod (sub_rdrs ++ map noLoc (availFieldsRdrNames sub_flds)) if any isNothing mb_names then do addErr (exportItemErr ie) - -- AMG TODO sort out this bit - return ( IEThingWith (L l name) [] [] - , AvailTC name [name] []) - else do let kids = catMaybes mb_names - (names, flds) = childrenNamesFlds kids - addUsedKids rdr $ map unLoc kids - return ( IEThingWith (L l name) names flds - , AvailTC name (name:map unLoc names) flds) + return (IEThingWith (L l name) [] [], AvailTC name [name] []) + else do let names = catMaybes mb_names + (non_flds, flds) = childrenNamesFlds names + addUsedKids rdr (map unLoc names) + return ( IEThingWith (L l name) non_flds flds + , AvailTC name (name:map unLoc non_flds) flds) lookup_ie _ = panic "lookup_ie" -- Other cases covered earlier @@ -1809,8 +1767,7 @@ printMinimalImports imports_w_usage (map noLoc (filter (/= n) ns)) fs] -- Note [Overloaded field import] - -- AMG TODO review - _other | all_non_overloaded fs -> map IEVar (map noLoc $ ns ++ availFieldsNames fs) + _other | all_non_overloaded fs -> map (IEVar . noLoc) $ ns ++ availFieldsNames fs | otherwise -> [IEThingWith (noLoc n) (map noLoc (filter (/= n) ns)) fs] where fld_lbls = availFieldsLabels fs From git at git.haskell.org Fri Mar 27 15:46:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:34 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Simplify rnField to take [FieldLabel] instead of looking it up from constructor Name (454b0f7) Message-ID: <20150327154634.117173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/454b0f7c4d29727bd8da4e460f11040212d42e37/ghc >--------------------------------------------------------------- commit 454b0f7c4d29727bd8da4e460f11040212d42e37 Author: Adam Gundry Date: Mon Feb 23 16:17:10 2015 +0000 Simplify rnField to take [FieldLabel] instead of looking it up from constructor Name >--------------------------------------------------------------- 454b0f7c4d29727bd8da4e460f11040212d42e37 compiler/rename/RnSource.hs | 5 +++-- compiler/rename/RnTypes.hs | 23 +++++++++++------------ compiler/typecheck/TcTyClsDecls.hs | 2 +- 3 files changed, 15 insertions(+), 15 deletions(-) diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index 356f799..330062b 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -1401,7 +1401,7 @@ rnConDecl decl@(ConDecl { con_names = names, con_qvars = tvs ; bindHsTyVars doc Nothing free_kvs new_tvs $ \new_tyvars -> do { (new_context, fvs1) <- rnContext doc lcxt - ; (new_details, fvs2) <- rnConDeclDetails (unLoc $ head new_names) doc details -- AMG TODO ? + ; (new_details, fvs2) <- rnConDeclDetails (unLoc $ head new_names) doc details ; (new_details', new_res_ty, fvs3) <- rnConResult doc (map unLoc new_names) new_details res_ty ; return (decl { con_names = new_names, con_qvars = new_tyvars @@ -1450,7 +1450,8 @@ rnConDeclDetails _ doc (InfixCon ty1 ty2) ; return (InfixCon new_ty1 new_ty2, fvs1 `plusFV` fvs2) } rnConDeclDetails con doc (RecCon (L l fields)) - = do { (new_fields, fvs) <- rnConDeclFields con doc fields + = do { fls <- lookupConstructorFields con + ; (new_fields, fvs) <- rnConDeclFields fls doc fields -- No need to check for duplicate fields -- since that is done by RnNames.extendGlobalRdrEnvRn ; return (RecCon (L l new_fields), fvs) } diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs index 29528f2..e62f74f 100644 --- a/compiler/rename/RnTypes.hs +++ b/compiler/rename/RnTypes.hs @@ -215,8 +215,7 @@ rnHsTyKi isType doc (HsBangTy b ty) rnHsTyKi _ doc ty@(HsRecTy flds) = do { addErr (hang (ptext (sLit "Record syntax is illegal here:")) 2 (ppr ty)) - ; let bogus_con = mkUnboundName (mkRdrUnqual (mkTcOcc "bogus_con")) - ; (flds', fvs) <- rnConDeclFields bogus_con doc flds + ; (flds', fvs) <- rnConDeclFields [] doc flds ; return (HsRecTy flds', fvs) } rnHsTyKi isType doc (HsFunTy ty1 ty2) @@ -515,23 +514,23 @@ dataKindsErr is_type thing ********************************************************* -} -rnConDeclFields :: Name -> HsDocContext -> [LConDeclField RdrName] +rnConDeclFields :: [FieldLabel] -> HsDocContext -> [LConDeclField RdrName] -> RnM ([LConDeclField Name], FreeVars) -rnConDeclFields con doc fields = mapFvRn (rnField con doc) fields +rnConDeclFields fls doc fields = mapFvRn (rnField fls doc) fields -rnField :: Name -> HsDocContext -> LConDeclField RdrName +rnField :: [FieldLabel] -> HsDocContext -> LConDeclField RdrName -> RnM (LConDeclField Name, FreeVars) -rnField con doc (L l (ConDeclField names ty haddock_doc)) - = do { new_names <- mapM help names +rnField fls doc (L l (ConDeclField names ty haddock_doc)) + = do { let new_names = map lookupField names ; (new_ty, fvs) <- rnLHsType doc ty ; new_haddock_doc <- rnMbLHsDoc haddock_doc ; return (L l (ConDeclField new_names new_ty new_haddock_doc), fvs) } where - help :: (Located RdrName, PlaceHolder) -> RnM (Located RdrName, Name) - help (l_rdr_name, _) = do { flds <- lookupConstructorFields con - ; let lbl = occNameFS $ rdrNameOcc $ unLoc l_rdr_name - ; let fl = expectJust "rnField" $ find ((== lbl) . flLabel) flds - ; return (l_rdr_name, flSelector fl) } + lookupField :: (Located RdrName, PlaceHolder) -> (Located RdrName, Name) + lookupField (l_rdr_name, _) = (l_rdr_name, flSelector fl) + where + lbl = occNameFS $ rdrNameOcc $ unLoc l_rdr_name + fl = expectJust "rnField" $ find ((== lbl) . flLabel) fls rnContext :: HsDocContext -> LHsContext RdrName -> RnM (LHsContext Name, FreeVars) rnContext doc (L loc cxt) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 1c85505..de83432 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1166,7 +1166,7 @@ tcConDecl new_or_data rep_tycon tmpl_tvs res_tmpl -- Data types do { ctxt <- tcHsContext hs_ctxt ; btys <- tcConArgs new_or_data hs_details ; res_ty <- tcConRes hs_res_ty - ; field_lbls <- lookupConstructorFields (unLoc $ head names) -- AMG TODO ??? + ; field_lbls <- lookupConstructorFields (unLoc $ head names) ; let (arg_tys, stricts) = unzip btys ; return (ctxt, arg_tys, res_ty, field_lbls, stricts) } From git at git.haskell.org Fri Mar 27 15:46:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:37 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: lookupOccRn_overloaded need not return FieldLabelString (8791b7e) Message-ID: <20150327154637.259F93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/8791b7e741a5711178fe55fac0e7c9889e6bcecd/ghc >--------------------------------------------------------------- commit 8791b7e741a5711178fe55fac0e7c9889e6bcecd Author: Adam Gundry Date: Mon Feb 23 16:29:46 2015 +0000 lookupOccRn_overloaded need not return FieldLabelString >--------------------------------------------------------------- 8791b7e741a5711178fe55fac0e7c9889e6bcecd compiler/rename/RnEnv.hs | 31 ++++++++++++++----------------- compiler/rename/RnPat.hs | 3 +-- 2 files changed, 15 insertions(+), 19 deletions(-) diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs index e927ff7..b505a28 100644 --- a/compiler/rename/RnEnv.hs +++ b/compiler/rename/RnEnv.hs @@ -826,12 +826,12 @@ lookupGlobalOccRn_maybe rdr_name -- The following are possible results of lookupOccRn_overloaded: --- Nothing -> name not in scope (no error reported) --- Just (Left x) -> name uniquely refers to x, or there is a name clash (reported) --- Just (Right (l, xs)) -> ambiguous between the fields xs with label l; --- fields are represented as (parent, selector) pairs +-- Nothing -> name not in scope (no error reported) +-- Just (Left x) -> name uniquely refers to x, or there is a name clash (reported) +-- Just (Right xs) -> ambiguous between the fields xs; +-- fields are represented as (parent, selector) pairs -lookupOccRn_overloaded :: RdrName -> RnM (Maybe (Either Name (FieldLabelString, [(Name, Name)]))) +lookupOccRn_overloaded :: RdrName -> RnM (Maybe (Either Name [(Name, Name)])) lookupOccRn_overloaded rdr_name = do { local_env <- getLocalRdrEnv ; case lookupLocalRdrEnv local_env rdr_name of { @@ -846,7 +846,7 @@ lookupOccRn_overloaded rdr_name -- and only happens for failed lookups ; lookupQualifiedNameGHCi_overloaded dflags is_ghci rdr_name } } } } } -lookupGlobalOccRn_overloaded :: RdrName -> RnM (Maybe (Either Name (FieldLabelString, [(Name, Name)]))) +lookupGlobalOccRn_overloaded :: RdrName -> RnM (Maybe (Either Name [(Name, Name)])) lookupGlobalOccRn_overloaded rdr_name | Just n <- isExact_maybe rdr_name -- This happens in derived code = do { n' <- lookupExactOcc n; return (Just (Left n')) } @@ -860,14 +860,11 @@ lookupGlobalOccRn_overloaded rdr_name ; overload_ok <- xoptM Opt_OverloadedRecordFields ; case lookupGRE_RdrName rdr_name env of [] -> return Nothing - [gre] | Just lbl <- greLabel gre - -> do { addUsedRdrName True gre rdr_name - ; return (Just (Right (lbl, [greBits gre]))) } [gre] -> do { addUsedRdrName True gre rdr_name ; return (Just (Left (gre_name gre))) } gres | all isRecFldGRE gres && overload_ok -> do { mapM_ (\ gre -> addUsedRdrName True gre rdr_name) gres - ; return (Just (Right (expectJust "greLabel" (greLabel (head gres)), map greBits gres))) } + ; return (Just (Right (map greBits gres))) } gres -> do { addNameClashErrRn rdr_name gres ; return (Just (Left (gre_name (head gres)))) } } where @@ -1081,7 +1078,7 @@ lookupQualifiedNameGHCi rdr_name -- should never be overloaded, so when we check for overloaded field -- matches, generate name clash errors if we find more than one. lookupQualifiedNameGHCi_overloaded :: DynFlags -> Bool -> RdrName - -> RnM (Maybe (Either Name (FieldLabelString, [(Name, Name)]))) + -> RnM (Maybe (Either Name [(Name, Name)])) lookupQualifiedNameGHCi_overloaded dflags is_ghci rdr_name | Just (mod,occ) <- isQual_maybe rdr_name , is_ghci @@ -1099,14 +1096,14 @@ lookupQualifiedNameGHCi_overloaded dflags is_ghci rdr_name , nameOccName name == occ ] -> ASSERT(null ns) return (Just (Left n)) - | xs@((p, lbl, sel):ys) <- [ (availName avail, lbl, sel) - | iface <- ifaces - , avail <- mi_exports iface - , (lbl, sel) <- availOverloadedFlds avail - , lbl == occNameFS occ ] + | xs@((p, _, sel):ys) <- [ (availName avail, lbl, sel) + | iface <- ifaces + , avail <- mi_exports iface + , (lbl, sel) <- availOverloadedFlds avail + , lbl == occNameFS occ ] -> do { when (not (null ys)) $ addNameClashErrRn rdr_name (map (toFakeGRE mod) xs) - ; return (Just (Right (lbl, [(p, sel)]))) } + ; return (Just (Right [(p, sel)])) } _ -> -- Either we couldn't load the interface, or -- we could but we didn't find the name in it diff --git a/compiler/rename/RnPat.hs b/compiler/rename/RnPat.hs index afd0d24..1249154 100644 --- a/compiler/rename/RnPat.hs +++ b/compiler/rename/RnPat.hs @@ -571,8 +571,7 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot }) ; case mb of Nothing -> do { addErr (unknownSubordinateErr doc lbl) ; return (Right []) } - Just (Left sel) -> return (Left sel) - Just (Right (_, xs)) -> return (Right xs) } + Just r -> return r } _ -> fmap Left $ lookupSubBndrOcc True parent doc lbl ; arg' <- if pun then do { checkErr pun_ok (badPun (L loc lbl)) From git at git.haskell.org Fri Mar 27 15:46:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:40 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Make pprIfaceConDecl play nicely with overloaded record field labels (545fffe) Message-ID: <20150327154640.3FFE43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/545fffe407bae0b4f38408229d0aa48b9265e579/ghc >--------------------------------------------------------------- commit 545fffe407bae0b4f38408229d0aa48b9265e579 Author: Adam Gundry Date: Mon Feb 23 17:03:42 2015 +0000 Make pprIfaceConDecl play nicely with overloaded record field labels >--------------------------------------------------------------- 545fffe407bae0b4f38408229d0aa48b9265e579 compiler/iface/IfaceSyn.hs | 25 ++++++++++++++++++---- .../ghci/overloadedrecfldsghci01.stdout | 4 ++-- 2 files changed, 23 insertions(+), 6 deletions(-) diff --git a/compiler/iface/IfaceSyn.hs b/compiler/iface/IfaceSyn.hs index 0b36c02..db54a18 100644 --- a/compiler/iface/IfaceSyn.hs +++ b/compiler/iface/IfaceSyn.hs @@ -61,6 +61,7 @@ import InstEnv import Control.Monad import System.IO.Unsafe +import Data.List (find) import Data.Maybe (isJust) infixl 3 &&& @@ -327,6 +328,15 @@ visibleIfConDecls IfDataFamTyCon = [] visibleIfConDecls (IfDataTyCon cs _ _) = cs visibleIfConDecls (IfNewTyCon c _ _) = [c] +ifaceConDeclFields :: OccName -> IfaceConDecls -> [FieldLbl OccName] +ifaceConDeclFields tc x = map (\ lbl -> mkFieldLabelOccs lbl tc is_overloaded) lbls + where + (is_overloaded, lbls) = case x of + IfAbstractTyCon {} -> (False, []) + IfDataFamTyCon {} -> (False, []) + IfDataTyCon _ is_o labels -> (is_o, labels) + IfNewTyCon _ is_o labels -> (is_o, labels) + ifaceDeclImplicitBndrs :: IfaceDecl -> [OccName] -- *Excludes* the 'main' name, but *includes* the implicitly-bound names -- Deeply revolting, because it has to predict what gets bound, @@ -617,8 +627,9 @@ pprIfaceDecl ss (IfaceData { ifName = tycon, ifCType = ctype, ok_con dc = showSub ss dc || any (showSub ss) (ifConFields dc) show_con dc - | ok_con dc = Just $ pprIfaceConDecl ss gadt_style mk_user_con_res_ty dc + | ok_con dc = Just $ pprIfaceConDecl ss gadt_style mk_user_con_res_ty fls dc | otherwise = Nothing + fls = ifaceConDeclFields tycon condecls mk_user_con_res_ty :: IfaceEqSpec -> ([IfaceTvBndr], SDoc) -- See Note [Result type of a data family GADT] @@ -794,8 +805,9 @@ isVanillaIfaceConDecl (IfCon { ifConExTvs = ex_tvs pprIfaceConDecl :: ShowSub -> Bool -> (IfaceEqSpec -> ([IfaceTvBndr], SDoc)) + -> [FieldLbl OccName] -> IfaceConDecl -> SDoc -pprIfaceConDecl ss gadt_style mk_user_con_res_ty +pprIfaceConDecl ss gadt_style mk_user_con_res_ty fls (IfCon { ifConOcc = name, ifConInfix = is_infix, ifConExTvs = ex_tvs, ifConEqSpec = eq_spec, ifConCtxt = ctxt, ifConArgTys = arg_tys, @@ -825,9 +837,14 @@ pprIfaceConDecl ss gadt_style mk_user_con_res_ty pprParendBangTy (bang, ty) = ppr_bang bang <> pprParendIfaceType ty pprBangTy (bang, ty) = ppr_bang bang <> ppr ty - maybe_show_label (lbl,bty) - | showSub ss lbl = Just (pprPrefixIfDeclBndr ss lbl <+> dcolon <+> pprBangTy bty) + maybe_show_label (sel,bty) + | showSub ss sel = Just (pprPrefixIfDeclBndr ss lbl <+> dcolon <+> pprBangTy bty) | otherwise = Nothing + where + -- IfaceConDecl contains the name of the selector function, so + -- we have to look up the field label (in case + -- OverloadedRecordFields was used for the definition) + lbl = maybe sel (mkVarOccFS . flLabel) $ find (\ fl -> flSelector fl == sel) fls ppr_fields [ty1, ty2] | is_infix && null labels diff --git a/testsuite/tests/overloadedrecflds/ghci/overloadedrecfldsghci01.stdout b/testsuite/tests/overloadedrecflds/ghci/overloadedrecfldsghci01.stdout index 5f16394..c05aa5b 100644 --- a/testsuite/tests/overloadedrecflds/ghci/overloadedrecfldsghci01.stdout +++ b/testsuite/tests/overloadedrecflds/ghci/overloadedrecfldsghci01.stdout @@ -1,8 +1,8 @@ True -data T a = MkT {foo :: Bool, ...} +data T a = MkT {Ghci2.foo :: Bool, ...} -- Defined at :4:18 -data S = MkS {foo :: Int} -- Defined at :3:16 +data S = MkS {Ghci1.foo :: Int} -- Defined at :3:16 :1:1: Ambiguous occurrence ?foo? From git at git.haskell.org Fri Mar 27 15:46:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:43 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Defuse dfid_rep_tycon landmine, albeit in a stupid way for now (8535533) Message-ID: <20150327154643.45F893A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/85355339c58de42e81de3e1a7f0a3d217d1dbd4c/ghc >--------------------------------------------------------------- commit 85355339c58de42e81de3e1a7f0a3d217d1dbd4c Author: Adam Gundry Date: Mon Mar 2 10:58:29 2015 +0000 Defuse dfid_rep_tycon landmine, albeit in a stupid way for now >--------------------------------------------------------------- 85355339c58de42e81de3e1a7f0a3d217d1dbd4c compiler/hsSyn/HsDecls.hs | 8 ++++---- compiler/rename/RnNames.hs | 3 ++- compiler/rename/RnSource.hs | 9 +++++---- compiler/typecheck/TcInstDcls.hs | 5 +++-- 4 files changed, 14 insertions(+), 11 deletions(-) diff --git a/compiler/hsSyn/HsDecls.hs b/compiler/hsSyn/HsDecls.hs index 009b1ca..b203ef2 100644 --- a/compiler/hsSyn/HsDecls.hs +++ b/compiler/hsSyn/HsDecls.hs @@ -1085,7 +1085,7 @@ type LDataFamInstDecl name = Located (DataFamInstDecl name) data DataFamInstDecl name = DataFamInstDecl { dfid_tycon :: Located name - , dfid_rep_tycon :: name -- See Note [Assigning names to instance declarations] in RnSource + , dfid_rep_tycon :: Maybe name -- See Note [Assigning names to instance declarations] in RnSource , dfid_pats :: HsTyPats name -- LHS , dfid_defn :: HsDataDefn name -- RHS , dfid_fvs :: PostRn name NameSet } -- Free vars for dependency analysis @@ -1099,9 +1099,9 @@ data DataFamInstDecl name deriving( Typeable ) deriving instance (DataId name) => Data (DataFamInstDecl name) -placeHolderRepTyCon :: name -- AMG TODO --- Used for dfid_rep_tycon in DataFamInstDecl prior to the renamer -placeHolderRepTyCon = panic "placeHolderRepTyCon" +-- | Used for dfid_rep_tycon in DataFamInstDecl prior to the renamer +placeHolderRepTyCon :: Maybe name +placeHolderRepTyCon = Nothing ----------------- Class instances ------------- diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs index ade177e..b42d4bd 100644 --- a/compiler/rename/RnNames.hs +++ b/compiler/rename/RnNames.hs @@ -626,7 +626,8 @@ getLocalNonValBinders fixity_env = do { main_name <- lookupFamInstName mb_cls (dfid_tycon ti_decl) ; let (bndrs, flds) = hsDataFamInstBinders ti_decl ; sub_names <- mapM newTopSrcBinder bndrs - ; flds' <- mapM (new_rec_sel overload_ok (rdrNameOcc (dfid_rep_tycon ti_decl)) . fstOf3) flds + ; let rep_tycon = expectJust "getLocalNonValBinders/new_di" $ dfid_rep_tycon ti_decl + ; flds' <- mapM (new_rec_sel overload_ok (rdrNameOcc rep_tycon) . fstOf3) flds ; let avail = AvailTC (unLoc main_name) sub_names (fieldLabelsToAvailFields flds') -- main_name is not bound here! diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index 330062b..46b3eda 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -53,7 +53,7 @@ import Data.List( partition, sortBy ) #if __GLASGOW_HASKELL__ < 709 import Data.Traversable (traverse) #endif -import Maybes( orElse, mapMaybe ) +import Maybes( orElse, mapMaybe, expectJust ) {- @rnSourceDecl@ `renames' declarations. @@ -276,7 +276,7 @@ assignNamesClsInstDecl cid = do assignNamesDataFamInstDecl :: DataFamInstDecl RdrName -> State OccSet (DataFamInstDecl RdrName) assignNamesDataFamInstDecl dfid = do occ <- assignOccName (mkInstTyTcOcc info_string) - return dfid { dfid_rep_tycon = mkRdrUnqual occ } + return dfid { dfid_rep_tycon = Just $ mkRdrUnqual occ } where info_string = occNameString (rdrNameOcc $ unLoc $ dfid_tycon dfid) ++ concatMap (getDFunHsTypeKey . unLoc) (hswb_cts (dfid_pats dfid)) @@ -669,15 +669,16 @@ rnDataFamInstDecl :: Maybe (Name, [Name]) -> DataFamInstDecl RdrName -> RnM (DataFamInstDecl Name, FreeVars) rnDataFamInstDecl mb_cls (DataFamInstDecl { dfid_tycon = tycon - , dfid_rep_tycon = rep_tycon + , dfid_rep_tycon = mb_rep_tycon , dfid_pats = HsWB { hswb_cts = pats } , dfid_defn = defn }) = do { (tycon', pats', defn', fvs) <- rnFamInstDecl (TyDataCtx tycon) mb_cls tycon pats defn rnDataDefn ; mod <- getModule + ; let rep_tycon = expectJust "rnDataFamInstDecl" mb_rep_tycon ; rep_tycon' <- newGlobalBinder mod (rdrNameOcc rep_tycon) (getLoc tycon) ; return (DataFamInstDecl { dfid_tycon = tycon' - , dfid_rep_tycon = rep_tycon' + , dfid_rep_tycon = Just rep_tycon' , dfid_pats = pats' , dfid_defn = defn' , dfid_fvs = fvs }, fvs) } diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index e61955f..090a741 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -60,7 +60,7 @@ import Util import BooleanFormula ( isUnsatisfied, pprBooleanFormulaNice ) import Control.Monad -import Maybes ( isNothing, isJust, whenIsJust, catMaybes ) +import Maybes ( isNothing, isJust, whenIsJust, catMaybes, expectJust ) import Data.List ( mapAccumL, partition ) {- @@ -663,7 +663,7 @@ tcDataFamInstDecl mb_clsinfo (L loc decl@(DataFamInstDecl { dfid_pats = pats , dfid_tycon = fam_tc_name - , dfid_rep_tycon = rep_tc_name + , dfid_rep_tycon = mb_rep_tc_name , dfid_defn = defn at HsDataDefn { dd_ND = new_or_data, dd_cType = cType , dd_ctxt = ctxt, dd_cons = cons } })) = setSrcSpan loc $ @@ -693,6 +693,7 @@ tcDataFamInstDecl mb_clsinfo ; gadt_syntax <- dataDeclChecks (tyConName fam_tc) new_or_data stupid_theta cons -- Construct representation tycon + ; let rep_tc_name = expectJust "tcDamFamInstDecl" mb_rep_tc_name ; axiom_name <- newImplicitBinder rep_tc_name mkInstTyCoOcc ; let orig_res_ty = mkTyConApp fam_tc pats' From git at git.haskell.org Fri Mar 27 15:46:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:46 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Squash unnecessary TODOs (03506e0) Message-ID: <20150327154646.30B3A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/03506e050f87f6b22eea171a8e35d43c48e90a04/ghc >--------------------------------------------------------------- commit 03506e050f87f6b22eea171a8e35d43c48e90a04 Author: Adam Gundry Date: Mon Mar 2 11:01:47 2015 +0000 Squash unnecessary TODOs >--------------------------------------------------------------- 03506e050f87f6b22eea171a8e35d43c48e90a04 compiler/hsSyn/HsExpr.hs | 2 +- compiler/typecheck/TcHsSyn.hs | 1 - 2 files changed, 1 insertion(+), 2 deletions(-) diff --git a/compiler/hsSyn/HsExpr.hs b/compiler/hsSyn/HsExpr.hs index 607a8f2..14f3c92 100644 --- a/compiler/hsSyn/HsExpr.hs +++ b/compiler/hsSyn/HsExpr.hs @@ -294,7 +294,7 @@ data HsExpr id -- For a type family, the arg types are of the *instance* tycon, -- not the family tycon - -- | Used to attach a selector id to non-overloaded fields (TODO: API annotation?) + -- | Used to attach a selector id to non-overloaded fields | HsSingleRecFld RdrName id -- | Expression with an explicit type signature. @e :: type@ diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs index c3c5c04..2928fcd 100644 --- a/compiler/typecheck/TcHsSyn.hs +++ b/compiler/typecheck/TcHsSyn.hs @@ -989,7 +989,6 @@ zonkRecFields env (HsRecFields flds dd) = do { flds' <- mapM zonk_rbind flds ; return (HsRecFields flds' dd) } where - -- TODO new_id <- zonkIdBndr env (unLoc (hsRecFieldId fld)) zonk_rbind (L l fld) = do { new_id <- zonkIdBndr env (unLoc (hsRecFieldId fld)) ; new_expr <- zonkLExpr env (hsRecFieldArg fld) From git at git.haskell.org Fri Mar 27 15:46:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:49 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Remove old misleading docs (287255e) Message-ID: <20150327154649.3C3213A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/287255ed7e639a2a9dc52208dead6e7b683802a3/ghc >--------------------------------------------------------------- commit 287255ed7e639a2a9dc52208dead6e7b683802a3 Author: Adam Gundry Date: Mon Mar 2 11:11:46 2015 +0000 Remove old misleading docs >--------------------------------------------------------------- 287255ed7e639a2a9dc52208dead6e7b683802a3 docs/users_guide/glasgow_exts.xml | 307 -------------------------------------- 1 file changed, 307 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 287255ed7e639a2a9dc52208dead6e7b683802a3 From git at git.haskell.org Fri Mar 27 15:46:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:52 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Get rid of dead code (9915fb4) Message-ID: <20150327154652.36CB03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/9915fb48a08e2ebfb4eda33f653f8241bea2d23f/ghc >--------------------------------------------------------------- commit 9915fb48a08e2ebfb4eda33f653f8241bea2d23f Author: Adam Gundry Date: Mon Mar 2 11:24:05 2015 +0000 Get rid of dead code >--------------------------------------------------------------- 9915fb48a08e2ebfb4eda33f653f8241bea2d23f compiler/typecheck/TcType.hs | 9 --------- compiler/types/Type.hs-boot | 2 -- 2 files changed, 11 deletions(-) diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index 1def1fe..d6fadc7 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -58,7 +58,6 @@ module TcType ( tcInstHeadTyNotSynonym, tcInstHeadTyAppAllTyVars, tcGetTyVar_maybe, tcGetTyVar, nextRole, tcSplitSigmaTy, tcDeepSplitSigmaTy_maybe, - tcSplitRecordsArgs, --------------------------------- -- Predicates. @@ -172,7 +171,6 @@ import VarEnv import PrelNames import TysWiredIn import BasicTypes -import FieldLabel import Util import Maybes import ListSetOps @@ -1106,13 +1104,6 @@ tcInstHeadTyAppAllTyVars ty get_tv (TyVarTy tv) = Just tv -- through synonyms get_tv _ = Nothing -tcSplitRecordsArgs :: [Type] -> Maybe (FieldLabelString, TyCon, [Type]) -tcSplitRecordsArgs (r:n:_) - | Just lbl <- isStrLitTy n - , Just (tc, tys) <- tcSplitTyConApp_maybe r - = Just (lbl, tc, tys) -tcSplitRecordsArgs _ = Nothing - tcEqKind :: TcKind -> TcKind -> Bool tcEqKind = tcEqType diff --git a/compiler/types/Type.hs-boot b/compiler/types/Type.hs-boot index 582b113..587454e 100644 --- a/compiler/types/Type.hs-boot +++ b/compiler/types/Type.hs-boot @@ -7,5 +7,3 @@ isPredTy :: Type -> Bool typeKind :: Type -> Kind substKiWith :: [KindVar] -> [Kind] -> Kind -> Kind eqKind :: Kind -> Kind -> Bool - -cmpType :: Type -> Type -> Ordering From git at git.haskell.org Fri Mar 27 15:46:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:55 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Add test for presence of mangled selector name in error messages (d924909) Message-ID: <20150327154655.A75F43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/d924909cd1738121e9fcf0093d40890f048e41b5/ghc >--------------------------------------------------------------- commit d924909cd1738121e9fcf0093d40890f048e41b5 Author: Adam Gundry Date: Fri Mar 20 14:02:24 2015 +0000 Add test for presence of mangled selector name in error messages >--------------------------------------------------------------- d924909cd1738121e9fcf0093d40890f048e41b5 testsuite/tests/overloadedrecflds/should_fail/all.T | 1 + .../overloadedrecflds/should_fail/overloadedrecfldsfail07.hs | 9 +++++++++ .../overloadedrecflds/should_fail/overloadedrecfldsfail07.stderr | 6 ++++++ 3 files changed, 16 insertions(+) diff --git a/testsuite/tests/overloadedrecflds/should_fail/all.T b/testsuite/tests/overloadedrecflds/should_fail/all.T index 9fb862d..a8b9308 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/all.T +++ b/testsuite/tests/overloadedrecflds/should_fail/all.T @@ -8,3 +8,4 @@ test('overloadedrecfldsfail05', normal, compile_fail, ['']) test('overloadedrecfldsfail06', extra_clean(['OverloadedRecFldsFail06_A.hi', 'OverloadedRecFldsFail06_A.o']), multimod_compile_fail, ['overloadedrecfldsfail06', '']) +test('overloadedrecfldsfail07', normal, compile_fail, ['']) diff --git a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail07.hs b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail07.hs new file mode 100644 index 0000000..fddab62 --- /dev/null +++ b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail07.hs @@ -0,0 +1,9 @@ +-- Test type errors contain field names, not selector names + +{-# LANGUAGE OverloadedRecordFields #-} + +data T = MkT { x :: Int } + +y = x x + +main = return () \ No newline at end of file diff --git a/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail07.stderr b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail07.stderr new file mode 100644 index 0000000..87de242 --- /dev/null +++ b/testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail07.stderr @@ -0,0 +1,6 @@ + +overloadedrecfldsfail07.hs:7:7: + Couldn't match expected type ?T? with actual type ?T -> Int? + Probable cause: ?x? is applied to too few arguments + In the first argument of ?x?, namely ?x? + In the expression: x x From git at git.haskell.org Fri Mar 27 15:46:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:46:58 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Fix renaming of HsVar to introduce HsSingleRecFld if necessary (fba738d) Message-ID: <20150327154658.C9A4F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/fba738d10d4ac7a98c610b4205c79cf8a8d0f9c3/ghc >--------------------------------------------------------------- commit fba738d10d4ac7a98c610b4205c79cf8a8d0f9c3 Author: Adam Gundry Date: Fri Mar 20 14:37:04 2015 +0000 Fix renaming of HsVar to introduce HsSingleRecFld if necessary >--------------------------------------------------------------- fba738d10d4ac7a98c610b4205c79cf8a8d0f9c3 compiler/rename/RnEnv.hs | 90 ++++++++++++++--------------------------------- compiler/rename/RnExpr.hs | 9 +++-- compiler/rename/RnPat.hs | 2 +- 3 files changed, 33 insertions(+), 68 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fba738d10d4ac7a98c610b4205c79cf8a8d0f9c3 From git at git.haskell.org Fri Mar 27 15:47:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:47:01 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Pretty-print HsSingleRecFld like HsVar (a5b8489) Message-ID: <20150327154701.E54A03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/a5b84898472376e4c8056956de04e70684d72f6e/ghc >--------------------------------------------------------------- commit a5b84898472376e4c8056956de04e70684d72f6e Author: Adam Gundry Date: Fri Mar 20 14:37:27 2015 +0000 Pretty-print HsSingleRecFld like HsVar >--------------------------------------------------------------- a5b84898472376e4c8056956de04e70684d72f6e compiler/hsSyn/HsExpr.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/compiler/hsSyn/HsExpr.hs b/compiler/hsSyn/HsExpr.hs index 14f3c92..1cb945d 100644 --- a/compiler/hsSyn/HsExpr.hs +++ b/compiler/hsSyn/HsExpr.hs @@ -813,6 +813,7 @@ hsExprNeedsParens (HsRnBracketOut {}) = False hsExprNeedsParens (HsTcBracketOut {}) = False hsExprNeedsParens (HsDo sc _ _) | isListCompExpr sc = False +hsExprNeedsParens (HsSingleRecFld{}) = False hsExprNeedsParens _ = True @@ -825,6 +826,7 @@ isAtomicHsExpr (HsIPVar {}) = True isAtomicHsExpr (HsUnboundVar {}) = True isAtomicHsExpr (HsWrap _ e) = isAtomicHsExpr e isAtomicHsExpr (HsPar e) = isAtomicHsExpr (unLoc e) +isAtomicHsExpr (HsSingleRecFld{}) = True isAtomicHsExpr _ = False {- From git at git.haskell.org Fri Mar 27 15:47:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:47:04 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Accept that TH contains $sel-mangled names for now (aefc790) Message-ID: <20150327154704.CEAD73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/aefc79035e439c5f5242d86cf8d699d1840e5371/ghc >--------------------------------------------------------------- commit aefc79035e439c5f5242d86cf8d699d1840e5371 Author: Adam Gundry Date: Fri Mar 20 14:42:00 2015 +0000 Accept that TH contains $sel-mangled names for now >--------------------------------------------------------------- aefc79035e439c5f5242d86cf8d699d1840e5371 .../tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout b/testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout index b34b9bd..2c5a5ff 100644 --- a/testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout +++ b/testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout @@ -1,2 +1,2 @@ -data Main.R = Main.MkR {Main.foo :: GHC.Types.Int} +data Main.R = Main.MkR {Main.$sel:foo:R :: GHC.Types.Int} 42 From git at git.haskell.org Fri Mar 27 15:47:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:47:07 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Use addUsedSelector to record occurrences of overloaded fields in pattern matches (6ff694b) Message-ID: <20150327154707.DDB873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/6ff694baaac9fbc79c9f44ebf805f2d1db233866/ghc >--------------------------------------------------------------- commit 6ff694baaac9fbc79c9f44ebf805f2d1db233866 Author: Adam Gundry Date: Fri Mar 20 14:52:00 2015 +0000 Use addUsedSelector to record occurrences of overloaded fields in pattern matches >--------------------------------------------------------------- 6ff694baaac9fbc79c9f44ebf805f2d1db233866 compiler/rename/RnEnv.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs index acc59bb..1bd71e2 100644 --- a/compiler/rename/RnEnv.hs +++ b/compiler/rename/RnEnv.hs @@ -482,7 +482,11 @@ lookupSubBndrOcc warnIfDeprec parent doc rdr_name -- NB: lookupGlobalRdrEnv, not lookupGRE_RdrName! -- The latter does pickGREs, but we want to allow 'x' -- even if only 'M.x' is in scope - [gre] -> do { addUsedRdrName warnIfDeprec gre (used_rdr_name gre) + [gre] | isOverloadedRecFldGRE gre -> + do { addUsedSelector (gre_name gre) + ; return (gre_name gre) } + | otherwise -> + do { addUsedRdrName warnIfDeprec gre (used_rdr_name gre) -- Add a usage; this is an *occurrence* site ; return (gre_name gre) } [] -> do { addErr (unknownSubordinateErr doc rdr_name) From git at git.haskell.org Fri Mar 27 15:47:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:47:11 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Merge remote-tracking branch 'origin/master' into wip/orf-reboot (a52d3a8) Message-ID: <20150327154711.957C83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/a52d3a8b6b777108ade1bfcad69efc1a3ddcf47b/ghc >--------------------------------------------------------------- commit a52d3a8b6b777108ade1bfcad69efc1a3ddcf47b Merge: 6ff694b 6da18b8 Author: Adam Gundry Date: Fri Mar 20 15:04:15 2015 +0000 Merge remote-tracking branch 'origin/master' into wip/orf-reboot Conflicts: compiler/rename/RnSource.hs compiler/typecheck/TcRnTypes.hs compiler/types/TyCon.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 a52d3a8b6b777108ade1bfcad69efc1a3ddcf47b From git at git.haskell.org Fri Mar 27 15:47:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:47:14 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Fix redundant import warnings, involving gratuitous CPP thanks to FTP (389793e) Message-ID: <20150327154714.871643A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/389793e6f1745e1fe6afb82aa598b5bdc2c737e4/ghc >--------------------------------------------------------------- commit 389793e6f1745e1fe6afb82aa598b5bdc2c737e4 Author: Adam Gundry Date: Fri Mar 20 15:28:09 2015 +0000 Fix redundant import warnings, involving gratuitous CPP thanks to FTP >--------------------------------------------------------------- 389793e6f1745e1fe6afb82aa598b5bdc2c737e4 compiler/basicTypes/FieldLabel.hs | 9 +++++---- compiler/hsSyn/HsPat.hs | 1 - compiler/hsSyn/HsUtils.hs | 5 ++++- compiler/main/InteractiveEval.hs | 1 - compiler/rename/RnEnv.hs | 3 --- compiler/rename/RnNames.hs | 6 ++++-- compiler/typecheck/TcExpr.hs | 2 -- compiler/typecheck/TcRnTypes.hs | 1 - compiler/types/TyCon.hs | 1 - 9 files changed, 13 insertions(+), 16 deletions(-) diff --git a/compiler/basicTypes/FieldLabel.hs b/compiler/basicTypes/FieldLabel.hs index d273028..9af7f88 100644 --- a/compiler/basicTypes/FieldLabel.hs +++ b/compiler/basicTypes/FieldLabel.hs @@ -39,7 +39,7 @@ dfuns/axioms differ. Each FieldLabel value is unique to its type constructor. -} -{-# LANGUAGE DeriveFunctor, DeriveFoldable, DeriveTraversable #-} +{-# LANGUAGE CPP, DeriveFunctor, DeriveFoldable, DeriveTraversable #-} module FieldLabel ( FieldLabelString , FieldLabelEnv @@ -53,11 +53,12 @@ import Name import Binary import FastString -import FastStringEnv import Outputable -import Data.Foldable -import Data.Traversable +#if __GLASGOW_HASKELL__ < 709 +import Data.Foldable ( Foldable ) +import Data.Traversable ( Traversable ) +#endif -- | Field labels are just represented as strings; -- they are not necessarily unique (even within a module) diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs index 2c72855..54fb472 100644 --- a/compiler/hsSyn/HsPat.hs +++ b/compiler/hsSyn/HsPat.hs @@ -48,7 +48,6 @@ import Var import ConLike import DataCon import TyCon -import FieldLabel import Outputable import Type import RdrName diff --git a/compiler/hsSyn/HsUtils.hs b/compiler/hsSyn/HsUtils.hs index 2580844..6206a78 100644 --- a/compiler/hsSyn/HsUtils.hs +++ b/compiler/hsSyn/HsUtils.hs @@ -101,10 +101,13 @@ import Bag import Outputable import Data.Either -import Data.Foldable ( foldMap ) import Data.Function import Data.List + +#if __GLASGOW_HASKELL__ < 709 +import Data.Foldable ( foldMap ) import Data.Monoid ( mempty, mappend ) +#endif {- ************************************************************************ diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs index ba1f2f7..ff588e1 100644 --- a/compiler/main/InteractiveEval.hs +++ b/compiler/main/InteractiveEval.hs @@ -58,7 +58,6 @@ import Name hiding ( varName ) import NameSet import Avail import RdrName -import TcRnMonad import VarSet import VarEnv import ByteCodeInstr diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs index 236b753..756b961 100644 --- a/compiler/rename/RnEnv.hs +++ b/compiler/rename/RnEnv.hs @@ -53,8 +53,6 @@ import RdrName import HscTypes import TcEnv import TcRnMonad -import Id -import Var import Name import NameSet import NameEnv @@ -63,7 +61,6 @@ import Module import ConLike import DataCon import TyCon -import CoAxiom import PrelNames ( mkUnboundName, isUnboundName, rOOT_MAIN, forall_tv_RDR ) import ErrUtils ( MsgDoc ) import BasicTypes ( Fixity(..), FixityDirection(..), minPrecedence, defaultFixity ) diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs index b42d4bd..b03d4cd 100644 --- a/compiler/rename/RnNames.hs +++ b/compiler/rename/RnNames.hs @@ -23,7 +23,6 @@ import TcEnv import RnEnv import RnHsDoc ( rnHsDoc ) import LoadIface ( loadSrcInterface ) -import IfaceEnv import TcRnMonad import PrelNames import Module @@ -47,13 +46,16 @@ import ListSetOps import Control.Monad import Data.Map ( Map ) import qualified Data.Map as Map -import Data.Monoid ( mconcat ) import Data.Ord ( comparing ) import Data.List ( partition, (\\), find, sortBy ) import qualified Data.Set as Set import System.FilePath (()) import System.IO +#if __GLASGOW_HASKELL__ < 709 +import Data.Monoid ( mconcat ) +#endif + {- ************************************************************************ * * diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs index dde5467..9d6980a 100644 --- a/compiler/typecheck/TcExpr.hs +++ b/compiler/typecheck/TcExpr.hs @@ -50,8 +50,6 @@ import Var import VarSet import VarEnv import TysWiredIn -import TysPrim -import MkId import TysPrim( intPrimTy, addrPrimTy ) import PrimOp( tagToEnumKey ) import PrelNames diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index 44578c9..ccdfe0c 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -106,7 +106,6 @@ import Type import CoAxiom ( Role ) import Class ( Class ) import TyCon ( TyCon ) -import CoAxiom import ConLike ( ConLike(..) ) import DataCon ( DataCon, FieldLabel, dataConUserType, dataConOrigArgTys ) import PatSyn ( PatSyn, patSynType ) diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index 8a38e05..8caef1e 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -112,7 +112,6 @@ import CoAxiom import PrelNames import Maybes import Outputable -import FastString import FastStringEnv import FieldLabel import Constants From git at git.haskell.org Fri Mar 27 15:47:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:47:17 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Accept a test output wibble (bacad58) Message-ID: <20150327154717.5EBCA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/bacad58025af54120095a811bb1e3819acc2872f/ghc >--------------------------------------------------------------- commit bacad58025af54120095a811bb1e3819acc2872f Author: Adam Gundry Date: Fri Mar 20 16:20:44 2015 +0000 Accept a test output wibble >--------------------------------------------------------------- bacad58025af54120095a811bb1e3819acc2872f testsuite/tests/ghci/scripts/ghci042.stdout | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/ghci/scripts/ghci042.stdout b/testsuite/tests/ghci/scripts/ghci042.stdout index 7a519f6..2a75ecb 100644 --- a/testsuite/tests/ghci/scripts/ghci042.stdout +++ b/testsuite/tests/ghci/scripts/ghci042.stdout @@ -3,4 +3,4 @@ data T = A {a :: Int} -- Defined at :3:13 a :: Integer -- Defined at :6:5 3 data R = B {a :: Int} -- Defined at :9:13 -data T = A {a :: Int} -- Defined at :3:1 +data T = A {Ghci1.a :: Int} -- Defined at :3:1 From git at git.haskell.org Fri Mar 27 15:47:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:47:20 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Fix whitespace error in test (37b0708) Message-ID: <20150327154720.7E4BD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/37b0708528e1866356def72a2223a8438429c526/ghc >--------------------------------------------------------------- commit 37b0708528e1866356def72a2223a8438429c526 Author: Adam Gundry Date: Fri Mar 27 13:28:27 2015 +0000 Fix whitespace error in test >--------------------------------------------------------------- 37b0708528e1866356def72a2223a8438429c526 testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail07.hs | 0 1 file changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Fri Mar 27 15:47:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:47:23 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Remove some redundant constraints (75de0c0) Message-ID: <20150327154723.773FF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/75de0c0d15372965d9a613fb0b53fb2be832d843/ghc >--------------------------------------------------------------- commit 75de0c0d15372965d9a613fb0b53fb2be832d843 Author: Adam Gundry Date: Fri Mar 27 13:37:57 2015 +0000 Remove some redundant constraints >--------------------------------------------------------------- 75de0c0d15372965d9a613fb0b53fb2be832d843 compiler/hsSyn/HsPat.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs index 54fb472..1a3d696 100644 --- a/compiler/hsSyn/HsPat.hs +++ b/compiler/hsSyn/HsPat.hs @@ -402,7 +402,7 @@ pprConArgs (PrefixCon pats) = sep (map pprParendLPat pats) pprConArgs (InfixCon p1 p2) = sep [pprParendLPat p1, pprParendLPat p2] pprConArgs (RecCon rpats) = ppr rpats -instance (OutputableBndr id, Outputable arg) +instance (Outputable arg) => Outputable (HsRecFields id arg) where ppr (HsRecFields { rec_flds = flds, rec_dotdot = Nothing }) = braces (fsep (punctuate comma (map ppr flds))) @@ -411,7 +411,7 @@ instance (OutputableBndr id, Outputable arg) where dotdot = ptext (sLit "..") <+> ifPprDebug (ppr (drop n flds)) -instance (OutputableBndr id, Outputable arg) +instance (Outputable arg) => Outputable (HsRecField id arg) where ppr (HsRecField { hsRecFieldLbl = f, hsRecFieldArg = arg, hsRecPun = pun }) From git at git.haskell.org Fri Mar 27 15:47:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:47:26 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Tidy up RnNames / fix lint errors (39c7957) Message-ID: <20150327154726.7ED273A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/39c79571df802f8f3e667fa16b065b6c27a8fd42/ghc >--------------------------------------------------------------- commit 39c79571df802f8f3e667fa16b065b6c27a8fd42 Author: Adam Gundry Date: Fri Mar 27 14:03:45 2015 +0000 Tidy up RnNames / fix lint errors >--------------------------------------------------------------- 39c79571df802f8f3e667fa16b065b6c27a8fd42 compiler/rename/RnNames.hs | 164 +++++++++++++++++++++++++++------------------ 1 file changed, 100 insertions(+), 64 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 39c79571df802f8f3e667fa16b065b6c27a8fd42 From git at git.haskell.org Fri Mar 27 15:47:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:47:31 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Merge remote-tracking branch 'origin/master' into wip/orf-reboot (1e9fba0) Message-ID: <20150327154731.4A6C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/1e9fba0a10b30d13c1d3b1649d456ab6fe77e55d/ghc >--------------------------------------------------------------- commit 1e9fba0a10b30d13c1d3b1649d456ab6fe77e55d Merge: 39c7957 5aa57d0 Author: Adam Gundry Date: Fri Mar 27 14:07:32 2015 +0000 Merge remote-tracking branch 'origin/master' into wip/orf-reboot >--------------------------------------------------------------- Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1e9fba0a10b30d13c1d3b1649d456ab6fe77e55d From git at git.haskell.org Fri Mar 27 15:47:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:47:34 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Comment tweak (9c06648) Message-ID: <20150327154734.8218A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/9c0664893bdb34cdd8a8e9a80b61790e8d99ea71/ghc >--------------------------------------------------------------- commit 9c0664893bdb34cdd8a8e9a80b61790e8d99ea71 Author: Adam Gundry Date: Fri Mar 27 14:30:53 2015 +0000 Comment tweak >--------------------------------------------------------------- 9c0664893bdb34cdd8a8e9a80b61790e8d99ea71 compiler/hsSyn/HsPat.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs index 1a3d696..cba3e04 100644 --- a/compiler/hsSyn/HsPat.hs +++ b/compiler/hsSyn/HsPat.hs @@ -309,9 +309,9 @@ data HsRecField id arg = HsRecField { -- -- and the typechecker will determine that $sel:x:S is meant. -- --- AMG TODO: it would be nice if we could enforce in the types that --- ambiguous fields occur only in record updates, and only between the --- renamer and the typechecker. +-- It would be nice if we could enforce in the types that ambiguous +-- fields occur only in record updates, and only between the renamer +-- and the typechecker, but this is not yet implemented. hsRecFieldSelMissing :: Either id [(id, id)] hsRecFieldSelMissing = Right [] From git at git.haskell.org Fri Mar 27 15:47:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 15:47:37 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Update haddock submodule for rough ORF compatibility (3c3e1dc) Message-ID: <20150327154737.71E103A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/3c3e1dc7e2fce256cdd786fe119774386ff76cd5/ghc >--------------------------------------------------------------- commit 3c3e1dc7e2fce256cdd786fe119774386ff76cd5 Author: Adam Gundry Date: Fri Mar 27 15:40:50 2015 +0000 Update haddock submodule for rough ORF compatibility >--------------------------------------------------------------- 3c3e1dc7e2fce256cdd786fe119774386ff76cd5 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index f9ae6aa..d137dae 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit f9ae6aaf269474228f368380966fc80b73587832 +Subproject commit d137dae000575e46a2144892329df1dfb5a28980 From git at git.haskell.org Fri Mar 27 20:38:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Mar 2015 20:38:20 +0000 (UTC) Subject: [commit: ghc] master: Rename driver phases C(obj)cpp to C(obj)cplusplus (abde5da) Message-ID: <20150327203820.A2E593A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/abde5da4dee5f3b83264f8471e458b20d04f8b29/ghc >--------------------------------------------------------------- commit abde5da4dee5f3b83264f8471e458b20d04f8b29 Author: Thomas Miedema Date: Fri Mar 27 21:37:49 2015 +0100 Rename driver phases C(obj)cpp to C(obj)cplusplus Before: Cpp = Pre-process C Ccpp = Compile C++ Cobjcpp = Compile Objective-C++ CmmCpp = Pre-process Cmm Quite confusing! This commit renames `Ccpp` to `Ccplusplus`, and `Cobjcpp` to `Cobjcplusplus`. The two letters `p-p` keep standing for `pre-processing` throughout the compiler. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D756 >--------------------------------------------------------------- abde5da4dee5f3b83264f8471e458b20d04f8b29 compiler/main/DriverPhases.hs | 32 ++++++++++++++++---------------- compiler/main/DriverPipeline.hs | 9 +++++---- ghc/Main.hs | 2 +- 3 files changed, 22 insertions(+), 21 deletions(-) diff --git a/compiler/main/DriverPhases.hs b/compiler/main/DriverPhases.hs index 2433f6d..2d7d904 100644 --- a/compiler/main/DriverPhases.hs +++ b/compiler/main/DriverPhases.hs @@ -111,10 +111,10 @@ data Phase | Cpp HscSource | HsPp HscSource | Hsc HscSource - | Ccpp - | Cc - | Cobjc - | Cobjcpp + | Ccplusplus -- Compile C++ + | Cc -- Compile C + | Cobjc -- Compile Objective-C + | Cobjcplusplus -- Compile Objective-C++ | HCc -- Haskellised C (as opposed to vanilla C) compilation | Splitter -- Assembly file splitter (part of '-split-objs') | SplitAs -- Assembler for split assembly files (part of '-split-objs') @@ -148,10 +148,8 @@ eqPhase (Unlit _) (Unlit _) = True eqPhase (Cpp _) (Cpp _) = True eqPhase (HsPp _) (HsPp _) = True eqPhase (Hsc _) (Hsc _) = True -eqPhase Ccpp Ccpp = True eqPhase Cc Cc = True eqPhase Cobjc Cobjc = True -eqPhase Cobjcpp Cobjcpp = True eqPhase HCc HCc = True eqPhase Splitter Splitter = True eqPhase SplitAs SplitAs = True @@ -163,7 +161,9 @@ eqPhase CmmCpp CmmCpp = True eqPhase Cmm Cmm = True eqPhase MergeStub MergeStub = True eqPhase StopLn StopLn = True -eqPhase _ _ = False +eqPhase Ccplusplus Ccplusplus = True +eqPhase Cobjcplusplus Cobjcplusplus = True +eqPhase _ _ = False -- Partial ordering on phases: we want to know which phases will occur before -- which others. This is used for sanity checking, to ensure that the @@ -189,10 +189,10 @@ nextPhase dflags p LlvmMangle -> As False SplitAs -> MergeStub As _ -> MergeStub - Ccpp -> As False + Ccplusplus -> As False Cc -> As False Cobjc -> As False - Cobjcpp -> As False + Cobjcplusplus -> As False CmmCpp -> Cmm Cmm -> maybeHCc HCc -> As False @@ -215,13 +215,13 @@ startPhase "hscpp" = HsPp HsSrcFile startPhase "hspp" = Hsc HsSrcFile startPhase "hc" = HCc startPhase "c" = Cc -startPhase "cpp" = Ccpp +startPhase "cpp" = Ccplusplus startPhase "C" = Cc startPhase "m" = Cobjc -startPhase "M" = Cobjcpp -startPhase "mm" = Cobjcpp -startPhase "cc" = Ccpp -startPhase "cxx" = Ccpp +startPhase "M" = Cobjcplusplus +startPhase "mm" = Cobjcplusplus +startPhase "cc" = Ccplusplus +startPhase "cxx" = Ccplusplus startPhase "split_s" = Splitter startPhase "s" = As False startPhase "S" = As True @@ -247,9 +247,9 @@ phaseInputExt (Hsc _) = "hspp" -- intermediate only -- because runPipeline uses the StopBefore phase to pick the -- output filename. That could be fixed, but watch out. phaseInputExt HCc = "hc" -phaseInputExt Ccpp = "cpp" +phaseInputExt Ccplusplus = "cpp" phaseInputExt Cobjc = "m" -phaseInputExt Cobjcpp = "mm" +phaseInputExt Cobjcplusplus = "mm" phaseInputExt Cc = "c" phaseInputExt Splitter = "split_s" phaseInputExt (As True) = "S" diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 24df3a2..845cc95 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1068,7 +1068,7 @@ runPhase (RealPhase Cmm) input_fn dflags -- way too many hacks, and I can't say I've ever used it anyway. runPhase (RealPhase cc_phase) input_fn dflags - | any (cc_phase `eqPhase`) [Cc, Ccpp, HCc, Cobjc, Cobjcpp] + | any (cc_phase `eqPhase`) [Cc, Ccplusplus, HCc, Cobjc, Cobjcplusplus] = do let platform = targetPlatform dflags hcc = cc_phase `eqPhase` HCc @@ -1137,9 +1137,9 @@ runPhase (RealPhase cc_phase) input_fn dflags ghcVersionH <- liftIO $ getGhcVersionPathName dflags - let gcc_lang_opt | cc_phase `eqPhase` Ccpp = "c++" + let gcc_lang_opt | cc_phase `eqPhase` Ccplusplus = "c++" | cc_phase `eqPhase` Cobjc = "objective-c" - | cc_phase `eqPhase` Cobjcpp = "objective-c++" + | cc_phase `eqPhase` Cobjcplusplus = "objective-c++" | otherwise = "c" liftIO $ SysTools.runCc dflags ( -- force the C compiler to interpret this file as C when @@ -1176,7 +1176,8 @@ runPhase (RealPhase cc_phase) input_fn dflags else []) -- GCC 4.6+ doesn't like -Wimplicit when compiling C++. - ++ (if (cc_phase /= Ccpp && cc_phase /= Cobjcpp) + ++ (if (cc_phase /= Ccplusplus && + cc_phase /= Cobjcplusplus) then ["-Wimplicit"] else []) diff --git a/ghc/Main.hs b/ghc/Main.hs index da95ebf..a95382f 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -653,7 +653,7 @@ doMake srcs = do haskellish (f,Nothing) = looksLikeModuleName f || isHaskellUserSrcFilename f || '.' `notElem` f haskellish (_,Just phase) = - phase `notElem` [ As True, As False, Cc, Cobjc, Cobjcpp, CmmCpp, Cmm + phase `notElem` [ As True, As False, Cc, Cobjc, Cobjcplusplus, CmmCpp, Cmm , StopLn] hsc_env <- GHC.getSession From git at git.haskell.org Sat Mar 28 00:28:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 28 Mar 2015 00:28:16 +0000 (UTC) Subject: [commit: ghc] master: Rename C(obj)cplusplus to C(obj)cxx (e2f1ffc) Message-ID: <20150328002816.3B2993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e2f1ffc396cb2c2ef754ba80d2907245864c82e9/ghc >--------------------------------------------------------------- commit e2f1ffc396cb2c2ef754ba80d2907245864c82e9 Author: Thomas Miedema Date: Sat Mar 28 01:27:59 2015 +0100 Rename C(obj)cplusplus to C(obj)cxx Reviewed By: kgardas Differential Revision: https://phabricator.haskell.org/D763 >--------------------------------------------------------------- e2f1ffc396cb2c2ef754ba80d2907245864c82e9 compiler/main/DriverPhases.hs | 28 ++++++++++++++-------------- compiler/main/DriverPipeline.hs | 9 ++++----- ghc/Main.hs | 2 +- 3 files changed, 19 insertions(+), 20 deletions(-) diff --git a/compiler/main/DriverPhases.hs b/compiler/main/DriverPhases.hs index 2d7d904..164de4c 100644 --- a/compiler/main/DriverPhases.hs +++ b/compiler/main/DriverPhases.hs @@ -111,10 +111,10 @@ data Phase | Cpp HscSource | HsPp HscSource | Hsc HscSource - | Ccplusplus -- Compile C++ + | Ccxx -- Compile C++ | Cc -- Compile C | Cobjc -- Compile Objective-C - | Cobjcplusplus -- Compile Objective-C++ + | Cobjcxx -- Compile Objective-C++ | HCc -- Haskellised C (as opposed to vanilla C) compilation | Splitter -- Assembly file splitter (part of '-split-objs') | SplitAs -- Assembler for split assembly files (part of '-split-objs') @@ -161,9 +161,9 @@ eqPhase CmmCpp CmmCpp = True eqPhase Cmm Cmm = True eqPhase MergeStub MergeStub = True eqPhase StopLn StopLn = True -eqPhase Ccplusplus Ccplusplus = True -eqPhase Cobjcplusplus Cobjcplusplus = True -eqPhase _ _ = False +eqPhase Ccxx Ccxx = True +eqPhase Cobjcxx Cobjcxx = True +eqPhase _ _ = False -- Partial ordering on phases: we want to know which phases will occur before -- which others. This is used for sanity checking, to ensure that the @@ -189,10 +189,10 @@ nextPhase dflags p LlvmMangle -> As False SplitAs -> MergeStub As _ -> MergeStub - Ccplusplus -> As False + Ccxx -> As False Cc -> As False Cobjc -> As False - Cobjcplusplus -> As False + Cobjcxx -> As False CmmCpp -> Cmm Cmm -> maybeHCc HCc -> As False @@ -215,13 +215,13 @@ startPhase "hscpp" = HsPp HsSrcFile startPhase "hspp" = Hsc HsSrcFile startPhase "hc" = HCc startPhase "c" = Cc -startPhase "cpp" = Ccplusplus +startPhase "cpp" = Ccxx startPhase "C" = Cc startPhase "m" = Cobjc -startPhase "M" = Cobjcplusplus -startPhase "mm" = Cobjcplusplus -startPhase "cc" = Ccplusplus -startPhase "cxx" = Ccplusplus +startPhase "M" = Cobjcxx +startPhase "mm" = Cobjcxx +startPhase "cc" = Ccxx +startPhase "cxx" = Ccxx startPhase "split_s" = Splitter startPhase "s" = As False startPhase "S" = As True @@ -247,9 +247,9 @@ phaseInputExt (Hsc _) = "hspp" -- intermediate only -- because runPipeline uses the StopBefore phase to pick the -- output filename. That could be fixed, but watch out. phaseInputExt HCc = "hc" -phaseInputExt Ccplusplus = "cpp" +phaseInputExt Ccxx = "cpp" phaseInputExt Cobjc = "m" -phaseInputExt Cobjcplusplus = "mm" +phaseInputExt Cobjcxx = "mm" phaseInputExt Cc = "c" phaseInputExt Splitter = "split_s" phaseInputExt (As True) = "S" diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 845cc95..f949531 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1068,7 +1068,7 @@ runPhase (RealPhase Cmm) input_fn dflags -- way too many hacks, and I can't say I've ever used it anyway. runPhase (RealPhase cc_phase) input_fn dflags - | any (cc_phase `eqPhase`) [Cc, Ccplusplus, HCc, Cobjc, Cobjcplusplus] + | any (cc_phase `eqPhase`) [Cc, Ccxx, HCc, Cobjc, Cobjcxx] = do let platform = targetPlatform dflags hcc = cc_phase `eqPhase` HCc @@ -1137,9 +1137,9 @@ runPhase (RealPhase cc_phase) input_fn dflags ghcVersionH <- liftIO $ getGhcVersionPathName dflags - let gcc_lang_opt | cc_phase `eqPhase` Ccplusplus = "c++" + let gcc_lang_opt | cc_phase `eqPhase` Ccxx = "c++" | cc_phase `eqPhase` Cobjc = "objective-c" - | cc_phase `eqPhase` Cobjcplusplus = "objective-c++" + | cc_phase `eqPhase` Cobjcxx = "objective-c++" | otherwise = "c" liftIO $ SysTools.runCc dflags ( -- force the C compiler to interpret this file as C when @@ -1176,8 +1176,7 @@ runPhase (RealPhase cc_phase) input_fn dflags else []) -- GCC 4.6+ doesn't like -Wimplicit when compiling C++. - ++ (if (cc_phase /= Ccplusplus && - cc_phase /= Cobjcplusplus) + ++ (if (cc_phase /= Ccxx && cc_phase /= Cobjcxx) then ["-Wimplicit"] else []) diff --git a/ghc/Main.hs b/ghc/Main.hs index a95382f..a91fb26 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -653,7 +653,7 @@ doMake srcs = do haskellish (f,Nothing) = looksLikeModuleName f || isHaskellUserSrcFilename f || '.' `notElem` f haskellish (_,Just phase) = - phase `notElem` [ As True, As False, Cc, Cobjc, Cobjcplusplus, CmmCpp, Cmm + phase `notElem` [ As True, As False, Cc, Cobjc, Cobjcxx, CmmCpp, Cmm , StopLn] hsc_env <- GHC.getSession From git at git.haskell.org Sat Mar 28 23:05:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 28 Mar 2015 23:05:17 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: docs/relnotes: update version numbers (774a716) Message-ID: <20150328230517.8D68A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/774a716a3bcfae92335d7a17ac114b9112fae3cd/ghc >--------------------------------------------------------------- commit 774a716a3bcfae92335d7a17ac114b9112fae3cd Author: Austin Seipp Date: Wed Mar 25 17:32:15 2015 -0500 docs/relnotes: update version numbers Signed-off-by: Austin Seipp >--------------------------------------------------------------- 774a716a3bcfae92335d7a17ac114b9112fae3cd docs/users_guide/7.10.1-notes.xml | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml index 7669d2c..fe430a5 100644 --- a/docs/users_guide/7.10.1-notes.xml +++ b/docs/users_guide/7.10.1-notes.xml @@ -531,7 +531,7 @@ echo "[]" > package.conf - Version number 0.5.0.1 (was 0.5.0.0) + Version number 0.5.1.0 (was 0.5.0.0) @@ -580,7 +580,7 @@ echo "[]" > package.conf - Version number XXXXX (was 0.7.1.0) + Version number 0.7.3.0 (was 0.7.1.0) @@ -624,7 +624,7 @@ echo "[]" > package.conf - Version number 1.4.0.0 (was 1.3.0.2) + Version number 1.4.1.1 (was 1.3.0.2) @@ -646,7 +646,7 @@ echo "[]" > package.conf - Version number 1.3.1.0 (was 1.3.0.2) + Version number 1.4.0.0 (was 1.3.0.2) @@ -688,7 +688,7 @@ echo "[]" > package.conf - Version number 0.3.1.0 (was 0.3.1.0) + Version number 0.4.0.0 (was 0.3.1.0) @@ -711,7 +711,7 @@ echo "[]" > package.conf - Version number 0.7.2.0 (was 0.7.1.2) + Version number 0.7.2.1 (was 0.7.1.2) @@ -787,7 +787,7 @@ echo "[]" > package.conf - Version number 1.2.2.0 (was 1.2.0.0) + Version number 1.2.3.0 (was 1.2.0.0) @@ -853,7 +853,7 @@ echo "[]" > package.conf - Version number 2.3.0.2 (was 2.3.0.1) + Version number 2.3.1.0 (was 2.3.0.1) From git at git.haskell.org Sat Mar 28 23:05:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 28 Mar 2015 23:05:20 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Set VERSION=7.10.1, RELEASE=YES (ca00def) Message-ID: <20150328230520.5018E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/ca00def1d7093d6b5b2a937ddfc8a01c152038eb/ghc >--------------------------------------------------------------- commit ca00def1d7093d6b5b2a937ddfc8a01c152038eb Author: Austin Seipp Date: Wed Mar 25 17:33:07 2015 -0500 Set VERSION=7.10.1, RELEASE=YES Signed-off-by: Austin Seipp >--------------------------------------------------------------- ca00def1d7093d6b5b2a937ddfc8a01c152038eb configure.ac | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/configure.ac b/configure.ac index b357f19..5743518 100644 --- a/configure.ac +++ b/configure.ac @@ -13,10 +13,10 @@ dnl # see what flags are available. (Better yet, read the documentation!) # -AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.10.0], [glasgow-haskell-bugs at haskell.org], [ghc]) +AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.10.1], [glasgow-haskell-bugs at haskell.org], [ghc]) # Set this to YES for a released version, otherwise NO -: ${RELEASE=NO} +: ${RELEASE=YES} # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line # above. If this is not a released version, then we will append the From git at git.haskell.org Sat Mar 28 23:09:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 28 Mar 2015 23:09:45 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Set VERSION=7.8.4, RELEASE=YES (9555516) Message-ID: <20150328230945.C194F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/95555163fda4f43c32c385500269cfb00f0cb565/ghc >--------------------------------------------------------------- commit 95555163fda4f43c32c385500269cfb00f0cb565 Author: Austin Seipp Date: Tue Dec 23 07:47:21 2014 -0600 Set VERSION=7.8.4, RELEASE=YES Signed-off-by: Austin Seipp >--------------------------------------------------------------- 95555163fda4f43c32c385500269cfb00f0cb565 configure.ac | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/configure.ac b/configure.ac index 27322c6..2414a2f 100644 --- a/configure.ac +++ b/configure.ac @@ -13,10 +13,10 @@ dnl # see what flags are available. (Better yet, read the documentation!) # -AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.8.3], [glasgow-haskell-bugs at haskell.org], [ghc]) +AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.8.4], [glasgow-haskell-bugs at haskell.org], [ghc]) # Set this to YES for a released version, otherwise NO -: ${RELEASE=NO} +: ${RELEASE=YES} # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line # above. If this is not a released version, then we will append the From git at git.haskell.org Sat Mar 28 23:10:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 28 Mar 2015 23:10:00 +0000 (UTC) Subject: [commit: ghc] tag 'ghc-7.8.4-release' created Message-ID: <20150328231000.891F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New tag : ghc-7.8.4-release Referencing: 62f1f48b78142fcead1e8e9da86abf5627ad81cf From git at git.haskell.org Sat Mar 28 23:10:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 28 Mar 2015 23:10:53 +0000 (UTC) Subject: [commit: ghc] tag 'ghc-7.10.1-release' created Message-ID: <20150328231053.815BC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New tag : ghc-7.10.1-release Referencing: 0038a83459c52fabbbd3d7790cc48187965513d6 From git at git.haskell.org Sat Mar 28 23:42:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 28 Mar 2015 23:42:56 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: RELEASE=NO (e98df4f) Message-ID: <20150328234256.B89C43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/e98df4f2afe33b19a6e221af24bc5b33b422f778/ghc >--------------------------------------------------------------- commit e98df4f2afe33b19a6e221af24bc5b33b422f778 Author: Austin Seipp Date: Sat Mar 28 18:36:46 2015 -0500 RELEASE=NO Signed-off-by: Austin Seipp >--------------------------------------------------------------- e98df4f2afe33b19a6e221af24bc5b33b422f778 configure.ac | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index 5743518..8200b90 100644 --- a/configure.ac +++ b/configure.ac @@ -16,7 +16,7 @@ dnl AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.10.1], [glasgow-haskell-bugs at haskell.org], [ghc]) # Set this to YES for a released version, otherwise NO -: ${RELEASE=YES} +: ${RELEASE=NO} # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line # above. If this is not a released version, then we will append the From git at git.haskell.org Sat Mar 28 23:42:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 28 Mar 2015 23:42:59 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix Git-commit-id detection for RELEASE=YES (346a1c1) Message-ID: <20150328234259.7BD623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/346a1c13c37f8378d9395a4b03bc84e7819006d4/ghc >--------------------------------------------------------------- commit 346a1c13c37f8378d9395a4b03bc84e7819006d4 Author: Herbert Valerio Riedel Date: Thu Mar 26 22:39:52 2015 +0100 Fix Git-commit-id detection for RELEASE=YES By mistake, the Git-commit-id detection was only enabled for `RELEASE=NO` (since the date-based GHC version computation is only active in that case). With this commit the commit-id detection is active regardless of the `RELEASE`-setting. This is a follow-up to 73e5e2f8bade2d8b2b1ecae958fe12d0b24591ef (cherry picked from commit 5aa57d0137e7626a2ed2b3656d24d7a1aac74e58) >--------------------------------------------------------------- 346a1c13c37f8378d9395a4b03bc84e7819006d4 aclocal.m4 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index 141a42d..f3f7406 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1586,6 +1586,7 @@ if test "$RELEASE" = "NO"; then dnl less likely to go wrong. PACKAGE_VERSION=${PACKAGE_VERSION}.`date +%Y%m%d` fi +fi AC_MSG_CHECKING([for GHC Git commit id]) if test -d .git; then @@ -1603,7 +1604,6 @@ if test "$RELEASE" = "NO"; then PACKAGE_GIT_COMMIT_ID="0000000000000000000000000000000000000000" fi -fi # Some renamings AC_SUBST([ProjectName], [$PACKAGE_NAME]) From git at git.haskell.org Sat Mar 28 23:43:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 28 Mar 2015 23:43:02 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: fix bus error (misaligned data access) on SPARC in __decodeDouble_Int64 (0b655e5) Message-ID: <20150328234302.280DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/0b655e5d89f6ebd1e3fb6b640d7f628b723c3c08/ghc >--------------------------------------------------------------- commit 0b655e5d89f6ebd1e3fb6b640d7f628b723c3c08 Author: Karel Gardas Date: Sun Mar 22 21:58:03 2015 +0100 fix bus error (misaligned data access) on SPARC in __decodeDouble_Int64 Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D749 (cherry picked from commit 12a03c44c006f142f93980e0dbdfab0f73db042c) >--------------------------------------------------------------- 0b655e5d89f6ebd1e3fb6b640d7f628b723c3c08 rts/StgPrimFloat.c | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/rts/StgPrimFloat.c b/rts/StgPrimFloat.c index e2eeee5..277ae66 100644 --- a/rts/StgPrimFloat.c +++ b/rts/StgPrimFloat.c @@ -182,9 +182,9 @@ __decodeDouble_Int64 (StgInt64 *const mantissa, const StgDouble dbl) I_ exp = 0; __decodeDouble_2Int (&man_sign, &man_high, &man_low, &exp, dbl); - - *mantissa = ((((StgInt64)man_high << 32) | (StgInt64)man_low) - * (StgInt64)man_sign); + ASSIGN_Int64((W_*)mantissa, ((((StgInt64)man_high << 32) + | (StgInt64)man_low) + * (StgInt64)man_sign)); return exp; #endif } From git at git.haskell.org Sun Mar 29 03:57:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 29 Mar 2015 03:57:09 +0000 (UTC) Subject: [commit: ghc] master: Doc typofix. (a4656eb) Message-ID: <20150329035709.BA2313A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a4656ebe97d5ee3579a36b6e3f9142cb9bc50a12/ghc >--------------------------------------------------------------- commit a4656ebe97d5ee3579a36b6e3f9142cb9bc50a12 Author: Edward Z. Yang Date: Sat Mar 28 20:57:20 2015 -0700 Doc typofix. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- a4656ebe97d5ee3579a36b6e3f9142cb9bc50a12 compiler/main/ErrUtils.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/main/ErrUtils.hs b/compiler/main/ErrUtils.hs index 82587d2..5762a57 100644 --- a/compiler/main/ErrUtils.hs +++ b/compiler/main/ErrUtils.hs @@ -323,7 +323,7 @@ chooseDumpFile dflags flag Just d -> d f Nothing -> f --- | Build a nice file name from name of a GeneralFlag constructor +-- | Build a nice file name from name of a 'DumpFlag' constructor beautifyDumpName :: DumpFlag -> String beautifyDumpName Opt_D_th_dec_file = "th.hs" beautifyDumpName flag From git at git.haskell.org Mon Mar 30 07:22:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Mar 2015 07:22:35 +0000 (UTC) Subject: [commit: ghc] master: Renames some files to help with validation cleanup (#10212) (e24f638) Message-ID: <20150330072235.BE33E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e24f638158f96f80e476000cd7ce8555987d84f2/ghc >--------------------------------------------------------------- commit e24f638158f96f80e476000cd7ce8555987d84f2 Author: Dave Laing Date: Mon Mar 30 09:21:13 2015 +0200 Renames some files to help with validation cleanup (#10212) Test Plan: validate twice Reviewed by: thomie Differential Revision: https://phabricator.haskell.org/D771 >--------------------------------------------------------------- e24f638158f96f80e476000cd7ce8555987d84f2 testsuite/tests/hpc/{.hpc.T10138 => .keepme.hpc.T10138}/Main.mix | 0 testsuite/tests/hpc/{T10138.tix => T10138.keepme.tix} | 0 testsuite/tests/hpc/all.T | 2 +- 3 files changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/hpc/.hpc.T10138/Main.mix b/testsuite/tests/hpc/.keepme.hpc.T10138/Main.mix similarity index 100% rename from testsuite/tests/hpc/.hpc.T10138/Main.mix rename to testsuite/tests/hpc/.keepme.hpc.T10138/Main.mix diff --git a/testsuite/tests/hpc/T10138.tix b/testsuite/tests/hpc/T10138.keepme.tix similarity index 100% rename from testsuite/tests/hpc/T10138.tix rename to testsuite/tests/hpc/T10138.keepme.tix diff --git a/testsuite/tests/hpc/all.T b/testsuite/tests/hpc/all.T index 0289733..757525c 100644 --- a/testsuite/tests/hpc/all.T +++ b/testsuite/tests/hpc/all.T @@ -1,6 +1,6 @@ test('T10138', ignore_output, run_command, # Using --hpcdir with an absolute path should work (exit code 0). - ['{hpc} report T10138.tix --hpcdir="`pwd`/.hpc.T10138"']) + ['{hpc} report T10138.keepme.tix --hpcdir="`pwd`/.keepme.hpc.T10138"']) # Run tests below only for the hpc way. # From git at git.haskell.org Mon Mar 30 08:19:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Mar 2015 08:19:55 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T10137' deleted Message-ID: <20150330081955.2AA663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T10137 From git at git.haskell.org Mon Mar 30 08:22:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Mar 2015 08:22:20 +0000 (UTC) Subject: [commit: ghc] master: Refactor the story around switches (#10137) (de1160b) Message-ID: <20150330082220.DE2393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/de1160be047790afde4ec76de0a81ba3be0c73fa/ghc >--------------------------------------------------------------- commit de1160be047790afde4ec76de0a81ba3be0c73fa Author: Joachim Breitner Date: Mon Mar 30 10:20:14 2015 +0200 Refactor the story around switches (#10137) This re-implements the code generation for case expressions at the Stg ? Cmm level, both for data type cases as well as for integral literal cases. (Cases on float are still treated as before). The goal is to allow for fancier strategies in implementing them, for a cleaner separation of the strategy from the gritty details of Cmm, and to run this later than the Common Block Optimization, allowing for one way to attack #10124. The new module CmmSwitch contains a number of notes explaining this changes. For example, it creates larger consecutive jump tables than the previous code, if possible. nofib shows little significant overall improvement of runtime. The rather large wobbling comes from changes in the code block order (see #8082, not much we can do about it). But the decrease in code size alone makes this worthwhile. ``` Program Size Allocs Runtime Elapsed TotalMem Min -1.8% 0.0% -6.1% -6.1% -2.9% Max -0.7% +0.0% +5.6% +5.7% +7.8% Geometric Mean -1.4% -0.0% -0.3% -0.3% +0.0% ``` Compilation time increases slightly: ``` -1 s.d. ----- -2.0% +1 s.d. ----- +2.5% Average ----- +0.3% ``` The test case T783 regresses a lot, but it is the only one exhibiting any regression. The cause is the changed order of branches in an if-then-else tree, which makes the hoople data flow analysis traverse the blocks in a suboptimal order. Reverting that gets rid of this regression, but has a consistent, if only very small (+0.2%), negative effect on runtime. So I conclude that this test is an extreme outlier and no reason to change the code. Differential Revision: https://phabricator.haskell.org/D720 >--------------------------------------------------------------- de1160be047790afde4ec76de0a81ba3be0c73fa compiler/basicTypes/Literal.hs | 23 +- compiler/cmm/CmmCommonBlockElim.hs | 8 +- compiler/cmm/CmmContFlowOpt.hs | 3 +- compiler/cmm/CmmImplementSwitchPlans.hs | 90 ++++ compiler/cmm/CmmLint.hs | 6 +- compiler/cmm/CmmNode.hs | 16 +- compiler/cmm/CmmParse.y | 36 +- compiler/cmm/CmmPipeline.hs | 5 + compiler/cmm/CmmProcPoint.hs | 5 +- compiler/cmm/CmmSwitch.hs | 415 +++++++++++++++++ compiler/cmm/CmmUtils.hs | 17 +- compiler/cmm/MkGraph.hs | 3 +- compiler/cmm/PprC.hs | 25 +- compiler/cmm/PprCmm.hs | 37 +- compiler/codeGen/StgCmmUtils.hs | 240 +++------- compiler/ghc.cabal.in | 2 + compiler/ghc.mk | 1 + compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 15 +- compiler/main/DynFlags.hs | 2 + compiler/nativeGen/PPC/CodeGen.hs | 14 +- compiler/nativeGen/SPARC/CodeGen.hs | 12 +- compiler/nativeGen/X86/CodeGen.hs | 14 +- .../tests/codeGen/should_run/CmmSwitchTest.hs | 505 +++++++++++++++++++++ .../tests/codeGen/should_run/CmmSwitchTestGen.hs | 115 +++++ testsuite/tests/codeGen/should_run/all.T | 1 + testsuite/tests/perf/compiler/all.T | 6 +- 26 files changed, 1323 insertions(+), 293 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc de1160be047790afde4ec76de0a81ba3be0c73fa From git at git.haskell.org Mon Mar 30 11:04:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Mar 2015 11:04:28 +0000 (UTC) Subject: [commit: ghc] master: Remove an unused include that doesn't exist on OS X (#10211) (c37ee4a) Message-ID: <20150330110428.28E3B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c37ee4a8009b438f86b1ca6df10901d7f783b4f0/ghc >--------------------------------------------------------------- commit c37ee4a8009b438f86b1ca6df10901d7f783b4f0 Author: Dave Laing Date: Mon Mar 30 13:02:33 2015 +0200 Remove an unused include that doesn't exist on OS X (#10211) Differential Revision: https://phabricator.haskell.org/D765 >--------------------------------------------------------------- c37ee4a8009b438f86b1ca6df10901d7f783b4f0 testsuite/tests/rts/linker_unload.c | 1 - 1 file changed, 1 deletion(-) diff --git a/testsuite/tests/rts/linker_unload.c b/testsuite/tests/rts/linker_unload.c index 435a451..acf41cb 100644 --- a/testsuite/tests/rts/linker_unload.c +++ b/testsuite/tests/rts/linker_unload.c @@ -2,7 +2,6 @@ #include #include #include "Rts.h" -#include #include #define ITERATIONS 1000 From git at git.haskell.org Mon Mar 30 21:06:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Mar 2015 21:06:38 +0000 (UTC) Subject: [commit: ghc] master: Delete unused field `PipeEnv.pe_isHaskellishFile` (b1d6a60) Message-ID: <20150330210638.3F6093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b1d6a6087cdc94f47075f0ad102a167c11b1bf8a/ghc >--------------------------------------------------------------- commit b1d6a6087cdc94f47075f0ad102a167c11b1bf8a Author: Thomas Miedema Date: Mon Mar 30 23:05:16 2015 +0200 Delete unused field `PipeEnv.pe_isHaskellishFile` Differential Revision: https://phabricator.haskell.org/D774 >--------------------------------------------------------------- b1d6a6087cdc94f47075f0ad102a167c11b1bf8a compiler/main/DriverPipeline.hs | 3 +-- compiler/main/PipelineMonad.hs | 1 - 2 files changed, 1 insertion(+), 3 deletions(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index f949531..334c151 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -597,8 +597,7 @@ runPipeline stop_phase hsc_env0 (input_fn, mb_phase) isHaskellishFile = isHaskell start_phase - env = PipeEnv{ pe_isHaskellishFile = isHaskellishFile, - stop_phase, + env = PipeEnv{ stop_phase, src_filename = input_fn, src_basename = basename, src_suffix = suffix', diff --git a/compiler/main/PipelineMonad.hs b/compiler/main/PipelineMonad.hs index c81f1f2..31f9169 100644 --- a/compiler/main/PipelineMonad.hs +++ b/compiler/main/PipelineMonad.hs @@ -50,7 +50,6 @@ instance Outputable PhasePlus where -- PipeEnv: invariant information passed down data PipeEnv = PipeEnv { - pe_isHaskellishFile :: Bool, stop_phase :: Phase, -- ^ Stop just before this phase src_filename :: String, -- ^ basename of original input source src_basename :: String, -- ^ basename of original input source From git at git.haskell.org Mon Mar 30 22:53:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Mar 2015 22:53:19 +0000 (UTC) Subject: [commit: ghc] master: Syntax check package-qualified imports (#9225) (5971ad5) Message-ID: <20150330225319.5C9E33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5971ad56afbdadc9af1cf9e8d708783d2fddbd95/ghc >--------------------------------------------------------------- commit 5971ad56afbdadc9af1cf9e8d708783d2fddbd95 Author: Thomas Miedema Date: Tue Mar 31 00:41:23 2015 +0200 Syntax check package-qualified imports (#9225) Version numbers are not allowed in the package name of a package-qualified import. Reviewed By: austin, ezyang Differential Revision: https://phabricator.haskell.org/D755 >--------------------------------------------------------------- 5971ad56afbdadc9af1cf9e8d708783d2fddbd95 compiler/parser/Parser.y | 12 ++++++++++-- compiler/utils/Util.hs | 15 +++++++++++++++ testsuite/tests/parser/should_fail/T9225.hs | 4 ++++ testsuite/tests/parser/should_fail/T9225.stderr | 4 ++++ testsuite/tests/parser/should_fail/all.T | 1 + 5 files changed, 34 insertions(+), 2 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 9389708..d6b7ed6 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -84,6 +84,9 @@ import TysWiredIn ( unitTyCon, unitDataCon, tupleTyCon, tupleCon, nilDataC unboxedUnitTyCon, unboxedUnitDataCon, listTyCon_RDR, parrTyCon_RDR, consDataCon_RDR, eqTyCon_RDR ) +-- compiler/utils +import Util ( looksLikePackageName ) + } {- Last updated: 03 Mar 2015 @@ -774,8 +777,13 @@ maybe_safe :: { ([AddAnn],Bool) } | {- empty -} { ([],False) } maybe_pkg :: { ([AddAnn],Maybe FastString) } - : STRING { ([mj AnnPackageName $1] - ,Just (getSTRING $1)) } + : STRING {% let pkgFS = getSTRING $1 in + if looksLikePackageName (unpackFS pkgFS) + then return ([mj AnnPackageName $1], Just pkgFS) + else parseErrorSDoc (getLoc $1) $ vcat [ + text "parse error" <> colon <+> quotes (ppr pkgFS), + text "Version number or non-alphanumeric" <+> + text "character in package name"] } | {- empty -} { ([],Nothing) } optqualified :: { ([AddAnn],Bool) } diff --git a/compiler/utils/Util.hs b/compiler/utils/Util.hs index ddcfe11..732f2b8f 100644 --- a/compiler/utils/Util.hs +++ b/compiler/utils/Util.hs @@ -67,6 +67,7 @@ module Util ( -- * Module names looksLikeModuleName, + looksLikePackageName, -- * Argument processing getCmd, toCmdArgs, toArgs, @@ -115,6 +116,10 @@ import Data.List hiding (group) import FastTypes #endif +#if __GLASGOW_HASKELL__ < 709 +import Control.Applicative (Applicative) +#endif +import Control.Applicative ( liftA2 ) import Control.Monad ( liftM ) import System.IO.Error as IO ( isDoesNotExistError ) import System.Directory ( doesDirectoryExist, getModificationTime ) @@ -655,6 +660,11 @@ cmpList cmp (a:as) (b:bs) removeSpaces :: String -> String removeSpaces = dropWhileEndLE isSpace . dropWhile isSpace +-- Boolean operators lifted to Applicative +(<&&>) :: Applicative f => f Bool -> f Bool -> f Bool +(<&&>) = liftA2 (&&) +infixr 3 <&&> -- same as (&&) + {- ************************************************************************ * * @@ -822,6 +832,11 @@ looksLikeModuleName (c:cs) = isUpper c && go cs go ('.':cs) = looksLikeModuleName cs go (c:cs) = (isAlphaNum c || c == '_' || c == '\'') && go cs +-- Similar to 'parse' for Distribution.Package.PackageName, +-- but we don't want to depend on Cabal. +looksLikePackageName :: String -> Bool +looksLikePackageName = all (all isAlphaNum <&&> not . (all isDigit)) . split '-' + {- Akin to @Prelude.words@, but acts like the Bourne shell, treating quoted strings as Haskell Strings, and also parses Haskell [String] diff --git a/testsuite/tests/parser/should_fail/T9225.hs b/testsuite/tests/parser/should_fail/T9225.hs new file mode 100644 index 0000000..8122779 --- /dev/null +++ b/testsuite/tests/parser/should_fail/T9225.hs @@ -0,0 +1,4 @@ +module T9225 where +-- Should be a parse error: +-- version numbers not allowed in package qualified imports +import "some-package-0.1.2.3" Some.Module diff --git a/testsuite/tests/parser/should_fail/T9225.stderr b/testsuite/tests/parser/should_fail/T9225.stderr new file mode 100644 index 0000000..abbfd0a --- /dev/null +++ b/testsuite/tests/parser/should_fail/T9225.stderr @@ -0,0 +1,4 @@ + +T9225.hs:4:8: + parse error: ?some-package-0.1.2.3? + Version number or non-alphanumeric character in package name diff --git a/testsuite/tests/parser/should_fail/all.T b/testsuite/tests/parser/should_fail/all.T index 7e286cf..0352235 100644 --- a/testsuite/tests/parser/should_fail/all.T +++ b/testsuite/tests/parser/should_fail/all.T @@ -86,3 +86,4 @@ test('ExportCommaComma', normal, compile_fail, ['']) test('T8430', literate, compile_fail, ['']) test('T8431', [timeout_multiplier(0.05)], compile_fail, ['-XAlternativeLayoutRule']) test('T8506', normal, compile_fail, ['']) +test('T9225', normal, compile_fail, ['']) From git at git.haskell.org Tue Mar 31 09:01:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Mar 2015 09:01:14 +0000 (UTC) Subject: [commit: ghc] master: Add `integer-gmp` specific hint to build.mk.sample (1f69f37) Message-ID: <20150331090114.A783D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1f69f37f34c6f15fd900c2c1cce3ce896168dde9/ghc >--------------------------------------------------------------- commit 1f69f37f34c6f15fd900c2c1cce3ce896168dde9 Author: Herbert Valerio Riedel Date: Tue Mar 31 10:54:15 2015 +0200 Add `integer-gmp` specific hint to build.mk.sample [skip ci] >--------------------------------------------------------------- 1f69f37f34c6f15fd900c2c1cce3ce896168dde9 mk/build.mk.sample | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/mk/build.mk.sample b/mk/build.mk.sample index c87d6f4..fd20e69 100644 --- a/mk/build.mk.sample +++ b/mk/build.mk.sample @@ -74,6 +74,10 @@ 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,) +# Uncomment the following to force `integer-gmp` to use the in-tree GMP 5.0.4 +# (other sometimes useful configure-options: `--with-gmp-{includes,libraries}`) +#libraries/integer-gmp_CONFIGURE_OPTS += --configure-option=--with-intree-gmp + # ----------- A Performance/Distribution build -------------------------------- ifeq "$(BuildFlavour)" "perf" From git at git.haskell.org Tue Mar 31 09:01:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Mar 2015 09:01:17 +0000 (UTC) Subject: [commit: ghc] master: Drop old integer-gmp-0.5 from GHC source tree (995e8c1) Message-ID: <20150331090117.790333A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/995e8c1c8692b60c907c7d2ccea179d52ca8e69e/ghc >--------------------------------------------------------------- commit 995e8c1c8692b60c907c7d2ccea179d52ca8e69e Author: Herbert Valerio Riedel Date: Sun Mar 29 19:02:08 2015 +0200 Drop old integer-gmp-0.5 from GHC source tree This completes what c774b28f76ee4c220f7c1c9fd81585e0e3af0e8a (#9281) started. `integer-gmp-1.0` was added as an additional `libraries/integer-gmp2` folder while retaining the ability to configure GHC w/ the old `integer-gmp-0.5` to have a way back, and or the ability to easily switch between old/new `integer-gmp` for benchmark/debugging purposes. This commit removes the old `libraries/integer-gmp` folder and moves `libraries/integer-gmp2` into its place, while removing any mentions of "gmp2" as well as the to support two different `integer-gmp` packages in GHC's source-tree. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D769 >--------------------------------------------------------------- 995e8c1c8692b60c907c7d2ccea179d52ca8e69e compiler/basicTypes/Module.hs | 1 - compiler/coreSyn/CorePrep.hs | 2 - compiler/ghc.mk | 3 - compiler/prelude/PrelNames.hs | 2 - ghc.mk | 12 - libraries/base/base.cabal | 9 - libraries/integer-gmp/.gitignore | 6 +- libraries/integer-gmp/GHC/Integer.lhs | 66 - libraries/integer-gmp/GHC/Integer/GMP/Internals.hs | 40 - libraries/integer-gmp/GHC/Integer/GMP/Prim.hs | 372 ---- libraries/integer-gmp/GHC/Integer/Logarithms.hs | 43 - .../GHC/Integer/Logarithms/Internals.hs | 260 --- libraries/integer-gmp/GHC/Integer/Type.lhs | 1021 ----------- libraries/integer-gmp/LICENSE | 80 +- libraries/integer-gmp/Setup.hs | 2 +- libraries/integer-gmp/cbits/alloc.c | 97 -- libraries/integer-gmp/cbits/cbits.c | 14 - libraries/integer-gmp/cbits/float.c | 249 --- libraries/integer-gmp/cbits/gmp-wrappers.cmm | 823 --------- libraries/integer-gmp/cbits/longlong.c | 66 - .../{integer-gmp2 => integer-gmp}/cbits/wrappers.c | 0 libraries/integer-gmp/changelog.md | 7 + libraries/integer-gmp/configure.ac | 36 +- .../{integer-gmp2 => integer-gmp}/gmp/ghc-gmp.h | 0 libraries/integer-gmp/gmp/ghc.mk | 92 +- .../{integer-gmp2 => integer-gmp}/gmp/gmpsrc.patch | 0 libraries/integer-gmp/include/HsIntegerGmp.h.in | 10 +- libraries/integer-gmp/integer-gmp.buildinfo.in | 2 +- libraries/integer-gmp/integer-gmp.cabal | 98 +- .../integer-gmp/mkGmpDerivedConstants/Makefile | 15 - libraries/integer-gmp/mkGmpDerivedConstants/ghc.mk | 39 - .../mkGmpDerivedConstants/mkGmpDerivedConstants.c | 75 - .../src/GHC/Integer.hs | 0 .../src/GHC/Integer/GMP/Internals.hs | 0 .../src/GHC/Integer/Logarithms.hs | 0 .../src/GHC/Integer/Logarithms/Internals.hs | 0 .../src/GHC/Integer/Type.hs | 0 libraries/integer-gmp2/.gitignore | 14 - libraries/integer-gmp2/LICENSE | 30 - libraries/integer-gmp2/Setup.hs | 6 - libraries/integer-gmp2/aclocal.m4 | 44 - libraries/integer-gmp2/changelog.md | 51 - libraries/integer-gmp2/config.guess | 1420 ---------------- libraries/integer-gmp2/config.sub | 1794 -------------------- libraries/integer-gmp2/configure.ac | 116 -- libraries/integer-gmp2/gmp/config.mk.in | 11 - libraries/integer-gmp2/gmp/ghc.mk | 139 -- libraries/integer-gmp2/gmp/ln | 3 - libraries/integer-gmp2/include/HsIntegerGmp.h.in | 14 - libraries/integer-gmp2/install-sh | 527 ------ libraries/integer-gmp2/integer-gmp.buildinfo.in | 5 - libraries/integer-gmp2/integer-gmp.cabal | 66 - mk/config.mk.in | 2 +- rules/foreachLibrary.mk | 2 - utils/ghc-cabal/Main.hs | 4 - 55 files changed, 137 insertions(+), 7653 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 995e8c1c8692b60c907c7d2ccea179d52ca8e69e From git at git.haskell.org Tue Mar 31 10:06:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Mar 2015 10:06:11 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: suppress errors when running GS on bad.ps (a3d0a7a) Message-ID: <20150331100611.78E933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a3d0a7a0ba3a1ee458a9883011247561dfe22f4a/ghc >--------------------------------------------------------------- commit a3d0a7a0ba3a1ee458a9883011247561dfe22f4a Author: Phil Ruffwind Date: Tue Mar 31 12:04:50 2015 +0200 Testsuite: suppress errors when running GS on bad.ps Suppress the errors that appear in standard output when running gs on bad.ps since it's expected to fail anyway. Reviewed By: thomie, austin Differential Revision: https://phabricator.haskell.org/D773 >--------------------------------------------------------------- a3d0a7a0ba3a1ee458a9883011247561dfe22f4a testsuite/driver/testlib.py | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index d3b9b20..b0d552e 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -2060,7 +2060,7 @@ if config.have_profiling: if config.gs != '': resultGood = runCmdExitCode(genGSCmd(config.confdir + '/good.ps')); if resultGood == 0: - resultBad = runCmdExitCode(genGSCmd(config.confdir + '/bad.ps')); + resultBad = runCmdExitCode(genGSCmd(config.confdir + '/bad.ps') + ' >/dev/null') if resultBad != 0: print("GhostScript available for hp2ps tests") gs_working = 1; From git at git.haskell.org Tue Mar 31 10:11:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Mar 2015 10:11:26 +0000 (UTC) Subject: [commit: ghc] master: Explicitly check for -C on registerised build (#7563) (9e073ce) Message-ID: <20150331101126.D79DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9e073ce41ff471d0b734ace095ece2a3e4c02f68/ghc >--------------------------------------------------------------- commit 9e073ce41ff471d0b734ace095ece2a3e4c02f68 Author: Thomas Miedema Date: Tue Mar 31 12:11:08 2015 +0200 Explicitly check for -C on registerised build (#7563) Show a more descriptive error message. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D775 >--------------------------------------------------------------- 9e073ce41ff471d0b734ace095ece2a3e4c02f68 ghc/Main.hs | 7 ++++++- testsuite/tests/driver/T7563.stderr | 2 +- 2 files changed, 7 insertions(+), 2 deletions(-) diff --git a/ghc/Main.hs b/ghc/Main.hs index a91fb26..2f013aa 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -339,10 +339,15 @@ checkOptions mode dflags srcs objs = do then throwGhcException (UsageError "no input files") else do + case mode of + StopBefore HCc | hscTarget dflags /= HscC + -> throwGhcException $ UsageError $ + "the option -C is only available with an unregisterised GHC" + _ -> return () + -- Verify that output files point somewhere sensible. verifyOutputFiles dflags - -- Compiler output options -- Called to verify that the output files point somewhere valid. diff --git a/testsuite/tests/driver/T7563.stderr b/testsuite/tests/driver/T7563.stderr index d9d296f..316e2c0 100644 --- a/testsuite/tests/driver/T7563.stderr +++ b/testsuite/tests/driver/T7563.stderr @@ -1,2 +1,2 @@ -ghc: cannot compile this file to desired target: T7563.hs +ghc-stage2: the option -C is only available with an unregisterised GHC Usage: For basic information, try the `--help' option. From git at git.haskell.org Tue Mar 31 10:15:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Mar 2015 10:15:54 +0000 (UTC) Subject: [commit: ghc] master: Don't throw exception when start_phase==stop_phase (#10219) (6981862) Message-ID: <20150331101554.41DF33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/698186268d3846c9984798ab32f34f83f3c2337e/ghc >--------------------------------------------------------------- commit 698186268d3846c9984798ab32f34f83f3c2337e Author: Thomas Miedema Date: Tue Mar 31 12:12:24 2015 +0200 Don't throw exception when start_phase==stop_phase (#10219) Just do nothing instead. This bug only shows up when using `-x hspp` in --make mode on registerised builds. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D776 >--------------------------------------------------------------- 698186268d3846c9984798ab32f34f83f3c2337e compiler/main/DriverPhases.hs | 19 ++++++++++++++++--- compiler/main/DriverPipeline.hs | 10 +++++----- testsuite/tests/driver/{T703.hs => T10219.hspp} | 0 testsuite/tests/driver/all.T | 5 +++++ 4 files changed, 26 insertions(+), 8 deletions(-) diff --git a/compiler/main/DriverPhases.hs b/compiler/main/DriverPhases.hs index 164de4c..f1db9bc 100644 --- a/compiler/main/DriverPhases.hs +++ b/compiler/main/DriverPhases.hs @@ -165,9 +165,22 @@ eqPhase Ccxx Ccxx = True eqPhase Cobjcxx Cobjcxx = True eqPhase _ _ = False --- Partial ordering on phases: we want to know which phases will occur before --- which others. This is used for sanity checking, to ensure that the --- pipeline will stop at some point (see DriverPipeline.runPipeline). +{- Note [Partial ordering on phases] + +We want to know which phases will occur before which others. This is used for +sanity checking, to ensure that the pipeline will stop at some point (see +DriverPipeline.runPipeline). + +A < B iff A occurs before B in a normal compilation pipeline. + +There is explicitly not a total ordering on phases, because in registerised +builds, the phase `HsC` doesn't happen before nor after any other phase. + +Although we check that a normal user doesn't set the stop_phase to HsC through +use of -C with registerised builds (in Main.checkOptions), it is still +possible for a ghc-api user to do so. So be careful when using the function +happensBefore, and don't think that `not (a <= b)` implies `b < a`. +-} happensBefore :: DynFlags -> Phase -> Phase -> Bool happensBefore dflags p1 p2 = p1 `happensBefore'` p2 where StopLn `happensBefore'` _ = False diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 334c151..498b2f0 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -606,14 +606,13 @@ runPipeline stop_phase hsc_env0 (input_fn, mb_phase) -- We want to catch cases of "you can't get there from here" before -- we start the pipeline, because otherwise it will just run off the -- end. - -- - -- There is a partial ordering on phases, where A < B iff A occurs - -- before B in a normal compilation pipeline. - let happensBefore' = happensBefore dflags case start_phase of RealPhase start_phase' -> - when (not (start_phase' `happensBefore'` stop_phase)) $ + -- See Note [Partial ordering on phases] + -- Not the same as: (stop_phase `happensBefore` start_phase') + when (not (start_phase' `happensBefore'` stop_phase || + start_phase' `eqPhase` stop_phase)) $ throwGhcExceptionIO (UsageError ("cannot compile this file to desired target: " ++ input_fn)) @@ -663,6 +662,7 @@ pipeLoop :: PhasePlus -> FilePath -> CompPipeline (DynFlags, FilePath) pipeLoop phase input_fn = do env <- getPipeEnv dflags <- getDynFlags + -- See Note [Partial ordering on phases] let happensBefore' = happensBefore dflags stopPhase = stop_phase env case phase of diff --git a/testsuite/tests/driver/T703.hs b/testsuite/tests/driver/T10219.hspp similarity index 100% copy from testsuite/tests/driver/T703.hs copy to testsuite/tests/driver/T10219.hspp diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T index 0585c9c..e1665f1 100644 --- a/testsuite/tests/driver/all.T +++ b/testsuite/tests/driver/all.T @@ -422,3 +422,8 @@ test('T9938B', test('T9963', exit_code(1), run_command, ['{compiler} --interactive --print-libdir']) + +test('T10219', normal, run_command, + # `-x hspp` in make mode should work. + # Note: need to specify `-x hspp` before the filename. + ['{compiler} --make -x hspp T10219.hspp -fno-code -v0']) From git at git.haskell.org Tue Mar 31 10:15:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Mar 2015 10:15:57 +0000 (UTC) Subject: [commit: ghc] master: Don't treat .hcr and .raw_s as haskellish suffixes (da17f99) Message-ID: <20150331101557.267A63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/da17f99bc6b1e90432108d430d4be1c503d4b977/ghc >--------------------------------------------------------------- commit da17f99bc6b1e90432108d430d4be1c503d4b977 Author: Thomas Miedema Date: Tue Mar 31 12:15:34 2015 +0200 Don't treat .hcr and .raw_s as haskellish suffixes .hcr: external core .raw_s: direct output from the c compiler, back in the day Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D777 >--------------------------------------------------------------- da17f99bc6b1e90432108d430d4be1c503d4b977 compiler/main/DriverPhases.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/compiler/main/DriverPhases.hs b/compiler/main/DriverPhases.hs index f1db9bc..e3aaf69 100644 --- a/compiler/main/DriverPhases.hs +++ b/compiler/main/DriverPhases.hs @@ -280,8 +280,9 @@ haskellish_src_suffixes, haskellish_suffixes, cish_suffixes, haskellish_user_src_suffixes, haskellish_sig_suffixes :: [String] haskellish_src_suffixes = haskellish_user_src_suffixes ++ - [ "hspp", "hscpp", "hcr", "cmm", "cmmcpp" ] -haskellish_suffixes = haskellish_src_suffixes ++ ["hc", "raw_s"] + [ "hspp", "hscpp", "cmm", "cmmcpp" ] +haskellish_suffixes = haskellish_src_suffixes ++ + [ "hc" ] cish_suffixes = [ "c", "cpp", "C", "cc", "cxx", "s", "S", "ll", "bc", "lm_s", "m", "M", "mm" ] -- Will not be deleted as temp files: haskellish_user_src_suffixes = From git at git.haskell.org Tue Mar 31 15:36:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Mar 2015 15:36:02 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: redirect stderr to /dev/null when running GS on bad.ps (8757e2d) Message-ID: <20150331153602.C88F13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8757e2db03d74ad8b0f9a0d32ddacd6ad616a795/ghc >--------------------------------------------------------------- commit 8757e2db03d74ad8b0f9a0d32ddacd6ad616a795 Author: Thomas Miedema Date: Tue Mar 31 14:12:52 2015 +0200 Testsuite: redirect stderr to /dev/null when running GS on bad.ps This is a followup to a3d0a7a0ba3a1ee458a9883011247561dfe22f4a. Reviewed by: Rufflewind Differential Revision: https://phabricator.haskell.org/D780 >--------------------------------------------------------------- 8757e2db03d74ad8b0f9a0d32ddacd6ad616a795 testsuite/driver/testlib.py | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index b0d552e..e178f2a 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -2060,7 +2060,8 @@ if config.have_profiling: if config.gs != '': resultGood = runCmdExitCode(genGSCmd(config.confdir + '/good.ps')); if resultGood == 0: - resultBad = runCmdExitCode(genGSCmd(config.confdir + '/bad.ps') + ' >/dev/null') + resultBad = runCmdExitCode(genGSCmd(config.confdir + '/bad.ps') + + ' >/dev/null 2>&1') if resultBad != 0: print("GhostScript available for hp2ps tests") gs_working = 1; From git at git.haskell.org Tue Mar 31 18:26:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Mar 2015 18:26:06 +0000 (UTC) Subject: [commit: ghc] master: uBackpack: simplified Backpack description. (694c4d5) Message-ID: <20150331182606.F28DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/694c4d543d94405ce13eb15ddf31db5cf58251dc/ghc >--------------------------------------------------------------- commit 694c4d543d94405ce13eb15ddf31db5cf58251dc Author: Edward Z. Yang Date: Tue Mar 24 12:28:16 2015 -0700 uBackpack: simplified Backpack description. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 694c4d543d94405ce13eb15ddf31db5cf58251dc docs/backpack/Makefile | 9 +- docs/backpack/backpack-impl.pdf | Bin 436890 -> 436175 bytes docs/backpack/ubackpack.pdf | Bin 0 -> 200784 bytes docs/backpack/ubackpack.tex | 381 ++++++++++++++++++++++++++++++++++++++++ 4 files changed, 387 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 694c4d543d94405ce13eb15ddf31db5cf58251dc