summaryrefslogtreecommitdiff
path: root/compiler
Commit message (Collapse)AuthorAgeFilesLines
* Reimplement Stream in "yoneda" style for efficiencywip/stream-rewriteMatthew Pickering2021-02-226-111/+119
| | | | | | | | | | | | | | | | | | | | | | | | | | | | 'Stream' is implemented in the "yoneda" style for efficiency. By representing a stream in this manner 'fmap' and '>>=' operations are accumulated in the function parameters before being applied once when the stream is destroyed. In the old implementation each usage of 'mapM' and '>>=' would traverse the entire stream in order to apply the substitution at the leaves. It is well-known for free monads that this representation can improve performance, and the test results demonstrate this for GHC as well. The operation mapAccumL is not used in the compiler and can't be implemented efficiently because it requires destroying and rebuilding the stream. I removed one use of mapAccumL_ which has similar problems but the other use was difficult to remove. In the future it may be worth exploring whether the 'Stream' encoding could be modified further to capture the mapAccumL pattern, and likewise defer the passing of accumulation parameter until the stream is finally consumed. The >>= operation for 'Stream' was a hot-spot in the ticky profile for the "ManyConstructors" test which called the 'cg' function many times in "StgToCmm.hs" Metric Decrease: ManyConstructors
* Fix #19377 by using lookupLOcc when desugaring TH-quoted ANNsRyan Scott2021-02-171-4/+7
| | | | | | | | | | Previously, the desugarer was looking up names referenced in TH-quoted `ANN`s by using `globalVar`, which would allocate a fresh TH `Name`. In effect, this would prevent quoted `ANN`s from ever referencing the correct identifier `Name`, leading to #19377. The fix is simple: instead of `globalVar`, use `lookupLOcc`, which properly looks up the name of the in-scope identifier. Fixes #19377.
* UnVarGraph: Improve asymptoticsBen Gamari2021-02-171-30/+66
| | | | | | | | | | | | | | | | | | This is a redesign of the UnVarGraph data structure used by the call arity analysis to avoid the pathologically-poor performance observed in issue #18789. Specifically, deletions were previously O(n) in the case of graphs consisting of many complete (bipartite) sub-graphs. Together with the nature of call arity this would produce quadratic behavior. We now encode deletions specifically, taking care to do some light normalization of empty structures. In the case of the `Network.AWS.EC2.Types.Sum` module from #19203, this brings the runtime of the call-arity analysis from over 50 seconds down to less than 2 seconds. Metric Decrease: T15164 WWRec
* CallArity: Small optimisations and strictnessBen Gamari2021-02-171-2/+4
|
* PPC NCG: print procedure end label for debugPeter Trommler2021-02-171-5/+11
| | | | Fixes #19118
* Parse symbolic names in ANN type correctly with otyconRyan Scott2021-02-161-1/+7
| | | | | | | | | | | | | | | | | This adds a new `otycon` production to the parser that allows for type constructor names that are either alphanumeric (`tycon`) or symbolic (`tyconsym`), where the latter must be parenthesized appropriately. `otycon` is much like the existing `oqtycon` production, except that it does not permit qualified names. The parser now uses `otycon` to parse type constructor names in `ANN type` declarations, which fixes #19374. To make sure that all of this works, I added three test cases: * `should_compile/T19374a`: the original test case from #19374 * `should_fail/T19374b`: a test that makes sure that an `ANN` with a qualified name fails to parse * `should_fail/T19374c`: a test that makes sure that an `ANN type` with a qualified name fails to parse
* Avoid false redundant import warning with DisambiguateRecordFieldsAdam Gundry2021-02-161-6/+8
| | | | | Fixes #17853. We mustn't discard the result of pickGREs, because doing so might lead to incorrect redundant import warnings.
* Avoid useless w/w splitSimon Peyton Jones2021-02-162-96/+139
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch is just a tidy-up for the post-strictness-analysis worker wrapper split. Consider f x = x Strictnesss analysis does not lead to a w/w split, so the obvious thing is to leave it 100% alone. But actually, because the RHS is small, we ended up adding a StableUnfolding for it. There is some reason to do this if we choose /not/ do to w/w on the grounds that the function is small. See Note [Don't w/w inline small non-loop-breaker things] But there is no reason if we would not have done w/w anyway. This patch just moves the conditional to later. Easy. This does move some -ddump-simpl printouts around a bit. I also discovered that the previous code was overwritten an InlineCompulsory with InlineStable, which is utterly wrong. That in turn meant that some default methods (marked InlineCompulsory) were getting their InlineCompulsory squashed. This patch fixes that bug --- but of course that does mean a bit more inlining! Metric Decrease: T9233 T9675 Metric Increase: T12707 T11374 T3064 T4029 T9872b T9872d haddock.Cabal
* Use explicit import list for Data.ListOleg Grenrus2021-02-161-1/+1
|
* Don't build extra object with -no-hs-mainSylvain Henry2021-02-162-12/+25
| | | | | | | | We don't need to compile/link an additional empty C file when it is not needed. This patch may also fix #18938 by avoiding trying to lookup the RTS unit when there is none (yet) in the unit database.
* Make sure HasField use counts for -Wunused-top-bindsAdam Gundry2021-02-163-2/+23
| | | | | | This is a small fix that depends on the previous commit, because it corrected the rnExpr free variable calculation for HsVars which refer to ambiguous fields. Fixes #19213.
* Implement NoFieldSelectors extension (ghc-proposals 160)Adam Gundry2021-02-1620-257/+710
| | | | | | | | | | | | | | | | | | | | | Fixes #5972. This adds an extension NoFieldSelectors to disable the generation of selector functions corresponding to record fields. When this extension is enabled, record field selectors are not accessible as functions, but users are still able to use them for record construction, pattern matching and updates. See Note [NoFieldSelectors] in GHC.Rename.Env for details. Defining the same field multiple times requires the DuplicateRecordFields extension to be enabled, even when NoFieldSelectors is in use. Along the way, this fixes the use of non-imported DuplicateRecordFields in GHCi with -fimplicit-import-qualified (fixes #18729). Moreover, it extends DisambiguateRecordFields to ignore non-fields when looking up fields in record updates (fixes #18999), as described by Note [DisambiguateRecordFields for updates]. Co-authored-by: Simon Hafner <hafnersimon@gmail.com> Co-authored-by: Fumiaki Kinoshita <fumiexcel@gmail.com>
* Document word-size rounding of ByteArray# memory (Fix #14731)Daniel Gröber2021-02-141-1/+2
|
* Improve ByteArray# documentation regarding alignmentDaniel Gröber2021-02-141-2/+3
|
* Fix over-eager inlining in SimpleOptSimon Peyton Jones2021-02-146-40/+109
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | In GHC.Core.SimpleOpt, I found that its inlining could duplicate an arbitary redex inside a lambda! Consider (\xyz. x+y). The occurrence-analysis treats the lamdda as a group, and says that both x and y occur once, even though the occur under the lambda-z. See Note [Occurrence analysis for lambda binders] in OccurAnal. When the lambda is under-applied in a call, the Simplifier is careful to zap the occ-info on x,y, because they appear under the \z. (See the call to zapLamBndrs in simplExprF1.) But SimpleOpt missed this test, resulting in #19347. So this patch * commons up the binder-zapping in GHC.Core.Utils.zapLamBndrs. * Calls this new function from GHC.Core.Opt.Simplify * Adds a call to zapLamBndrs to GHC.Core.SimpleOpt.simple_app This change makes test T12990 regress somewhat, but it was always very delicate, so I'm going to put up with that. In this voyage I also discovered a small, rather unrelated infelicity in the Simplifier: * In GHC.Core.Opt.Simplify.simplNonRecX we should apply isStrictId to the OutId not the InId. See Note [Dark corner with levity polymorphism] It may never "bite", because SimpleOpt should have inlined all the levity-polymorphic compulsory inlnings already, but somehow it bit me at one point and it's generally a more solid thing to do. Fixing the main bug increases runtime allocation in test perf/should_run/T12990, for (acceptable) reasons explained in a comement on Metric Increase: T12990
* Drop GHC_LOADED_IN_GHCIBen Gamari2021-02-143-36/+0
| | | | | | | This previously supported the ghc-in-ghci script which has been since dropped. Hadrian's ghci support does not need this macro (which disabled uses of UnboxedTuples) since it uses `-fno-code` rather than produce bytecode.
* Introduce keepAlive primopBen Gamari2021-02-144-1/+54
|
* StringBuffer: Use unsafeWithForeignPtrBen Gamari2021-02-141-12/+18
|
* GHC.Utils.Binary: Eliminate allocating withForeignPtr usesBen Gamari2021-02-141-7/+16
|
* Fix a serious bug in roughMatchTcsSimon Peyton Jones2021-02-138-71/+110
| | | | | | | | | | | | | | | | | | | | | | | | | | | The roughMatchTcs function enables a quick definitely-no-match test in lookupInstEnv. Unfortunately, it didn't account for type families. This didn't matter when type families were flattened away, but now they aren't flattened it matters a lot. The fix is very easy. See INVARIANT in GHC.Core.InstEnv Note [ClsInst laziness and the rough-match fields] Fixes #19336 The change makes compiler perf worse on two very-type-family-heavy benchmarks, T9872{a,d}: T9872a(normal) ghc/alloc 2172536442.7 2216337648.0 +2.0% T9872d(normal) ghc/alloc 614584024.0 621081384.0 +1.1% (Everything else is 0.0% or at most 0.1%.) I think we just have to put up with this. Some cases were being wrongly filtered out by roughMatchTcs that might actually match, which could lead to false apartness checks. And it only affects these very type-family-heavy cases. Metric Increase: T9872a T9872d
* Remove deprecated -XGenerics and -XMonoPatBindsKrzysztof Gogolewski2021-02-132-19/+1
| | | | | They have no effect since 2011 (GHC 7.2/7.4), commits cb698570b2b and 49dbe60558.
* Always set `safeInferred`, not only when it turns `False`Joachim Breitner2021-02-131-4/+3
| | | | | | | | | | | | | | | previously, `safeFlagCheck` would be happy to switch the `safeFlag` to `False`, but not the other way around. This meant that after :set -XGeneralizedNewtypeDeriving :set -XNoGeneralizedNewtypeDeriving in GHCi all loaded files would be still be infered as unsafe. This fixes #19243. This is a corner case, but somewhat relevant once ghci by default starts with `GeneralizedNewtypeDeriving` on (due to GHC2021).
* Refactor LoggerSylvain Henry2021-02-1372-1494/+1830
| | | | | | | | | | | | | | | | | | | | | Before this patch, the only way to override GHC's default logging behavior was to set `log_action`, `dump_action` and `trace_action` fields in DynFlags. This patch introduces a new Logger abstraction and stores it in HscEnv instead. This is part of #17957 (avoid storing state in DynFlags). DynFlags are duplicated and updated per-module (because of OPTIONS_GHC pragma), so we shouldn't store global state in them. This patch also fixes a race in parallel "--make" mode which updated the `generatedDumps` IORef concurrently. Bump haddock submodule The increase in MultilayerModules is tracked in #19293. Metric Increase: MultiLayerModules
* Fix a long standing bug in constraint solvingSimon Peyton Jones2021-02-093-20/+78
| | | | | | | | | | | | | | | | When combining Inert: [W] C ty1 ty2 Work item: [D] C ty1 ty2 we were simply discarding the Derived one. Not good! We should turn the inert back into [WD] or keep both. E.g. fundeps work only on Derived (see isImprovable). This little patch fixes it. The bug is hard to tickle, but #19315 did so. The fix is a little messy (see Note [KeepBoth] plus the change in addDictCt), but I am disinclined to refine it further because it'll all be swept away when we Kill Deriveds.
* Fix pretty-printing of invisible arguments for FUN 'Many (#19310)Krzysztof Gogolewski2021-02-091-2/+4
|
* Reduce inlining in deeply-nested casesSimon Peyton Jones2021-02-096-26/+175
| | | | | | | | | | | | This adds a new heuristic, controllable via two new flags to better tune inlining behaviour. The new flags are -funfolding-case-threshold and -funfolding-case-scaling which are document both in the user guide and in Note [Avoid inlining into deeply nested cases]. Co-authored-by: Andreas Klebinger <klebinger.andreas@gmx.at>
* Fix typosBrian Wignall2021-02-0648-67/+67
|
* Make pattern synonyms play with CallStackSimon Peyton Jones2021-02-061-2/+27
| | | | | | | | This small patch makes pattern synonyms play nicely with CallStack constraints, using logic explained in GHC.Tc.Gen.Pat Note [Call-stack tracing of pattern synonyms] Fixes #19289
* Make unsafeDupablePerformIO have a lazy demandAndreas Klebinger2021-02-061-34/+8
| | | | | | | | | | | | | | | | | | | | | | | | | | When a user writes code like: unsafePerformIO $ do let x = f x writeIORef ref x return x We might expect that the write happens before we evaluate `f x`. Sadly this wasn't to case for reasons detailed in #19181. We fix this by avoiding the strict demand by turning: unsafeDupablePerformIO (IO m) = case runRW# m of (# _, a #) -> a into unsafeDupablePerformIO (IO m) = case runRW# m of (# _, a #) -> lazy a This makes the above code lazy in x. And ensures the side effect of the write happens before the evaluation of `f x`. If a user *wants* the code to be strict on the returned value he can simply use `return $! x`. This fixes #19181
* Fix buglet in expandSynTyCon_maybeSimon Peyton Jones2021-02-061-5/+6
| | | | | | | | | | The fix for #17958, implemented in MR !2952, introduced a small bug in GHC.Core.TyCon.expandSynTyCon_maybe, in the case of under-saturated type synonyms. This MR fixes the bug, very easy. Fixes #19279
* The Char kind (#11342)Daniel Rogozin2021-02-0628-115/+406
| | | | | | | | | | | | | | | | | | | | | | Co-authored-by: Rinat Stryungis <rinat.stryungis@serokell.io> Implement GHC Proposal #387 * Parse char literals 'x' at the type level * New built-in type families CmpChar, ConsSymbol, UnconsSymbol * New KnownChar class (cf. KnownSymbol and KnownNat) * New SomeChar type (cf. SomeSymbol and SomeNat) * CharTyLit support in template-haskell Updated submodules: binary, haddock. Metric Decrease: T5205 haddock.base Metric Increase: Naperian T13035
* Mark both parameters of SimplM one-shot (#19302)Sebastian Graf2021-02-051-2/+7
| | | | | | | Just marking the `SimplTopEnv` parameter as one-shot was not enough to eta-expand `simplExpr`. Fixes #19302.
* FFI: Revisit fix pass small ints in foreign call wrappersStefan Schulze Frielinghaus2021-02-051-26/+5
| | | | | | | Since commit be5d74ca small ints/words are passed according to their natural size which obsoletes fix from commit 01f7052cc1. Reverted 01f7052cc1 but kept the introduced test case.
* IntVar: fix allocation sizeSylvain Henry2021-02-051-2/+2
| | | | | | As found by @phadej in https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4740/diffs#note_327510 Also fix FastMutInt which allocating the size in bits instead of bytes.
* Try eta expanding FCode (See #18202)Andreas Klebinger2021-02-052-2/+33
| | | | | | | | | Also updates the note with the case of multi-argument lambdas. Seems slightly beneficial based on the Cabal test: -O0: -1MB allocations (out of 50GB) -O : -1MB allocations (out of ~200GB)
* UnVarGraph: Use foldl' rather than foldr in unionUnVarSetsBen Gamari2021-02-051-1/+1
| | | | | This is avoids pushing the entire list to the stack before we can begin computing the result.
* CallArity: Various comment fixesBen Gamari2021-02-051-10/+10
|
* typecheck: Eliminate allocations in tc_eq_typeBen Gamari2021-02-021-13/+36
| | | | | | | | | | Previously tc_eq_type would allocate a number of closures due to the two boolean "mode" flags, despite the fact that these were always statically known. To avoid this we force tc_eq_type to inline into its call sites, allowing the simplifier to eliminate both some runtime branches and the closure allocations.
* Introduce the DecoratedSDoc typeAlfredo Di Napoli2021-02-0118-111/+125
| | | | | This commit introduces a DecoratedSDoc type which replaces the old ErrDoc, and hopefully better reflects the intent.
* Rename ErrMsg into MsgEnvelopeAlfredo Di Napoli2021-02-0118-129/+143
| | | | Updates Haddock submodule
* Remove ErrDoc and MsgDocAlfredo Di Napoli2021-02-0137-297/+272
| | | | | | | | | | | | | This commit boldly removes the ErrDoc and the MsgDoc from the codebase. The former was introduced with the only purpose of classifying errors according to their importance, but a similar result can be obtained just by having a simple [SDoc], and placing bullets after each of them. On top of that I have taken the perhaps controversial decision to also banish MsgDoc, as it was merely a type alias over an SDoc and as such it wasn't offering any extra type safety. Granted, it was perhaps making type signatures slightly more "focused", but at the expense of cognitive burden: if it's really just an SDoc, let's call it with its proper name.
* Fix -dynamic-too with wired-in modules (#19264)Sylvain Henry2021-01-301-12/+23
| | | | | | | | | | | | | See T19264 for a tricky corner case when explicitly importing GHC.Num.BigNat and another module. With -dynamic-too, the FinderCache contains paths for non-dynamic interfaces so they must be loaded first, which is usually the case, except for some interfaces loaded in the backend (e.g. in CorePrep). So we must run the backend for the non-dynamic way first for -dynamic-too to work as it is but I broke this invariant in c85f4928d4dbb2eb2cf906d08bfe7620d6f04ca5 by mistakenly making the backend run for the dynamic way first.
* Zonk the returned kind in tcFamTyPatsSimon Peyton Jones2021-01-301-0/+31
| | | | | | The motivation is given in Note [tcFamTyPats: zonking the result kind]. Fixes #19250 -- the fix is easy.
* Fix parsing of -fstg-lift-lams-non-recKrzysztof Gogolewski2021-01-291-2/+2
| | | | | | | | -fstg-lift-lams-rec-* and -fstg-lift-lams-non-rec-* were setting the same field. Fix manual: -fstg-lift-lams-non-rec-args is disabled by -fstg-lift-lams-non-rec-args-any, there's no -fno-stg-lift-*.
* Make PatSyn immutableSimon Peyton Jones2021-01-2928-204/+203
| | | | | | | | | | Provoked by #19074, this patch makes GHC.Core.PatSyn.PatSyn immutable, by recording only the *Name* of the matcher and builder rather than (as currently) the *Id*. See Note [Keep Ids out of PatSyn] in GHC.Core.PatSyn. Updates haddock submodule.
* Ppr: compute length of string literals at compile time (#19266)Sylvain Henry2021-01-291-1/+10
| | | | | | | | | | | | | | | | | | | | | | | | | | | SDoc string literals created for example with `text "xyz"` are converted into `PtrString` (`Addr#` + size in bytes) with a rewrite rule to avoid allocating a String. Before this patch, the size in bytes was still computed at runtime. For every literal, we obtained the following pseudo STG: x :: Addr# x = "xzy"# s :: PtrString s = \u [] case ffi:strlen [x realWorld#] of (# _, sz #) -> PtrString [x sz] But since GHC 9.0, we can use `cstringLength#` instead to get: x :: Addr# x = "xzy"# s :: PtrString s = PtrString! [x 3#] Literals become statically known constructor applications. Allocations seem to decrease a little in perf tests (between -0.1% and -0.7% on CI).
* Add missing .hi-boot dependencies with ghc -M (#14482)Sylvain Henry2021-01-292-1/+19
|
* Add explicit import lists to Data.List importsOleg Grenrus2021-01-2954-61/+62
| | | | | | | | | | | | | Related to a future change in Data.List, https://downloads.haskell.org/ghc/8.10.3/docs/html/users_guide/using-warnings.html?highlight=wcompat#ghc-flag--Wcompat-unqualified-imports Companion pull&merge requests: - https://github.com/judah/haskeline/pull/153 - https://github.com/haskell/containers/pull/762 - https://gitlab.haskell.org/ghc/packages/hpc/-/merge_requests/9 After these the actual change in Data.List should be easy to do.
* Remove StgLamLeif Metcalf2021-01-2911-67/+65
| | | | | | | | | | | | | | | | StgLam is used exclusively in the work of CoreToStg, but there's nothing in the type of StgExpr that indicates this, so we're forced throughout the Stg.* codebase to handle cases like: case expr of ... StgLam lam -> panic "Unexpected StgLam" ... This patch removes the StgLam constructor from the base StgExpr so these cases no longer need to be handled. Instead, we use a new intermediate type in CoreToStg, PreStgRhs, to represent the RHS expression of a binding.
* typecheck: Account for -XStrict in irrefutability checkBen Gamari2021-01-294-27/+71
| | | | | | | | | | | | | | | | | | | | | | When -XStrict is enabled the rules for irrefutability are slightly modified. Specifically, the pattern in a program like do ~(Just hi) <- expr cannot be considered irrefutable. The ~ here merely disables the bang that -XStrict would usually apply, rendering the program equivalent to the following without -XStrict do Just hi <- expr To achieve make this pattern irrefutable with -XStrict the user would rather need to write do ~(~(Just hi)) <- expr Failing to account for this resulted in #19027. To fix this isIrrefutableHsPat takes care to check for two the irrefutability of the inner pattern when it encounters a LazyPat and -XStrict is enabled.