summaryrefslogtreecommitdiff
path: root/docs
Commit message (Collapse)AuthorAgeFilesLines
* Fix kind inference for data types. Again.Simon Peyton Jones2020-12-082-85/+158
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch fixes several aspects of kind inference for data type declarations, especially data /instance/ declarations Specifically 1. In kcConDecls/kcConDecl make it clear that the tc_res_kind argument is only used in the H98 case; and in that case there is no result kind signature; and hence no need for the disgusting splitPiTys in kcConDecls (now thankfully gone). The GADT case is a bit different to before, and much nicer. This is what fixes #18891. See Note [kcConDecls: kind-checking data type decls] 2. Do not look at the constructor decls of a data/newtype instance in tcDataFamInstanceHeader. See GHC.Tc.TyCl.Instance Note [Kind inference for data family instances]. This was a new realisation that arose when doing (1) This causes a few knock-on effects in the tests suite, because we require more information than before in the instance /header/. New user-manual material about this in "Kind inference in data type declarations" and "Kind inference for data/newtype instance declarations". 3. Minor improvement in kcTyClDecl, combining GADT and H98 cases 4. Fix #14111 and #8707 by allowing the header of a data instance to affect kind inferece for the the data constructor signatures; as described at length in Note [GADT return types] in GHC.Tc.TyCl This led to a modest refactoring of the arguments (and argument order) of tcConDecl/tcConDecls. 5. Fix #19000 by inverting the sense of the test in new_locs in GHC.Tc.Solver.Canonical.canDecomposableTyConAppOK.
* Remove flattening variablesRichard Eisenberg2020-12-013-1/+49
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch redesigns the flattener to simplify type family applications directly instead of using flattening meta-variables and skolems. The key new innovation is the CanEqLHS type and the new CEqCan constraint (Ct). A CanEqLHS is either a type variable or exactly-saturated type family application; either can now be rewritten using a CEqCan constraint in the inert set. Because the flattener no longer reduces all type family applications to variables, there was some performance degradation if a lengthy type family application is now flattened over and over (not making progress). To compensate, this patch contains some extra optimizations in the flattener, leading to a number of performance improvements. Close #18875. Close #18910. There are many extra parts of the compiler that had to be affected in writing this patch: * The family-application cache (formerly the flat-cache) sometimes stores coercions built from Given inerts. When these inerts get kicked out, we must kick out from the cache as well. (This was, I believe, true previously, but somehow never caused trouble.) Kicking out from the cache requires adding a filterTM function to TrieMap. * This patch obviates the need to distinguish "blocking" coercion holes from non-blocking ones (which, previously, arose from CFunEqCans). There is thus some simplification around coercion holes. * Extra commentary throughout parts of the code I read through, to preserve the knowledge I gained while working. * A change in the pure unifier around unifying skolems with other types. Unifying a skolem now leads to SurelyApart, not MaybeApart, as documented in Note [Binding when looking up instances] in GHC.Core.InstEnv. * Some more use of MCoercion where appropriate. * Previously, class-instance lookup automatically noticed that e.g. C Int was a "unifier" to a target [W] C (F Bool), because the F Bool was flattened to a variable. Now, a little more care must be taken around checking for unifying instances. * Previously, tcSplitTyConApp_maybe would split (Eq a => a). This is silly, because (=>) is not a tycon in Haskell. Fixed now, but there are some knock-on changes in e.g. TrieMap code and in the canonicaliser. * New function anyFreeVarsOf{Type,Co} to check whether a free variable satisfies a certain predicate. * Type synonyms now remember whether or not they are "forgetful"; a forgetful synonym drops at least one argument. This is useful when flattening; see flattenView. * The pattern-match completeness checker invokes the solver. This invocation might need to look through newtypes when checking representational equality. Thus, the desugarer needs to keep track of the in-scope variables to know what newtype constructors are in scope. I bet this bug was around before but never noticed. * Extra-constraints wildcards are no longer simplified before printing. See Note [Do not simplify ConstraintHoles] in GHC.Tc.Solver. * Whether or not there are Given equalities has become slightly subtler. See the new HasGivenEqs datatype. * Note [Type variable cycles in Givens] in GHC.Tc.Solver.Canonical explains a significant new wrinkle in the new approach. * See Note [What might match later?] in GHC.Tc.Solver.Interact, which explains the fix to #18910. * The inert_count field of InertCans wasn't actually used, so I removed it. Though I (Richard) did the implementation, Simon PJ was very involved in design and review. This updates the Haddock submodule to avoid #18932 by adding a type signature. ------------------------- Metric Decrease: T12227 T5030 T9872a T9872b T9872c Metric Increase: T9872d -------------------------
* Set dynamic users-guide TOC spacing (fixes #18554)Tim Barnes2020-11-261-0/+3
|
* Implement -ddump-c-backend argumentBen Gamari2020-11-221-0/+9
| | | | To dump output of the C backend.
* rts: Post ticky entry counts to the eventlogBen Gamari2020-11-213-4/+49
| | | | | | | | We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit.
* Move Plugins into HscEnv (#17957)Sylvain Henry2020-11-211-7/+11
| | | | | | | | | | Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule
* Introduce -fprof-callers flagBen Gamari2020-11-212-0/+36
| | | | | | | | This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566.
* users-guide: A bit of clean-up in profiling flag documentationBen Gamari2020-11-211-43/+31
|
* Update user's guide entry on demand analysis and worker/wrapperSebastian Graf2020-11-204-24/+170
| | | | | | | | | The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation.
* Clarify interruptible FFI wrt masking stateKamil Dworakowski2020-11-201-4/+7
|
* nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3Ben Gamari2020-11-151-1/+4
| | | | | Standard debugging tools don't know how to understand these so let's not produce them unless asked.
* Enable -fexpose-internal-symbols when debug level >=2Ben Gamari2020-11-112-3/+5
| | | | | This seems like a reasonable default as the object file size increases by around 5%.
* codeGen: Produce local symbols for module-internal functionsBen Gamari2020-11-111-0/+13
| | | | | | | | | | | | | | | | | | | | It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code.
* [AArch64] Aarch64 Always PICMoritz Angermann2020-11-061-2/+4
|
* Update inlining flags documentationMatthew Pickering2020-11-032-13/+1
|
* Expand type synonyms with :kind!Simon Peyton Jones2020-11-021-0/+3
| | | | | | | | | | The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott@gmail.com>
* Document that ccall convention doesn't support varargsBen Gamari2020-11-021-0/+15
| | | | | | | | | | | We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854.
* Make typechecker equality consider visibility in ForAllTysRyan Scott2020-10-312-20/+20
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863.
* Split HsConDecl{H98,GADT}DetailsRyan Scott2020-10-301-3/+41
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule.
* Remove unnecessary gender from comments/docsRichard Eisenberg2020-10-291-1/+1
| | | | | | | While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing.
* Minor comments, update linear types docsKrzysztof Gogolewski2020-10-201-4/+14
| | | | | | | - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs
* Implement -Woperator-whitespace (#18834)Vladislav Zavialov2020-10-191-0/+52
| | | | | | | | | | | | | | This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers.
* Add flags for annotating Generic{,1} methods INLINE[1] (#11068)Andrzej Rybczak2020-10-152-0/+50
| | | | | | | | Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227
* users-guide: Add missing :ghc-flag: directiveBen Gamari2020-10-141-2/+2
|
* Add -Wnoncanonical-{monad,monoid}-instances to standardWarningsFumiaki Kinoshita2020-10-141-0/+4
| | | | | | | | | ------------------------- Metric Decrease: T12425 Metric Increase: T17516 -------------------------
* Remove "Operator sections" from docs/users_guide/bugs.rstVladislav Zavialov2020-10-141-25/+0
| | | | | The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979
* Make DataKinds the sole arbiter of kind-level literals (and friends)Ryan Scott2020-10-142-23/+29
| | | | | | | | | | | | | | | | | | | | | | | Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831.
* Unification of Nat and NaturalsHaskellMouse2020-10-132-2/+24
| | | | | | | | | | | | | | | | | | | | | | | This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated.
* Add a flag to indicate that gcc supports -no-pieKrzysztof Gogolewski2020-10-091-0/+14
| | | | Fixes #17919.
* Document -Wderiving-typeableMaxGabriel2020-10-092-1/+14
| | | | Tracking: #18641
* Document profiling flags, warning flags, and no-pieRachel2020-10-074-46/+133
|
* Small documentation fixesKrzysztof Gogolewski2020-10-037-14/+25
| | | | | | | | | - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci]
* Replaced MkT1 with T1 in type signatures.Icelandjack2020-10-021-2/+2
|
* Fix typos in commentsKrzysztof Gogolewski2020-10-021-1/+1
| | | | [skip ci]
* Description of flag `-H` was in 'verbosity options', moved to 'misc'.Benjamin Maurer2020-09-291-8/+8
| | | | Fixes #18699
* New linear types syntax: a %p -> b (#18459)Vladislav Zavialov2020-09-292-28/+24
| | | | | | Implements GHC Proposal #356 Updates the haddock submodule.
* Various documentation fixesKrzysztof Gogolewski2020-09-259-20/+21
| | | | | | | | | | | * Remove UnliftedFFITypes from conf. Some time ago, this extension was undocumented and we had to silence a warning. This is no longer needed. * Use r'' in conf.py. This fixes a Sphinx warning: WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax. * Mark GHCForeignImportPrim as documented * Fix formatting in template_haskell.rst * Remove 'recursive do' from the list of unsupported items in TH
* Improve kind generalisation, error messagesSimon Peyton Jones2020-09-241-0/+5
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch does two things: * It refactors GHC.Tc.Errors a bit. In debugging Quick Look I was forced to look in detail at error messages, and ended up doing a bit of refactoring, esp in mkTyVarEqErr'. It's still quite a mess, but a bit better, I think. * It makes a significant improvement to the kind checking of type and class declarations. Specifically, we now ensure that if kind checking fails with an unsolved constraint, all the skolems are in scope. That wasn't the case before, which led to some obscure error messages; and occasional failures with "no skolem info" (eg #16245). Both of these, and the main Quick Look patch itself, affect a /lot/ of error messages, as you can see from the number of files changed. I've checked them all; I think they are as good or better than before. Smaller things * I documented the various instances of VarBndr better. See Note [The VarBndr tyep and its uses] in GHC.Types.Var * Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds * A bit of refactoring in bindExplicitTKTele, to avoid the footwork with Either. Simpler now. * Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType Fixes #16245 (comment 211369), memorialised as typecheck/polykinds/T16245a Also fixes the three bugs in #18640
* Implement Quick Look impredicativitySimon Peyton Jones2020-09-243-53/+46
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch implements Quick Look impredicativity (#18126), sticking very closely to the design in A quick look at impredicativity, Serrano et al, ICFP 2020 The main change is that a big chunk of GHC.Tc.Gen.Expr has been extracted to two new modules GHC.Tc.Gen.App GHC.Tc.Gen.Head which deal with typechecking n-ary applications, and the head of such applications, respectively. Both contain a good deal of documentation. Three other loosely-related changes are in this patch: * I implemented (partly by accident) points (2,3)) of the accepted GHC proposal "Clean up printing of foralls", namely https://github.com/ghc-proposals/ghc-proposals/blob/ master/proposals/0179-printing-foralls.rst (see #16320). In particular, see Note [TcRnExprMode] in GHC.Tc.Module - :type instantiates /inferred/, but not /specified/, quantifiers - :type +d instantiates /all/ quantifiers - :type +v is killed off That completes the implementation of the proposal, since point (1) was done in commit df08468113ab46832b7ac0a7311b608d1b418c4d Author: Krzysztof Gogolewski <krzysztof.gogolewski@tweag.io> Date: Mon Feb 3 21:17:11 2020 +0100 Always display inferred variables using braces * HsRecFld (which the renamer introduces for record field selectors), is now preserved by the typechecker, rather than being rewritten back to HsVar. This is more uniform, and turned out to be more convenient in the new scheme of things. * The GHCi debugger uses a non-standard unification that allows the unification variables to unify with polytypes. We used to hack this by using ImpredicativeTypes, but that doesn't work anymore so I introduces RuntimeUnkTv. See Note [RuntimeUnkTv] in GHC.Runtime.Heap.Inspect Updates haddock submodule. WARNING: this patch won't validate on its own. It was too hard to fully disentangle it from the following patch, on type errors and kind generalisation. Changes to tests * Fixes #9730 (test added) * Fixes #7026 (test added) * Fixes most of #8808, except function `g2'` which uses a section (which doesn't play with QL yet -- see #18126) Test added * Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted * Fixes #17332 (test added) * Fixes #4295 * This patch makes typecheck/should_run/T7861 fail. But that turns out to be a pre-existing bug: #18467. So I have just made T7861 into expect_broken(18467)
* Remove the list of loaded modules from the ghci promptHécate2020-09-231-239/+224
|
* users guide: Fix various documentation issuesBen Gamari2020-09-195-11/+20
|
* Fix a codeblock in ghci.rstAndreas Klebinger2020-09-191-0/+1
|
* Fix docs who misstated how the RTS treats size suffixes.Andreas Klebinger2020-09-191-2/+2
| | | | | | | They are parsed as multiples of 1024. Not 1000. The docs used to imply otherwise. See decodeSize in rts/RtsFlags.c for the logic for this.
* Documented '-m' flags for machine specific instruction extensions.Benjamin Maurer2020-09-172-11/+142
| | | | See #18641 'Documenting the Expected Undocumented Flags'
* docs: correct haddock referenceAdam Sandberg Eriksson2020-09-161-2/+2
| | | [skip ci]
* Include -f{write,validate}-ide-info in the User's Guide flag referenceRyan Scott2020-09-162-0/+16
| | | | | | | Previously, these were omitted from the flag reference due to a layout oversight in `docs/users_guide/flags.{rst,py}`. Fixes #18426.
* Fix rtsopts documentationDenisFrezzato2020-09-151-1/+1
|
* docs: -B rts option sounds the bell on every GC (#18351)Adam Sandberg Eriksson2020-09-141-1/+1
|
* PmCheck: Disattach COMPLETE pragma lookup from TyConsSebastian Graf2020-09-121-23/+0
| | | | | | | | | | | | | | | | | | | By not attaching COMPLETE pragmas with a particular TyCon and instead assume that every COMPLETE pragma is applicable everywhere, we can drastically simplify the logic that tries to initialise available COMPLETE sets of a variable during the pattern-match checking process, as well as fixing a few bugs. Of course, we have to make sure not to report any of the ill-typed/unrelated COMPLETE sets, which came up in a few regression tests. In doing so, we fix #17207, #18277 and #14422. There was a metric decrease in #18478 by ~20%. Metric Decrease: T18478
* Make the forall-or-nothing rule only apply to invisible foralls (#18660)Ryan Scott2020-09-081-11/+16
| | | | | | | | This fixes #18660 by changing `isLHsForAllTy` to `isLHsInvisForAllTy`, which is sufficient to make the `forall`-or-nothing rule only apply to invisible `forall`s. I also updated some related documentation and Notes while I was in the neighborhood.