- Mar 11, 2016
-
-
`AC_PACKAGE_TARNAME` is used by autoconf to generate the default value of docdir, which we now set to include a version number (see #11354). This fixed #11659. Test Plan: `./configure --help`, validate Reviewers: austin, thomie, hvr, erikd Reviewed By: hvr, erikd Subscribers: erikd Differential Revision: https://phabricator.haskell.org/D1983 GHC Trac Issues: #11659
-
Test Plan: read it Reviewers: austin, goldfire Reviewed By: goldfire Subscribers: hvr, thomie Differential Revision: https://phabricator.haskell.org/D1981 GHC Trac Issues: #11679
-
The original TH failure observed by the ticket, namely that Template Haskell quotes of data instance GADTs are broken, is not observable anymore in HEAD. I therefore just added the corresponding regression test. Test Plan: ./validate Reviewers: goldfire, austin, thomie, jstolarek, bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D1978 GHC Trac Issues: #11145
-
Previously ```lang=haskell catch (error "uh oh") (\(_ :: SomeException) -> print "it failed") ``` would unexpectedly fail with "uh oh" instead of the handler being run due to the strictness of `catch` in its first argument. See #11555 for details. Test Plan: Validate Reviewers: austin, hvr, simonpj Reviewed By: simonpj Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D1973 GHC Trac Issues: #11555
-
These are cases in the standard library that may benefit from the strictness signature of catchException and where we know that the action won't bottom. Test Plan: Validate, carefully consider changed callsites Reviewers: austin, hvr Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1972
-
Ben Gamari authored
-
Edward Z. Yang authored
I'm not sure if this fix is the "right way" to do it, but it solves the proximal problem, which is that lookupBindGroupOcc was picking out the wrong renaming for hs-boot signatures, which then lead to an interface file error. Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: simonpj, hvr, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1963 GHC Trac Issues: #11624
-
- Mar 10, 2016
-
-
Sergei Trofimovich authored
Looking at more failures on m68k (Trac #11395) I've noticed the arith001 and arith012 test failures. (--host=x86_64-linux --target=m68k-linux). The following example was enough to reproduce a problem: v :: Float v = 43 main = print v m68k binaries printed '0.0' instead of '43.0'. The bug here is how we encode Floats and Double as Words with the same binary representation. Floats: Before the patch we just coerced Float to Int. That breaks when we cross-compile from 64-bit LE to 32-bit BE. The patch fixes conversion by accounting for padding. when we extend 32-bit value to 64-bit value (LE and BE do it slightly differently). Doubles: Before the patch Doubles were coerced to a pair of Ints (not correct as x86_64 can hold Double in one Int) and then trucated this pair of Ints to pair of Word32. The patch fixes conversion by always decomposing in Word32 and accounting for host endianness (newly introduced hostBE) and target endianness (wORDS_BIGENDIAN). I've tested this patch on Double and Float conversion on --host=x86_64-linux --target=m68k-linux crosscompiler. It fixes 10 tests related to printing Floats and Doubles. Thanks to Bertram Felgenhauer who poined out this probem. Signed-off-by:
Sergei Trofimovich <siarheit@google.com> Test Plan: checked some examples manually, fixed 10 tests in test suite Reviewers: int-e, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1990 GHC Trac Issues: #11395
-
- Mar 09, 2016
-
-
Herbert Valerio Riedel authored
-
Simon Peyton Jones authored
Just comments, a bit of refactoring, and a better error-reporting infrastructure
-
Simon Peyton Jones authored
'lazy' was doing part of its job, but not all! In particular, an application f (lazy e) where f is strict, was still being compiled using call-by-value in CorePrep. This defeated the purpose of defining catch as catch a b = catch# (lazy a) b See Trac #11555, and Neil Mitchell's test case in comment:14 This patch makes 'lazy' behave properly. I updated Note [lazyId magic] in MkId, but all the action is in CorePrep. I can't say I really like this, but it does the job.
-
- Mar 08, 2016
-
-
Herbert Valerio Riedel authored
When `MonadFail`is available, this patch makes `MonadFail` a superclass of `Quasi`, and `Q` an instance of `MonadFail`. NB: Since f16ddcee, we need to be able to compile `template-haskell` with stage0 compilers that don't provide a `MonadFail` class yet. Once we reach GHC 8.3 development we can drop the CPP conditionals again. Addresses #11661 Reviewed By: bgamari, goldfire Differential Revision: https://phabricator.haskell.org/D1982
-
Herbert Valerio Riedel authored
GHC 8.1's template-haskell package requires base>=4.8 anyway, so we can assume Numeric.Natural to be available unconditionally.
-
Herbert Valerio Riedel authored
As per #6032, `Rank2Types` and `PolymorphicComponents` have been deprecated in favour of `RankNTypes`. also update `other-extensions` in template-haskell.cabal flag to reflect reality.
-
Sergei Trofimovich authored
Before the patch both Cmm and C symbols were declared with 'EF_' macro: #define EF_(f) extern StgFunPtr f() but for Cmm symbols we know exact prototypes. The patch splits there prototypes in to: #define EFF_(f) void f() /* See Note [External function prototypes] */ #define EF_(f) StgFunPtr f(void) Cmm functions are 'EF_' (External Functions), C functions are 'EFF_' (External Foreign Functions). While at it changed external C function prototype to return 'void' to workaround ghc bug on m68k. Described in detail in Trac #11395. This makes simple tests work on m68k-linux target! Thanks to Michael Karcher for awesome analysis happening in Trac #11395. Signed-off-by:
Sergei Trofimovich <siarheit@google.com> Test Plan: ran "hello world" on m68k successfully Reviewers: simonmar, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1975 GHC Trac Issues: #11395
-
- Mar 07, 2016
-
-
niteria authored
This patch brings in two improvements: a) m32_allocator will now reuse the pages that are no longer used by anyone else. b) m32_allocator will preallocate the "filling" area, so that the pages it allocates end up as a big chunk instead of being allocated on demand in random places, fragmenting the precious lower 2G address space. Test Plan: testsuite - 3 tests failing with substTy asserts Reviewers: ezyang, austin, bgamari, erikd, hsyl20, simonmar Reviewed By: hsyl20, simonmar Subscribers: hvr, thomie Differential Revision: https://phabricator.haskell.org/D1976
-
Ben Gamari authored
This reverts commit 90fa8cf2. As noted in #11643, these should be fixed. Updates hpc submodule.
-
Test Plan: Build with clang Reviewers: thomie, rwbarton, austin, bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D1977
-
- Mar 06, 2016
-
-
Sergei Trofimovich authored
The bug is observed on m68k-linux target as crash in RTS: -- a.hs: main = print 43 $ inplace/bin/ghc-stage1 --make -debug a.hs $ ./a Program terminated with signal SIGSEGV, Segmentation fault. #0 0x80463b0a in LOOKS_LIKE_INFO_PTR_NOT_NULL (p=32858) at includes/rts/storage/ClosureMacros.h:248 (gdb) bt #0 0x80463b0a in LOOKS_LIKE_INFO_PTR_NOT_NULL (p=32858) at includes/rts/storage/ClosureMacros.h:248 #1 0x80463b46 in LOOKS_LIKE_INFO_PTR (p=32858) at includes/rts/storage/ClosureMacros.h:253 #2 0x80463b6c in LOOKS_LIKE_CLOSURE_PTR ( p=0x805aac6e <stg_dummy_ret_closure>) at includes/rts/storage/ClosureMacros.h:258 #3 0x80463e4c in initStorage () at rts/sm/Storage.c:121 #4 0x8043ffb4 in hs_init_ghc (...) at rts/RtsStartup.c:181 #5 0x80455982 in hs_main (...) at rts/RtsMain.c:51 #6 0x80003c1c in main () GHC assumes last 2 pointer bits are tags on 32-bit targets. But here 'stg_dummy_ret_closure' address violates the assumption: LOOKS_LIKE_CLOSURE_PTR (p=0x805aac6e <stg_dummy_ret_closure>) I've added compiler hint for static StgClosure objects to align closures at least by their natural alignment (what GHC assumes). See Note [StgWord alignment]. Signed-off-by:
Sergei Trofimovich <siarheit@google.com> Test Plan: ran basic test on m68k qemu, it got past ASSERTs Reviewers: simonmar, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1974 GHC Trac Issues: #11395
-
- Mar 05, 2016
-
-
A record pattern match, construction or update like `Rec { Mod.f }` should expand to `Rec { Mod.f = f }` rather than `Rec { Mod.f = Mod.f }`. Test Plan: New test rename/should_compile/T11662 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: hesselink, thomie Differential Revision: https://phabricator.haskell.org/D1965 GHC Trac Issues: #11662
-
A safe import is unnecessary considering rtsSupportsBoundThreads simply returns a constant. This commit doesn't fix the main issue of ticket #9696 that "readRawBufferPtr and writeRawBufferPtr allocate memory". Reviewers: bgamari, austin, hvr Reviewed By: hvr Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1964 GHC Trac Issues: #9696
-
Now the existentially quantified type variables are printed at the correct location when printing a pattern synonym type from an `IfacePatSyn`. The function `pprIfaceContextMaybe` has been removed as it is no longer needed. Fixes #11524. Reviewers: austin, goldfire, thomie, bgamari, mpickering Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D1958 GHC Trac Issues: #11524
-
This patch addresses GHCi load/reload space leaks which could be fixed without adversely affecting performance. Test Plan: make test "TEST=T4029" Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: mpickering, thomie Differential Revision: https://phabricator.haskell.org/D1950 GHC Trac Issues: #4029
-
Sylvain Henry authored
Reviewers: erikd, simonmar, austin, bgamari Reviewed By: simonmar, bgamari Subscribers: hvr, thomie Differential Revision: https://phabricator.haskell.org/D1947 GHC Trac Issues: #10840
-
Ben Gamari authored
-
- Mar 04, 2016
-
-
Ben Gamari authored
-
Ben Gamari authored
-
- Mar 02, 2016
-
-
Simon Peyton Jones authored
A bit more efficient
-
Simon Peyton Jones authored
The bug was in this code: go subst (TyConApp tc tys) | Just (tenv, rhs, tys') <- expandSynTyCon_maybe tc tys = let subst' = unionTCvSubst subst (mkTvSubstPrs tenv) in go subst' (mkAppTys rhs tys') This is wrong in two ways. * It is wrong to apply the expanded substitution to tys', * The unionTCvSubst is utterly wrong; after all, rhs is completely separate, and the union makes a non-idempotent substitution. It was the non-idempotency that gave the Lint failure in Trac #11665, when there was a type synonym whose RHS mentioned another type synonym, something like type T a b = a -> b type S x y = T y x It only affects SpecConstr because that's about the only place where expandTypeSyonym is called. I tried to trigger the failure with a simple test case, but failed, so I have not added a regression test. Fortunately the solution is very simple and solid. FWIW, the culprit was 674654, "Add kind equalities to GHC".
-
- Mar 01, 2016
-
-
Simon Peyton Jones authored
This fixes Trac #11643. It's a corner case, now documented in Note [Linting rules] in CoreLint
-
Simon Peyton Jones authored
These extra tests were added by Richard when he had CoVars floating around in places where previously only TyVars had been. But fortunately those days are gone, so these tests are unnecessary, and are slowing GHC down. Let's remove them.
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
With this patch we no longer check the RHS of a type synonym declaration for ambiguity. It only affects type synonyms with foralls on the RHS (which are rare in the first place), and it's arguably over-aggressive to check them for ambiguity. See TcValidity Note [When we don't check for ambiguity] This fixes the ASSERT failures in th T3100 typecheck/should_compile T3692 typecheck/should_fail T3592
-
- Feb 29, 2016
-
-
Thomas Miedema authored
-
Thomas Miedema authored
-
Thomas Miedema authored
-
Thomas Miedema authored
Might be a little faster. Avoids testing for #6113 (.prof file not written when process is killed with any signal but SIGINT) for tests that don't have a .prof.sample file (which is almost all of them) when running the profiling ways. Tests that were failing because of #6113: T8089, overflow1, overflow2 and overflow3.
-
Test Plan: It works, I promise. Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1956 GHC Trac Issues: #11370
-
When building the bundled GMP sources, the `HOSTPLATFORM` value was passed to the `--host` flag of the `./configure` call. This is incorrect: when building a cross-compiler, e.g. a compiler targeting ARM but running on X86, the host on which GMP will run is ARM, i.e. the target platform of the compiler, and the host platform (i.e. the platform on which the compiler will run) is X86. See e.g. [1] for more information about the meaning of and relation between build, host and target. [1] https://www.gnu.org/software/autoconf/manual/ autoconf-2.65/html_node/Specifying-Target-Triplets.html Test Plan: Building ARM cross-compiler with `integer-gmp` Reviewers: thomie, gracjan, austin, erikd, Phyx, hvr, bgamari Reviewed By: erikd, bgamari Subscribers: erikd, gracjan Differential Revision: https://phabricator.haskell.org/D1960
-