[commit: ghc] wip/rae's head updated: Intermediate state toward new levity polymorphism (089b085)

git at git.haskell.org git at git.haskell.org
Mon Dec 12 13:18:55 UTC 2016


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

Branch 'wip/rae' now includes:

     9bc2233 Fix typo in Data.Bitraverse Haddocks
     31b5806 Clean up outdated comments in template-haskell changelog
     a33b498 Add template-haskell changelog note for #8761
     5fdb854 s/Invisible/Inferred/g s/Visible/Required/g
     4cc5a39 Refactor tcInferArgs and add comments.
     8c1cedd Allow building static libs.
     da60e3e rts/Linker.c: Improve ugly C pre-processor hack
     7843c71 Make T8761 deterministic, I hope
     ff1cc26 Don't run the run_command tests with ext-interp
     82282e8 Remove some `undefined`s
     60c24b2 Typos in user manual and code: recurisve -> recursive
     afa6e83 rts/Linker.c: Rename ONLY_USED_x86_64_HOST_ARCH macro
     bbf0aa2 Testsuite: never pick up .T files in .run directories
     7593c2f Testsuite: report duplicate testnames when `make TEST=<name>`
     1f45bce Testsuite: remove one level of indentation [skip ci]
     206b4a1 Testsuite: simplify extra_file handling
     bafd615 Testsuite: do not print timeout message
     58f0086 Testsuite: open/close stdin/stdout/stderr explicitly
     d8e9b87 Testsuite: cleanup printing of summary
     782cacf Testsuite: framework failure improvements (#11165)
     6b3b631 Testsuite: run all indexed-types ways on ./validate --slow
     0eb0378 Testsuite: do not add -debug explicitly in .T file
     3fb9837 Testsuite: mark tests expect_broken
     af21e38 Don't omit any evidence bindings
     23b80ac Deal correctly with unused imports for 'coerce'
     dc62a22 Wibble error message for #11471
     dd92c67 Stop the simplifier from removing StaticPtr binds.
     2e9079f Test Trac #12185
     848e3ce Testsuite: fixes for python2.6 support
     9a645a1 Refactor match to not use Unique order
     8f7194f Double the file descriptor limit for openFile008
     1084d37 Testsuite: use ignore_stderr/stdout instead of ignore_output
     24194a6 Fix pretty-printer for IfaceCo
     e8d6271 Testsuite: do not depend on sys.stdout.encoding
     fb6e2c7 Delete Ord Unique
     9854f14 Add a new determinism test
     b6b20a5 Reorganize some determinism tests
     480e066 Remove ufmToList
     b8b3e30 Axe RecFlag on TyCons.
     0701db1 Updates to handle new Cabal
     430f5c8 Trac #11554 fix loopy GADTs
     6a5d13c nativeGen: Allow -fregs-graph to be used
     f68d40c ghc-pkg: Drop trailing slashes in computing db paths
     f1e16e9 CmmExpr: remove unused `vgcFlag` function
     b65363d Fix check_uniques in non-unicode locale
     0afc41b Testsuite: be less strict about topHandler03's stderr
     c27ce26 users-guide: Fix markup in release notes
     81b437b Add NamedThing (GenLocated l e) instance
     b412d82 Allow one type signature for multiple pattern synonyms
     6ba4197 rules/sphinx.mk: stop xelatex on error
     ee8d1fa Remove unused oc->isImportLib (#12230)
     6377757 Linker: some extra debugging / logging
     cbfeff4 Remove uniqSetToList
     0d522b8 Document some benign nondeterminism
     0ab63cf Kill varEnvElts in seqDmdEnv
     01f449f Fix 32-bit build failures
     9031382 MkCore: Fix some note names
     a6819a0 base: Add release date to changelog
     bf7cbe7 users-guide: Note multiple pattern signature change in relnotes
     afec447 testsuite: Add testcase for #12355
     2a3af15 Treat duplicate pattern synonym signatures as an error
     3b2deca users-guide: Remove static field type from rts-flag
     331febf CallArity: Use not . null instead of length > 0
     0bd7c4b Enum: Ensure that operations on Word fuse
     18e71e4 Revert "Fix 32-bit build failures"
     890ec98 Revert "Linker: some extra debugging / logging"
     e10497b Kill some varEnvElts
     85aa6ef Check generic-default method for ambiguity
     1267048 Extra ASSERTs for nameModule
     55e43a6 Use DVarEnv for vectInfoVar
     5f79394 Delete out-of-date comment
     895eefa Make unique auxiliary function names in deriving
     cbe30fd Tidy up tidying
     f2d36ea White space only
     6cedef0 Test Trac #12133
     27fc75b Document codegen nondeterminism
     18b782e Kill varEnvElts in zonkEnvIds
     1b058d4 Remove varEnvElts
     b7b130c Fix GetTime.c on Darwin with clock_gettime
     f560a03 Adds x86_64-apple-darwin14 target.
     567dbd9 Have addModFinalizer expose the local type environment.
     56f47d4 Mention addModFinalizer changes in release notes.
     672314c Switch to LLVM version 3.8
     b9cea81 Show testcase where demand analysis abortion code fails
     979baec --without-libcharset disables the use of libcharset
     bedd620 Style changes for UniqFM
     6ed7c47 Document some codegen nondeterminism
     9858552 Use deterministic maps for FamInstEnv
     34085b5 Correct the message displayed for syntax error (#12146)
     64bce8c Add Note [FamInstEnv determinism]
     6e280c2 Utils: Fix `lengthIs` and `lengthExceeds` for negative args
     0481324 Use UniqDFM for InstEnv
     b8cd94d GHC.Stack.CCS: Fix typo in Haddocks
     91fd87e FastString: Reduce allocations of concatFS
     15751f2 FastString: Add IsString instance
     c4a9dca FastString: Supply mconcat implementation
     fc53d36 OccName: Implement startsWithUnderscore in terms of headFS
     eb3d659 OccName: Avoid re-encoding derived OccNames
     4f21a51 Kill eltsUFM in classifyTyCons
     6c7c193 DsExpr: Remove usage of concatFS in fingerprintName
     0177c85 Testsuite: expose TEST_CC (path to gcc)
     f53d761 TysWiredIn: Use UniqFM lookup for built-in OccNames
     9a3df1f check-api-annotations utility loads by filename
     17d0b84 Add -package-env to the flags reference
     372dbc4 Pretty: delete really old changelog
     45d8f4e Demand analyser: Implement LetUp rule (#12370)
     18ac80f tidyType: Rename variables of nested forall at once
     cd0750e tidyOccNames: Rename variables fairly
     37aeff6 Added type family dependency to Data.Type.Bool.Not
     b35e01c Bring comments in TcGenGenerics up to date
     a9bc547 Log heap profiler samples to event log
     ffe4660 IfaceEnv: Only check for built-in OccNames if mod is GHC.Types
     24f5f36 Binary: Use ByteString's copy in getBS
     0f0cdb6 Bugfix for bug 11632: `readLitChar` should consume null characters
     1ba79fa CodeGen: Way to dump cmm only once (#11717)
     89a8be7 Pretty: remove a harmful $! (#12227)
     5df92f6 hp2ps: fix invalid PostScript for names with parentheses
     d213ab3 Fix misspellings of the word "instance" in comments
     3fa3fe8 Make DeriveFunctor work with unboxed tuples
     514c4a4 Fix Template Haskell reification of unboxed tuple types
     1fc41d3 Make okConIdOcc recognize unboxed tuples
     0df3f4c Fix PDF build for the User's Guide.
     98b2c50 Support SCC pragmas in declaration context
     e46b768 Make Data.{Bifoldable,Bitraversable} -XSafe
     908f8e2 TcInteract: Add braces to matchClassInst trace output
     8de6e13 Fix bytecode generator panic
     cac3fb0 Cleanup PosixSource.h
     a0f83a6 Data.Either: Add fromLeft and fromRight (#12402)
     627c767 Update docs for partial type signatures (#12365)
     ed48098 InstEnv: Ensure that instance visibility check is lazy
     9513fe6 Clean up interaction between name cache and built-in syntax
     a4f2b76 testsuite: Add regression test for #12381
     93acc02 Add another testcase for #12082
     cf989ff Compact Regions
     83e4f49 Revert "Clean up interaction between name cache and built-in syntax"
     714bebf Implement unboxed sum primitive type
     a09c0e3 Comments only
     9c54185 Comments + tiny refactor of isNullarySrcDataCon
     8d4760f Comments re ApThunks + small refactor in mkRhsClosure
     6a4dc89 Bump Haddock submodule
     8265c78 Fix and document Unique generation for sum TyCon and DataCons
     e710f8f Correct a few mistyped words in prose/comments
     bbf36f8 More typos in comments
     fb34b27 Revert "Cleanup PosixSource.h"
     86b1522 Unboxed sums: More unit tests
     bfef2eb StgCmmBind: Some minor simplifications
     c4f3d91 Add deepseq dependency and a few NFData instances
     648fd73 Squash space leaks in the result of byteCodeGen
     7f0f1d7 -fprof-auto-top
     1fe5c89 UNPACK the size field of SizedSeq
     d068220 Fix the non-Linux build
     4036c1f Testsuite: fix T10482a
     1967d74 Some typos in comments
     a9251c6 MonadUtils: Typos in comments
     1783011 Fix productivity calculation (#12424)
     9d62f0d Accept better stats for T9675
     8f63ba3 Compute boot-defined TyCon names from ModIface.
     b0a5144 Add mblocks_allocated to GC stats API
     e98edbd Move stat_startGCSync
     d3feb16 Make Unique a newtype
     c06e3f4 Add atomic operations to package.conf.in
     89ae1e8 Relevant Bindings no longer reports shadowed bindings (fixes #12176)
     750553a Use MO_Cmpxchg in Primops.cmm instead of ccall cas(..)
     2078909 Typo in comment
     36565a9 ForeignCall.hs: Remove DrIFT directives
     55f5aed Track the lengths of the thread queues
     988ad8b Fix to thread migration
     d1fe08e Only trace cap/capset events if we're tracing anything else
     4dcbbd1 Remove the DEBUG_<blah> variables, use RtsFlags directly
     9df9490 StgSyn: Remove unused StgLiveVars types
     2f79e79 Add comment about lexing of INLINE and INLINABLE pragma
     0c37aef Update old comment InlinePragma
     b1e6415 More comments about InlinePragmas
     7a06b22 Typo in comment [skip ci]
     7a8ef01 Remove `setUnfoldingInfoLazily`
     a13fda7 Clarify comment on makeCorePair
     d85b26d CmmLive: Remove some redundant exports
     8ecac25 CmmLayoutStack: Minor simplification
     fc66415 Replace an unsafeCoerce with coerce
     db5a226 Fix omission in haddock instance head
     1101045 Trim all spaces after 'version:'
     fe4008f Remove identity update of field componentsConfigs
     f09d654 check that the number of parallel build is greater than 0
     e3e2e49 codeGen: Remove binutils<2.17 hack, fixes T11758
     ca7e1ad Expanded abbreviations in Haddock documentation
     ce13a9a Fix an assertion that could randomly fail
     89fa4e9 Another try to get thread migration right
     8fe1672 Bump `hoopl` submodule, mostly cosmetics
     253fc38 Temporarily mark T1969 perf test as broken (#12437)
     7354f93 StgCmm: Remove unused Bool field of Return sequel
     02614fd Replace some `length . filter` with `count`
     9aa5d87 Util.count: Implement as a left-fold instead of a right-fold
     affcec7 rts/Printer.h: fix constness of argument declaration
     03af399 AsmCodeGen: Give linear-scan and coloring reg. allocators different cc names
     3bfe6a5 RegAlloc: Remove duplicate seqList (use seqList from Util)
     bd51064 RegAlloc: Use IntSet/IntMaps instead of generic Set/Maps
     7a2e933 Use Data.Functor.Const to implement Data.Data internals
     6fe2355 configure.ac: Remove checks for bug 9439
     773e3aa T1969: Enable it again but bump the max residency temporarily
     4d9c22d Fix typo in Data.Bitraversable Haddocks
     fe19be2 Cabal submodule update.
     dd23a4c Actually update haddock.Cabal stats.
     e79bb2c Fix a bug in unboxed sum layout generation
     9684dbb Remove StgRubbishArg and CmmArg
     ac0e112 Improve missing-sig warning
     bd0c310 Fix GHCi perf-llvm build on x86_64
     37a7bcb Update `nofib` submodule to newest commit
     7ad3b49 Misspellings in comments [skip ci]
     18f0687 Fix configure detection.
     ffd4029 fix compilation failure on OpenBSD with system supplied GNU C 4.2.1
     fc1432a Update hoopl submodule (extra .gitignore entry)
     3551e62 refactor test for __builtin_unreachable into Rts.h macro RTS_UNREACHABLE
     da99a7f Darwin: Detect broken NM program at configure time
     f9a11a2 When in sanity mode, un-zero malloc'd memory; fix uninitialized memory bugs.
     d331ace Minor typofix.
     b222ef7 Typofix in System.Environment docs.
     34da8e5 Typo in comment
     efc0372 Not-in-scope variables are always errors
     f352e5c Keep the bindings local during defaultCallStacks
     58e7316 Refactor nestImplicTcS
     d610274 Revert "T1969: Enable it again but bump the max residency temporarily"
     113d50b Add gcoerceWith to Data.Type.Coercion
     b2c5e4c Revert "codeGen: Remove binutils<2.17 hack, fixes T11758"
     896d216 Annotate initIfaceCheck with usage information.
     e907e1f Axe initIfaceTc, tie the knot through HPT (or if_rec_types).
     704913c Support for noinline magic function.
     1f1bd92 Introduce BootUnfolding, set when unfolding is absent due to hs-boot file.
     5a8fa2e When a value Id comes from hi-boot, insert noinline. Fixes #10083.
     8fd1848 Retypecheck both before and after finishing hs-boot loops in --make.
     e528061 We also need to retypecheck before when we do parallel make.
     0d3bf62 Fix #12472 by looking for noinline/lazy inside oversaturated applications.
     f9aa996 pass -z wxneeded or -Wl,-zwxneeded for linking on OpenBSD
     fb0d87f Splice singleton unboxed tuples correctly with Template Haskell
     1f75440 Extra comments, as per SPJ in #12035.
     acdbd16 Move #12403, #12513 users guide notes to 8.2.1 release notes
     89facad Add T12520 as a test
     1766bb3 RtClosureInspect: Fix off-by-one error in cvReconstructType
     613d745 Template Haskell support for unboxed sums
     7a86f58 Comments only: Refer to actually existing Notes
     8d92b88 DmdAnal: Add a final, safe iteration
     d6fd2e3 DmdAnal: Testcase about splitFVs and dmdFix abortion
     ec7fcfd Degrade "case scrutinee not known to diverge for sure" Lint error to warning
     faaf313 WwLib: Add strictness signature to "let x = absentError …"
     1083f45 Fix doc build inconsistency
     ae66f35 Allow typed holes to be levity-polymorphic
     a60ea70 Move import to avoid warning
     0050aff Fix scoping of type variables in instances
     ca8c0e2 Typofix in docs.
     983f660 Template Haskell support for TypeApplications
     822af41 Fix broken Haddock comment
     f4384ef Remove unused DerivInst constructor for DerivStuff
     21c2ebf Missing stderr for T12531.
     9d17560 GhcMake: limit Capability count to CPU count in parallel mode
     a5d26f2 rts: enable parallel GC scan of large (32M+) allocation area
     044e81b OccName: Remove unused DrIFT directive
     ff1931e TcGenDeriv: Typofix
     d168c41 Fix and complete runghc documentation
     6781f37 Clarify pkg selection when multiple versions are available
     83b326c Fix binary-trees regression from unnecessary floating in CorePrep.
     a25bf26 Tag pointers in interpreted constructors
     ef784c5 Fix handling of package-db entries in .ghc.environment files, etc.
     2ee1db6 Fixes #12504: Double-escape paths used to build call to hsc_line
     28b71c5 users_guide: More capabilities than processors considered harmful
     0e74925 GHC: Expose installSignalHandlers, withCleanupSession
     3005fa5 iserv: Show usage message on argument parse failure
     d790cb9 Bump the default allocation area size to 1MB
     d40d6df StgCmmPrim: Add missing MO_WriteBarrier
     d1f2239 Clarify scope of `getQ`/`putQ` state.
     22259c1 testsuite: Failing testcase for #12091
     2d22026 ErrUtils: Expose accessors of ErrDoc and ErrMsg
     a07a3ff A failing testcase for T12485
     9306db0 TysWiredIn: Use dataConWorkerUnique instead of incrUnique
     9cfef16 Add Read1/Read2 methods defined in terms of ReadPrec
     1ad770f Add -flocal-ghci-history flag (#9089).
     010b07a PPC NCG: Implement minimal stack frame header.
     ca6d0eb testsuite: Update bytes allocated of parsing001
     75321ff Add -fdefer-out-of-scope-variables flag (#12170).
     e9b0bf4 Remove redundant-constraints from -Wall (#10635)
     043604c RnExpr: Fix ApplicativeDo desugaring with RebindableSyntax
     dad6a88 LoadIFace: Show known names on inconsistent interface file
     3fb8f48 Revert "testsuite: Update bytes allocated of parsing001"
     a69371c users_guide: Document removal of -Wredundant-constraints from -Wall
     ad1e072 users_guide: Move addModFinalizer mention to 8.0.2 release notes
     1f5d4a3 users_guide: Move -fdefer-out-of-scope-variables note to 8.0.2 relnotes
     da920f6 users_guide: Move initGhcMonad note to 8.0.2 relnotes
     a48de37 restore -fmax-worker-args handling (Trac #11565)
     1e39c29 Kill vestiages of DEFAULT_TMPDIR
     8d35e18 Fix startsVarSym and refactor operator predicates (fixes #4239)
     b946cf3 Revert "Fix startsVarSym and refactor operator predicates (fixes #4239)"
     f233f00 Fix startsVarSym and refactor operator predicates (fixes #4239)
     e5ecb20 Added support for deprecated POSIX functions on Windows.
     0cc3931 configure.ac: fix --host= handling
     818760d Fix #10923 by fingerprinting optimization level.
     36bba47 Typos in notes
     33d3527 Protect StablPtr dereference with the StaticPtr table lock.
     133a5cc ghc-cabal: accept EXTRA_HC_OPTS make variable
     f93c363 extend '-fmax-worker-args' limit to specialiser (Trac #11565)
     ac2ded3 Typo in comment
     57aa6bb Fix comment about result
     f8b139f test #12567: add new testcase with expected plugin behaviour
     1805754 accept current (problematic) output
     cdbb9da cleanup: drop 11 years old performance hack
     71dd6e4 Don't ignore addTopDecls in module finalizers.
     6ea6242 Turn divInt# and modInt# into bitwise operations when possible
     8d00175 Less scary arity mismatch error message when deriving
     4ff4929 Make generated Ord instances smaller (per #10858).
     34010db Derive the Generic instance in perf/compiler/T5642
     05b497e distrib: Fix libdw bindist check
     a7a960e Make the test for #11108 less fragile
     dcc4904 Add failing testcase for #12433
     feaa31f Remove references to -XRelaxedPolyRec
     5eab6a0 Document meaning of order of --package-db flags, fixes #12485.
     a8238a4 Update unix submodule to latest HEAD.
     65d9597 Add hook for creating ghci external interpreter
     1b5f920 Make start address of `osReserveHeapMemory` tunable via command line -xb
     7b4bb40 Remove -flocal-ghci-history from default flags
     710f21c Add platform warning to Foreign.C.Types
     158288b Generalise type of mkMatchGroup to unify with mkMatchGroupName
     04184a2 Remove uses of mkMatchGroupName
     7b7ea8f Fix derived Ix instances for one-constructor GADTs
     0e7ccf6 Fix TH ppr output for list comprehensions with only one Stmt
     454033b Add hs_try_putmvar()
     03541cb Be less picky about reporing inaccessible code
     21d0bfe Remove unused exports
     35086d4 users_guide: Fix Docbook remnant
     b451fef users_guide: #8761 is now fixed
     c6ac1e5 users_guide: TH now partially supports typed holes
     6555c6b rts: Disable -hb with multiple capabilities
     5eeabe2 Test wibbles for commit 03541cba
     ec3edd5 Testsuite wibbles, to the same files
     505a518 Comments and white space only
     8074e03 Comments and white space only
     876b00b Comments and white space
     86836a2 Fix codegen bug in PIC version of genSwitch (#12433)
     9123845 tryGrabCapability should be using TRY_ACQUIRE_LOCK
     626db8f Unify CallStack handling in ghc
     a001299 Comments only
     a72d798 Comments in TH.Syntax (Trac #12596)
     97b47d2 Add test case for #7611
     ea310f9 Remove directories from include paths
     14c2e8e Codegen for case: Remove redundant void id checks
     6886bba Bump Haddock submodule to fix rendering of class methods
     8bd3d41 Fix failing test T12504
     9cbcdb4 shutdownHaskellAndExit: just do a normal hs_exit() (#5402)
     74c4ca0 Expose hs_exit_(rtsFalse) as hs_exit_nowait()
     3a17916 Improved documentation for Foreign.Concurrent (#12547)
     9766b0c Fix #12442.
     d122935 Mark mapUnionFV as INLINABLE rather than INLINE
     68f72f1 Replace INLINEABLE by INLINABLE (#12613)
     55d92cc Update test output
     bc7c730 Pattern Synonyms documentation update
     796f0f2 Print foralls in user format
     b0ae0dd Remove #ifdef with never fulfilled condition
     c36904d Fix layout of MultiWayIf expressions (#10807)
     f897b74 TH: Use atomicModifyIORef' for fresh names
     0b6024c Comments and manual only: spelling
     13d3b53 Test Trac #12634
     f21eedb Check.hs: Use actual import lists instead of comments
     0b533a2 A bit of tracing about flattening
     2fbfbca Fix desugaring of pattern bindings (again)
     66a8c19 Fix a bug in occurs checking
     3012c43 Add Outputable Report in TcErrors
     b612da6 Fix impredicativity (again)
     fc4ef66 Comments only
     5d473cd Add missing stderr file
     3f27237 Make tcrun042 fail
     28a00ea Correct spelling in note references
     b3d55e2 Document Safe Haskell restrictions on Generic instances
     9e86276 Implement deriving strategies
     b61b7c2 CodeGen X86: fix unsafe foreign calls wrt inlining
     59d7ee5 GHCi: Don't remove shadowed bindings from typechecker scope.
     3c17905 Support more than 64 logical processors on Windows
     151edd8 Recognise US spelling for specialisation flags.
     f869b23 Move -dno-debug-output to the end of the test flags
     d1b4fec Mark T11978a as broken due to #12019
     1e795a0 Use check stacking on Windows.
     c93813d Add NUMA support for Windows
     2d6642b Fix interaction of record pattern synonyms and record wildcards
     1851349 Don't warn about name shadowing when renaming the patten in a PatSyn decl
     ce3370e PPC/CodeGen: fix lwa instruction generation
     48ff084 Do not warn about unused underscore-prefixed fields (fixes Trac #12609)
     0014fa5 ghc-pkg: Allow unregistering multiple packages in one call
     b0d53a8 Turn `__GLASGOW_HASKELL_LLVM__` into an integer again
     f547b44 Eliminate some unsafeCoerce#s with deriving strategies
     23cf32d Disallow standalone deriving declarations involving unboxed tuples or sums
     4d2b15d validate: Add --build-only
     42f1d86 runghc: use executeFile to run ghc process on POSIX
     3630ad3 Mark #6132 as broken on OS X
     8cab9bd Ignore output from derefnull and divbyzero on Darwin
     e9104d4 DynFlags: Fix absolute import path to generated header
     eda5a4a testsuite: Mark test for #12355 as unbroken on Darwin.
     22c6b7f Update Cabal submodule to latest version.
     8952cc3 runghc: Fix import of System.Process on Windows
     7a6731c genapply: update source file in autogenerated text
     c5d6288 Mark zipWithAndUnzipM as INLINABLE rather than INLINE
     e4cf962 Bring Note in TcDeriv up to date
     465c6c5 Improve error handling in TcRnMonad
     58ecdf8 Remove unused T12124.srderr
     4a03012 Refactor TcDeriv and TcGenDeriv
     a2bedb5 RegAlloc: Make some pattern matched complete
     57a207c Remove dead code “mkHsConApp”
     cbe11d5 Add compact to packages so it gets cleaned on make clean.
     e41b9c6 Fix memory leak from #12664
     f3be304 Don't suggest deprecated flags in error messages
     76aaa6e Simplify implementation of wWarningFlags
     082991a Tc267, tests what happens if you forgot to knot-tie.
     3b9e45e Note about external interface changes.
     940ded8 Remove reexports from ghc-boot, help bootstrap with GHC 8.
     887485a Exclude Cabal PackageTests from gen_contents_index.
     00b530d The Backpack patch.
     4e8a060 Distinguish between UnitId and InstalledUnitId.
     5bd8e8d Make InstalledUnitId be ONLY a FastString.
     027a086 Update haddock.Cabal perf for Cabal update.
     61b143a Report that we support Backpack in --info.
     46b78e6 Cabal submodule update.
     e660f4b Rework renaming of children in export lists.
     f2d80de Add trailing comma to fix the build.
     21647bc Fix build
     7b060e1 Generate a unique symbol for signature object stub files, fixes #12673
     bcd3445 Do not segfault if no common root can be found
     8dc72f3 Cleanup PosixSource.h
     6c47f2e Default +RTS -qn to the number of cores
     85e81a8 Turn on -n4m with -A16m or greater
     1a9705c Escape lambda.
     b255ae7 Orient improvement constraints better
     b5c8963 Rename a parameter; trivial refactor
     88eb773 Delete orphan where clause
     76a5477 Move zonking out of tcFamTyPats
     cc5ca21 Improved stats for Trac #1969
     a6111b8 More tests for Trac #12522
     b5be2ec Add test case for #12689
     f8d2c20 Add a broken test case for #12689
     8fa5f5b Add derived shadows only for Wanted constraints
     d2959df Comments and equation ordering only
     bce9908 RnExpr: Actually fail if patterns found in expression
     577effd testsuite: Bump T1969 allocations
     184d7cb Add test for #12411
     042c593 Add test for #12589
     fef1df4 Add test for #12456
     57f7a37 Add missing @since annotations
     2fdf21b Further improve error handling in TcRn monad
     015e9e3 Cabal submodule update.
     1cccb64 Unique: Simplify encoding of sum uniques
     34d933d Clean up handling of known-key Names in interface files
     3991da4 MkIface: Turn a foldr into a foldl'
     aa06883 Improve find_lbl panic message
     90df91a PrelInfo: Fix style
     8c6a3d6 Add missing Semigroup instances for Monoidal datatypes in base
     d5a4e49 Make error when deriving an instance for a typeclass less misleading
     3ce0e0b Build ghc-iserv with --export-dynamic
     6c73932 Check for empty entity string in "prim" foreign imports
     0d9524a Disable T-signals-child test on single-threaded runtime
     e39589e Fix Windows build following D2588
     b501709 Fix Show derivation in the presence of RebindableSyntax/OverloadedStrings
     512541b Add a forward reference for a Note
     afdde48 Correct name of makeStableName in haddock
     3174beb Comments about -Wredundant-constraints
     82b54fc Fix comment typo
     692c8df Fix shadowing in mkWwBodies
     609d2c8 Typo in comment
     a693d1c Correct order of existentials in pattern synonyms
     f7278a9 Fix wrapping order in matchExpectedConTy
     1790762 Test Trac #12681
     db71d97 Reduce trace output slightly
     156db6b Add more variants of T3064 (in comments)
     a391a38 Comments only
     f43db14 Typos in comments
     3adaacd Re-add accidentally-deleted line
     9cb4459 testsuite: Work around #12554
     deed418 testsuite: Mark break011 as broken
     8b84b4f testsuite: Mark T10858 as broken on Windows
     3325435 testsuite: Mark T9405 as broken on Windows
     8bb960e testsuite/driver: Never symlink on Windows
     c6ee773 testsuite/timeout: Ensure that processes are cleaned up on Windows
     17d696f validate: Allow user to override Python interpreter
     7d2df32 testsuite/driver: More Unicode awareness
     5b55e4b testsuite: Eliminate unnecessary compile_timeout_multiplier
     2864ad7 testsuite/driver: Allow threading on Windows
     c5c6d80 testsuite: Mark T7037 as broken on Windows
     cf5eec3 Bump parallel submodule
     8fa2cdb Track dep_finsts in exports hash, as it affects downstream deps.
     f148513 Add option to not retain CAFs to the linker API
     1275994 remove unnecessary ifdef
     46f5f02 fixup! Add option to not retain CAFs to the linker API
     7129861 DynamicLoading: Replace map + zip with zipWith
     161f463 ghc/Main.hs: Add import list to DynamicLoading
     fa8940e fix build failure on Solaris caused by usage of --export-dynamic
     a3bc93e Add some missing RTS symbols
     3866481 Compute export hash based on ALL transitive orphan modules.
     02f2f21 cmm/Hoopl/Dataflow: remove unused code
     1f09c16 Test for newtype with unboxed argument
     2cb8cc2 StgCmmPrim: Add missing write barrier.
     a6094fa configure.ac: Report Unregisterised setting
     518f289 New story for abstract data types in hsig files.
     7e77c4b Support constraint synonym implementations of abstract classes.
     9df4ce4 Only delete instances when merging when there is an exact match.
     01490b4 Mark previously failing backpack tests as passing, with correct output.
     c2142ca Fix Mac OS X build by removing space after ASSERT.
     c23dc61 check-cpp: Make it more robust
     ff225b4 Typos in comments
     45bfd1a Refactor typechecking of pattern bindings
     82efad7 Comments and trivial refactoring
     cdbc73a Test Trac #12507
     d61c7e8 Make TcLevel increase by 1 not 2
     3f5673f A collection of type-inference refactorings.
     1f09b24 Accept 20% dedgradation in Trac #5030 compile time
     9417e57 Refactor occurrence-check logic
     e1fc5a3 Define emitNewWantedEq, and use it
     6ddba64 Improve TcCanonical.unifyWanted and unifyDerived
     f41a8a3 Add and use a new dynamic-library-dirs field in the ghc-pkg info
     acc9851 Fix failure in setnumcapabilities001 (#12728)
     1050e46 rts: configure.ac should populate HAVE_LIBNUMA instead of USE_LIBNUMA
     a662f46 Skip T5611 on OSX as it fails non-deterministically.
     3cb32d8 Add -Wcpp-undef warning flag
     6e9a51c Refactoring: Delete copied function in backpack/NameShape
     b76cf04 cmm/Hoopl/Dataflow: minor cleanup
     aaede1e rts/package.conf.in: Fix CPP usage
     a6bcf87 Refactoring: Replace when (not ...) with unless in ErrUtils
     f084e68 rts: Move path utilities to separate source file
     1c4a39d Prioritise class-level equality costraints
     1221f81 Don't instantaite when typechecking a pattern synonym
     08ba691 Take account of kinds in promoteTcType
     03b0b8e Test Trac #12174
     853cdae Test Trac #12081
     a182c0e testsuite: Bump peak_megabytes_allocated for T3064
     801c263 Fundeps work even for unary type classes
     9f814b2 Delete extraneous backtick in users' guide
     925d178 Make traceRn behave more like traceTc
     488a9ed rts/linker: Move loadArchive to new source file
     23143f6 Refine ASSERT in buildPatSyn for the nullary case.
     48876ae Remove -dtrace-level
     b8effa7 CmmUtils: remove the last dataflow functions
     3562727 Simple refactor to remove misleading comment
     f9308c2 Collect coercion variables, not type variables
     eefe86d Allow levity-polymorpic arrows
     0eb8934 Fix typo in comment
     cc29eb5 Revert "rts/linker: Move loadArchive to new source file"
     815b837 Minor doc addition as requested in #12774.
     7187ded Clarify comments on kinds (Trac #12536)
     aae2b3d Make it possible to use +RTS -qn without -N
     60343a4 Add test for #12732
     5ebcb3a Document unpackClosure# primop
     4b300a3 Minor refactoring in stg_unpackClosurezh
     4e088b4 Fix a bug in parallel GC synchronisation
     7ddbdfd Zap redundant imports
     80d4a03 Typos in comments
     795be0e Align GHCi's library search order more closely with LDs
     0b70ec0 Have static pointers work with -fno-full-laziness.
     19ce8a5 Sparc*: Prevent GHC from doing unaligned accesses
     79fb6e6 Tiny refactor
     9968949 Get rid of TcTyVars more assiduously
     7a50966 Simplify the API for TcHsType.kcHsTyVarBndrs
     f4a14d6 Use substTyUnchecked in TcMType.new_meta_tv_x
     13508ba Fix Trac #12797: approximateWC
     623b8e4 Renaming and comments in CorePrep
     8a5960a Uninstall signal handlers
     cc4710a testsuite: Simplify kernel32 glue logic
     f4fb3bc linker: Split out CacheFlush logic
     abfa319 linker: Shuffle configuration into LinkerInternals.h
     43c8c1c linker: Move mmapForLinker declaration into LinkerInternals.h
     3f05126 linker: Split symbol extras logic into new source file
     c3446c6 Shuffle declarations into LinkerInternals.h
     6ea0b4f linker: Split PEi386 implementation into new source file
     f6c47df linker: Split MachO implementation into new source file
     bdc262c linker: Split ELF implementation into separate source file
     6fecb7e linker: Move ARM interworking note to SymbolExtras.c
     dc4d596 Hoopl/Dataflow: make the module more self-contained
     80076fa Add notes describing SRT concepts
     b5460dd Add testcase for #12757
     967dd5c Merge cpe_ExprIsTrivial and exprIsTrivial
     eaa3482 testsuite: Update T10858 allocations
     ec22bac Add test for #12788
     f46bfeb API Annotations: make all ModuleName Located
     a977c96 Omit unnecessary linker flags
     e43f05b Add comments from Trac #12768
     7b0ae41 Remove a debug trace
     2cdd9bd Take account of injectivity when doing fundeps
     b012120 Handle types w/ type variables in signatures inside patterns (DsMeta)
     1cab42d Update release notes for type sigs in TH patterns patch
     1c886ea Stop -dno-debug-output suppressing -ddump-tc-trace
     25c8e80 Add tracing infrastructure to pattern match checker
     630d881 Allow GeneralizedNewtypeDeriving for classes with associated type families
     ead83db Describe symptoms of (and the cure for) #12768 in 8.0.2 release notes
     1964d86 Some minor linker cleanups.
     7d988dd Fix broken validate build.
     91f9e13 Fix hs_try_putmvar003 (#12800)
     2e8463b Update 8.0.2 release notes for #12784
     2325afe Fix comment about pointer tagging
     7fe7163 Adapt the (commented out) pprTrace in OccurAnal
     f05d685 Refactoring of mkNewTypeEqn
     317236d Refactor CallStack defaulting slightly
     500d90d ghc-cabal: Use correct name of linker flags env variable
     816d2e4 build system: Include CONF_LD_LINKER_OPTS in ALL_LD_OPTS
     9030d8e configure: Pass HC_OPTS_STAGEx to build system
     bae4a55 Pass -no-pie to GCC
     0a122a4 testsuite: Update allocation numbers for T5631
     e06e21a Add Richard Eisenberg's new email to mailmap
     bef7e78 Read parentheses better
     122d826 rts: Add api to pin a thread to a numa node but without fixing a capability
     aa10c67 rts/linker: Move loadArchive to new source file
     e8ae4dc Update user's guide after D2490
     03e8d26 Prevent GND from inferring an instance context for method-less classes
     60bb9d1 Revert "Pass -no-pie to GCC"
     7a7bb5d Revert "Refactor CallStack defaulting slightly"
     ec0bf81 rts: Fix LoadArchive on OS X
     d421a7e Pass -no-pie to GCC
     46e2bef testsuite: Lower allocations for T876
     7eae862 ghc-pkg: Munge dynamic library directories
     2cfbee8 rts: Fix build when linked with gold
     4e0b8f4 rts: Fix #include of <linker/PEi386.h>
     587dccc Make default output less verbose (source/object paths)
     568e003 template-haskell: Version bump
     ca1b986 ghc: Fix ghc's template-haskell bound
     8cb7bc5 rts: Fix references to UChar
     6c0f10f Kill Type pretty-printer
     55d535d Remove CONSTR_STATIC
     034e01e Accept output for scc003
     e0ca7ff Fix numa001 failure with "too many NUMA nodes"
     cb16890 testsuite: Fix creep of T4029
     011af2b configure: Verify that GCC recognizes -no-pie flag
     1b336d9 Skip 64-bit symbol tables
     98f9759 Hopefully fix build on OS X
     642adec Mark T12041 as expect_broken with -DDEBUG (#12826)
     017d11e Typos in comments, notes and manual
     31d5b6e fixup! Stop the simplifier from removing StaticPtr binds.
     0e58652 Test for unnecessary register spills
     4a835f0 Update xhtml submodule
     a637eeb Don't use mmap symbols when !RTS_LINKER_USE_MMAP
     0135188 Storage.c: Pass a size to sys_icache_invalidate
     fa70b1e Fix -fobject-code with -fexternal-interpreter
     7acee06 Avoid calling newDynFlags when there are no changes
     d3542fa Generalise the implicit prelude import
     8dfca69 Inline compiler/NOTES into X86/Ppr.hs
     b769586 Fix windows validate
     31398fb Test for type synonym loops on TyCon.
     2878604 Correct spelling of command-line option in comment
     cede770 Correct name of Note in comment
     07e40e9 Add Data instance for Const
     18eb57b Revert "Add Data instance for Const"
     9a4983d Pass autoconf triplets to sub-project configures
     20fb781 LLVM generate llvm.expect for conditional branches
     4d4f353 testsuite: Rip out hack for #12554
     04b024a GHCi: Unconditionally import System.Directory
     231a3ae Have reify work for local variables with functional dependencies.
     9c39e09 Switch to LLVM version 3.9
     94d1221 Add missing SMP symbols to RT linker.
     d328abc Spelling in comment only
     3bd1dd4 Add Data instance for Const
     4b72f85 Optimise whole module exports
     6ad94d8 Updated code comment regarding EquationInfo. Trac #12856
     ea37b83 A few typos in comments
     5bce207 testsuite: Add test for #12855
     926469f testsuite: Add test for #12024
     b98dbdf testsuite: Add (still broken) testcase for #12447
     e7ec521 testsuite: Add (still failing) testcase for #12550
     ea76a21 add ieee754 next* functions to math_funs
     514acfe Implement fine-grained `-Werror=...` facility
     4c0dc76 Ignore Hadrian build products.
     7e4b611 Make transformers upstream repository location consistent with others
     1399c8b ghc/hschooks.c: Fix include path of Rts.h
     f430253 Allow to unregister threadWaitReadSTM action.
     14ac372 Collect wildcards in sum types during renaming (#12711)
     d081fcf Make quoting and reification return the same types
     9a431e5 Make a panic into an ASSERT
     0476a64 Fix a bug in mk_superclasses_of
     f04f118 Comments only in TcType
     0123efd Add elemDVarEnv
     1eec1f2 Another major constraint-solver refactoring
     18d0bdd Allow TyVars in TcTypes
     4431e48 Remove redundant kind check
     90a65ad Perf improvements in T6048, T10547
     e319466 Typos in comments
     c1b4b76 Fix a name-space problem with promotion
     f0f4682 Test Trac #12867
     83a952d Test Trac #12845
     a5a3926 Kill off ifaceTyVarsOfType
     bc35c3f Use 'v' instead of 'tpl' for template vars
     edbe831 Use TyVars in a DFunUnfolding
     12eff23 Use TyVars in PatSyns
     5f349fe Improve pretty-printing of types
     eb55ec2 Refactor functional dependencies a bit
     1bfff60 Fix inference of partial signatures
     086b483 A tiny bit more tc tracing
     f8c966c Be a bit more selective about improvement
     6ec2304 Fix an long-standing bug in OccurAnal
     5238842 Typos in comments only [ci skip]
     605af54 Test Trac #12776
     27a6bdf Test Trac #12885
     3aa9368 Comments only (related to #12789)
     abd4a4c Make note of #12881 in 8.0.2 release notes
     f8c8de8 Zonk the free tvs of a RULE lhs to TyVars
     e755930 Typos in comments
     36e3622 Store string as parsed in SourceText for CImport
     1732d7a Define thread primitives if they're supported.
     30cecae users_guide: Bring 8.0.2 release notes up-to-date with ghc-8.0 branch
     f1fc8cb Make diagnostics slightly more colorful
     52222f9b Detect color support
     da5a61e Minor cleanup of foldRegs{Used,Defd}
     2d99da0 testsuite: Mention CLEANUP option in README
     3ec8563 Replace -fshow-source-paths with -fhide-source-paths
     c2268ba Refactor Pattern Match Checker to use ListT
     6845087 Purge GHC of literate Perl
     4d4e7a5 Use newBlockId instead of newLabelC
     7753273 AsmCodeGen: Refactor worker in cmmNativeGens
     6d5c2e7 NCGMonad: Add MonadUnique NatM instance
     eaed140 OrdList: Add Foldable, Traversable instances
     fe3748b testsuite: Bump haddock.compiler allocations
     795f8bd hschooks.c: Ensure correct header file is included
     6f7ed1e Make globals use sharedCAF
     56d7451 Fix type of GarbageCollect declaration
     428e152 Use C99's bool
     758b81d rts: Add missing #include <stdbool.h>
     23dc6c4 Remove most functions from cmm/BlockId
     b92f8e3 Added Eq1, Ord1, Read1 and Show1 instances for NonEmpty
     679ccd1 Hoopl/Dataflow: use block-oriented interface
     0ce59be Fix testsuite threading, timeout, encoding and performance issues on Windows
     dd9ba50 Update test output for Windows
     605bb9b testsuite: Use python3 by default
     20c0614 Update Mingw-w64 bindist for Windows
     ef37580 Fix windows validate.
     be8a47f Tweaks to grammar and such.
     03766cd Rename RuntimeRepPolymorphism to LevityPolymorphism
     e2330b6 Revert "Make globals use sharedCAF"
     c2a2911 Revert "Fix windows validate."
     6c54fa5 testsuite: Add another testcase for #11821
     0200ded Fix typo in functional dependencies doc
     f48f5a9e Ensure flags destined for ld are properly passed
     514c01e Levity polymorphic expressions mustn't be floated-out in let-bindings.
     a452c6e Make note of #12907 in 8.0.2 release notes
     0ac5e0c rts: Fix type of bool literal
     7214e92 testsuite: Remove Unicode literals from driver
     6576bf8 rts: Ensure we always give MADV_DONTNEED a chance in osDecommitMemory
     0f37550 Typos in comments
     a934e25 testsuite: Actually update haddock.compiler allocations
     afb9c30 Reshuffle levity polymorphism checks.
     089b085 Intermediate state toward new levity polymorphism


More information about the ghc-commits mailing list