summaryrefslogtreecommitdiff
path: root/docs
Commit message (Collapse)AuthorAgeFilesLines
* users-guide: Add release notes entry for thread introspection supportwip/thread-statusBen Gamari2022-08-061-0/+5
|
* Change `-fprof-late` to insert cost centres after unfolding creation.Andreas Klebinger2022-08-062-5/+39
| | | | | | | | | | | | | | | | | | | | | | | | | | The former behaviour of adding cost centres after optimization but before unfoldings are created is not available via the flag `prof-late-inline` instead. I also reduced the overhead of -fprof-late* by pushing the cost centres into lambdas. This means the cost centres will only account for execution of functions and not their partial application. Further I made LATE_CC cost centres it's own CC flavour so they now won't clash with user defined ones if a user uses the same string for a custom scc. LateCC: Don't put cost centres inside constructor workers. With -fprof-late they are rarely useful as the worker is usually inlined. Even if the worker is not inlined or we use -fprof-late-linline they are generally not helpful but bloat compile and run time significantly. So we just don't add sccs inside constructor workers. ------------------------- Metric Decrease: T13701 -------------------------
* Remove backported items from 9.6 release notesKrzysztof Gogolewski2022-08-051-10/+1
| | | | | They have been backported to 9.4 in commits 5423d84bd9a28f, 13c81cb6be95c5, 67ccbd6b2d4b9b.
* User's guide: fix typo in hasfield.rstsheaf2022-08-021-1/+1
| | | | Fixes #21950
* Add -dsuppress-coercion-types to make coercions even smaller.Andreas Klebinger2022-08-021-0/+5
| | | | | Instead of `` `cast` <Co:11> :: (Some -> Really -> Large Type)`` simply print `` `cast` <Co:11> :: ... ``
* Docs: fix mistaken claim about kind signaturessheaf2022-07-281-8/+37
| | | | | | | | | This patch fixes #21806 by rectifying an incorrect claim about the usage of kind variables in the header of a data declaration with a standalone kind signature. It also adds some clarifications about the number of parameters expected in GADT declarations and in type family declarations.
* docs: Fix documentation of \casesSimon Jakobi2022-07-251-3/+3
| | | | Fixes #21902.
* Docs: clarify ConstraintKinds infelicitysheaf2022-07-251-11/+17
| | | | | | | | | | | GHC doesn't consistently require the ConstraintKinds extension to be enabled, as it allows programs such as type families returning a constraint without this extension. MR !7784 fixes this infelicity, but breaking user programs was deemed to not be worth it, so we document it instead. Fixes #21061.
* Implement DeepSubsumptionSimon Peyton Jones2022-07-252-10/+36
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This MR adds the language extension -XDeepSubsumption, implementing GHC proposal #511. This change mitigates the impact of GHC proposal The changes are highly localised, by design. See Note [Deep subsumption] in GHC.Tc.Utils.Unify. The main changes are: * Add -XDeepSubsumption, which is on by default in Haskell98 and Haskell2010, but off in Haskell2021. -XDeepSubsumption largely restores the behaviour before the "simple subsumption" change. -XDeepSubsumpition has a similar flavour as -XNoMonoLocalBinds: it makes type inference more complicated and less predictable, but it may be convenient in practice. * The main changes are in: * GHC.Tc.Utils.Unify.tcSubType, which does deep susumption and eta-expanansion * GHC.Tc.Utils.Unify.tcSkolemiseET, which does deep skolemisation * In GHC.Tc.Gen.App.tcApp we call tcSubTypeNC to match the result type. Without deep subsumption, unifyExpectedType would be sufficent. See Note [Deep subsumption] in GHC.Tc.Utils.Unify. * There are no changes to Quick Look at all. * The type of `withDict` becomes ambiguous; so add -XAllowAmbiguousTypes to GHC.Magic.Dict * I fixed a small but egregious bug in GHC.Core.FVs.varTypeTyCoFVs, where we'd forgotten to take the free vars of the multiplicity of an Id. * I also had to fix tcSplitNestedSigmaTys When I did the shallow-subsumption patch commit 2b792facab46f7cdd09d12e79499f4e0dcd4293f Date: Sun Feb 2 18:23:11 2020 +0000 Simple subsumption I changed tcSplitNestedSigmaTys to not look through function arrows any more. But that was actually an un-forced change. This function is used only in * Improving error messages in GHC.Tc.Gen.Head.addFunResCtxt * Validity checking for default methods: GHC.Tc.TyCl.checkValidClass * A couple of calls in the GHCi debugger: GHC.Runtime.Heap.Inspect All to do with validity checking and error messages. Acutally its fine to look under function arrows here, and quite useful a test DeepSubsumption05 (a test motivated by a build failure in the `lens` package) shows. The fix is easy. I added Note [tcSplitNestedSigmaTys].
* rel-notes: Drop mention of #21745 fixBen Gamari2022-07-161-6/+0
| | | | Since we have backported the fix to 9.4.1.
* Identify the extistence of the `runhaskell` command and that it is ↵Mike Pilgrem2022-07-021-1/+2
| | | | equivalent to the `runghc` command. Add an entry to the index for `runhaskell`. See https://gitlab.haskell.org/ghc/ghc/-/issues/21411
* rts: gc stats: account properly for copied bytes in sequential collectionsDouglas Wilson2022-07-011-0/+6
| | | | | | | | | | | We were not updating the [copied,any_work,scav_find_work, max_n_todo_overflow] counters during sequential collections. As well, we were double counting for parallel collections. To fix this we add an `else` clause to the `if (is_par_gc())`. The par_* counters do not need to be updated in the sequential case because they must be 0.
* runhaskellEric Lindblad2022-06-221-1/+1
|
* Correct documentation of defaults of the `-V` RTS optionAlexander Esgen2022-06-221-6/+7
|
* Break out thNameToGhcNameIO (ref. #21730)Brandon Chinn2022-06-221-0/+2
|
* Use lookupNameCache instead of lookupOrigIOBrandon Chinn2022-06-221-0/+2
|
* Flags to disable local let-floating; -flocal-float-out, ↵Vanessa McHale2022-06-221-0/+48
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | -flocal-float-out-top-level CLI flags These flags affect the behaviour of local let floating. If `-flocal-float-out` is disabled (the default) then we disable all local floating. ``` …(let x = let y = e in (a,b) in body)... ===> …(let y = e; x = (a,b) in body)... ``` Further to this, top-level local floating can be disabled on it's own by passing -fno-local-float-out-top-level. ``` x = let y = e in (a,b) ===> y = e; x = (a,b) ``` Note that this is only about local floating, ie, floating two adjacent lets past each other and doesn't say anything about the global floating pass which is controlled by `-fno-float`. Fixes #13663
* ghc-heap: Don't Box NULL pointersBen Gamari2022-06-181-0/+7
| | | | | | | | | Previously we could construct a `Box` of a NULL pointer from the `link` field of `StgWeak`. Now we take care to avoid ever introducing such pointers in `collect_pointers` and ensure that the `link` field is represented as a `Maybe` in the `Closure` type. Fixes #21622
* Deprecate TypeInType extensionHaskellMouse2022-06-061-0/+2
| | | | | | | | | | | | | | | | This commit fixes #20312 It deprecates "TypeInType" extension according to the following proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0083-no-type-in-type.rst It has been already implemented. The migration strategy: 1. Disable TypeInType 2. Enable both DataKinds and PolyKinds extensions Metric Decrease: T16875
* Make -fcompact-unwind the defaultMatthew Pickering2022-06-011-0/+2
| | | | | | | | This is a follow-up to !7247 (closed) making the inclusion of compact unwinding sections the default. Also a slight refactoring/simplification of the flag handling to add -fno-compact-unwind.
* Desugar RecordUpd in `tcExpr`wip/T18802CarrieMY2022-05-251-0/+52
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch typechecks record updates by desugaring them inside the typechecker using the HsExpansion mechanism, and then typechecking this desugared result. Example: data T p q = T1 { x :: Int, y :: Bool, z :: Char } | T2 { v :: Char } | T3 { x :: Int } | T4 { p :: Float, y :: Bool, x :: Int } | T5 The record update `e { x=e1, y=e2 }` desugars as follows e { x=e1, y=e2 } ===> let { x' = e1; y' = e2 } in case e of T1 _ _ z -> T1 x' y' z T4 p _ _ -> T4 p y' x' The desugared expression is put into an HsExpansion, and we typecheck that. The full details are given in Note [Record Updates] in GHC.Tc.Gen.Expr. Fixes #2595 #3632 #10808 #10856 #16501 #18311 #18802 #21158 #21289 Updates haddock submodule
* Change `Backend` type and remove direct dependencieswip/backend-as-recordNorman Ramsey2022-05-211-0/+113
| | | | | | | | | | | | | | | | | | | With this change, `Backend` becomes an abstract type (there are no more exposed value constructors). Decisions that were formerly made by asking "is the current back end equal to (or different from) this named value constructor?" are now made by interrogating the back end about its properties, which are functions exported by `GHC.Driver.Backend`. There is a description of how to migrate code using `Backend` in the user guide. Clients using the GHC API can find a backdoor to access the Backend datatype in GHC.Driver.Backend.Internal. Bumps haddock submodule. Fixes #20927
* docs: Fix LlvmVersion in manpage (#21280)Zubin Duggal2022-05-203-5/+7
|
* base: Introduce [sg]etFinalizerExceptionHandlerBen Gamari2022-05-191-0/+4
| | | | | This introduces a global hook which is called when an exception is thrown during finalization.
* driver: Introduce pgmcxxBen Gamari2022-05-171-0/+7
| | | | | | | | | | Here we introduce proper support for compilation of C++ objects. This includes: * logic in `configure` to detect the C++ toolchain and propagating this information into the `settings` file * logic in the driver to use the C++ toolchain when compiling C++ sources
* TcPlugin: access to irreducible givens + fix passed ev_binds_varPavol Vargovcik2022-05-161-4/+9
|
* Update extending_ghc for TcPlugin changessheaf2022-05-121-6/+6
| | | | | The documentation still mentioned Derived constraints and an outdated datatype TcPluginResult.
* docs: Fix path to GHC API docs in index.htmlMatthew Pickering2022-05-101-1/+1
| | | | | | | | | | | | In the make bindists we generate documentation in docs/ghc-<VER> but the hadrian bindists generate docs/ghc/ so the path to the GHC API docs was wrong in the index.html file. Rather than make the hadrian and make bindists the same it was easier to assume that if you're using the mkDocs script that you're using hadrian bindists. Fixes #21509
* Allow `let` just before pure/return in ApplicativeDoZiyang Liu2022-05-061-5/+4
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The following is currently rejected: ```haskell -- F is an Applicative but not a Monad x :: F (Int, Int) x = do a <- pure 0 let b = 1 pure (a, b) ``` This has bitten me multiple times. This MR contains a simple fix: only allow a "let only" segment to be merged with the next (and not the previous) segment. As a result, when the last one or more statements before pure/return are `LetStmt`s, there will be one more segment containing only those `LetStmt`s. Note that if the `let` statement mentions a name bound previously, then the program is still rejected, for example ```haskell x = do a <- pure 0 let b = a + 1 pure (a, b) ``` or the example in #18559. To support this would require a more complex approach, but this is IME much less common than the previous case.
* Start 9.6.1-notessheaf2022-05-053-435/+25
| | | | | Updates the documentation notes to start tracking changes for the 9.6.1 release (instead of 9.4).
* Update supported LLVM versionsBen Gamari2022-05-041-0/+6
| | | | | | Pull forward minimum version to match 9.2. (cherry picked from commit c26faa54c5fbe902ccb74e79d87e3fa705e270d1)
* users guide: add categories to some flagsAdam Sandberg Ericsson2022-04-301-6/+6
|
* Update user guide example rewrite rules formattingMarius Ghita2022-04-301-3/+3
| | | | | | | | | | | | | | Change the rewrite rule examples to include a space between the composition of `f` and `g` in the map rewrite rule examples. Without this change, if the user has locally enabled the extension OverloadedRecordDot the copied example will result in a compile time error that `g` is not a field of `f`. ``` • Could not deduce (GHC.Records.HasField "g" (a -> b) (a1 -> b)) arising from selecting the field ‘g’ ```
* Update docs for change to type-checking pluginssheaf2022-04-272-2/+13
| | | | | | There was no mention of the changes to type-checking plugins in the 9.4.1 notes, and the extending_ghc documentation contained a reference to an outdated type.
* Enable eventlog support in all ways by defaultBen Gamari2022-04-272-2/+11
| | | | | | | | | | | | | | | | | Here we deprecate the eventlogging RTS ways and instead enable eventlog support in the remaining ways. This simplifies packaging and reduces GHC compilation times (as we can eliminate two whole compilations of the RTS) while simplifying the end-user story. The trade-off is a small increase in binary sizes in the case that the user does not want eventlogging support, but we think that this is a fine trade-off. This also revealed a latent RTS bug: some files which included `Cmm.h` also assumed that it defined various macros which were in fact defined by `Config.h`, which `Cmm.h` did not include. Fixing this in turn revealed that `StgMiscClosures.cmm` failed to import various spinlock statistics counters, as evidenced by the failed unregisterised build. Closes #18948.
* Basic response file supportBen Gamari2022-04-272-0/+14
| | | | | | | | Here we introduce support into our command-line parsing infrastructure and driver for handling gnu-style response file arguments, typically used to work around platform command-line length limitations. Fixes #16476.
* Ensure that Any is Boxed in FFI imports/exportssheaf2022-04-271-2/+3
| | | | | | | | | | We should only accept the type `Any` in foreign import/export declarations when it has type `Type` or `UnliftedType`. This patch adds a kind check, and a special error message triggered by occurrences of `Any` in foreign import/export declarations at other kinds. Fixes #21305
* Document behaviour of RULES with KnownNatBodigrim2022-04-251-0/+9
|
* Drop libtool path from settings fileBen Gamari2022-04-251-7/+0
| | | | | GHC no longers uses libtool for linking and therefore this is no longer necessary.
* Include the way string in the file name for dump files.Andreas Klebinger2022-04-221-0/+11
| | | | | | This can be disabled by `-fno-dump-with-ways` if not desired. Finally we will be able to look at both profiled and non-profiled dumps when compiling with dump flags and we compile in both ways.
* Add -dkeep-comments flag to keep comments in the parserAlan Zimmerman2022-04-201-0/+7
| | | | | | | | | This provides a way to set the Opt_KeepRawTokenStream from the command line, allowing exact print annotation users to see exactly what is produced for a given parsed file, when used in conjunction with -ddump-parsed-ast Discussed in #19706, but this commit does not close the issue.
* Document that DuplicateRecordFields doesn't tolerates ambiguous fieldsHécate Moonlight2022-04-123-106/+70
| | | | Fix #19891
* Add flag -fprof-manual which controls if GHC should honour manual cost centres.Andreas Klebinger2022-04-081-0/+11
| | | | | | | This allows disabling of manual control centres in code a user doesn't control like libraries. Fixes #18867
* Fixes to 9.4 release notesKrzysztof Gogolewski2022-04-083-10/+22
| | | | | | - Mention -Wforall-identifier - Improve description of withDict - Fix formatting
* Properly explain where INLINE pragmas can appear.Andreas Klebinger2022-04-071-6/+41
| | | | Fixes #20676
* Add warnings for file header pragmas that appear in the body of a module ↵Zubin Duggal2022-04-061-0/+14
| | | | | | | | | | | | | | | (#20385) Once we are done parsing the header of a module to obtain the options, we look through the rest of the tokens in order to determine if they contain any misplaced file header pragmas that would usually be ignored, potentially resulting in bad error messages. The warnings are reported immediately so that later errors don't shadow over potentially helpful warnings. Metric Increase: T13719
* users-guide: Fix various markup issuesBen Gamari2022-04-011-15/+15
|
* Implement \cases (Proposal 302)Jakob Bruenker2022-04-013-5/+25
| | | | | | | | | | | | This commit implements proposal 302: \cases - Multi-way lambda expressions. This adds a new expression heralded by \cases, which works exactly like \case, but can match multiple apats instead of a single pat. Updates submodule haddock to support the ITlcases token. Closes #20768
* Keep track of promotion ticks in HsOpTywip/no-c-stubswip/matt-merge-batchsheaf2022-04-012-0/+11
| | | | | | | | | | | | | | | | This patch adds a PromotionFlag field to HsOpTy, which is used in pretty-printing and when determining whether to emit warnings with -fwarn-unticked-promoted-constructors. This allows us to correctly report tick-related warnings for things like: type A = Int : '[] type B = [Int, Bool] Updates haddock submodule Fixes #19984
* docs: Update documentation interaction of search path, -hidir and -c mode.Matthew Pickering2022-04-011-5/+9
| | | | | | | | | As noted in #20569 the documentation for search path was wrong because it seemed to indicate that `-i` dirs were important when looking for interface files in `-c` mode, but they are not important if `-hidir` is set. Fixes #20569