[commit: ghc] wip/aarch64-regd's head updated: Switch to LLVM version 3.7 (96586c4)

git at git.haskell.org git at git.haskell.org
Fri Oct 9 23:42:54 UTC 2015


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

Branch 'wip/aarch64-regd' now includes:

     7ea156a Refactor RdrName.Provenance, to fix #7672
     cd9c5c6 Allow Any return in foreign prim, fixes #10460.
     08558a3 Move liftData and use it as a default definition for Lift.
     942cfa4 typo: 'Ture' / 'True'
     21d7c85 Travis: Send notifications to author and commiter
     c69b69d ghc-pkg support query by package-key, fixes #9507
     d8f66f1 Re-center perf numbers for haddock.compiler
     75c6e06 Build: make configure and ghc-pkg a bit less chatty
     14652b5 ghc-cabal: don't warn about missing cabal fields
     092082e Build: ./boot && ./configure && make sdist (#8723)
     cac68d0 Build: remove unnecessary CLEANING/=YES check
     5dd0286 Build: remove more unnecessary CLEANING/=YES checks
     d0063e8 Make validate more quiet
     e340f6e Testsuite: add/fix cleanup for certain tests
     07feab1 Testsuite: ignore `stdcall attribute ignored` (#1288)
     0686d76 Testsuite: don't show compile/link info for some tests
     7beb477 Travis: allow user forks
     761fb7c Fix #10488 by unwrapping type synonyms.
     53c1374 Minor code cleanup
     61b96a8 Fix #10489
     dcaaa98 docs: Fix #10416
     ae83a81 Testsuite: only show output diff when test is expected to pass
     328c212 Fix the sdist build
     89223ce Fix the build when SplitObjs=YES
     19ec6a8 Fix for CAF retention when dynamically loading & unloading code
     7944a68 Revert "docs: Fix #10416"
     058af6c Refactor wild card renaming
     a48167e build: Clean testsuite before sdist
     3b55659 Always force the exception in enqueued commands
     bb99671 Revert "The test runner now also works under the msys-native Python."
     43ebe24 Testsuite: delete expect_fail setups for hugs
     3445947 Testsuite: delete expect_fail setups for ghc < 7.1
     4a0b7a1 Build: run autoreconf jobs in parallel
     5828457 make sdist: distclean testsuite for real (#10406)
     ca39b96 docs: Fix #10416
     ddbb97d Another major improvement of "improvement"
     c0dc79f IndTypesPerfMerge no longer seems to requre -M20M
     a66ef35 Fix DWARF generation for MinGW (#10468)
     c1dc421 Update submodule process to master
     da84fd5 Testsuite Windows: fix T8172 (#8172)
     a765f72 Testsuite: mark tests as expect_broken on win64
     506522c Testsuite: mark T4945 as expect_broken (#4945)
     6cefeb3 Testsuite: mention the existence of ticket #10510
     5e66a69 Testsuite: change some expect_fail tests to expect_broken
     a4318c6 Travis: use apt-get -q
     0db0ac4 Removes all occurrences of __MINGW32__ (#10485)
     23582b0 Add failing test for #9562.
     28e04de Remove redundant tcg_visible_orphan_mods, it is recorded in imp_orphs.
     bac927b Revert "Support for multiple signature files in scope."
     c60704f Revert "Change loadSrcInterface to return a list of ModIface"
     ce53138 Delete _MSC_VER when not necessary, fix #10511
     016bbfd docs: Fix unicode alternatives table (fixes #10509).
     0ef7174 Squash typos in comments
     c14bd01 Testsuite: fix the little known CHECK_FILES_WRITTEN=1
     d20031d Add parseExpr and compileParsedExpr and use them in GHC API and GHCi
     892c3e9 Do not copy stack after stack overflow, refix #8435
     dd5cac7 Fix typo in `traceShowM` haddock comment (#10392)
     0a086c8 Docs: it's `gv --orientation=seascape` nowadays (#10497)
     b07dccc Docs: `-XTypeOperators` (#10175)
     e02a4f2 Add versioning section to Backpack docs.
     5ddd904 Testsuite: diff non-whitespace normalised output (#10152)
     6e542a6 Testsuite: add function compile_timeout_multiplier (#10345)
     a508455 UNREG: fix pprHexVal to emit zeros (#10518)
     1cf7fc0 add type annotations to SrcLoc functions
     dd3080f Increase constraint tuple limit to 62 (Trac #10451)
     a607011 Test Trac #10348
     77e5ec8 Demonstrate that inferring Typeable for type literals works
     efa136f Remove derived CFunEqCans after solving givens
     a3f6239 GHCi: fix scoping for record selectors
     a6cbf41 Spelling in comments
     855f56b Improved peak_megabytes_allocated
     2613271 Testsuite: fix framework failure
     89c7168 Fix #10534
     df63736 ghc.mk: Update instances of -auto-all
     1ff7f09 Lexer: Suggest adding 'let' on unexpected '=' token
     0d6c97b Lexer: Suggest adding 'let' on unexpected '=' token
     a90712b users_guide: Various spelling fixes
     d46fdf2 users_guide: Various spelling fixes
     681973c Encode alignment in MO_Memcpy and friends
     a0d158f Encode alignment in MO_Memcpy and friends
     c772f57 Fix #10494
     0de0b14 Fix #10495.
     ace8d4f Fix #10493.
     6644039 Test case for #10428.
     ff82387 Decompose wanted repr. eqs. when no matchable givens.
     93f97be (mostly) Comments only
     f108003 Testsuite wibble around decomposing newtypes.
     7eceffb Refactor handling of decomposition.
     9b105c6 Reimplement Unify.typesCantMatch in terms of apartness.
     298c424 Treat funTyCon like any other TyCon in can_eq_nc.
     a6b8b9c Fix typo in comment
     daf1eee Clarify some comments around injectivity.
     65d4b89 Add `Monoid` instance for `IO`
     f063656 Fix ghc-pkg reports cache out date (#10205)
     0760b84 Update foreign export docs, fixes #10467
     b98ca17 Make enum01/enum02/enum03 tests clang-compatible
     023a0ba Care with impossible-cons in combineIdenticalAlts
     5879d5a Report arity errors correctly despite kinds
     f4370c6 Comments only
     4a7a6c3 Rename getCtLoc, setCtLoc
     02bac02 Remove some horrible munging of origins for Coercible
     760b079 A bit more tracing
     0899911 Comments plus tiny refactoring
     ee64369 Refactor filterAlts into two parts
     5d98b68 Trac #4945 is working again
     72b21c3 Parser: commas_tup_tail duplicate SrcSpan on "Missing" value
     ba7c8e5 Test Trac #10503
     c45f8ce Elaborate test for Trac #10403
     40698fe Spelling in comments
     e283cec testsuite: mark T4945 as expect_broken
     440d1bc docs: Unbreak the PS/PDF builds for the User's Guide (#10509)
     7d5a845 should_run/allocLimit4: disable ghci way
     e491803 Amend tcrun024, tcrun025 after Trac #7854 fix
     7c2293a Amend tcrun037 after Trac #7854 fix
     2c6a041 Fix a couple of tests for GHCi/-O* (Trac #10052)
     5cc08eb Recognise 'hardhloat' as a valid vendor in a host tuple
     f2ffdc6 Updated output for test ghci024
     85d5397 Make GHC install libraries to e.g. xhtml-3000.2.1-0ACfOp3hebWD9jGWE4v4Gh.
     0cb1f5c Filter orphan rules based on imports, fixes #10294 and #10420.
     29bc13a Fix all.T for T8131/T8131b.
     15ef5fc Remove duplicate test.
     13ba87f Build system: unset HADDOCK when haddock is not found
     4854fce Change `Typeable` instance for type-lis to use the Known* classes.
     38f3745 Add parsePattern parser entry point
     b5a2e87 Documentation: add section on .haskeline file (#2531)
     e60dbf3 Check KnownSymbol => Typeable deduction
     f70fb68 Use -package-id to specify libraries on command line.
     6c5a66a Fix #10551 by using LIB_NAMES.
     01f7e44 Rename $1_$2_$3_LIB_NAME to LIB_FILE.
     55843f1 Further elaborate Trac #10403 test
     c084796 powerpc: add basic support for PLT relocations (#10402)
     73a6265 Make $1 in $1_$2_$3_FOO actually be directory.
     95d5031 Build system: delete unused variables in config.mk.in
     ece2c43 Drop prefix from package keys.
     aa26731 Clean outdated ext-core references in comments.
     4d1316a driver: pass '-fPIC' option to all CC invocations
     9a34864 Improve kind-checking for 'deriving' clauses
     c7b6fb5 Test Trac #10562
     a2f828a Be aware of overlapping global STG registers in CmmSink (#10521)
     a7eee0d Comments only
     3edc186 White space only
     9195927 Improve pretty-printing for CoPat
     ff8a671 Use a Representaional coercion for data families
     0b7e538 Allow recursive unwrapping of data families
     cc0dba1 Minor fix to free-vars in RnTypes
     9014a7e Fix addDataConStrictness
     b69dc73 Don't float out alpha[sig] ~ Int
     97e313c Add module header to test
     2f16a3b Get rid of irrlevant result type signature
     95fc6d5 Get rid of irrelevant impredicative polymoprhism
     fb7b692 Treat out-of-scope variables as holes
     b98ff25 Error message wibbles from out-of-scope changes
     0aaea5b Tiny refactor plus comments
     be0ce87 Fix for crash in setnumcapabilities001
     111ba4b Fix deadlock (#10545)
     7c8ffd3 GHCi docs: layout rule is respected inside :{ :}
     cbd9278 Comments only
     caf9d42 Small doc fixes
     0696fc6 Improve CPR behavior for strict constructors
     7c07cf1 closeOverKinds *before* oclose in coverage check
     614ba3c Kill off sizePred
     8e34783 Make fvType ignore kinds
     a64a26f Better tracing and tiny refactoring
     ceb3c84 Improve error message for Typeable k (T k)
     0e1e798 Test Trac #10524
     8d221bb Test #10582
     89834d6 Add -fcross-module-specialise flag
     302d937 Add -fcross-module-specialise flag
     bb0e462 Mask to avoid uncaught ^C exceptions
     9b5df2a Update performance numbers due to #10482
     c6bb2fc Correct BangPat SrcSpan calculation
     c495c67 Build system: remove unused variable CHECK_PACKAGES
     897a46c Testsuite: accept T2592.stderr (minor changes)
     6b9fc65 Testsuite: put extra_run_opts last on command line
     daa5097 Build system: prevent "warning: overriding commands for target..."
     bbf6078 disable check for .init_array section on OpenBSD
     9aa0e4b ghc-pkg: use read/writeUTF8File from Cabal
     bdd0b71 bin-package-db: copy paste writeFileAtomic from Cabal
     bdf7f13 Build system: rename bindist to bindist-list...
     d3c1dda Implement PowerPC 64-bit native code backend for Linux
     b5e1944 Use `+RTS -G1` for more stable residency measurements (#9675)
     1d6ead7 Enable using qualified field of constructor in GHCi
     f856383 Fix Trac #10519
     f07b7a8 Remove unnecessary OrdList from decl parser.
     6400c76 users_guide: Describe order-dependence of -f and -O flags
     e4bf4bf Remove redundant parser entry point
     8b55788 Add "since" column for LANGUAGE extensions in user guide
     39d83f2 Generalize traceM, traceShowM (fixes #10023)
     6b01d3c parser: Allow Lm (MODIFIER LETTER) category in identifiers
     889c81c Fix some validation errors.
     69beef5 Replace usages of `-w` by `-fno-warn`s
     b1d1c65 Support MO_{Add,Sub}IntC and MO_Add2 in the LLVM backend
     124f399 Testsuite: add -ignore-dot-ghci to some tests
     ced27de Remove dead code / overlapping pattern (#9723)
     a4b0342 Lexer: remove -fno-warn-unused-do-bind
     aa778c8 Comments only [skip ci]
     c875b08 Use -fno-warn-unused-imports instead of hiding `ord`
     8e12a21 Lexer.x and Parser.y: delete dead code
     5d48e67 Easy way to defer type errors (implements #8353)
     3fabb71 Fix typo [skip ci] (#10605)
     75de613 rts: fix incorrect checking start for -x arguments (#9839)
     edb2c54 Remove Hugs specific test setups (omit_compiler_type)
     7a3d85e Remove all *.stderr/stdout-hugs files
     4681f55 Specialise: Avoid unnecessary recomputation of free variable information
     2765fcf Remove warnings for -fwarn-incomplete-patterns
     a07898e Spelling in comments
     9180df1 Fix offset calculation in __stg_gc_fun
     aaa0cd2 Don't eagerly blackhole single-entry thunks (#10414)
     d27e7fd Add more discussion of black-holing logic for #10414
     d59cf4e Fix "CPP directive" in comment
     db530f1 Add Note [Warnings in code generated by Alex]
     37de4ad Build system: don't set GhcLibWays explicitly in build.mk.sample (#10536)
     62fcf05 Fix word repetitions in comments
     ebfc2fb Update comments around blackholes
     f753cf1 Allow deferred type error warnings to be suppressed
     31580e2 Fix todo in compiler/nativeGen: Rename Size to Format
     9a3e165 Deferred type errors now throw TypeError (#10284)
     5857e0a fix EBADF unqueueing in select backend (Trac #10590)
     6d69c3a Generalize `Control.Monad.forever`
     d03bcfa always use -fPIC on OpenBSD/AMD64 platform
     00c8d4d Fix #10596 by looking up 'Int' not 'Maybe Int' in the map.
     1967a52 Export more types from GHC.RTS.Flags (#9970)
     8800a73 Backpack: Flesh out more Cabal details
     d71b65f holePackageKey and isHoleModule utility functions.
     3d5f8e7 Unbreak Windows build: delete unusud throwIOIO
     6f9efcb Delete duplicate "Note [Unpack equality predicates]"
     f3bfa3b Broaden Outputable instance for Termination
     85b14a7 Comments only
     4f9d600 Fix Trac #10618 (out of scope operator)
     b29633f Bitmap: Fix thunk explosion
     889824d Document RULES and class methods
     c58dc1a White space only
     b5aabfb Infer types with flexible contexts
     7dcf86f users_guide: Fix errant "a" in RULES/class methods docs
     a6359f2 Add testcase for #10602
     6f1c076 Make mkQualPackage more robust when package key is bad.
     0a3c43f Comments only
     9e86bf1 Better type wildcard errors
     888026d Update .mailmap [skip ci]
     2d06a9f Improve error message for fundeps
     9b1ebba Delete the WayPar way
     d69dfba Fix self-contained handling of ASCII encoding
     ee28a79 T1969: Update max_bytes_used
     a846088 T876 (32-bit): Update bytes allocated
     de6597e perf/compiler: Switch to -G1 and update performance metrics
     b935497 T9872d: Update 32-bit allocations
     d073c77 Do not optimise RULE lhs in substRule
     e922847 Add Linting for Rules
     7da7b0e Make sure rule LHSs are simplified
     875723b Reformat a leading # in a comment
     d7335f7 Test Trac #10463
     02a6b29 Test Trac #10634
     946c8b1 Another comment with a leading # (sigh)
     2e52057 Build system: comments only [skip ci]
     ec197d3 Build system: add `make show!` command (#7810)
     f70f1b6 Build system: delete two unused files
     47ebe26 Build system: delete REGULAR_INSTALL_DYNLIBS and INSTALL_DYNLIBS
     392ff06 Build system: do not build stm and parallel by default
     5764ade Testsuite: delete unused with_namebase
     322ae32 Testsuite: delete remaining only_compiler_types(['ghc']) setups
     783b79b traivs: Use the new container based travis setup
     4dc3877 Testsuite: rename *.stderr-ghc to *.stderr
     ab5257b Testsuite: delete *.stderr-ghc-7.0 *.stdout-ghc-7.0
     4ee658a0 Mark test case for #10294 expect_broken on #10301
     0a40278 Flush stdout in test case for #10596
     8e6a503 Mark test case for #10294 conditionally expect_broken on #10301
     b1063b1 Testsuite: mark T10294 conditionally expect_broken on #10301
     348f5ca Build system: delete fingerprint.py [skip ci]
     a592e9f Remove all references to sync-all
     75fd5dc Don't get a new nursery if we exceeded large_alloc_lim
     9f978b6 Fix #10642.
     74a00bc initGroup: only initialize the first and last blocks of a group
     504c2ae Docs: `sortOn = sortBy (comparing f)` [skip ci]
     02897c5 Failing test case: idArity invariant check, #10181
     e29c2ac CoreUtils: Move seq* functions to CoreSeq
     ae0e340 CoreUtils: Move size utilities to CoreStats
     fa33f45 PprCore: Add size annotations for top-level bindings
     29f8225 CoreLint: Use size-annotated ppr variant
     82f1c78 Fix tests
     ae96c75 Implement -fprint-expanded-synonyms
     415351a Put Opt_Static into defaultFlags if not pc_DYNAMIC_BY_DEFAULT (#7478)
     2c5c297 DeriveFoldable for data types with existential constraints (#10447)
     2c9de9c Handle Char#, Addr# in TH quasiquoter (fixes #10620)
     a5e9da8 Fix off-by-one error in GHCi line reporting (Trac #10578)
     3448f98 Reduce non-determinism in ABI hashes with RULES and instance decls
     bc604bd Update assert to fix retc001 and retc002 (#9243)
     0d4b074 Travis: actually do debug builds
     ac0feec Testsuite: small test cleanups
     f607393 Testsuite: accept new stderr for T9497{a,b,c}-run (#10224)
     a0371c0 Build system: fail when encountering an unknown package tag
     dc6e556 Testsuite: mark T2497 expect_broken_for(#10657, ['optasm', 'optllvm'])
     dcaa486 Testsuite: mark T7919 expect_broken_for(#7919, ['optasm','dyn','optllvm'])
     11f8612 Testsuite: mark 3 tests expect_broken_for(#10181, ['optasm', 'optllvm'])
     16a8739 Testsuite: mark qq007 and qq008 expect_broken(#10181)
     cbb4d78 Testsuite: mark qq007 and qq008 expect_broken(#10047)
     43dafc9 Testsuite: mark gadt/termination expect_broken_for(#10658, ['optasm','optllvm'])
     34bb460 Testsuite: mark array001 and conc034 expect_broken_for(#10659, ['optasm',...])
     9834fea Add regression test for unused implicit parameter warning (#10632)
     4c96e7c Testsuite: add ImpredicativeTypes to T7861 (#7861)
     7f37274 Testsuite: add -XUndecidableInstances to T3500a
     029367e Testsuite: add regression test for missing class constraint
     82ffc80 LlvmCodeGen: add support for MO_U_Mul2 CallishMachOp
     49373ff Support wild cards in TH splices
     c526e09 primops: Add haddocks to BCO primops
     4cd008b Do not treat prim and javascript imports as C imports in TH and QQ
     96de809 Fix primops documentation syntax
     d71d9a9 Testsuite: fix concprog002 (AMP)
     2f18b197 Testsuite: mark concprog002 expect_broken_for(#10661, ['threaded2_hT'])
     d0cf8f1 Testsuite: simplify T8089 (#8089)
     b4ef8b8 Update submodule hpc with fix for #10529
     0c6c015 Revert "Revert "Change loadSrcInterface to return a list of ModIface""
     214596d Revert "Revert "Support for multiple signature files in scope.""
     9ade087 primops: Fix spelling mistake
     e0a3c44 Delete __GLASGOW_HASKELL__ ifdefs for stage0 < 7.8
     8f48fdc Use varToCoreExpr in mkWWcpr_help
     3fbf496 Comments only (superclasses and improvement)
     3509191 Refactor newSCWorkFromFlavoured
     7c0fff4 Improve strictness analysis for exceptions
     cd48797 Comments and white space only
     3c44a46 Refactor self-boot info
     efa7b3a Add NOINLINE for hs-boot functions
     aa78cd6 Documents -dsuppress-unfoldings
     0df2348 Comments and layout only
     a0e8bb7 Implement -dsuppress-unfoldings
     b5c1400 Comments and white space only
     f1d0480 Avoid out-of-scope top-level Ids
     7a6ed66 Comments only
     55754ea Fix test T2497 to avoid infinite loop in RULES
     feaa095 Do occurrence analysis on result of BuiltInRule
     00f3187 Make seq-of-cast rule generate a case
     35eb736 T4945 is working again
     f519cb5 testsuite: Show killed command line on timeout
     97a50d5 configure: Bump minimum bootstrap GHC version to 7.8
     dbe6dac When iconv is unavailable, use an ASCII encoding to encode ASCII
     18c6ee2 Travis: use ghc-7.8.4 as stage0 to fix the build
     d941a89 Validate: by default do show commands
     a7e0326 Validate: document --quiet [skip ci]
     1224bb5 Add utility function isHoleName.
     50b9a7a Revert "Trac #4945 is working again"
     1b76997 Testsuite: recenter haddock.base allocation numbers
     b949c96 Eliminate zero_static_objects_list()
     0d1a8d0 Two step allocator for 64-bit systems
     e3df1b1 Validate: explain THREADS instead of CPUS in --help
     cf57f8f Travis: do pass `--quiet` to validate
     0b12aca Switch from recording IsBootInterface to recording full HscSource.
     adea827 Add ExceptionMonad instance for IOEnv.
     144096e Give more informative panic for checkFamInstConsistency.
     4a9b40d Export alwaysQualifyPackages and neverQualifyPackages.
     939f1b2 Some utility functions for testing IfaceType equality.
     dd365b1 Use lookupIfaceTop for loading IfaceDecls.
     5c3fc92 Fix Trac #10670
     9851275 Comments only
     d784bde Lexer: support consecutive references to Haddock chunks (#10398)
     d2b4df1 Generate .dyn_o files for .hsig files with -dynamic-too
     76e2341 Accept next-docstrings on GADT constructors.
     e78841b Update encoding001 to test the full range of non-surrogate code points
     b5c9426 Parenthesise TypeOperator in import hints
     1852c3d DataCon: Fix redundant import
     4c8e69e rts/sm: Add missing argument names in function definitions
     7ec07e4 Slight refactoring to the fix for #4012
     608e76c Document type functions in the Paterson conditions
     e809ef5 ghci: fixity declarations for infix data constructors (#10018)
     5ff4dad Add a few comments from SPJ on fixity declarations
     f9687ca Library names, with Cabal submodule update
     45c319f Fix line number in T10018 testcase
     30d8349 Comments only
     e161634 Comments about stricteness of catch#
     d53d808 Refactoring around FunDeps
     6e618d7 Improve instanceCantMatch
     09d0505 RetainerProfile: Add missing UNTAG_STATIC_LIST_PTR
     b04bed0 renamer: fix module-level deprecation message
     070f76a -include-pkg-deps takes only one hyphen.
     7e70c06 Use isTrue# around primitive comparisons in integer-gmp
     c55f61c Add missing parentheses in eqBigNatWord#
     474d4cc Comment tweaks only
     f842ad6 Implementation of StrictData language extension
     2178273 Add UInfixT to TH types (fixes #10522)
     81fffc4 Remove runSTRep from PrelNames
     bc4b64c Do not inline or apply rules on LHS of rules
     2d88a53 Improve warnings for rules that might not fire
     09925c3 Revert "RetainerProfile: Add missing UNTAG_STATIC_LIST_PTR"
     a1e8620 Revert "Eliminate zero_static_objects_list()"
     e343c0a Test case for #10698
     a1dd7dd Fallout from more assiduous RULE warnings
     f83aab9 Eliminate zero_static_objects_list()
     2dbb01a Add a missing check for -fcpr-off
     fac11f8 Comments only
     4e8d74d Deal with phantom type variables in rules
     92d2567 Define DsUtils.mkCastDs and use it
     fa915af Spit out a little more info with -dppr-debug
     e4114c8 Fix an outright error in competesWith
     499b926 Fix Trac #10694: CPR analysis
     918dcf8 The parallel package has warnings
     2e33b9c Modify spec002 to be less trivial
     72d23c3 Better treatment of signatures in cls/inst
     24afe6d Fix missing files
     5a8a8a6 Don't allowInterrupt inside uninterruptibleMask
     9f7cdfe Make configure error out on missing ghc-tarballs on Windows
     e7c331a Make headers C++ compatible (fixes #10700)
     26315ed Fix misspelled function name in a comment
     4f80ec0 Improve error message for newtypes and deriving clauses
     e9ad42d Typos in comments and strings
     d7c2b01 Fix comment that confused Haddock
     b5097fe Testsuite: rename rename/should_fail/T5001 to T5001b (#5001)
     e273c67 Testsuite: mark tests recently fixed as passing + accept new stderr
     756fa0a Testsuite: skip T10489 unless compiler_debugged (#10489)
     6880277 Testsuite: add arrows/should_compile/T5333 (#5333)
     58b5f04 Testsuite: add typecheck/should_fail/T9260 (#9260)
     58986c4 Testsuite: add typecheck/should_fail/T8034 (#8034)
     aee19d0 Testsuite: T10245 is passing for WAY=ghci (#10245)
     36bbfbd Backpack docs on renamer and depsolver, also s/package/unit/.
     a442800 Build system: remove function keyword from configure.ac (#10705)
     a66e1ba User's guide: delete ancient "Core syntax" example
     7cf87df Fix #7919 (again)
     353db30 Remove checked-in PDFs.
     8f81af9 Typos in comments
     ad089f5 Give raise# a return type of open kind (#10481)
     75504f3 Typos in comments
     15dd700 Replace (SourceText,FastString) with StringLiteral data type
     d9b618f Typo in comment
     37227d3 Make BranchFlag a new kind
     92f5385 Support MO_U_QuotRem2 in LLVM backend
     948e03e Update parallel submodule, and re-enable warnings
     b38ee89 Fix incorrect stack pointer usage in StgRun() on x86_64
     4d8859c Typos in comments
     d7ced09 Minor improvement to user guide
     30b32f4 Test Trac #10134
     697079f 4 reduce/reduce parser conflicts resolved
     d9d2102 Support wild cards in data/type family instances
     7ec6ffc Typos in comments [skip ci]
     64b6733 CmmParse: Don't force alignment in memcpy-ish operations
     30c981e Removed deprecated syntax for GADT constuctors.
     f063bd5 Fix #10713.
     b5f1c85 Test #9233 in perf/compiler/T9233
     d7b053a Pretty: reformat using style from libraries/pretty (#10735)
     9d24b06 Pretty: rename variables to the ones used by libraries/pretty (#10735)
     25bc406 Pretty: improve error messages (#10735)
     53484d3 Pretty: remove superfluous parenthesis (#10735)
     2d1eae2 Pretty: kill code that has been dead since 1997 (#10735)
     6f6d082 Pretty: Args of NilAbove/TextBeside/Nest/Union are always RDocs (#10735)
     926e428 Pretty: use BangPatterns instead of manual unboxing Ints (#10735)
     f951ffc Pretty: mimic pretty API more closely (#10735)
     85179b5 Pretty: use replicate for spaces and multi_ch (#10735)
     dd7e188 Add framework flags when linking a dynamic library
     4c55f14 users_guide: Add note about #367 to Bugs section
     6029748 Drop custom mapM impl for []
     ecb1752 Make -fcpr-off a dynamic flag
     b12dba7 Make Exception datatypes into newtypes
     22bbc1c Make sure that `all`, `any`, `and`, and `or` fuse (#9848)
     fd6b24f Additions to users' guide and release notes
     575abf4 Add Fixity info for infix types
     e2b5738 Allow proper errors/warnings in core2core passes
     617f696 Do not complain about SPECIALISE for INLINE
     a426154 Warn about missed specialisations for imports
     49615d9 Comments only
     ab98860 Minor refactor to use filterInScope
     9536481 Tidy up and refactor wildcard handling
     28096b2 Fix quantification for inference with sigs
     75f5f23 Coments only
     cc07c40 Comments only
     294553e T8968-1 and -3 should pass
     64dba51 Test Trac #10742
     eca9a1a Ensure DynFlags are consistent
     97843d0 base: Add instances
     600b153 llvmGen: Rework LLVM mangler
     aa23054 Add test for #10600 (exhaustiveness check with --make and -fno-code)
     bc43d23 Rejigger OSMem.my_mmap to allow building on Mac
     a1c934c base: Add missing Traversable instance for ZipList
     6cab3af Big batch of Backpack documentation edits.
     79e0a10 Test Trac #10753
     a192d6b Comments only
     f1b4864 Sync base/changelog.md with GHC 7.10.2 release
     590aa0f Make oneShot open-kinded
     92f35cd cmmCreateSwitchPlan: Handle singletons up-front
     2c4a7d3 Update transformers submodule to 0.4.3.0 release
     f04c7be Fix unused-matches warnings in CmmLex.x
     a40ec75 Update testsuite/.gitignore [skip ci]
     b4ed130 Replace HsBang type with HsSrcBang and HsImplBang
     2da06d7 User manual update, as prodded by #10760.
     2b4710b Add missing </para> to User's guide to fix the build
     8cce7e4 Bump template-haskell to new major version 2.11
     67576dd Pretty: bugfix fillNB (#10735)
     bcfae08 Pretty: fix potential bad formatting of error message (#10735)
     5d57087 Pretty: fix a broken invariant (#10735)
     85bf76a Pretty: show rational as is (#10735)
     f903949 Pretty: improving the space/time performance of vcat, hsep, hcat (#10735)
     b0dee61 template-haskell: Add changelog entry to infix type operators
     7b211b4 Upgrade GCC to 5.2.0 for Windows x86 and x86_64
     e415369 Update mingw tarball location
     8c5b087 SysTools: Fix whitespace in error message
     d2dd5af DynFlags: Prohibit hpc and byte-code interpreter
     ec68618 Name: Show NameSort in warning
     1857191 Testsuite: mark T8089 expect_broken(#7325) on Windows
     8906037 Testsuite: mark encoding005 expect_broken(#10623) on Windows
     ca85442 Testsuite: recenter 2 performance tests on Windows
     744ff88 Testsuite: speedup running a single test
     e367e27 Travis: prevent 10' no output, by setting VERBOSE=2
     74897de Make rts/ThreadLabels.c threadsafe for debug runtime.
     22aca53 Transliterate unknown characters at output
     ab9403d Dump files always use UTF8 encoding #10762
     b17ec56 Fix rdynamic flag and test on Windows
     ebca3f8 rts/Printer.c: speed up '-Da' printer for 'LIBBFD' build
     18a1567 Add selectors for common fields (DataCon/PatSyn) to ConLike
     d97e60f Comments reformating/corrections
     b6be81b Build system: delete half-baked Cygwin support
     98f8c9e Delete sync-all
     a146b28 GhcMake: Fix spelling in comment
     0d0e651 Bag: Add Foldable instance
     9e8562a Implement getSizeofMutableByteArrayOp primop
     3452473 Delete FastBool
     2f29ebb Refactor: delete most of the module FastTypes
     47493e6 Build system: simplify install.mk.in
     a1c008b Build system: delete unused distrib/Makefile
     a5061a9 Check options before warning about source imports.
     37a0b50 Delete ExtsCompat46 (#8330)
     b78494e fix 64bit two-stage allocator on Solaris/AMD64 platform (#10790)
     fba724c configure.ac: Allow disabling of large-address-space
     1c643ba Fix algorithm.tex build and update with some new info.
     0f3335f Comments and white space
     816d48a Implement lookupGlobal in TcEnv, and use it
     711e0bf tcRnDeclsi can use tcRnSrcDecls
     ac0d052 TcDeriv: Kill dead code
     de476e9 PrelNames: Clean up list a bit
     89d25b9 BinIface: Clean up whitespace
     7924469 Clean up handling of knownKeyNames
     a8601a8 Revert "Clean up handling of knownKeyNames"
     28ad98e PrelNames: introduce dcQual in place of conName
     211b349 Move newImplicitBinder to from IfaceEnv to BuildTyCl
     70ea94c IfaceEnv: Clean up updNameCache a bit
     f6035bc MkIface: Introduce PatSynId, ReflectionId, DefMethId
     7bd8f8f TysWiredIn: Shuffle code around
     15c63d2 base: Remove a redundant 'return'
     38c98e4 RTS: Reduce MBLOCK_SPACE_SIZE on AArch64
     15cb83d Add testcase for #7411
     a6826c5 Make Generic (Proxy t) instance poly-kinded (fixes #10775)
     1b56c40 Respect GHC_CHARENC environment variable #10762
     81ae26d Dwarf: Fix DW_AT_use_UTF8 attribute
     cbf58a2 Dwarf: Produce {low,high}_pc attributes for compilation units
     8476ce2 Dwarf: Produce .dwarf_aranges section
     0c823af Fix identifier parsing in hp2ps
     cd2dc9e ghc-pkg --enable-multi-instance should not complain about case sensitivity.
     c7f0626 integer-gmp: optimise bitBigNat
     c1d7b4b StgCmmHeap: Re-add check for large static allocations
     60120d2 Fix 7.10 validate
     12098c2 Fix typo in pattern synonym documentation.
     10a0775 Anchor type family instances deterministically
     ad26c54 Testsuite: refactoring only
     6740d70 Use IP based CallStack in error and undefined
     010e187 Fix trac #10413
     ff9432f Add test for updating a record with existentially quantified fields.
     296bc70 Use a response file for linker command line arguments #10777
     ba5554e Allow annotations though addTopDecls (#10486)
     c8f623e Expand declaration QQs first (#10047)
     28ac9d3 Improve the error messages for class instance errors
     3cc8f07 stm: Fix test case
     5d7a873 Testsuite: don't warn about missing specialisations
     e0b3ff0 Testsuite: update expected output
     3b23379 Testsuite: mark 4 tests expect_broken_for(#10712, opt_ways)
     32a9ead Fix some tests that were broken by D861
     c43c8e2 Testsuite: by default run all tests for a single way
     bd16e0b Testsuite: delete dead code
     3744578 Injective type families
     5dc88b7 Add test for T10836 (expected broken)
     34b106f Accept underscores in the module parser. (Thanks spinda for the fix.)
     b639c97 Testsuite: fix tcfail220 - Maybe is wired-in now
     e1293bb Testsuite: only print msg when timeout kills process unexpectedly
     79cdb25 Testsuite: ignore line number differences in call stacks (#10834)
     85915e9 Make Data.List.foldr1 inline
     19c6049 Fix T6018th test failure
     64761ce Build system: implement `make install-strip` (#1851)
     5c372fe ghc-pkg: don't print ignored errors when verbosity=0
     c60c462 user-guide: Add missing <para> tags around <listitem> body
     96b986b EventLog: Factor out ensureRoomFor*Event
     062feee tracing: Kill EVENT_STARTUP
     2c24fd7 Build system: put each BuildFlavour in a separate file (#10223)
     b40e559 Build system: simplify *-llvm BuildFlavours (#10223)
     1abbacd Build system: cleanup utils/ghc-pkg/ghc.mk
     dc671a1 SPECIALIZE strictMinimum for Int and Integer
     c6b82e9 Further simplify the story around minimum/maximum
     554be5e Build system: detect when user cloned from GitHub
     864a9c4 Build system: remove hack for Mac OSX in configure.ac (#10476)
     a158607 Build system: delete the InstallExtraPackages variable
     330fbbd Build system: make *-cross BuildFlavours consistent (#10223)
     8be43dd Build system: cleanup BUILD_DIRS + add lots of Notes
     e4a73f4 Move GeneralCategory et al to GHC.Unicode
     1b8eca1 Build system: check for inconsistent settings (#10157)
     dbb4e41 HeapStackCheck: Small refactoring
     4356dac Forbid annotations when Safe Haskell safe mode is enabled.
     23a301a Testsuite: comment out `setnumcapabilities001` (#10860)
     cdca31e Don't check in autogenerated hs files for recomp013.
     3a71d78 Comments on oneShot
     a870738 Improve rejigConRes (again)
     487c90e Add a test for Trac #10806
     a7f6909 A CFunEqCan can be Derived
     377395e Improve documentation for transform list-comps
     50d1c72 Fix broken links in documentation
     413fa95 Improve documentation of comprehensions
     f30a492 Testsuite cleanup
     8c0eca3 Add assertions
     18759cc Remove redundant language extensions
     195af2d Dead code removal, export cleanup
     4275028 Code movement
     7ad4b3c s/StgArrWords/StgArrBytes/
     89324b8 Testsuite: normalise slashes in callstack output
     37081ac Testsuite: mark enum01-enum03 expect_broken(#9399) on Windows
     3ec205a CodeGen: fix typo in error message
     08af42f hpc: use `takeDirectory` instead of `dropWhileEnd (/= '/')`
     c8d438f Testsuite: mark T6037 expect_fail on Windows (#6037)
     12b0bb6 Account for stack allocation in the thread's allocation counter
     14c4090 Pretty: fix unicode arrow operators.
     325efac Fix `hp2ps -i-`
     e66daec DynFlags: remove unused sPgm_sysman (#8689)
     8d89d80 Testsuite: add test for #10781
     43eb1dc Show minimal complete definitions in ghci (#10847)
     8ecf6d8 ApplicativeDo transformation
     77662e1 Add namePackage function to template-haskell
     48746ff Docs: make sure all libs are included in index.html (#10879)
     a8406f8 Pass TEST_HC_OPTS in bug1465 and T5792.
     2d4db40 Fix #10815 by kind-checking type patterns against known kinds.
     8ee2b95 Polish some error messages.
     b89c491 Always run explicitly requested ways (extra_ways) for fast runs.
     c738b12 Replace [PostTc id Type] with PostTc id [Type]
     e156361 Put stable pointer names in the name cache.
     1637e4d Driver: --make -o without Main should be an error (#10895)
     1a13551 Test #10347
     d19a77a Update user guide, fixing #10772
     d7f2ab0 Test #10770
     79b8e89 Print associated types a bit better.
     1292c17 Allow TH quoting of assoc type defaults.
     27f9186 Clarify parsing infelicity.
     93fafe0 Re-polish error messages around injective TFs.
     6a20920 Small improvement in pretty-printing constructors.
     cbcad85 Fix typo in test for #10347.
     2f9809e Slightly better `Coercible` errors.
     e27b267 Perform a validity check on assoc type defaults.
     8e8b9ed Run simplifier only when the env is clean.
     cd2840a Refactor BranchLists.
     c234acb `_ <- mapM` --> `mapM_`
     3f13c20 Revert "Revert "Revert "Support for multiple signature files in scope."""
     09d214d Revert "Revert "Revert "Change loadSrcInterface to return a list of ModIface"""
     06d46b1 Unify hsig and hs-boot; add preliminary "hs-boot" merging.
     d516d2e Fix build failure, I think.
     07f6418 Remove graphFromVerticesAndAdjacency
     5a8b055 TcDeriv: Use a NameEnv instead of association list
     83e23c1 Remove (now bogus) assert.
     0b852fc base: use Show for ErrorCall in uncaughtExceptionHandler
     d4d34a7 Make derived names deterministic
     089b72f DeriveLift extension (#1830)
     4cdab73 HscMain: Place CPP macro invocation on one line
     79f5732 testsuite: attempt fixing fallout from 089b72f52
     c6bdf4f Remove references to () from types of mkWeak# and friends
     65bf7ba DsBinds: Avoid using String when desugaring CallStack construction
     939a7d6 Annotate CmmBranch with an optional likely target
     cf90a1e Add constant-folding rule for Data.Bits.bit
     73921df Update Cabal to recognize DeriveLift
     453cdbf base: export allocation counter/limit API from System.Mem
     5c11523 reify associated types when reifying typeclasses
     39a262e Revert "reify associated types when reifying typeclasses"
     2440e3c Fix a bug with mallocForeignPtr and finalizers (#10904)
     b08a533d Fix DeriveGeneric for types with same OccName (#10487)
     4f9ee91 Testsuite: update expected output for T8832 on 32-bit systems (#8832)
     5883b56 Testsuite: properly fix T8832.stdout-ws-32 (#8832)
     1395185 Testsuite: add test for #10767
     fb40926 Weak: Don't require wrapping/unwrapping of finalizers
     a98815a Dwarf: Rename binding to avoid shadowing ppr
     a0b1f41 Dwarf: Ensure block length is encoded correctly
     f7fd864 Skip a possible BOM in utf8 encoding
     3fbf8f4 Debug: Remove extraneous LANGUAGE CPP
     988b2ba rts: Clean up whitespace in Trace.h
     b4d43b4 reify associated types when reifying typeclasses(#10891)
     78053f4 Allow enumDeltaIntegerFB to be inlined
     2eddcd9 Lexer: delete dead code for binary character literals
     23baa65 .gitignore update for some test files.
     e3ab25a Typos in comments
     03b3804 Add Data.Semigroup and Data.List.NonEmpty (re #10365)
     f2a174a Update nofib submodule
     a52db23 Update nofib submodule again
     eb975d2 Fix treatment of -0.0
     57e3742 Document peculiarities of `traceM`.
     b29f20e nativeGen PPC: fix > 16 bit offsets in stack handling
     bd41eb2 LLVM: Implement atomic operations in terms of LLVM primitives
     9539408 LLVM: Factor out accumulation of LLVM statements and variables
     7442434 Move CallStack back to base
     e3d2bab Fix signature of atomic builtins
     9ed700b Don't use old linkable for hs-boot files.
     4fd6207 Move user's guide to ReStructuredText
     93e21b9 docs: Fix ghc_config.py.in
     b6f76b9 Prevent GHC from silently dying when preprocessor is not found
     c4d7df0 Fix broken validation Build 6564 and accepting a few other test results
     a3c78ab Build system: add mk/validate.mk.sample
     a96f1ac Testsuite: update expected output for T8602
     6cde981 Make GHC generics capable of handling unboxed types
     0eb8fcd Enable `Enumeration is empty` warnings for `Integer`
     2f74be9 Fill in associated type defaults with DeriveAnyClass
     d2fb532 testsuite: Bump up haddock.base expected allocations
     620fc6f Make Windows linker more robust to unknown sections
     aecf4a5 Build system: don't create mk/are-validating.mk
     c0bdfee Testsuite: only add -fno-warn-missed-specialisations for ghc>=7.11
     7fcfee1 A few typos in comments
     5ca1d31 Testsuite: make driver python 2.6 compatible again
     427f8a1 Deduplicate one-shot/make compile paths.
     8c1866a Comments only
     0e169a8 Fix kind-var abstraction in SimplUtils.abstractFloats
     ca816c6 Remove dead code: ruleLhsOrphNames
     7da3d30 Comments only
     3833e71 Comments about TcLevel assignment
     59883ae Documentation for FrontendResult
     36811bf AsmCodeGen: Ensure LLVM .line directives are sorted
     ea4df12 Ensure shiftL/shiftR arguments aren't negative
     7b443bb Improve error messages for ambiguous type variables
     69a6e42 Allow non-operator infix pattern synonyms
     e2b579e Parser: revert some error messages to what they were before 7.10
     f64f7c3 Tests for #10945 and #10946
     931d0a7 Move orphan instance/rule warnings to typechecker/desugarer.
     e99e6db Extra files to ignore from the new Restructured documentation.
     0ead0ca Disable man building for most quick build styles.
     c7ab799 Ignore __pycache__.
     e5baf62 Simplify type of ms_srcimps and ms_textual_imps.
     f00525d rts: Fix clobbered regs list for aarch64 StgRun
     3ac9b92 configure.ac: AArch64 is now registerised
     96586c4 Switch to LLVM version 3.7


More information about the ghc-commits mailing list