[commit: ghc] wip/T13904's head updated: update to current master again (84c2ad9)

git at git.haskell.org git at git.haskell.org
Mon Sep 24 15:59:14 UTC 2018


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

Branch 'wip/T13904' now includes:

     746ab0b Add an Outputable instance for ListMap
     75bf11c Fix binder visiblity for default methods
     6386fc3 Comments and tc-tracing only
     f959624 Comments only
     d31181b Test Trac #14033
     362339d Fix note references and some typos
     d774b4e Fix #13968 by consulting isBuiltInOcc_maybe
     4a26415 Remove unneeded import
     8e15e3d Improve error messages around kind mismatches.
     c9667d3 Fix #11400, #11560 by documenting an infelicity.
     9a54975 Test #11672 in typecheck/should_fail/T11672.
     ef39af7 Don't tidy vars when dumping a type
     bb2a446 Preserve CoVar uniques during pretty printing
     79cfb19 Remove old coercion pretty-printer
     c2417b8 Fix #13819 by refactoring TypeEqOrigin.uo_thing
     fb75213 Track visibility in TypeEqOrigin
     10d13b6 Fix #11963 by checking for more mixed type/kinds
     ca47186 Document that type holes kill polymorphic recursion
     1696dbf Fix #12176 by being a bit more careful instantiating.
     4239238 Fix #12369 by being more flexible with data insts
     791947d Refactor tcInferApps.
     7af0b90 Initialize hs_init with UTF8 encoded arguments on Windows.
     6b77914 Fix instantiation of pattern synonyms
     af6d225 Remove redundant constraint in context
     b1317a3 Fix ASSERT failure in tc269
     452755d Do not discard insolubles in implications
     ad0037e Add DebugCallStack to piResultTy
     d618649 Error eagerly after renaming failures in reifyInstances
     b3b564f Merge types and kinds in DsMeta
     424ecad Add regression tests for #13601, #13780, #13877
     5e940bd Switched out optparse for argparse in runtests.py
     54d3a1f testsuite: Produce JUnit output
     262bb95 testsuite: Add test for #14028
     274e9b2 Add “BINARY_DIST_DIR” to Makefile
     dac4b9d ByteCodeGen: use byte indexing for BCenv
     2974f81 Fix lld detection if both gold and lld are found
     f134bfb gitmodules: Delete entry for dead hoopl submodule
     d08b9cc configure: Ensure that user's LD setting is respected
     0e3c101 Ensure that we always link against libm
     0e3eacc testsuite: Don't pass allow_abbrev
     121fee9 Remove unnecessary GHC option from SrcLoc
     9e9fb57 Fix hs-boot knot-tying with record wild cards.
     d75bba8 Add rtsopts ignore and ignoreAll.
     84f8e86 Ensure that GHC.Stack.callStack doesn't fail
     9cfabbb Add '<&>' operator to Data.Functor. '<&>' calls '<$>' with flipped arguments.
     d1ef223 Fix #14045 by omitting an unnecessary check
     f839b9d Add regression test for #14055
     7089dc2 Follow-up to #13887, for promoted infix constructors
     9699286 Typofixes [ci skip]
     f2c12c3 Add haddock markup
     49e334c Allow Windows to set blank environment variables
     c6d4219 Clarify comment about data family arities
     2535a67 Refactoring around FunRhs
     4636886 Improve the desugaring of -XStrict
     3ab342e Do a bit more CSE
     af89d68 Reject top-level banged bindings
     7f2dee8 Remove redundant goop
     4fdc523 Use field names for all uses of datacon Match
     2ef973e A bunch of typofixes
     7a74f50 Typofixes [ci skip]
     5a7af95 KnownUniques: Handle DataCon wrapper names
     29f07b1 Allow bundling pattern synonyms with exported data families
     74c7016 rts: Fix "variable set but not used" warning
     b311096 Simplify OccurAnal.tagRecBinders
     c13720c Drop GHC 7.10 compatibility
     36fe21a Enable building Cabal with parsec
     9df71bf Bump unix submodule
     8ef8520 Add .gitmodules entries for text, parsec, mtl submodules
     d74983e Get the roles right for newtype instances
     f68a00c Remove unneeded uses of ImplicitParams
     884bd21 Add the bootstrapping/ dir to .gitignore
     394c391 Add MonadIO Q - by requiring MonadIO => Quasi
     a81b5b0 Remove the deprecated Typeable{1..7} type synonyms
     a267580 Don't warn when empty casing on Type
     6ea13e9 Add forgotten > in Control.Applicative
     e8fe12f Fix string escaping in JSON
     2f29f19 Convert examples to doctests, and add a handful of new ones
     14457cf Fix EmptyCase documentation
     a4f347c Split out inferConstraintsDataConArgs from inferConstraints
     3f05e5f Don't suppress unimplemented type family warnings with DeriveAnyClass
     7d69978 Use NonEmpty lists to represent lists of duplicate elements
     4f1f986 Change isClosedAlgType to be TYPE-aware, and rename it to pmIsClosedType
     0bb1e84 Expand type synonyms during role inference
     c6462ab Add test for #14101
     7c37ffe Point to FunDeps documentation on Haskell wiki
     ad7b945 Fix #14060 by more conservatively annotating TH-reified types
     0a891c8 Properly handle dlerror() message on FreeBSD when linking linker scripts
     ddb870b Don't drop GHCi-defined functions with -fobject-code enabled
     ed7a830 Use a ReaderT in TcDeriv to avoid some tedious plumbing
     21bd9b2 Recognize FreeBSD compiler as Clang.
     a520adc Bump mtl, parsec, text submodules
     441c52d Add Semigroup/Monoid instances to ST monad
     b0285d1 Bump nofib submodule
     e054c5f Bump mtl, parsec, text submodules
     6e9c8eb Bump mtl, parsec, text submodules (again)
     a8da0de Speed up compilation of profiling stubs
     b0ed07f Allow TcDerivInfer to compile with GHC 8.0.1
     38260a9 Fix #13972 by producing tidier errors
     039fa1b Suggest how to fix illegally nested foralls in GADT constructor type signatures
     c948b78 Fix #11785 by making reifyKind = reifyType
     af9f3fa Remove extra ` from "kind-indexed GADTs" doc
     03327bf Handle ListPat in isStrictPattern
     36d1b08 Doctest for Void.absurd
     49ddea9 Sections with undefined operators have non-standard behavior
     43b0c2c Insert missing blank line to fix Applicative doc
     63397cb Add some Monoid doctests
     f762181 Mention the category laws explicitly
     a30187d Convert documentation examples to doctests for ReadP module
     bfa9048 Loads of doc(test)s
     2c0ab47 Add missing initial version for extension doc.
     0e1b6f8 Fix index entries in "separate compilation" section
     3385669 user-guide: fix examples of ghci commands
     69a0f01 rts: Enable USDT probes object on Linux
     82ee71f user-guide: add `:type +d` and `:type +v` in release highlight
     dc42c0d Fix #13399 by documenting higher-rank kinds.
     0385347 Remove unneeded reqlibs for mtl and parsec in the GHC testsuite
     c5605ae Make function intToSBigNat# preserve sign (fixes #14085)
     0286214 testsuite: Add test for #13916
     fee253f CSE.cseOneExpr: Set InScopeSet correctly
     6257fb5 Comments about GlobalRdrEnv shadowing
     118efb0 Restrict Lint's complaints about recursive INLINEs somewhat
     698adb5 Tracing in OccAnal (commented out)
     4c6fcd7 Comments only
     61c4246 Test Trac #14110
     f50e30e Doctests for Data.Tuple
     6267d8c Enable -Wcpp-undef for GHC and runtime system
     cf8ab1c users_guide: Convert mkUserGuidePart generation to a Sphinx extension
     8e5b6ec Add strict variant of iterate
     ee2e9ec Correct incorrect free in PE linker
     1cdceb9 Revert "Add strict variant of iterate"
     34bd43d Fix loading of dlls on 32bit windows
     6982ee9 Fix #14125 by normalizing data family instances more aggressively
     a89bb80 Fix #14114 by checking for duplicate vars on pattern synonym RHSes
     79b259a Fix #13885 by freshening reified GADT constructors' universal tyvars
     8476097 Revise function arity mismatch errors involving TypeApplications
     8fd9599 Make the Read instance for Proxy (and friends) ignore precedence
     afc2f79 Move validate cleaning from distclean to clean
     4717ce8 Fix incorrect retypecheck loop in -j (#14075)
     9afaebe StgLint: Allow join point bindings of unlifted type
     cd5a970 Make law for Foldable.length explicit
     20c7053 Bump haddock submodule
     090d896 fix typo (expreesions -> expressions)
     028645c Fixed a typo in template-haskell documentation
     dbaa9a2 DynFlags: Add inverse of -dno-debug-output
     3625728 Add support for producing position-independent executables
     7463a95 users-guide: Better error messages on incomplete ghc-flag directives
     74af2e7 Typo fixed
     11657c4 Better pretty-printing for CHoleCan
     a211dca Fix defer-out-of-scope-variables
     aeb4bd9 Remove typeKind from Type.hs-boot
     5f3d2d3 CNF: Implement compaction for small pointer arrays
     a0b7b10 Restrict exprOkForSpeculation/case to unlifted types
     407c11b Bottoming expressions should not be expandable
     33452df Refactor the Mighty Simplifier
     8649535 Don't do the RhsCtxt thing for join points
     dd89a13 Comments, plus adjust debug print of TcTyThing(ATyVar)
     a67b66e Add strict variant of iterate
     f135fb2 rts: Fix warnings on aarch64 and clean up style
     80ccea8 rts: Fix references to Note [BFD import library]
     76e59a2 rts: Fix ASSERTs with space before opening paren
     8f19c65 Rip out mkUserGuidePart
     83484a6 Fix two typos in the ImpredicativeTypes user guide
     a055f24 Adjust test suite stats
     682e8e6 Actually bump T12150
     29da01e Make parsed AST dump output lazily
     6e0e0b0 Comments only
     8834d48 Better debug-printing for Outputable TyConBinder
     547e4c0 A bit more -ddump-tc tracing
     6f050d9 Add TcRnMonad.unlessXOptM
     0257dac Refactor bindHsQTyVars and friends
     86e6a5f Small refactoring of meta-tyvar cloning
     4455c86 Use a well-kinded substitution to instantiate
     8eead4d Improve kind-application-error message
     a6c448b Small refactor of getRuntimeRep
     aed7d43 Add HasDebugStack for typeKind
     248ad30 testsuite: Add test for #14128
     db3a8e1 desugar: Ensure that a module's dep_orphs doesn't contain itself
     5266ab9 Remove dll-split.
     895a765 Refactor type family instance abstract syntax declarations
     3c6b2fc Fix decomposition error on Windows
     5f6a820 Add gen-dll as replacement for dll-split
     f86de44 ghc-pkg: Try opening lockfiles in read-write mode first
     a27bb1b base: Add support for file unlocking
     779b9e6 PackageDb: Explicitly unlock package database before closing
     9d57d8c nativeGen: Don't index into linked lists
     651b4dc StgLint: Show type of out-of-scope binders
     a36b34c StgLint: Enforce MultiValAlt liveness invariant only after unariser
     f17f106 StgLint: Give up on trying to compare types
     1561525 HsExpr: Fix typo
     6f1ccaa Add a Note describing #14128
     567dca6 Add some traceRn and (Outputable StmtTree)
     628b666 Add comments to RnTypes
     fca1962 Define and use HsArg
     805b29b Add debugPprType
     3790ea9 Small changes to ddump-tc tracing
     2c133b6 Really fix Trac #14158
     c0feee9 Add missing Semigroup instances to compiler
     b2c2e3e Add missing Semigroup instances in utils/{hpc,runghc}
     dd643bc Improve stm haddocks
     1f052c5 Fix order of PrelRule
     8a1de42 Add testcase for #14178
     f089c32 Remove broken citeseer citation links
     590e737 Update transformers submodule
     6330b0b Document the intricacies of ForallC variable quantification better
     5dd6b13 Disallow bang/lazy patterns in the RHSes of implicitly bidirectional patsyns
     8e4229a Fix #14167 by using isGadtSyntaxTyCon in more places
     0ec4376 Document the Generic(1) laws
     cb3363e Move NonEmpty definition into GHC.Base
     31281a4 testsuite: Fix validation of ways
     b996e12 testsuite: Add test for #14129
     7e5d4a0 Remember the AvailInfo for each IE
     b9ac9e0 Fix egregious duplication of vars in RnTypes
     1300afa get-win32-tarballs: Use bash, not sh
     a4c2ac2 get-win32-tarballs: Use correct `find`
     542f89f Replace hashing function for string keys implementation with xxhash
     cd857dd SetLevels: Substitute in ticks in lvlMFE
     6458b8d base: Update acosh to handle -1::Complex
     c2881a2 StgLint: Show constructor arity in mismatch message
     822abbb eventlog: Clean up profiling heap breakdown type
     24e50f9 rts: Add heap breakdown type for -hT
     0829821 Implicitly bind kind variables in type family instance RHSes when it's sensible
     0cd467b rts: Fix use of #if
     2273353 Clean up opt and llc
     c6726d6 Cleanups, remove commented-out code
     a04cfcf Update xhtml submodule
     fee403f Handle W80 in floatFormat
     d97a6fe Fix typos in diagnostics, testsuite and comments
     055d73c Travis: Boot with ghc-8.2.1, and disable test suite
     8ae263c Make Semigroup a superclass of Monoid (re #14191)
     be514a6 includes/rts: Drop trailing comma
     cb4878f Drop special handling of iOS and Android
     011e15a Deal with unbreakable blocks in Applicative Do
     22f11f1 Bump T783 expected allocations
     cf6b4d1 Remove now redundant CPP
     122f183 Remove now redundant cabal conditionals in {ghc,template-haskell}.cabal
     400ead8 Remove makefile logic for legacy -this-package-key
     dab0e51 Canonicalise Monoid instances in GHC
     346e562 Canonicalise MonoidFail instances in GHC
     838a10f Retire cabal_macros_boot.h hack
     fe35b85 Add testcase for #14186
     fe04f37 Allow CSE'ing of work-wrapped bindings (#14186)
     0ebc8dc Add a test for #14140
     9ff9c35 Check if -XStaticPointers is enabled when renaming static expressions
     dafa012 Add regression test for #14209
     b890e88 rts: Print message before SIGUSR2 backtrace
     d645e44 DriverMkDepend: Kill redundant import
     f8e383f Clarify Data.Data documentation
     91262e7 Use ar for -staticlib
     e62391a [RTS] Harden against buffer overflow
     cbd4911 Make IntPtr and WordPtr as instance of Data.Data typeclass, fix #13115
     8ff11c4 Fix @since annotations in GHC.Stats
     6139f7f Add non-ASCII isLetter True example
     2fe6f6b Option "-ddump-rn-ast" dumps imports and exports too
     f9bf621 Better document TypeRep patterns
     4be195e Simplify Data.Type.Equality.==
     4e22220 Clarify seq documentation
     4cead3c rts: Add regsterCc(s)List to RTS symbols list
     10a1a47 Model divergence of retry# as ThrowsExn, not Diverges
     959a623 No need to check ambiguity for visible type args
     ab2d3d5 More refinements to debugPprType
     3a27e34 Fix subtle bug in TcTyClsDecls.mkGADTVars
     8bf865d Tidying could cause ill-kinded types
     0390e4a Refactor to eliminate FamTyConShape
     a38acda Refactor tcInferApps
     9218ea6 Interim fix for a nasty type-matching bug
     9e46167 Remove unused variable binding
     b6b56dd [RTS] Make -po work
     93da9f9 Add test for Trac #14232
     3b68687 Test #14038 in dependent/should_compile/T14038
     c813d8c Regression test for #12742
     b977630 Test #12938 in indexed-types/should_compile/T12938
     04bb873 Fix #13407 by suppressing invisibles better.
     ecb316c nativeGen: A few strictness fixes
     58f1f73 Bump primitive submodule
     3edbf5c testsuite: Fix dependence on grep behavior in T8129
     89c8d4d Fix #13909 by tweaking an error message.
     e5beb6e Make rejigConRes do kind substitutions
     fa626f3 Fix #13929 by adding another levity polymorphism check
     86e1db7 Test #13938, with expect_broken
     8f99cd6 Fix #13963.
     7b8827a Bump submodule nofib (Semigroup now required)
     f043cd5 Fix name of note
     4340165 Ignore untracked in text, parsec and mtl submodules [skip ci]
     9e227bb Fix missing fields warnings in empty record construction, fix #13870
     f4d50a0 Fix #14228 by marking SumPats as non-irrefutable
     2bfba9e base: Fix mixed tabs/spaces indentation in inputReady.c
     9498c50 Renamer now preserves location for IEThingWith list items
     47a9ec7 Remove dead function TcUnify.wrapFunResCoercion
     b099171 base: Enable TypeInType in Data.Type.Equality
     4ec4ca9 base: Add missing MonadFail instance for strict ST
     60a3f11 Fix pointer tagging mistake
     a83f17e base: Fix missing import of Control.Monad.Fail
     2258a29 testsuite: Fix MonadFail test output for new ST instance
     cdaf5f2 [RTS] Add getObjectLoadStatus
     120c568 Allow opt+llc from LLVM5
     10ca801 Generalise constraint on `instance Monoid (Maybe a)` to Semigroup
     a2f004b Remove redundant/obsolete CPP usage
     1db0f4a Fix unused-given-constraint bug
     6252292 rts/RetainerProfile: Adding missing closure types to isRetainer
     8b007ab nativeGen: Consistently use blockLbl to generate CLabels from BlockIds
     12a92fe OccurAnal: Ensure SourceNotes don't interfere with join-point analysis
     f63bc73 compiler: introduce custom "GhcPrelude" Prelude
     7c7914d Fix Windows build regression due to GhcPrelude change
     28a115e base: fdReady(): Improve accuracy and simplify code.
     c2a1fa7 base: Fix fdReady() potentially running forever on Windows.
     826c3b1 base: Fix fdReady() potentially running forever for Windows Char devices.
     66240c9 base: Fix fdReady() returning immediately for pipes on Windows.
     11c478b rts: Update comment about FreeBSD's unsigned FD_SETSIZE
     b7f2d12 rts: Fix typo in comment
     ba4dcc7 base: Make it less likely for fdReady() to fail on Windows sockets.
     022455f base: Add more detail to FD_SETSIZE related error message
     bbb8cb9 users-guide: Mention changes necessary due to #13391
     3198956 Factor mkCoreApp and mkCoreApps
     7920a7d cmm/CBE: Collapse blocks equivalent up to alpha renaming of local registers
     0aba999 Restore function powModSecInteger
     11d9615 Make zipWith and zipWith3 inlinable.
     02ff705 Add 'stm' package to the global package database
     d7705f2 aclocal.m4: call cygpath on mingw32 only
     ced2cb5 Typofixes (visiblity -> visibility)
     283eb1a Initial CircleCI support.
     cc6be3a Typeable: Allow App to match arrow types
     9e46d88 Typeable: Generalize kind of represented type
     72b00c3 Identify fields by selector when type-checking (fixes #13644)
     acd346e testsuite: Add testcase for #14253
     d86b237 testsuite: Add unboxed sum to T13929
     58a7062 base: Add changelog entry for withTypeable generalization
     063e0b4 Bump base to 4.11.0.0
     1c92083 Also show types that subsume a hole as valid substitutions for that hole.
     ddb38b5 testsuite: Bump allocations of T12150
     9aa7389 cmm/CBE: Use foldLocalRegsDefd
     feac0a3 Reexport Semigroup's <> operator from Prelude (#14191)
     760b9a3 rts: Set unwind information for remaining stack frames
     a9d417d rts: Set unwind information for catch_frame
     1755869 Implement TH addCorePlugin.
     d7b8da1 Fix broken LLVM code gen
     5a8b843 Remove 'stm' from EXTRA_PACKAGES set
     2f10438 Fix build with GhcWithInterpreter=NO
     65943a3 Bump haskeline submodule
     c2373b7 Additional LLVM_TARGET logic.
     d559612 Fix AsmTempLabel
     d7b260f [Semigroup] fix genapply
     9c7d065 Revert "Typeable: Allow App to match arrow types"
     b3ae47c don't allow AsmTempLabel in UNREG mode (Trac #14264)
     3c74a51 Deal with large extra-contraints wildcards
     7721e8e Make pprQuotedList use fsep not hsep
     3b4833a Comments only
     1b476ab Improve type-error reporting
     abed9bf Fix solving of implicit parameter constraints
     0e60cc1 Document how GHC disambiguates between multiple COMPLETE sets
     3804a7e Bump template-haskell to 2.13.0.0
     2b2595e Ensure text mode when calling debug functions
     c839c57 Fix the searching of target AR tool
     abca29f Adds mingw64 to the valid GHC OSs.
     6de1a5a Document Typeable's treatment of kind polymorphic tycons
     d07b8c7 Include original process name in worker thread name (#14153)
     9acbeb5 integer-gmp: Fix style
     d11611f Add NOINLINE pragma to builtinRules
     9738e8b Use SIGQUIT for DWARF backtraces instead of SIGUSR2
     49c1a20 configure: Catch case where LLVM tools can't be found
     65f7d87 configure: Don't hard-code strip tool
     2f8e6e7 testsuite: Expect T13168 to be broken on Windows
     7446c7f A bunch of typofixes
     c41ccbf Omit Typeable from the "naturally coherent" list
     6e7c09d StgCmmMonad: Remove unnecessary use of unboxed tuples
     6246407 primops: Add some notes regarding the meaning of the "type" field
     1d1b991 rts: Inform kernel that we won't need reserved address space
     57372a7 PrelRules: Handle Int left shifts of more than word-size bits
     0ffa396 testsuite: Add test for #14272
     f9f1e38 TcInteract: Remove redundant import of Typeable
     3ec579d Release console for ghci wrapper
     8c23b54 Rules: Show the binder type in the unbound template binder error
     7fb89e8 rts: Silence missing __noreturn__ warning
     1825cbd Switch VEH to VCH and allow disabling of SEH completely.
     8f468fe base: fdReady(): Add note about O_NONBLOCK requirement
     018c40f desugar: Catch levity polymorphism in unboxed sum expressions
     30a1eee rts: Throw proper HeapOverflow exception on allocating large array
     47888fd Revert "Switch VEH to VCH and allow disabling of SEH completely."
     1421d87 Switch VEH to VCH and allow disabling of SEH completely.
     07ddeaf GHC_LLVM_TARGET: Keep android OS
     60b0645 llvm-targets: drop soft-float
     4364f1e Typofixes
     1e9f90a Move check-ppr and check-api-annotations to testsuite/utils
     9bf6310 Add TODO about getMonotonicNSec() wrapping that can no longer happen.
     dddef31 fdReady(): Fix some C -Wconversion warnings.
     03009aa base: fdReady(): Ensure and doc that return values are always -1/0/1
     a10729f configure: Make sure we try all possible linkers
     5935acd mkDataConRep: fix bug in strictness signature (#14290)
     7aa000b Fix #13391 by checking for kind-GADTs
     464396d Fix Raspberry Pi target name
     9c05fc4 user-guide: Document -Weverything
     626f045 Document a law for TH's Lift class
     effcd56 Don't use "character" in haddocks of Char
     c15c427 iserv: Don't build vanilla iserv unless vanilla libraries are built
     e515c7f Allow libffi snapshots
     e299121 Bump submodule nofib again (Semigroup now required)
     00ff023 Travis: Install texinfo
     11a59de CircleCI: Install texinfo
     0e96812 Pretty-printer missing parens for infix class declaration
     c0e6c73 Rewrite boot in Python
     e30d9ca rel-notes: Mention libffi packaging change
     e462b65 Bump libffi-tarballs submodule
     d5e60de user-guide: Fix :since: annotation of -pie and add documentation for -fPIE
     d0c5d8d No libffi docs
     a4ee289 Adds x86 NONE relocation type
     a1fc7ce Comments only
     a8fde18 Fix bug in the short-cut solver
     b1e0c65 Make GHC.IO.Buffer.summaryBuffer strict
     dbbee1b Fix nasty bug in w/w for absence analysis
     cb76754 Suppress error cascade in record fields
     a02039c Add regression test for #9725
     a36eea1 Revert installing texinfo in CI systems
     55001c0 Sync base/changelog.md
     ec9ac20 Add ability to produce crash dumps on Windows
     8d64745 Optimize linker by minimizing calls to tryGCC to avoid fork/exec overhead.
     ef26182 Track the order of user-written tyvars in DataCon
     fa8035e Implement Div, Mod, and Log for type-level nats.
     377d5a2 base: Add missing @since annotations in GHC.TypeNats
     de1b802 genapply: Explicitly specify arguments
     f3f624a Include libraries which fill holes as deps when linking.
     4899a86 Don't pass HscEnv to functions in the Hsc monad
     361af62 base: Remove deprecated Chan combinators
     3201d85 user-guide: Mention COMPLETE pragma in release notes
     3030eee rts: Print newline after "Stack trace:" on barf
     7109fa8 configure: Accept *-msys as a Windows OS in a triple
     d8d87fa Remove m_type from Match (#14313)
     429fafb Add regression test for #14326
     f6bca0c Testsuite update following d8d87fa
     341d3a7 Incorporate changes from #11721 into Template Haskell
     f1d2db6 Fix #14320 by looking through HsParTy in more places
     f337a20 Simply Data instance context for AmbiguousFieldOcc
     e51e565 Split SysTools up some
     7720c29 Tidy up some convoluted "child/parent" code
     ab1a7583 Typos in comments only
     461c831 Minor refactoring
     c81f66c Fix over-eager error suppression in TcErrors
     79ae03a Change "cobox" to "co" in debug output
     3e44562 Delete two unused functions
     f20cf98 Remove wc_insol from WantedConstraints
     9c3f731 Fix #10816 by renaming FixitySigs more consistently
     6869864 Pretty-printing of derived multi-parameter classes omits parentheses
     4bb54a4 Avoid creating dependent types in FloatOut
     13fdca3 Add a missing zonk in TcDerivInfer.simplifyDeriv
     82b77ec Do not quantify over deriving clauses
     15aefb4 Add missing T14325.stderr
     fb050a3 Do not bind coercion variables in SpecConstr rules
     3de788c Re-apply "Typeable: Allow App to match arrow types"
     2be55b8 Delete obsolete docs on GADT interacton with TypeApplications
     4a677f7 Remove section about ApplicativeDo & existentials (#13875)
     8adb84f Fix calculation in threadStackOverflow
     afac6b1 Fix typo
     6aa6a86 Fix typo
     add85cc Fix panic for `ByteArray#` arguments in CApiFFI foreign imports
     e3ba26f Implement new `compareByteArrays#` primop
     5984a69 Override default `clearBit` method impl for `Natural`
     843772b Enable testing 'Natural' type in TEST=arith011
     6cc232a Implement {set,clear,complement}BitBigNat primitives
     71a4235 configure: Fix CC version check on Apple compilers
     fd8b044 Levity polymorphic Backpack.
     5dab544 FreeBSD dtrace probe support
     7e790b3 rts: Label all threads created by the RTS
     8536b7f users-guide: Rework and finish debug flag documentation
     d7f4f41 users guide: Eliminate redundant :category: tags in debugging.rst
     c5da84d users-guide: Fix various warnings
     a69fa54 rts/posix: Ensure that memory commit succeeds
     d6c33da RtClosureInspect: Fix inspecting Char# on 64-bit big-endian
     366182a ghci: Include "Rts.h" before using TABLES_NEXT_TO_CODE
     9e3add9 Flags.hsc: Peek a CBool (Word8), not a Bool (Int32)
     aa98268 updateThunk: indirectee can be tagged
     21b7057 users-guide: Clarify -ddump-asm-regalloc-stages documentation
     6cb4642 Bump ghc-prim to 0.5.2.0 and update changelog
     ed48d13 Simplify, no functionality change
     2f43615 Fix grammaros in comments
     317aa96 Improve user’s guide around deriving
     74cd1be Don't deeply expand insolubles
     5a66d57 Better solving for representational equalities
     aba7786 Typofix in comment
     870020e whitespace only
     20ae22b Accept test output for #14350
     e023e78 Disable -XRebindableSyntax when running internal GHCi expressions
     101a8c7 Error when deriving instances in hs-boot files
     8846a7f Fix #14369 by making injectivity warnings finer-grained
     de8752e Export injectiveVarsOf{Binder,Type} from TyCoRep
     7ac22b7 User's guide: Fix the category of some flags
     3befc1a Bump arcanist-external-json-linter submodule
     1ba2851 Expose monotonic time from GHC.Event.Clock
     13758c6 Added a test for 'timeout' to be accurate.
     098dc97 Give a reference to Foreign.Concurrent.
     b6204f7 Untag the potential AP_STACK in stg_getApStackValzh
     2ca8cf6 Add Functor Bag instance
     afc04b2 Outputable: Add pprTraceException
     c1efc6e Comments and white space
     3acd616 Improve kick-out in the constraint solver
     e375bd3 Update record-wildcard docs
     99c61e2 Add stack traces on crashes on Windows
     bb537b2 nofib submodule: Fix a problem with fasta-c.c
     1e24a24 submodule nofib: Add digits-of-e1.faststdout
     052ec24 submodule nofib: Add digits-of-e2.faststdout
     b10a768 Comments only
     d1eaead Temporary fix to Trac #14380
     671b1ed User’s guide: Properly link to RTS flag -V
     8843a39 Include usg_file_hash in ghc --show-iface output
     3825b7e Remove the 'legroom' part of the timeout-accurate-pure test.
     b62097d Windows: Bump to GCC 7.2 for GHC 8.4
     e888a1f Revert "Windows: Bump to GCC 7.2 for GHC 8.4"
     561bdca Update Win32 version for GHC 8.4.
     f744261 ghc-cabal: Inline removed function from Cabal.
     2e16a57 Revert "ghc-cabal: Inline removed function ..."
     b1ad0bb Revert "Update Win32 version for GHC 8.4."
     61f1b46 Make language extensions their own category in the documentation
     bf83435 typecheck: Clarify errors mentioned in #14385
     bd53b48 Add info about Github pull requests.
     2a4c24e Make layLeft and reduceDoc stricter (#7258)
     980e127 Windows: Update the mirror script to generate hashes and use mirror fallback
     1c15d8e Fix space leak in BinIface.getSymbolTable
     df63668 Performance improvements linear regAlloc (#7258)
     f7f270e Implement `-Wpartial-fields` warning (#7169)
     821adee Fix a bug in 'alexInputPrevChar'
     2c23fff user-guide: Clarify default optimization flags
     4c06ccb base: Enable listToMaybe to fuse via foldr/build
     dbd81f7 Factor out readField (#14364)
     d91a6b6 Declare upstram repo location for hsc2hs
     160a491 users-guide: Disable index node generation
     9ae24bb configure: Add Alpine Linux to checkVendor
     a10c2e6 Don't use $SHELL in wrapper scripts
     355318c Add more pprTrace to SpecConstr (debug only)
     7d7d94f Fix an exponential-blowup case in SpecConstr
     41f9055 ApplicativeDo: handle BodyStmt (#12143)
     acd355a relnotes: Fix a few minor formatting issues
     faf60e8 Make tagForCon non-linear
     922db3d Manual: The -ddump-cmm-* flags had a wrong spelling in the manual
     97ca0d2 simplNonRecJoinPoint: Handle Shadowing correctly
     0e953da Implement a dedicated exitfication pass #14152
     3b784d4 base: Implement file locking in terms of POSIX locks
     cecd2f2 Add -falignment-sanitization flag
     7673561 Turn `compareByteArrays#` out-of-line primop into inline primop
     85aa1f4 Fix #14390 by making toIfaceTyCon aware of equality
     cca2d6b Allow packing constructor fields
     82bad1a A bit more tc-tracing
     1b115b1 Fix typo in accessor name
     ec356e8 Typofix in panic
     1569668 Typofixes in comments
     53700a9 minor wordsmithing
     201b5aa Catch a few more typos in comments
     609f284 Add Note [Setting the right in-scope set]
     af0aea9 core-spec: Add join points to formalism
     29ae833 Tidy up IfaceEqualityTyCon
     1317ba6 Implement the EmptyDataDeriving proposal
     1130c67 PPC NCG: Impl branch prediction, atomic ops.
     b0b80e9 Implement the basics of hex floating point literals
     e0df569 Use proper Unique for Name
     b938576 Add custom exception for fixIO
     36f0cb7 TcRnDriver: Bracket family instance consistency output in -ddump-rn-trace
     cbd6a4d Introduce -dsuppress-stg-free-vars flag
     bd765f4 Fix atomicread/write operations
     d9b6015 Revert "Move check-ppr and check-api-annotations to testsuite/utils"
     51321cf rts/PrimOps.cmm: add declaration for heapOverflow closure
     4353756 CmmSink: Use a IntSet instead of a list
     15f788f llvmGen: Pass vector arguments in vector registers by default
     eb37132 Bump haddock submodule
     3c8e55c Name TypeRep constructor fields
     19ca2ca Deserialize all function TypeReps
     5d48f7c Fix documentation and comment issues
     df479f7 change example from msum to mfilter
     436b3ef Clean up comments about match algorithm a bit.
     f6521e6 testsuite: Bump metrics of haddock.Cabal
     4dfb790 rts/win32: Emit exception handler output to stderr
     6f990c5 cmm/CBE: Fix comparison between blocks of different lengths
     a27056f cmm/CBE: Fix a few more zip uses
     2ded536 Typo in glasgow_exts.rst
     35642f4 Update ErrorCall documentation for the location argument
     8613e61 DynFlags: Introduce -show-mods-loaded flag
     59de290 Update autoconf test for gcc to require 4.7 and up
     66b5b3e Specialise lcm :: Word -> Word -> Word (trac#14424)
     275ac8e base: Add examples to Bifunctor documentation
     7b0b9f6 Squashed 'hadrian/' content from commit 438dc57
     5cee480 Merge commit '7b0b9f603bb1215e2b7af23c2404d637b95a4988' as 'hadrian'
     0ff152c WIP on combining Step 1 and 3 of Trees That Grow
     7d6fa32 Set up Linux, OSX and FreeBSD on CircleCI.
     b0cabc9 Set up AppVeyor, Windows CI.
     6f665cc Sdist -> bindist -> tests
     07e0d0d Revert "Sdist -> bindist -> tests"
     ed18f47 Factor out builds into steps. Address ghc/ghc#83 comments.
     ae7c33f testsuite: Bump haddock.compiler allocations
     7d34f69 relnotes: Clarify a few things
     c1bc923 relnotes: Note enabling of -fllvm-pass-vectorse-in-regs
     93b4820 Revert "WIP on combining Step 1 and 3 of Trees That Grow"
     9f8dde0 Update link to Haskeline user preferences
     bf9ba7b base: Escape \ in CallStack example
     14d885e Merge remote-tracking branch 'github/pr/83'
     21970de Imrpove comments about equality types
     30058b0 Fix another dark corner in the shortcut solver
     2c2f3ce Minimise provided dictionaries in pattern synonyms
     fe6848f Fix in-scope set in simplifier
     438dd1c WIP on Doing a combined Step 1 and 3 for Trees That Grow
     803ed03 Invoke lintUnfolding only on top-level unfoldings (#14430)
     6bd352a Remove left-overs from compareByteArray# inline conversion
     10ff3e3 testsuite: Fix output of T14394
     bdd2d28 Update Win32 version for GHC 8.4.
     9773053 Merge initial Hadrian snapshot
     ce9a677 base: Add test for #14425
     c59d6da base: Normalize style of approxRational
     5834da4 base: Fix #14425
     0656cb4 Update comment in GHC.Real (trac#14432)
     6b52b4c Remove unreliable Core Lint empty case checks
     e6b13c9 testsuite: Add test for #5889
     75291ab Change `OPTIONS_GHC -O` to `OPTIONS_GHC -O2`
     f8e7fec Fix PPC NCG after blockID patch
     5229c43 Squashed 'hadrian/' changes from 438dc576e7..5ebb69ae1e
     506ba62 Merge commit '5229c43ccf77bcbffeced01dccb27398d017fa34'
     f11f252 Windows: Bump to GCC 7.2 for GHC 8.4
     ba2ae2c Adds cmm-sources to base
     426af53 Use LICENSE instead of ../LICENSE in the compiler.cabal file
     5f158bc circleci: Bump down thread count
     86c50a1 Declare proper spec version in `base.cabal`
     e3ec2e7 WIP on combined Step 1 and 3 for Trees That Grow, HsExpr
     0a85190 Fix a TyVar bug in the flattener
     f570000 A bit more tc-tracing
     47ad657 TTG3 Combined Step 1 and 3 for Trees That Grow
     f5dc8cc Add new mbmi and mbmi2 compiler flags
     6dfe982 StaticPointers: Clarify documentation
     5dea62f Adds rts/rts.cabal.in file
     8b1020e RTS: Disable warnings in ffi.h
     ea26162 CLabel: Clean up unused label types
     1aba27a CLabels: Remove CaseLabel
     383016b Add dump flag for timing output
     d9f0c24 rts: Fix gc timing
     d0a641a Allow the rts lib to be called rts-1.0
     3bed4aa Cabalify all the things
     e14945c Adjust AltCon Ord instance to match Core linter requirements.
     ec080ea users_guide: Fix "CancelSynchronousIo" casing
     c1fcd9b Squashed 'hadrian/' changes from 5ebb69a..fa3771f
     07ac921 Pull recent Hadrian changes from upstream
     2f46387 Detect overly long GC sync
     2da7813 Document -ddump-timings
     c729734 configure: Fix incorrect quoting
     12a7444 Adds -ghc-version flag to ghc.
     835d8dd GHC.Prim use virtual-modules
     bb11a2d Relocatable GHC
     74070bb Fix rts.cabal.in
     912a72d Fix T4437
     b8e324a base: Make documentation of atomically more accurate
     7d16d8a Fix #elfi -> #elif; unbreak -Werror.
     ca3700a Rename ghc-version -> ghcversion-file
     606bbc3 Stop generating make files when using hadrian.
     e66913d Bump hsc2hs submodule
     25f36bd Bump haddock submodule
     ddded7e ghc-pkg: Add missing newlines to usage message
     1b1ba9d rel-notes: Fix up formatting in release notes
     d213ee8 CircleCI: Disable artifact collection on OS X
     66d1799 configure: Fix ar probed flags
     0b20d9c base: Document GHC.Stack.CCS internals
     314bc31 Revert "trees that grow" work
     90a819b CircleCI: Add webhook for Harbormaster builds
     2ca2259 Update ANNOUNCE
     763ecac rts: Move libdwPrintBacktrace to public interface
     f376eba rts: Fix inconsistencies in how retainer and heap censuses are timed.
     63e4ac3 Add warn-missing-export-lists
     8a8a79a Update leftover reference to refer to [FunBind vs PatBind]
     dad9864 Remove hadrian sub-dir from .gitignore
     0db4627 Test Trac #14488
     bb2a08e testsuite: Add test for #14257
     23116df cmm: Optimise remainders by powers of two
     eb5a40c base: Remove redundant subtraction in (^) and stimes
     7a73a1c Bump stm submodule
     2d1c671 ErrUtils: Refactor dump file logic
     c11f145 ErrUtils: Ensure timing dumps are always output on one line
     360d740 Squashed 'hadrian/' changes from fa3771fe6b..4499b294e4
     abdb555 Update Hadrian
     341013e Revert "Add new mbmi and mbmi2 compiler flags"
     5fdb858 Fix README
     33cbc9f CircleCI: Perform nightly validation of unregisterised build
     866f669 CircleCI: Try validating LLVM as well
     e2cc106 circleci: Build with Hadrian
     ad57e28 CircleCI: Install lbzip2 and patch
     5e35627 rts/Printer: add closure name entries for small arrays (Fixes #14513)
     30aa643 SysTools: Expand occurrences of $topdir anywhere in a Settings path
     69cd1e9 SysTools: Split up TopDir logic into new module
     599243e DynFlags: Expand $topdir in --info output
     99089fc users-guide: Fix :default: placement
     f209e66 base: fdReady(): Fix timeouts > ~49 days overflowing. Fixes #14262.
     a1950e6 CircleCI: Reenable artifact collection on Darwin
     471d677 Don't complain about UNPACK in -fno-code.
     6282366 Follow symlinks in the Win32 code for System.Environment.getExecutablePath
     b241d6d Add obvious Outputable Integer instance.
     f713be7 RtsFlags: allow +RTS -K0
     00b96b2 boot: Eliminate superfluous output
     4efe5fe Check quantification for partial type signatues
     df1a0c0 typecheck: Consistently use pretty quotes in error messages
     eb86e86 Don't call alex for Cabal lib during GHC build
     e4dc2cd relnotes: Rework treatment of included package list
     54fda25 base: Rip out old RTS statistics interface
     17e71c1 CLabel.labelType: Make catch-all case explicit
     048a913 cmm: Use LocalBlockLabel instead of AsmTempLabel to represent blocks
     16dd532 CLabel: Refactor pprDynamicLinkerAsmLabel
     55e621c nativeGen: Use plusUFMList instead of foldr
     7dc82d6 nativeGen: Use foldl' instead of foldl
     66c1c8e CLabel: More specific debug output from CLabel
     d3b80c7 Cmm: Add missing cases for BlockInfoTable
     030d9d4 CLabel: A bit of documentation
     4c65867 CircleCI: Disallow hscolour 1.24.3
     3c0ffd1 CircleCI: Freeze all packages at fixed index state
     5b3f33b Minor tweaks to codegens.rst
     b6428af Comments only: Trac #14511
     b6a2691 Bump unix submodule
     f246d35 Darwin: Set deployment target
     d672b7f Darwin: Use gmp from homebrew
     6998772 Make use of boot TyThings during typechecking.
     e1fb283 Handle CPP properly in Backpack
     12efb23 Add trace injection
     bc761ad Cache TypeRep kinds aggressively
     1acb922 Make the Con and Con' patterns produce evidence
     cfea745 template-haskell: Rip out FamFlavour
     595f60f Fix ghc_packages
     d6fccfb Bump version to 8.5
     30d6373 rts: fix filename case for mingw32 target
     1ecbe9c utils/hsc2hs: update submodule
     5f332e1 Forward-port changes from GHC 8.2 branch
     fa29df0 Refactor ConDecl: Trac #14529
     e4a1f03 Revert accidental hsc2hs submodule downgrade
     de20440 Refactor kcHsTyVarBndrs
     800009d Improve LiberateCase
     5695f46 Occurrrence analysis improvements for NOINLINE functions
     7733e44 Rip out hadrian subtree
     4335c07 Add hadrian as a submodule
     716acbb Improved panic message for zonkTcTyVarToTyVar
     8b36ed1 Build only well-kinded types in type checker
     8361b2c Fix SigTvs at the kind level
     abd5db6 Only look for locales of the form LL.VV
     21be5bd Fixed misprint 'aqcuired'
     6847c6b Improve Control.Monad.guard and Control.Monad.MonadPlus docs
     00d7132 Add information about irrefutable pattern Syntax to XStrict.
     21cdfe5 Add NOINLINE pragma to hPutStr'
     4bfff7a rts: Don't default to single capability when profiled
     cafe983 Always use the safe open() call
     708ed9c Allow users to ignore optimization changes
     430d1f6 fdReady: Use C99 bools / CBool in signature
     9d29925 base: fdReady(): Return only after sycall returns after `msecs` have passed
     be1ca0e Add regression test for #14040
     a106a20 Minor refactor of TcExpr.tcApp
     e40db7b Detect levity-polymorphic uses of unsafeCoerce#
     321b420 Tidy up of wired-in names
     aef4dee Add missing stderr for Trac #14561
     63e968a Re-centre perf for T5321Fun
     0a12d92 Further improvements to well-kinded types
     6eb3257 Typofix in comment
     6f6d105 Add test for Trac #14580
     b1ea047 Fix an outright bug in the unflattener
     fa1afcd Better tc-trace messages
     eeb36eb typos in local var
     16c7d9d Fix #14135 by validity checking matches
     d4c8d89 users-guide: Consistently document LLVM version requirement
     4a331e6 users-guide: Fix various bits of markup
     6814945 Fix tcDataKindSig
     3910d3e Add some commentary re: fix to #11203
     23b5b80 Add missing case to HsExpr.isMonadFailStmtContext
     1e64fc8 Tiny refactor: use mkTyVarNamePairs
     f1fe5b4 Fix scoping of pattern-synonym existentials
     fb1f0a4 Blackholes can be large objects (#14497)
     0302439 testsuite: Exit with non-zero exit code when tests fail
     8c9906c testsuite: Semigroup/Monoid compat for T3001-2
     244d144 Typos in comments
     a100763 Get rid of some stuttering in comments and docs
     10ed319 Stop runRW# being magic
     ff1544d Rmove a call to mkStatePrimTy
     71f96bb Sync up ghc-prim changelog from GHC 8.2 branch
     1bd91a7 Fix #14578 by checking isCompoundHsType in more places
     9caf40e Fix #14588 by checking for more bang patterns
     9cb289a Remove hack put in place for #12512
     b6304f8 Document ScopedTypeVariables' interaction with nested foralls
     4d41e92 Improve treatment of sectioned holes
     584cbd4 Simplify HsPatSynDetails
     72938f5 Check for bogus quantified tyvars in partial type sigs
     a492af0 Refactor coercion holes
     f5cf9d1 Fix floating of equalities
     bcb519c Typos in comments
     05551d0 Comments only [skip ci]
     fc257e4 Sync `ghc-prim` changelog from GHC 8.2
     c88564d MkIface: Ensure syntactic compatibility with ghc 8.0.1
     6549706 relnotes: Fix typo in pattern synonym example
     e237e1f Bump Cabal submodule
     d7d0aa3 Add GHC 8.6.1 release notes
     02aaeab aclocal.m4: add minimal support for nios2 architecture
     e19b646 Compute InScopeSet in substInteractiveContext
     722a658 Fix #14618 by applying a subst in deeplyInstantiate
     f2db228 Typos in comments [ci skip]
     862c59e Rewrite Note [The polymorphism rule of join points]
     a2e9549 users-guide: Fix markup
     b31c721 Fix sign error in kelvinToC.
     12f5c00 Prevent "C--" translating to "C–" in the User's Guide.
     69f1e49 Reformat Control.Monad.mfilter docs
     a67c264 Add example to Control.Monad.join docs
     4887c30 Improve Control.Monad docs
     27b7b4d Windows: fix all failing tests.
     46287af Make System.IO.openTempFile thread-safe on Windows
     ecff651 Fix #14608 by restoring an unboxed tuple check
     3382ade Rename HEq_sc and Coercible_sc to heq_sel and coercible_sel
     2c7b183 Comments only
     83b96a4 More informative pretty-printing for phantom coercions
     f3a0fe2 Comments about join point types
     1e12783 Tiny refactor around fillInferResult
     3bf910d Small refactoring in Coercion
     112266c White space only
     9e5535c Fix OptCoercion
     bd438b2 Get evaluated-ness right in the back end
     298ec78 No deferred type errors under a forall
     7a25659 Typos in comments
     649e777 Make typeToLHsType produce kind signatures for tycon applications
     6c34824 Cache the number of data cons in DataTyCon and SumTyCon
     954cbc7 Drop dead Given bindings in setImplicationStatus
     e2998d7 Stop double-stacktrace in ASSERT failures
     86ea3b1 comments only
     307d1df Fix deep, dark corner of pattern synonyms
     c732711 Improve pretty-printing for pattern synonyms
     40cbab9 Fix another obscure pattern-synonym crash
     303106d Make the Div and Mod type families `infixl 7`
     a1a689d Improve accuracy of get/setAllocationCounter
     fb78b0d Export typeNat{Div;Mod;Log}TyCon from TcTypeNats
     30b1fe2 Remove a bogus warning
     66ff794 Fix join-point decision
     1c1e46c preInlineUnconditionally is ok for INLINEABLE
     448685c Small local refactoring
     1577908 Fix two more bugs in partial signatures
     dbdf77d Lift constructor tag allocation out of a loop
     f3f90a0 Fix previous patch
     6c3eafb KQueue: Fix write notification requests being ignored...
     b2f10d8 Fix mistaken merge
     e20046a Support constructor Haddocks in more places
     a770226 Fix regression on i386 due to get/setAllocationCounter change
     d1ac1c3 Rename -frule-check to -drule-check and document
     492e604 Kill off irrefutable pattern errors
     3d17f1f Tweak link order slightly to prefer user shared libs before system ones.
     87917a5 Support LIBRARY_PATH and LD_LIBRARY_PATH in rts
     9f7edb9 Fix hashbang of gen-data-layout
     78306b5 CoreLint: typo in a comment
     2feed11 Fix hash in haddock of ghc-prim.
     41afbb3 Add flag -fno-it
     f380115 Parenthesize forall-type args in cvtTypeKind
     1bf70b2 Remove executable filename check on windows
     bc383f2 Simplify guard in createSwitchPlan.
     8de8930 configure: Various cleanups
     cf2c029 Fix quadratic behavior of prepareAlts
     c65104e Typos in comments
     6b1ff00 Fix references to cminusminus.org
     1e14fd3 Inform hole substitutions of typeclass constraints (fixes  #14273).
     8bb150d Revert "Fix regression on i386 due to get/setAllocationCounter change"
     e1d4140 Revert "Improve accuracy of get/setAllocationCounter"
     3335811 cmm: Include braces on default branch as required by the parser
     2a78cf7 Remove unused extern cost centre collection
     575c009 Fix #14681 and #14682 with precision-aimed parentheses
     5e8ea6a testsuite: Add test for #14335
     f855769 Add new mbmi and mbmi2 compiler flags
     765ba65 testsuite: Add testcase for #14670
     0074a08 Fix #14692 by correcting an off-by-one error in TcGenDeriv
     5edb18a tentative improvement to callstack docs
     180ca65 [rts] Adjust whitehole_spin
     4a13c5b Implement underscores in numeric literals (NumericUnderscores extension)
     8829743 Use IntSet in Dataflow
     6c0db98 SysTools: Add detection support for LLD linker
     2671ccc Update Cabal submodule
     24e56eb Bump transformers submodule to 0.5.5.0
     a3cde5f Improve comments about TcLevel invariants
     452dee3 Pass -dsuppress-uniques when running T14507
     f00ddea Allocate less in plus_mod_dep
     d36ae5d Comments about CoercionHoles
     076bdb3 Remove dead code: mkNthCoRole
     2a2e6a8 Comments only
     0636689 Fix the lone-variable case in callSiteInline
     d6e0338 Bump terminfo submodule
     40c753f testsuite: Bump haddock.Cabal allocations due to submodule bump
     0e022e5 Turn EvTerm (almost) into CoreExpr (#14691)
     983e491 testsuite: Add testcase for #12158
     66961dc Haddock needs to pass visible modules for instance filtering
     302aee5 base: Refactor Show ErrorCall instance into proper ShowS style
     52dfb25 Handle the likely:True case in CmmContFlowOpt
     e7dcc70 Add ability to parse likely flags for ifs in Cmm.
     31c260f Add ptr-eq short-cut to `compareByteArrays#` primitive
     cbdea95 Sort valid substitutions for typed holes by "relevance"
     cacba07 Linker: ignore empty paths in addEnvPaths
     bd58e29 Remove Hoopl.Unique
     9a57cfe Option for LINE pragmas to get lexed into tokens
     a55d581 Fix Windows stack allocations.
     59fa7b3 Fix #14719 by using the setting the right SrcSpan
     7ff6023 cmm: Use two equality checks for two alt switch with default
     1cb12ea Bump hadrian submodule
     96d2eb2 Invert likeliness when improving conditionals
     1205629 Add likely annotation to cmm files in a few obvious places.
     5e8d314 Update outputs of T12962, scc003
     47031db A bit more tc-tracing
     e7c3878 Move zonkWC to the right place in simplfyInfer
     0f43d0d More tc-tracing
     efba054 Prioritise equalities when solving, incl deriveds
     e9ae0ca Look inside implications in simplifyRule
     55aea8f testsuite: Mark scc001 and T5363 as broken due to #14705
     370b167 circleci: Add Dockerfile for x86_64-linux
     b37dc23 appveyor: Don't install gcc
     fe6fdf6 testsuite: Fix test output of T14715
     7d9812e testsuite: Fix test output broken by efba054640d3
     5f922fb appveyor: Refactor
     0171e09 Make RTS keep less memory (fixes #14702)
     0bff9e6 Don't add targets that can't be found in GHCi
     be84823 Implement BlockArguments (#10843)
     1a911f2 Sequester deriving-related validity check into cond_stdOK
     382c12d rts: Ensure that forkOS releases Task on termination
     add4e1f Mark xmm6 as caller saved in the register allocator for windows.
     e4ab65b Optimize coercionKind (Trac #11735)
     ced9fbd UnboxedTuples can't be used as constraints
     618a805 Experiment with eliminating the younger tyvar
     db5a4b8 Re-center improved perf for T3064
     efce943 Add -ddump-ds-preopt
     e31b41b Flag `-fdefer-typed-holes` also implies `-fdefer-out-of-scope-variables`.
     2974b2b Hoopl.Collections: change right folds to strict left folds
     c3ccd83 testsuite: Fix scc001 profile output
     7fb3287 Add HasDebugCallStack to nameModule
     4f52bc1 DriverPhases: Fix flipped input extensions for cmm and cmmcpp
     3441b14 integer-gmp: Simplify gmp/configure invocation
     fdf518c Upgrade containers submodule
     217e417 ghc-prim: Emulate C11 atomics when not available
     d8a0e6d Don't apply dataToTag's caseRules for data families
     e5d0101 base: Deprecate STM invariant checking primitives
     50adbd7 cmm: Revert more aggressive CBE due to #14226
     606edbf testsuite: Add testcase for #14754
     d987f71 Improve unboxed sum documentation
     326df5d Bump Cabal submodule
     d2511e3 Compute the union of imp_finsts on the side
     7ad72eb cmm: Remove unnecessary HsVersion.h includes
     1512b63 rts: Fix format of failed memory commit message
     4d1c3b7 rts: Add format attribute to barf
     4c36440 Restore 'It is a member of hidden package' message.
     2987b04 Improve X86CodeGen's pprASCII.
     3cd1305 rts: Use BITS_IN macro in bitmap calculations
     00f1a4a rts: fix some barf format specifiers.
     da46813 testsuite: Add test for #14768
     4aa98f4 Fix utterly bogus TagToEnum rule in caseRules
     41d29d5 Comments only
     6506980 Fix solveOneFromTheOther for RecursiveSuperclasses
     be53d19 Use SPDX syntax in rts/package.conf.in
     059596d rts: fix barf format attribute
     6edafe3 Fix isDroppableCt (Trac #14763)
     f489c12 Simplify Foreign.Marshal.Alloc functions with ScopedTypeVariables
     583f561 Evac.c: remove unused CPP guard
     c9a88db Make ($!) representation-polymorphic
     5957405 Collect CCs in CorePrep, including CCs in unfoldings
     0c9777b Fix tests broken by c9a88db3ac4f1c3e97e3492ebe076f2df6463540
     8936ab6 Raise parse error for `data T where`.
     df449e1 Various documentation improvements
     ec9aacf adds -latomic to. ghc-prim
     d5ff33d Adds `smp` flag to rts.cabal.
     e03ca71 Update .cabal files for Cabal 2.1
     0c2350c rts.cabal.in: advertise profiling flavours of libraries, behind a flag
     8529fbb Get eqTypeRep to inline
     7c173b9 Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv`
     d5ac582 Fix #14811 by wiring in $tcUnit#
     a644dff circleci: Add nightly build using devel2 flavour
     9080466 base: Fix changelog entry for openTempFile
     1ede46d Implement stopgap solution for #14728
     918c0b3 Add valid refinement substitution suggestions for typed holes
     9ff4cce Build Haddocks with --quickjump
     bfb90bc Remove doubled words
     ccda486 Tidy up and consolidate canned CmmReg and CmmGlobals
     c05529c myThreadId# is trivial; make it an inline primop
     4e513bf CBE: re-introduce bgamari's fixes
     d924c17 testsuite: Add newline to test output
     fc33f8b Improve error message for UNPACK/strictness annotations.
     7f389a5 StgLint overhaul
     043466b Rename the types in a GADT constructor in toposorted order
     5b63240 Increase the amount of parallelism in circleci.
     9fc4608 Bump haddock submodule again
     2382bbf Bump process submodule
     fc04a8f Bump filepath submodule
     d20524e Bump pretty submodule
     9ad3fa1 Bump stm submodule to 2.4.5.0
     bd0af2a Bump primitive submodule to 0.6.3.0
     e26d774 Bump parsec submodule to 0.3.13.0
     1ee5abc Bump haskeline submodule to 0.7.4.2
     2cb19b4 Bump text submodule to 1.2.3.0
     71294f3 testsuite: Bump allocations for T1969 and T5837
     eb2daa2 Change how includes for input file directory works
     517c194 Document missing dataToTag# . tagToEnum# rule
     81a5e05 circleci: Skip performance tests
     f511bb5 Add ghc-prim.buildinfo to .gitignore
     f433659 Slight refactor of stock deriving internals
     abfe104 Revert "Move `iserv` into `utils` and change package name
     a032ff7 Add references to #6087
     0a3629a Don't use ld.gold when building libraries for GHCi
     3483423 Comments in Unify, fixing #12442
     bf3f0a6 Update Hadrian submodule
     c969c98 driver/utils/dynwrapper.c: Remove unused variable
     be498a2 RTS: Remember to free some pointers
     cb89ba8 RTS: Remove unused retainer schemes
     3d43fd5 Introduce the flag -dsuppress-timestamps to avoid timestamps in dumps.
     5e5e60d boot: Create GNUmakefiles for libraries
     f57c305 testsuite: Bump allocations for T9630
     ffdb110 Update .gitignore
     da4766c circleci: Simplify Hadrian build
     8c1d6b7 Tiny refactor in Core Lint
     40fa420 Comments only
     e99fdf7 Fix a nasty bug in the pure unifier
     d675a35 Better stats for T5837
     3dec923 Test for Trac #13075 is working now
     51e0a38 Comments only
     b2996f1 Fix test for Trac #13075
     df2c3b3 Build quick flavor and run some tests on Windows
     2756117 Revert "Better stats for T5837"
     b8f03bb Cache the fingerprint of sOpt_P
     e261b85 forkProcess: fix task mutex release order
     8dab89b rts: Note functions which must take all_tasks_mutex.
     f8e3cd3 Only load plugins once
     d8e47a2 Make cost centre symbol names deterministic.
     8c7a155 Move Data.Functor.Contravariant from the contravariant package to base.
     e8e9f6a Improve exhaustive checking for guards in pattern bindings and MultiIf.
     125d151 Add regression test for #12790
     aef2b42 Fix #14817 by not double-printing data family instance kind signatures
     4a0d0d8 Various Windows / Cross Compile to Windows fixes
     1773964 DynFlags: Support British spelling of GeneralisedNewtypeDeriving
     969e747 GHCi info: Use src file for cache invalidation
     6a7e159 Improve missing-home-modules warning formatting
     5c28ee8 Add @since annotations for derived instances in base
     6e4fa81 rts/win32: Assert that the IO manager has been initialised
     bc1bcaa configure: Enable LD_NO_GOLD is set in all codepaths
     7782b47 Add Applicative, Semigroup, and Monoid instances in GHC.Generics
     e4dcebf Adds *-cross-ncg flavour.
     6835702 Permit conversion of partially applied PromotedTupleTs
     ffb2738 Fix #14838 by marking TH-spliced code as FromSource
     5f6fcf7 Compile with `--via-asm` when cross compiling.
     44ba60f doCorePass: Expand catch-all
     821daad Correct default -A value in RTS flag usage info
     a2d03c6 Fix the coverage checker's treatment of existential tyvars
     99c556d Parenthesize (() :: Constraint) in argument position
     4631ceb Bump hsc2hs submodule
     8f0b2f5 Bump Cabal submodule to 2.2
     a9f680f Bump Cabal submodule
     e7653bc Wombling around in Trac #14808
     3d25203 Respect Note [The tcType invariant]
     6ee831f Fix #14888 by adding more special cases for ArrowT
     1c062b7 Simplify rnLHsInstType
     df7ac37 Fixup include of gmp/config.mk to use new location
     f6cf400 `--via-asm` only for windows targets
     cf5bc96 add CCX=$(CXX) to integer-gmp
     ee597e9 Schedule.c: remove a redundant CPP guard
     5bc195a Allow top level ticked string literals
     9bccfcd Correct -g flag description
     64c0af7 cmm/: Avoid using lazy left folds
     08345bd Make accumArray and accum stricter
     1488591 Bump nofib submodule
     488d63d Fix interpreter with profiling
     40c4313 Add perf test for #14052
     b120e64 Add bindist-list.uniq to .gitignore
     d9d4632 Schedule.c: remove unreachable code block
     648cb28 Use docker images with non-root user
     b320ba8 Fix a typo about pattern synonyms in documentation.
     b3bfbed Users Guide: Add that --numa is available on Windows too
     43fbb90 Fix typo in description of -V RTS flag
     d99a65a Add -fexternal-dynamic-refs
     98c7749 Revert "GHCi: Don't remove shadowed bindings from typechecker scope."
     bc95fed Error message and doc improvements for #14335
     ed6f9fb ghc-prim: Reduce scope of Clang sync_fetch_and_nand workaround
     94f0254 ghc-prim: Silence -Wsync-nand warning in atomic.c
     47e2a28 Remove outdated documentation bits concerning -Wmissing-methods
     a25b763 configure: Accept suffix in OpenBSD triple's OS name
     df2ea10 Compacted arrays are pinned for isByteArrayPinned#
     dd3906b UNREG: fix implicit declarations from pdep and pext
     8e34101 Fix a debug print in disassembler (#14905)
     e3ae0eb testsuite: disable T13615 on non-smp targets
     5c804e5 Remove splitEithers, use partitionEithers from base
     02b3dad Bump Cabal submodule
     50972d6 Comment improvements on interpreter breakpoint IO action
     ba57979 Update a comment in Exception.cmm
     152055a Drop GHC 8.0 compatibility
     cb6d858 Slighly improve infix con app pattern errors
     1522cf0 aclocal.m4: allow more GNU/Hurd tuples
     0693b0b aclocal.m4: add OSHurd (debian patch)
     2a3702d Comments and tiny refactor
     5a1ad23 Update test for #5129:
     f9a6d42 Add a build with 32bit Ubuntu container
     2918abf rts: Add --internal-counters RTS flag and several counters
     3d378d9 Also check local rules with -frules-check
     39c7406 Be more selective in which conditionals we invert
     fad822e Improve the warning message of qualified unused imports.
     0db0e46 Get rid of more CPP in cmm/ and codeGen/
     bbcea13 Hoopl: improve postorder calculation
     a00b88b Implement -dword-hex-literals
     b37a87b PPC nativeGen: Add support for MO_SS_Conv_W32_W64
     5241f29 SPARC nativeGen: Support for MO_SS_Conv_W32_W64
     d27336e [RFC] nativeGen: Add support for MO_SS_Conv_W32_W64 on i386
     20cbb01 Improve accuracy of get/setAllocationCounter
     256577f CmmUtils: get rid of insertBlock
     fbd9b88 Implement equalKeysUFM the right way
     9868f91 Turn a TH Name for built-in syntax into an unqualified RdrName
     e358854 Require GHC 8.2 to bootstrap GHC
     c3aea39 Fix #14934 by including axSub0R in typeNatCoAxiomRules
     f748c52 Don't permit data types with return kind Constraint
     fdec06a Update tests for #12870 to pass with a slow run of the testsuite.
     98c1f22 Bump array submodule
     960cd42 Fix typo in user guide about ConstraintKinds
     82e8d1f Fix typo
     b3b394b gen-data-layout.sh: Use bash array for readability
     2d4bda2 rts, base: Refactor stats.c to improve --machine-readable report
     afad556 Add -flate-specialise which runs a later specialisation pass
     6a71ef7 Bump autoconf version bound to >= 2.69
     d718023 relnotes: Fix parsing of Version: field from Cabal file
     60aa53d configure: Accept version suffix in solaris name
     57001d9 Update T5129 test:
     0a778eb Revert "rts, base: Refactor stats.c to improve --machine-readable report"
     abaf43d Fix seq# case of exprOkForSpeculation
     49ac3f0 Fix #14869 by being more mindful of Type vs. Constraint
     411a97e Allow as-patterns in unidirectional patttern synonyms
     3446cee Fix two obscure bugs in rule matching
     efc844f Fix over-eager constant folding in bitInteger
     034c32f Improve shortOutIndirections slightly
     d5577f4 Special-case record fields ending with hash when deriving Read
     affdea8 Allow PartialTypeSignatures in standalone deriving contexts
     ceb9147 Support adding objects from TH
     7bb1fde testsuite: Add test for #14931
     10566a8 Support iOS variants elsewhere when configuring
     9893042 Fix two pernicious bugs in DeriveAnyClass
     cf80995 Add Note [BLACKHOLE points to IND]
     f7bbc34 Run C finalizers incrementally during mutation
     fb462f9 Fix panic on module re-exports of DuplicateRcordFields
     c16df60 document: fix trac issue #14229
     9a00bfb rts/RetainerProfile: Dump closure type if push() fails
     0703c00 testsuite: Add test for #14925
     20f14b4 Fix #14916 with an additional validity check in deriveTyData
     0cbb13b Don't refer to blocks in debug info when -g1
     a3986d7 Fix scoped type variables in TH for several constructs
     41db237 llvmGen: Pass -optlo flags last to opt
     20ae19f base: Fix Unicode handling of TyCon's Show instance
     ecfb4d3 Add new debugging flag -dinline-check
     efd70cf Add unaligned bytearray access primops. Fixes #4442.
     d152dab Add a job running on Fedora
     60e29dc circleci: Bump Hackage index state
     f0b258b rts, base: Refactor stats.c to improve --machine-readable report
     41c1558 Make it evident in types that StgLam can't have empty args
     97e1f30 Fix compilation stopper on macOS with -Werror
     e3dbb44 Fix #12919 by making the flattener homegeneous.
     b47a6c3 Fix performance of flattener patch (#12919)
     f13a0fc Comments only
     1fce2c3 Avoid quadratic complexity in typeKind
     71d50db Minor refactor and commments
     9cc6a18 White space only
     a7628dc Deal with join points with RULES
     3ebf05f Fix the test for #13938
     8cfd2e4 configure: Throw error if OS is found to be msys
     d5c4d46 CmmPipeline: add a second pass of CmmCommonBlockElim
     d1fb583 testsuite: Add test for #14965
     ab9e986 rts: Fix profiled build after D4529
     b58282a More format string fixes
     88f06d4 rts: One last formatting string fix
     bf2b9cc Update Note [Documenting optimisation flags]
     d06a5a9 Rename CI docker images
     0951e03 Full AppVeyor build with tests
     0017a7b Fix syntax in -flate-specialise docs
     c00b6d2 Update a few comments regarding CAF lists
     afb686a printClosure: slightly improve MVAR printing
     4de585a Remove MAX_PATH restrictions from RTS, I/O manager and various utilities
     ca535f9 testsuite: allow accepting of fine grained results [skip ci]
     faec8d3 Track type variable scope more carefully.
     ef44382 Apply the interim fix for #14119 to liftCoMatch
     3eaa55d Apply Note [EtaAppCo] in OptCoercion to another case
     1845d1b Clarify comments around dropping Derived constraints
     07abff7 Test #14884, #14969
     9187d5f Allow unpacking of single-data-con GADTs
     5ab8094 SpecConstr: accommodate casts in value arguments
     ddf8955 Mark test as expected to pass.
     d8d4266 Fix #14991.
     72b5f64 Fix accidental breakage in T7050
     c2f90c8 Remove unused bdescr flag BF_FREE
     891ffd5 Comments only, about exitifcation
     54acfbb base: Add dependency on GHC.Integer in a few boot files
     875e59d testsuite: Accept output for T12593
     718a018 Fix #14238 by always pretty-printing visible tyvars
     5819ae2 Remove HasSourceText and SourceTextX classes
     d386cd6 Collect build artifacts with S3
     26cfe29 Document SumTyCon
     7bd7fec Improve documentation for refineDefaultAlt
     605ae8d Run tests after artifact collection
     a5bfb7e CoreUtils.filterAlts: Correct docs
     8b823f2 docs(Data.Function): fix and augment `on` annotation
     b14c037 Some cleanup of the Exitification code
     48f55e7 Bump template-haskell to 2.14.0.0
     1aa1d40 Restore Trees That Grow reverted commits
     ae0cff0 CSE: Walk past join point lambdas (#15002)
     a1fcdf3 Add a forgotten newline in a debug print
     b2eb9ad Fix GHC collector flavor for Fedora job (Circle CI)
     3f59d38 Add test case for #15005
     635a784 Remove PARALLEL_HASKELL comments
     5161609 testsuite: Add test for negative sqrts (#10010)
     d5f6d7a rts/RetainerProfile: Handle BLOCKING_QUEUES
     81e7980 Minor typofix in LoadArchive.c
     2534164 Move gmp/config.mk.in to config.mk.in, fix #14972
     c054162 Revert "Fix #14838 by marking TH-spliced code as FromSource"
     7bb7f99 Discard reflexive casts during Simplify
     3cfb12d In Exitify, zap idInfo of abstracted variables (fixes #15005)
     a323f21 Move T14925.stdout to its correct location, remove expect_broken
     ed57a34 Schedule.c: remove unused code
     74e768e Schedule.c: remove some unused parameters
     270e3e9 No need for sortQuantVars in Exitify after all
     111556f Remove fs files from rts install-includes.
     4e6da0f Revert "Remove fs files from rts install-includes."
     5417c68 Remove fs files from rts install-includes.
     b138694 TTG for HsBinds and Data instances Plan B
     c4814ab Bump version numbers: base-4.11.1.0, integer-gmp-1.0.2.0
     f02309f users-guide: Update release notes and language extensions
     78ff6e5 Revert "CmmPipeline: add a second pass of CmmCommonBlockElim"
     a303584 Fix processHeapClosureForDead CONSTR_NOCAF case:
     120a261 Update JMP_TBL targets during shortcutting in X86 NCG.
     f78df87 Fix rts.cabal.in
     6f62303 Remove unused function: mkFunCos
     7613a81 Fix #9438 by converting a panic to an error message
     6a78a40 Use newtype deriving for Hoopl code
     9430901 Revert "Fix processHeapClosureForDead CONSTR_NOCAF case:"
     ce27c7d Correct FixIOException's @since annotation retroactively
     00b8ecb Declare `catchRetry#` lazy in its first argument
     3c7f9e7 Make shortcutting at the asm stage toggleable and default for O2.
     9e89092 Omit ways depending on rts flags for #12870 related tests.
     4b831c2 Configure option to disable dtrace
     fea04de Enhanced constant folding
     09128f3 users guide: Note improved constant folding in 8.6 release notes
     0e37361 Revert "Enhanced constant folding"
     90283b5 rts: Comment wibbles
     4d30bc8 Remove markSignalHandlers
     7889659 Minor comments in CSE
     fe325d3 Comments only
     4a16804 Fix markup in the UNPACK pragma section of the user's guide.
     cab3e6b Proper safe coercions paper link
     5d76846 Introduce a $tooldir variable for nicer toolchain detection on Windows
     447d126 Fix #14710 with more validity checks during renaming
     2fdfe05 Bump unix submodule to version 2.8.0.0
     19ddd04 Add a test case from the nested CPR work
     803178a users-guide: Override mathjax_path
     48b8842 rts: fix format arguments for debugBelch calls on 32-bit systems
     f7f567d Add a test for #14815:
     cac8be6 Better error message for empty character literal, for Trac #13450.
     b08a6d7 Fix #15012 with a well-placed use of Any
     8f19ecc Bump base to version 4.12.0.0
     d9d8015 testsuite: Fix `./validate --slow`
     3c3e731 parsec: Make version hack compatible with Windows
     cbd73bb configure: Use -Werror to check for existence of -no-pie
     8fa688a boot: Fix computation of TOP
     257c13d Lint types in newFamInst
     a26983a Fixes isAlphaNum re. isAlpha/isNumber and doc fix (trac issue #10412)
     b41a42e Bump transformers submodule
     2fbe0b5 Caching coercion roles in NthCo and coercionKindsRole refactoring
     8b10b89 Inline wrappers earlier
     f6db0b2 comments only
     430e6fe Remove broken top-level shell.nix
     698db813 Fix implementation of rnIfaceBndr
     da74385 base: Add a test for T10412
     2a5bdd9 Remove unnecessary check in simplCast
     98b0c3f s/traverse_weak_ptr_list/traverseWeakPtrList in comments [skip ci]
     ea01daf rts: Use g0 for &generations[0]
     c7c53c6 Remove a outdated comment [skip ci]
     bfc1fc2 Typo fix in scavenge_one comment [skip ci]
     f19b07a users-guide: Fix up formatting in 8.6 release notes
     2eafd76 coercion: Improve debugging output
     f04ac4d Add testcase for #15050
     e732210 ghc-prim: Refactor and document __sync_fetch_and_nand workaround
     1126e69 testsuite: Fix overflow in T13623 on 32-bit machines
     ec9638b testsuite: Fix T4442 on 32-bit architectures
     acb7361 Stable.c: minor refactoring, add/update some comments
     625eea9 Update Hadrian submodule
     3d38e82 Do not unpack class dictionaries with INLINABLE
     693857f Comments only
     705dcb0 Refactor in OccurAnal
     313720a Rename a local variable
     c3823cb TTG : complete for balance of hsSyn AST
     56bbe1e Add missing stdout file for T14955
     512f503 Minor refactoring in Exitify
     69119b2 Comments only: the FVAnn invariant
     0c01224 Refactor tcExtendLocalFamInst a bit
     08003e7 Make out-of-scope errors more prominent
     6da5b87 Better linting for types
     4e45ebe Add test case for #15108
     07cc603 Don't crash when pretty-printing bad joins
     d4cc74f Preserve join-point arity in CoreOpt
     b5739bd rts: Don't disable formatting warning in RetainerSet.c
     6212d01 testsuite: Bump performance meterics due to 3d38e8284b73
     260e23b rts: Add -hT to the rts usage message
     b7b6617 rts: Allow profiling by closure type in prof way
     60f9e46 Exitify: Do not trip over shadowing (fixes #15110)
     dc655bf errorWithoutStackTrace: omit profiling stack trace (#14970)
     4cb5595 storageAddCapabilities: fix bug in updating nursery pointers
     198db04 Set arity for absentError
     6742ce2 Test Trac #15114
     5de0be8 Add regression tests for #14904
     358b508 Compute DW_FORM_block length correctly; also fixes #15068
     e34e30e Warn against using Data.Monoid.First
     90589a9 document the plan for removing Data.Semigroup.Option
     cf35ab9 minor improvement to wording of warning against First. Add warning against Last
     107d2cb Don't shadow "result" in JUnit driver
     1ad0277 CircleCI: Save test results as JUnit XML
     75361b1 Fix NUMA support on Windows (#15049)
     6132d7c Correctly add unwinding info in manifestSp and makeFixupBlocks
     866525a Move the ResponseFile module from haddock into base
     721e826 GHCi: Improve the error message for hidden packages
     6462d90 rts: Throw better error if --numa is used without libnuma support
     79c4f10 Enable warning flags to safe-guard against regressions in `base`
     5697432 Normalize T14999 test output some more
     33de71f Simplify callSiteInline a little
     b750dcc testsuite: Bump T9630 allocations as a result of 33de71fa06d0
     56e8c6f Update docker images to use GHC 8.4.2 and cabal-install-2.2
     13e8bc0 Fix typo in user guide about promoted list
     49f5943 rel-notes: Note that -hT is now allowed
     426ae98 Split TrieMap into a general (TrieMap) and core specific (CoreTrieMap) module.
     361d23a Normalize the element type of ListPat, fix #14547
     0f046aa testsuite: Add test for #15067
     cb1ee7e Do not supply `-mcpu` if `-optlc` provides `-mcpu` already.
     418881f Use unsafeInsertNew to create timers in TimerManager
     6243bba Add 'addWordC#' PrimOp
     be580b4 Add test for invertability of `Floating` methods.
     d814dd3 Add hyperbolic functions to test of Float-inverses
     3ea3341 Stable area hyperbolic sine for `Double` and `Float`.
     46548ed base/changelog: Note stabilization of asinh (#14927)
     7271db4 testsuite: Bump T5631 expected allocations
     875b61e printStackChunk: recognise a few more ret frames
     61b245a Small refactoring in Exitify
     5b3104a Used named fields for DataDeclRn
     aa03ad8 Simplify the kind checking for type/class decls
     37acca7 users-guide: Move discussion MAX_PATH out of release notes
     280de0c Revert "Normalize the element type of ListPat, fix #14547"
     981bf47 Normalize the element type of ListPat, fix #14547
     849547b Revert "Normalize the element type of ListPat, fix #14547"
     ba6e445 Normalize the element type of ListPat, fix #14547
     5fe6aaa Add -fghci-leak-check to check for space leaks
     b2ff5dd Fix #15038
     e5bb515 rts: remove unused round_up_to_mblocks function
     87e169a Revert "Add -fghci-leak-check to check for space leaks"
     40a76c9 BlockAlloc.c: reuse tail_of function
     cb5c2fe Fix unwinding of C -> Haskell FFI calls with -threaded
     3781034 Expand $tooldir in ghc --info output
     2323ffd Adds CTRL-C handler in Windows's timeout (trac issue #12721)
     bec2e71 Revert "Fix unwinding of C -> Haskell FFI calls with -threaded"
     78db41e Use correct source spans for EmptyCase
     00049e2 Emit info-level log message when package envs are loaded
     6ab7cf9 Simplify -ddump-json implementation
     9039f84 base: Fix handling of showEFloat (Just 0)
     f0212a9 TcInteract: Ensure that tycons have representations before solving for Typeable
     2188427 Bump array submodule
     7c665f9 Refactor LitString
     eb39f98 Fix a few GCC warnings
     2828dbf Fix changelog message for asinh
     cdbe00f Remove unused things from utils/Digraph
     d4abd03 rts: Compile with gcc -Og
     30c887d GHCi: Include a note in the hint to expose a hidden package
     48dee7c Clarify what the FFI spec says
     bf6cad8 Add note documenting refineDefaultAlt
     21e1a00 Fix #14875 by introducing PprPrec, and using it
     cf88c2b ghc-pkg: Configure handle encodings
     8f3c149 Add support for opting out of package environments
     ca3d303 Fix another batch of `./validate --slow` failures
     b713986 Improve some Foldable methods for NonEmpty
     6d57a92 utils/fs: use <sys/stat.h>, not <sys\stat.h>
     e408d03 Fix #14973
     1e27209 Revert "rts: Compile with gcc -Og"
     d92c755 Fix performance regressions from #14737
     79bbb23 rts: export new absentSumFieldError from base
     f49f90b Tidy up error suppression
     df6670e testsuite: Fix expected allocations of T9020 and T12425
     9dbf66d Revert "Simplify callSiteInline a little"
     45ad0c3 Ensure that RTS cabal file reflects dependency on libnuma
     1154c9b More explicit comment on switch in registerDelay
     af986f9 testsuite: Disable T14697 on Windows
     01b15b8 Calling GetLastError() on Windows for socket IO (trac issue #12012)
     bb338f2 Algebraically simplify add/sub with carry/overflow
     bb3fa2d Less Tc inside simplCore (Phase 1 for #14391)
     a18e7df Force findPtr to be included in the binary
     eb8e692 An overhaul of the SRT representation
     fbd28e2 Allow CmmLabelDiffOff with different widths
     2b0918c Save a word in the info table on x86_64
     838b690 Merge FUN_STATIC closure with its SRT
     01bb17f Make finalizers more reliable.
     3310f7f InfoTables: Fix #if uses introduced by D4634
     126b412 Add pprTraceM to Outputable as analog to traceM.
     99f8cc8 Fix #15039 by pretty-printing equalities more systematically
     4ffaf4b Improve numeric stability of numericEnumFrom for floating numbers
     0c7db22 Fix #15073 by suggesting UnboxedTuples in an error message
     f2d27c1 Comments and refactoring only
     b701e47 Update Cabal submodule
     5f15d53 Add /* fallthrough */ to fix -Wimplicit-fallthrough warning
     f27e4f6 Fix GHCi space leaks (#15111)
     5d3b15e Fix unwinding of C -> Haskell FFI calls with -threaded (2nd try)
     819b9cf Add regression tests for #11515 and #12563
     797a462 Comments only
     efe4054 Tiny refactor
     2bbdd00 Orient TyVar/TyVar equalities with deepest on the left
     5a7c657 Debug tracing only
     ae292c6 Do not unify representational equalities
     d78dde9 Fix retainer profiling after SRT overhaul
     c617c1f base: Add Foldable and Traversable instances for Alt
     9171c7f base: Fix typo
     c4219d9 Another batch of './validation --slow' tweaks
     12deb9a rts: Fix compaction of SmallMutArrPtrs
     ec22f7d Add HeapView functionality
     e1fd946 ghc-prim: Bump version
     1cdc14f ghc-pkg: recompute `abi-depends` for updated packages
     f2ce86c Do better sharing in the short-cut solver
     5f3fb71 Fix perf numbers for #15164
     b7e80ae Remove TcType.toTcType
     57858fc Make dischargeFmv handle Deriveds
     af0757d Check for type families in an instance context
     97121b6 Revert "ghc-pkg: recompute `abi-depends` for updated packages"
     db6085b Improve performance of CallArity
     928f606 Typo in comments
     49a832d Remove special case from TcTyVar level check
     86bba7d Add missing check to isReflCoVar_maybe
     d191db4 Don't expose strictness when sm_inline is False
     a32c8f7 Use dischargeFunEq consistently
     d424d4a Fix a bug in SRT generation
     bf10456 Disable the SRT offset optimisation on MachO platforms
     49691c4 testsuite: Bump OS X performance numbers
     1879d9d Check for mismatched class methods during typechecking
     979f085 Clean up the conflicting data family instances error message
     5ca623a Minor typos
     5b6ef59 Add -fghci-leak-check to check for space leaks
     c618732 isDllName: use Opt_ExternalDynamicRefs, not WayDyn
     40d5b9e Comments about the substition invariant
     11eed2f testsuite: Don't rely on find command in T15038
     72835ff Add regression test for #11766
     00f7e28 Add regression test for #14172
     9ed7e8d Add regression test for #14246
     6a9b9b4 Mark #12447's test case as expected to pass
     b67e8a3 base: Introduce Data.Monoid.Ap
     a5446c4 Update GHC.Stats docs
     4778cba Fix 32 bit windows build
     60fb2b2 Clean up Windows testsuite failures
     f804811 Factor stack chunk printing out of printTSO
     25f01db Typofixes [ci skip]
     6848a99 remove dead maybeIsLFCon
     36656b9 Typofix in manual [ci skip]
     d14b1ec Minor refactoring
     9969863 Use a less confusing type variable in a few types
     576078a base: Improve zip documentation
     5e91cde Unmask readMVar in readChan
     fa2d7e1 testsuite: Fix incorrectly capitalized True in testlib.py
     1245835 testsuite: Use /usr/bin/env instead of /bin/bash
     929bbe4 Handle TREC_CHUNK in printClosure
     857005a Move printMutableList to Printer.c next to other printers
     e4003b6 llvm-targets: Add versioned ARM targets
     bdfc85b Fix validate for GHCi without TABLES_NEXT_TO_CODE
     bd429dc Update repository sub-dir for ghc-heap in ghc-heap.cabal.in
     2ea93a7 Improve the documentation of lexically scoped type variables
     8fe99c7 Remove incorrect comment
     9ded0d6 Delete duplicate definition of fingerprintByteString
     c65159d T14732 now passes with the profasm way
     49e423e Put the `ev_binds` of main function inside `runMainIO`
     34464fe rts: Don't madvise if mmap failed
     9aac442 Define MCoercion type
     a4ae199 Extract hard-coded LLVM opt flags into a file
     b876c1b users-guide: Point out GNTD may require additional extensions
     e0b44e2 Improved Valid Hole Fits
     1d1e2b7 Implement "An API for deciding whether plugins should cause recompilation"
     64fd0fa ghc-heap: Add dependency from GHC.Exts.Heap.Closures to InfoTableProf
     5030109 testsuite: Fix hashbangs
     730781b rts/posix: Use less aggressive backoff schedule for heap reservation sizing
     b57a54f SplicePat's should not trip -Wunused-pattern-binds
     91a82de testsuite: Make T3234 more robust
     15ece72 base: Improve documentation of indexArray#
     533d345 configure: Make sphinx-build version test work on recent versions
     471b2a0 users-guide: Fix various issues in debugging flags section
     d1beebb Make HsDocString a newtype of ByteString
     21a9fb5 base/TimerManager: Clamp timer expiration time to maxBound
     b592bd9 dead strip dylibs on macOS
     5748c79 Change jump targets in JMP_TBL from blocks to X86.JumpDest.
     9921f5b Cleanups [ci skip]
     9fd4ed9 UNREG: mark SRT as writable in generated C code
     bd43378 Optimizations for CmmBlockElim.
     c983a1d testsuite: Add test for #15186
     f0c1eb8 Conservatively estimate levity in worker/wrapper
     13a8660 Add llvm-target for powerpc64le-unknown-linux
     faee23b vectorise: Put it out of its misery
     9ea4596 C codegen: print details of pprStatics panics
     a122d4f rts: Rip out support for STM invariants
     e0f33a6 testsuite: Don't assume location of bash
     7272566 Bump version of stm submodule back to 2.4
     c2783cc Extended the plugin system to run plugins on more representations
     ac91d07 Fix #13777 by improving the underdetermined CUSK error message
     18cb4f5 Check for singletons when creating Bag/OrdList from a list.
     21e9d4f Fix #15214 by listing (~) in isBuiltInOcc_maybe
     2627377 rts: Query system rlimit for maximum address-space size
     1626fe6 Handle abi-depends correctly in ghc-pkg
     5b82ee6 Remove ~# from surface syntax
     4d80044 Fix a bad interaction between GADTs and COMPLETE sets
     08073e1 Turn "inaccessible code" error into a warning
     9b7eec8 tcExtendTyVarEnv2 changed to tcExtendNameTyVarEnv
     f68c2cb Allow aligning of cmm procs at specific boundry
     1f88f54 Improve exhaustiveness checking for literal values and patterns, fix #14546
     6128037 Fix typo in OverloadedLabels docs
     90e99c4 Add tests for #8128 and #8740
     b564eb7 testsuite: Mark T14547 as broken
     4dd1895 testsuite: Really mark T14547 as broken
     554bc7f Provide `getWithUserData` and `putWithUserData`
     0e5d2b7 Do a late CSE pass
     9d600ea Expand type synonyms when Linting a forall
     a1a507a Refactor SetLevels.abstractVars
     c560f38 Bump stm and haskeline submodules
     d8efb09 Fix broken test T14547.
     36091ec Document the fact that cmm dumps won't show unreachable blocks.
     7df5896 Implement QuantifiedConstraints
     1a61c6b Add Outputable instance for HsArg
     97cea31 Improve extendTvSubst assertion
     aa77c60 Also suppress uniques in cmm dumps with `-dsuppress-uniques`.
     85309a3 Serialize docstrings to ifaces, display them with new GHCi :doc command
     8ed8b03 Introduce DerivingVia
     4075656 Rename some mutable closure types for consistency
     455477a rts: Reuse dbl_link_remove in a few places
     d964b05 Let the simplifier know that seq# forces
     635a59a Do not scavenge SMALL_MUT_ARR_PTRS_CLEAN in mut_lists
     7f45906 Comments only
     c16382d Remove ad-hoc special case in occAnal
     1508600 testsuite: Fix dynamic-paper stderr file
     f741711 Update hadrian submodule
     64c71ce Don't use unsafeGlobalDynFlags in optCoercion
     db4f064 WorkWrap: Rip out unsafeGlobalDynFlags usage in mkWwInlineRule
     e7678d6 Index arrays more eagerly
     767536c Fix unparseable pretty-printing of promoted data cons
     efea32c Check if both branches of an Cmm if have the same target.
     0361fc0 Move 'HsBangTy' out in constructor arguments
     5026840 testsuite: Add test for #15232
     569c16a Fix #15243 by fixing incorrect uses of NotPromoted
     bc9a838 Document #15079 in the users' guide
     04e29fc testsuite: Skip T13838 in ghci way
     5926b6e Don't expose (~#), (~R#), (~P#) from GHC.Prim
     3397396 Fix #15236 by removing parentheses from funTyConName
     838cb53 rts: Fix reference to srt_bitmap in ASSERT in RetainerProfile
     fa34ced Rename dataConRepNameUnique to dataConTyRepNameUnique
     dc8c03b Run typeCheckResultAction and renamedResultAction in TcM rather than Hsc
     200c8e0 Allow Haddock comments before function arguments.
     6fbe5f2 Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv`
     297879a Add support for FreeBSD arm
     d66ca01 typecheck: Don't warn about "redundant" TypeError constraints
     838aeb9 Run Linux slow validate nightly on Circle CI
     40db277 Fix `print-explicit-runtime-reps` (#11786).
     a9eb645 users guide: Fix spelling
     9976bed rts: Handle SMALL_MUT_ARR_PTRS in checkClosure
     bb83831 Do not omit T4030 in GHCi mode
     e1f74aa users-guide: Spelling and style pass over QuantifiedConstraints docs
     229789a testsuite: Bump performance metrics of T9233 and T13035
     14f4347 Bump Cabal submodule
     96ddfa4 testsuite: Suppress uniques in T15243 output
     93220d4 testsuite: Remove uniques from T15243's stderr output
     502026f Make seq# evaluatedness look through casts
     25597a9 Comments only
     a169149 Remove duplicate quantified constraints
     97d0542 Small refactor, adding checkBadTelescope
     6ccfa62 Remove a tc-trace
     0180230 rts: Fix a var name in a comment, fix a typo
     da53417 docs: Add mentions of new plugins mechanisms to users guide
     aab3c6d Refactor TcExpr.tcSeq
     bb539cf Bump hadrian submodule
     a610c21 Fix some of the failures in sanity way
     cc78d25 testuite: remove strace call.
     b5ccee4 Do not skip conc004 in GHCi way
     a3c0b42 testsuite: Print summary even if interrupted
     f7b9456 Minor refactoring and docs in selector optimisation
     16c70da Disable T12903 on Darwin due to flakiness
     f1b097f OptCoercion: Ensure we use new UnivCo provenance to construct optimised cos.
     908edbf libiserv: Add license file
     3606075 testsuite: Add -fghci-leak-check to expected output on mingw32
     5600729 testsuite: Add Windows-specific output for T5611
     261209d Duplicated and
     97d1419 Update user manual sections for -rtsopts and -with-rtsopts
     ca7653a testsuite: Fix T4442 on i386
     0238a6c UNREG: PprC: add support for of W32 literals
     4a93166 Disable `-fdefer-out-of-scope-variables` in ghci.
     8ae7c1b Make Control.Exception.throw levity polymorphic.
     5f5d0c9 Mark test broken on powerpc64[le]
     87d691c users-guide: Fix PtrRepLifted to LiftedRep
     69b50ef Fix deserialization of docs (#15240)
     d24e73a Replace `showSDocUnsafe` with `showSDoc` in extending_ghc.rst
     233d815 rts: Ignore RLIMIT_AS if it is zero
     6f083b3 desugar: Rip out unsafeGlobalDynFlags usage in decomposeRuleLhs
     e4c41ec rts: Don't keep findPtr symbol alive if not -DDEBUG
     4672e2e relnotes: Add mention of QuantifiedConstraints
     d650729 Embrace -XTypeInType, add -XStarIsType
     0c5aac8 Revert inadvertant changes to .gitmodules
     8ffac59 Revert "rts: Don't keep findPtr symbol alive if not -DDEBUG"
     8062d7f Fix binary and haddock submodule commits
     f9b925a Bump haddock submodule
     3a18a82 Fix broken link
     db5ef2b Exclude libraries/libiserv/ghc.mk and other things via .gitignore.
     01c9d95 UNREG: PprC: add support for of W16 literals (Ticket #15237)
     807ab22 Fix the bind-recovery type
     f903e55 Fix corner case in typeKind, plus refactoring
     2f6069c Make better "fake tycons" in error recovery
     dbe5370 circleci: Remove systemd from Fedora nsswitch configuration
     69954a1 Fix documentation for `-dth-dec-file`
     b7deeed testsuite: Make T4442 compile on i386 and mark as broken
     e6498d6 Bump supported LLVM version to 6.0
     78f5344 No Unicode in Parser.y
     b67b971 Make NameSort note into proper Note
     91822e4 Add "quantified constraint" context in error message, fix #15231.
     9c89ef3 Make dtrace enabled GHC work as a bootstrap compiler on FreeBSD
     7100850 Use data con name instead of parent in lookupRecFieldOcc
     42f3b53 Fix #13833: accept type literals with no FlexibleInstances
     fe770c2 Built-in Natural literals in Core
     1279428 Quantify unfixed kind variables in CUSKs
     8ee9c57 Amend configure script to support lndir build tree
     1ab2dcb testsuite: Mark num009 as broken due to #15062
     1f2ed99 testsuite: Mark overflow1 as broken on 32-bit platforms due to #15255
     86210b2 rts: Use .cfi_{start|end}proc directives
     cd95c2f Preserve parenthesis in function application in typechecker
     a81b99d Bump nofib submodule
     dbc8c0f base: Improve the documentation of the enumFrom series of functions
     de34a71 rts: Remove use of __USE_MINGW_ANSI_STDIO
     819d8ef circleci: Bump fedora docker image tag
     f998947 circleci: Add a reference to the documentation on the Wiki
     60e4bb4 Enhanced constant folding
     d55035f Revert "Amend configure script to support lndir build tree"
     4cd5521 base: Add default implementation for Data.Bits.bitSize
     8df2447 Warn about implicit kind variables with -Wcompat
     76b343f Revert "rts: Use .cfi_{start|end}proc directives"
     0db05ad Bump process submodule
     d1c7239 configure: Fail when bootstrapping with GHC 8.2.1
     749bc1a testsuite: Mark T3001-2 as broken on 32-bit platforms
     9897440 testsuite: Mark print022 as broken on 32-bit platforms
     ccd8ce4 Handle DuplicateRecordFields correctly in filterImports (fixes #14487)
     df0f148 Improve error message when importing an unusable package
     793902e Improve documentation of Eq, Ord instances for Float and Double
     c637541 Provide a better error message for unpromotable data constructor contexts
     b8e3499 UNREG: fix CmmRegOff large offset handling on W64 platforms
     008ea12 Use __FILE__ for Cmm assertion locations, fix #8619
     04e9fe5 Add -Werror=compat
     50d7b2a Remove accidentally checked-in T14845.stderr
     d621644 Fix an infinite loop in niFixTCvSubst
     850ae8c Two small refactorings
     30b029b Fix typechecking of kind signatures
     6ac8a72 Typofixes in docs and comments [ci skip]
     de692fd Fix typo in comment only
     a9b01c0 Mark some TH tests as req_interp
     83a7b1c Adjust comments (Trac #14164)
     676c575 Fix API Annotations for GADT constructors
     26e9806 Document and simplify tcInstTyBinders
     4cdd574 configure: Bump version to 8.6.0
     000ac86 testsuite: Bump metrics for T5631 and T6048
     50e7bff containers: Bump to 0.6.0.1
     f0179e3 testsuite: Skip T11627a and T11627b on Darwin
     7b8dcd9 testsuite: Add broken test for #15289
     a5eaa0f Tweak wording in documentation
     436c0e9 findPtr: don't search the nursery
     21fa62f base: Add missing instances for Data.Ord.Down
     7363ba4 Revert "containers: Bump to 0.6.0.1"
     e839ee2 A few more typofixes in docs/comments [ci skip]
     942e6c9 configure: Fix libnuma detection logic
     f4dce6c Allow :info for (~) in GHCi
     b948398 Remove HsEqTy and XEqTy
     76e110f rts: A bit of cleanup of posix itimer implementation
     227ede4 Fix gcc.exe: error: CreateProcess: No such file or directory
     c35ad6e containers: Bump to 0.6.0.1
     c7cd5a6 configure: Set version to 8.7
     3048a87 Fix incorrect GHC versioning
     50a35e5 Drop redundant Note
     32eb419 Instances in no-evidence implications
     e065369 Refactor try_solve_fromInstance in shortCutSolver
     d5459a3 Remove unnecessary call to checkReductionDepth
     122ba98 Move a Note to the module that refers to it
     5f06cf6 TTG for IPBind had wrong extension name
     391b0ca Explain why opt-cmm is not dumped by ddump-cmm-verbose.
     63d474b Include ghc-heap and libiserv in the "package" file.
     c7b1e93 rts: Abort if timerfd read fails
     67c422c rts/linker/{SymbolExtras,elf_got}.c: map code as read-only
     33724fc Remove -Wamp flag
     5db9f91 Tweak API Annotations for ConDeclGADT
     2896082 Fix error recovery for pattern synonyms
     95324f0 Improve tc-tracing a bit
     9fc40c7 Refactor the kind-checking of tyvar binders
     577399c Coments and debug tracing only
     b4d5459 More misc comments
     cea409a Remove unused BottomFound from Tick
     1c2c2d3 Record some notes about "innocuous" transformations
     e53c113 API Annotations when parsing typapp
     261dd83 Fix TcLevel manipulation in TcDerivInfer.simplifyDeriv
     7a2b5d0 A bit more tc-tracking in TcUnify.uUnfilledVar
     bb50eca Remove dead code
     629d01a Typofixes in comments and whitespace only [ci skip]
     5865e9a Typo fix in rts [skip ci]
     3d00208 Add commnent about binder order
     4168ee3 rts: Update some comments, minor refactoring
     a54c94f Show addresses of live objects in GHCi leak check
     437ff69 Add ghc-prim as dependency to ghc-bin
     45de833 Clarify role of coercion in flattening function
     904abd4 Document SRT scavenging behavior of scavenge_block() and scavenge_one()
     4760a8c Add -ddump-rtti to user's guide and man page
     9a371d6 A few typofixes in comments
     6bb0c5d Don't lock the MVar closure on tryReadMVar
     6e4e6d1 Fix mkGadtDecl does not set con_forall correctly
     b4e6483 testsuite: remove unused scc001 target
     6cb189d RtClosureInspect: add some docs, remove unused stuff
     15bb4e0 Fix nptr field alignment in RtClosureInspect
     39de4e3 Fix errors caused by invalid candidates leaking from hole fits
     e835fdb Add regression test for #15321
     f6ac083 Add regression test for #15007
     8f44995 Revert "Don't lock the MVar closure on tryReadMVar"
     7ce6f64 Add comments on Typeable (n :: Nat)
     14dfdf6 Fix comment
     45f44e2 Refactor validity checking for constraints
     59a15a5 Fix #15307 by making nlHsFunTy parenthesize more
     93b7ac8 Fix #15308 by suppressing invisble args more rigorously
     132273f Instantiate GND bindings with an explicit type signature
     9275186 Fix newtype instance GADTs
     5773397 Parenthesize rank-n contexts in Convert
     b6a3386 Fix #15331 with careful blasts of parenthesizeHsType
     dbdcacf Make ppr_tc_args aware of -fprint-explicit-kinds
     9b26aa0 Comment out a pprTrace
     45f0026 Accept new stdout for tcrun045
     18cedbb Make a variant of mkCastErr for kind coercions
     8c628ad Remove BUILD_DPH, not used
     de95bf4 circleci: Detect core count
     87b28a8 users guide: Mention -fprint-typechecker-elaboration in -ddump-tc docs
     f59332f Mark AutoDeriveTypeable as deprecated
     fbe162f Add a broken test for lingering state from TH unique names #9693
     379bb20 Simplify lintIdUnfolding
     987b5e7 Fix for built-in Natural literals desugaring
     f03f0d6 testsuite: Add test for #15053
     8736715 rts: Enable two-step allocator on FreeBSD
     6715373 Revert "rts: Enable two-step allocator on FreeBSD"
     6595bee Define an Outputable MCoercion instance
     55a3f85 Refactor coercion rule
     fd0f033 More refactoring in TcValidity
     aedbf7f Fix decompsePiCos and visible type application
     03d7268 More tc-tracing
     5067b20 Add nakedSubstTy and use it in TcHsType.tcInferApps
     8ec2946 Optional context for a quantified constraint
     042df60 Unwrap casts before checking vars in eager unifier
     030211d Kind-check CUSK associated types separately
     cf67e59 Expand and implement Note [The tcType invariant]
     7f4dd88 Note [Ordering of implicit variables]
     9768c94 Remove bad debugging output.
     81d8b17 Add test for Trac #15352
     e24da5e Better Note [The well-kinded type invariant]
     1c35362 Use IfaceAppArgs to store an IfaceAppTy's arguments
     3efd7cd Minor refactoring in CmmUtils.mkLiveness
     5ee9a1c Correct Simple to Complex wording
     00cb530 Adding missing 'no'
     7527d1f Attempt to fix travis build
     6a1e7e7 Link to iterate' doesn't work.
     8bccefc Register 'haddockHTMLs' for inplace builds
     8e51ece Bump xhtml submodule to 3000.2.2.1
     471a992 Trac #8581 users_guide/glasgow_exts section 10.7
     19e1e6b The Types section in Core-Spec doc is out-dated
     7c207c8 Fix gcdExtInteger (trac#15350)
     101e904 Make boot work if ACLOCAL_PATH is not set
     c4d9834 Add flag to show docs of valid hole fits
     234093c Fix handling of ApplicativeDo in TH AST quotes
     0f79b0e Fix handling of unbound constructor names in TH #14627
     2b1adaa Export findImportUsage and ImportDeclUsage
     f282f02 docs: remove leftovers of static flags
     305da44 Release notes about source plugins
     1a79270 Run the renamed source plugin after each HsGroup
     7fc418d Fix deadlock between STM and throwTo
     3ee7ca1 Update submodule
     2625f13 Fix processHeapClosureForDead CONSTR_NOCAF case
     b56926d Refactor floatEqualities slightly
     56b9e47 Improve comments about CUSKs
     e40eb73 submodule update
     2928b92 Comments only
     cbd4b33 Bump haskeline submodule to 0.7.4.3
     c67cf9e Bump mtl submodule to v2.2.2
     b794c7e Bump directory submodule to v1.3.3.0
     c3328ff Bump unix submodule
     0905fec Remove random submodule
     502640c Optimise wakeups for STM
     a754a42 Remove ASSERTion about increasing TcLevels
     b7d6002 Make some tests robust against DEBUG compiler
     fe0fa63 Move check for dcUserTyVarBinders invariant
     15ce9b4 Don't mkNakedCastTy on something unsaturated
     6d55e36 Disable -fghci-leak-check in DEBUG mode
     8a70ccb Reclassify some performance tests
     af9b744 Replace atomicModifyMutVar#
     9269541 TTG typo: XFieldOcc should be XCFieldOcc
     8b6a9e5 Fix parse errors in core-spec.pdf
     71f6b18 Fix space leaks
     0d6ef6d #15387 Fix setting testsuite verbose to zero
     8ec4899 driver: skip -Bsymbolic on unregisterised targets (Trac #15338)
     beba89a aclocal.m4: allow riscv and riscv64 CPU
     7fe4993 Modernize S_TPush in the core spec
     65c186f Do not imply NoStarIsType by TypeOperators/TypeInType
     5de8e26 Fix example in `asum` docs
     28199a2 Fix hash in haddock of ghc-prim.
     c4b8e71 Fixed "Memory Model" example.
     3bdf0d0 Support the GHCi debugger with -fexternal-interpreter
     5364994 split-obj: disable split-objects on Windows.
     973ff4a Fix a typo in related trac ticket number
     5e63a25 aclocal.m4: narrow down 'riscv*' to 'riscv-*' and 'riscv32*'
     ab0c238 Fix a typo
     2c38a6e Fix spelling errors
     1f924cb Correct spelling errors
     932300b Fix some typos in docs
     b290f15 testsuite: force plugin tests sequentially on Windows.
     d0bbe1b stack: fix stack allocations on Windows
     e175aaf fix osReserveHeapMemory block alignment
     176abdf Small spelling fixes for Unify.hs
     99f45e2 Fix #15423 by using pprAStmtContext
     f64f06b Avoid redundant invocation of 'findTopDir'
     b202e7a Fix the TcLevel not being set correctly when finding valid hole fits
     5a49651 Harden fixST
     4ea9311 Fix the GHCi debugger with ApplicativeDo
     f629442 Fix a major copy'n'paste error in LLVM CodeGen
     3aa09cc Fix pretty-printing of data declarations in splices
     fd1cf1f Disable T10962 on llvm for now
     a606750 fixup! Disable T10962 on llvm for now
     af62407 Fix some casts.
     f0d27f5 Stop marking soluble ~R# constraints as insoluble
     e1b5a11 Fix a nasty bug in piResultTys
     44a7b9b Suppress -Winaccessible-code in derived code
     47561c9 Remove dead code in TcUnify
     0dc86f6 Clone relevant constraints to avoid side-effects on HoleDests. Fixes #15370.
     6c19112 Build more implications
     12c0f03 Set GenSigCtxt for the argument part of tcSubType
     f7d3054 Improve error message on un-satisfied import
     c5d31df Treat isConstraintKind more consistently
     857ef25 Fix and document cloneWC
     a434bcb tc-tracing only
     0f5a63e Comments only
     9897f67 Fix PrelRules.caseRules to account for out-of-range tags
     4c571f3 Comments only
     f265008 Refactor (~) to reduce the suerpclass stack
     45cfe65 Small refactor in desugar of pattern matching
     890f646 Bump haddock submodule
     7a3e1b2 rts: Flush eventlog in hs_init_ghc (fixes #15440)
     25e1ea9 Make :doc work for the ghc library
     13d40ff Add a script for running a ghci that can load and run ghc
     774f366 Fail instead of panic-ing when qAddTopDecls has conversion error
     3c311e5 Run StgCse after unarise, fixes #15300
     e431d75 Fix gcCAFs()
     3581212 Add an expect_broken test for #14185
     e5f3de2 update core-spec for GRefl and re-factored Refl
     60ecf43 Modifications to support loading GHC into GHCi
     ccdc032 rts: More forceful cc debugging flags
     40e9ec9 Disable GNUC_ATTR_HOT when compiling with DEBUG
     d7cb1bb Fix endian issues in ghc-heap
     2cb08d7 Remove dead code in testsuite driver
     754c3a5 Fix Ar crashing on odd-sized object files (Trac #15396)
     3539561 Fix Git commit ID detection in Git worktrees
     11de438 Fix #15453: bug in ForAllCo case in opt_trans_rule
     9d388eb Fix #15385 by using addDictsDs in matchGuards
     a7c8acd GHC doesn't handle ./ prefixed paths correctly (#12674)
     c626246 Bump terminfo submodule to 0.4.1.2
     a698bbf Fix minor formatting issue in users_guide/bugs.rst
     56590db base: Make Foreign.Marshal.Alloc.allocBytes[Aligned] NOINLINE
     2110738 Don't inline functions with RULES too early
     3a06561 Add the paper "Evidence normalisation in System FC"
     80b8540 rts: Disable -fkeep-inline-functions due to lack of support on Clang
     123aeb9 Enable two-step allocator on FreeBSD
     cb8efe7 doc: Fix command for creating a shared library.
     6d2a9ec Bump Cabal submodule
     f8e5da9 testsuite: Add test for #14346
     0e34a9f users-guide: Document default +RTS -I value
     5e103a1 base: Fix documentation of System.Environment.Blank
     9bd4864 rts: Fix unused function
     1df50a0 Revert "Don't inline functions with RULES too early"
     f8618a9 Remove the type-checking knot.
     52065e9 Plugin dependency information is stored separately
     b803c40 linker: Nub rpaths
     7f3cb50 Fix #15450 by refactoring checkEmptyCase'
     120cc9f Fix #15415 and simplify tcWildCardBinders
     c50574a Remove obsolete file
     c955a51 Remove decideKindGeneralisationPlan
     653dc5f Bump Cabal submodule
     8d04822 Bump binary submodule
     7535fd6 Bump filepath submodule
     8801642 testsuite: Bump T3064 expected allocations
     47e54a0 Bump hadrian submodule
     73683f1 Refactor printMinimalImports (#15439)
     0095cde Fix typos
     f355b72 circleci: Don't build validate-x86_64-linux-debug unregisterised
     4d91cab Allow scoped type variables refer to types
     d7bc05e Create 8.8.1 release notes
     b14040d Move 8.8.1-notes.rst to the right directory
     f811685 Mention #15050 in the release notes for 8.8.1
     e94cc29 Use -fobject-code in the GHCi script for loading GHC
     29dfb63 Strip ../ from testdir (fixes #15469)
     36a4c19 Testsuite driver: fix encoding issue when calling ghc-pkg
     4fc6524 Stop the linker panic
     ff06176 Improve error message for flags with missing required arguments (#12625)
     c6cc93b rts: Ensure that the_gc_thread is aligned
     8b357c6 Add since annotation to GHC.ByteOrder
     ce9b459 docs: Fix wrong module name in hsig example
     672f177 Unhide GHC.List for haddock
     24b76d1 [docs] Add missed specialisations warnings to list of those not enabled by -Wall
     e28bb01 fix timeout related i686 validation issues
     7d77198 Support typechecking of type literals in backpack
     2604d9b Bump binary submodule to 0.8.6.0
     f22baa4 users-guide: Enlarge title underlines in 8.8 release notes
     aab8656 Turn on MonadFail desugaring by default
     e5b128c Bump Cabal submodule
     5487f30 testsuite: Add (broken) test for #15473
     e2db2d5 Yet another Cabal submodule bump
     4d6dfc3 Allow arbitrary options to be passed to tar compression
     e2b5c54 Revert "rts: Ensure that the_gc_thread is aligned"
     9f93714 circleci: Fix documentation building
     5be646f circleci: Reduce build verbosity
     60e12f2 circleci: Reduce compression effort to 3
     396aac4 Add FreeBSD amd64 LLVM target
     ce47a9c base: improve Functor documentation
     342f27f Bump unix submodule
     b44e747 testsuite: Bump for unix 2.7
     b324c56 Filter plugin dylib locations
     f27d714 Simplify testsuite driver
     97596a4 Simplify testsuite driver, part 2
     ec49b42 CSE should deal with letrec
     193eeee use *test instead of *slowtest for llvm validation on Circle CI
     d42eef3 --show-iface: Qualify all non-local names
     f7f9820 Check if files are same in combineSrcSpans
     c552fee Suppress redundant givens during error reporting
     bd48a88 Bump parsec submodule
     32008a9 Properly designate LambdaCase alts as CaseAlt in TH
     2908899 primops: Drop support for WORD_SIZE_IN_BITS < 32
     9f932d8 Add a test for Trac #15523
     1e741fe Cosmetics in GraphColor
     7a63f75 primops: Drop documentation for WORD_SIZE_IN_BITS < 32
     5238f20 Fix #15527 by pretty-printing an RdrName prefixly
     a50244c Rename SigTv to TyVarTv (#15480)
     23f6f31 Document default value of +RTS -N in user's guide
     63b6a1d Be mindful of GADT tyvar order when desugaring record updates
     ae68f32 base: rewrite Monoid module docs
     2748e95 base: Rewrite semigroup documentation
     8154faf Make ghci work for stage1 and Hadrian
     1bbb5fa Add comment explaining change in syntax error suggestion for #12146.
     8f4df7f Add test cases for Ticket #12146.
     a08b285 CSE should deal with letrec (#9441)
     ecc0ddf Initialise cec_suppress properly
     d04a152 Update .mailmap [skip ci]
     2671ec5 Bump stm submodule
     9c4e6c6 Expose the StableName constructor
     ce6ce78 Set strictness correctly for JoinIds
     18c302c Improve ambiguous-occurrence error message
     828e949 Comments only
     43b08cf Add a solveEqualities to tcClassDecl1
     1cc9061 driver: unconditionally disable relaxation when linking partially
     966aa78 Fix redundant imports of Class
     02518f9 Fix #line pragmas in nested comments
     09c1d5a Replace most occurences of foldl with foldl'.
     23774c9 function-section: enable on windows
     ebcbfba Introduce flag -keep-hscpp-files
     8a05836 Simplify callSiteInline a little
     92db10b testsuite: Deduplicate source in wcompat-warnings test
     c971e11 Explicitly tell 'getNameToInstances' mods to load
     2bacf6f rts/RetainerProfile: Dump closure type if pop() fails
     1481762 base: Mark `findIndices` as INLINABLE instead of INLINE (fixes #15426)
     ddffa0c Fix ambiguous/out-of-scope Haddock identifiers
     dcf27e6 Show -with-rtsopts options in runtime's --info (#15261)
     68a1fc2 rts: Align the_gc_thread to 64 bytes
     2693eb1 Properly tag fun field of PAPs generated by ap_0_fast
     c331592 Correct limb length and assertion for gcdExtInteger
     c6f4eb4 Fix precision of asinh/acosh/atanh by making them primops
     8546afc docs: "state transformer" -> "state monad" / "ST" (whichever is meant)
     21f0f56 Add traceBinaryEvent# primop
     ab55b4d Revert "Properly tag fun field of PAPs generated by ap_0_fast"
     44ba665 Revert "driver: unconditionally disable relaxation when linking partially"
     db6f1d9 Turn infinite loop into a panic
     8c7f90a Fix a typo in TcValidity.checkFamInstRhs
     2a54209 Comments only
     4293a80 Accommodate API change in transSuperClasses
     8d72f87 TcSimplify: Condense MASSERT2() usage onto a single line
     edb4714 docs: Add changelog and release notes entry for traceBinaryEvent#
     14d8838 Update unicode tables to v. 12 of the standard
     184a569 Clean up TcHsSyn.zonkEnv
     1cca442 Comments only
     4b79329 Add comments about pretty-printing via IfaceSyn
     ff29fc8 Better error reporting for inaccessible code
     c523525 ghc, ghc-pkg: use getExecutablePath on Windows when base >= 4.11.0
     5e6cf2a Fix #15550 by quoting RULE names during TH conversion
     7a3cda5 Fix #15502 by not casting to Int during TH conversion
     744b034 Take strict fields into account in coverage checking
     6e765ae Don't reify redundant class method tyvars/contexts
     2d953a6 Fix #10859 by using foldr1 while deriving Eq instances
     b1f5d2f Bump nofib submodule
     154d4e2 Remove dph, vector, primitive and random from .gitmodules
     2cf98e2 rts: Handle SMALL_MUT_ARR_PTRS in retainer profilter
     c18b525 Remove dead code for commandline parsing
     c46a5f2 Fix #15572 by checking for promoted names in ConT
     34b8e61 Fix typo in 8.6.1 notes
     102284e Rename kind vars in left-to-right order in bindHsQTyVars
     36c1431 Fixed typo in exponent example
     65eec9c Fix a constant folding rule
     f48e276 Finish stable split
     97826e3 Fix the __GLASGOW_HASKELL__ comparison
     12e6e19 A few typos [ci skip]
     140563f fix -ddump-asm description
     5d3eb64 Minor improvements to comments [skip ci]
     5851885 Comments only
     fda2ea5 Commets on flatten_args_tc
     565ef4c Remove knot-tying bug in TcHsSyn.zonkTyVarOcc
     6dea7c1 Reject class instances with type families in kinds
     ed78951 make iToBase62's inner loop stricter in one of its arguments
     2e226a4 canCFunEqCan: use isTcReflexiveCo (not isTcReflCo)
     d1514e8 Remove duplicate "since" field in glasgow_exts.rst
     fa3143c Fix typos in -Wsimplifiable-class-constraints flag docs
     df363a6 Compiler panic on invalid syntax (unterminated pragma)
     a3a1a17 Add a test for Trac #15586
     2254912 testsuite: make CHECK_API_ANNOTATIONS and CHECK_PPR overridable
     24d610a Fix tests ghci057 and T9293. (#15071)
     c0e5087 Skip eventlog tests in GHCi way
     49d50b2 testsuite: Add test for #15368
     a811d93 base: Add references to Notes for certain special imports
     ecde954 testsuite: Use bools for booleans, not ints
     e29ac2d Expose 'moduleToPkgConfAll' from 'PackageState'
     1152a3b Define activeAfterInitial, activeDuringFinal
     3addf72 Preserve specialisations despite CSE
     16bc7ae Remove an incorrect assertion in threadPaused:
     c6fbac6 Fix a race between GC threads in concurrent scavenging
     d9a26c7 Various RTS bug fixes:
     4caad16 Documentation tweaks
     9400a5c ghc: Remove warning of StaticPointers not being supported by GHCi
     2b6694a users-guide: Disable syntax highlighting
     62cd440 Refactor Foreign.Marshal modules for more modern style
     510c5f4 Avoid creating unevaluated Int thunks when iterating in GHC.Foreign
     3cc3edf Update UnsafeReenter test
     d36b1ff Build debugged prof runtimes
     36740b4 Revert incorrect STM wakeup optimisation
     5d67d06 rts.cabal.in: advertise new default profiling ways for hadrian
     03b779f Make CoreMonad independent of TcEnv (#14391)
     ce23451 Refactor info table entry error messages
     0e6d42f Be a bit more aggressive about let-to-case
     7ab8007 Revert "ghc: Remove warning of StaticPointers not being supported by GHCi"
     5c48c41 template-haskell: Fix typo in changelog
     900c47f rts/Printer.c: always define the findPtr symbol
     b9b1f99 Honor INLINE on 0-arity bindings (#15578)
     1ad3c82 Typo in user guide wrongly claims DeriveLift was added in 7.2
     0c07208 Comments about join-point return types
     6bf11e6 Delete duplicated comment line
     291b0f8 Comments only (on IfDataInstance)
     bd76875 Allow (~) in the head of a quantified constraints
     0d4f394 Add regression test for Trac #15629
     02edb8f More info for Implication with -dppr-debug
     8533428 Remove dead variable binding
     9912cdf Fix build
     5f5898a eventlog: Factor out eventlog header generation into separate function
     e71e341 base: showEFloat: Handle negative precisions the same of zero precision
     ce240b3 Update hsc2hs submodule
     9c6b749 Add support for ImplicitParams and RecursiveDo in TH
     3040444 tests: increase (compile) timeout multiplier for T13701 and MultiLayerModules
     ecbe26b Fix T15502 on 32-bit
     64c54ff Mark system and internal symbols as private symbols in asm
     c23f057 Mark code related symbols as @function not @object
     ea5ade3 Coercion Quantification
     a3bce95 Correct submodule update for haddock
     c6bff52 Fix for #13862: Optional "-v" not allowed with :load in GHCi
     d1c2f29 Stable name comment wibbles
     88130db base: Add bangs to GHC.IO.Handle.Text hGet* functions
     43967c0 users-guide: Fix code-block layout for QuantifiedConstraints
     e655aac Make sure forM_ and related functions fuse cleanly
     5840734 Updated PE linker, section alignment and cleanup.
     4edc6d6 Users guide: EmptyDataDecls on by default
     01f7cd7 NoImplicitPrelude in ghc-boot-th, ghc-boot, ghc-heap, ghci
     ce3897f Fix check whether GCC supports __atomic_ builtins
     6bb9bc7 Invert FP conditions to eliminate the explicit NaN check.
     e40b388 Bump stm submodule
     989dca6 Bump text submodule
     2b763b5 Bump deepseq submodule
     1971e99 Don't shortcut SRTs for static functions (#15544)
     a4ae97e docs: fix example code
     45befe2 Use predefined known-key names when possible
     077b92f Remove -Waggregate-return when building RTS
     4e3f6a0 users guide: Fix a few issues
     ba086ca Add testcase for #14251
     d7fa869 Revert "adds -latomic to. ghc-prim"
     4eebc80 users-guide: Fix build with sphinx 1.8
     8c7d33a users_guide: fix sphinx error caused by non-explicit override
     a257782 user-guide: Allow build with sphinx < 1.8
     66c1729 Fix slop zeroing for AP_STACK eager blackholes in debug build
     29f1c55 Remove redundant slop zeroing
     d0d7484 testsuite: Don't force run of llvm ways in T14251
     73d9cad testsuite: Mark readFail032 and readFail048 as broken on Darwin
     3e5b8e3 testsuite: Fix readFail048 and readFail032 brokenness declarations
     fd89bb4 testsuite: Bump expected allocations of T9675
     78beade testsuite: Bump expected allocations for T12707
     7e77f41 testsuite: Bump T9630 expected allocations
     cad5d0b Buglet in reporting out of scope errors in rules
     4bde71d Don't look up unnecessary return in LastStmt
     ab44ff8 Comments only
     2dbf88b Fix get getIdFromTrivialExpr
     e68b439 Add a recursivity check in nonVoid
     84c2ad9 update to current master again


More information about the ghc-commits mailing list