- Dec 02, 2014
-
-
Herbert Valerio Riedel authored
Effective immediately, pushing to the `libraries/parallel` submodule requires pushing via ssh://git@github.com/haskell/parallel.git.
-
The QuickCheck property now succeeds: prop :: Fixed B7 -> Bool prop a = read (show a) == a This changes the Show instance for Fixed to round up, rather than down when calculating a digit. This needs to happen because Read also rounds down: data B7 instance HasResolution B7 where resolution _ = 128 1 / 128 = 0.0078125 read "0.007" = (0.000 :: Fixed B7) Here is an example of the change to Show: showFixed False (0.009 :: Fixed B7) -- Broken: "0.007" -- Fixed: "0.008" And now Read can continue to round down: read "0.008" = (0.0078125 :: Fixed B7) Reviewed By: hvr, ekmett Differential Revision: https://phabricator.haskell.org/D547
-
Herbert Valerio Riedel authored
Currently it's an AND when at least one of the operands is big. Reviewed By: hvr Differential Revision: https://phabricator.haskell.org/D549
-
Simon Peyton Jones authored
The problem and its solution are explained in Note [Auxiliary binders] in TcGenDeriv
-
Simon Peyton Jones authored
If we have data family D a data instance D (a,b,c) = ... deriving( Data ) then we want to generate instance ... => Data (D (a,b,c)) where ... dataCast1 x = gcast1 x The "1" here comes from the kind of D. But the kind of the *representation* TyCon is data Drep a b c = .... ie Drep :: * -> * -> * -> * So we must look for the *family* TyCon in this (rather horrible) dataCast1 / dataCast2 binding.
-
Simon Peyton Jones authored
This patch is all small stuff - Move VisibleOrphanModules from Module to InstEnv (with the other orphan stuff) - Move Notes about orphans from IfaceSyn to InstEnv (ditto) - Make use of the record field names in InstEnvs
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
This is a long-overdue renaming Untouchables --> TcLevel It is renaming only; no change in functionality. We really wanted to get this done before the 7.10 fork.
-
Jan Stolarek authored
-
Jan Stolarek authored
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
Simon Peyton Jones authored
This reverts commit b5e8b3b1. I reverted it because one of these two patches 9e6e4796 Add purgeObj() b5e8b3b1 Make the linker API thread-safe causes a seg-fault on Windows. The seg-fault happens immediately the linker is invoked, in ghci or in Template Haskell. I believe that it is the "linker API thread-safe" commit that causes the seg-fault; it happens even if the "purgeObj" commit alone is reverted. But since the two patches mess with the same code, to revert the "linker API" patch I had revert both.
-
Simon Peyton Jones authored
This reverts commit 9e6e4796. I reverted it because one of these two patches 9e6e4796 Add purgeObj() b5e8b3b1 Make the linker API thread-safe causes a seg-fault on Windows. The seg-fault happens immediately the linker is invoked, in ghci or in Template Haskell. I believe that it is the "linker API thread-safe" commit that causes the seg-fault; it happens even if the "purgeObj" commit alone is reverted. But since the two patches mess with the same code, to revert the "linker API" patch I had revert both.
-
Simon Peyton Jones authored
-
Herbert Valerio Riedel authored
This replaces the note mentioning the lack of a `Natural`-type by a note pointing to the new "Numeric.Natural" (#9818) module.
-
- Dec 01, 2014
-
-
Herbert Valerio Riedel authored
Don't pass empty string `[]` as "action-if-not-given" to `AC_ARG_ENABLE()` macro, as this would otherwise lead to an empty else-block in the resulting bash `configure` script. This bug was introduced via cb0a503a. This issue was pointed out by @christiaanb Reviewed By: christiaanb Differential Revision: https://phabricator.haskell.org/D545
-
Simon Peyton Jones authored
{-# NOUNPACK #-} {-# NOUNPACK #-} ! were being parsed the same way. The former was wrong. Thanks to Alan Zimmerman for pointing this out
-
Simon Peyton Jones authored
Fixed by e6a2050e along with #9582, #9833
-
Thomas Miedema authored
Summary: Commit 37d64a51 removed the preprocessing step for Parser.y. Reviewers: rodlogic, austin Reviewed By: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D543
-
Simon Peyton Jones authored
Sorry about this. I somehow failed to include this one line in my patch.
-
Simon Peyton Jones authored
This finally solves the issue of instance-method signatures that are more polymorphic than the instanted class method. See Note [Instance method signatures] in TcInstDcls. A very nice fix for the two Trac tickets above.
-
Herbert Valerio Riedel authored
Differential Revision: https://phabricator.haskell.org/D544
-
Herbert Valerio Riedel authored
Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D541
-
Herbert Valerio Riedel authored
This reverts commit 460eebec. Thomas requested to revert the commit with the words: > Please revert this commit, it is horribly wrong. I'll have a proper look > later, but not supplying `-traditional` to the C preprocessor is the cause > of #9828. the reverted commit was related to #9094
-
- Nov 30, 2014
-
-
Herbert Valerio Riedel authored
Fwiw, this wasn't really a proper .lhs to begin with...
-
Herbert Valerio Riedel authored
Reviewers: austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D540
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
sivteck authored
Summary: This patch changes the error message as suggested in trac issue #8815 comments. Reviewers: jstolarek, austin Reviewed By: jstolarek, austin Subscribers: jstolarek, thomie, carter Differential Revision: https://phabricator.haskell.org/D533 GHC Trac Issues: #8815
-
Austin Seipp authored
Summary: Signed-off-by: Austin Seipp <austin@well-typed.com> Test Plan: `./validate` Reviewers: hvr Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D537
-
Peter Trommler authored
Summary: In a statically linked GHCi symbol `environ` resolves to NULL when called from a Haskell script. When resolving symbols in a Haskell script we need to search the executable program and its dependent (DT_NEEDED) shared libraries first and then search the loaded libraries. We want to be able to override functions in loaded libraries later. Libraries must be opened with local scope (RTLD_LOCAL) and not global. The latter adds all symbols to the executable program's symbols where they are then searched in loading order. We want reverse loading order. When libraries are loaded with local scope the dynamic linker cannot use symbols in that library when resolving the dependencies in another shared library. This changes the way files compiled to object code must be linked into temporary shared libraries. We link with the last temporary shared library created so far if it exists. Since each temporary shared library is linked to the previous temporary shared library the dynamic linker finds the latest definition of a symbol by following the dependency chain. See also Note [RTLD_LOCAL] for a summary of the problem and solution. Cherry-picked commit 2f8b4c Changed linker argument ordering On some ELF systems GNU ld (and others?) default to --as-needed and the order of libraries in the link matters. The last temporary shared library, must appear before all other libraries. Switching the position of extra_ld_inputs and lib_path_objs does that. Fixes #8935 and #9186 Reviewers: austin, hvr, rwbarton, simonmar Reviewed By: simonmar Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D349 GHC Trac Issues: #8935, #9186, #9480
-
Lennart Kolmodin authored
Summary: The bash completion is simple but works both for ghc and ghci. The README explains to the user what they have to do to get it working (hopefully nothing). Test Plan: Follow the README, then enjoy the cli completion in your terminal! Reviewers: austin Subscribers: thomie, carter, jstolarek Differential Revision: https://phabricator.haskell.org/D536 GHC Trac Issues: #9005
-
Alan Zimmerman authored
Summary: Attaching semis to preceding AST element, not following Test Plan: sh ./validate Reviewers: hvr, austin Reviewed By: austin Subscribers: cactus, thomie, carter Differential Revision: https://phabricator.haskell.org/D529
-
Lennart Kolmodin authored
Summary: Shorten long lines in DynFlags. Describe --show-options in ghci usage guide. Reviewers: jstolarek, austin Reviewed By: jstolarek, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D532 GHC Trac Issues: #9259
-
Edward Z. Yang authored
Summary: Amazingly, the fix for this very old bug is quite simple: when type-checking, maintain a set of "visible orphan modules" based on the orphans list of modules which we explicitly imported. When we import an instance and it is an orphan, we check if it is in the visible modules set, and if not, ignore it. A little bit of refactoring for when orphan-hood is calculated happens so that we always know if an instance is an orphan or not. For GHCi, we preinitialize the visible modules set based on the list of interactive imports which are active. Future work: Cache the visible orphan modules set for GHCi, rather than recomputing it every type-checking round. (But it's tricky what to do when you /remove/ a module: you need a data structure a little more complicated than just a set of modules.) Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: new tests and validate Reviewers: simonpj, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D488 GHC Trac Issues: #2182
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
- Nov 29, 2014
-
-
Herbert Valerio Riedel authored
`gcdExtInteger` has been available since `integer-gmp-0.5.1` (added via 71e29584)
-
Herbert Valerio Riedel authored
This also exposes the following two type-specialised modular exponentiation variants of `recipModInteger` useful for implementing a `recipModNatural` operation. recipModBigNat :: BigNat -> BigNat -> BigNat recipModWord :: Word# -> Word# -> Word# `recipModInteger` has been available since `integer-gmp-0.5.1` (added via 4d516855)
-
Herbert Valerio Riedel authored
This makes use of the `powMod*` primitives provided by `integer-gmp-1.0.0`. This is the `Natural`-version of the related `GHC.Integer.GMP.Internals.powModInteger` operation. The fallback implementation uses a square and multiply algorithm, compared to which the optimized GMP-based implementation needs much less allocations due to in-place mutation during the computation.
-
Herbert Valerio Riedel authored
This also exposes the following type-specialised modular exponentiation variants of `powModInteger` useful for implementing a `powModNatural` operation. powModBigNat :: BigNat -> BigNat -> BigNat -> BigNat powModBigNatWord :: BigNat -> BigNat -> Word# -> Word# powModWord :: Word# -> Word# -> Word# -> Word# `powModInteger` has been available since `integer-gmp-0.5.1` (added via 4d516855)
-
Herbert Valerio Riedel authored
A few instances were missed in 447f5926 Moreover, be more paranoid when testing for zero values, and try harder to avoid passing denormalized zero `mpz_t`-values into GMP functions.
-