summaryrefslogtreecommitdiff
path: root/compiler/GHC/Utils
Commit message (Collapse)AuthorAgeFilesLines
* Implement BoxedRep proposalwip/boxed-repBen Gamari2021-03-072-1/+13
| | | | | | | | | | | | | | | | | | | | | | | This implements the BoxedRep proposal, refactoring the `RuntimeRep` hierarchy from: ```haskell data RuntimeRep = LiftedPtrRep | UnliftedPtrRep | ... ``` to ```haskell data RuntimeRep = BoxedRep Levity | ... data Levity = Lifted | Unlifted ``` Updates binary, haddock submodules. Closes #17526. Metric Increase: T12545
* Fix typechecking time bug for large rationals (#15646)Andreas Klebinger2021-02-271-7/+103
| | | | | | | | | When desugaring large overloaded literals we now avoid computing the `Rational` value. Instead prefering to store the significant and exponent as given where reasonable and possible. See Note [FractionalLit representation] for details.
* Use explicit import list for Data.ListOleg Grenrus2021-02-161-1/+1
|
* GHC.Utils.Binary: Eliminate allocating withForeignPtr usesBen Gamari2021-02-141-7/+16
|
* Refactor LoggerSylvain Henry2021-02-133-339/+531
| | | | | | | | | | | | | | | | | | | | | 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 typosBrian Wignall2021-02-061-1/+1
|
* The Char kind (#11342)Daniel Rogozin2021-02-062-1/+12
| | | | | | | | | | | | | | | | | | | | | | 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
* Try eta expanding FCode (See #18202)Andreas Klebinger2021-02-051-0/+11
| | | | | | | | | 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)
* Introduce the DecoratedSDoc typeAlfredo Di Napoli2021-02-011-6/+8
| | | | | This commit introduces a DecoratedSDoc type which replaces the old ErrDoc, and hopefully better reflects the intent.
* Rename ErrMsg into MsgEnvelopeAlfredo Di Napoli2021-02-011-12/+12
| | | | Updates Haddock submodule
* Remove ErrDoc and MsgDocAlfredo Di Napoli2021-02-011-23/+22
| | | | | | | | | | | | | 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.
* Add explicit import lists to Data.List importsOleg Grenrus2021-01-292-9/+9
| | | | | | | | | | | | | 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.
* Parameterise Messages over eAlfredo Di Napoli2021-01-221-15/+6
| | | | | | | | | This commit paves the way to a richer and more structured representation of GHC error messages, as per GHC proposal #306. More specifically 'Messages' from 'GHC.Types.Error' now gains an extra type parameter, that we instantiate to 'ErrDoc' for now. Later, this will allow us to replace ErrDoc with something more structure (for example messages coming from the parser, the typechecker etc).
* Remove unused extension pragmas from the compiler code baseHécate2021-01-171-1/+1
|
* Remove errShortString, cleanup error-related functionsAlfredo Di Napoli2021-01-091-106/+2
| | | | | | | | | | | This commit removes the errShortString field from the ErrMsg type, allowing us to cleanup a lot of dynflag-dependent error functions, and move them in a more specialised 'GHC.Driver.Errors' closer to the driver, where they are actually used. Metric Increase: T4801 T9961
* Make proper fixed-width number literalsSylvain Henry2021-01-021-13/+23
| | | | | | | | (Progress towards #11953, #17377, #17375) Besides being nicer to use, this also will allow for better constant folding for the fixed-width types, on par with what `Int#` and `Word#` have today.
* Revert "Implement BoxedRep proposal"Ben Gamari2020-12-152-13/+1
| | | | | | This was inadvertently merged. This reverts commit 6c2eb2232b39ff4720fda0a4a009fb6afbc9dcea.
* Implement BoxedRep proposalAndrew Martin2020-12-142-1/+13
| | | | | | | | | | | | | | | | | | This implements the BoxedRep proposal, refacoring the `RuntimeRep` hierarchy from: ```haskell data RuntimeRep = LiftedPtrRep | UnliftedPtrRep | ... ``` to ```haskell data RuntimeRep = BoxedRep Levity | ... data Levity = Lifted | Unlifted ``` Closes #17526.
* Optimize dumping of consecutive whitespace.wip/andreask/opt_dumpsAndreas Klebinger2020-12-143-6/+49
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The naive way of putting out n characters of indent would be something like `hPutStr hdl (replicate n ' ')`. However this is quite inefficient as we allocate an absurd number of strings consisting of simply spaces as we don't cache them. To improve on this we now track if we can simply write ascii spaces via hPutBuf instead. This is the case when running with -ddump-to-file where we force the encoding to be UTF8. This avoids both the cost of going through encoding as well as avoiding allocation churn from all the white space. Instead we simply use hPutBuf on a preallocated unlifted string. When dumping stg like this: > nofib/spectral/simple/Main.hs -fforce-recomp -ddump-stg-final -ddump-to-file -c +RTS -s Allocations went from 1,778 MB to 1,702MB. About a 4% reduction of allocation! I did not measure the difference in runtime but expect it to be similar. Bumps the haddock submodule since the interface of GHC's Pretty slightly changed. ------------------------- Metric Decrease: T12227 -------------------------
* Cmm.Sink: Optimize retaining of assignments, live sets.Andreas Klebinger2020-12-081-0/+4
| | | | | | | | | | | | | | | | | | | | | | | | | Sinking requires us to track live local regs after each cmm statement. We used to do this via "Set LocalReg". However we can replace this with a solution based on IntSet which is overall more efficient without losing much. The thing we lose is width of the variables, which isn't used by the sinking pass anyway. I also reworked how we keep assignments to regs mentioned in skipped assignments. I put the details into Note [Keeping assignemnts mentioned in skipped RHSs]. The gist of it is instead of keeping track of it via the use count which is a `IntMap Int` we now use the live regs set (IntSet) which is quite a bit faster. I think it also matches the semantics a lot better. The skipped (not discarded) assignment does in fact keep the regs on it's rhs alive so keeping track of this in the live set seems like the clearer solution as well. Improves allocations for T3294 by yet another 1%.
* Rename the flattener to become the rewriter.Richard Eisenberg2020-12-011-3/+1
| | | | | | | | Now that flattening doesn't produce flattening variables, it's not really flattening anything: it's rewriting. This change also means that the rewriter can no longer be confused the core flattener (in GHC.Core.Unify), which is sometimes used during type-checking.
* withTimings: Emit allocations counterBen Gamari2020-11-291-5/+14
| | | | | | | This will allow us to back out the allocations per compiler pass from the eventlog. Note that we dump the allocation counter rather than the difference since this will allow us to determine how much work is done *between* `withTiming` blocks.
* [Sized Cmm] properly retain sizes.Moritz Angermann2020-11-261-5/+25
| | | | | | | | | | | | | | | | | | | | | | | | | | | This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben@well-typed.com> Metric Increase: T13701 T14697
* Demand: Interleave usage and strictness demands (#18903)Sebastian Graf2020-11-201-1/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj
* Replace HsImplicitBndrs with HsOuterTyVarBndrsRyan Scott2020-11-061-0/+7
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj@microsoft.com> Co-authored-by: Richard Eisenberg <rae@richarde.dev> Co-authored-by: Zubin Duggal <zubin@cmi.ac.in>
* Add the proper HLint rules and remove redundant keywords from compilerHécate2020-11-015-48/+41
|
* Remove unnecessary gender from comments/docsRichard Eisenberg2020-10-291-2/+2
| | | | | | | 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.
* Split GHC.Driver.TypesSylvain Henry2020-10-295-637/+267
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule
* Remove pdocPrecSylvain Henry2020-10-191-6/+0
| | | | | | pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance.
* Fix some missed opportunities for preInlineUnconditionallySimon Peyton Jones2020-10-141-5/+5
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370
* Initial ShortText code and conversion of package db codeWander Hillen2020-10-131-526/+0
| | | | | | | | | | | | | | | | | | | | | | | | | Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH
* Lint the compiler for extraneous LANGUAGE pragmasHécate2020-10-101-6/+5
|
* Fix pretty-printing of the mult-polymorphic arrowVladislav Zavialov2020-10-011-1/+1
| | | | A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04)
* Use ADTs for parser errors/warningsSylvain Henry2020-10-011-4/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001
* Remove unsafeGlobalDynFlags (#17957, #14597)Sylvain Henry2020-09-304-63/+125
| | | | | There are still global variables but only 3 booleans instead of a single DynFlags.
* New linear types syntax: a %p -> b (#18459)Vladislav Zavialov2020-09-291-1/+1
| | | | | | Implements GHC Proposal #356 Updates the haddock submodule.
* Remove sdocWithDynFlags (fix #10143)Sylvain Henry2020-09-231-11/+2
|
* Refactor CLabel pretty-printingSylvain Henry2020-09-231-10/+16
| | | | | | | | | | * Don't depend on the selected backend to know if we print Asm or C labels: we already have PprStyle to determine this. Moreover even when a native backend is used (NCG, LLVM) we may want to C headers containing pretty-printed labels, so it wasn't a good predicate anyway. * Make pretty-printing code clearer and avoid partiality
* Export singleton function from Data.ListWander Hillen2020-09-191-1/+1
| | | | | | | | | | | | | | | Data.OldList exports a monomorphized singleton function but it is not re-exported by Data.List. Adding the export to Data.List causes a conflict with a 14-year old function of the same name and type by SPJ in GHC.Utils.Misc. We can't just remove this function because that leads to a problems when building GHC with a stage0 compiler that does not have singleton in Data.List yet. We also can't hide the function in GHC.Utils.Misc since it is not possible to hide a function from a module if the module does not export the function. To work around this, all places where the Utils.Misc singleton was used now use a qualified version like Utils.singleton and in GHC.Utils.Misc we are very specific about which version we export.
* Remove pprPrec from Outputable (unused)Sylvain Henry2020-09-171-8/+1
|
* Add note about OutputablePSylvain Henry2020-09-171-9/+108
|
* Generalize OutputablePSylvain Henry2020-09-171-20/+21
| | | | | Add a type parameter for the environment required by OutputableP. It avoids tying Platform with OutputableP.
* Introduce OutputablePSylvain Henry2020-09-171-2/+47
| | | | | | | | | | | | | | | | | | | | | | | | | Some types need a Platform value to be pretty-printed: CLabel, Cmm types, instructions, etc. Before this patch they had an Outputable instance and the Platform value was obtained via sdocWithDynFlags. It meant that the *renderer* of the SDoc was responsible of passing the appropriate Platform value (e.g. via the DynFlags given to showSDoc). It put the burden of passing the Platform value on the renderer while the generator of the SDoc knows the Platform it is generating the SDoc for and there is no point passing a different Platform at rendering time. With this patch, we introduce a new OutputableP class: class OutputableP a where pdoc :: Platform -> a -> SDoc With this class we still have some polymorphism as we have with `ppr` (i.e. we can use `pdoc` on a variety of types instead of having a dedicated `pprXXX` function for each XXX type). One step closer removing `sdocWithDynFlags` (#10143) and supporting several platforms (#14335).
* Make Z-encoding comment into a noteLeif Metcalf2020-09-171-1/+2
|
* PmCheck: Big refactor using guard tree variants more closely following ↵Sebastian Graf2020-09-101-3/+2
| | | | | | | | | | | | | | | | | | | | | | | | source syntax (#18565) Previously, we desugared and coverage checked plain guard trees as described in Lower Your Guards. That caused (in !3849) quite a bit of pain when we need to partially recover tree structure of the input syntax to return covered sets for long-distance information, for example. In this refactor, I introduced a guard tree variant for each relevant source syntax component of a pattern-match (mainly match groups, match, GRHS, empty case, pattern binding). I made sure to share as much coverage checking code as possible, so that the syntax-specific checking functions are just wrappers around the more substantial checking functions for the LYG primitives (`checkSequence`, `checkGrds`). The refactoring payed off in clearer code and elimination of all panics related to assumed guard tree structure and thus fixes #18565. I also took the liberty to rename and re-arrange the order of functions and comments in the module, deleted some dead and irrelevant Notes, wrote some new ones and gave an overview module haddock.
* Remove "Ord FastString" instanceSylvain Henry2020-09-013-0/+44
| | | | | | | | | | | | | | | | | | | FastStrings can be compared in 2 ways: by Unique or lexically. We don't want to bless one particular way with an "Ord" instance because it leads to bugs (#18562) or to suboptimal code (e.g. using lexical comparison while a Unique comparison would suffice). UTF-8 encoding has the advantage that sorting strings by their encoded bytes also sorts them by their Unicode code points, without having to decode the actual code points. BUT GHC uses Modified UTF-8 which diverges from UTF-8 by encoding \0 as 0xC080 instead of 0x00 (to avoid null bytes in the middle of a String so that the string can still be null-terminated). This patch adds a new `utf8CompareShortByteString` function that performs sorting by bytes but that also takes Modified UTF-8 into account. It is much more performant than decoding the strings into [Char] to perform comparisons (which we did in the previous patch). Bump haddock submodule
* Refactor UnitId pretty-printingSylvain Henry2020-08-262-3/+23
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | When we pretty-print a UnitId for the user, we try to map it back to its origin package name, version and component to print "package-version:component" instead of some hash. The UnitId type doesn't carry these information, so we have to look into a UnitState to find them. This is why the Outputable instance of UnitId used `sdocWithDynFlags` in order to access the `unitState` field of DynFlags. This is wrong for several reasons: 1. The DynFlags are accessed when the message is printed, not when it is generated. So we could imagine that the unitState may have changed in-between. Especially if we want to allow unit unloading. 2. We want GHC to support several independent sessions at once, hence several UnitState. The current approach supposes there is a unique UnitState as a UnitId doesn't indicate which UnitState to use. See the Note [Pretty-printing UnitId] in GHC.Unit for the new approach implemented by this patch. One step closer to remove `sdocDynFlags` field from `SDocContext` (#10143). Fix #18124. Also fix some Backpack code to use SDoc instead of String.
* Perf: make SDoc monad one-shot (#18202)Sylvain Henry2020-08-241-1/+13
| | | | | | | | | | | | | | | | | | | | | | | | With validate-x86_64-linux-deb9-hadrian: T1969 -3.4% (threshold: +/-1%) T3294 -3.3% (threshold: +/-1%) T12707 -1.4% (threshold: +/-1%) Additionally with validate-x86_64-linux-deb9-unreg-hadrian: T4801 -2.4% (threshold: +/-2%) T13035 -1.4% (threshold: +/-1%) T13379 -2.4% (threshold: +/-2%) ManyAlternatives -2.5% (threshold: +/-2%) ManyConstructors -3.0% (threshold: +/-2%) Metric Decrease: T12707 T1969 T3294 ManyAlternatives ManyConstructors T13035 T13379 T4801
* Do not print synonyms in :i (->), :i Type (#18594)Krzysztof Gogolewski2020-08-231-0/+2
| | | | | This adds a new printing flag `sdocPrintTypeAbbreviations` that is used specifically to avoid ghci printing 'type (->) = (->)' and 'type Type = Type'.
* Utils: clarify docs slightlyCraig Ferguson2020-08-221-1/+1
| | | | | The previous comment implies `nTimes n f` is either `f^{n+1}` or `f^{2^n}` (when in fact it's `f^n`).