- 11 Apr, 2016 5 commits
-
-
Ryan Scott authored
While the deriving machinery always unifies the kind of the typeclass argument with the kind of the datatype, this proves not to be sufficient to produce well kinded instances for some poly-kinded datatypes. For example: ``` newtype Compose (f :: k2 -> *) (g :: k1 -> k2) (a :: k1) = Compose (f (g a)) deriving Functor ``` would fail because only `k1` would get unified with `*`, causing the following ill kinded instance to be generated: ``` instance (Functor (f :: k2 -> *), Functor (g :: * -> k2)) => Functor (Compose f g) where ... ``` To prevent this, we need to take the subtypes and unify their kinds with `* -> *`. Fixes #10524 for good. Test Plan: ./validate Reviewers: simonpj, hvr, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2097 GHC Trac Issues: #10524, #10561 (cherry picked from commit aadde2b9)
-
duairc authored
* `Identity` and `Const` now have `Num`, `Real`, `Integral`, `Fractional`, `Floating`, `RealFrac` and `RealFloat` instances * `Identity` and `Const` now have `Bits` and `FiniteBits` instances * `Identity` and `Const` now have `IsString` instances Reviewers: RyanGlScott, austin, hvr, bgamari, ekmett Reviewed By: ekmett Subscribers: nomeata, ekmett, RyanGlScott, thomie Differential Revision: https://phabricator.haskell.org/D2079 GHC Trac Issues: #11790 (cherry picked from commit 8b57cac5)
-
Ryan Scott authored
Previously, all kind arguments were being reified, which would cause something like this: ``` type Id a = a data Proxy (a :: Id k) = Proxy ``` to output ``` data Proxy (a :: Id * k) = Proxy ``` when `Proxy`'s `Info` is reified. The fix is simple: simply call `filterOutInvisibleTypes` on the kind arguments of a kind synonym application. Fixes #11463. Test Plan: ./validate Reviewers: austin, bgamari, goldfire Reviewed By: goldfire Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2081 GHC Trac Issues: #11463 (cherry picked from commit 02a5c580)
-
Rik Steenkamp authored
Now we check whether a closed type family's equation is headed with the correct type before we kind-check the equation. Also, instead of "expected only no parameters" we now generate the message "expected no parameters". Fixes #11623. Reviewers: simonpj, austin, bgamari Reviewed By: simonpj, bgamari Subscribers: simonpj, goldfire, thomie Differential Revision: https://phabricator.haskell.org/D2089 GHC Trac Issues: #11623 (cherry picked from commit 46e8f199)
-
- 10 Apr, 2016 15 commits
-
-
Tamar Christina authored
The Runtime Linker is currently eagerly loading all object files on all platforms which do not use the system linker for `GHCi`. The problem with this approach is that it requires all symbols to be found. Even those of functions never used/called. This makes the number of libraries required to link things like `mingwex` quite high. To work around this the `rts` was relying on a trick. It itself was compiled with `MingW64-w`'s `GCC`. So it was already linked against `mingwex`. As such, it re-exported the symbols from itself. While this worked it made it impossible to link against `mingwex` in user libraries. And with this means no `C99` code could ever run in `GHCi` on Windows without having the required symbols re-exported from the rts. Consequently this rules out a large number of packages on Windows. SDL2, HMatrix etc. After talking with @rwbarton I have taken the approach of loading entire object files when a symbol is needed instead of doing the dependency tracking on a per symbol basis. This is a lot less fragile and a lot less complicated to implement. The changes come down to the following steps: 1) modify the linker to and introduce a new state for ObjectCode: `Needed`. A Needed object is one that is required for the linking to succeed. The initial set consists of all Object files passed as arguments to the link. 2) Change `ObjectCode`'s to be indexed but not initialized or resolved. This means we know where we would load the symbols, but haven't actually done so. 3) Mark any `ObjectCode` belonging to `.o` passed as argument as required: ObjectState `NEEDED`. 4) During `Resolve` object calls, mark all `ObjectCode` containing the required symbols as `NEEDED` 5) During `lookupSymbol` lookups, (which is called from `linkExpr` and `linkDecl` in `GHCI.hs`) is the symbol is in a not-yet-loaded `ObjectCode` then load the `ObjectCode` on demand and return the address of the symbol. Otherwise produce an unresolved symbols error as expected. 6) On `unloadObj` we then change the state of the object and remove it's symbols from the `reqSymHash` table so it can be reloaded. This change affects all platforms and OSes which use the runtime linker. It seems there are no real perf tests for `GHCi`, but performance shouldn't be impacted much. We gain a lot of time not loading all `obj` files, and we lose some time in `lookupSymbol` when we're finding sections that have to be loaded. The actual finding itself is O(1) (Assuming the hashtnl is perfect) It also consumes slighly more memory as instead of storing just the address of a symbol I also store some other information, like if the symbol is weak or not. This change will break any packages relying on renamed POSIX functions that were re-named and re-exported by the rts. Any packages following the proper naming for functions as found on MSDN will work fine. Test Plan: ./validate on all platforms which use the Runtime linker. Reviewers: thomie, rwbarton, simonmar, erikd, bgamari, austin, hvr Reviewed By: erikd Subscribers: kgardas, gridaphobe, RyanGlScott, simonmar, rwbarton, #ghc_windows_task_force Differential Revision: https://phabricator.haskell.org/D1805 GHC Trac Issues: #11223 (cherry picked from commit 90538d86)
-
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 (cherry picked from commit 82e36edc)
-
Tamar Christina authored
Windows uses wchar_t* for paths. The code committed won't compile for Windows as the types are incorrect and the types in the branches of the ternary operator aren't consistent. Test Plan: ./validate --fast Reviewers: austin, rwbarton, erikd, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1878 (cherry picked from commit 01c587c0)
-
rwbarton authored
Test Plan: Actually run validate. This fixes test linker_error3. Reviewers: austin, erikd, bgamari Reviewed By: erikd, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1874 (cherry picked from commit 73293109)
-
rwbarton authored
Test Plan: Used this to track down an issue I was having. Reviewers: simonmar, austin, erikd, bgamari Reviewed By: erikd, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1863 (cherry picked from commit 34519f08)
-
Ben Gamari authored
Fixes #11818, where haddock's documentation broke `make install` when Sphinx is not available.
-
Ben Gamari authored
Otherwise we get a const-ness mismatch when we free the buffer, which for some reason gcc 5.3 didn't notice. (cherry picked from commit 378091c9)
-
Ryan Scott authored
Previously, deriving `Generic(1)` bailed out when attempting to instantiate visible type parameters (#5939), but this instantiation check was quite fragile and doesn't interact well with `-XTypeInType`. It has been decided that `Generic(1)` shouldn't be subjected to this check anyway, so it has been removed, and `gen_Generic_binds`'s machinery has been updated to substitute the type variables in a generated `Rep`/`Rep1` instance with the user-supplied type arguments. In addition, this also refactors `Condition` in `TcDeriv` a bit. Namely, since we no longer need `tc_args` to check any conditions, the `[Type]` component of `Condition` has been removed. Fixes #11732. Test Plan: ./validate Reviewers: goldfire, kosmikus, simonpj, bgamari, austin Reviewed By: simonpj, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2061 GHC Trac Issues: #5939, #11732 (cherry picked from commit 7443e5c8)
-
Ben Gamari authored
I have no idea where "4.11" came from. (cherry picked from commit ad532ded)
-
Jason Eisenberg authored
When the typechecker generates the error message for an out-of-scope variable, it now uses the GlobalRdrEnv with respect to which the variable is unbound, not the GlobalRdrEnv which is available at the time the error is reported. Doing so ensures we do not provide suggestions which themselves are out-of-scope (because they are bound in a later inter-splice group). Nonetheless, we do note in the error message if an unambiguous, exact match to the out-of-scope variable is found in a later inter-splice group, and we specify where that match is not in scope. Test Plan: ./validate Reviewers: goldfire, austin, bgamari Reviewed By: goldfire Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2000 GHC Trac Issues: #11680 (cherry picked from commit 470d4d5b)
-
conal authored
Needed for constructing correct constraint-satisfying code (particularly type class instances) in a Core-to-Core transformation. Reviewers: simonpj, austin, bgamari Reviewed By: austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2088 GHC Trac Issues: #11804 (cherry picked from commit 5a1add13)
-
Herbert Valerio Riedel authored
The commit 28f951ed introduced the `-fmax-pmcheck-iterations` flag and set the default limit to 1e7 iterations. However, this value is still high enough that it can result GHC to exhibit memory spikes beyond 1 GiB of RAM usage (heap profile showed several `(:)`s, as well as `THUNK_2_0`, and `PmCon` during the memory spikes) A value of 2e6 seems to be a safer upper bound which still manages to let the checker not run into the limit in most cases. Test Plan: Validate, try building a few Hackage packages Reviewers: austin, gkaracha, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2095 (cherry picked from commit d2e05c6b)
-
bollmann authored
Record selectors of data types spliced in with Template Haskell are not renamer-resolved correctly in GHC HEAD. The culprit is `newRecordSelector` which violates notes `Note [Binders in Template Haskell] in Convert.hs` and `Note [Looking up Exact RdrNames] in RnEnv.hs`. This commit fixes `newRecordSelector` accordingly. Test Plan: ./validate Reviewers: thomie, mpickering, bgamari, austin, simonpj, goldfire Reviewed By: goldfire Differential Revision: https://phabricator.haskell.org/D2091 GHC Trac Issues: #11809 (cherry picked from commit 2f82da76)
-
Chris Martin authored
This is another documentation addition similar to D1989, this time comparing the type of the Kleisli composition operator (<=<) to that of plain function composition (.). Reviewers: hvr, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2100 (cherry picked from commit 90d66ded)
-
Michael Snoyman authored
In my testing, the worker/wrapper transformation applied here significantly decreases the number of allocations performed when using replicateM_. Additionally, this version of the function behaves correctly for negative numbers (namely, it will behave the same as replicateM_ 0, which is what previous versions of base have done). Reviewers: bgamari, simonpj, hvr, austin Reviewed By: bgamari, simonpj, austin Subscribers: nomeata, simonpj, mpickering, thomie Differential Revision: https://phabricator.haskell.org/D2086 GHC Trac Issues: #11795 (cherry picked from commit c4a7520e)
-
- 08 Apr, 2016 2 commits
-
-
Ben Gamari authored
69822f0c broke this as it held on to a reference into the `arg` string, which is later freed. Humbug. Test Plan: Try using filtering Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2090 GHC Trac Issues: #11810 (cherry picked from commit 535896e5)
-
Ben Gamari authored
Previously the `_static` and `_sources` directories were installed in the wrong parents. See #11803 (cherry picked from commit 6b6bebaf)
-
- 06 Apr, 2016 10 commits
-
-
Simon Peyton Jones authored
This just adds the Prox stuff from the Description in Trac #11376 to the test case, The class stuff seems weird becuase the type is ambiguous (cherry picked from commit b3ecd047)
-
Ben Gamari authored
-
Ben Gamari authored
-
Ben Gamari authored
-
Ben Gamari authored
-
Ben Gamari authored
It's been quite a while since this has happened for some of our tests.
-
Ben Gamari authored
Shifts by amounts greater-than-or-equal-to the word size are undefined.
-
Ben Gamari authored
-
Simon Peyton Jones authored
See Trac #11376 and Note [Deeply instantiate in :type] in TcRnDriver Sadly this showed up one new problem (Trac #11786) and one opportunity (Trac #11787), so test T11549 is now marked expect-broken on these two. (cherry picked from commit f2a2b79f)
-
- 05 Apr, 2016 2 commits
-
-
Herbert Valerio Riedel authored
This fixes a bug where warnings actually controlled by - `Opt_WarnUnusedMatches` - `Opt_WarnUnusedTypePatterns` - `Opt_WarnUnusedTopBinds` were incorrectly reported as being controlled by `Opt_WarnUnusedLocalBinds` as well This bug was introduced in bb5afd3c while implementing #10752 Test Plan: ./validate still running -- testsuite output wiggles expected Reviewers: barrucadu, quchen, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2077 (cherry picked from commit 003e0802fdc2b38b2c3e96cdd387619d33c44967)
-
Jason Eisenberg authored
Stable pointers can now be safely dereferenced while the stable pointer table is simultaneously being enlarged. Test Plan: ./validate Reviewers: ezyang, austin, bgamari, simonmar Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D2031 GHC Trac Issues: #10296 (cherry picked from commit 90d7d608)
-
- 04 Apr, 2016 4 commits
-
-
Eric Seidel authored
We originally wanted CallStacks to be opt-in, but dealing with let binders complicated things, forcing us to infer CallStacks. It turns out that the inference is actually unnecessary though, we can let the wanted CallStacks bubble up to the outer context by refusing to quantify over them. Eventually they'll be solved from a given CallStack or defaulted to the empty CallStack if they reach the top. So this patch prevents GHC from quantifying over CallStacks, getting us back to the original plan. There's a small ugliness to do with PartialTypeSignatures, if the partial theta contains a CallStack constraint, we *do* want to quantify over the CallStack; the user asked us to! Note that this means that foo :: _ => CallStack foo = getCallStack callStack will be an *empty* CallStack, since we won't infer a CallStack for the hole in the theta. I think this is the right move though, since we want CallStacks to be opt-in. One can always write foo :: (HasCallStack, _) => CallStack foo = getCallStack callStack to get the CallStack and still have GHC infer the rest of the theta. Test Plan: ./validate Reviewers: goldfire, simonpj, austin, hvr, bgamari Reviewed By: simonpj, bgamari Subscribers: bitemyapp, thomie Projects: #ghc Differential Revision: https://phabricator.haskell.org/D1912 GHC Trac Issues: #11573 (cherry picked from commit 7407a66d)
-
Ben Gamari authored
(cherry picked from commit 9b6820cd)
-
Rik Steenkamp authored
Add the function `pprPatSynType :: PatSyn -> SDoc` for printing pattern synonym types, and remove the ambiguous `patSynType` function. Also, the types in a `PatSyn` are now tidy. Haddock submodule updated to reflect the removal of `patSynType` by mpickering. Fixes: #11213. Reviewers: goldfire, simonpj, austin, mpickering, bgamari Reviewed By: simonpj, mpickering Subscribers: bollmann, simonpj, thomie Differential Revision: https://phabricator.haskell.org/D1896 GHC Trac Issues: #11213 (cherry picked from commit 72bd7f7b)
-
niteria authored
`ghc` fails without `-dep-suffix ''`. Test Plan: visual inspection Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie, simonmar Differential Revision: https://phabricator.haskell.org/D2075 (cherry picked from commit 38068913)
-
- 31 Mar, 2016 1 commit
-
-
Simon Peyton Jones authored
Richard accidetally introduced this change in his big kind-equality patch. The code is wrong, and potentially could cause binders to be re-ordered. Worth merging to 8.0. (cherry picked from commit da260a5b)
-
- 30 Mar, 2016 1 commit
-
-
Simon Peyton Jones authored
See Note [Eta-reduction in -O0] in DynFlags. Bottom line: doing eta reduction unconditionally is benign, and removes an ASSERT failure (Trac #11562). (cherry picked from commit 85008555)
-