[commit: ghc] wip/T12357-built-in-map's head updated: DsExpr: Remove unnecessary usage of concatFS (5446684)

git at git.haskell.org git at git.haskell.org
Fri Jul 8 14:11:24 UTC 2016


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

Branch 'wip/T12357-built-in-map' now includes:

     a607011 Test Trac #10348
     77e5ec8 Demonstrate that inferring Typeable for type literals works
     efa136f Remove derived CFunEqCans after solving givens
     a3f6239 GHCi: fix scoping for record selectors
     a6cbf41 Spelling in comments
     855f56b Improved peak_megabytes_allocated
     2613271 Testsuite: fix framework failure
     89c7168 Fix #10534
     df63736 ghc.mk: Update instances of -auto-all
     1ff7f09 Lexer: Suggest adding 'let' on unexpected '=' token
     0d6c97b Lexer: Suggest adding 'let' on unexpected '=' token
     a90712b users_guide: Various spelling fixes
     d46fdf2 users_guide: Various spelling fixes
     681973c Encode alignment in MO_Memcpy and friends
     a0d158f Encode alignment in MO_Memcpy and friends
     c772f57 Fix #10494
     0de0b14 Fix #10495.
     ace8d4f Fix #10493.
     6644039 Test case for #10428.
     ff82387 Decompose wanted repr. eqs. when no matchable givens.
     93f97be (mostly) Comments only
     f108003 Testsuite wibble around decomposing newtypes.
     7eceffb Refactor handling of decomposition.
     9b105c6 Reimplement Unify.typesCantMatch in terms of apartness.
     298c424 Treat funTyCon like any other TyCon in can_eq_nc.
     a6b8b9c Fix typo in comment
     daf1eee Clarify some comments around injectivity.
     65d4b89 Add `Monoid` instance for `IO`
     f063656 Fix ghc-pkg reports cache out date (#10205)
     0760b84 Update foreign export docs, fixes #10467
     b98ca17 Make enum01/enum02/enum03 tests clang-compatible
     023a0ba Care with impossible-cons in combineIdenticalAlts
     5879d5a Report arity errors correctly despite kinds
     f4370c6 Comments only
     4a7a6c3 Rename getCtLoc, setCtLoc
     02bac02 Remove some horrible munging of origins for Coercible
     760b079 A bit more tracing
     0899911 Comments plus tiny refactoring
     ee64369 Refactor filterAlts into two parts
     5d98b68 Trac #4945 is working again
     72b21c3 Parser: commas_tup_tail duplicate SrcSpan on "Missing" value
     ba7c8e5 Test Trac #10503
     c45f8ce Elaborate test for Trac #10403
     40698fe Spelling in comments
     e283cec testsuite: mark T4945 as expect_broken
     440d1bc docs: Unbreak the PS/PDF builds for the User's Guide (#10509)
     7d5a845 should_run/allocLimit4: disable ghci way
     e491803 Amend tcrun024, tcrun025 after Trac #7854 fix
     7c2293a Amend tcrun037 after Trac #7854 fix
     2c6a041 Fix a couple of tests for GHCi/-O* (Trac #10052)
     5cc08eb Recognise 'hardhloat' as a valid vendor in a host tuple
     f2ffdc6 Updated output for test ghci024
     85d5397 Make GHC install libraries to e.g. xhtml-3000.2.1-0ACfOp3hebWD9jGWE4v4Gh.
     0cb1f5c Filter orphan rules based on imports, fixes #10294 and #10420.
     29bc13a Fix all.T for T8131/T8131b.
     15ef5fc Remove duplicate test.
     13ba87f Build system: unset HADDOCK when haddock is not found
     4854fce Change `Typeable` instance for type-lis to use the Known* classes.
     38f3745 Add parsePattern parser entry point
     b5a2e87 Documentation: add section on .haskeline file (#2531)
     e60dbf3 Check KnownSymbol => Typeable deduction
     f70fb68 Use -package-id to specify libraries on command line.
     6c5a66a Fix #10551 by using LIB_NAMES.
     01f7e44 Rename $1_$2_$3_LIB_NAME to LIB_FILE.
     55843f1 Further elaborate Trac #10403 test
     c084796 powerpc: add basic support for PLT relocations (#10402)
     73a6265 Make $1 in $1_$2_$3_FOO actually be directory.
     95d5031 Build system: delete unused variables in config.mk.in
     ece2c43 Drop prefix from package keys.
     aa26731 Clean outdated ext-core references in comments.
     4d1316a driver: pass '-fPIC' option to all CC invocations
     9a34864 Improve kind-checking for 'deriving' clauses
     c7b6fb5 Test Trac #10562
     a2f828a Be aware of overlapping global STG registers in CmmSink (#10521)
     a7eee0d Comments only
     3edc186 White space only
     9195927 Improve pretty-printing for CoPat
     ff8a671 Use a Representaional coercion for data families
     0b7e538 Allow recursive unwrapping of data families
     cc0dba1 Minor fix to free-vars in RnTypes
     9014a7e Fix addDataConStrictness
     b69dc73 Don't float out alpha[sig] ~ Int
     97e313c Add module header to test
     2f16a3b Get rid of irrlevant result type signature
     95fc6d5 Get rid of irrelevant impredicative polymoprhism
     fb7b692 Treat out-of-scope variables as holes
     b98ff25 Error message wibbles from out-of-scope changes
     0aaea5b Tiny refactor plus comments
     be0ce87 Fix for crash in setnumcapabilities001
     111ba4b Fix deadlock (#10545)
     7c8ffd3 GHCi docs: layout rule is respected inside :{ :}
     cbd9278 Comments only
     caf9d42 Small doc fixes
     0696fc6 Improve CPR behavior for strict constructors
     7c07cf1 closeOverKinds *before* oclose in coverage check
     614ba3c Kill off sizePred
     8e34783 Make fvType ignore kinds
     a64a26f Better tracing and tiny refactoring
     ceb3c84 Improve error message for Typeable k (T k)
     0e1e798 Test Trac #10524
     8d221bb Test #10582
     89834d6 Add -fcross-module-specialise flag
     302d937 Add -fcross-module-specialise flag
     bb0e462 Mask to avoid uncaught ^C exceptions
     9b5df2a Update performance numbers due to #10482
     c6bb2fc Correct BangPat SrcSpan calculation
     c495c67 Build system: remove unused variable CHECK_PACKAGES
     897a46c Testsuite: accept T2592.stderr (minor changes)
     6b9fc65 Testsuite: put extra_run_opts last on command line
     daa5097 Build system: prevent "warning: overriding commands for target..."
     bbf6078 disable check for .init_array section on OpenBSD
     9aa0e4b ghc-pkg: use read/writeUTF8File from Cabal
     bdd0b71 bin-package-db: copy paste writeFileAtomic from Cabal
     bdf7f13 Build system: rename bindist to bindist-list...
     d3c1dda Implement PowerPC 64-bit native code backend for Linux
     b5e1944 Use `+RTS -G1` for more stable residency measurements (#9675)
     1d6ead7 Enable using qualified field of constructor in GHCi
     f856383 Fix Trac #10519
     f07b7a8 Remove unnecessary OrdList from decl parser.
     6400c76 users_guide: Describe order-dependence of -f and -O flags
     e4bf4bf Remove redundant parser entry point
     8b55788 Add "since" column for LANGUAGE extensions in user guide
     39d83f2 Generalize traceM, traceShowM (fixes #10023)
     6b01d3c parser: Allow Lm (MODIFIER LETTER) category in identifiers
     889c81c Fix some validation errors.
     69beef5 Replace usages of `-w` by `-fno-warn`s
     b1d1c65 Support MO_{Add,Sub}IntC and MO_Add2 in the LLVM backend
     124f399 Testsuite: add -ignore-dot-ghci to some tests
     ced27de Remove dead code / overlapping pattern (#9723)
     a4b0342 Lexer: remove -fno-warn-unused-do-bind
     aa778c8 Comments only [skip ci]
     c875b08 Use -fno-warn-unused-imports instead of hiding `ord`
     8e12a21 Lexer.x and Parser.y: delete dead code
     5d48e67 Easy way to defer type errors (implements #8353)
     3fabb71 Fix typo [skip ci] (#10605)
     75de613 rts: fix incorrect checking start for -x arguments (#9839)
     edb2c54 Remove Hugs specific test setups (omit_compiler_type)
     7a3d85e Remove all *.stderr/stdout-hugs files
     4681f55 Specialise: Avoid unnecessary recomputation of free variable information
     2765fcf Remove warnings for -fwarn-incomplete-patterns
     a07898e Spelling in comments
     9180df1 Fix offset calculation in __stg_gc_fun
     aaa0cd2 Don't eagerly blackhole single-entry thunks (#10414)
     d27e7fd Add more discussion of black-holing logic for #10414
     d59cf4e Fix "CPP directive" in comment
     db530f1 Add Note [Warnings in code generated by Alex]
     37de4ad Build system: don't set GhcLibWays explicitly in build.mk.sample (#10536)
     62fcf05 Fix word repetitions in comments
     ebfc2fb Update comments around blackholes
     f753cf1 Allow deferred type error warnings to be suppressed
     31580e2 Fix todo in compiler/nativeGen: Rename Size to Format
     9a3e165 Deferred type errors now throw TypeError (#10284)
     5857e0a fix EBADF unqueueing in select backend (Trac #10590)
     6d69c3a Generalize `Control.Monad.forever`
     d03bcfa always use -fPIC on OpenBSD/AMD64 platform
     00c8d4d Fix #10596 by looking up 'Int' not 'Maybe Int' in the map.
     1967a52 Export more types from GHC.RTS.Flags (#9970)
     8800a73 Backpack: Flesh out more Cabal details
     d71b65f holePackageKey and isHoleModule utility functions.
     3d5f8e7 Unbreak Windows build: delete unusud throwIOIO
     6f9efcb Delete duplicate "Note [Unpack equality predicates]"
     f3bfa3b Broaden Outputable instance for Termination
     85b14a7 Comments only
     4f9d600 Fix Trac #10618 (out of scope operator)
     b29633f Bitmap: Fix thunk explosion
     889824d Document RULES and class methods
     c58dc1a White space only
     b5aabfb Infer types with flexible contexts
     7dcf86f users_guide: Fix errant "a" in RULES/class methods docs
     a6359f2 Add testcase for #10602
     6f1c076 Make mkQualPackage more robust when package key is bad.
     0a3c43f Comments only
     9e86bf1 Better type wildcard errors
     888026d Update .mailmap [skip ci]
     2d06a9f Improve error message for fundeps
     9b1ebba Delete the WayPar way
     d69dfba Fix self-contained handling of ASCII encoding
     ee28a79 T1969: Update max_bytes_used
     a846088 T876 (32-bit): Update bytes allocated
     de6597e perf/compiler: Switch to -G1 and update performance metrics
     b935497 T9872d: Update 32-bit allocations
     d073c77 Do not optimise RULE lhs in substRule
     e922847 Add Linting for Rules
     7da7b0e Make sure rule LHSs are simplified
     875723b Reformat a leading # in a comment
     d7335f7 Test Trac #10463
     02a6b29 Test Trac #10634
     946c8b1 Another comment with a leading # (sigh)
     2e52057 Build system: comments only [skip ci]
     ec197d3 Build system: add `make show!` command (#7810)
     f70f1b6 Build system: delete two unused files
     47ebe26 Build system: delete REGULAR_INSTALL_DYNLIBS and INSTALL_DYNLIBS
     392ff06 Build system: do not build stm and parallel by default
     5764ade Testsuite: delete unused with_namebase
     322ae32 Testsuite: delete remaining only_compiler_types(['ghc']) setups
     783b79b traivs: Use the new container based travis setup
     4dc3877 Testsuite: rename *.stderr-ghc to *.stderr
     ab5257b Testsuite: delete *.stderr-ghc-7.0 *.stdout-ghc-7.0
     4ee658a0 Mark test case for #10294 expect_broken on #10301
     0a40278 Flush stdout in test case for #10596
     8e6a503 Mark test case for #10294 conditionally expect_broken on #10301
     b1063b1 Testsuite: mark T10294 conditionally expect_broken on #10301
     348f5ca Build system: delete fingerprint.py [skip ci]
     a592e9f Remove all references to sync-all
     75fd5dc Don't get a new nursery if we exceeded large_alloc_lim
     9f978b6 Fix #10642.
     74a00bc initGroup: only initialize the first and last blocks of a group
     504c2ae Docs: `sortOn = sortBy (comparing f)` [skip ci]
     02897c5 Failing test case: idArity invariant check, #10181
     e29c2ac CoreUtils: Move seq* functions to CoreSeq
     ae0e340 CoreUtils: Move size utilities to CoreStats
     fa33f45 PprCore: Add size annotations for top-level bindings
     29f8225 CoreLint: Use size-annotated ppr variant
     82f1c78 Fix tests
     ae96c75 Implement -fprint-expanded-synonyms
     415351a Put Opt_Static into defaultFlags if not pc_DYNAMIC_BY_DEFAULT (#7478)
     2c5c297 DeriveFoldable for data types with existential constraints (#10447)
     2c9de9c Handle Char#, Addr# in TH quasiquoter (fixes #10620)
     a5e9da8 Fix off-by-one error in GHCi line reporting (Trac #10578)
     3448f98 Reduce non-determinism in ABI hashes with RULES and instance decls
     bc604bd Update assert to fix retc001 and retc002 (#9243)
     0d4b074 Travis: actually do debug builds
     ac0feec Testsuite: small test cleanups
     f607393 Testsuite: accept new stderr for T9497{a,b,c}-run (#10224)
     a0371c0 Build system: fail when encountering an unknown package tag
     dc6e556 Testsuite: mark T2497 expect_broken_for(#10657, ['optasm', 'optllvm'])
     dcaa486 Testsuite: mark T7919 expect_broken_for(#7919, ['optasm','dyn','optllvm'])
     11f8612 Testsuite: mark 3 tests expect_broken_for(#10181, ['optasm', 'optllvm'])
     16a8739 Testsuite: mark qq007 and qq008 expect_broken(#10181)
     cbb4d78 Testsuite: mark qq007 and qq008 expect_broken(#10047)
     43dafc9 Testsuite: mark gadt/termination expect_broken_for(#10658, ['optasm','optllvm'])
     34bb460 Testsuite: mark array001 and conc034 expect_broken_for(#10659, ['optasm',...])
     9834fea Add regression test for unused implicit parameter warning (#10632)
     4c96e7c Testsuite: add ImpredicativeTypes to T7861 (#7861)
     7f37274 Testsuite: add -XUndecidableInstances to T3500a
     029367e Testsuite: add regression test for missing class constraint
     82ffc80 LlvmCodeGen: add support for MO_U_Mul2 CallishMachOp
     49373ff Support wild cards in TH splices
     c526e09 primops: Add haddocks to BCO primops
     4cd008b Do not treat prim and javascript imports as C imports in TH and QQ
     96de809 Fix primops documentation syntax
     d71d9a9 Testsuite: fix concprog002 (AMP)
     2f18b197 Testsuite: mark concprog002 expect_broken_for(#10661, ['threaded2_hT'])
     d0cf8f1 Testsuite: simplify T8089 (#8089)
     b4ef8b8 Update submodule hpc with fix for #10529
     0c6c015 Revert "Revert "Change loadSrcInterface to return a list of ModIface""
     214596d Revert "Revert "Support for multiple signature files in scope.""
     9ade087 primops: Fix spelling mistake
     e0a3c44 Delete __GLASGOW_HASKELL__ ifdefs for stage0 < 7.8
     8f48fdc Use varToCoreExpr in mkWWcpr_help
     3fbf496 Comments only (superclasses and improvement)
     3509191 Refactor newSCWorkFromFlavoured
     7c0fff4 Improve strictness analysis for exceptions
     cd48797 Comments and white space only
     3c44a46 Refactor self-boot info
     efa7b3a Add NOINLINE for hs-boot functions
     aa78cd6 Documents -dsuppress-unfoldings
     0df2348 Comments and layout only
     a0e8bb7 Implement -dsuppress-unfoldings
     b5c1400 Comments and white space only
     f1d0480 Avoid out-of-scope top-level Ids
     7a6ed66 Comments only
     55754ea Fix test T2497 to avoid infinite loop in RULES
     feaa095 Do occurrence analysis on result of BuiltInRule
     00f3187 Make seq-of-cast rule generate a case
     35eb736 T4945 is working again
     f519cb5 testsuite: Show killed command line on timeout
     97a50d5 configure: Bump minimum bootstrap GHC version to 7.8
     dbe6dac When iconv is unavailable, use an ASCII encoding to encode ASCII
     18c6ee2 Travis: use ghc-7.8.4 as stage0 to fix the build
     d941a89 Validate: by default do show commands
     a7e0326 Validate: document --quiet [skip ci]
     1224bb5 Add utility function isHoleName.
     50b9a7a Revert "Trac #4945 is working again"
     1b76997 Testsuite: recenter haddock.base allocation numbers
     b949c96 Eliminate zero_static_objects_list()
     0d1a8d0 Two step allocator for 64-bit systems
     e3df1b1 Validate: explain THREADS instead of CPUS in --help
     cf57f8f Travis: do pass `--quiet` to validate
     0b12aca Switch from recording IsBootInterface to recording full HscSource.
     adea827 Add ExceptionMonad instance for IOEnv.
     144096e Give more informative panic for checkFamInstConsistency.
     4a9b40d Export alwaysQualifyPackages and neverQualifyPackages.
     939f1b2 Some utility functions for testing IfaceType equality.
     dd365b1 Use lookupIfaceTop for loading IfaceDecls.
     5c3fc92 Fix Trac #10670
     9851275 Comments only
     d784bde Lexer: support consecutive references to Haddock chunks (#10398)
     d2b4df1 Generate .dyn_o files for .hsig files with -dynamic-too
     76e2341 Accept next-docstrings on GADT constructors.
     e78841b Update encoding001 to test the full range of non-surrogate code points
     b5c9426 Parenthesise TypeOperator in import hints
     1852c3d DataCon: Fix redundant import
     4c8e69e rts/sm: Add missing argument names in function definitions
     7ec07e4 Slight refactoring to the fix for #4012
     608e76c Document type functions in the Paterson conditions
     e809ef5 ghci: fixity declarations for infix data constructors (#10018)
     5ff4dad Add a few comments from SPJ on fixity declarations
     f9687ca Library names, with Cabal submodule update
     45c319f Fix line number in T10018 testcase
     30d8349 Comments only
     e161634 Comments about stricteness of catch#
     d53d808 Refactoring around FunDeps
     6e618d7 Improve instanceCantMatch
     09d0505 RetainerProfile: Add missing UNTAG_STATIC_LIST_PTR
     b04bed0 renamer: fix module-level deprecation message
     070f76a -include-pkg-deps takes only one hyphen.
     7e70c06 Use isTrue# around primitive comparisons in integer-gmp
     c55f61c Add missing parentheses in eqBigNatWord#
     474d4cc Comment tweaks only
     f842ad6 Implementation of StrictData language extension
     2178273 Add UInfixT to TH types (fixes #10522)
     81fffc4 Remove runSTRep from PrelNames
     bc4b64c Do not inline or apply rules on LHS of rules
     2d88a53 Improve warnings for rules that might not fire
     09925c3 Revert "RetainerProfile: Add missing UNTAG_STATIC_LIST_PTR"
     a1e8620 Revert "Eliminate zero_static_objects_list()"
     e343c0a Test case for #10698
     a1dd7dd Fallout from more assiduous RULE warnings
     f83aab9 Eliminate zero_static_objects_list()
     2dbb01a Add a missing check for -fcpr-off
     fac11f8 Comments only
     4e8d74d Deal with phantom type variables in rules
     92d2567 Define DsUtils.mkCastDs and use it
     fa915af Spit out a little more info with -dppr-debug
     e4114c8 Fix an outright error in competesWith
     499b926 Fix Trac #10694: CPR analysis
     918dcf8 The parallel package has warnings
     2e33b9c Modify spec002 to be less trivial
     72d23c3 Better treatment of signatures in cls/inst
     24afe6d Fix missing files
     5a8a8a6 Don't allowInterrupt inside uninterruptibleMask
     9f7cdfe Make configure error out on missing ghc-tarballs on Windows
     e7c331a Make headers C++ compatible (fixes #10700)
     26315ed Fix misspelled function name in a comment
     4f80ec0 Improve error message for newtypes and deriving clauses
     e9ad42d Typos in comments and strings
     d7c2b01 Fix comment that confused Haddock
     b5097fe Testsuite: rename rename/should_fail/T5001 to T5001b (#5001)
     e273c67 Testsuite: mark tests recently fixed as passing + accept new stderr
     756fa0a Testsuite: skip T10489 unless compiler_debugged (#10489)
     6880277 Testsuite: add arrows/should_compile/T5333 (#5333)
     58b5f04 Testsuite: add typecheck/should_fail/T9260 (#9260)
     58986c4 Testsuite: add typecheck/should_fail/T8034 (#8034)
     aee19d0 Testsuite: T10245 is passing for WAY=ghci (#10245)
     36bbfbd Backpack docs on renamer and depsolver, also s/package/unit/.
     a442800 Build system: remove function keyword from configure.ac (#10705)
     a66e1ba User's guide: delete ancient "Core syntax" example
     7cf87df Fix #7919 (again)
     353db30 Remove checked-in PDFs.
     8f81af9 Typos in comments
     ad089f5 Give raise# a return type of open kind (#10481)
     75504f3 Typos in comments
     15dd700 Replace (SourceText,FastString) with StringLiteral data type
     d9b618f Typo in comment
     37227d3 Make BranchFlag a new kind
     92f5385 Support MO_U_QuotRem2 in LLVM backend
     948e03e Update parallel submodule, and re-enable warnings
     b38ee89 Fix incorrect stack pointer usage in StgRun() on x86_64
     4d8859c Typos in comments
     d7ced09 Minor improvement to user guide
     30b32f4 Test Trac #10134
     697079f 4 reduce/reduce parser conflicts resolved
     d9d2102 Support wild cards in data/type family instances
     7ec6ffc Typos in comments [skip ci]
     64b6733 CmmParse: Don't force alignment in memcpy-ish operations
     30c981e Removed deprecated syntax for GADT constuctors.
     f063bd5 Fix #10713.
     b5f1c85 Test #9233 in perf/compiler/T9233
     d7b053a Pretty: reformat using style from libraries/pretty (#10735)
     9d24b06 Pretty: rename variables to the ones used by libraries/pretty (#10735)
     25bc406 Pretty: improve error messages (#10735)
     53484d3 Pretty: remove superfluous parenthesis (#10735)
     2d1eae2 Pretty: kill code that has been dead since 1997 (#10735)
     6f6d082 Pretty: Args of NilAbove/TextBeside/Nest/Union are always RDocs (#10735)
     926e428 Pretty: use BangPatterns instead of manual unboxing Ints (#10735)
     f951ffc Pretty: mimic pretty API more closely (#10735)
     85179b5 Pretty: use replicate for spaces and multi_ch (#10735)
     dd7e188 Add framework flags when linking a dynamic library
     4c55f14 users_guide: Add note about #367 to Bugs section
     6029748 Drop custom mapM impl for []
     ecb1752 Make -fcpr-off a dynamic flag
     b12dba7 Make Exception datatypes into newtypes
     22bbc1c Make sure that `all`, `any`, `and`, and `or` fuse (#9848)
     fd6b24f Additions to users' guide and release notes
     575abf4 Add Fixity info for infix types
     e2b5738 Allow proper errors/warnings in core2core passes
     617f696 Do not complain about SPECIALISE for INLINE
     a426154 Warn about missed specialisations for imports
     49615d9 Comments only
     ab98860 Minor refactor to use filterInScope
     9536481 Tidy up and refactor wildcard handling
     28096b2 Fix quantification for inference with sigs
     75f5f23 Coments only
     cc07c40 Comments only
     294553e T8968-1 and -3 should pass
     64dba51 Test Trac #10742
     eca9a1a Ensure DynFlags are consistent
     97843d0 base: Add instances
     600b153 llvmGen: Rework LLVM mangler
     aa23054 Add test for #10600 (exhaustiveness check with --make and -fno-code)
     bc43d23 Rejigger OSMem.my_mmap to allow building on Mac
     a1c934c base: Add missing Traversable instance for ZipList
     6cab3af Big batch of Backpack documentation edits.
     79e0a10 Test Trac #10753
     a192d6b Comments only
     f1b4864 Sync base/changelog.md with GHC 7.10.2 release
     590aa0f Make oneShot open-kinded
     92f35cd cmmCreateSwitchPlan: Handle singletons up-front
     2c4a7d3 Update transformers submodule to 0.4.3.0 release
     f04c7be Fix unused-matches warnings in CmmLex.x
     a40ec75 Update testsuite/.gitignore [skip ci]
     b4ed130 Replace HsBang type with HsSrcBang and HsImplBang
     2da06d7 User manual update, as prodded by #10760.
     2b4710b Add missing </para> to User's guide to fix the build
     8cce7e4 Bump template-haskell to new major version 2.11
     67576dd Pretty: bugfix fillNB (#10735)
     bcfae08 Pretty: fix potential bad formatting of error message (#10735)
     5d57087 Pretty: fix a broken invariant (#10735)
     85bf76a Pretty: show rational as is (#10735)
     f903949 Pretty: improving the space/time performance of vcat, hsep, hcat (#10735)
     b0dee61 template-haskell: Add changelog entry to infix type operators
     7b211b4 Upgrade GCC to 5.2.0 for Windows x86 and x86_64
     e415369 Update mingw tarball location
     8c5b087 SysTools: Fix whitespace in error message
     d2dd5af DynFlags: Prohibit hpc and byte-code interpreter
     ec68618 Name: Show NameSort in warning
     1857191 Testsuite: mark T8089 expect_broken(#7325) on Windows
     8906037 Testsuite: mark encoding005 expect_broken(#10623) on Windows
     ca85442 Testsuite: recenter 2 performance tests on Windows
     744ff88 Testsuite: speedup running a single test
     e367e27 Travis: prevent 10' no output, by setting VERBOSE=2
     74897de Make rts/ThreadLabels.c threadsafe for debug runtime.
     22aca53 Transliterate unknown characters at output
     ab9403d Dump files always use UTF8 encoding #10762
     b17ec56 Fix rdynamic flag and test on Windows
     ebca3f8 rts/Printer.c: speed up '-Da' printer for 'LIBBFD' build
     18a1567 Add selectors for common fields (DataCon/PatSyn) to ConLike
     d97e60f Comments reformating/corrections
     b6be81b Build system: delete half-baked Cygwin support
     98f8c9e Delete sync-all
     a146b28 GhcMake: Fix spelling in comment
     0d0e651 Bag: Add Foldable instance
     9e8562a Implement getSizeofMutableByteArrayOp primop
     3452473 Delete FastBool
     2f29ebb Refactor: delete most of the module FastTypes
     47493e6 Build system: simplify install.mk.in
     a1c008b Build system: delete unused distrib/Makefile
     a5061a9 Check options before warning about source imports.
     37a0b50 Delete ExtsCompat46 (#8330)
     b78494e fix 64bit two-stage allocator on Solaris/AMD64 platform (#10790)
     fba724c configure.ac: Allow disabling of large-address-space
     1c643ba Fix algorithm.tex build and update with some new info.
     0f3335f Comments and white space
     816d48a Implement lookupGlobal in TcEnv, and use it
     711e0bf tcRnDeclsi can use tcRnSrcDecls
     ac0d052 TcDeriv: Kill dead code
     de476e9 PrelNames: Clean up list a bit
     89d25b9 BinIface: Clean up whitespace
     7924469 Clean up handling of knownKeyNames
     a8601a8 Revert "Clean up handling of knownKeyNames"
     28ad98e PrelNames: introduce dcQual in place of conName
     211b349 Move newImplicitBinder to from IfaceEnv to BuildTyCl
     70ea94c IfaceEnv: Clean up updNameCache a bit
     f6035bc MkIface: Introduce PatSynId, ReflectionId, DefMethId
     7bd8f8f TysWiredIn: Shuffle code around
     15c63d2 base: Remove a redundant 'return'
     38c98e4 RTS: Reduce MBLOCK_SPACE_SIZE on AArch64
     15cb83d Add testcase for #7411
     a6826c5 Make Generic (Proxy t) instance poly-kinded (fixes #10775)
     1b56c40 Respect GHC_CHARENC environment variable #10762
     81ae26d Dwarf: Fix DW_AT_use_UTF8 attribute
     cbf58a2 Dwarf: Produce {low,high}_pc attributes for compilation units
     8476ce2 Dwarf: Produce .dwarf_aranges section
     0c823af Fix identifier parsing in hp2ps
     cd2dc9e ghc-pkg --enable-multi-instance should not complain about case sensitivity.
     c7f0626 integer-gmp: optimise bitBigNat
     c1d7b4b StgCmmHeap: Re-add check for large static allocations
     60120d2 Fix 7.10 validate
     12098c2 Fix typo in pattern synonym documentation.
     10a0775 Anchor type family instances deterministically
     ad26c54 Testsuite: refactoring only
     6740d70 Use IP based CallStack in error and undefined
     010e187 Fix trac #10413
     ff9432f Add test for updating a record with existentially quantified fields.
     296bc70 Use a response file for linker command line arguments #10777
     ba5554e Allow annotations though addTopDecls (#10486)
     c8f623e Expand declaration QQs first (#10047)
     28ac9d3 Improve the error messages for class instance errors
     3cc8f07 stm: Fix test case
     5d7a873 Testsuite: don't warn about missing specialisations
     e0b3ff0 Testsuite: update expected output
     3b23379 Testsuite: mark 4 tests expect_broken_for(#10712, opt_ways)
     32a9ead Fix some tests that were broken by D861
     c43c8e2 Testsuite: by default run all tests for a single way
     bd16e0b Testsuite: delete dead code
     3744578 Injective type families
     5dc88b7 Add test for T10836 (expected broken)
     34b106f Accept underscores in the module parser. (Thanks spinda for the fix.)
     b639c97 Testsuite: fix tcfail220 - Maybe is wired-in now
     e1293bb Testsuite: only print msg when timeout kills process unexpectedly
     79cdb25 Testsuite: ignore line number differences in call stacks (#10834)
     85915e9 Make Data.List.foldr1 inline
     19c6049 Fix T6018th test failure
     64761ce Build system: implement `make install-strip` (#1851)
     5c372fe ghc-pkg: don't print ignored errors when verbosity=0
     c60c462 user-guide: Add missing <para> tags around <listitem> body
     96b986b EventLog: Factor out ensureRoomFor*Event
     062feee tracing: Kill EVENT_STARTUP
     2c24fd7 Build system: put each BuildFlavour in a separate file (#10223)
     b40e559 Build system: simplify *-llvm BuildFlavours (#10223)
     1abbacd Build system: cleanup utils/ghc-pkg/ghc.mk
     dc671a1 SPECIALIZE strictMinimum for Int and Integer
     c6b82e9 Further simplify the story around minimum/maximum
     554be5e Build system: detect when user cloned from GitHub
     864a9c4 Build system: remove hack for Mac OSX in configure.ac (#10476)
     a158607 Build system: delete the InstallExtraPackages variable
     330fbbd Build system: make *-cross BuildFlavours consistent (#10223)
     8be43dd Build system: cleanup BUILD_DIRS + add lots of Notes
     e4a73f4 Move GeneralCategory et al to GHC.Unicode
     1b8eca1 Build system: check for inconsistent settings (#10157)
     dbb4e41 HeapStackCheck: Small refactoring
     4356dac Forbid annotations when Safe Haskell safe mode is enabled.
     23a301a Testsuite: comment out `setnumcapabilities001` (#10860)
     cdca31e Don't check in autogenerated hs files for recomp013.
     3a71d78 Comments on oneShot
     a870738 Improve rejigConRes (again)
     487c90e Add a test for Trac #10806
     a7f6909 A CFunEqCan can be Derived
     377395e Improve documentation for transform list-comps
     50d1c72 Fix broken links in documentation
     413fa95 Improve documentation of comprehensions
     f30a492 Testsuite cleanup
     8c0eca3 Add assertions
     18759cc Remove redundant language extensions
     195af2d Dead code removal, export cleanup
     4275028 Code movement
     7ad4b3c s/StgArrWords/StgArrBytes/
     89324b8 Testsuite: normalise slashes in callstack output
     37081ac Testsuite: mark enum01-enum03 expect_broken(#9399) on Windows
     3ec205a CodeGen: fix typo in error message
     08af42f hpc: use `takeDirectory` instead of `dropWhileEnd (/= '/')`
     c8d438f Testsuite: mark T6037 expect_fail on Windows (#6037)
     12b0bb6 Account for stack allocation in the thread's allocation counter
     14c4090 Pretty: fix unicode arrow operators.
     325efac Fix `hp2ps -i-`
     e66daec DynFlags: remove unused sPgm_sysman (#8689)
     8d89d80 Testsuite: add test for #10781
     43eb1dc Show minimal complete definitions in ghci (#10847)
     8ecf6d8 ApplicativeDo transformation
     77662e1 Add namePackage function to template-haskell
     48746ff Docs: make sure all libs are included in index.html (#10879)
     a8406f8 Pass TEST_HC_OPTS in bug1465 and T5792.
     2d4db40 Fix #10815 by kind-checking type patterns against known kinds.
     8ee2b95 Polish some error messages.
     b89c491 Always run explicitly requested ways (extra_ways) for fast runs.
     c738b12 Replace [PostTc id Type] with PostTc id [Type]
     e156361 Put stable pointer names in the name cache.
     1637e4d Driver: --make -o without Main should be an error (#10895)
     1a13551 Test #10347
     d19a77a Update user guide, fixing #10772
     d7f2ab0 Test #10770
     79b8e89 Print associated types a bit better.
     1292c17 Allow TH quoting of assoc type defaults.
     27f9186 Clarify parsing infelicity.
     93fafe0 Re-polish error messages around injective TFs.
     6a20920 Small improvement in pretty-printing constructors.
     cbcad85 Fix typo in test for #10347.
     2f9809e Slightly better `Coercible` errors.
     e27b267 Perform a validity check on assoc type defaults.
     8e8b9ed Run simplifier only when the env is clean.
     cd2840a Refactor BranchLists.
     c234acb `_ <- mapM` --> `mapM_`
     3f13c20 Revert "Revert "Revert "Support for multiple signature files in scope."""
     09d214d Revert "Revert "Revert "Change loadSrcInterface to return a list of ModIface"""
     06d46b1 Unify hsig and hs-boot; add preliminary "hs-boot" merging.
     d516d2e Fix build failure, I think.
     07f6418 Remove graphFromVerticesAndAdjacency
     5a8b055 TcDeriv: Use a NameEnv instead of association list
     83e23c1 Remove (now bogus) assert.
     0b852fc base: use Show for ErrorCall in uncaughtExceptionHandler
     d4d34a7 Make derived names deterministic
     089b72f DeriveLift extension (#1830)
     4cdab73 HscMain: Place CPP macro invocation on one line
     79f5732 testsuite: attempt fixing fallout from 089b72f52
     c6bdf4f Remove references to () from types of mkWeak# and friends
     65bf7ba DsBinds: Avoid using String when desugaring CallStack construction
     939a7d6 Annotate CmmBranch with an optional likely target
     cf90a1e Add constant-folding rule for Data.Bits.bit
     73921df Update Cabal to recognize DeriveLift
     453cdbf base: export allocation counter/limit API from System.Mem
     5c11523 reify associated types when reifying typeclasses
     39a262e Revert "reify associated types when reifying typeclasses"
     2440e3c Fix a bug with mallocForeignPtr and finalizers (#10904)
     b08a533d Fix DeriveGeneric for types with same OccName (#10487)
     4f9ee91 Testsuite: update expected output for T8832 on 32-bit systems (#8832)
     5883b56 Testsuite: properly fix T8832.stdout-ws-32 (#8832)
     1395185 Testsuite: add test for #10767
     fb40926 Weak: Don't require wrapping/unwrapping of finalizers
     a98815a Dwarf: Rename binding to avoid shadowing ppr
     a0b1f41 Dwarf: Ensure block length is encoded correctly
     f7fd864 Skip a possible BOM in utf8 encoding
     3fbf8f4 Debug: Remove extraneous LANGUAGE CPP
     988b2ba rts: Clean up whitespace in Trace.h
     b4d43b4 reify associated types when reifying typeclasses(#10891)
     78053f4 Allow enumDeltaIntegerFB to be inlined
     2eddcd9 Lexer: delete dead code for binary character literals
     23baa65 .gitignore update for some test files.
     e3ab25a Typos in comments
     03b3804 Add Data.Semigroup and Data.List.NonEmpty (re #10365)
     f2a174a Update nofib submodule
     a52db23 Update nofib submodule again
     eb975d2 Fix treatment of -0.0
     57e3742 Document peculiarities of `traceM`.
     b29f20e nativeGen PPC: fix > 16 bit offsets in stack handling
     bd41eb2 LLVM: Implement atomic operations in terms of LLVM primitives
     9539408 LLVM: Factor out accumulation of LLVM statements and variables
     7442434 Move CallStack back to base
     e3d2bab Fix signature of atomic builtins
     9ed700b Don't use old linkable for hs-boot files.
     4fd6207 Move user's guide to ReStructuredText
     93e21b9 docs: Fix ghc_config.py.in
     b6f76b9 Prevent GHC from silently dying when preprocessor is not found
     c4d7df0 Fix broken validation Build 6564 and accepting a few other test results
     a3c78ab Build system: add mk/validate.mk.sample
     a96f1ac Testsuite: update expected output for T8602
     6cde981 Make GHC generics capable of handling unboxed types
     0eb8fcd Enable `Enumeration is empty` warnings for `Integer`
     2f74be9 Fill in associated type defaults with DeriveAnyClass
     d2fb532 testsuite: Bump up haddock.base expected allocations
     620fc6f Make Windows linker more robust to unknown sections
     aecf4a5 Build system: don't create mk/are-validating.mk
     c0bdfee Testsuite: only add -fno-warn-missed-specialisations for ghc>=7.11
     7fcfee1 A few typos in comments
     5ca1d31 Testsuite: make driver python 2.6 compatible again
     427f8a1 Deduplicate one-shot/make compile paths.
     8c1866a Comments only
     0e169a8 Fix kind-var abstraction in SimplUtils.abstractFloats
     ca816c6 Remove dead code: ruleLhsOrphNames
     7da3d30 Comments only
     3833e71 Comments about TcLevel assignment
     59883ae Documentation for FrontendResult
     36811bf AsmCodeGen: Ensure LLVM .line directives are sorted
     ea4df12 Ensure shiftL/shiftR arguments aren't negative
     7b443bb Improve error messages for ambiguous type variables
     69a6e42 Allow non-operator infix pattern synonyms
     e2b579e Parser: revert some error messages to what they were before 7.10
     f64f7c3 Tests for #10945 and #10946
     931d0a7 Move orphan instance/rule warnings to typechecker/desugarer.
     e99e6db Extra files to ignore from the new Restructured documentation.
     0ead0ca Disable man building for most quick build styles.
     c7ab799 Ignore __pycache__.
     e5baf62 Simplify type of ms_srcimps and ms_textual_imps.
     5dc3db7 Switch to LLVM version 3.7
     80602af Revert "Switch to LLVM version 3.7"
     e331392 Fix error msg: ghci can't be used with -prof or -static (#10936)
     5d84110 Add short library names support to Windows linker
     182c44d Keep `shift{L,R}` on `Integer` from segfaulting
     840df33 Rename SpecInfo to RuleInfo (upon SPJ's advice).
     fa5eabe sphinx: Don't share doctrees between targets
     614ce4b Testsuite: T3333 still fails on non-linux statically linked ghci (#3333)
     bbad4f6 Delete ShPackageKey for now.
     f002340 compiler/nativeGen/PPC/Ppr.hs: Whitespace
     4bd58c1 PPC: Fix right shift by 32 bits #10870
     e737a51 base: MRP-refactoring of AMP instances
     6b7bad9 Test Trac #10931
     f8fbf38 Reinstate monomorphism-restriction warnings
     dcc3428 Don't inline/apply other rules when simplifying a rule RHS.
     330ba6a testsuite: attempt fixing T10935 output
     94ef79a Slightly wibble TcSimplify documentation
     d2f9972 Make dataToQa aware of Data instances which use functions to implement toConstr
     1818b48 Fix incorrect import warnings when methods with identical names are imported
     e5bfd70 docs: overhaul Derive{Functor,Foldable,Traversable} notes
     dec5cd4 base: Add forkOSWithUnmask
     e8c8173 Allow arr ∧ (first ∨ (***)) as minimal definition of Arrow instance
     29310b6 Switch to LLVM version 3.7
     7756161 travis: use LLVM 3.7
     933adc0 Fix GHCi on Arm (#10375).
     729bf08 User should use -package-id flag if value in question is IPID.
     5b0191f Update Cabal to HEAD, IPID renamed to Component ID.
     b92a51f Rename package key to unit ID, and installed package ID to component ID.
     6338a1c Rename PACKAGE_KEY and LIB_NAME in build system.
     20e30d5 Minor stylistic update.
     04e8366 ELF/x86_64: map object file sections separately into the low 2GB
     78c9dea Fix windows build after D975
     4d6844a rts/Linker.c : Fix armhf build (#10977)
     808bbdf Remove dead function patSynTyDetails
     b1884b0 Implement DuplicateRecordFields
     75492e7 Add typed holes support in Template Haskell.
     6a8ca65 Allow left ∨ (+++) as minimal definition of ArrowChoice instance
     e7c076d base: changelog entries for Arrow/ArrowChoice
     324e0ac base: MINIMAL pragmas for Arrow/ArrowChoice
     3340fe0 Build system: fix `make -j1` (#10973)
     603a369 Silence the linker on Windows so tests pass
     fff0254 Move Control.Monad.IO.Class to base from transformers
     a6a3dab Libdw: Add libdw-based stack unwinding
     40cbf9a Signals: Print backtrace on SIGUSR2
     e8ed213 Make Monad/Applicative instances MRP-friendly
     6638bfd CmmParse: Clarify description of calling convention
     d990b5f Signals: Always install SIGUSR2 handler
     75c7cda ghc-pkg: Express return-method in terms of pure
     c6781a5 template-haskell: MRP-refactor Applicative/Monad instances
     1e34f62 MRP-refactor `GHCi` Applicative/Monad instance
     d6d421c template-haskell: set explicit return=pure
     40235c3 fix RTS linker compilation failure on Solaris
     7bbb61b Driver: `ghci -e` should behave like `ghc -e` (#9360)
     2b25a58 base: Have the argument of mask restore the state.
     96dc041 Systools.hs: Improve detection of GCC and Clang
     ae4acbd Testsuite Windows: don't use forward slashes in topdir path
     1750ebc Reject top-level typed TH splices. Fixes #10945
     bb7e93c Extended default rules now specialize Foldable, Traversable to [] (#10971)
     68a084f Testsuite: add test for #10997
     2bc6efc Fix caching of pagesize
     7855afb Fix breakage in the GHCi debugger
     e3e5a96 Remove old trace statement
     d77c404 Stop the pipeline when it doesn't need to be run.
     c633f71 Add another test for #10549
     1e8d1f1 Suggest enabling PatternSynonyms (#10943)
     9ec5996 rts/Schedule.c: remove unused variable
     0499aa7 Add missing stderr file
     9cb192c Make stronglyConnCompFromEdgedVertices deterministic
     0ae6a43 Suggest chmod 755 instead of 644
     fa7d582 Quote GHC path in configure so we can deal with multiple spaces.
     8f5ad1a Quote GHC_PKG in Makefile.
     fdb08e2 Add testcase for #10426
     0afba67 arclint: ReST doesn't need ArcanistMergeConflictLinter
     fd63ea5 base: Note platform dependence of registerFd
     7dae074 Verify minimum required version of sphinx-build
     67284a0 gitignore: Ignore sphinx doctrees directories
     2866dfb Fix broken .arclint
     4e40340 Support more sphinx-build versions in configure script
     ec14392 typo in comments: s/selectg/select/
     798d2e2 configure.ac: Fix autotool warnings
     7aea0cf use Proxy instead of undefined -- we already dropped support for 7.6
     ca12c24 Update example GHCi startup
     abc214b rts/Linker.c:  Split RTS symbols out into separate file
     3ed4b80 rts/Linker.c: Convert #if/#else to if/else
     898f34c rts/RtsSymbols.c: Fix Windows build
     43751b2 Provide a utility to check API Annotations
     c2fab84 Add testcase for #10370
     86e5eb9 Remove redundant typedef
     0b79aa1 base: Add Haddocks to GHC.RTS.Flags
     73c273a Fix a typo in the User's Guide ReST intro
     23e344b Remove cygwin32_HOST_OS #ifdefs
     499ce29 Add flag to reverse errors in GHC/GHCi
     a9c93bd Implement MIN_VERSION and VERSION macros natively in GHC.
     c10c01c Build system: comments only [skip ci]
     f86fb5e Add regression tests for #10045, #10999
     6831815 Comments only
     0ce858e Zonk properly when checkig pattern synonyms
     adc3d17 manpage: Mark as orphan document
     d1d8704 Use correct documentation flag for freverse-errors
     158d2a9 Make it possible to have different UniqSupply strategies
     079dd12 Fix "Use correct documentation flag for freverse-errors"
     dc13467 DynFlags: Fix more merge errors
     ffcdd84 Sort field labels before fingerprint hashing
     166c597 DynFlags: Yet one more fix
     31704ad Make worker-wrapper optional
     9efa56d Fix the DYNAMIC_GHC_PROGRAMS=NO build on Mac/Windows
     19354fb Make T10970a non-dependent on GCC version.
     7c2ab6f Testsuite: accept output for T10999 (#10999)
     d1ab6fc PrelNames: Fix duplicate unique
     9fc2d77 Build system: don't add ALL_HC_OPTS when linking
     04b0a73 Pattern synonyms: swap provided/required
     de27bed Update haskeline/terminfo submodules
     c1e1584 Update `deepseq` submodule
     776d55c rts/Linker.c: Drop support for legacy OS X dyn loading
     ce2416b Fix rts/T9579 tests on OS X
     08f5c4e Backpack documentation updates for component IDs [no-ci]
     032be43 Testsuite: report and error out on unfound tests
     a051788 Revert "Build system: don't add ALL_HC_OPTS when linking"
     2a74a64 Record pattern synonyms
     fa58731 Revert "Build system: don't create mk/are-validating.mk"
     e31113f Move mkDefaultMethodIds, mkRecSelBinds from TcTyClsDecls to TcTyDecls
     d25fa86 TcTyDecls: Remove redundant import of Applicative
     40e6214 DynFlags: Add (another) missing hunk from D1360
     bef2f03 Generate Typeable info at definition sites
     bbaf76f Revert "Generate Typeable info at definition sites"
     e272ab9 x86 codegen: don't generate location comments
     8ddf417 Linker: Fix type in m32_free_internal
     9b3a058 Swap prov/req in variable naming in Parser.y
     9376249 Fix unused-import stuff in a better way
     3e94842 Record usage information using GlobalRdrElt
     da58d15 Kill redundant import
     268aa9a integerConstantFolding: when(compiler_debugged(), expect_broken(#11006))
     0a16374 Disambiguate record selectors by type signature
     1f1c7c6 Build system: rename runghc.hs to Main.hs
     b05ab1a Build system: cleanup a few .cabal files
     314395e Build system: cabalise deriveConstants + genprimopcode
     2624298 Fix segfault due to reading non-existent memory
     42e8528 CmmParse: Expose popcnt operations
     3e2c227 Linker: Clean up USE_MMAP usage
     1c80db5 Insert an empty line between two STG definitions in dump output.
     56f9ef4 Unify: Add Outputable instance for UnifyResultM
     aa289d2 Move win32 tarball download logic to script
     f78b477 driver: use PROGBITS type for .debug-ghc-link-info section
     59e728b Testsuite: suggest quoting $(TEST_HC)
     91c6b1f Generate Typeable info at definition sites
     39b71e8 Reimplement shadowing on a per database basis.
     f5974c8 rts: Make MBLOCK_SPACE_SIZE dynamic
     fce758c Add failing test for #11039
     a5cb27f Make type-class dictionary let binds deterministic
     e03e22c testsuite: performGC requires SMP support for 'qg' option
     d9d201c testsuite: 'threaded2' tests require '-N' RTS option support
     e0071c3 unreg: handle CmmStack in C codegen (unbreaks '-g')
     8995865 Update primitive/vector submodules
     62f0fbc Update parallel submodule
     8160f42 Add subWordC# on x86ish
     7a48e6c Make ghc-cabal's `System.Directory` import more robust
     6bef55c Fix documentation build on windows
     e2a78ee Signals: Ensure libdw session is freed
     8f02baa Remove Data.List.NonEmpty.{words,unwords,lines,unlines}
     bc7cc25 disable large address space on OpenBSD
     da1a8da llvmGen: Fix build with Clang
     8fd5cff llvmGen: Really fix build with Clang
     3021cc0 Add rts/Linker support for more than 64k sections
     31bcf9b Apply WERROR only to stage2 HC options
     c3b0215 Provide a utility to check API Annotations docs
     4ad2a8f rts/posix: Reduce heap allocation amount on mmap failure
     c8e866a Enforce linkage with pthread library on OpenBSD
     184dfce Linker: More uint64_t to uintptr_t fixes
     9f0ecb4 ghc-prim: Fix hs_ctz64 for powerpc
     62e1b35 Update array/stm/hpc/haddock submodules
     d2a7fb9 Update directory submodule
     12abc77 Update filepath submodule
     de8443c Update process submodule
     3238ef7 Update unix submodule
     32f92a3 Update hoopl submodule
     f8ba4b5 Bump `base` version to 4.9.0.0 (closes #11026)
     4b8b934 ghc-prim: add API delta as changelog (re #11043)
     84bf1eb Bump ghc-prim version to 0.5.0.0 (closes #11043)
     f16827f ApiAnnotations: BooleanFormula is not properly Located
     5a48180 keepCAFsForGHCi was broken
     677d768 DynFlags: -freverse-errors should be defFlag
     3431ad6 Update Cabal submodule
     6fb0ba6 Dwarf: Preserve stack pointer register
     76611d7 Dwarf.Types: Fix comment style
     159a1a2 cmm: Expose machine's stack and return address register
     d9f8862 StgStartup: Setup unwinding for stg_stop_thread
     bb446b2 Libdw: Remove special treatment for stg_stop_thread
     b8df858 Dwarf.Constants: Introduce Haddock sections
     52c6e3d Libdw: Fix symbol naming
     e9bfb3f Minor simplification in unariser pass:
     65f3c4c Change sphinx for documentation building on windows to the python3 version
     f46f32b EventLog: Loop fwrite if necessary during flush
     9fe5497 rts: Produce stack trace on fatal error
     1e2259b Update process submodule to process-1.4 release
     c00c5e5 get rid of Elf32/Elf64_Section as this is a non-portable Linux-ism.
     130ca3e Update filepath submodule for proper version
     5065cf4 base: Update `@since 4.8.2` annotations (re #11026)
     0bc8c6a base: GHC.RTS.Flags symbols really were introduced in 4.8.2
     83fd2ba base: Add changelog entry for 4.8.2.0
     8c80dcc base: Add new Control.Monad.Fail module (re #10751)
     b62605e Add `MonadPlus IO` and `Alternative IO` instances
     334fe45 rts/Hash: Constify HashTable* in lookupHashTable
     987d542 Build system: renable -Wall on validate (base)
     0e21678 Cabal-level sanity check to enforce Cabal flag-invariant
     22fcf9c Tweak settings for LLVM tests
     e547954 Use full name of LLVM program in error message
     10647d4 Linker: #ifdef cleanup
     a58eeb7 Call Arity: In "e x", the result of "x" is not shared
     ce1f160 Make GHCi & TH work when the compiler is built with -prof
     6e6438e Allow the GHCi Linker to resolve related dependencies when loading DLLs
     be88585 fix #10734 by adding braces to pretty-printing of let inside do
     2208011 Remove PatSynBuilderId
     d9c1450 Build system: use stage0 to build dll-split
     8262c95 Parser: allow empty multi-line deprecation warnings
     bd69f6f minor: use unless instead of (when . not)
     932d503 Replace freeVarsOf scrut with scrut_fvs to avoid repetition
     80d7ce8 Add pprSTrace for debugging with call stacks
     0e40c01 Quote file paths in linker scripts
     2b7d9c2 Add OpenBSD specific RTS symbols
     f405632 Fix sporadic failing ghci/Linker/Dyn tests
     3cfe60a Abstract TFs can have injectivity information
     96621b1 Associate pattern synonyms with types in module exports
     5eb56ed Fix link in documentation
     fbc2537 OPTIONS_GHC compiler flags may contain spaces (#4931)
     ea8c116 Remove unused field in ConDecl
     f0f9365 Remove fun_infix from Funbind, as it is now in Match
     109d7ce Systools: read ELF section without calling readelf
     fa61edd Improve documentation of Data.List.lines:
     0f49508 Put kind variables before type variables when specializing
     badf5d5 Detect invalid foreign imports in bytecode compiler
     fb0d512 nativeGen.PPC: Fix shift arith. right > 31 bits
     afbd30b mkGadtDecl no longer in P monad
     63cad5d Rename bundled pattern synonym tests to reflect new terminology
     a038b72 Remove redundant test.
     9bea234 fix RTS Linker on platforms without SHN_XINDEX support
     4a32bf9 Implement function-sections for Haskell code, #8405
     e090f1b Change demand information for foreign calls
     8755719 rules/haddock: Set __HADDOCK_VERSION__
     351de16 New magic function for applying realWorld#
     ac2e1e5 T10678: Fix bytes allocated statistic
     5d6133b Ignore comments in getOptions
     2290c8b APIAnnotations:add Locations in hsSyn for layout
     e66f79d Give helpful advice when a fully qualified name is not in scope
     b8d263d Turn ImportedModsVal into a data type
     5a86292 Remove imv_empty from ImportedModsVal
     8868ff3 Update note for Parent to explain PatternSynonym.
     8988be8 Make 'error' include the CCS call stack when profiled
     3353f62 Rip out __HADDOCK__ references
     5488422 Fix bootstrapping with GHC 7.10.1
     46a03fb Implement the Strict language extension
     fe95463 ApiAnnotations: Add SourceText for unicode tokens
     ee91482 ApiAnnotations : ITopenExpQuote needs SourceText
     83b214d RtsFlags: Clean up stale CPP
     b8a849b users-guide: Limit column width
     69822f0 RtsFlags: Refactor some of the deeper switches
     7485d0c ghc.mk: Make install_docs rule sh-compatible
     82cf672 haddock.mk: Use \{1,\} instead of \+
     3773e91 Use TcM instead of it's expanded form, in TcSplice
     741cf18 Weaken monadic list operations to Applicative
     e2d9821 Data.List.isSubsequenceOf documentation clarification
     2d1a563 Implement support for user-defined type errors.
     3d88e89 s/FrontendMerge/FrontendInterface/g
     9193629 Move usage calculation to desugaring, simplifying ModGuts.
     ac1a379 Revert "Unify hsig and hs-boot; add preliminary "hs-boot" merging."
     df8169c Bump process submodule
     4e74ef9 T9181: Fix testsuite output
     615ba5f Remove orphan Functor instance of Data.Graph.SCC
     7c9cbfd template-haskell: drop `TemplateHaskell` requirement
     b3d6c0f Update Cabal submodule for new known extension
     8ad9e74 Make `timer_create(CLOCK_REALTIME)` autoconf test more reliable
     acce37f Fix archive loading on Windows by the runtime loader
     7b962ba Implement OverloadedLabels
     233d131 MonadFail proposal, phase 1
     98a4fa5 DynFlags: Don't list TemplateHaskell as supported if it's not
     11e336e More import related hints
     f405e1e Disable failed specialisation warnings by default & update documentation.
     f9e17fd Add -fwarn-missing-monadfail-instance to mkUserGuidePart
     6b3d5b5 rts: Kill PAPI support
     c945c90 base: Documentation for TypeError
     112ce87 docs: Ignore Sphinx doctrees produced by manpage build
     3ee0c14 Improve MonadFail errors by mentioning the pattern
     2f7e895 users-guide: Give links more contrast
     a0f977e relnotes: Update base version
     8eefdf0 users-guide: Use tango pygments style
     02eb44d users-guide: Fix typo in conf.py
     2d0e1db Comments only
     8e8d26a Comments on TcRnTypes.canDischarge
     07eb258 Refactor HsExpr.RecordCon, RecordUpd
     c61759d Fix inconsistent pretty-printing of type families
     cc79dd1 users-guide: Move <h1> outside of <a> tag
     971f2c9 Correct > to > in user's guide
     a41830f Mention "-XMonadFailDesugaring" in the docs
     a586622 Release Notes: Mention out-of-scope error message improvements
     2442038 Fix interaction of DuplicateRecordFields and GHC.Generics
     3e2a4ee Fix broken build-system when libffi uses install-sh
     65d7ff0 Make `derivedConstants` more crosscompile-friendly
     7dfde0e derivedConstants: Add support for AIX
     c5d8162 Make GHC aware of OSAIX and AixLD
     75036aa Set AIX specific CFLAGS flags
     fce0465 Unbreak Text.Read.Lex.lex on Unicode symbols
     d732ce0 Bump process submodule
     b72ca3e Pattern Synonym Documentation
     a689c8e ghci: don't let ctags/etags overwrite source files
     1994304 user's guide: Fix some accidental triple-` quote
     998c371 users-guide: Fix version number
     7e6dcf4 base: Delete errant GHC/Stack.hsc
     f40fe62 Follow-up fixup to c5d8162d230c373
     7f77e4e Fix Windows builds after D1242
     d585073 RtsFlags: Fix const warning
     192dd06 Suppress conflicting types for builtins warnings
     6664ab8 Add DVarSet - a deterministic set of Vars
     2325bd4 Create a deterministic version of tyVarsOfType
     b98ff3c Function definition in GHCi
     a703fbc Remove accidentally added T10359 blob
     4976ab2 Follow-up fix to 3e2a4eefbed7002437c3f (re #11109)
     638fde5 Add comment to Parser.y re extra API Annotation
     64737f2 New expected test output for 32 bit platforms
     3df9563 ApiAnnotations: Make all RdrName occurences Located
     6393dd8 Make abstractVars deterministic in SetLevel
     02c689c build.mk.sample: Document meaning of WERROR
     5d6cfbc Rip out Papi configure check
     7c9a04d Add a note explaining why every RdrName is Located
     dbad0d5 Libdw: Fix build on 32-bit platforms
     70ee638 Libdw: Fix initial register collection on i386
     36b2139 rts: Expose more libdw symbols
     a3a8ce6 rts: Add simple resource pool
     6fbf22d rts: Add LibdwPool, a pool for libdw sessions
     bb249aa base: Add Haskell interface to ExecutionStack
     7aaeaf8 Support multiple debug output levels
     40be909 Dwarf: Ensure tick parentage is preserved
     9471562 Output source notes in extended DWARF DIEs
     5955510 Improve constraint-used-as-type error msg
     70efb62 Add tests/monadfail/Makefile
     e587217 Add the rest of the notes for Located RdrName
     1c45f41 rts: Always export Libdw* symbols
     12dbc89 Add `PrelNames.thenAName` for `Applicative(*>)`
     f09f247 Implement new `-fwarn-noncanonical-monad-instances`
     c05fddd Rearrange error msgs and add section markers (Trac #11014).
     6d14793 Add -Wcompat warning flag group
     e506f02 Rewrite checkUniques and incorporate into validate
     8c5fe53 DynFlags: Update comments to reflect new users guide
     8dc6da8 Comments only
     5e04c38 Simplify the MonadFail code
     76f3142 DynFlags: Drop stale comment
     9032d05 update link to MonadFail proposal
     924f851 Refactor default methods (Trac #11105)
     e9a4c09 Comments only
     e913676 Add a simplifier trace for eta-expansion
     9aa9458 Note STM's vulnerability to non-allocating loops
     c7a058f User's Guide: Add links to MFP wiki page
     5699ac9 User documentation for DuplicateRecordFields
     d2a2d5e Note #11108 in the bugs section of users guide
     c4308b4 rts/Pool: Add poolTryTake
     1712a9e LibdwPool: Use poolTryTake
     ba14f04 Libdw: Handle failure to grab session for location lookup
     d25f853 Update transformers submodule
     49aae12 Check arity on default decl for assoc types
     583867b Update haskeline & terminfo submodules
     85fcd03 Implement new -XTemplateHaskellQuotes pragma
     72e3620 ghci: Add support for prompt functions
     55c737f ghc-pkg: print version when verbose
     399a5b4 Remove deprecated quasiquoter syntax.
     71c0cc1 GHCi should not defer typed holes
     54a9456 Update containers submodule
     616aceb Update deepseq submodule
     5897213 Remove redundant `#if`s
     f101a82 ghci: Refactor handling of :show
     bcd55a9 Some improvements on CoreToDos passed to plugins
     290def7 Implement warnings for Semigroups as parent of Monoid
     afb7213 MkId: Typos in comments
     14d0f7f Build system: Add stage specific SRC_HC_(WARNING_)OPTS
     6dce643 Fix grammar and typo in TcTyDecls
     36c1247 Remove duplicated line
     44c3e37 Fix warning about unused pattern variable
     b432e2f Make the determinism tests more robust
     1e041b7 Refactor treatment of wildcards
     218fdf9 Make the order of fixities in the iface file deterministic
     741f837 Implement more deterministic operations and document them
     52b02e6 Comments only (isIrrefutablePat)
     b564731 Comments (TcSMonad)
     d00cdf2 Revert "ghci: Add support for prompt functions"
     1caff20 StgSyn: Remove unused SRT constructor
     c75948b Move Stg-specific code from DynFlags to SimplStg
     d4d54b4 Remove *.xml from gitignore
     a12e47b Avoid panic due to partial ieName
     8cba907 Create empty dump files when there was nothing to dump
     0d1a2d2 ErrUtils: Spruce up Haddocks
     e7929ba Update bytestring submodule
     d25f3c0 users_guide/glasgow_exts.rst: fix link markup
     8a50610 Major Overhaul of Pattern Match Checking (Fixes #595)
     43a31fe testsuite: haddock.compiler: Bump expected allocations
     a034031 extending_ghc.rst: fix broken link (Trac #10950)
     c5597bb Revert "Create empty dump files when there was nothing to dump"
     7b29b0b Fix haddock syntax
     0dd61fe Kill redundant patterns
     934b3a0 Update test output
     40fc353 Bump hoopl submodule
     ae4398d Improve performance for PM check on literals (Fixes #11160 and #11161)
     99d01e1 Remove unused import in deSugar/TmOracle.hs
     7af29da Use Autoconf's AC_USE_SYSTEM_EXTENSIONS
     cd9f3bf RTS: Rename InCall.stat struct field to .rstat
     6ef351d On AIX we need -D_BSD defined in <Stg.h>
     d40f5b7 PmExpr: Fix CPP unacceptable too clang's CPP
     36a208f Use builtin ISO 8859-1 decoder in mkTextEncoding
     befc4e4 Check: More Clang/CPP wibbles
     e9220da Bump allocations for T783
     dc33e4c T5642 is broken
     96e67c0 T5642: Skip it entirely
     5b2b7e3 Make callToPats deterministic in SpecConstr
     1c9fd3f Case-of-empty-alts is trivial (Trac #11155)
     28035c0 Add derived constraints for wildcard signatures
     1cb3c8c Wibbles only
     822141b Make -dppr-debug show contents of (TypeError ...)
     1160dc5 Fix egregious error in eta-reduction of data families
     31b482b Minor refactoring of user type errors
     67565a7 Tidy user type errors in checkValidType
     43a5970 Comments only
     16aae60 T5642: Fix skip usage
     caa6851 testsuite: Rename pmcheck/T7669 to pmcheck/T7669a
     d4bf863 Update peak_megabytes_allocated for T9675
     020375d Add linter to check for binaries accidentally added to repository
     901cab1 lint: Add linter to catch uses of ASSERT macro that Clang dislikes
     c865c42 StgCmmMonad: Implement Outputable instance for Sequel for debugging
     e2c518e libdw: enable support only on i386 and amd64
     81cf200 pmcheck: Comments about term equality representation
     406444b pmcheck: Comments about undecidability of literal equality
     8f28797 Fix broken linters when using python3
     c714f8f Use git.h.o copy of arcanist-external-json-linter
     a14296c Temporarily disable external-json linters
     51d08d8 Enable non-canonical Monad instance warnings for stage1/2
     314bc99 ghc.mk: cleanup: use tab consistently
     d6512c7 ghc.mk: don't run mkUserGuidePart more than once
     13ab2c6 ghc.mk: fix docs re-rebuilding
     5f1e42f Allow to compile OSMem.c when MEM_NORESERVE is not available
     df67940 Make ghc.mk compatible with pedantic /bin/sh impls
     986ceb1 Implement new `-fwarn-noncanonical-monoid-instances`
     8b42214 Tweak use of AC_USE_SYSTEM_EXTENSIONS
     be92c28 Update hoopl submodule
     f5127c8 linters/check-cpp: Don't produce debug log
     3ea4fb7 Documentation: escape characters in template-haskell Haddocks
     42a5469 Ignore generated linter.log
     3d55e41 ghc-pkg: Restore old behavior in colored version; fixes 6119
     8cef8af Re-export data family when exporting a data instance without an export list
     91e985c Minor stylistic fixes in glasgow_exts.rst
     2110037 Add isImport, isDecl, and isStmt functions to GHC API
     d4bcd05 rts: Remove space before argument list in ASSERTs
     700c42b Use TypeLits in the meta-data encoding of GHC.Generics
     51a5e68 Refactor ConDecl
     1bd40c8 Move checking for missing signatures to RnNames.reportUnusedNames
     151c4b0 ghc-pkg: don't sort packages unnecessarily
     04e1c27 rts: One more Clang-unfriendly CPP usage
     0933331 Re-use `transformers`'s `MaybeT` rather than our own
     b292720 Remove redundant CPP conditionals
     834f9a4 Get rid of tcView altogether
     2f6e87a Introduce HasGhciState class and refactor use-sites
     9f4ca5a Associate ErrorCall pattern with ErrorCall type
     fd3b845 Make HasDynFlags more transformers friendly
     7a40a6c Update libffi-tarballs submodule to libffi 3.1 (re #10238)
     bb753c5 Rename s/7.12.1/8.0.1/ two minor occurences
     2cfa5db Fix double MaybeT instance
     2106d86 Fix typo sneaked in with fd3b845c01aa26b6e5
     69c3964 docs/glasgow_exts: Use warning admonition
     e792711 users_guide: Show sub-sub-sections in ToC
     aa6ae8a Comments only
     6c794c3 Comments about polymorphic recursion
     d7729c7 An assortment of typos
     7997d6c Refactor GHCi Command type; allow "hidden" commands
     31bddc4 Add missing whitespace in toArgs' error msg
     af77089 Fix DeriveAnyClass (Trac #9968)
     e9ea020 Comments only
     8317893 Improve documentation for DeriveAnyClass
     688069c More typos in comments/docs
     602889a Test Trac #11192
     f4f00c0 Test Trac #11187
     41ef8f7 Make sure PatSyns only get added once to tcg_patsyns
     f7c17c8 T7478: Don't expect broken on Darwin
     5447c20 Mark retc001 as broken on Darwin
     262954c T4801: Update expected allocations on Darwin
     c205aeb Removed colon append operation (fixes #10785)
     b138248 Improved data family export documentation
     ceaf0f4 testsuite: Only run recomp015 on ELF-based platforms
     6e56ac5 Fix infix record field fixity (#11167 and #11173).
     6746549 Add kind equalities to GHC.
     5183109 Revert README.md changes from 6746549772c5
     a6e0394 haddock: Fix submodule commit to point to ghc-head
     b5d5d83 Revert .gitmodules changes from 6746549772c5
     a459451 rm rae.txt
     68f198f Test case for #7961.
     779dfea Test #9017 in polykinds/T9017
     a3c2a26 Frontend plugins.
     1883afb Implement -fwarn-missing-pat-syn-sigs
     3ec8288 Rework the Implicit CallStack solver to handle local lets.
     4935b48 Make -XStrict imply -XStrictData
     3640ae9 Dwarf: Use .short instead of .hword on Darwin
     aaed24a Build system: fix 'make install-strip' in bindist
     9934819 Refactor type families in Template Haskell
     59cc6ed Fix release notes markup
     669c5ed Remove redundant imports
     f48015b configure: add support for 'sh4' (Trac #11209)
     0bf0cf9 Update Cabal submodule
     fcc6b1d Use idiomatic way to tell Autoconf the c compiler
     baed2f5 Don't pass CC= explicitly to `./configure` scripts
     65920c9 Some more typos in comments
     04ab55d Use Cxt for deriving clauses in TH (#10819)
     023f11f Suggest import Data.Kinds when * is out of scope
     419b6c0 Make binds in do-blocks strict when -XStrict (#11193)
     59d3948 Add testcase for #11216
     402bbe6 Add IsString Outputable.SDoc instance
     05fe546 Test #9632 in dependent/should_compile/T9632
     ddde542 DynFlags Remove -fwarn-context-quantification flag
     9017f16 Mention "handle is semi-closed" in error messages
     05a5ebe Fix runghc when $1_$2_SHELL_WRAPPER = NO
     6d9c18c DynFlags: remove Opt_Static
     33742db DynFlags: delete function that doesn't do anything
     f4dd486 Document -XOverloadedLabels
     8e6f9bf TysWiredIn: Fix a comment - Note [TYPE] is in TysPrim
     4c9d1ea Update expected test output for 32 bit platforms
     f4d90f9 Reset process submodule to v1.4.1.0 release tag
     d1ca5d2 Fix formatting complaint from Sphinx
     98cdaee Improve documentation for -XStrict
     b8ca645 Comments on equality types and classes
     6eabb6d Allow recursive (undecidable) superclasses
     947e44f Comment layout only
     e2c9173 Narrow scope of special-case for unqualified printing of names in core libraries
     758e6b3 base: NonEmpty: Fix documentation example
     a701694 Add testcase for #11224
     28638df primops: Mark actions evaluated by `catch*` as lazy
     c1e2553 Expose enabled language extensions to TH
     50c795c Update pretty submodule to v1.1.3.2 release
     3a48e6e Update binary submodule to binary-0.8 snapshot
     2206fa8 Add `-W(no-)xxx` aliases for `-f(no-)warn-xxx` flags
     437ebdd Start using `-W` instead of `-f(no-)warn` in some places
     d36e9e1 GHC.Stack: Fix Haddock markup
     4c7da9c Update haddock submodule
     ab79ed7 Improve detection of `fdatasync(2)` (re #11137)
     11b9ada Synchronize Haddock submodule with master branch
     efaa51d Look through type synonyms in GADT kind signatures
     046b47a Note [The equality types story] in TysPrim
     b35cc1f Update Cabal submodule to latest snapshot
     1687f99 Update transformers submodule to latest v0.5.0.0
     6c9258d Add test for #10897
     7221ad7 GHC doesn't have a way to ask for user-package-db, so Cabal reimplemented it.
     4905b83 Remote GHCi, -fexternal-interpreter
     a6d664c accept output
     dd3837a Fix tests when run in parallel
     acd447e Bump haddock expected performance numbers
     b20a65d testsuite: Add missing LiteralsTest2.hs
     786d528 TcTypeable: Don't use bogus fingerprints when suppress-uniques is enabled
     62e60bb Fix haddock hyperlinker
     27f47cd Fix libffi dependency, and remove redundant LibFFI.hsc
     0cc4aad Build system: Cabalize genapply
     86ad116 Add Shake configuration to configure.ac
     109d847 Build system: Make cGhcRtsWithLibdw flag a proper Bool
     e58a936 rules/haddock: Add EXTRA_HADDOCK_OPTS flag
     4f870f8 Conditionally show plural "s" in warnings
     cab1316 Fix #11232.
     4b161c9 Reify DuplicateRecordFields by label, rather than by selector
     d3dac4e Add -fprint-typechecker-elaboration flag (fixes #10662)
     575f0ad users_guide: Remove extraneous vertical whitespace
     e7f22bf Improve pretty-printing in pprIfaceIdBndr
     e32c2e1 Remove unused T10524.stderr
     89d70f9 Update Cabal submodule
     aee58e1 T9961 allocations crept further upwards
     e2e24f2 Disable recomp015 on ARM
     ece8aff Remove warning-suppression flags for Cabal
     a2f04a2 Testsuite: #10712 is fixed
     9d9c534 Lexer: update outdated comments [skip ci]
     1b6323b IO Handles: update comments [skip ci]
     ae86eb9 Fix tcTyClTyVars to handle SigTvs
     1722fa1 Fix #11230.
     c1bd3d4 Build system: also put scripts in libexecdir/bin
     272e1cc Testsuite: allow spaces in TEST_HC passed in by the user
     116ba5e Build system: allow bindist without docs
     f1fa383 Suppress warnings when compiling primitive and random
     bc436f9 Testsuite: mark frontend01 conditionally expect_broken on #10301
     e0e03d5 Move Data.Functor.(Classes,Compose,Product,Sum) into base
     c5c72aa Update containers submodule to v0.5.7.0 release
     3dd06d5 Random typo fixes
     06cb695 ghci: fix UNREG build (missing fromJust import)
     98ccb72 Testsuite: widen lazy-bs-alloc 3->5%
     8d45ccd Testsuite Windows: fix sigof01m, sigof012m and sigof02dm
     dc8b647 Testsuite Windows: fix ghcpkg03 and ghcpkg05
     34393d9 Documentation for -fexternal-interpreter
     77b7f24 Use `-Wno-tabs` more targetted
     ba80fc6 Fix PowerPC build
     55e9ab8 Update directory submodule to v1.2.5.0 release
     83e4140 Comments only
     ed3bfca Update Win32 submodule to fix 77b7f24543f fallout
     8946ee6 GHCi.Run: Remove redundant language pragma
     53a567c configure.ac: Rename shake/ to build/
     f857d27 configure.ac: Rename build/ to shake-build/
     9d921d6 Test Trac #11248, #11249
     ff752a1 tcCheckSatisfiability: less aggressive superclass expansion
     987426c SrcLoc: Eliminate constructors of RealSrcSpan
     d6b91ea Add test for T11122
     4198b81 ghc.cabal: Backpack directory no longer exists
     0e9a331 LLVM backend: Show expected LLVM version in warnings/errors
     e02a4c2 Fix build for AArch64/Arm64
     9356393 Update terminfo submodule to v0.4.0.2 release
     97281b4 Update terminfo submodule to v0.7.2.2 release
     ccc5a1a Build system: fix 'make sdist'
     d1416c3 Update .mailmap [skip ci]
     5431273 Bump hsc2hs submodule
     b2670fc fix typo
     2cc5b60 Documentation, tests for hsc2hs's new #alignment macro
     b028384 Add -Nmax<n> RTS feature (#10728)
     59de6e8 Add sparc64 a known architecture (Ticket #11211)
     7b8a822 Make ghc-boot Hackage-ready
     64b6a76 Fix typo in 7b8a8222e8f0
     d8c8902 First pass at cleaning up ghci.cabal
     34eaf2b Fix two occurences of `x86_HOST_ARCH`
     bcc213d Update time submodule to v1.6 release
     dd56eb1 Merge new commands from ghci-ng (re #10874)
     59cc32c Update containers submodule to v0.5.7.1 release tag
     3b66960 Remove unused/redundant fields from ghc-cabal.
     f7bd37e aclocal.m4: Fix llc/opt detection code
     1a86413 Update binary submodule to final 0.8.0.0 release
     8d95412 Disallow empty where bindings in pattern synonym declarations.
     44640af Allow as-patterns in pattern synonym declarations.
     29ca4a1 DynFlags: call defaultWays when creating defaultFlags
     62155a6 TcTyClsDecls: use zipWith3M_ instead of generating triplets
     850710a TcTyClsDecls: Add a type annotation
     d8ed20c Add Location to RdrName in FieldOcc
     b225b23 Modify IsString String instance (fixes #10814)
     eb7796f Warn about unused type variables in type families
     edcf17b Move Const to own module in Data.Functor.Const and enable PolyKinds
     6457903 Implement phase 1 of expanded Floating
     9f23dd9 testsuite: Add ClassOperator testcase
     25db56c Minor clean-up to ghc-bin.cabal.in
     e29ee49 Fix AnnDotDot in module export
     99b956e Fix-up GHC 7.12 artifacts
     ee6fba8 Encode strictness in GHC generics metadata
     c8c44fd Maintain cost-centre stacks in the interpreter
     4bb9f88 TcTyClsDecls: Remove invalid comments about list monads
     fd1b5ae testsuite/ClassOperator: This actually should_fail
     a61e717 testsuite: Add testcase for #8316
     eeecb86 Add proper GADTs support to Template Haskell
     55250a6 Rename GHCi's UI modules into GHCi.UI(.*)
     ff3f918 Fix #11256 by not immediately erroring if we can't find a module.
     2dff6c1 Added missing instances for Identity and Const (#11210)
     1fcdcae testsuite/ClassOperator: Mark as compile_fail instead of should_fail
     fb3302c base: Add sections to changelog
     083b700 users_guide: Synchronize relnotes with base changelog
     c12fc2e Update hoopl submodule to final 3.10.2.1 release
     aa7fb9a Fix GHCi segfault in Windows 32bit
     ff92395 Make HsAppsType contents Located
     44de66b Update Cabal submodule to latest snapshot
     ea3f733 Comments only, about coercion holes
     b407bd7 Retain AnnTilde in splitTildeApps
     f975b0b Rework Template Haskell's handling of strictness
     6eabd93 Update stm submodule to v2.4.4.1 release
     29928f2 Fix grouping for pattern synonyms
     f40e122 Fix typechecking for pattern synonym signatures
     51d8330 Remove duplicate T11224 test definition
     7966eea Localize API Annotation in LInjectivtyAnn
     01b0461 Remove another duplicate test
     575a98e Refactor named wildcards (again)
     721d56d APIAnnotations:AnnComma in wrong place in qcnames1
     d3ce417 Tweak comments around UnivCos.
     21b25df CoercionN is not in scope in TyCoRep
     998739d Refactor package flags into several distinct types.
     1faf1fc Implement -hide-all-plugin-packages and -plugin-package(-id), fixing #11244
     3e99980 Update filepath submodule to latest snapshot
     5f08681 - fix tests on OpenBSD which requires _DYNAMIC symbol
     48e0634 Revert "Allow as-patterns in pattern synonym declarations."
     b55ad1b Wibble to error message in Trac #10426
     1963250 Comments and white space
     c069be8 Add a pattern-syn form of PromotionErr
     99eb002 Comments only
     6eb9dc9 Tidy up and comment wildcards in family instances
     ed213ea Test Trac #11274
     7ed0da6 Modify Nmax to maxN Trac #10728
     dab8e34 Delete incorrect *-ws-32 expected test output
     84f6739 - fix gc_thread related compilation failure on Solaris/i386 platform
     f13de71 Fix super-class cycle check
     b37f216 Comments only
     7824870 Fix ASSERT in buildPatSyn, and T10897 test
     380b25e Allow CallStacks to be frozen
     cb989e2 API Annotaions:add name in PatBind Match
     d1e9f82 Update tests for Trac #11039
     f141f41 Test #10432
     7cddcde Docs: -interactive-print should reside in registered package
     3221599 Make testsuite work again with Py3
     353e97a config.mk.in: Disable stripping by default on ARM
     3017cbc ghc-cabal: Bring back TRANSITIVE_DEP_NAMES
     6ec236b Improve SimplUtils.interestingArg
     d990354 Improve the runRW magic in CorePrep
     fcc7498 Improve tracing a bit in CoreSubst
     1af0d36 Refactoring only
     e338376 Fix normalisation of TyCon representations
     48db13d Don't drop last char of file if -osuf contains dot
     2db18b8 Visible type application
     2032635 Testsuite: fix qq005 and qq006 (#11279)
     bc8cac1 Testsuite: mark T7681 expect_broken (#11287)
     5e4e9e0 Fix #11255.
     bd7ab66 Test #11254 in typecheck/should_compile/T11254
     1411eaf Note [TyBinder] in TyCoRep
     52da6bd Have mkCastTy look more closely for reflexivity.
     da69358 Fix #11287.
     b218241 Test #10589 in typecheck/should_compile/T10589
     05e3541 Test #10619 in typecheck/should_fail/T10619
     0fda908 Bump Haddock submodule again
     8bf2d8f Linker: Fix cut-and-paste error in debug output
     422107e T10518: Ensure literal has 64-bit type
     e39d10f testsuite/T8274: Remove 32-bit test output
     fb5d26d testsuite/codegen: Add missing dummy Makefiles
     0b0652f testsuite/T9430: Fix word-size dependence
     b62215d Linker: Reenable Thumb support
     e8672e5 libraries/ghci: Implement mkJumpToAddr for ppc64
     909bbdb Linker(ELF): Fix addProddableBlocks usage
     da5e693 testsuite/joao-circular: Clean up test results
     a3b34b6 Clean up a botched merge.
     d1ebbb0 testsuite/CmmSwitchTest: Mark as broken on 32-bit platforms
     11778f7 Add testcase for getSizeofMutableByteArray#
     07b3be7 integer-gmp: Fix #11296
     bec5350 Adding flags: -ffull-guard-reasoning and too-many-guards
     c8d0af3 RTS: Detect powerpc64le as ELF 64-bit system
     1b00016 The -package flag should select match from right-most package db.
     0054bcd rts/Linker(ARM): Ensure all code sections are flushed from cache
     01299ca Synchronise ghci-package version with ghc-package
     4a10ecb Patch-level increment integer-gmp to 1.0.0.1
     e01aa22 Patch-level increment integer-simple version 0.1.1.1
     c7830bd Update hpc submodule to 0.6.0.3 version
     3aa4a45 Update filepath submodule to v1.4.1.0 rls tag
     295085c Update time submodule to latest snapshot
     bab5109 Make git-committer inferred version-date TZ-invariant
     7fef7fe drop obsolete/redundant OPTIONS pragma [skip ci]
     af92ef3 ghc/Main: Update list of --print modes
     4f69203 Fix panic when using pattern synonyms with DisambiguateRecordFields
     5bb7fec Export some useful GHC API functions.
     8e735fd Fix GEq1 when optimizations are enabled
     2e49c8c users_guide: Move 7.12.1-notes to 8.0.1-notes
     9cb79c5 Update a few references to GHC 7.12
     b093e63 Modify getFullArgs to include program name
     df6cb57 Accept submodule libraries/primitive commit 1af89788d
     fcc7649 Introduce negative patterns for literals (addresses #11303)
     a1e01b6 testlib: Make TyCon normalization Python 2.6-compatible
     adcbc98 Add regression test for #11303
     e4cc19d Update Cabal submodule to latest snapshot
     c6cab9d Remove `cabal07`-test broken by e4cc19de4bdbcc
     34af60c testsuite: normalise away `ld`-warning on AIX
     c06b46d Fix #11305.
     8fcf1e7 Make iserv-bin compatible with GHC version bump to 8.0
     07779c2 T11303: Set maximum heap size
     630303a users_guide/ghci: Fix heading
     3bbc01a Testsuite: mark T7653 with high_memory_usage
     b0fa286 Fix some typos
     e9ab6d5 rts/PrimOps.cmm: fix UNREG profiled build
     d3a79bc rts/Linker.c: mark ia64 as 64-bit ELF, drop unused branches
     0380a95 glasgow_exts.rst: fix code block
     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
     83e899a TysWiredIn: Use map lookup for built-in OccNames
     5446684 DsExpr: Remove unnecessary usage of concatFS


More information about the ghc-commits mailing list