- Jan 14, 2018
-
-
Simon Peyton Jones authored
Trac #13032 pointed out that we sometimes generate unused bindings for Givens, and (worse still) we can't always discard them later (we don't drop a case binding unless we can prove that the scrutinee is non-bottom. It looks as if this may be a major reason for the performace problems in #14338 (see comment:29). This patch fixes the problem at source, by pruning away all the dead Givens. See Note [Delete dead Given evidence bindings] Remarkably, compiler allocation falls by 23% in perf/compiler/T12227! I have not confirmed whether this change actualy helps with (cherry picked from commit 954cbc7c)
-
- Sep 19, 2017
-
-
This switches the compiler/ component to get compiled with -XNoImplicitPrelude and a `import GhcPrelude` is inserted in all modules. This is motivated by the upcoming "Prelude" re-export of `Semigroup((<>))` which would cause lots of name clashes in every modulewhich imports also `Outputable` Reviewers: austin, goldfire, bgamari, alanz, simonmar Reviewed By: bgamari Subscribers: goldfire, rwbarton, thomie, mpickering, bgamari Differential Revision: https://phabricator.haskell.org/D3989
-
- Mar 01, 2017
-
-
David Feuer authored
The fundamental problem with `type UniqSet = UniqFM` is that `UniqSet` has a key invariant `UniqFM` does not. For example, `fmap` over `UniqSet` will generally produce nonsense. * Upgrade `UniqSet` from a type synonym to a newtype. * Remove unused and shady `extendVarSet_C` and `addOneToUniqSet_C`. * Use cached unique in `tyConsOfType` by replacing `unitNameEnv (tyConName tc) tc` with `unitUniqSet tc`. Reviewers: austin, hvr, goldfire, simonmar, niteria, bgamari Reviewed By: niteria Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D3146
-
- Feb 03, 2017
-
-
Sylvain Henry authored
This patch converts the 4 lasting static flags (read from the command line and unsafely stored in immutable global variables) into dynamic flags. Most use cases have been converted into reading them from a DynFlags. In cases for which we don't have easy access to a DynFlags, we read from 'unsafeGlobalDynFlags' that is set at the beginning of each 'runGhc'. It's not perfect (not thread-safe) but it is still better as we can set/unset these 4 flags before each run when using GHC API. Updates haddock submodule. Rebased and finished by: bgamari Test Plan: validate Reviewers: goldfire, erikd, hvr, austin, simonmar, bgamari Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2839 GHC Trac Issues: #8440
-
- Feb 01, 2017
-
-
This major patch implements Join Points, as described in https://ghc.haskell.org/trac/ghc/wiki/SequentCore. You have to read that page, and especially the paper it links to, to understand what's going on; but it is very cool. It's Luke Maurer's work, but done in close collaboration with Simon PJ. This Phab is a squash-merge of wip/join-points branch of http://github.com/lukemaurer/ghc. There are many, many interdependent changes. Reviewers: goldfire, mpickering, bgamari, simonmar, dfeuer, austin Subscribers: simonpj, dfeuer, mpickering, Mikolaj, thomie Differential Revision: https://phabricator.haskell.org/D2853
-
- Nov 25, 2016
-
-
Simon Peyton Jones authored
I need this in a later patch
-
- Aug 25, 2016
-
-
Joachim Breitner authored
this fixes #12368. It also refactors dmdFix a bit, removes some redundancies (such as passing around an strictness signature right next to an id, when that id is guaranteed to have been annotated with that strictness signature). Note that when fixed-point iteration does not terminate, we conservatively delete their strictness signatures (set them to nopSig). But this loses the information on how its strict free variables are used! Lazily used variables already escape via lazy_fvs. We ensure that in the case of an aborted fixed-point iteration, also the strict variables are put there (with a conservative demand of topDmd). Differential Revision: https://phabricator.haskell.org/D2392
-
- Aug 05, 2016
-
-
Ben Gamari authored
This adds notes to the Haddock documentation for various core datatypes expanding abbreviations. Reviewers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D2406 GHC Trac Issues: #12405
-
- Jul 05, 2016
-
-
niteria authored
varEnvElts can introduce unnecessary nondeterminism and we can finally remove it, so that no one will use it by accident. If someone wants to use varEnvElts they should either use DVarEnv or use nonDetEltsUFM and document why it doesn't introduce nondeterminism. GHC Trac: #4012
-
- Jun 18, 2016
-
-
Ömer Sinan Ağacan authored
-
- Jun 07, 2016
-
-
niteria authored
This eradicates varSetElems from the codebase. This function used to introduce nondeterminism. I've also documented benign nondeterminism in three places. GHC Trac: #4012
-
- May 24, 2016
-
-
niteria authored
I've changed the functions to their nonDet equivalents and explained why they're OK there. This allowed me to remove foldNameSet, foldVarEnv, foldVarEnv_Directly, foldVarSet and foldUFM_Directly. Test Plan: ./validate, there should be no change in behavior Reviewers: simonpj, simonmar, austin, goldfire, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2244 GHC Trac Issues: #4012
-
- May 18, 2016
-
-
niteria authored
The order inert_model and intert_eqs fold affects the order that the typechecker looks at things. I've been able to experimentally confirm that the order of equalities and the order of the model matter for determinism. This is just a straigthforward replacement of nondeterministic VarEnv for deterministic DVarEnv. Test Plan: ./validate Reviewers: simonpj, goldfire, austin, bgamari, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2232 GHC Trac Issues: #4012
-
- May 12, 2016
-
-
niteria authored
We need the order of specialized binds and rules to be deterministic, so we use a deterministic set here. Test Plan: ./validate Reviewers: simonmar, bgamari, austin, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2197 GHC Trac Issues: #4012
-
- May 04, 2016
-
-
niteria authored
Summary: foldUFM introduces unnecessary non-determinism that actually leads to different generated code as explained in Note [TrieMap determinism]. As we're switching from UniqFM to UniqDFM here you might be concerned about performance. There's nothing that ./validate detects. nofib reports no change in Compile Allocations, but Compile Time got better on some tests and worse on some, yielding this summary: -1 s.d. ----- -3.8% +1 s.d. ----- +5.4% Average ----- +0.7% This is not a fair comparison as the order of Uniques changes what GHC is actually doing. One benefit from making this deterministic is also that it will make the performance results more stable. Full nofib results: P108 Test Plan: ./validate, nofib Reviewers: goldfire, simonpj, simonmar, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2169 GHC Trac Issues: #4012
-
- Feb 16, 2016
-
-
Reviewers: bgamari, austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1915
-
- Jan 26, 2016
-
-
Simon Peyton Jones authored
With -dppr-debug the output for the (ofen-large) InScope set was overwhelming. This makes it smaller. Only affects debugging.
-
- Jan 19, 2016
-
-
niteria authored
This adds sanity checks to `substTy` that implement: > when calling substTy subst ty it should be the case that the in-scope > set in the substitution is a superset of > * The free vars of the range of the substitution > * The free vars of ty minus the domain of the substitution and replaces violators with unchecked version. The violators were found by running the GHC test suite. This ensures that I can work on this incrementally and that what I fix won't be undone by some other change. It also includes a couple of fixes that I've already done. Test Plan: ./validate Reviewers: simonmar, goldfire, simonpj, austin, bgamari Reviewed By: simonpj, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1792 GHC Trac Issues: #11371
-
- Jan 18, 2016
-
-
Jan Stolarek authored
Summary: In the past the canonical way for constructing an SDoc string literal was the composition `ptext . sLit`. But for some time now we have function `text` that does the same. Plus it has some rules that optimize its runtime behaviour. This patch takes all uses of `ptext . sLit` in the compiler and replaces them with calls to `text`. The main benefits of this patch are clener (shorter) code and less dependencies between module, because many modules now do not need to import `FastString`. I don't expect any performance benefits - we mostly use SDocs to report errors and it seems there is little to be gained here. Test Plan: ./validate Reviewers: bgamari, austin, goldfire, hvr, alanz Subscribers: goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1784
-
- Jan 08, 2016
-
-
This was non-obvious to me when reading the sources and the paper provides the motivation and explores the design space. Test Plan: just a comment Reviewers: simonpj, austin, ezyang, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1749
-
- Dec 11, 2015
-
-
Richard Eisenberg authored
This implements the ideas originally put forward in "System FC with Explicit Kind Equality" (ICFP'13). There are several noteworthy changes with this patch: * We now have casts in types. These change the kind of a type. See new constructor `CastTy`. * All types and all constructors can be promoted. This includes GADT constructors. GADT pattern matches take place in type family equations. In Core, types can now be applied to coercions via the `CoercionTy` constructor. * Coercions can now be heterogeneous, relating types of different kinds. A coercion proving `t1 :: k1 ~ t2 :: k2` proves both that `t1` and `t2` are the same and also that `k1` and `k2` are the same. * The `Coercion` type has been significantly enhanced. The documentation in `docs/core-spec/core-spec.pdf` reflects the new reality. * The type of `*` is now `*`. No more `BOX`. * Users can write explicit kind variables in their code, anywhere they can write type variables. For backward compatibility, automatic inference of kind-variable binding is still permitted. * The new extension `TypeInType` turns on the new user-facing features. * Type families and synonyms are now promoted to kinds. This causes trouble with parsing `*`, leading to the somewhat awkward new `HsAppsTy` constructor for `HsType`. This is dispatched with in the renamer, where the kind `*` can be told apart from a type-level multiplication operator. Without `-XTypeInType` the old behavior persists. With `-XTypeInType`, you need to import `Data.Kind` to get `*`, also known as `Type`. * The kind-checking algorithms in TcHsType have been significantly rewritten to allow for enhanced kinds. * The new features are still quite experimental and may be in flux. * TODO: Several open tickets: #11195, #11196, #11197, #11198, #11203. * TODO: Update user manual. Tickets addressed: #9017, #9173, #7961, #10524, #8566, #11142. Updates Haddock submodule.
-
- Oct 30, 2015
-
-
When generating dictionary let binds in dsTcEvBinds we may end up generating them in arbitrary order according to Unique order. Consider: ``` let $dEq = GHC.Classes.$fEqInt in let $$dNum = GHC.Num.$fNumInt in ... ``` vs ``` let $dNum = GHC.Num.$fNumInt in let $dEq = GHC.Classes.$fEqInt in ... ``` The way this change fixes it is by using `UniqDFM` - a type of deterministic finite maps of things keyed on `Unique`s. This way when you pull out evidence variables corresponding to type-class dictionaries they are in deterministic order. Currently it's the order of insertion and the way it's implemented is by tagging the values with the time of insertion. Test Plan: I've added a new test case to reproduce the issue. ./validate Reviewers: ezyang, simonmar, austin, simonpj, bgamari Reviewed By: simonmar, simonpj, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1396 GHC Trac Issues: #4012
-
- Aug 21, 2015
-
-
This reverses some of the work done in #1405, and goes back to the assumption that the bootstrap compiler understands GHC-haskell. In particular: * use MagicHash instead of _ILIT and _CLIT * pattern matching on I# if possible, instead of using iUnbox unnecessarily * use Int#/Char#/Addr# instead of the following type synonyms: - type FastInt = Int# - type FastChar = Char# - type FastPtr a = Addr# * inline the following functions: - iBox = I# - cBox = C# - fastChr = chr# - fastOrd = ord# - eqFastChar = eqChar# - shiftLFastInt = uncheckedIShiftL# - shiftR_FastInt = uncheckedIShiftRL# - shiftRLFastInt = uncheckedIShiftRL# * delete the following unused functions: - minFastInt - maxFastInt - uncheckedIShiftRA# - castFastPtr - panicDocFastInt and pprPanicFastInt * rename panicFastInt back to panic# These functions remain, since they actually do something: * iUnbox * bitAndFastInt * bitOrFastInt Test Plan: validate Reviewers: austin, bgamari Subscribers: rwbarton Differential Revision: https://phabricator.haskell.org/D1141 GHC Trac Issues: #1405
-
- Dec 03, 2014
-
-
Austin Seipp authored
Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
- Dec 16, 2013
-
-
Joachim Breitner authored
by adding Notes and using easier to understand combinators.
-
- Nov 06, 2013
-
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
- Oct 01, 2013
-
-
Simon Marlow authored
-
- Aug 28, 2012
-
-
Simon Peyton Jones authored
(Before merging to HEAD we need to tidy up and write a proper commit message.)
-
- Nov 04, 2011
-
-
Ian Lynagh authored
We only use it for "compiler" sources, i.e. not for libraries. Many modules have a -fno-warn-tabs kludge for now.
-
- Jul 28, 2011
-
-
Simon Peyton Jones authored
I need these for a trie data structure I'm working on
-
- Jul 27, 2011
-
-
Simon Peyton Jones authored
-
- Jul 21, 2011
-
-
Simon Peyton Jones authored
-
- Jun 29, 2011
-
-
batterseapower authored
-
- Apr 19, 2011
-
-
Simon Peyton Jones authored
See the paper "Practical aspects of evidence based compilation in System FC" * Coercion becomes a data type, distinct from Type * Coercions become value-level things, rather than type-level things, (although the value is zero bits wide, like the State token) A consequence is that a coerion abstraction increases the arity by 1 (just like a dictionary abstraction) * There is a new constructor in CoreExpr, namely Coercion, to inject coercions into terms
-
- Dec 02, 2010
-
-
Simon Peyton Jones authored
See Note [Matching lets], which explains it all in detail. It took me a day to think of a nice way to fix the bug, but I think the result is quite respectable. Subtle, though.
-
- Oct 19, 2010
-
-
Simon Peyton Jones authored
-
- Oct 07, 2010
-
-
Simon Peyton Jones authored
Previously it was rejecting the match Template: forall s t. map s t Actual: map Int t which should obviously be fine. It turns out that this kind of match comes up when specialising. By freshening that t we could avoid the difficulty, but morally the (forall t) binds t and the rule should be alpha-equivalent regardless of the forall'd variables. This patch makes it so, and incidentally makes matching a little more efficient. See Note [Eta expansion] in VarEnv.
-
- Sep 13, 2010
-
-
Simon Peyton Jones authored
This major patch implements the new OutsideIn constraint solving algorithm in the typecheker, following our JFP paper "Modular type inference with local assumptions". Done with major help from Dimitrios Vytiniotis and Brent Yorgey.
-