[commit: ghc] wip/all-inlinable's head updated: missing import (ea6a686)

git at git.haskell.org git at git.haskell.org
Fri Jan 6 16:34:58 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

Branch 'wip/all-inlinable' now includes:

     947c8a5 Bump GHC HEAD's Version from 7.11 to 8.1
     bb7f2e3 Address #11245: Ensure the non-matched list is always non-empty
     25e4556 Various API Annotations fixes
     75851bf fix ghci build on ArchUnknown targets
     0579fe9 Improve exprIsBottom
     5ba3caa Comments only
     70eefbc Test Trac #11245
     351dea4 Drop redundant `-D__GLASGOW_HASKELL__=...` flag
     eae40e1 Use 0/1 instead of YES/NO as `__GLASGOW_HASKELL_TH__` macro value
     0d20737 Drop redundant/explicit `=1` in `-DFOO=1` flags
     2f923ce Drop pre-AMP compatibility CPP conditionals
     3c8cb7f Remove some redundant definitions/constraints
     12ee511 Remove ghc-7.8 `-package-name`-compat handling
     37945c1 Simplify -fcmm-sink handling for Parser.hs
     6a010b9 Update haskeline submodule to latest snapshot
     8afeaad travis: use GHC 7.10.3
     dafeb51 Canonicalise `MonadPlus` instances
     b469b30 Minor fix of MonadFail instance for `ReadPrec`
     ab0d733 Update Cabal submodule, Fixes #11326
     f3cc345 Add strictness for runRW#
     0b8dc7d API Annotations: AnnTilde missing
     78daabc mk/config.mk.in: drop unused CONF_CC_OPTS for ia64
     f5ad1f0 AnnDotDot missing for Pattern Synonym export
     256c2cf Test Trac #11336
     0490fed Linker: ARM: Ensure that cache flush covers all symbol extras
     d159a51 Linker: ARM: Refactor relocation handling
     48e0f9c Linker: Make debugging output a bit more readable
     07d127a Linker: Use contiguous mmapping on ARM
     d935d20 Omit TEST=T10697_decided_3 WAY=ghci
     1dbc8d9 Add test for #10379
     04f3524 Linker: ARM: Don't change to BLX if jump needed veneer
     c7d84d2 Update .mailmap [skip ci]
     7e599f5 Linker: Move helpers to #ifdef
     da0f043 Rewrite Haddocks for GHC.Base.const
     5c10f5c users_guide: Add ghci-cmd directive
     4c56ad3 Build system: delete ghc-pwd
     0acdcf2 Avoid generating guards for CoPats if possible (Addresses #11276)
     1a8b752 Add (failing) test case for #11347
     1f526d2 Release notes: Mention remote GHCi
     cdeefa4 ghc.mk: Add reference to Trac #5987
     77494fa Remove -Wtoo-many-guards from default flags (fixes #11316)
     e32a6e1 Add Cabal synopses and descriptions
     bbee3e1 StgCmmForeign: Push local register creation into code generation
     bd702f4 StgCmmForeign: Break up long line
     aa699b9 Extend ghc environment file features
     4dc4b84 relnotes: Note dropped support for Windows XP and earlier
     852b603 Restore old GHC generics behavior vis-à-vis Fixity
     cac0795 Change Template Haskell representation of GADTs.
     89ba83d Bump Cabal and Haddock to fix #11308
     7861a22 Add a note describing the protocol for adding a language extension
     f01eb54 Fall back on ghc-stage2 when using Windows' GHCi driver
     568736d users guide: Add documentation for custom compile-time errors
     5040686 users guide: Add links to release notes
     47367e0 Rewrite announce file
     0a04837 users guide: Tweak wording of RTS -Nmax description
     0839a66 Remove unused export
     3f98045 Tiny refactor
     97c49e9 Spelling in a comment
     290a553 Tidy up tidySkolemInfo
     4dda4ed Comment wibble
     29b4632 Inline solveTopConstraints
     dc97096 Refactor simpl_top
     02c1c57 Use an Implication in 'deriving' error
     a5cea73 Turn AThing into ATcTyCon, in TcTyThing
     9915b65 Make demand analysis understand catch
     1ee9229 Test Trac #10625
     c78fedd Typos in docs and comments
     6be09e8 Enable stack traces with ghci -fexternal-interpreter -prof
     09425cb Support for qRecover in TH with -fexternal-interpreter
     6f2e722 User's Guide: injective type families section
     0163427 Fix Template Haskell's handling of infix GADT constructors
     1abb700 Improve GHC.Event.IntTable performance
     c33e7c2 Fix +RTS -h when compiling without -prof
     10769a1 Rename the test-way prof_h to normal_h
     47ccf4d Add a pointer to the relevant paper for InScopeSet
     2bd05b8 Docs for stack traces in GHCi
     f7b45c3 Build system: fix `pwd` issues on Windows
     1cdf12c Fix test for T9367 (Windows)
     a6c3289 users_guide: Use semantic directive/role for command line options
     86d0657 users-guide: A few fixes
     8f60fd4 docs: Fix DeriveAnyClass reference in release notes and ANNOUNCE
     67b5cec user-guide: More semantic markup
     0dc2308 user-guide/safe_haskell: Fix typos
     a84c21e Reject import declaration with semicolon in GHCi
     831102f Parser: delete rule numbers + validate shift/reduce conlicts
     4405f9d Add failing testcase for #10603
     5cb236d fix -ddump-splices to parenthesize ((\x -> x) a) correctly
     fbd6de2 Add InjectiveTypeFamilies language extension
     4c9620f TrieMap: Minor documentation fix
     b1c063b ghc.mk: Use Windows_Target instead of Windows_Host
     8e0c658 Linker: Define ELF_64BIT for aarch64_HOST_ARCH
     00c8076 fix typo causing compilation failure on SPARC (ArchSparc -> ArchSPARC)
     6cb860a Add -prof stack trace to assert
     3e796e1 A little closer to supporting breakpoints with -fexternal-interpreter
     88d6d5a Use implicit CallStacks for ASSERT when available
     d44bc5c TemplateHaskell: revive isStrict, notStrict and unpacked
     ac3cf68 Add missing type representations
     e782e88 Add test for Data.Typeable.typeOf
     c3f9246 Print a message when loading a .ghci file.
     6ea24af Handle over-applied custom type errors too.
     c313327 Minor improvement in CoreDump outputs:
     c73333a Minor code refactoring
     61011b4 users-guide: Wibbles
     91dcc65 GHC.Generics: Fix documentation
     f0c4e46 Add tests for #11391
     b0641ad INSTALL.md: Mention -j and other wibbles
     78a4c72 Rename InjectiveTypeFamilies to TypeFamilyDependencies
     4dbc31b users-guide: Update language extension implications
     b355b8f users-guide: Add since annotations for language extensions
     83c13c2 user-guide: Use ghc-flag for dump formatting flags
     fd686c4 API Annotations: use AnnValue for (~)
     db371c1 T11300: Fix test on windows
     49e414a Remove lookup of sections by name instead use the index numbers as offsets
     91f1c60 Fix #11015 with a nice note.
     8959b03 ANNOUNCE: Mention powerpc code generator
     b90cac6 user-guide: Note Cabal version limitation
     faf3f96 users-guide: Fix cabal version number
     c6a3e22 Link command line libs to temp so
     e7eec3a Use XZ compression by default
     7cf16aa Don't output manpage in same directory as source
     756b228 Refactor lookupFixityRn-related code following D1744
     67fc3f3 configure.ac: Export MAKECMD to build system
     443bf04 Allow pattern synonyms which have several clauses.
     165ae44 Expand type/kind synonyms in TyVars before deriving-related typechecking
     e6ca930 Fix #11355.
     d4af57f Test #11252 in ghci/scripts/T11252
     d459f55 Fix #10872.
     6c07f14 Fix #11311
     3a7f204 Clarify topological sorting of spec vars in manual
     39ea4b4 Fix #11254.
     bafbde7 Constrained types have kind * in validity check.
     072191f Fix #11404
     33950aa Tiny refactoring in TcUnify
     80b4c71 Fix typo in error message (#11409)
     3c6635e Fix #11405.
     148a50b Fix some typos
     3a1babd Work SourceText in for all integer literals
     9308c73 Fix a number of subtle solver bugs
     3b6a490 Add missing T11408.hs
     ae1c48c rts/posix: Fail with HEAPOVERFLOW when out of memory during mmap
     d1ce1aa users-guide: Clean manpage build artifacts and fix usage of clean-target
     b3eb8fa Complete operators properly
     65b810b Show TYPE 'Lifted/TYPE 'Unlifted as */# in Show TypeRep instance
     f3a867e Add testcase for #11414
     2fd407c validate: Use gz compression during bindist check
     a7b751d un-wire-in error, undefined, CallStack, and IP
     5a62b6a Simplify API to tcMatchTys
     f02200f Layout only
     cb24e68 Fix typecheck of default associated type decls
     b7e5c30 White space only
     6e0c0fd Improve debug printing/warnings
     ec8a188 Refactoring on IdInfo and system derived names
     8e6a68d Add Trac #11427 to Note [Recursive superclasses]
     e2c7b7e Implement scoped type variables in pattern synonyms
     8e50301 Test Trac #11379
     5412899 Typo in comment
     817dd92 Fixes to "make clean" for the iserv dir
     b8abd85 Replace calls to `ptext . sLit` with `text`
     240ddd7 Switch from -this-package-key to -this-unit-id.
     cbc03f1 ghci: Kill global macros list
     d2ea7f9 Hide derived OccNames from user
     38666bd user-guide: Delete errant fragment
     aff51af users-guide: Begin documenting --frontend
     80265c4 Typos in comments
     9d33adb Check InScopeSet in substTy and provide substTyUnchecked
     713aa90 Re-export ghc-boot:GHC.Serialized as Serialized
     952eda2 Fix IfaceType generation for TyCons without TyVars
     975bdac T11266: Improve the test by adding more of the other problematic modules
     514bac2 Fix combineIdenticalAlts
     0373a84 Oops.  Add missing close-comment
     5cce095 Use (&&) instead of `if` in Ix derivation
     84b0ebe Rework derivation of type representations for wired-in things
     225afc4 Add test T9407 (Windows)
     6ddc991 Update submodule stm + random
     48d4bc5 substTy to substTyUnchecked to fix Travis build
     1ce1371 MkId: Update OpenKind reference
     2e65aae Add comments about tyCoVarsOfType
     e604e91 Comments only
     c572430 Re-add missing kind generalisation
     6f95e23 Comments only
     b3ee37c Improve pretty-printing of UnivCo
     07afe44 Remove the check_lifted check in TcValidity
     b2e6350 Strip casts in checkValidInstHead
     395ec41 Allow implicit parameters in constraint synonyms
     ede055e TyCoRep: Restore compatibility with 7.10.1
     f23b578 user-guide:: Improve -D description
     928484d user-guide: Refer to MIN_VERSION_GLASGOW_HASKELL from intro
     3883f99 rel-notes: Note the return of -Wmonomorphism-restriction
     7cb893f Update and improve documentation in Data.Foldable
     96303db Add a missing .gitignore entry in annotations tests
     2ffc260 Add -ignore-dot-ghci to tests that use --interactive
     4c4a0a5 Fix docstring GHC.IO.Handle.FD.openFileBLocking
     4c11db6 sphinx-build: fix python stack overflow (Trac #10950)
     b617e9f Improve comments in CmmSwitch
     85e147e Always run test T9407
     36b174d Add expected stderr for #11466 test case
     adb721b Make a constraint synonym for repeated BinaryStringRep and use it.
     835a2a2 Default non-canonical CallStack constraints
     2df4221 Add tests for #11465 and the kind invariant
     9048c3d Don't print "Loaded GHCi configuration" message in ghc -e (#11478)
     65881c0 Mark some ghci tests as req_interp
     6e5f828 Fix a formatting error in the user's guide
     4d51bfc Do not count void arguments when considering a function for loopification.
     b01288d rts: Disable tick timer unless really needed
     4e04043 Add test for Trac #11056
     f42db15 Remove unused IND_PERM
     06c2547 Small doc fix
     7cd37c5 Give a more verbose error message when desugaring a HsTypeOut
     8e9a870 Remove -Wredundant-superclasses from standard warnings
     1be8491 mkUserGuidePart: Better flag cross-referencing
     6f96109 user-guide: Reformat warning lists
     b5e52bf user-guide: Fix typos
     ec87788 Don't add ticks around type applications (#11329)
     923d215 user-guide: Document -L RTS flag
     89bdac7 Add test for #11473
     8b5ea7c User's guide: fix singular/plural typo in flagnames
     98d6a29 Docs: delete section on Hierarchical Modules
     edc68b2 Remove `replaceDynFlags` from `ContainsDynFlags`
     2c6fe5b Add -fwarn-redundant-constrains to test for #9708
     fd6dd41 Implement `-Wnoncanonical-monadfail-instances` warning
     ff21795 Special-case implicit params in superclass expansion
     746764c Refactor validity checking for type/data instances
     42c6263 Avoid recursive use of immSuperClasses
     f7e0e5f Improve tracing in checkValidInstance
     3c060f3 Fix exprIsHNF (Trac #11248)
     5c82333 Show error message for unknown symbol on Elf_Rel platforms
     edb30fd Comments only: more alternate names for ARM registers [skip ci]
     bc1e085 HscTypes: Fix typo in comment
     132c208 Rename -Wmissing-monadfail-instance to plural-form
     6e2658f Better document behavior of -Wmissed-specialisations
     128b678 user-guide: Note order-dependence of flags
     f0f63b3 Implement -Wunrecognised-warning-flag
     9fe7d20 Ensure that we don't produce code for pre-ARMv7 without barriers
     632f020 Less verbose output for the in-scope set
     cf788a5 White space only
     47b3f58 Add "ticks-exhausted" comment
     1c6d70c Kill off zipTopTCvSubst in favour of zipOpenTCvSubst
     016a0bd Fix two cloning-related bugs
     34c9a4e Missed plural renaming in user's guide
     5f5dc86 Minor users-guide markup fixup [skip ci]
     9b71695 Update transformers submodule to 0.5.1.0 release
     f1885df Update process submodule to 1.4.2.0 release
     3798b2a Fix three broken tests involving exceptions
     01809bc Pass InScopeSet to substTy in lintTyApp
     e24a9b5 Nicer error on +RTS -hc without -rtsopts or -prof
     6d2bdfd Fix segmentation fault when .prof file not writeable
     6817703 Split off -Wunused-type-variables from -Wunused-matches
     144ddb4 Construct in_scope set in mkTopTCvSubst
     eeb67c9 Testsuite: fixup req_profiling tests (#11496)
     e2bdf03 Build profiling libraries on `validate --slow` (#11496)
     44a5d51 Enable RemoteGHCi on Windows
     45fd83b Fix a typo in the note name in comments
     448ea97 Typos in comments
     1f6d142 ghci: fix trac issue #11481
     1c6130d rts/Timer: Actually fix #9105
     0dc7b36 Restore original alignment for info tables
     0d92d9c Use stage1 build variables when building the RTS
     d50609e Test for undef bugs in the LLVM backend when validating
     45c6fbc Document -fllvm-fill-undef-with-garbage
     4faa1a6 s/unLifted/unlifted for consistency
     2899aa5 Fix some substitution InScopeSets
     00cbbab Refactor the typechecker to use ExpTypes.
     5dcae88 Rename "open" subst functions
     85daac5 Fix cost-centre-stack bug when creating new PAP (#5654)
     a496f82 Remote GHCi: create cost centre stacks in batches
     71b1183 Update profiling test output
     0d5ddad fix validate breakage
     63700a1 Use the in_scope set in lint_app
     1b72534 Fixup test for #10728
     61e4d6b Mark dynamic-paper as expect_fail_for optasm and optllvm (#11330)
     d3b7db0 Fix the Windows build
     0dd663b Add closing parenthesis in comment for eqString (#11507)
     bc83c73 Add release note about flexible RebindableSyntax
     bb956eb Add asserts to other substitution functions
     6c7760b Define CTYPE for more Posix types
     2fbf370 Update unix submodule to latest snapshot
     b61f5f7 Put docs in /usr/share/doc/ghc-<version>
     4d0e4fe Add type signatures.
     90f688e Code formatting cleanup.
     6544f8d Properly track live registers when saving the CCCS.
     669cbef Fix Trac issue #11487.
     34519f0 When encountering a duplicate symbol, show source of the first symbol
     f8e2b7e Minor doc fixes to GHC.Generics
     a883c1b Missing @since annotations in GHC.Generics
     e5a0a89 Suppress substitution assertions to fix tests
     0d60165 Simplify ghc-boot database representation with new type class.
     94048f9 Hide the CallStack implicit parameter
     86897e1 Implement basic uniform warning set tower
     ba88aab Fix LOOKS_LIKE_PTR for 64-bit platforms
     2ad46a8 Add some Outputable instances
     02e3ce0 Typo in docs
     7329310 Fix runtime linker error message when old symbol had no owner
     dd0b7c7 Avoid mangled/derived names in GHCi autocomplete (fixes #11328)
     ddd38e7 Update unix submodule to latest snapshot
     af8fdb9 TyCoRep: Implement some helpers for dropping/checking Levity arguments
     2fb6a8c Remote GHCi: Optimize the serialization/deserialization of byte code
     7cb1fae Remote GHCi: batch the creation of strings
     c996db5 Remote GHCi: parallelise BCO serialization
     01c587c Fix Windows build after D1874
     07ed241 Use a correct substitution in tcCheckPatSynDecl
     a7ad0b9 Make TypeError a newtype, add changelog entry
     db97ed9 Add (failing) test for #11247
     871c96f TcMType: Add some elementary notes
     92c46a4 Update cabal_macros_boot.h
     483858e Update binary submodule to 0.8.2.0 release
     db121b2 Allow all RTS options to iserv
     28f951e Overhaul the Overhauled Pattern Match Checker
     bbc0ec5 Fix a few loose ends from D1795
     4f9967a Remove unused LiveVars and SRT fields of StgCase and StgLetNoEscape
     91a56e9 Use default xz compression level
     70980b1 GHCi: Fix Windows build (again)
     8aa9f35 Fix @since annotations for renamed pretty{CallStack,SrcLoc}
     38af3d1 Add a derived `Show SrcLoc` instance
     b49d509 Add test for #11516
     5d73fb6 Revert "Remove unused LiveVars and SRT fields of StgCase and StgLetNoEscape"
     f1f5837 unlit: mark local functions as 'static'
     72545c7 hp2ps: mark local functions as 'static'
     f3923d5 testsuite: ignore *.prof.normalised files
     1060301 mkDocs: Update for xz
     c96acf3 mkDocs: Fix fallout from c5f4f95c64006a9f
     66fa0ed validate: enable -DDEBUG in stage 1 by default
     7362809 rts: drop unused calcLiveBlocks, calcLiveWords
     9e43c7f rts: mark scavenge_mutable_list as static
     4f283a6 rts: mark 'copied' as static
     256c1b3 rts: drop unused getThreadCPUTime
     3dbd836 rts: mark 'wakeBlockingQueue' as static
     8abc7e7 rts: drop unused mut_user_time_during_heap_census
     39cba20 rts: mark 'removeFromRunQueue' as static
     7a48865 rts: mark 'setProgName' as static
     a49c9d4 rts: drop unused 'traverseAllRetainerSet'
     c358567 rts: mark 'blockedThrowTo' as static
     e1ca583 rts: mark 'ccs_mutex' and 'prof_arena' as static
     0e51109 rts: drop unused 'traceEventThreadRunnable'
     0a2bd9c rts: mark 'shutdownCapability' as static
     c0a0ee3 Fix haddocks for TypeError
     b3e9452 Bump haddock submodule
     8263d09 Remove unused export from TcUnify
     2cf3cac Allow foralls in instance decls
     20f90ea Fix SimpleFail12 error output
     e2b66a0 user-guide: Add cross-reference for -XUnicodeSyntax
     4e65301 Add Edward Kmett's example as a test case
     6036cb6 Comments only, on the invariants of GlobalRdrEnv
     a96c4e7 Add comments to TcCoercibleFail
     ee11a84 White space and comments only
     8871737 Document and improve superclass expansion
     e72665b Comment out some traceFlat calls
     7212968 Improve tracing in TcInteract
     d6b68be Improve error messages for recursive superclasses
     f79b9ec Use runTcSDeriveds for simplifyDefault
     6252b70 A small, local refactoring of TcSimplify.usefulToFloat
     43e02d1 Fix a nasty superclass expansion bug
     5a58634 release notes: Note new two-step allocator
     96d4514 Some tiding up in TcGenDeriv
     fac0efc Define mkTvSubst, and use it
     c9ac9de Test Trac #11552
     489a9a3 Define tyConRolesRepresentational and use it
     023fc92 Remove unused LiveVars and SRT fields of StgCase
     da19c13 Print * has Unicode star with -fprint-unicode-syntax
     16cf460 testsuite: Un-break T5642
     4ec6141 Fix the removal of unnecessary stack checks
     04fb781 Early error when crosscompiling + haddock/docs
     bfec4a6 Unset GREP_OPTIONS in build system
     1f894f2 Restore derived Eq instance for SrcLoc
     c8702e3 TcErrors: Fix plural form of "instance" error
     99cb627 TcPatSyn: Fix spelling of "pattern" in error message
     7953b27 DynFlags: drop tracking of '-#include' flags
     2f9931e add Template Haskell regression test for #9022.
     93e2c8f Expand users' guide TH declaration groups section (#9813)
     d80caca Error early when you register with too old a version of Cabal.
     c57d019 docs: add newline after '.. ghc-flag::'
     a824972 mkUserGuide: fix option wrapping in a table
     b565830 Wrap solveEqualities in checkNoErrs
     d27da53 Replace mkTvSubstPrs (a `zip` b) with zipTvSubst a b
     8500855 Always do eta-reduction
     62d1888 Comments about ru_auto
     023bf8d Ignore untracked in nofib
     51a3392 sizeExpr: fix a bug in the size calculation
     46af683 compiler: Do not suggest nor complete deprecated flags fix trac issue #11454
     efba41e Another batch of typo fixes in non-code
     dbf72db Build the substitution correctly in piResultTy
     b7dfbb4 Add test for #11319
     8da6a16 Revert "sizeExpr: fix a bug in the size calculation"
     be3d7f6 Add IsList instance for CallStack, restore Show instance for CallStack
     f3b9db3 Revert "Build the substitution correctly in piResultTy"
     c6485d5 Simplify AbsBinds wrapping
     1251518 Beef up tc124
     d084624 Improve pretty-printing of HsWrappers
     24305be Minor refactoring to tauifyMultipleMatches
     6cf9b06 User manual improvments
     f37bb54 testsuite: tweak error messages for new Show instance
     cd4a7d0 renamer discards name location for HsRecField
     4bba19a Update directory submodule to v1.2.5.1 release
     18cd712 Improve error message suppression
     bb7f230 Comments only
     160765f Document -dynamic-too (#11488)
     f6b98ea Tiny refactor; use guards instead of 'if'
     0057125 Comments and white space
     e2f7d77 A tiny, outright bug in tcDataFamInstDecl
     023742e Add a testcase for #11362
     426a25c Make T11361 actually run with reversed uniques
     3c39bec Rename missing-pat-syn-sigs to missing-pat-syn-signatures
     ed69b21 Add missing newlines at end of file [skip ci]
     d066e68 Testsuite: delete only_compiler_types, assume ghc
     c8df3f1 Bump haddock submodule
     525a304 Make bootstrapping more robust
     693a54e Improved error message about exported type operators.
     af5a0e5 Fix two wrong uses of "data constructor" in error msgs
     3116003 PowerPC: Improve float register assignment.
     49c5cb4 Fix typos
     5fc06b9 Suggest candidate instances in error message
     ad30c76 Remove documentation for -Wlazy-unlifted-bindings
     2b906af DynFlags: Don't panic on incompatible Safe Haskell flags
     6f25fb3 Testsuite: delete compiler_lt/le/gt/ge setup functions
     34c9523 Comments only
     21b4228 Simplify the defn of coreViewOneStarKind
     4c6e95e Small refactor and comments
     b962bcc Make exactTyCoVarsOfTypes closed over kinds.
     90f3561 Existentials should be specified.
     aff5bb4 Add missing kind cast to pure unifier.
     7d8031b Remove extraneous fundeps on (~)
     6f952f5 Use CoercionN and friends in TyCoRep
     43468fe Fix #11241.
     489e6ab Fix #11246.
     a615215 Fix #11313.
     67d2226 Derive Eq and Ord instance for SrcLoc and RealSrcLoc
     a82956d Remove superfluous code when deriving Foldable/Traversable
     525b54c users-guide: Fix typos
     0c420cb Comments only (#11513)
     27842ec Fix thinko that crept into D1908
     01449eb Fix desugaring of bang-pattern let-bindings
     b529255 (Another) minor refactoring of substitutions
     4d031cf Improve piResultTys and friends
     a008ead Take type-function arity into account
     206a8bf Unwire Typeable representation types
     0b68cbe Bump haddock submodule
     8b073f6 A few more typos in non-code
     2f733b3 Delete support for deprecated "-- # ..."-style haddock options
     d738e66 Modifier letter in middle of identifier is ok
     c6007fe Pass -haddock to tests in should_compile_*flag*_nohaddock
     a8653c8 Docs: no space in `-i⟨dir1⟩:⟨dir2⟩` [skip ci]
     6cec905 Refactoring only: use ExprLStmt
     3259bf6 Fix a bug in ApplicativeDo (#11612)
     2340485 Fix a double-free bug in -fexternal-interpreter
     80d35be Use a better test for profiling
     1ef7add Add test (only) to assure that #11535 is fixed
     9634e24 unexport MAKEFLAGS when running tests (#11569)
     0b00add Add test for #6132: hash bang + CPP
     6e691ca Testsuite: pass '-s --no-print-directory' to MAKE
     f451039 Build system: fix sed expression (#11537)
     bb9cd45 Fix GHC.Stats documentation markup (#11619)
     ed11909 Docs: -keep-llvm-file(s)/-ddump-llvm imply -fllvm
     d3cf2a9 Add missing files
     31c312e Testsuite: delete Windows line endings [skip ci] (#11631)
     8626ac9 Testsuite: delete Windows line endings [skip ci] (#11631)
     754a2f2 Testsuite: delete Windows line endings [skip ci] (#11631)
     6074c10 Testsuite: delete Windows line endings [skip ci] (#11631)
     d5e8b39 Testsuite: delete Windows line endings [skip ci] (#11631)
     978c3ea Testsuite: accept output without Windows line endings (#11631)
     42f06f6 Testsuite: accept output without Windows line endings (#11631)
     28620ba Testsuite: delete Windows line endings [skip ci] (#11631)
     6d0aa9f Testsuite: delete Windows line endings [skip ci] (#11631)
     73e4095 Testsuite: cleanup profiling/should_run/all.T (#11521)
     176be87 Filter out -prof callstacks from test output (#11521)
     661aa07 Testsuite: failing profiling tests (#10037)
     2aee419 Allow combining characters in identifiers (#7650)
     a3e0e93 Testsuite: MAKEFLAGS is magic, do not unexport it
     32a9a7f Extend `-Wunrecognised-warning-flag` to cover `-f(no-)warn-*`
     ce36115 Follow-up to 32a9a7f514bdd33ff72a673ade
     d8c64e8 Address #11471 by putting RuntimeRep in kinds.
     a9dc62a Remove "use mask" from StgAlt syntax
     009a999 TyCoRep: Add haddock sections
     c1efdcc Overload the static form to reduce verbosity.
     feb19ea testsuite: mark tests broken on powerpc64
     8e19d3a base: A selection of fixes to the comments in GHC.Stats
     0c7db61 ApplicativeDo: Handle terminal `pure` statements
     6319a8c HscMain: Delete some unused code
     673efcc Add more type class instances for GHC.Generics
     6658491 Make warning names more consistent
     52879d1 Reconstruct record expression in bidir pattern synonym
     ebaa638 Bump haddock.base allocations
     073e20e cmpTypeX: Avoid kind comparison when possible
     6739397 (Alternative way to) address #8710
     6350eb1 Handle multiline named haddock comments properly
     e38c07b Improve accuracy of suggestion to use TypeApplications
     20ab2ad Note new GHC.Generics instances in release notes
     116528c Improve pattern synonym error messages (add `PatSynOrigin`)
     8e6e022 Testsuite: Introduce config.plugin_way_flags.
     e02b8c8 Testsuite: for tests that use TH, omit *all* prof_ways
     90fa8cf Mark tests for #11643, #11644, #11645 and #9406 expect_broken
     9b49c65 Testsuite: delete empty files [skip ci]
     1badf15 Testsuite: do not write empty files on 'make accept'
     bb5afd3 Print which warning-flag controls an emitted warning
     bbfff22 Unconditionally handle TH known key names.
     a026112 Typos in comments, etc.
     e3f341f Fix and refactor strict pattern bindings
     a81e9d5 Special case for desugaring AbsBinds
     4ddfe13 Get the right in-scope set in specUnfolding
     7496be5 Exclude TyVars from the constraint solver
     253ccdf Comments and white space only
     b4dfe04 Fix kind generalisation for pattern synonyms
     e193f66 Filter out BuiltinRules in occurrence analysis
     ef7b1d5 Test Trac #11611
     eee040c Update transformer submodule to v0.5.2.0 release
     890e2bb GHC.Generics: Ensure some, many for U1 don't bottom
     3ee4fc0 rts: drop unused global 'blackhole_queue'
     b9c697e Print which flag controls emitted desugaring warnings
     869d9c6 Print which flag controls emitted lexer warnings
     82f200b Annotate `[-Wredundant-constraints]` in warnings (re #10752)
     b6c61e3 Print which flag controls emitted SafeHaskell warnings
     3cd4c9c Annotate `[-Wdeferred-type-errors]` in warnings (re #10752)
     46f3775 Default to -fno-show-warning-groups (re #10752)
     171d95d Missing Proxy instances, make U1 instance more Proxy-like
     ad4428d base: Mark Data.Type.Equality as Trustworthy
     2535c82 Fix bug where reexports of wired-in packages don't work.
     f72bdbd Refactor `warnMissingSignatures` in `RnNames.hs`
     16e97c1 Build system: Correctly pass `TARGETPLATFORM` as host
     2e49a31 DynFlags: Add -Wredundant-constraints to -Wall
     e3b9dbf Testsuite: check actual_prof_file only when needed
     de01de7 Remove some more Windows line endings [skip ci]
     f8a5dd0 Only add -fshow-warning-groups for ghc >= 7.11 (#10752)
     49c55e6 Skip TEST=TcCoercibleFail when compiler_debugged
     3c29c77 Do not check synonym RHS for ambiguity
     243e2ab Comments only
     2d52c3a A bit more tracing in TcHsType.tcTyVar
     a0899b2 Remove unnecessary isTyVar tests in TcType
     57b4c55 Don't complain about unused Rule binders
     286dc02 Fix an outright bug in expandTypeSynonyms
     aea1e5d Use tyConArity rather than (length tvs)
     91a6a9c Add Monoid instance for FastString
     15517f3 SimplEnv: Add Haddock headings to export list
     1f3d953 users-guide: Mention #11558 in release notes
     120b9cd rts/timer: use timerfd_* on Linux instead of alarm signals
     6ca9b15 GHCi: Fix load/reload space leaks (#4029)
     3801262 Fix printing of an `IfacePatSyn`
     1d6177b Using unsafe foreign import for rtsSupportsBoundThreads (part of #9696)
     bd681bc Drop module qualifier from punned record fields (#11662)
     ade1a46 Fix minimum alignment for StgClosure (Trac #11395)
     5e2605e GhcMake: Clang/ASSERT fix
     13a801a Revert "Mark tests for #11643, #11644, #11645 and #9406 expect_broken"
     82e36ed Reduce fragmentation from m32_allocator
     90e1e16 Split external symbol prototypes (EF_) (Trac #11395)
     1a9734a template-haskell: Drop use of Rank2Types/PolymorphicComponents
     941b8f5 template-haskell: remove redundant CPP use
     1c76e16 template-haskell: define `MonadFail Q` instance
     4c3a0a4 Fix the implementation of lazyId
     5a494d8 Refactoring around TcPatSyn.tcPatToExpr
     374f919 Update Cabal submodule to latest HEAD snapshot
     c42cdb7 fix Float/Double unreg cross-compilation
     fc16690 Fix #11624, cannot declare hs-boot if already one in scope.
     c937f42 Add regression test for #11555
     a1c4230 Use catchException in a few more places
     30ee910 Make `catch` lazy in the action
     f3def76 add regression test for #11145.
     767ff7c Document Quasi-quotes/list comprehension ambiguity
     a74a384 Include version in AC_PACKAGE_TARNAME
     f8056fc Make integer-gmp operations more strict
     d48220e Add Note [Running splices in the Renamer]
     90b8af0 Fix readme link to FixingBugs wiki page
     06b70ff Add doc to (<$>) explaining its relationship to ($)
     8626d76 rtx/posix/Itimer.c: Handle return value of `read`
     6a2992d Add MonadUnique instance for LlvmM
     e764ede Add ghc-flag directory for -XPatternGuards
     2908ae8 Handle unset HOME environment variable more gracefully
     3ea11eb Move getOccFS to Name
     7ba817c Bump allocations for T6048
     2f45cf3 Add -foptimal-applicative-do
     e46742f rts: fix threadStackUnderflow type in cmm
     4d791b4 Simplify: Make generated names more useful
     41051dd ghci: add message when reusing compiled code #9887
     92821ec LlvmCodeGen: Fix generation of malformed LLVM blocks
     9ee51da users_guide: Break up -fprint-* description
     d12166a Fix the name of the Word16ElemRep wired-in datacon
     3f60ce8 Add regression test for #11702
     18fbfa3 Move and expand (slightly) TypeApplications docs
     e9bf7bb Fix #11407.
     84c773e Fix #11334.
     35d37ff Fix #11401.
     972730c Refactor visible type application.
     6c768fc Expand Note [Non-trivial definitional equality]
     693b38c Test case for #11699 in typecheck/should_compile
     e7a8cb1 Document TypeInType (#11614)
     55577a9 Fix #11648.
     3f5d1a1 Allow eager unification with type families.
     de4df6b Testsuite wibbles from previous commits.
     19be538 Remove redundant anonymiseTyBinders (#11648)
     857e9b0 Incorporate bgamari's suggestions for #11614.
     1eefedf Fix #11357.
     aade111 Fix #11473.
     f602f4a Fix printing of "kind" vs. "type"
     5d98b8b Clean up some pretty-printing in errors.
     46f9a47 DriverPipeline: Fix 'unused arguments' warnings from Clang
     b5565f1 Fix #11711.
     c5ed41c typechecker: fix trac issue #11708
     3fe87aa Fix #11716.
     f4f315a Fix #11512 by getting visibility right for methods
     220a0b9 Add test for #9646
     3ddfcc9 PrelRules: Fix constant folding for WordRemOp
     2841cca Mark GHC.Real.even and odd as INLINEABLE
     c095ec5 Ensure T11702 always runs with optasm
     c0f628d Revert "Add test for #11473"
     cb7ecda Fix duplicate T11334 test
     08d254b Fix T9646
     7186a01 Dwarf: Add support for labels in unwind expressions
     ba95f22 prof: Fix heap census for large ARR_WORDS (#11627)
     b735e99 DsExpr: Don't build/foldr huge lists
     289d57a Add test for incompatible flags (issue #11580)
     cb3456d base: Rework System.CPUTime
     e6a44f2 T11145: Fix expected output
     286c65f base: Fix CPUTime on Windows
     3ade8bc Delete a misleading comment in TyCon
     2cb5577 Remove unnecessary Ord instance for ConLike
     c37a583 Remove unused substTyWithBinders functions
     af2f7f9 Fix exponential algorithm in pure unifier.
     01b29eb TypeApplications does not imply AllowAmbiguousTypes
     0706a10 Add two small optimizations. (#11196)
     1701255 Fix #11635 / #11719.
     0b89064 Make equality print better. (#11712)
     f8ab575 Rename test for #11334 to 11334b, fixing conflict
     3e1b882 Prevent eager unification with type families.
     9477093 Comment a suspicious zonk in TcFlatten.
     35e9379 Track specified/invisible more carefully.
     5c0c751 Zonk before calling splitDepVarsOfType.
     d978c5e Fix #11723 and #11724.
     e19e58c Improve panicking output
     1934f7f stgMallocBytes: Tolerate malloc(0) returning a NULL ptr
     2d6d907 Comments (only) in TcFlatten
     6f0e41d PPC NCG: Emit more portable `fcmpu 0, ...` instead of `fcmpu cr0, ...`
     685398e Use the correct in-scope set in coercionKind
     0beb82c Avoid running afoul of the zipTvSubst check.
     7e74079 Comment fix
     7d5ff3d Move applyTysX near piResultTys
     db9e4eb Move DFunUnfolding generation to TcInstDcls
     e57b9ff Fix regression test for #11145.
     2ddfb75 base: Fix ClockGetTime on OS X
     da3b29b Ensure T9646 dump-simpl output is cleaned
     8048d51 ErrUtils: Add timings to compiler phases
     997312b Add `PatSynSigSkol` and modify `PatSynCtxt`
     2708c22 Close ticky profiling file stream after printing (#9405)
     03a1bb4 Add unicode syntax for banana brackets
     6c2c853 Various ticky-related work
     9f9345e Create empty dump files (fixes #10320)
     0db0594 DsExpr: Rip out static/dynamic check in list desugaring
     8335cc7 Add expected output for T9405
     ef653f1 Revert "Various ticky-related work"
     1448f8a Show: Restore redundant parentheses around records
     371608f Default RuntimeRep variables unless -fprint-explicit-runtime-reps
     0bd0c31 Defer inlining of Eq for primitive types
     2b5929c Comments only
     cb08f8d Tidy up handling of coercion variables
     343349d Avoid local label syntax for assembler on AIX
     2cebbe6 users_guide: Fix various issues
     8ff6518 users-guide: Add -Wredundant-constraints to flags reference
     173a5d8 users_guide: small improvements on pattern synonyms.
     2414952 Add option `no-keep-hi-files` and `no-keep-o-files` (fixes #4114)
     df26b95 Add NCG support for AIX/ppc32
     4dc8835 Remove code-duplication in the PPC NCG
     26f86f3 base: Fix GHC.Word and GHC.Int on 32-bit platforms
     84dd9d0 An extra traceTc in tcExpr for ExprWithSig
     356e5e0 Do not eta-reduce across Ticks in CorePrep
     12372ba CorePrep: refactoring to reduce duplication
     067335a A raft of comments about TyBinders
     b416630f Test Trac #11728
     da4bc0c Document implicit quantification better
     454585c More clarification in docs for implicit quantification
     4e98b4f DynFlags: Initialize unsafeGlobalDynFlags enough to be useful
     e8d3567 Panic: Try outputting SDocs
     d0787a2 testsuite: Identify framework failures in testsuite summary
     1b4d120 DWARF: Add debugging information chapter to users guide
     882179d RTS: Fix & refactor "portable inline" macros
     4da8e73 Fix #11754 by adding an additional check.
     12a76be Check for rep poly on wildcard binders.
     9f73e46 Clarify Note [Kind coercions in Unify]
     06cd26b Remove now obsolete LD_STAGE0 hack
     c7b32ad Remove now pointless INLINE_ME macro
     61df7f8 Fix AIX/ppc codegen in `-prof` compilation mode
     0bca3f3 Scrap IRIX support
     f911358 Scrap DEC OSF/1 support
     ffc802e Drop Xcode 4.1 hack and fix ignored CC var issue
     afc48f8 Autoconf: detect and set CFLAGS/CPPFLAGS needed for C99 mode
     49b9d80 Do not test for existence of the executable
     eb25381 Update bytestring submodule to latest snapshot
     cd3fbff Remove obsolete --with-hc flag from ./configure
     91b96e1 fix compilation failure on Solaris 11
     a658ad9 Reenable external-json linters
     0f0c138 base: Document caveats about Control.Concurrent.Chan
     415b706 users-guide: Provide more depth in table-of-contents
     eb8bc4d users-guide: Wibbles
     aa61174 users-guide: Add references to various issues in bugs section
     7393532 Use a correct substitution in tcInstType
     a49228e Build correct substitution in instDFunType
     4a93e4f Use the correct substitution in lintCoercion
     5097f38 Add Data.Functor.Classes instances for Proxy (trac issue #11756)
     b0ab8db base: Add comment noting import loop
     be2a7ba cleanup POSIX/XOPEN defines for switch to C99
     85e6997 Remove all mentions of IND_OLDGEN outside of docs/rts
     30b9061 Be more explicit about closure types in ticky-ticky-report
     38c7714 Ticky: Do not count every entry twice
     8af1d08 Typo in Note name
     80d4fdf SpecConstr: Transport strictness data to specialization’s argument’s binders
     e6e17a0 Rename isNopSig to isTopSig
     c8138c8 Do not print DmdType in Core output
     cf768ec Tes suite output updates
     d5d6804 rename: Disallow type signatures in patterns in plain Haskell
     ae6a56e users-guide/rel-notes: Note broken-ness of ImpredicativeTypes
     eb6b709 base: Fix haddock typo
     cb9a1e6 Add testcase for #11770
     a76e6f5 Typos in non-code
     1757dd8 Don't recompute some free vars in lintCoercion
     3d245bf Do not claim that -O2 does not do better than -O
     973633a Comments only in Unify.hs
     7aa4c52 rts/posix/Itimer.c: Handle EINTR when reading timerfd
     d1179c4 ghc-prim: Delay inlining of {gt,ge,lt,le}Int to phase 1
     c0e3e63 Defer inlining of Ord methods
     58bbb40 ghc-prim: Mark unpackCStringUtf8# and unpackNBytes# as NOINLINE
     e9c2555 Don't require -hide-all-packages for MIN_VERSION_* macros
     bc953fc Add -f(no-)version-macro to explicitly control macros.
     24d7615 Kill the magic of Any
     8f66bac Comments only
     1f68da1 Minor refactoring in mkExport
     2e5e822 Comments only
     bdd9042 Refactor in TcMatches
     174d3a5 Small refactor of TcMType.tauifyExpType
     0ad2021 Make SigSkol take TcType not ExpType
     9fc65bb Refactor error generation for pattern synonyms
     28fe0ee Demand Analyzer: Do not set OneShot information
     da260a5 Revert accidental change to collectTyAndValBinders
     6ea42c7 Revert "Demand Analyzer: Do not set OneShot information"
     3806891 Make the example for -M work
     72bd7f7 Improve printing of pattern synonym types
     f2a2b79 Deeply instantiate in :type
     90d7d60 rts: Make StablePtr derefs thread-safe (#10296)
     b3ecd04 Elaborate test for #11376
     9b6820c Bump binary submodule
     7407a66 Don't infer CallStacks
     2f3b803 Use exprCtOrigin in tcRnExpr
     1e6ec12 Fix misattribution of `-Wunused-local-binds` warnings
     351f976 T10272, T4340: Add 32-bit output
     726cbc2 T10870: Skip on 32-bit architectures
     1a8d61c testsuite: Update 32-bit performance numbers
     2265c84 Core pretty printer: Omit wild case binders
     5b986a4 CSE code cleanup and improvement
     0f58d34 Demand Analyzer: Do not set OneShot information (second try)
     c9e8f80 Set tct_closed to TopLevel for closed bindings.
     eda273b runtime: replace hw.ncpu with hw.logicalcpu for Mac OS X
     27528b3 Adjust performance numbers
     06b7ce2 testsuite: One more 32-bit performance slip
     6b6beba Fix installation of static sphinx assets
     535896e rts: Fix parsing of profiler selectors
     2bcf0c3 Revert "testsuite: One more 32-bit performance slip"
     eca8648 GHC.Base: Use thenIO in instance Applicative IO
     f0af351 Remove obsolete comment about the implementation of foldl
     f9d26e5 Fix a comment: triple -> tuple
     485608d Refactor comments about shutdown
     c4a7520 Provide an optimized replicateM_ implementation #11795
     90d66de Add doc to (<=<) comparing its type to (.)
     f3beed3 Remove left-over shell-tools.c
     6d7fda5 Remove spurious STG_UNUSED annotation
     2f82da7 Fix Template Haskell bug reported in #11809.
     d2e05c6 Reduce default for -fmax-pmcheck-iterations from 1e7 to 2e6
     5a1add1 Export zonkEvBinds from TcHsSyn.
     470d4d5 Fix suggestions for unbound variables (#11680)
     cf5ff08 Bump haddock submodule
     ad532de base: Fix "since" annotation on GHC.ExecutionStack
     7443e5c Remove the instantiation check when deriving Generic(1)
     378091c RtsFlags: Un-constify temporary buffer
     8987ce0 Typos in Note
     90538d8 Change runtime linker to perform lazy loading of symbols/sections
     46e8f19 Fix a closed type family error message
     02a5c58 Filter out invisible kind arguments during TH reification
     8b57cac Added (more) missing instances for Identity and Const
     aadde2b Deriving Functor-like classes should unify kind variables
     2ef35d8 Use `@since` annotation in GHC.ExecutionStack
     c6e579b Add linker notes
     83eb4fd Small simplification (#11777)
     5c4cd0e Cache the size of part_list/scavd_list (#11783)
     f4446c5 Allocate blocks in the GC in batches
     b1084fd Fix #11811.
     dd99f2e Fix #11797.
     0b6dcf6 Fix #11814 by throwing more stuff into InScopeSets
     d81cdc2 Teach lookupLocalRdrEnv about Exacts. (#11813)
     49560ba Fix commented out debugging code in ByteCodeGen
     227a29d Fix typos: tyars -> tyvars
     20f9056 Remove some old commented out code in StgLint
     3a34b5c Add a test case for #11731.
     f4fd98c Add a final demand analyzer run right before TidyCore
     928d747 Kill some unnecessary varSetElems
     2acfaae Comments only
     e24b3b1 Adjust error check for class method types
     31e4974 Remove some gratitious varSetElemsWellScoped
     8d66765 Increase an InScopeSet for a substitution
     aaaa61c users-guide: Note change in LLVM support policy
     10c6df0 utils: Provide CallStack to expectJust
     116088d testsuite: Add T11824
     cb0d29b testsuite: Add test for #11827
     9d063b6 Linker: Fix signedness mismatch
     933abfa rel-notes: Add note about UndecidableSuperClasses and #11762
     54e67c1 Remove dead function SimplUtils.countValArgs
     f0e331b Comments only, on Type.topSortTyVars
     a7ee2d4 Improve TcFlatten.flattenTyVar
     e9ad489 libdw: More precise version check
     d77981e rts/RetainerProfile: Remove unused local
     bf17fd0 deriveConstants: Verify sanity of nm
     f4e6591 Bump haddock submodule
     865602e Rework CC/CC_STAGE0 handling in `configure.ac`
     3f3ad75 Update `directory` submodule to v1.2.6.0 release
     4cbae1b Update array submodule to v0.5.1.1 release tag
     97f2b16 Add Windows import library support to the Runtime Linker
     04b70cd Add TemplateHaskell support for Overlapping pragmas
     89b6674 TH: Tweak Haddock language
     7a1c073 users-guide: Fix typo
     07dc330 validate: Note existence of config_args variable
     7005b9f Add flag to control number of missing patterns in warnings
     36a0b6d Check CCS tree for pointers into shared object during checkUnload
     177aec6 Linker: Clean up #if USE_MMAP usage
     a392208 Resolve symlinks when attempting to find GHC's lib folder on Windows
     93d85af Update `directory` submodule to v1.2.6.1 release
     dd920e4 Silence unused-import warning introduced by 93d85af9fec968b
     8a75bb5 Update haskeline submodule to 0.7.2.3 release
     3dac53f Make it easy to get hyperlinked sources
     10d808c relnotes: Add note about #11744 and workaround
     87114ae Use stdint types to define SIZEOF and ALIGNMENT of INTx/WORDx
     32ddd96 Remove obsolete/redundant FLEXIBLE_ARRAY macro
     350ffc3 rts: Limit maximum backtrace depth
     d1ce35d rts: Don't use strndup
     8556f56 Update `directory` submodule to v1.2.6.2 release
     a3c37c3 Remove unused import of emptyNameEnv
     d59939a Define TyCoRep.ppSuggestExplicitKinds, and use it
     17eb241 Refactor computing dependent type vars
     8136a5c Tighten checking for associated type instances
     9de405d Kill dead TauTvFlavour, and move code around
     81e2279 Update hsc2hs submodule
     91ee509 Mark GHC.Stack.Types Trustworthy
     96e1bb4 Update deepseq submodule to latest 1.4.2.0 snapshot
     ff290b8 Update binary submodule to 0.8.3.0 release
     15b7e87 Update `pretty` submodule to v1.1.3.3 release
     81b14c1 Update unix submodule to v2.7.2.0 release
     7f71dbe Bump haddock submodule
     81aa3d1 Reduce use of instances in hs-boot files
     871f684 Define NameSet.intersectFVs
     7319b80 Tighten up imports, white space
     353d8ae SCC analysis for instances as well as types/classes
     61191de Fix two buglets in 17eb241 noticed by Richard
     cdcf014 Tighten up imports on TcTyClsDecls
     687c778 Kill unnecessary varSetElemsWellScoped in deriveTyData
     62943d2 Build a correct substitution in dataConInstPat
     55b1b85 Accept tcrun045 output
     2e33320 Rename FV related functions
     98a14ff Point to note about FV eta-expansion performance
     7c6585a Remove mysterious varSetElemsWellScoped in tidyFreeTyCoVars
     8c33cd4 testsuite: Bump max bytes used of T4029
     f02af79 Improve the behaviour of warnIf
     edf54d7 Do not use defaulting in ambiguity check
     9421b0c Warn about simplifiable class constraints
     251a376 Test Trac #3990
     26a1804 wibble to simplifiable
     24d3276 A little more debug tracing
     c2b7a3d Avoid double error on out-of-scope identifier
     970ff58 Simplify defaultKindVar and friends
     6ad2b42 Refactor free tyvars on LHS of rules
     ed4a228 Fix typos: alpah -> alpha
     4221cc2 Typo: veraibles -> variables
     a9076fc Remove unused tyCoVarsOfTelescope
     0f96686 Make benign non-determinism in pretty-printing more obvious
     03006f5 Get rid of varSetElemsWellScoped in abstractFloats
     28503fe deriveConstants: Fix nm-classic error message
     e8c04d4 Testsuite: Delete test for deprecated "packedstring"
     dadf82d Testsuite: fixup lots of tests
     2a83713 Testsuite: delete Roles9.stderr
     fd5212f Testsuite: delete unused concurrent/prog002/FileIO.hs
     c9bcaf3 Kill varSetElemsWellScoped in quantifyTyVars
     e68195a RTS: Add setInCallCapability()
     95f9334 GHCi: use real time instead of CPU time for :set -s
     d396996 Doc improvement for ApplicativeDo
     24864ba Use __builtin_clz() to implement log_2()
     0712f55 Just comments & reformatting
     2dc5b92 Kill varSetElems in TcErrors
     94320e1 Kill varSetElems try_tyvar_defaulting
     f13a8d2 Kill varSetElems in markNominal
     a48ebcc Implement the state hack without modifiyng OneShotInfo
     5adf8f3 Document -fmax-pmcheck-iterations a bit better
     a0e1051 Recommend more reliable recourse for broken nm
     57c636f Update nofib submodule to nofib master
     fa3ba06 Expand the comment on pprVarSet
     82538f6 Kill varSetElems in injImproveEqns
     af6dced Comments only
     a2abcf6 Minor improvement to error message
     1e86cab Comments only
     9ed57d6 Remove unused unifyType_
     4c746cb Add missing solveEqualities
     3dce4f2 Refactor RecordPatSynField, FieldLabel
     c4dd4ae Better documentation of -XConstrainedClassMethods
     c5b1014 Fix debug-only check in CoreLint
     546f24e Revert "Use __builtin_clz() to implement log_2()"
     3a53380 Kill unused foldOccSet
     196ce62 Testsuite: delete accidentally committed .stderr.normalised file
     89c6d07 Testsuite: add -ignore-dot-ghci to some ghci tests [skip ci]
     9dc34d3 Testsuite: fix T11223_simple_(unused_)duplicate_lib
     b0569e8 Testsuite: benign test fixes
     3c426b0 Add uniqSetAny and uniqSetAll and use them
     7312923 Kill mapUniqSet
     32c0aba Testsuite: delete -fesc tests
     e20b3ed Testsuite: delete T5054 and T5054_2 (#5054)
     bcfee21 rts/LdvProfile.c: Fix NULL dereference on shutdown
     f255f80 Linker: Fix implicit function declaration warning on OS X
     6e195f4 Remove unused foldFsEnv
     031de8b Remove unused foldNameEnv
     f99db38 Fix path to the new build system, now called Hadrian.
     0fa1d07 testsuite: fix up T11223's Makefile
     a2970f8 RTS: delete BlockedOnGA* + dead code
     c5919f7 Remove the incredibly hairy splitTelescopeTvs.
     7242582 Test #11484 in th/T11484
     00053ee Fix typo: Superclases -> Superclasses
     b725fe0 PPC NCG: Improve pointer de-tagging code
     c4259ff Testsuite: make CLEANUP=1 the default (#9758)
     2ae39ac Testsuite: accept new output for 2 partial-sigs tests
     2fe7a0a Fix reference to Note in TcCanonical
     cb05860 Comment typos: Mkae -> Make, Hsakell -> Haskell
     49bae46 Comment typo: unambigious -> unambiguous
     f69e707 Typos in DmdAnal
     e6627d1 Fix aggressive cleanup of T1407
     868d2c4 rts: Remove deprecated C type `lnat`
     eac6967 users-guide: Add index entry for "environment file"
     18676a4 Bump haddock submodule
     533037c Greater customization of GHCi prompt
     16a51a6 rts: Close livelock window due to rapid ticker enable/disable
     65e13f6 rts: Split up Itimer.c
     df9b772 Catch errors from timerfd_settime
     55f4009 Kill Itimer.h
     999c464 rts/itimer/pthread: Stop timer when ticker is stopped
     116d3fe Remove unused getScopedTyVarBinds
     1161932 Add T11747 as a test
     ecc0603 deriveConstants: Fix nm advice one last time
     a28611b Export constructors for IntPtr and WordPtr
     ea34f56 Remove unused equivClassesByUniq
     cd85dc8 Make sure record pattern synonym selectors are in scope in GHCi.
     db2bfe0 added docstring for '-fhistory-size' flag
     81d8a23 glasgow_exts.rst: fix quoting
     c5be5e2 docs/users_guide/glasgow_exts.rst: fix merge conflict
     fa86ac7 Make validDerivPred ignore non-visible arguments to a class type constructor
     36d29f7 StaticPointers: Allow closed vars in the static form.
     5f8c0b8 Revert "Revert "Use __builtin_clz() to implement log_1()""
     ef44606 Cleanups related to MAX_FREE_LIST
     0051ac1 Update libraries/hpc submodule to v0.6.0.3 release tag
     4466ae6 Update bytestring submodule to 0.10.8.0 release tag
     50e7055 Export oneShot from GHC.Exts
     f9d9375 Adjust testsuite output to bytestring-0.10.8.0
     76ee260 Allow limiting the number of GC threads (+RTS -qn<n>)
     f703fd6 Add +RTS -AL<size>
     1fa92ca schedulePushWork: avoid unnecessary wakeups
     dbcaa8c Don't STATIC_INLINE giveCapabilityToTask
     aa5e2dd Make 'make fast' work for the User Guide
     b75d194 Be more aggressive when checking constraints for custom type errors.
     4f2afe1 testsuite: Add test for #11959
     763610e base: Export runRW# from GHC.Exts
     ad4392c Kill non-deterministic foldUFM in TrieMap and TcAppMap
     db9de7e rts: Replace `nat` with `uint32_t`
     e340520 Comments only explaining export list parsing.
     94f2ee1 Explain linter optimization for StaticPtr checks.
     990ce8c Use tcExtendGlobalValEnv for default methods
     ecc1d58 Update Win32 submodule to v2.3.1.1 release tag
     018487e Fix pretty printing of IEThingWith
     fe190ae Remove trailing whitespace from 'testsuite/tests/module/all.T'
     633b099 Update time submodule to 1.6.0.1 release tag
     8e5776b rts/ProfHeap.c: Use `ssize_t` instead of `long`.
     dd3e847 Documentation for simplifyDeriv.
     260a564 Use stdint types for Stg{Word,Int}{8,16,32,64}
     2593e20 White space only
     76d9156 Emit wild-card constraints in the right place
     cc75a5d Comments only
     e1ff2b4 Fix partial sigs and pattern bindings interaction
     9dbf5f5 Tidy up partial-sig quantification
     bb296bf Error message wibbles, re partial type sigs
     0597493 Re-do the invariant for TcDepVars
     3ca7806 stg/Types.h: Fix comment and #include
     53f26f5 Forbid variables to be parents in import lists.
     e996e85 RdrHsSyn: Only suggest `type` qualification when appropriate
     ea3d1ef Fix a crash in requestSync()
     bff6e1b Comments only
     4ac0e81 Kill unnecessary cmpType in lhs_cmp_type
     b58b0e1 Make simplifyInstanceContexts deterministic
     a4717f5 Comments about static forms
     b21e8cc Comments only
     e7e5939 Add Outputable ShowHowMuch
     e24b50c Use partial-sig constraints as givens
     1a43783 Record that EqualityConstraint now works
     f6e58be Test Trac #11640
     7e28e47 Get rid of Traversable UniqFM and Foldable UniqFM
     402f201 Fix typos
     ab91b85 make accept for Make simplifyInstanceContexts deterministic
     e207198 Kill foldUFM in classifyTyCon
     8669c48 Document why closeOverKind is OK for determinism
     584ade6 RtsFlags: Make `mallocFailHook` const correct
     0efbf18 rts: Fix C compiler warnings on Windows
     9363f04 Handle promotion failures when scavenging a WEAK (#11108)
     0e71988 Remove some varSetElems in dsCmdStmt
     3edbd09 Document SCC determinism
     cfc5df4 Fix ASSERT failure and re-enable setnumcapabilities001
     2a0d00d Make random an "extra" package
     86a1f20 Remove a copy of System.Random and use reqlib('random')
     b5f85ce Remove stale comment.
     da105ca Don't prematurely force TyThing thunks with -ddump-if-trace.
     925b0ae Make absentError not depend on uniques
     eae3362 docs: add skeleton 8.2.1 release notes
     e217287 Bump haddock submodule
     c079de3 Add TH support for pattern synonyms (fixes #8761)
     e53f218 Fix deriveTyData's kind unification when two kind variables are unified
     b8e2565 Make Generic1 poly-kinded
     6971430 Allow putting Haddocks on derived instances
     01bc109 Document zonkTyCoVarsAndFV determinism
     6bf0eef Kill varEnvElts in specImports
     69c974f Use StgHalfWord instead of a CPP #if
     995cf0f rts: Make function pointer parameters `const` where possible
     0c0129b RtsUtils: Use `size_t` instead of `int` where appropriate
     7c0b595 Fix comments about scavenging WEAK objects
     5416fad Refactor some ppr functions to use pprUFM
     bd01bbb Test Trac #12039
     8e48d24 Bump haddock submodule
     e4834ed Fix a performance issue with -fprint-expanded-synonyms
     c974927 Update bytestring submodule to 0.10.8.1 release tag
     bf669a0 Bump haddock submodule
     2dbdc79 PPC NCG: Fix pretty printing of st[wd]ux instr.
     563a485 PPC: Implement SMP primitives using gcc built-ins
     d78faa1 testsuite/ImpSafe03: Normalize version of bytestring
     eed820b Move Extension type to ghc-boot-th
     21fe4ff Kill varSetElems in tcInferPatSynDecl
     d20d843 Another bump of haddock submodule
     7814420 Remove html_theme requirement of haddock docs
     4a037a9 Set `USE_MMAP` at configure time
     770d708 Add ghc-boot-th to rules/foreachLibrary
     dc94914 Document determinism in shortOutIndirections
     3f3dc23 Testsuite: run tests in /tmp after copying required files
     1a9ae4b Testsuite: delete old cleanup code (#11980)
     a9dd9b7 Testsuite: delete unused file [skip ci]
     c92cfbc Testsuite: don't skip concio001 and concio001_thr
     931b3c7 Delete libraries/ghci/GNUmakefile [skip ci]
     a54d87a rules: Fix name of ghc-boot-th library
     5d80d14 rules/build-prog: Ensure programs depend upon their transitive deps
     33c029d rts: More const correct-ness fixes
     b088c02 Testsuite: T10052 requires interpreter (#11730)
     3251743 Testsuite: don't warn when mk/ghcconfig_* hasn't been created yet
     77ee3a9 Update .mailmap [skip ci]
     fffe3a2 Make inert_model and inert_eqs deterministic sets
     f0f0ac8 Fix histograms for ticky code
     ba3e1fd Add a test for #11108
     39a2faa Rework parser to allow use with DynFlags
     310371f rts: Add isPinnedByteArray# primop
     f091218 CLabel: Catch #11155 during C-- pretty-printing
     9dd0481 Add (broken) test for #12063.
     5f1557e Failing test case for #12076.
     f18e8d8 rts: Add missing `const` from HashTable API
     6282bc3 Kill varSetElems in tidyFreeTyCoVars
     13e40f9 Kill varEnvElts in tcPragExpr
     72b677d Fix Trac #12051
     ad7f122 Improve pretty-printing of equalities
     f9e90bc Improve documentation for type wildcards
     0bfcfd0 Comments only
     d1efe86 Comments only
     358567a testsuite: Add expected output for T11108
     470def9 Testsuite: fix T11827 (#11827)
     296b8f1 Add libraries/ghci/GNUmakefile to .gitignore [skip ci]
     f0f3517 Remove use of caddr_t
     8abc193 Get types in osFreeMBlocks in sync with osGetMBlocks
     464b6f8 {,M}BLOCK_SIZE_W * sizeof(W_) -> {,M}BLOCK_SIZE
     2e6433a testsuite: Add a TypeRep test
     a88bb1b Give lifted primitive types a representation
     1ee47c1 Use the correct return type for Windows' send()/recv() (Fix #12010)
     3910306 Add -XStaticPointers to the flag reference.
     08e47ca FunDep printer: Fix unicode arrow
     43589f5 testsuite: add CmmSwitchTest for 32-bit platforms
     ae7e9cb Fix Windows build after Ticky changes
     8e92974 Testsuite: mark T8761 expect_broken #12077
     a1f3bb8 Fix failing T12010
     d9cb7a8 compiler/iface: compress .hi files
     e44a6f9 users-guide: Vector version of Thomson-Wheeler logo
     6d6d6e4 rules/sphinx: Add missing dependency on conf.py for pdf rule
     cf1efc7 users-guide: Fix index in PDF output
     da3c1eb Enable checkProddableBlock on x86_64
     527ed72 Fix deriving Ord when RebindableSyntax is enabled
     c81e7b2 Build system: temp solution for parallelisation bug (#11960)
     f669764 Use `setSession` instead of `modifySession` when setting `HscEnv`
     a70a6da rts/Linker.c: Fix compile error on Arm
     fa58710 Update format specifiers for Tickey.c
     2230c88 Testsuite: fix T12010 for real
     8c9b8a3 Allow unlifted types in pattern synonym result type
     d835ee6 Fix build by removing unused import.
     785b38f testsuite: Update max_bytes_used for T4029
     9bb2772 Revert "compiler/iface: compress .hi files"
     4f5b335 Suppress the warning about __sync_fetch_and_nand (#9678)
     03d8960 Don't split the arg types in a PatSyn signature
     eb8eb02 Spelling in comment
     839b424 Remove unused Type.splitFunTysN
     9c3e55b Comments only
     35053eb Testsuite: delete check_files_written
     1bf5c12 Spelling
     8f7d016 Add support for unicode TH quotes (#11743)
     4c6e69d Document some benign nondeterminism
     9d06ef1 Make Arrow desugaring deterministic
     95dfdce Remove 'deriving Typeable' statements
     fe8a4e5 Runtime linker: Break m32 allocator out into its own file
     1956cbf Fix: #12084 deprecate old profiling flags
     31f1804 Testsuite: delete drvfail015.stderr-7.0 [skip ci]
     1319363 Always use native-Haskell de/encoders for ASCII and latin1
     ac38c02 Update submodule vector [skip ci]
     961ed26 Fix broken links to mdo papers
     eec88ee RTS: simplify read_heap_profiling_flag
     bdc5558 Testsuite: introduce TEST_HC_OPTS_INTERACTIVE (#11468)
     8408d84 Spelling in comments
     6a5bce1 Testsuite: also normalise platform-dependent .stdout/stderr
     f07bf19 Testsuite: fix enum01/02/03 on Windows (#9399)
     5020bc8 Testsuite: add a test for #5522 (-fliberate-case -fspec-constr)
     0f1e315 Fix bytecode gen to deal with rep-polymorphism
     e9e61f1 Reduce special-casing for nullary unboxed tuple
     5b8bec2 StgCmmExpr: Fix a duplication
     5b145c9 Coverage.hs: Fix a duplication
     cd50d23 StgCmmCon: Do not generate moves from unused fields to local variables
     b43a793 More fixes for unboxed tuples
     72fd407 Comments and white space only
     59250dc StgCmmExpr: Remove a redundant list
     3a00ff9 Do not init record accessors as exported
     3f20da1 Typos in comments
     d0dd572 Clarify users' guide section on GeneralizedNewtypeDeriving
     d40682e Testsuite: don't use --interactive in Makefiles
     1e67010 RtsFlags.c: Const correct fixes
     7e4f3dc StgCmmUtils.emitMultiAssign: Make assertion msg more helpful
     0ffa23d Remove unused FAST_STRING_NOT_NEEDED macro defs
     930e74f Update a Cmm note
     0676e68 Fix detection and use of `USE_LIBDW`
     cb2c042 Use nameSetAny in findUses
     f2b3be0 Improve failed knot-tying error message.
     99ace83 Kill nameSetElems in getInfo
     36d254a Testsuite: run tests in /tmp/ghctest-xxx instead of /tmp/ghctest/xxx
     940229c Travis: llvm's apt repository is offline
     cb9f635 Localize orphan-related nondeterminism
     d348acd Serialize vParallelTyCons in a stable order
     3eac3a0 Add nameSetElemsStable and fix the build
     dad39ff Remove dead generics-related code from OccName
     d753ea2 Use UniqDSet for finding free names in the Linker
     e2446c0 Kill nameSetElems in findImportUsage
     be47085 Kill nameSetElems in rnCmdTop
     060c176 Whitespace only
     1d1987e HscMain: Minor simplification
     9cc6fac Make FieldLabelEnv a deterministic set
     2046297 Document putSymbolTable determinism
     4842a80 Derive instances in Data.Data
     1dadd9a testsuite: Mark broken tests on powerpc64le
     3747372 Refactored SymbolInfo to lower memory usage in RTS
     079c1b8 Use useful names for Symbol Addr and Names in Linker.c
     02f893e integer-gmp: Make minusInteger more efficient
     4aa299d PrelInfo: Ensure that tuple promoted datacon names are in knownKeyNames
     eda73a3 RTS SMP: Use compiler built-ins on all platforms.
     4dbacbc Rename isPinnedByteArray# to isByteArrayPinned#
     b948a1d Refactor the SymbolName and SymbolAddr types to be pointers
     5965117 Replace hand-written Bounded instances with derived ones
     0d963ca Add relocation type R_X86_64_REX_GOTPCRELX
     4848ab9 Testsuite: fixup comments for T9872d [skip ci]
     886f4c1 Better comment for orIfNotFound.
     f91d87d Failing test-case for #12135.
     3042a9d Use UniqDFM for HomePackageTable
     48e9a1f Implement deterministic CallInfoSet
     a90085b Add @since annotations to base instances
     e684f54 Desugar ApplicativeDo and RecDo deterministically
     31ba8d6 Kill nameSetElems
     46d2da0 Document putDictionary determinism
     3e7a876 Kill foldUniqSet
     1937ef1 Make UnitIdMap a deterministic map
     a13cb27 Merge MatchFixity and HsMatchContext
     77ccdf3 Kill occSetElts
     7fea712 Use a deterministic map for imp_dep_mods
     d05dee3 CoreToStg: Remove hand-written Eq instances of HowBound and LetInfo
     4426c5f Kill two instances of uniqSetToList
     0d6f428 Fix build by removing unused import
     c148212 Kill varSetElems in checkValidInferredKinds
     ad8e203 Use DVarSet in Vectorise.Exp
     3b698e8 Document determinism in pprintClosureCommand
     5db93d2 Make vectInfoParallelVars a DVarSet
     7008515 Kill varSetElems
     7d58a97 Use pprUFM in pprStgLVs
     00e3a5d Typofix.
     4d5b2f6 Testsuite driver: always quote opts.testdir
     f5f5a8a Testsuite Windows: mark T8308 expect_broken (#8308)
     d4b548e Add some determinism tests
     dd33245 Desugar: Display resulting program stats with -v2
     44a3c18 Revert "Desugar: Display resulting program stats with -v2"
     c2bbc8b Report term sizes with -v3 even when -ddump is enabled
     80cf4cf Literal: Remove unused hashLiteral function
     d7933cb Show sources of cost centers in .prof
     8f6d292 Fix #12064 by making IfaceClass typechecking more lazy.
     acb9e85 Minor performance note about IdInfo.
     11ff1df Fix #12076 by inlining trivial expressions in CorePrep.
     48385cb Remove special casing of Windows in generic files
     ceaf7f1 Implement Eq TyCon directly
     68c1c29 Remove Ord (CoAxiom br)
     9dbf354 Testsuite: delete dead code [skip ci]
     e703a23 Docs: fix links to ghc-flags
     70e0a56 Remove Ord Class
     b2624ee Remove Ord PatSyn
     77b8c29 Remove Ord AltCon
     c22ab1a Docs: delete PatternGuards documentation
     b020db2 Fix Ticky histogram on Windows
     e9dfb6e Improve the error messages for static forms.
     b0a7664 prettyPrintClosure(): Untag the closure before accessing fields
     47d8173 Remove Printer.c:prettyPrintClosure()
     bcb419a Fix #12099: Remove bogus flags
     6adff01 Comments only
     6905ce2 Refine imports slightly
     0f0b002 Comments only
     3ae18df Minor refactoring
     b9fa72a Small refactor to mkRuntimErrorId
     9e5ea67 NUMA support
     c88f31a Rts flags cleanup
     5990016 ModuleSet: Use an actual set instead of map to units
     6ace660 rts: Fix build when USE_LARGE_ADDRESS_SPACE is undefined
     9130867 Skip retc001 on OSX
     b40e1b4 Fix incorrect calculated relocations on Windows x86_64
     29e1464 Disable T12031 on linux
     2bb6ba6 rts: Fix NUMA when cross compiling
     d25cb61 Kill off redundant SigTv check in occurCheckExpand
     15b9bf4 Improve typechecking of let-bindings
     c28dde3 Tidy up zonkQuantifiedTyVar
     7afb7ad Get in-scope set right in top_instantiate
     35c9de7 Move the constraint-kind validity check
     1f66128 Beef up mkNakedCastTy
     15fc528 Fix the in-scope set for extendTvSubstWithClone
     599d912 Beef up isPredTy
     8104f7c Remove some traceTc calls
     e064f50 Add to .gitignore
     921ebc9 Test Trac #12055
     1dcb32d A second test for Trac #12055
     5cee88d Add thin library support to Windows too
     7de776c Kill unused foldModuleEnv
     586d558 Use UniqFM for SigOf
     0497ee5 Make the Ord Module independent of Unique order
     d55a9b4 Update Haddock to follow change in LHsSigWcType
     4f35646 Adjust error message slightly
     8dfd4ae Build system: mention ghc version in bindist's `configure --help` docdir
     a2deee0 Testsuite: enable ghci.prog010 (#2542)
     23b73c9 Don't GC sparks for CAFs
     9d22fbe Rename cmpType to nonDetCmpType
     753c5b2 Simplify readProcessEnvWithExitCode + set LANGUAGE=C
     70a4589 Revert "Make the Ord Module independent of Unique order"
     e33ca0e Fix testsuite wibble
     77bb092 Re-add FunTy (big patch)
     e368f32 Major patch to introduce TyConBinder
     c56f8bd CoreMonad: Update error msg function docs
     930a525 Abort the build when a Core plugin pass is specified in stage1 compiler
     a7f65b8 Remove dead code: countOnce, countMany
     498ed26 NUMA cleanups
     8d33af9 CoreLint: Slightly improve case type annotation error msgs
     3e8c495 CmmNode: Make CmmTickScope's Unique strict
     2396d9b llvmGen: Make metadata ids a newtype
     85e09b1 llvmGen: Consolidate MetaExpr pretty-printing
     9bb0578 Revert accidental submodule updates
     e02beb1 Driver: `ghc ../Test` (without file extension) should work
     f72f23f Testsuite: run tests in <testdir>.run instead of /tmp
     6f6f515 Testsuite: write "\n" instead of "\r\n" when using mingw Python
     d94c405 Testsuite: validate the tests/stage1 directory with the stage1 compiler
     a4c8532 Validate: use `rm -f` instead of `rm`
     6354991 VarEnv: Comment only
     270d545 Add Bifoldable and Bitraversable to base
     9649fc0 Refactor derived Generic instances to reduce allocations
     4d71cc8 Avoid find_tycon panic if datacon is not in scope
     f12fb8a Fix trac #10647: Notice about lack of SIMD support
     2897be7 PPC NCG: Fix float parameter passing on 64-bit.
     f4b0488 PPC NCG: Fix and refactor TOC handling.
     0be38a2 llvmGen: Add strictness to metadata fields
     0e92af9 Remove use of KProxy in GHC.Generics
     0ba34b6 ApplicativeDo: allow "return $ e"
     e7e42c8 Fix double-free in T5644 (#12208)
     cdc14b4 Testsuite: remove Windows CR again.. [skip ci]
     9cdde38 Testsuite: remove Windows CR [skip ci]
     cf6e656 Testsuite: remove Windows CR [skip ci]
     3dc1202 Testsuite: tabs -> spaces [skip ci]
     7e7094f Testsuite: tabs -> spaces [skip ci]
     46ff80f Testsuite: tabs -> spaces [skip ci]
     915e07c Testsuite: tabs -> spaces [skip ci]
     5b03dc6 Testsuite: tabs -> spaces [skip ci]
     a7160fa Testsuite: tabs -> spaces [skip ci]
     4a4bdda Testsuite: recover from utf8 decoding errors
     6d0a4fc Testsuite: fix WAY=ghci when LOCAL=0
     1ddc10b Testsuite: *do* replace backslashes in config.libdir
     1d938aa Testsuite: mark tests expect broken
     3b49f8f Testsuite: remove `-fforce-recomp` from default flags (#11980)
     82f7f18 Testsuite: delete TEST_HC_OPTS_NO_RECOMP
     135fc86 Testsuite: remove `-Wno-warn-tabs` from default flags
     ebaf26b Testsuite: delete dead code + cleanup
     e170d19 Testsuite: assume timeout_prog always exists
     ee3bde7 Expand and clarify the docs for ApplicativeDo (#11835)
     7301404 Typos in comments
     d09e982 Don't quantify over Refl in a RULE
     97a50f8 Delete commented-out code
     1230629 Make checkFamInstConsistency less expensive
     a47b62c Second attempt to fix sizeExpr
     c0583a9 Fix build breakage due to rebase
     9d62d09 Hopefully fix all the rebase-induced breakage
     4e7d835 Typos in comments [skip ci]
     6199588 More typos in comments [skip ci]
     93f40cb Don't error on GCC inlining warning in rts
     348f2db Make the Ord Module independent of Unique order (2nd try)
     15641b0 Accept new (lower) allocations for T7257
     7e7aeab Comments only
     cc92a44 Improve error message in deriving( Functor )
     a1b3359 Remove unused arg to tcSuperClasses
     ce97b72 Expand given superclasses more eagerly
     210a2e1 Test Trac #12163
     3e0af46 Give lookupGRE_Name a better API
     e556f76 Remove unused import
     643706e Narrow the warning for simplifiable constraints
     2f8cd14 Narrow the use of record wildcards slightly
     7fc20b0 Have Core linter accept programs using StaticPointers and -fhpc.
     35d1564 Provide Uniquable version of SCC
     bb74021 Remove Ord TyCon
     7f5d560 Very confusing typo in error message.
     9a34bf1 Fix #11974 by adding a more smarts to TcDefaults.
     8035d1a Fix #10963 and #11975 by adding new cmds to GHCi.
     4ae950f Release notes for #11975 and #10963
     df9611e Testsuite: do not copy .hi/.o files to testdir (#12112)
     d2958bd Improve typechecking of instance defaults
     c871ce4 Comments around invisibility
     393928d Fix renamer panic
     f86a337 Remove bogus comment on ForAllTy
     bb84ee4 Improve pretty-printing of Avail
     12c4449 Implement ReifyConStrictness for -fexternal-interpreter (#12219)
     d2006d0 Run all TH tests with -fexternal-interpreter (#12219)
     bdb0d24 Remote GHCi: separate out message types
     eb73219 Remote GHCi: comments only
     0bab375 Fix T8761  (#12219, #12077)
     dadd8b8 Test Trac #12229
     9bc2233 Fix typo in Data.Bitraverse Haddocks
     31b5806 Clean up outdated comments in template-haskell changelog
     a33b498 Add template-haskell changelog note for #8761
     5fdb854 s/Invisible/Inferred/g s/Visible/Required/g
     4cc5a39 Refactor tcInferArgs and add comments.
     8c1cedd Allow building static libs.
     da60e3e rts/Linker.c: Improve ugly C pre-processor hack
     7843c71 Make T8761 deterministic, I hope
     ff1cc26 Don't run the run_command tests with ext-interp
     82282e8 Remove some `undefined`s
     60c24b2 Typos in user manual and code: recurisve -> recursive
     afa6e83 rts/Linker.c: Rename ONLY_USED_x86_64_HOST_ARCH macro
     bbf0aa2 Testsuite: never pick up .T files in .run directories
     7593c2f Testsuite: report duplicate testnames when `make TEST=<name>`
     1f45bce Testsuite: remove one level of indentation [skip ci]
     206b4a1 Testsuite: simplify extra_file handling
     bafd615 Testsuite: do not print timeout message
     58f0086 Testsuite: open/close stdin/stdout/stderr explicitly
     d8e9b87 Testsuite: cleanup printing of summary
     782cacf Testsuite: framework failure improvements (#11165)
     6b3b631 Testsuite: run all indexed-types ways on ./validate --slow
     0eb0378 Testsuite: do not add -debug explicitly in .T file
     3fb9837 Testsuite: mark tests expect_broken
     af21e38 Don't omit any evidence bindings
     23b80ac Deal correctly with unused imports for 'coerce'
     dc62a22 Wibble error message for #11471
     dd92c67 Stop the simplifier from removing StaticPtr binds.
     2e9079f Test Trac #12185
     848e3ce Testsuite: fixes for python2.6 support
     9a645a1 Refactor match to not use Unique order
     8f7194f Double the file descriptor limit for openFile008
     1084d37 Testsuite: use ignore_stderr/stdout instead of ignore_output
     24194a6 Fix pretty-printer for IfaceCo
     e8d6271 Testsuite: do not depend on sys.stdout.encoding
     fb6e2c7 Delete Ord Unique
     9854f14 Add a new determinism test
     b6b20a5 Reorganize some determinism tests
     480e066 Remove ufmToList
     b8b3e30 Axe RecFlag on TyCons.
     0701db1 Updates to handle new Cabal
     430f5c8 Trac #11554 fix loopy GADTs
     6a5d13c nativeGen: Allow -fregs-graph to be used
     f68d40c ghc-pkg: Drop trailing slashes in computing db paths
     f1e16e9 CmmExpr: remove unused `vgcFlag` function
     b65363d Fix check_uniques in non-unicode locale
     0afc41b Testsuite: be less strict about topHandler03's stderr
     c27ce26 users-guide: Fix markup in release notes
     81b437b Add NamedThing (GenLocated l e) instance
     b412d82 Allow one type signature for multiple pattern synonyms
     6ba4197 rules/sphinx.mk: stop xelatex on error
     ee8d1fa Remove unused oc->isImportLib (#12230)
     6377757 Linker: some extra debugging / logging
     cbfeff4 Remove uniqSetToList
     0d522b8 Document some benign nondeterminism
     0ab63cf Kill varEnvElts in seqDmdEnv
     01f449f Fix 32-bit build failures
     9031382 MkCore: Fix some note names
     a6819a0 base: Add release date to changelog
     bf7cbe7 users-guide: Note multiple pattern signature change in relnotes
     afec447 testsuite: Add testcase for #12355
     2a3af15 Treat duplicate pattern synonym signatures as an error
     3b2deca users-guide: Remove static field type from rts-flag
     331febf CallArity: Use not . null instead of length > 0
     0bd7c4b Enum: Ensure that operations on Word fuse
     18e71e4 Revert "Fix 32-bit build failures"
     890ec98 Revert "Linker: some extra debugging / logging"
     e10497b Kill some varEnvElts
     85aa6ef Check generic-default method for ambiguity
     1267048 Extra ASSERTs for nameModule
     55e43a6 Use DVarEnv for vectInfoVar
     5f79394 Delete out-of-date comment
     895eefa Make unique auxiliary function names in deriving
     cbe30fd Tidy up tidying
     f2d36ea White space only
     6cedef0 Test Trac #12133
     27fc75b Document codegen nondeterminism
     18b782e Kill varEnvElts in zonkEnvIds
     1b058d4 Remove varEnvElts
     b7b130c Fix GetTime.c on Darwin with clock_gettime
     f560a03 Adds x86_64-apple-darwin14 target.
     567dbd9 Have addModFinalizer expose the local type environment.
     56f47d4 Mention addModFinalizer changes in release notes.
     672314c Switch to LLVM version 3.8
     b9cea81 Show testcase where demand analysis abortion code fails
     979baec --without-libcharset disables the use of libcharset
     bedd620 Style changes for UniqFM
     6ed7c47 Document some codegen nondeterminism
     9858552 Use deterministic maps for FamInstEnv
     34085b5 Correct the message displayed for syntax error (#12146)
     64bce8c Add Note [FamInstEnv determinism]
     6e280c2 Utils: Fix `lengthIs` and `lengthExceeds` for negative args
     0481324 Use UniqDFM for InstEnv
     b8cd94d GHC.Stack.CCS: Fix typo in Haddocks
     91fd87e FastString: Reduce allocations of concatFS
     15751f2 FastString: Add IsString instance
     c4a9dca FastString: Supply mconcat implementation
     fc53d36 OccName: Implement startsWithUnderscore in terms of headFS
     eb3d659 OccName: Avoid re-encoding derived OccNames
     4f21a51 Kill eltsUFM in classifyTyCons
     6c7c193 DsExpr: Remove usage of concatFS in fingerprintName
     0177c85 Testsuite: expose TEST_CC (path to gcc)
     f53d761 TysWiredIn: Use UniqFM lookup for built-in OccNames
     9a3df1f check-api-annotations utility loads by filename
     17d0b84 Add -package-env to the flags reference
     372dbc4 Pretty: delete really old changelog
     45d8f4e Demand analyser: Implement LetUp rule (#12370)
     18ac80f tidyType: Rename variables of nested forall at once
     cd0750e tidyOccNames: Rename variables fairly
     37aeff6 Added type family dependency to Data.Type.Bool.Not
     b35e01c Bring comments in TcGenGenerics up to date
     a9bc547 Log heap profiler samples to event log
     ffe4660 IfaceEnv: Only check for built-in OccNames if mod is GHC.Types
     24f5f36 Binary: Use ByteString's copy in getBS
     0f0cdb6 Bugfix for bug 11632: `readLitChar` should consume null characters
     1ba79fa CodeGen: Way to dump cmm only once (#11717)
     89a8be7 Pretty: remove a harmful $! (#12227)
     5df92f6 hp2ps: fix invalid PostScript for names with parentheses
     d213ab3 Fix misspellings of the word "instance" in comments
     3fa3fe8 Make DeriveFunctor work with unboxed tuples
     514c4a4 Fix Template Haskell reification of unboxed tuple types
     1fc41d3 Make okConIdOcc recognize unboxed tuples
     0df3f4c Fix PDF build for the User's Guide.
     98b2c50 Support SCC pragmas in declaration context
     e46b768 Make Data.{Bifoldable,Bitraversable} -XSafe
     908f8e2 TcInteract: Add braces to matchClassInst trace output
     8de6e13 Fix bytecode generator panic
     cac3fb0 Cleanup PosixSource.h
     a0f83a6 Data.Either: Add fromLeft and fromRight (#12402)
     627c767 Update docs for partial type signatures (#12365)
     ed48098 InstEnv: Ensure that instance visibility check is lazy
     9513fe6 Clean up interaction between name cache and built-in syntax
     a4f2b76 testsuite: Add regression test for #12381
     93acc02 Add another testcase for #12082
     cf989ff Compact Regions
     83e4f49 Revert "Clean up interaction between name cache and built-in syntax"
     714bebf Implement unboxed sum primitive type
     a09c0e3 Comments only
     9c54185 Comments + tiny refactor of isNullarySrcDataCon
     8d4760f Comments re ApThunks + small refactor in mkRhsClosure
     6a4dc89 Bump Haddock submodule
     8265c78 Fix and document Unique generation for sum TyCon and DataCons
     e710f8f Correct a few mistyped words in prose/comments
     bbf36f8 More typos in comments
     fb34b27 Revert "Cleanup PosixSource.h"
     86b1522 Unboxed sums: More unit tests
     bfef2eb StgCmmBind: Some minor simplifications
     c4f3d91 Add deepseq dependency and a few NFData instances
     648fd73 Squash space leaks in the result of byteCodeGen
     7f0f1d7 -fprof-auto-top
     1fe5c89 UNPACK the size field of SizedSeq
     d068220 Fix the non-Linux build
     4036c1f Testsuite: fix T10482a
     1967d74 Some typos in comments
     a9251c6 MonadUtils: Typos in comments
     1783011 Fix productivity calculation (#12424)
     9d62f0d Accept better stats for T9675
     8f63ba3 Compute boot-defined TyCon names from ModIface.
     b0a5144 Add mblocks_allocated to GC stats API
     e98edbd Move stat_startGCSync
     d3feb16 Make Unique a newtype
     c06e3f4 Add atomic operations to package.conf.in
     89ae1e8 Relevant Bindings no longer reports shadowed bindings (fixes #12176)
     750553a Use MO_Cmpxchg in Primops.cmm instead of ccall cas(..)
     2078909 Typo in comment
     36565a9 ForeignCall.hs: Remove DrIFT directives
     55f5aed Track the lengths of the thread queues
     988ad8b Fix to thread migration
     d1fe08e Only trace cap/capset events if we're tracing anything else
     4dcbbd1 Remove the DEBUG_<blah> variables, use RtsFlags directly
     9df9490 StgSyn: Remove unused StgLiveVars types
     2f79e79 Add comment about lexing of INLINE and INLINABLE pragma
     0c37aef Update old comment InlinePragma
     b1e6415 More comments about InlinePragmas
     7a06b22 Typo in comment [skip ci]
     7a8ef01 Remove `setUnfoldingInfoLazily`
     a13fda7 Clarify comment on makeCorePair
     d85b26d CmmLive: Remove some redundant exports
     8ecac25 CmmLayoutStack: Minor simplification
     fc66415 Replace an unsafeCoerce with coerce
     db5a226 Fix omission in haddock instance head
     1101045 Trim all spaces after 'version:'
     fe4008f Remove identity update of field componentsConfigs
     f09d654 check that the number of parallel build is greater than 0
     e3e2e49 codeGen: Remove binutils<2.17 hack, fixes T11758
     ca7e1ad Expanded abbreviations in Haddock documentation
     ce13a9a Fix an assertion that could randomly fail
     89fa4e9 Another try to get thread migration right
     8fe1672 Bump `hoopl` submodule, mostly cosmetics
     253fc38 Temporarily mark T1969 perf test as broken (#12437)
     7354f93 StgCmm: Remove unused Bool field of Return sequel
     02614fd Replace some `length . filter` with `count`
     9aa5d87 Util.count: Implement as a left-fold instead of a right-fold
     affcec7 rts/Printer.h: fix constness of argument declaration
     03af399 AsmCodeGen: Give linear-scan and coloring reg. allocators different cc names
     3bfe6a5 RegAlloc: Remove duplicate seqList (use seqList from Util)
     bd51064 RegAlloc: Use IntSet/IntMaps instead of generic Set/Maps
     7a2e933 Use Data.Functor.Const to implement Data.Data internals
     6fe2355 configure.ac: Remove checks for bug 9439
     773e3aa T1969: Enable it again but bump the max residency temporarily
     4d9c22d Fix typo in Data.Bitraversable Haddocks
     fe19be2 Cabal submodule update.
     dd23a4c Actually update haddock.Cabal stats.
     e79bb2c Fix a bug in unboxed sum layout generation
     9684dbb Remove StgRubbishArg and CmmArg
     ac0e112 Improve missing-sig warning
     bd0c310 Fix GHCi perf-llvm build on x86_64
     37a7bcb Update `nofib` submodule to newest commit
     7ad3b49 Misspellings in comments [skip ci]
     18f0687 Fix configure detection.
     ffd4029 fix compilation failure on OpenBSD with system supplied GNU C 4.2.1
     fc1432a Update hoopl submodule (extra .gitignore entry)
     3551e62 refactor test for __builtin_unreachable into Rts.h macro RTS_UNREACHABLE
     da99a7f Darwin: Detect broken NM program at configure time
     f9a11a2 When in sanity mode, un-zero malloc'd memory; fix uninitialized memory bugs.
     d331ace Minor typofix.
     b222ef7 Typofix in System.Environment docs.
     34da8e5 Typo in comment
     efc0372 Not-in-scope variables are always errors
     f352e5c Keep the bindings local during defaultCallStacks
     58e7316 Refactor nestImplicTcS
     d610274 Revert "T1969: Enable it again but bump the max residency temporarily"
     113d50b Add gcoerceWith to Data.Type.Coercion
     b2c5e4c Revert "codeGen: Remove binutils<2.17 hack, fixes T11758"
     896d216 Annotate initIfaceCheck with usage information.
     e907e1f Axe initIfaceTc, tie the knot through HPT (or if_rec_types).
     704913c Support for noinline magic function.
     1f1bd92 Introduce BootUnfolding, set when unfolding is absent due to hs-boot file.
     5a8fa2e When a value Id comes from hi-boot, insert noinline. Fixes #10083.
     8fd1848 Retypecheck both before and after finishing hs-boot loops in --make.
     e528061 We also need to retypecheck before when we do parallel make.
     0d3bf62 Fix #12472 by looking for noinline/lazy inside oversaturated applications.
     f9aa996 pass -z wxneeded or -Wl,-zwxneeded for linking on OpenBSD
     fb0d87f Splice singleton unboxed tuples correctly with Template Haskell
     1f75440 Extra comments, as per SPJ in #12035.
     acdbd16 Move #12403, #12513 users guide notes to 8.2.1 release notes
     89facad Add T12520 as a test
     1766bb3 RtClosureInspect: Fix off-by-one error in cvReconstructType
     613d745 Template Haskell support for unboxed sums
     7a86f58 Comments only: Refer to actually existing Notes
     8d92b88 DmdAnal: Add a final, safe iteration
     d6fd2e3 DmdAnal: Testcase about splitFVs and dmdFix abortion
     ec7fcfd Degrade "case scrutinee not known to diverge for sure" Lint error to warning
     faaf313 WwLib: Add strictness signature to "let x = absentError …"
     1083f45 Fix doc build inconsistency
     ae66f35 Allow typed holes to be levity-polymorphic
     a60ea70 Move import to avoid warning
     0050aff Fix scoping of type variables in instances
     ca8c0e2 Typofix in docs.
     983f660 Template Haskell support for TypeApplications
     822af41 Fix broken Haddock comment
     f4384ef Remove unused DerivInst constructor for DerivStuff
     21c2ebf Missing stderr for T12531.
     9d17560 GhcMake: limit Capability count to CPU count in parallel mode
     a5d26f2 rts: enable parallel GC scan of large (32M+) allocation area
     044e81b OccName: Remove unused DrIFT directive
     ff1931e TcGenDeriv: Typofix
     d168c41 Fix and complete runghc documentation
     6781f37 Clarify pkg selection when multiple versions are available
     83b326c Fix binary-trees regression from unnecessary floating in CorePrep.
     a25bf26 Tag pointers in interpreted constructors
     ef784c5 Fix handling of package-db entries in .ghc.environment files, etc.
     2ee1db6 Fixes #12504: Double-escape paths used to build call to hsc_line
     28b71c5 users_guide: More capabilities than processors considered harmful
     0e74925 GHC: Expose installSignalHandlers, withCleanupSession
     3005fa5 iserv: Show usage message on argument parse failure
     d790cb9 Bump the default allocation area size to 1MB
     d40d6df StgCmmPrim: Add missing MO_WriteBarrier
     d1f2239 Clarify scope of `getQ`/`putQ` state.
     22259c1 testsuite: Failing testcase for #12091
     2d22026 ErrUtils: Expose accessors of ErrDoc and ErrMsg
     a07a3ff A failing testcase for T12485
     9306db0 TysWiredIn: Use dataConWorkerUnique instead of incrUnique
     9cfef16 Add Read1/Read2 methods defined in terms of ReadPrec
     1ad770f Add -flocal-ghci-history flag (#9089).
     010b07a PPC NCG: Implement minimal stack frame header.
     ca6d0eb testsuite: Update bytes allocated of parsing001
     75321ff Add -fdefer-out-of-scope-variables flag (#12170).
     e9b0bf4 Remove redundant-constraints from -Wall (#10635)
     043604c RnExpr: Fix ApplicativeDo desugaring with RebindableSyntax
     dad6a88 LoadIFace: Show known names on inconsistent interface file
     3fb8f48 Revert "testsuite: Update bytes allocated of parsing001"
     a69371c users_guide: Document removal of -Wredundant-constraints from -Wall
     ad1e072 users_guide: Move addModFinalizer mention to 8.0.2 release notes
     1f5d4a3 users_guide: Move -fdefer-out-of-scope-variables note to 8.0.2 relnotes
     da920f6 users_guide: Move initGhcMonad note to 8.0.2 relnotes
     a48de37 restore -fmax-worker-args handling (Trac #11565)
     1e39c29 Kill vestiages of DEFAULT_TMPDIR
     8d35e18 Fix startsVarSym and refactor operator predicates (fixes #4239)
     b946cf3 Revert "Fix startsVarSym and refactor operator predicates (fixes #4239)"
     f233f00 Fix startsVarSym and refactor operator predicates (fixes #4239)
     e5ecb20 Added support for deprecated POSIX functions on Windows.
     0cc3931 configure.ac: fix --host= handling
     818760d Fix #10923 by fingerprinting optimization level.
     36bba47 Typos in notes
     33d3527 Protect StablPtr dereference with the StaticPtr table lock.
     133a5cc ghc-cabal: accept EXTRA_HC_OPTS make variable
     f93c363 extend '-fmax-worker-args' limit to specialiser (Trac #11565)
     ac2ded3 Typo in comment
     57aa6bb Fix comment about result
     f8b139f test #12567: add new testcase with expected plugin behaviour
     1805754 accept current (problematic) output
     cdbb9da cleanup: drop 11 years old performance hack
     71dd6e4 Don't ignore addTopDecls in module finalizers.
     6ea6242 Turn divInt# and modInt# into bitwise operations when possible
     8d00175 Less scary arity mismatch error message when deriving
     4ff4929 Make generated Ord instances smaller (per #10858).
     34010db Derive the Generic instance in perf/compiler/T5642
     05b497e distrib: Fix libdw bindist check
     a7a960e Make the test for #11108 less fragile
     dcc4904 Add failing testcase for #12433
     feaa31f Remove references to -XRelaxedPolyRec
     5eab6a0 Document meaning of order of --package-db flags, fixes #12485.
     a8238a4 Update unix submodule to latest HEAD.
     65d9597 Add hook for creating ghci external interpreter
     1b5f920 Make start address of `osReserveHeapMemory` tunable via command line -xb
     7b4bb40 Remove -flocal-ghci-history from default flags
     710f21c Add platform warning to Foreign.C.Types
     158288b Generalise type of mkMatchGroup to unify with mkMatchGroupName
     04184a2 Remove uses of mkMatchGroupName
     7b7ea8f Fix derived Ix instances for one-constructor GADTs
     0e7ccf6 Fix TH ppr output for list comprehensions with only one Stmt
     454033b Add hs_try_putmvar()
     03541cb Be less picky about reporing inaccessible code
     21d0bfe Remove unused exports
     35086d4 users_guide: Fix Docbook remnant
     b451fef users_guide: #8761 is now fixed
     c6ac1e5 users_guide: TH now partially supports typed holes
     6555c6b rts: Disable -hb with multiple capabilities
     5eeabe2 Test wibbles for commit 03541cba
     ec3edd5 Testsuite wibbles, to the same files
     505a518 Comments and white space only
     8074e03 Comments and white space only
     876b00b Comments and white space
     86836a2 Fix codegen bug in PIC version of genSwitch (#12433)
     9123845 tryGrabCapability should be using TRY_ACQUIRE_LOCK
     626db8f Unify CallStack handling in ghc
     a001299 Comments only
     a72d798 Comments in TH.Syntax (Trac #12596)
     97b47d2 Add test case for #7611
     ea310f9 Remove directories from include paths
     14c2e8e Codegen for case: Remove redundant void id checks
     6886bba Bump Haddock submodule to fix rendering of class methods
     8bd3d41 Fix failing test T12504
     9cbcdb4 shutdownHaskellAndExit: just do a normal hs_exit() (#5402)
     74c4ca0 Expose hs_exit_(rtsFalse) as hs_exit_nowait()
     3a17916 Improved documentation for Foreign.Concurrent (#12547)
     9766b0c Fix #12442.
     d122935 Mark mapUnionFV as INLINABLE rather than INLINE
     68f72f1 Replace INLINEABLE by INLINABLE (#12613)
     55d92cc Update test output
     bc7c730 Pattern Synonyms documentation update
     796f0f2 Print foralls in user format
     b0ae0dd Remove #ifdef with never fulfilled condition
     c36904d Fix layout of MultiWayIf expressions (#10807)
     f897b74 TH: Use atomicModifyIORef' for fresh names
     0b6024c Comments and manual only: spelling
     13d3b53 Test Trac #12634
     f21eedb Check.hs: Use actual import lists instead of comments
     0b533a2 A bit of tracing about flattening
     2fbfbca Fix desugaring of pattern bindings (again)
     66a8c19 Fix a bug in occurs checking
     3012c43 Add Outputable Report in TcErrors
     b612da6 Fix impredicativity (again)
     fc4ef66 Comments only
     5d473cd Add missing stderr file
     3f27237 Make tcrun042 fail
     28a00ea Correct spelling in note references
     b3d55e2 Document Safe Haskell restrictions on Generic instances
     9e86276 Implement deriving strategies
     b61b7c2 CodeGen X86: fix unsafe foreign calls wrt inlining
     59d7ee5 GHCi: Don't remove shadowed bindings from typechecker scope.
     3c17905 Support more than 64 logical processors on Windows
     151edd8 Recognise US spelling for specialisation flags.
     f869b23 Move -dno-debug-output to the end of the test flags
     d1b4fec Mark T11978a as broken due to #12019
     1e795a0 Use check stacking on Windows.
     c93813d Add NUMA support for Windows
     2d6642b Fix interaction of record pattern synonyms and record wildcards
     1851349 Don't warn about name shadowing when renaming the patten in a PatSyn decl
     ce3370e PPC/CodeGen: fix lwa instruction generation
     48ff084 Do not warn about unused underscore-prefixed fields (fixes Trac #12609)
     0014fa5 ghc-pkg: Allow unregistering multiple packages in one call
     b0d53a8 Turn `__GLASGOW_HASKELL_LLVM__` into an integer again
     f547b44 Eliminate some unsafeCoerce#s with deriving strategies
     23cf32d Disallow standalone deriving declarations involving unboxed tuples or sums
     4d2b15d validate: Add --build-only
     42f1d86 runghc: use executeFile to run ghc process on POSIX
     3630ad3 Mark #6132 as broken on OS X
     8cab9bd Ignore output from derefnull and divbyzero on Darwin
     e9104d4 DynFlags: Fix absolute import path to generated header
     eda5a4a testsuite: Mark test for #12355 as unbroken on Darwin.
     22c6b7f Update Cabal submodule to latest version.
     8952cc3 runghc: Fix import of System.Process on Windows
     7a6731c genapply: update source file in autogenerated text
     c5d6288 Mark zipWithAndUnzipM as INLINABLE rather than INLINE
     e4cf962 Bring Note in TcDeriv up to date
     465c6c5 Improve error handling in TcRnMonad
     58ecdf8 Remove unused T12124.srderr
     4a03012 Refactor TcDeriv and TcGenDeriv
     a2bedb5 RegAlloc: Make some pattern matched complete
     57a207c Remove dead code “mkHsConApp”
     cbe11d5 Add compact to packages so it gets cleaned on make clean.
     e41b9c6 Fix memory leak from #12664
     f3be304 Don't suggest deprecated flags in error messages
     76aaa6e Simplify implementation of wWarningFlags
     082991a Tc267, tests what happens if you forgot to knot-tie.
     3b9e45e Note about external interface changes.
     940ded8 Remove reexports from ghc-boot, help bootstrap with GHC 8.
     887485a Exclude Cabal PackageTests from gen_contents_index.
     00b530d The Backpack patch.
     4e8a060 Distinguish between UnitId and InstalledUnitId.
     5bd8e8d Make InstalledUnitId be ONLY a FastString.
     027a086 Update haddock.Cabal perf for Cabal update.
     61b143a Report that we support Backpack in --info.
     46b78e6 Cabal submodule update.
     e660f4b Rework renaming of children in export lists.
     f2d80de Add trailing comma to fix the build.
     21647bc Fix build
     7b060e1 Generate a unique symbol for signature object stub files, fixes #12673
     bcd3445 Do not segfault if no common root can be found
     8dc72f3 Cleanup PosixSource.h
     6c47f2e Default +RTS -qn to the number of cores
     85e81a8 Turn on -n4m with -A16m or greater
     1a9705c Escape lambda.
     b255ae7 Orient improvement constraints better
     b5c8963 Rename a parameter; trivial refactor
     88eb773 Delete orphan where clause
     76a5477 Move zonking out of tcFamTyPats
     cc5ca21 Improved stats for Trac #1969
     a6111b8 More tests for Trac #12522
     b5be2ec Add test case for #12689
     f8d2c20 Add a broken test case for #12689
     8fa5f5b Add derived shadows only for Wanted constraints
     d2959df Comments and equation ordering only
     bce9908 RnExpr: Actually fail if patterns found in expression
     577effd testsuite: Bump T1969 allocations
     184d7cb Add test for #12411
     042c593 Add test for #12589
     fef1df4 Add test for #12456
     57f7a37 Add missing @since annotations
     2fdf21b Further improve error handling in TcRn monad
     015e9e3 Cabal submodule update.
     1cccb64 Unique: Simplify encoding of sum uniques
     34d933d Clean up handling of known-key Names in interface files
     3991da4 MkIface: Turn a foldr into a foldl'
     aa06883 Improve find_lbl panic message
     90df91a PrelInfo: Fix style
     8c6a3d6 Add missing Semigroup instances for Monoidal datatypes in base
     d5a4e49 Make error when deriving an instance for a typeclass less misleading
     3ce0e0b Build ghc-iserv with --export-dynamic
     6c73932 Check for empty entity string in "prim" foreign imports
     0d9524a Disable T-signals-child test on single-threaded runtime
     e39589e Fix Windows build following D2588
     b501709 Fix Show derivation in the presence of RebindableSyntax/OverloadedStrings
     512541b Add a forward reference for a Note
     afdde48 Correct name of makeStableName in haddock
     3174beb Comments about -Wredundant-constraints
     82b54fc Fix comment typo
     692c8df Fix shadowing in mkWwBodies
     609d2c8 Typo in comment
     a693d1c Correct order of existentials in pattern synonyms
     f7278a9 Fix wrapping order in matchExpectedConTy
     1790762 Test Trac #12681
     db71d97 Reduce trace output slightly
     156db6b Add more variants of T3064 (in comments)
     a391a38 Comments only
     f43db14 Typos in comments
     3adaacd Re-add accidentally-deleted line
     9cb4459 testsuite: Work around #12554
     deed418 testsuite: Mark break011 as broken
     8b84b4f testsuite: Mark T10858 as broken on Windows
     3325435 testsuite: Mark T9405 as broken on Windows
     8bb960e testsuite/driver: Never symlink on Windows
     c6ee773 testsuite/timeout: Ensure that processes are cleaned up on Windows
     17d696f validate: Allow user to override Python interpreter
     7d2df32 testsuite/driver: More Unicode awareness
     5b55e4b testsuite: Eliminate unnecessary compile_timeout_multiplier
     2864ad7 testsuite/driver: Allow threading on Windows
     c5c6d80 testsuite: Mark T7037 as broken on Windows
     cf5eec3 Bump parallel submodule
     8fa2cdb Track dep_finsts in exports hash, as it affects downstream deps.
     f148513 Add option to not retain CAFs to the linker API
     1275994 remove unnecessary ifdef
     46f5f02 fixup! Add option to not retain CAFs to the linker API
     7129861 DynamicLoading: Replace map + zip with zipWith
     161f463 ghc/Main.hs: Add import list to DynamicLoading
     fa8940e fix build failure on Solaris caused by usage of --export-dynamic
     a3bc93e Add some missing RTS symbols
     3866481 Compute export hash based on ALL transitive orphan modules.
     02f2f21 cmm/Hoopl/Dataflow: remove unused code
     1f09c16 Test for newtype with unboxed argument
     2cb8cc2 StgCmmPrim: Add missing write barrier.
     a6094fa configure.ac: Report Unregisterised setting
     518f289 New story for abstract data types in hsig files.
     7e77c4b Support constraint synonym implementations of abstract classes.
     9df4ce4 Only delete instances when merging when there is an exact match.
     01490b4 Mark previously failing backpack tests as passing, with correct output.
     c2142ca Fix Mac OS X build by removing space after ASSERT.
     c23dc61 check-cpp: Make it more robust
     ff225b4 Typos in comments
     45bfd1a Refactor typechecking of pattern bindings
     82efad7 Comments and trivial refactoring
     cdbc73a Test Trac #12507
     d61c7e8 Make TcLevel increase by 1 not 2
     3f5673f A collection of type-inference refactorings.
     1f09b24 Accept 20% dedgradation in Trac #5030 compile time
     9417e57 Refactor occurrence-check logic
     e1fc5a3 Define emitNewWantedEq, and use it
     6ddba64 Improve TcCanonical.unifyWanted and unifyDerived
     f41a8a3 Add and use a new dynamic-library-dirs field in the ghc-pkg info
     acc9851 Fix failure in setnumcapabilities001 (#12728)
     1050e46 rts: configure.ac should populate HAVE_LIBNUMA instead of USE_LIBNUMA
     a662f46 Skip T5611 on OSX as it fails non-deterministically.
     3cb32d8 Add -Wcpp-undef warning flag
     6e9a51c Refactoring: Delete copied function in backpack/NameShape
     b76cf04 cmm/Hoopl/Dataflow: minor cleanup
     aaede1e rts/package.conf.in: Fix CPP usage
     a6bcf87 Refactoring: Replace when (not ...) with unless in ErrUtils
     f084e68 rts: Move path utilities to separate source file
     1c4a39d Prioritise class-level equality costraints
     1221f81 Don't instantaite when typechecking a pattern synonym
     08ba691 Take account of kinds in promoteTcType
     03b0b8e Test Trac #12174
     853cdae Test Trac #12081
     a182c0e testsuite: Bump peak_megabytes_allocated for T3064
     801c263 Fundeps work even for unary type classes
     9f814b2 Delete extraneous backtick in users' guide
     925d178 Make traceRn behave more like traceTc
     488a9ed rts/linker: Move loadArchive to new source file
     23143f6 Refine ASSERT in buildPatSyn for the nullary case.
     48876ae Remove -dtrace-level
     b8effa7 CmmUtils: remove the last dataflow functions
     3562727 Simple refactor to remove misleading comment
     f9308c2 Collect coercion variables, not type variables
     eefe86d Allow levity-polymorpic arrows
     0eb8934 Fix typo in comment
     cc29eb5 Revert "rts/linker: Move loadArchive to new source file"
     815b837 Minor doc addition as requested in #12774.
     7187ded Clarify comments on kinds (Trac #12536)
     aae2b3d Make it possible to use +RTS -qn without -N
     60343a4 Add test for #12732
     5ebcb3a Document unpackClosure# primop
     4b300a3 Minor refactoring in stg_unpackClosurezh
     4e088b4 Fix a bug in parallel GC synchronisation
     7ddbdfd Zap redundant imports
     80d4a03 Typos in comments
     795be0e Align GHCi's library search order more closely with LDs
     0b70ec0 Have static pointers work with -fno-full-laziness.
     19ce8a5 Sparc*: Prevent GHC from doing unaligned accesses
     79fb6e6 Tiny refactor
     9968949 Get rid of TcTyVars more assiduously
     7a50966 Simplify the API for TcHsType.kcHsTyVarBndrs
     f4a14d6 Use substTyUnchecked in TcMType.new_meta_tv_x
     13508ba Fix Trac #12797: approximateWC
     623b8e4 Renaming and comments in CorePrep
     8a5960a Uninstall signal handlers
     cc4710a testsuite: Simplify kernel32 glue logic
     f4fb3bc linker: Split out CacheFlush logic
     abfa319 linker: Shuffle configuration into LinkerInternals.h
     43c8c1c linker: Move mmapForLinker declaration into LinkerInternals.h
     3f05126 linker: Split symbol extras logic into new source file
     c3446c6 Shuffle declarations into LinkerInternals.h
     6ea0b4f linker: Split PEi386 implementation into new source file
     f6c47df linker: Split MachO implementation into new source file
     bdc262c linker: Split ELF implementation into separate source file
     6fecb7e linker: Move ARM interworking note to SymbolExtras.c
     dc4d596 Hoopl/Dataflow: make the module more self-contained
     80076fa Add notes describing SRT concepts
     b5460dd Add testcase for #12757
     967dd5c Merge cpe_ExprIsTrivial and exprIsTrivial
     eaa3482 testsuite: Update T10858 allocations
     ec22bac Add test for #12788
     f46bfeb API Annotations: make all ModuleName Located
     a977c96 Omit unnecessary linker flags
     e43f05b Add comments from Trac #12768
     7b0ae41 Remove a debug trace
     2cdd9bd Take account of injectivity when doing fundeps
     b012120 Handle types w/ type variables in signatures inside patterns (DsMeta)
     1cab42d Update release notes for type sigs in TH patterns patch
     1c886ea Stop -dno-debug-output suppressing -ddump-tc-trace
     25c8e80 Add tracing infrastructure to pattern match checker
     630d881 Allow GeneralizedNewtypeDeriving for classes with associated type families
     ead83db Describe symptoms of (and the cure for) #12768 in 8.0.2 release notes
     1964d86 Some minor linker cleanups.
     7d988dd Fix broken validate build.
     91f9e13 Fix hs_try_putmvar003 (#12800)
     2e8463b Update 8.0.2 release notes for #12784
     2325afe Fix comment about pointer tagging
     7fe7163 Adapt the (commented out) pprTrace in OccurAnal
     f05d685 Refactoring of mkNewTypeEqn
     317236d Refactor CallStack defaulting slightly
     500d90d ghc-cabal: Use correct name of linker flags env variable
     816d2e4 build system: Include CONF_LD_LINKER_OPTS in ALL_LD_OPTS
     9030d8e configure: Pass HC_OPTS_STAGEx to build system
     bae4a55 Pass -no-pie to GCC
     0a122a4 testsuite: Update allocation numbers for T5631
     e06e21a Add Richard Eisenberg's new email to mailmap
     bef7e78 Read parentheses better
     122d826 rts: Add api to pin a thread to a numa node but without fixing a capability
     aa10c67 rts/linker: Move loadArchive to new source file
     e8ae4dc Update user's guide after D2490
     03e8d26 Prevent GND from inferring an instance context for method-less classes
     60bb9d1 Revert "Pass -no-pie to GCC"
     7a7bb5d Revert "Refactor CallStack defaulting slightly"
     ec0bf81 rts: Fix LoadArchive on OS X
     d421a7e Pass -no-pie to GCC
     46e2bef testsuite: Lower allocations for T876
     7eae862 ghc-pkg: Munge dynamic library directories
     2cfbee8 rts: Fix build when linked with gold
     4e0b8f4 rts: Fix #include of <linker/PEi386.h>
     587dccc Make default output less verbose (source/object paths)
     568e003 template-haskell: Version bump
     ca1b986 ghc: Fix ghc's template-haskell bound
     8cb7bc5 rts: Fix references to UChar
     6c0f10f Kill Type pretty-printer
     55d535d Remove CONSTR_STATIC
     034e01e Accept output for scc003
     e0ca7ff Fix numa001 failure with "too many NUMA nodes"
     cb16890 testsuite: Fix creep of T4029
     011af2b configure: Verify that GCC recognizes -no-pie flag
     1b336d9 Skip 64-bit symbol tables
     98f9759 Hopefully fix build on OS X
     642adec Mark T12041 as expect_broken with -DDEBUG (#12826)
     017d11e Typos in comments, notes and manual
     31d5b6e fixup! Stop the simplifier from removing StaticPtr binds.
     0e58652 Test for unnecessary register spills
     4a835f0 Update xhtml submodule
     a637eeb Don't use mmap symbols when !RTS_LINKER_USE_MMAP
     0135188 Storage.c: Pass a size to sys_icache_invalidate
     fa70b1e Fix -fobject-code with -fexternal-interpreter
     7acee06 Avoid calling newDynFlags when there are no changes
     d3542fa Generalise the implicit prelude import
     8dfca69 Inline compiler/NOTES into X86/Ppr.hs
     b769586 Fix windows validate
     31398fb Test for type synonym loops on TyCon.
     2878604 Correct spelling of command-line option in comment
     cede770 Correct name of Note in comment
     07e40e9 Add Data instance for Const
     18eb57b Revert "Add Data instance for Const"
     9a4983d Pass autoconf triplets to sub-project configures
     20fb781 LLVM generate llvm.expect for conditional branches
     4d4f353 testsuite: Rip out hack for #12554
     04b024a GHCi: Unconditionally import System.Directory
     231a3ae Have reify work for local variables with functional dependencies.
     9c39e09 Switch to LLVM version 3.9
     94d1221 Add missing SMP symbols to RT linker.
     d328abc Spelling in comment only
     3bd1dd4 Add Data instance for Const
     4b72f85 Optimise whole module exports
     6ad94d8 Updated code comment regarding EquationInfo. Trac #12856
     ea37b83 A few typos in comments
     5bce207 testsuite: Add test for #12855
     926469f testsuite: Add test for #12024
     b98dbdf testsuite: Add (still broken) testcase for #12447
     e7ec521 testsuite: Add (still failing) testcase for #12550
     ea76a21 add ieee754 next* functions to math_funs
     514acfe Implement fine-grained `-Werror=...` facility
     4c0dc76 Ignore Hadrian build products.
     7e4b611 Make transformers upstream repository location consistent with others
     1399c8b ghc/hschooks.c: Fix include path of Rts.h
     f430253 Allow to unregister threadWaitReadSTM action.
     14ac372 Collect wildcards in sum types during renaming (#12711)
     d081fcf Make quoting and reification return the same types
     9a431e5 Make a panic into an ASSERT
     0476a64 Fix a bug in mk_superclasses_of
     f04f118 Comments only in TcType
     0123efd Add elemDVarEnv
     1eec1f2 Another major constraint-solver refactoring
     18d0bdd Allow TyVars in TcTypes
     4431e48 Remove redundant kind check
     90a65ad Perf improvements in T6048, T10547
     e319466 Typos in comments
     c1b4b76 Fix a name-space problem with promotion
     f0f4682 Test Trac #12867
     83a952d Test Trac #12845
     a5a3926 Kill off ifaceTyVarsOfType
     bc35c3f Use 'v' instead of 'tpl' for template vars
     edbe831 Use TyVars in a DFunUnfolding
     12eff23 Use TyVars in PatSyns
     5f349fe Improve pretty-printing of types
     eb55ec2 Refactor functional dependencies a bit
     1bfff60 Fix inference of partial signatures
     086b483 A tiny bit more tc tracing
     f8c966c Be a bit more selective about improvement
     6ec2304 Fix an long-standing bug in OccurAnal
     5238842 Typos in comments only [ci skip]
     605af54 Test Trac #12776
     27a6bdf Test Trac #12885
     3aa9368 Comments only (related to #12789)
     abd4a4c Make note of #12881 in 8.0.2 release notes
     f8c8de8 Zonk the free tvs of a RULE lhs to TyVars
     e755930 Typos in comments
     36e3622 Store string as parsed in SourceText for CImport
     1732d7a Define thread primitives if they're supported.
     30cecae users_guide: Bring 8.0.2 release notes up-to-date with ghc-8.0 branch
     f1fc8cb Make diagnostics slightly more colorful
     52222f9b Detect color support
     da5a61e Minor cleanup of foldRegs{Used,Defd}
     2d99da0 testsuite: Mention CLEANUP option in README
     3ec8563 Replace -fshow-source-paths with -fhide-source-paths
     c2268ba Refactor Pattern Match Checker to use ListT
     6845087 Purge GHC of literate Perl
     4d4e7a5 Use newBlockId instead of newLabelC
     7753273 AsmCodeGen: Refactor worker in cmmNativeGens
     6d5c2e7 NCGMonad: Add MonadUnique NatM instance
     eaed140 OrdList: Add Foldable, Traversable instances
     fe3748b testsuite: Bump haddock.compiler allocations
     795f8bd hschooks.c: Ensure correct header file is included
     6f7ed1e Make globals use sharedCAF
     56d7451 Fix type of GarbageCollect declaration
     428e152 Use C99's bool
     758b81d rts: Add missing #include <stdbool.h>
     23dc6c4 Remove most functions from cmm/BlockId
     b92f8e3 Added Eq1, Ord1, Read1 and Show1 instances for NonEmpty
     679ccd1 Hoopl/Dataflow: use block-oriented interface
     0ce59be Fix testsuite threading, timeout, encoding and performance issues on Windows
     dd9ba50 Update test output for Windows
     605bb9b testsuite: Use python3 by default
     20c0614 Update Mingw-w64 bindist for Windows
     ef37580 Fix windows validate.
     be8a47f Tweaks to grammar and such.
     03766cd Rename RuntimeRepPolymorphism to LevityPolymorphism
     e2330b6 Revert "Make globals use sharedCAF"
     c2a2911 Revert "Fix windows validate."
     6c54fa5 testsuite: Add another testcase for #11821
     0200ded Fix typo in functional dependencies doc
     f48f5a9e Ensure flags destined for ld are properly passed
     514c01e Levity polymorphic expressions mustn't be floated-out in let-bindings.
     a452c6e Make note of #12907 in 8.0.2 release notes
     0ac5e0c rts: Fix type of bool literal
     7214e92 testsuite: Remove Unicode literals from driver
     6576bf8 rts: Ensure we always give MADV_DONTNEED a chance in osDecommitMemory
     0f37550 Typos in comments
     a934e25 testsuite: Actually update haddock.compiler allocations
     7fafb84 testsuite/conc059: Don't attempt to use stdcall where it isn't supported
     747e77c Fix naming of the native latin1 encodings
     ddc271e Travis: Add dependency on python3
     27731f1 Note Trac #12141 in mk/build.mk.sample
     f46369b fdReady: use poll() instead of select()
     895a131 Install toplevel handler inside fork.
     2350906 Maintain in-scope set in deeply_instantiate (fixes #12549).
     eb6f673 8.2.1-notes.rst: tweak binutils version
     90c5af4 core-spec: Fix S_MatchData
     517d03e Fix an asymptotic bug in the occurrence analyser
     6305674 Fix used-variable calculation (Trac #12548)
     e912310 Use isFamFreeTyCon now we have it
     3e3f7c2 Test Trac #12925
     847d229 Color output is wreaking havoc on test results
     b82f71b Fix x86 Windows build and testsuite
     eec02ab Give concrete example for #12784 in 8.0.2 release notes
     24e6594 Overhaul GC stats
     19ae142 Mark rn017 and T7672 as expect_broken(#12930) with -DDEBUG
     6e4188a Fix unsafe usage of `is_iloc` selector in Ord instance for ImportSpec
     eafa06d Revert "Mark rn017 and T7672 as expect_broken(#12930) with -DDEBUG"
     b7e88ee Reduce the size of string literals in binaries.
     41ec722d Test Trac #12919
     39143a4 Mark T9577 as broken on Darwin due to #12937
     4dd6b37 Really mark T9577 as broken
     7036fde Overhaul of Compact Regions (#12455)
     c02aeb5 Ignore output for compact_gc: sizes change when profiling
     5aa9c75 Fix the test with -O
     9043a40 Fix crashes in hash table scanning with THREADED_RTS
     d70d452 rts: Use pthread itimer implementation on Darwin
     83d69dc Don't barf() on failures in loadArchive()
     499e438 Add HsSyn prettyprinter tests
     58d78dc Fix pretty printer test to nog generate stdout
     9bcc4e3 Remove stray commented out line in all.T
     c5fbbac Ignore stderr of all printer tests
     62332f3 Setup tcg_imports earlier during signature matching, so orphans are visible.
     617d57d Reduce qualification in error messages from signature matching.
     58c290a hschooks.c: Fix long line
     5063edb arclint: Lint cabal files
     c766d53 rts/linker: Fix LoadArchive build on Windows
     6889400 testsuite: Add test for #10249
     1e5b7d7 Update Windows GCC driver.
     55361b3 nativeGen: Fix string merging on Windows
     2bb099e BlockId: remove BlockMap and BlockSet synonyms
     6da6253 rts/PosixSource.h: Define __USE_MINGW_ANSI_STDIO on Windows
     f65ff2c Disambiguate reified closed type family kinds in TH
     61932cd Bump haddock submodule
     d3b546b Scrutinee Constant Folding
     cee72d5 Disable colors unless printing to stderr
     1c296c0c Export `warningGroups' and `warningHierarchies'
     62418b8 Mark T12903 as broken on OS X
     90fae01 Fix LLVM TBAA metadata
     2823492 NCG: Implement trivColorable for PowerPC 64-bit
     ca593c7 testsuite: make tests respond to SIGINT properly
     d1df8d1 Ensure each test inherits the TEST_HC_OPTS
     5349d64 Rename TH constructors for deriving strategies
     24a4fe2 testsuite: Mark prog003 as broken on Windows
     2618090 testsuite: Fix syntax error in rts/all.T
     17ac9b1 rts: Provide _lock_file in symbol table on Windows
     0ac5a00 Add `_unlock_file` to RTS symbols
     490b942 Automate GCC driver wrapper
     c3c7024 Make globals use sharedCAF
     818e027 Refactor pruning of implication constraints
     f1036ad Make dropDerivedSimples restore [WD] constraints
     6720376 Disable T12903 due to flakiness
     d03dd23 Fix a long-standing bug in CSE
     bc3d37d Float unboxed expressions by boxing
     8f6d241 Add infix flag for class and data declarations
     24f6bec Sanity check if we pick up an hsig file without -instantiated-with.
     db23ccf Fix recompilation detection when set of signatures to merge changes.
     f723ba2 Revert "Float unboxed expressions by boxing"
     cc2e3ec base: Make raw buffer IO operations more strict
     cb582b6 Don't have CPP macros expanding to 'defined'.
     9cb4a13 Fix Win32 x86 build validation after D2756
     aa123f4 Fix testcase T12903 on OS X
     7031704 print * in unicode correctly (fixes #12550)
     8ec864d Fix pretty printing of top level SCC pragmas
     9c9a222 Load orphan interfaces before checking if module implements signature
     26ce99c Fix typo in users' guide
     52c5e55 mk/config.mk.in: enable SMP on ARMv7+ (Trac #12981)
     0c3341b Show constraints when reporting typed holes
     6f7d827 Reset FPU precision back to MSVCRT defaults
     8b2e588 Adds llvm-prof flavour
     6370a56 Build terminfo on iOS.
     3c7cf18 Fix pprCLabel on platforms without native codegen.
     be5384c testsuite: Mark T9577 as broken due to #12965
     27287c8 procPointAnalysis doesn't need UniqSM
     fe5d68a Add entry to .gitignore to for __.SYMDEF_SORTED
     9550b8d Make unboxedTuple{Type,Data}Name support 0- and 1-tuples
     2940a61 testsuite: Specify expected allocations of T12877 for Windows
     5c76f83 check-ppr: Add a --dump flag to aid in debugging
     394231b Fix cost-centre-stacks bug (#5654)
     1ec632f Fix pretty printing of MINIMAL signatures
     503219e Warn about missing instance methods that start with an underscore
     d398162 testsuite: Separate out Windows results for T5205
     4d683fa base: Bump version to 4.10.0.0
     8f0546b testsuite: Add test for #12971
     0cad52d testsuite: Mark T10294 as fixed
     81c4956 testsuite: Add test for #12966
     cd4b202 array: Check for integer overflow during allocation
     0d213c1 UniqSupply: Use full range of machine word
     ffc2327 base: Add more POSIX types (fixes #12795)
     6fecb2a Verify that known-key uniques fit in interface file
     ed4cf03 Typos in comments
     13c1fc4 DynFlags: Rip out remnants of WarnContextQuantification
     c889df8 Packages: Kill unused UnitId argument to isDllName
     5bf344b CLabel: Kill redundant UnitId argument from labelDynamic
     222e99d Make up a module name for c-- files
     4026b45 Fix string merging with -split-sections
     8f71d95 Enable split sections by default where possible
     c8ed1bd testsuite: Add test for #12993
     2fa00f5 UNREG: include CCS_OVERHEAD to STG
     a6657bd revert '-Wl' prefixing to *_LD_OPTS
     c480860 rts/Compact.cmm: fix UNREG build failure
     d88efb7 Fix Pretty printer tests on Windows
     0af959b Revert "Do not init record accessors as exported"
     87c3b1d fix OpenBSD linkage (wxneeded)
     6c816c5 utils/genargs: delete unused tool
     8906e7b Reshuffle levity polymorphism checks.
     3dbd2b0 Windows: Improve terminal detection mechanism
     2d1beb1 rts/win32/IOManager: Fix integer types
     343b147 Reexport Language.Haskell.TH.Lib from Language.Haskell.TH
     2a02040 Fix bug in previous fix for #5654
     90cfa84 Run some tests with -fexternal-interpreter -prof
     21dde81 Improve StringBuffer and FastString docs
     e0fe7c3 Docs: Delete duplicate paragraph in user guide
     52ba947 Allow use of the external interpreter in stage1.
     25b70a2 Check family instance consistency of hs-boot families later, fixes #11062.
     630cfc3 Fix Haddock comment typo.
     b5d788a Introduce unboxedSum{Data,Type}Name to template-haskell
     513eb6a Fix #12998 by removing CTimer
     88e8194 T12035j: disable on NOSMP targets
     4704d65 T8209: disable on NOSMP targets
     7f5be7e T10296a: disable on NOSMP targets
     d327ebd regalloc_unit_tests: disable on UNREG targets
     bb74bc7 T8242: disable on NOSMP targets
     f1dfce1 Revert "Allow use of the external interpreter in stage1."
     6263e10 Fix timeout's timeout on Windows
     c0c1f80 Mark T8089 as unbroken since #7325 is now resolved
     27f7925 Allow use of the external interpreter in stage1.
     4535fa2 Test Trac #12996
     8fdb937 Make CompactionFailed a newtype
     574abb7 Rewrite Note [Api annotations] for clarity.
     9a29b65 Suppress duplicate .T files
     1771da2 Fix typos (not test relevant)
     f97d489 Test Trac #12968, plus some comments
     c73a982 Add note for rebindable syntax of [a..b]
     c66dd05 Move typeSize/coercionSize into TyCoRep
     d250d49 Add INLINE pragamas on Traversable default methods
     e07ad4d Don't eta-expand in stable unfoldings
     0a18231 Lint DFunUnfoldings
     05d233e Move InId/OutId to CoreSyn
     c48595e Never apply worker/wrapper to DFuns
     1a4c04b Fix 'SPECIALISE instance'
     c469db4 Test Trac #12950
     74033c4 Improved perf for T12227
     ccc918c Fix a forward reference to a Note
     2189239 Disambiguate two Notes with identical names
     ee4e165 Support for abi-depends for computing shadowing.
     99db12f Update ghc-cabal command line usage text.
     46f7f31 Notes on parsing lists in Parser.y
     41ade95 Fix another forward reference to a Note
     b7a6e62 Revert "Suppress duplicate .T files"
     efc4a16 Allow timeout to kill entire process tree.
     7a13f1f Alpha-renaming and white space only
     f06b71a Fix a bug in ABot handling in CoreArity
     ea8f91d White space only
     9a4af2c Comments only
     11306d6 Ensure that even bottoming functions have an unfolding
     432f952 Float unboxed expressions by boxing
     793ddb6 Tiny refactor in CoreTidy
     75e8c30 Propagate evaluated-ness a bit more faithfully
     ee872d3 Removed dead code in DsCCall.mk_alt
     b4c3a66 Push coercions in exprIsConApp_maybe
     8712148 testsuite: Split out Windows allocations numbers for T12234
     f95e669 users-guide: Kill extraneous link
     8f89e76 rename: Don't require 'fail' in non-monadic contexts
     158530a Add caret diagnostics
     46a195f Use python3 for linters
     1b06231 Fix test for T12877
     94d2cce base: Override Foldable.{toList,length} for NonEmpty
     2689a16 Define MAP_ANONYMOUS on systems that only provide MAP_ANON
     48a5da9 rename: Add note describing #11216
     9331e33 check-ppr: Make --dump the default behavior
     3c9fbba Remove redudant import from check-ppr
     815099c CallArity: Use exprIsCheap to detect thunks
     d2788ab Expand I/O CP in comments
     88f5add testsuite: Fix T13025
     4dec7d1 Testsuite: Skip failing tests on PowerPC 64-bit
     f3b99c7 Bump array submodule
     a370440 Fix various issues with testsuite code on Windows
     bab4ae8 Fix incorrect statement about plugin packages.
     9ff0738 Remove documentation about non-existent flag.
     c560957 Disallow users to write instances of KnownNat and KnownSym
     cc0abfa Update .mailmap
     b28ca38 Don't suggest enabling TypeApplications when it's already enabled
     8d63ca9 Refactor importdecls/topdecls parsing.
     5800b02 Add specialization rules for realToFrac on Complex
     683ed47 Don't use $ in the definition of (<**>) in GHC.Base
     6b3c039 Typo in manual [ci skip]
     df72368 Typofixes in manual and comments [ci skip]
     2664641 Remove a redundant test
     c909e6e Minor refactoring in CSE
     baf9ebe Ensure nested binders have Internal Names
     19d5c73 Add a CSE pass to Stg (#9291)
     5d2a92a Use atomic counter for GHC.Event.Unique
     5797784 Remove single top-level section in Foldable docs
     5ef956e Fix doctests in Data.Functor
     5f91ac8 Coerce for fmapDefault and foldMapDefault
     e6aefd6 Use the right in-scope set
     3540d1e Avoid exponential blowup in FamInstEnv.normaliseType
     b4f2afe Fix the implementation of the "push rules"
     4e3fc82 Inline work start
     e408eab Always expose unfoldings for overloaded functions.
     95dcb8b tidy
     ea6a686 missing import


More information about the ghc-commits mailing list