[commit: ghc] wip/kavon-nosplit-llvm's head updated: fix build due to the removal of Hoopl.Unique (54321d5)

git at git.haskell.org git at git.haskell.org
Thu Mar 8 03:58:29 UTC 2018


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

Branch 'wip/kavon-nosplit-llvm' now includes:

     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
     4a6eb16 Merge branch 'master' into wip/kavon-nosplit-llvm
     54321d5 fix build due to the removal of Hoopl.Unique


More information about the ghc-commits mailing list