- 25 Sep, 2017 9 commits
-
-
Tamar Christina authored
Summary: Ar was being checked twice prior to D3883 where I removed one of the checks because the converted path was being overridden after the check because of the second check for Ar. However the one in configure.ac was a target check so I'm changing the path check to a target check now. Test Plan: ./configure Reviewers: angerman, austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, erikd GHC Trac Issues: #14274 Differential Revision: https://phabricator.haskell.org/D4020
-
Tamar Christina authored
Summary: Something seems to be changing stderr into binary mode, so when the `traceIO` is called, the C code that ultimately calls `vfprintf` is using a binary mode handle. This causes newlines not to be encoded properly. The patch ensures we're in text mode when writing the debug messages (% interleaving as it's not thread safe at all) and restores the previous mode when done. I'm slightly concerned about the performance implications of writing large dumps out in text mode, but I think the current behavior is not intended as I cannot see any of the printing code setting the mode of the std handles. Test Plan: ./validate Reviewers: austin, bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #14188 Differential Revision: https://phabricator.haskell.org/D4018
-
Ryan Scott authored
Summary: Now that `MonadIO` is a superclass of `Quasi`, it's a good time to bump the `template-haskell` version so that libraries can accommodate the change using CPP. Test Plan: ./validate Reviewers: bgamari, austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4007
-
Ryan Scott authored
Summary: Up until now, the knowledge of how GHC chooses which `COMPLETE` set to use in the presence of multiple applicable `COMPLETE` sets for a single data type constructor was only documented in the GHC wiki. But this really should be advertised to anyone who uses `COMPLETE` pragmas heavily, so per SPJ's advice in https://ghc.haskell.org/trac/ghc/ticket/14253#comment:10, this adds this wisdom to the GHC users' guide. Test Plan: Read it Reviewers: austin, bgamari Subscribers: mpickering, rwbarton, thomie GHC Trac Issues: #14253 Differential Revision: https://phabricator.haskell.org/D4005
-
Simon Peyton Jones authored
Trac #14218 showed that we were not solving implicit-parameter constraints correctly. In particular, - A tuple constraint could "hide" an implicit-parameter wanted constraint, and that in turn could that we solved it from the wrong implicit-parameter binding. - As a special case the HasCallStack constraint (which is just short for (IP "callStack" CallStack), was getting mis-solved. The big change is to arrange that, in TcSMonad.findDict when looking for a dictionary, either when looking for a matching inert or solved dictionary, we fail for - Tuples that are hiding implicit parameters See Note [Tuples hiding implicit parameters] - HasCallStack constraints where we have not yet pushed on the call-site info See Note [Solving CallStack constraints] I also did a little refactoring * Move naturallyCoherentClass from Class to TcInteract, its sole use site. Class.hs seems like the wrong place. (And I also do not understand the reason that we need the eq/Coercible/ Typable stuff in this predicate, but I'll tackle that separately.) * Move the code that pushes call-site info onto a call stack from the "interact" part to the "canonicalise" part of the solver.
-
Simon Peyton Jones authored
This patch does two things: * When reporting a hole, we now include its kind if the kind is not just '*'. This addresses Trac #14265 * When reporting things like "'a' is a rigid type varaible bound by ...", this patch arranges to group the type variables together, so we don't repeat the "bound by..." stuff endlessly
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
This just does wrapping on very long lists
-
Simon Peyton Jones authored
For reasons explained in TcHsType Note [Extra-constraint holes in partial type signatures], if we had f :: (_) => blahs and the '_' was filled in by more than a 62-tuple of contraints, GHC crashed. The same Note explains the hacky solution I have adopted to evade this. Maybe there is some better way, but I couldn't see one that didn't involve a great deal of work. And the problem is a very narrow one! If the hack bites us we'll need to think again.
-
- 24 Sep, 2017 3 commits
-
-
Sergei Trofimovich authored
AsmTempLabel is really a label that describes label in assembly output (or equivalent like LLVM IR). Unregisterised build does not handle it correctly. This change does not fix UNREG build failure in Ticket #14264 but reverts back to panic: pprCLbl AsmTempLabel Signed-off-by:
Sergei Trofimovich <slyfox@gentoo.org>
-
Herbert Valerio Riedel authored
This reverts commit cc6be3a2. because it caused the regression #14270 which according to Richard probably doesn't have an easy fix. So this one goes back to the drawning board. This reopens #14236
-
Moritz Angermann authored
Summary: The SMP causes <> to be exported from Prelude by default. When building HEAD with HEAD, genapply suffers from <> being imported from Prelude. Reviewers: hvr, bgamari, austin Reviewed By: hvr Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4015
-
- 23 Sep, 2017 2 commits
-
-
Moritz Angermann authored
Summary: This is another fallout from 8b007abb should fix Trac #14264. I am not sure if this is complete. It does however allow me to build an iOS LLVM cross compiler. Reviewers: bgamari, trofi, austin, simonmar Reviewed By: trofi Subscribers: rwbarton, thomie GHC Trac Issues: #14264 Differential Revision: https://phabricator.haskell.org/D4014
-
Moritz Angermann authored
Summary: This should help resolve the compilcation that came up in Trac #14261 Test Plan: validate on various platforms Reviewers: trofi, bgamari, austin, hvr Reviewed By: trofi Subscribers: rwbarton, thomie, erikd GHC Trac Issues: #14261 Differential Revision: https://phabricator.haskell.org/D4004
-
- 22 Sep, 2017 7 commits
-
-
Ben Gamari authored
Should fix the win32 build.
-
Herbert Valerio Riedel authored
This is a consequence of NoImplicitPrelude which was introduced in f63bc730.
-
Herbert Valerio Riedel authored
This effectively broke `make sdist`; the surprising thing is that ./validate didn't catch this (and thus the buildbots didn't either). Also, I would have expected `EXTRA_PACKAGES` to be populated by the data in `./packages` which already encodes that information... This is a follow-up to 02ff7056
-
Moritz Angermann authored
In 8b007abb (nativeGen: Consistently use blockLbl to generate CLabels from BlockIds) all blockLbls were changed. This interfered with the `toInfoLbl` call in CmmProcPoint, and caused the LLVM backend to fall over. Reviewers: bgamari, austin, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4006
-
Facundo Domínguez authored
This allows template-haskell code to add plugins to the compilation pipeline. Otherwise, the user would have to pass -fplugin=... to ghc. For now, plugin modules in the current package can't be used. This is because when TH runs, it is too late to let GHC know that the plugin modules needed to be compiled first. Test Plan: ./validate Reviewers: simonpj, bgamari, austin, goldfire Reviewed By: bgamari Subscribers: angerman, rwbarton, mboes, thomie GHC Trac Issues: #13608 Differential Revision: https://phabricator.haskell.org/D3821
-
Ben Gamari authored
Reviewers: austin, erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3937
-
Ben Gamari authored
Reviewers: austin, erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3985
-
- 21 Sep, 2017 13 commits
-
-
Herbert Valerio Riedel authored
This completes the 2nd phase of the Semigroup=>Monoid Proposal (SMP) initiated in 8ae263ce. This updates a couple submodules to address <> naming clashes.
-
Ben Gamari authored
Simonpj suggested this as a follow-on to #14226 to avoid code duplication. This also gives us the ability to CBE cases involving foreign calls for free. Test Plan: Validate Reviewers: austin, simonmar, simonpj Reviewed By: simonpj Subscribers: michalt, simonpj, rwbarton, thomie GHC Trac Issues: #14226 Differential Revision: https://phabricator.haskell.org/D3999
-
Ben Gamari authored
It looks like this is probably just drift.
-
Matthías Páll Gissurarson authored
This builds on the previous "Valid substitutions include..." functionality, but add subsumption checking as well, so that the suggested valid substitutions show not only exact matches, but also identifiers that fit the hole by virtue of subsuming the type of the hole (i.e. being more general than the type of the hole). Building on the previous example, in the given program ``` ps :: String -> IO () ps = putStrLn ps2 :: a -> IO () ps2 _ = putStrLn "hello, world" main :: IO () main = _ "hello, world" ``` The results would be something like ``` • Found hole: _ :: [Char] -> IO () • In the expression: _ In the expression: _ "hello, world" In an equation for ‘main’: main = _ "hello, world" • Relevant bindings include main :: IO () (bound at t1.hs:8:1) Valid substitutions include ps :: String -> IO () (defined at t1.hs:2:1) ps2 :: forall a. a -> IO () (defined at t1.hs:5:1) putStrLn :: String -> IO () (imported from ‘Prelude’ at t1.hs:1:1 (and originally defined in ‘System.IO’)) fail :: forall (m :: * -> *). Monad m => forall a. String -> m a (imported from ‘Prelude’ at t1.hs:1:1 (and originally defined in ‘GHC.Base’)) mempty :: forall a. Monoid a => a (imported from ‘Prelude’ at t1.hs:1:1 (and originally defined in ‘GHC.Base’)) print :: forall a. Show a => a -> IO () (imported from ‘Prelude’ at t1.hs:1:1 (and originally defined in ‘System.IO’)) (Some substitutions suppressed; use -fmax-valid-substitutions=N or -fno-max-valid-substitutions) ``` Signed-off-by:
Matthías Páll Gissurarson <mpg@mpg.is> Modified according to suggestions from Simon PJ Accept tests that match the expectations, still a few to look better at Swithced to using tcLookup, after sit down with SPJ at ICFP. Implications are WIP. Now works with polymorphism and constraints! We still need to merge the latest master, before we can make a patch. Wrap the type of the hole, instead of implication shenanigans, As per SPJs suggestion, this is simpler and feels closer to what we actually want to do. Updated tests with the new implementation Remove debugging trace and update documentation Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: RyanGlScott, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3930
-
Ben Gamari authored
Bumps numerous submodules. Reviewers: austin, hvr Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3974
-
Ben Gamari authored
-
Ben Gamari authored
Test Plan: Validate Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #13929 Differential Revision: https://phabricator.haskell.org/D3993
-
Ben Gamari authored
Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3997
-
Adam Gundry authored
Test Plan: new test for #13847, and the test for #13644 now passes Reviewers: mpickering, austin, bgamari, simonpj Reviewed By: mpickering, simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #13644, #13847 Differential Revision: https://phabricator.haskell.org/D3988
-
Ben Gamari authored
This allows withTypeable to be used with things that are of kind other than Type. Test Plan: Validate Reviewers: austin, hvr, dfeuer Reviewed By: dfeuer Subscribers: rwbarton, thomie, dfeuer Differential Revision: https://phabricator.haskell.org/D3996
-
Ben Gamari authored
Test Plan: T14236 Reviewers: austin, hvr, goldfire Reviewed By: goldfire Subscribers: RyanGlScott, simonpj, rwbarton, goldfire, thomie, dfeuer GHC Trac Issues: #14236 Differential Revision: https://phabricator.haskell.org/D3969
-
Mathieu Boespflug authored
-
Ryan Scott authored
-
- 20 Sep, 2017 2 commits
-
-
Sergei Trofimovich authored
The only reason I noticed is warning these lines on linux: ``` $ ./configure --target=sparc-unknown-linux-gnu ... ./configure: line 9708: cygpath: command not found ./configure: line 9708: ArCmd: command not found ``` POSIX shell syntax requires no spaces in assignments. Fixed guarding condition while at it. Signed-off-by:
Sergei Trofimovich <slyfox@gentoo.org>
-
Herbert Valerio Riedel authored
This is a preparation for `haskeline` picking up a dependency on `stm` real soon now. See https://github.com/judah/haskeline/pull/61 for details. If we figure out a way to not bundle the libraries depended upon by the GHCi executable in the global package database (see #8919 for the original reason why we had to start bundling terminfo/haskeline in the first place) we can get rid of `stm` again... On the bright side, we were able to avoid uploading new `stm` releases for over two years already, so it shouldn't cause too much trouble if GHC imposes a strong preference on the `stm` package's version (this most likely will mostly affect Linux distributions & similiar). While at it, this also update the stm submodule to include relaxed bounds to allow the upcoming base-4.11 version.
-
- 19 Sep, 2017 4 commits
-
-
Tao He authored
Reviewers: austin, hvr, bgamari, dfeuer Reviewed By: dfeuer Subscribers: rwbarton, thomie GHC Trac Issues: #14224 Differential Revision: https://phabricator.haskell.org/D3986
-
ocheron authored
The function existed in integer-gmp-0.5.1.0 but was removed as part of integer-gmp2 rewrite in #9281. This is to bring it back. Test Plan: Case integerGmpInternals, with GMP 4.3.2 and GMP 6.1.2 Reviewers: austin, hvr, goldfire, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3947
-
Ben Gamari authored
As noted in #14226, the common block elimination pass currently implements an extremely strict equivalence relation, demanding that two blocks are equivalent including the names of their local registers. This is quite restrictive and severely hampers the effectiveness of the pass. Here we allow the CBE pass to collapse blocks which are equivalent up to alpha renaming of locally-bound local registers. This is completely safe and catches many more duplicate blocks. Test Plan: Validate Reviewers: austin, simonmar, michalt Reviewed By: michalt Subscribers: rwbarton, thomie GHC Trac Issues: #14226 Differential Revision: https://phabricator.haskell.org/D3973
-
Arnaud Spiwack authored
`mkCoreApps` re-implemented `mkCoreApp` in a recursive function, rather than using a simple `foldl'` in order to avoid repeatingly computing the type of the function argument. I've factored the two logic into a new (internal) function `mkCoreType` which assumes that the type is known. `mkCoreApp` and `mkCoreApps` are thin wrappers around it. Differences - The assertion failure message of `mkCoreApps` has more information in it. - `mkCoreApps` now special-cases coercion argument like `mkCoreApp` (previously they were given to `mk_val_app` instead) Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3971
-