[commit: ghc] wip/T5642's head updated: LoadIFace: Show known names on inconsistent interface file (dad6a88)

git at git.haskell.org git at git.haskell.org
Thu Sep 1 14:31:26 UTC 2016


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

Branch 'wip/T5642' now includes:

     886f4c1 Better comment for orIfNotFound.
     f91d87d Failing test-case for #12135.
     3042a9d Use UniqDFM for HomePackageTable
     48e9a1f Implement deterministic CallInfoSet
     a90085b Add @since annotations to base instances
     e684f54 Desugar ApplicativeDo and RecDo deterministically
     31ba8d6 Kill nameSetElems
     46d2da0 Document putDictionary determinism
     3e7a876 Kill foldUniqSet
     1937ef1 Make UnitIdMap a deterministic map
     a13cb27 Merge MatchFixity and HsMatchContext
     77ccdf3 Kill occSetElts
     7fea712 Use a deterministic map for imp_dep_mods
     d05dee3 CoreToStg: Remove hand-written Eq instances of HowBound and LetInfo
     4426c5f Kill two instances of uniqSetToList
     0d6f428 Fix build by removing unused import
     c148212 Kill varSetElems in checkValidInferredKinds
     ad8e203 Use DVarSet in Vectorise.Exp
     3b698e8 Document determinism in pprintClosureCommand
     5db93d2 Make vectInfoParallelVars a DVarSet
     7008515 Kill varSetElems
     7d58a97 Use pprUFM in pprStgLVs
     00e3a5d Typofix.
     4d5b2f6 Testsuite driver: always quote opts.testdir
     f5f5a8a Testsuite Windows: mark T8308 expect_broken (#8308)
     d4b548e Add some determinism tests
     dd33245 Desugar: Display resulting program stats with -v2
     44a3c18 Revert "Desugar: Display resulting program stats with -v2"
     c2bbc8b Report term sizes with -v3 even when -ddump is enabled
     80cf4cf Literal: Remove unused hashLiteral function
     d7933cb Show sources of cost centers in .prof
     8f6d292 Fix #12064 by making IfaceClass typechecking more lazy.
     acb9e85 Minor performance note about IdInfo.
     11ff1df Fix #12076 by inlining trivial expressions in CorePrep.
     48385cb Remove special casing of Windows in generic files
     ceaf7f1 Implement Eq TyCon directly
     68c1c29 Remove Ord (CoAxiom br)
     9dbf354 Testsuite: delete dead code [skip ci]
     e703a23 Docs: fix links to ghc-flags
     70e0a56 Remove Ord Class
     b2624ee Remove Ord PatSyn
     77b8c29 Remove Ord AltCon
     c22ab1a Docs: delete PatternGuards documentation
     b020db2 Fix Ticky histogram on Windows
     e9dfb6e Improve the error messages for static forms.
     b0a7664 prettyPrintClosure(): Untag the closure before accessing fields
     47d8173 Remove Printer.c:prettyPrintClosure()
     bcb419a Fix #12099: Remove bogus flags
     6adff01 Comments only
     6905ce2 Refine imports slightly
     0f0b002 Comments only
     3ae18df Minor refactoring
     b9fa72a Small refactor to mkRuntimErrorId
     9e5ea67 NUMA support
     c88f31a Rts flags cleanup
     5990016 ModuleSet: Use an actual set instead of map to units
     6ace660 rts: Fix build when USE_LARGE_ADDRESS_SPACE is undefined
     9130867 Skip retc001 on OSX
     b40e1b4 Fix incorrect calculated relocations on Windows x86_64
     29e1464 Disable T12031 on linux
     2bb6ba6 rts: Fix NUMA when cross compiling
     d25cb61 Kill off redundant SigTv check in occurCheckExpand
     15b9bf4 Improve typechecking of let-bindings
     c28dde3 Tidy up zonkQuantifiedTyVar
     7afb7ad Get in-scope set right in top_instantiate
     35c9de7 Move the constraint-kind validity check
     1f66128 Beef up mkNakedCastTy
     15fc528 Fix the in-scope set for extendTvSubstWithClone
     599d912 Beef up isPredTy
     8104f7c Remove some traceTc calls
     e064f50 Add to .gitignore
     921ebc9 Test Trac #12055
     1dcb32d A second test for Trac #12055
     5cee88d Add thin library support to Windows too
     7de776c Kill unused foldModuleEnv
     586d558 Use UniqFM for SigOf
     0497ee5 Make the Ord Module independent of Unique order
     d55a9b4 Update Haddock to follow change in LHsSigWcType
     4f35646 Adjust error message slightly
     8dfd4ae Build system: mention ghc version in bindist's `configure --help` docdir
     a2deee0 Testsuite: enable ghci.prog010 (#2542)
     23b73c9 Don't GC sparks for CAFs
     9d22fbe Rename cmpType to nonDetCmpType
     753c5b2 Simplify readProcessEnvWithExitCode + set LANGUAGE=C
     70a4589 Revert "Make the Ord Module independent of Unique order"
     e33ca0e Fix testsuite wibble
     77bb092 Re-add FunTy (big patch)
     e368f32 Major patch to introduce TyConBinder
     c56f8bd CoreMonad: Update error msg function docs
     930a525 Abort the build when a Core plugin pass is specified in stage1 compiler
     a7f65b8 Remove dead code: countOnce, countMany
     498ed26 NUMA cleanups
     8d33af9 CoreLint: Slightly improve case type annotation error msgs
     3e8c495 CmmNode: Make CmmTickScope's Unique strict
     2396d9b llvmGen: Make metadata ids a newtype
     85e09b1 llvmGen: Consolidate MetaExpr pretty-printing
     9bb0578 Revert accidental submodule updates
     e02beb1 Driver: `ghc ../Test` (without file extension) should work
     f72f23f Testsuite: run tests in <testdir>.run instead of /tmp
     6f6f515 Testsuite: write "\n" instead of "\r\n" when using mingw Python
     d94c405 Testsuite: validate the tests/stage1 directory with the stage1 compiler
     a4c8532 Validate: use `rm -f` instead of `rm`
     6354991 VarEnv: Comment only
     270d545 Add Bifoldable and Bitraversable to base
     9649fc0 Refactor derived Generic instances to reduce allocations
     4d71cc8 Avoid find_tycon panic if datacon is not in scope
     f12fb8a Fix trac #10647: Notice about lack of SIMD support
     2897be7 PPC NCG: Fix float parameter passing on 64-bit.
     f4b0488 PPC NCG: Fix and refactor TOC handling.
     0be38a2 llvmGen: Add strictness to metadata fields
     0e92af9 Remove use of KProxy in GHC.Generics
     0ba34b6 ApplicativeDo: allow "return $ e"
     e7e42c8 Fix double-free in T5644 (#12208)
     cdc14b4 Testsuite: remove Windows CR again.. [skip ci]
     9cdde38 Testsuite: remove Windows CR [skip ci]
     cf6e656 Testsuite: remove Windows CR [skip ci]
     3dc1202 Testsuite: tabs -> spaces [skip ci]
     7e7094f Testsuite: tabs -> spaces [skip ci]
     46ff80f Testsuite: tabs -> spaces [skip ci]
     915e07c Testsuite: tabs -> spaces [skip ci]
     5b03dc6 Testsuite: tabs -> spaces [skip ci]
     a7160fa Testsuite: tabs -> spaces [skip ci]
     4a4bdda Testsuite: recover from utf8 decoding errors
     6d0a4fc Testsuite: fix WAY=ghci when LOCAL=0
     1ddc10b Testsuite: *do* replace backslashes in config.libdir
     1d938aa Testsuite: mark tests expect broken
     3b49f8f Testsuite: remove `-fforce-recomp` from default flags (#11980)
     82f7f18 Testsuite: delete TEST_HC_OPTS_NO_RECOMP
     135fc86 Testsuite: remove `-Wno-warn-tabs` from default flags
     ebaf26b Testsuite: delete dead code + cleanup
     e170d19 Testsuite: assume timeout_prog always exists
     ee3bde7 Expand and clarify the docs for ApplicativeDo (#11835)
     7301404 Typos in comments
     d09e982 Don't quantify over Refl in a RULE
     97a50f8 Delete commented-out code
     1230629 Make checkFamInstConsistency less expensive
     a47b62c Second attempt to fix sizeExpr
     c0583a9 Fix build breakage due to rebase
     9d62d09 Hopefully fix all the rebase-induced breakage
     4e7d835 Typos in comments [skip ci]
     6199588 More typos in comments [skip ci]
     93f40cb Don't error on GCC inlining warning in rts
     348f2db Make the Ord Module independent of Unique order (2nd try)
     15641b0 Accept new (lower) allocations for T7257
     7e7aeab Comments only
     cc92a44 Improve error message in deriving( Functor )
     a1b3359 Remove unused arg to tcSuperClasses
     ce97b72 Expand given superclasses more eagerly
     210a2e1 Test Trac #12163
     3e0af46 Give lookupGRE_Name a better API
     e556f76 Remove unused import
     643706e Narrow the warning for simplifiable constraints
     2f8cd14 Narrow the use of record wildcards slightly
     7fc20b0 Have Core linter accept programs using StaticPointers and -fhpc.
     35d1564 Provide Uniquable version of SCC
     bb74021 Remove Ord TyCon
     7f5d560 Very confusing typo in error message.
     9a34bf1 Fix #11974 by adding a more smarts to TcDefaults.
     8035d1a Fix #10963 and #11975 by adding new cmds to GHCi.
     4ae950f Release notes for #11975 and #10963
     df9611e Testsuite: do not copy .hi/.o files to testdir (#12112)
     d2958bd Improve typechecking of instance defaults
     c871ce4 Comments around invisibility
     393928d Fix renamer panic
     f86a337 Remove bogus comment on ForAllTy
     bb84ee4 Improve pretty-printing of Avail
     12c4449 Implement ReifyConStrictness for -fexternal-interpreter (#12219)
     d2006d0 Run all TH tests with -fexternal-interpreter (#12219)
     bdb0d24 Remote GHCi: separate out message types
     eb73219 Remote GHCi: comments only
     0bab375 Fix T8761  (#12219, #12077)
     dadd8b8 Test Trac #12229
     9bc2233 Fix typo in Data.Bitraverse Haddocks
     31b5806 Clean up outdated comments in template-haskell changelog
     a33b498 Add template-haskell changelog note for #8761
     5fdb854 s/Invisible/Inferred/g s/Visible/Required/g
     4cc5a39 Refactor tcInferArgs and add comments.
     8c1cedd Allow building static libs.
     da60e3e rts/Linker.c: Improve ugly C pre-processor hack
     7843c71 Make T8761 deterministic, I hope
     ff1cc26 Don't run the run_command tests with ext-interp
     82282e8 Remove some `undefined`s
     60c24b2 Typos in user manual and code: recurisve -> recursive
     afa6e83 rts/Linker.c: Rename ONLY_USED_x86_64_HOST_ARCH macro
     bbf0aa2 Testsuite: never pick up .T files in .run directories
     7593c2f Testsuite: report duplicate testnames when `make TEST=<name>`
     1f45bce Testsuite: remove one level of indentation [skip ci]
     206b4a1 Testsuite: simplify extra_file handling
     bafd615 Testsuite: do not print timeout message
     58f0086 Testsuite: open/close stdin/stdout/stderr explicitly
     d8e9b87 Testsuite: cleanup printing of summary
     782cacf Testsuite: framework failure improvements (#11165)
     6b3b631 Testsuite: run all indexed-types ways on ./validate --slow
     0eb0378 Testsuite: do not add -debug explicitly in .T file
     3fb9837 Testsuite: mark tests expect_broken
     af21e38 Don't omit any evidence bindings
     23b80ac Deal correctly with unused imports for 'coerce'
     dc62a22 Wibble error message for #11471
     dd92c67 Stop the simplifier from removing StaticPtr binds.
     2e9079f Test Trac #12185
     848e3ce Testsuite: fixes for python2.6 support
     9a645a1 Refactor match to not use Unique order
     8f7194f Double the file descriptor limit for openFile008
     1084d37 Testsuite: use ignore_stderr/stdout instead of ignore_output
     24194a6 Fix pretty-printer for IfaceCo
     e8d6271 Testsuite: do not depend on sys.stdout.encoding
     fb6e2c7 Delete Ord Unique
     9854f14 Add a new determinism test
     b6b20a5 Reorganize some determinism tests
     480e066 Remove ufmToList
     b8b3e30 Axe RecFlag on TyCons.
     0701db1 Updates to handle new Cabal
     430f5c8 Trac #11554 fix loopy GADTs
     6a5d13c nativeGen: Allow -fregs-graph to be used
     f68d40c ghc-pkg: Drop trailing slashes in computing db paths
     f1e16e9 CmmExpr: remove unused `vgcFlag` function
     b65363d Fix check_uniques in non-unicode locale
     0afc41b Testsuite: be less strict about topHandler03's stderr
     c27ce26 users-guide: Fix markup in release notes
     81b437b Add NamedThing (GenLocated l e) instance
     b412d82 Allow one type signature for multiple pattern synonyms
     6ba4197 rules/sphinx.mk: stop xelatex on error
     ee8d1fa Remove unused oc->isImportLib (#12230)
     6377757 Linker: some extra debugging / logging
     cbfeff4 Remove uniqSetToList
     0d522b8 Document some benign nondeterminism
     0ab63cf Kill varEnvElts in seqDmdEnv
     01f449f Fix 32-bit build failures
     9031382 MkCore: Fix some note names
     a6819a0 base: Add release date to changelog
     bf7cbe7 users-guide: Note multiple pattern signature change in relnotes
     afec447 testsuite: Add testcase for #12355
     2a3af15 Treat duplicate pattern synonym signatures as an error
     3b2deca users-guide: Remove static field type from rts-flag
     331febf CallArity: Use not . null instead of length > 0
     0bd7c4b Enum: Ensure that operations on Word fuse
     18e71e4 Revert "Fix 32-bit build failures"
     890ec98 Revert "Linker: some extra debugging / logging"
     e10497b Kill some varEnvElts
     85aa6ef Check generic-default method for ambiguity
     1267048 Extra ASSERTs for nameModule
     55e43a6 Use DVarEnv for vectInfoVar
     5f79394 Delete out-of-date comment
     895eefa Make unique auxiliary function names in deriving
     cbe30fd Tidy up tidying
     f2d36ea White space only
     6cedef0 Test Trac #12133
     27fc75b Document codegen nondeterminism
     18b782e Kill varEnvElts in zonkEnvIds
     1b058d4 Remove varEnvElts
     b7b130c Fix GetTime.c on Darwin with clock_gettime
     f560a03 Adds x86_64-apple-darwin14 target.
     567dbd9 Have addModFinalizer expose the local type environment.
     56f47d4 Mention addModFinalizer changes in release notes.
     672314c Switch to LLVM version 3.8
     b9cea81 Show testcase where demand analysis abortion code fails
     979baec --without-libcharset disables the use of libcharset
     bedd620 Style changes for UniqFM
     6ed7c47 Document some codegen nondeterminism
     9858552 Use deterministic maps for FamInstEnv
     34085b5 Correct the message displayed for syntax error (#12146)
     64bce8c Add Note [FamInstEnv determinism]
     6e280c2 Utils: Fix `lengthIs` and `lengthExceeds` for negative args
     0481324 Use UniqDFM for InstEnv
     b8cd94d GHC.Stack.CCS: Fix typo in Haddocks
     91fd87e FastString: Reduce allocations of concatFS
     15751f2 FastString: Add IsString instance
     c4a9dca FastString: Supply mconcat implementation
     fc53d36 OccName: Implement startsWithUnderscore in terms of headFS
     eb3d659 OccName: Avoid re-encoding derived OccNames
     4f21a51 Kill eltsUFM in classifyTyCons
     6c7c193 DsExpr: Remove usage of concatFS in fingerprintName
     0177c85 Testsuite: expose TEST_CC (path to gcc)
     f53d761 TysWiredIn: Use UniqFM lookup for built-in OccNames
     9a3df1f check-api-annotations utility loads by filename
     17d0b84 Add -package-env to the flags reference
     372dbc4 Pretty: delete really old changelog
     45d8f4e Demand analyser: Implement LetUp rule (#12370)
     18ac80f tidyType: Rename variables of nested forall at once
     cd0750e tidyOccNames: Rename variables fairly
     37aeff6 Added type family dependency to Data.Type.Bool.Not
     b35e01c Bring comments in TcGenGenerics up to date
     a9bc547 Log heap profiler samples to event log
     ffe4660 IfaceEnv: Only check for built-in OccNames if mod is GHC.Types
     24f5f36 Binary: Use ByteString's copy in getBS
     0f0cdb6 Bugfix for bug 11632: `readLitChar` should consume null characters
     1ba79fa CodeGen: Way to dump cmm only once (#11717)
     89a8be7 Pretty: remove a harmful $! (#12227)
     5df92f6 hp2ps: fix invalid PostScript for names with parentheses
     d213ab3 Fix misspellings of the word "instance" in comments
     3fa3fe8 Make DeriveFunctor work with unboxed tuples
     514c4a4 Fix Template Haskell reification of unboxed tuple types
     1fc41d3 Make okConIdOcc recognize unboxed tuples
     0df3f4c Fix PDF build for the User's Guide.
     98b2c50 Support SCC pragmas in declaration context
     e46b768 Make Data.{Bifoldable,Bitraversable} -XSafe
     908f8e2 TcInteract: Add braces to matchClassInst trace output
     8de6e13 Fix bytecode generator panic
     cac3fb0 Cleanup PosixSource.h
     a0f83a6 Data.Either: Add fromLeft and fromRight (#12402)
     627c767 Update docs for partial type signatures (#12365)
     ed48098 InstEnv: Ensure that instance visibility check is lazy
     9513fe6 Clean up interaction between name cache and built-in syntax
     a4f2b76 testsuite: Add regression test for #12381
     93acc02 Add another testcase for #12082
     cf989ff Compact Regions
     83e4f49 Revert "Clean up interaction between name cache and built-in syntax"
     714bebf Implement unboxed sum primitive type
     a09c0e3 Comments only
     9c54185 Comments + tiny refactor of isNullarySrcDataCon
     8d4760f Comments re ApThunks + small refactor in mkRhsClosure
     6a4dc89 Bump Haddock submodule
     8265c78 Fix and document Unique generation for sum TyCon and DataCons
     e710f8f Correct a few mistyped words in prose/comments
     bbf36f8 More typos in comments
     fb34b27 Revert "Cleanup PosixSource.h"
     86b1522 Unboxed sums: More unit tests
     bfef2eb StgCmmBind: Some minor simplifications
     c4f3d91 Add deepseq dependency and a few NFData instances
     648fd73 Squash space leaks in the result of byteCodeGen
     7f0f1d7 -fprof-auto-top
     1fe5c89 UNPACK the size field of SizedSeq
     d068220 Fix the non-Linux build
     4036c1f Testsuite: fix T10482a
     1967d74 Some typos in comments
     a9251c6 MonadUtils: Typos in comments
     1783011 Fix productivity calculation (#12424)
     9d62f0d Accept better stats for T9675
     8f63ba3 Compute boot-defined TyCon names from ModIface.
     b0a5144 Add mblocks_allocated to GC stats API
     e98edbd Move stat_startGCSync
     d3feb16 Make Unique a newtype
     c06e3f4 Add atomic operations to package.conf.in
     89ae1e8 Relevant Bindings no longer reports shadowed bindings (fixes #12176)
     750553a Use MO_Cmpxchg in Primops.cmm instead of ccall cas(..)
     2078909 Typo in comment
     36565a9 ForeignCall.hs: Remove DrIFT directives
     55f5aed Track the lengths of the thread queues
     988ad8b Fix to thread migration
     d1fe08e Only trace cap/capset events if we're tracing anything else
     4dcbbd1 Remove the DEBUG_<blah> variables, use RtsFlags directly
     9df9490 StgSyn: Remove unused StgLiveVars types
     2f79e79 Add comment about lexing of INLINE and INLINABLE pragma
     0c37aef Update old comment InlinePragma
     b1e6415 More comments about InlinePragmas
     7a06b22 Typo in comment [skip ci]
     7a8ef01 Remove `setUnfoldingInfoLazily`
     a13fda7 Clarify comment on makeCorePair
     d85b26d CmmLive: Remove some redundant exports
     8ecac25 CmmLayoutStack: Minor simplification
     fc66415 Replace an unsafeCoerce with coerce
     db5a226 Fix omission in haddock instance head
     1101045 Trim all spaces after 'version:'
     fe4008f Remove identity update of field componentsConfigs
     f09d654 check that the number of parallel build is greater than 0
     e3e2e49 codeGen: Remove binutils<2.17 hack, fixes T11758
     ca7e1ad Expanded abbreviations in Haddock documentation
     ce13a9a Fix an assertion that could randomly fail
     89fa4e9 Another try to get thread migration right
     8fe1672 Bump `hoopl` submodule, mostly cosmetics
     253fc38 Temporarily mark T1969 perf test as broken (#12437)
     7354f93 StgCmm: Remove unused Bool field of Return sequel
     02614fd Replace some `length . filter` with `count`
     9aa5d87 Util.count: Implement as a left-fold instead of a right-fold
     affcec7 rts/Printer.h: fix constness of argument declaration
     03af399 AsmCodeGen: Give linear-scan and coloring reg. allocators different cc names
     3bfe6a5 RegAlloc: Remove duplicate seqList (use seqList from Util)
     bd51064 RegAlloc: Use IntSet/IntMaps instead of generic Set/Maps
     7a2e933 Use Data.Functor.Const to implement Data.Data internals
     6fe2355 configure.ac: Remove checks for bug 9439
     773e3aa T1969: Enable it again but bump the max residency temporarily
     4d9c22d Fix typo in Data.Bitraversable Haddocks
     fe19be2 Cabal submodule update.
     dd23a4c Actually update haddock.Cabal stats.
     e79bb2c Fix a bug in unboxed sum layout generation
     9684dbb Remove StgRubbishArg and CmmArg
     ac0e112 Improve missing-sig warning
     bd0c310 Fix GHCi perf-llvm build on x86_64
     37a7bcb Update `nofib` submodule to newest commit
     7ad3b49 Misspellings in comments [skip ci]
     18f0687 Fix configure detection.
     ffd4029 fix compilation failure on OpenBSD with system supplied GNU C 4.2.1
     fc1432a Update hoopl submodule (extra .gitignore entry)
     3551e62 refactor test for __builtin_unreachable into Rts.h macro RTS_UNREACHABLE
     da99a7f Darwin: Detect broken NM program at configure time
     f9a11a2 When in sanity mode, un-zero malloc'd memory; fix uninitialized memory bugs.
     d331ace Minor typofix.
     b222ef7 Typofix in System.Environment docs.
     34da8e5 Typo in comment
     efc0372 Not-in-scope variables are always errors
     f352e5c Keep the bindings local during defaultCallStacks
     58e7316 Refactor nestImplicTcS
     d610274 Revert "T1969: Enable it again but bump the max residency temporarily"
     113d50b Add gcoerceWith to Data.Type.Coercion
     b2c5e4c Revert "codeGen: Remove binutils<2.17 hack, fixes T11758"
     896d216 Annotate initIfaceCheck with usage information.
     e907e1f Axe initIfaceTc, tie the knot through HPT (or if_rec_types).
     704913c Support for noinline magic function.
     1f1bd92 Introduce BootUnfolding, set when unfolding is absent due to hs-boot file.
     5a8fa2e When a value Id comes from hi-boot, insert noinline. Fixes #10083.
     8fd1848 Retypecheck both before and after finishing hs-boot loops in --make.
     e528061 We also need to retypecheck before when we do parallel make.
     0d3bf62 Fix #12472 by looking for noinline/lazy inside oversaturated applications.
     f9aa996 pass -z wxneeded or -Wl,-zwxneeded for linking on OpenBSD
     fb0d87f Splice singleton unboxed tuples correctly with Template Haskell
     1f75440 Extra comments, as per SPJ in #12035.
     acdbd16 Move #12403, #12513 users guide notes to 8.2.1 release notes
     89facad Add T12520 as a test
     1766bb3 RtClosureInspect: Fix off-by-one error in cvReconstructType
     613d745 Template Haskell support for unboxed sums
     7a86f58 Comments only: Refer to actually existing Notes
     8d92b88 DmdAnal: Add a final, safe iteration
     d6fd2e3 DmdAnal: Testcase about splitFVs and dmdFix abortion
     ec7fcfd Degrade "case scrutinee not known to diverge for sure" Lint error to warning
     faaf313 WwLib: Add strictness signature to "let x = absentError …"
     1083f45 Fix doc build inconsistency
     ae66f35 Allow typed holes to be levity-polymorphic
     a60ea70 Move import to avoid warning
     0050aff Fix scoping of type variables in instances
     ca8c0e2 Typofix in docs.
     983f660 Template Haskell support for TypeApplications
     822af41 Fix broken Haddock comment
     f4384ef Remove unused DerivInst constructor for DerivStuff
     21c2ebf Missing stderr for T12531.
     9d17560 GhcMake: limit Capability count to CPU count in parallel mode
     a5d26f2 rts: enable parallel GC scan of large (32M+) allocation area
     044e81b OccName: Remove unused DrIFT directive
     ff1931e TcGenDeriv: Typofix
     d168c41 Fix and complete runghc documentation
     6781f37 Clarify pkg selection when multiple versions are available
     83b326c Fix binary-trees regression from unnecessary floating in CorePrep.
     a25bf26 Tag pointers in interpreted constructors
     ef784c5 Fix handling of package-db entries in .ghc.environment files, etc.
     2ee1db6 Fixes #12504: Double-escape paths used to build call to hsc_line
     28b71c5 users_guide: More capabilities than processors considered harmful
     0e74925 GHC: Expose installSignalHandlers, withCleanupSession
     3005fa5 iserv: Show usage message on argument parse failure
     d790cb9 Bump the default allocation area size to 1MB
     d40d6df StgCmmPrim: Add missing MO_WriteBarrier
     d1f2239 Clarify scope of `getQ`/`putQ` state.
     22259c1 testsuite: Failing testcase for #12091
     2d22026 ErrUtils: Expose accessors of ErrDoc and ErrMsg
     a07a3ff A failing testcase for T12485
     9306db0 TysWiredIn: Use dataConWorkerUnique instead of incrUnique
     9cfef16 Add Read1/Read2 methods defined in terms of ReadPrec
     1ad770f Add -flocal-ghci-history flag (#9089).
     010b07a PPC NCG: Implement minimal stack frame header.
     ca6d0eb testsuite: Update bytes allocated of parsing001
     75321ff Add -fdefer-out-of-scope-variables flag (#12170).
     e9b0bf4 Remove redundant-constraints from -Wall (#10635)
     043604c RnExpr: Fix ApplicativeDo desugaring with RebindableSyntax
     dad6a88 LoadIFace: Show known names on inconsistent interface file


More information about the ghc-commits mailing list