[commit: ghc] wip/orf-reboot's head updated: Remove unused test file (97fd90b)

git at git.haskell.org git at git.haskell.org
Mon Jun 29 08:30:38 UTC 2015


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

Branch 'wip/orf-reboot' now includes:

     90dd11b Remove some unimplemented GranSim primops
     af45feb Update list of primops that don't get wrappers (#10191)
     7f15a07 Implement part 1 of OverloadedRecordFields
     abde5da Rename driver phases C(obj)cpp to C(obj)cplusplus
     e2f1ffc Rename C(obj)cplusplus to C(obj)cxx
     a4656eb Doc typofix.
     e24f638 Renames some files to help with validation cleanup (#10212)
     de1160b Refactor the story around switches (#10137)
     c37ee4a Remove an unused include that doesn't exist on OS X (#10211)
     b1d6a60 Delete unused field `PipeEnv.pe_isHaskellishFile`
     5971ad5 Syntax check package-qualified imports (#9225)
     1f69f37 Add `integer-gmp` specific hint to build.mk.sample
     995e8c1 Drop old integer-gmp-0.5 from GHC source tree
     a3d0a7a Testsuite: suppress errors when running GS on bad.ps
     9e073ce Explicitly check for -C on registerised build (#7563)
     6981862 Don't throw exception when start_phase==stop_phase (#10219)
     da17f99 Don't treat .hcr and .raw_s as haskellish suffixes
     8757e2d Testsuite: redirect stderr to /dev/null when running GS on bad.ps
     694c4d5 uBackpack: simplified Backpack description.
     d4cf705 Don't `make accept` output of expect_broken tests
     7cec6c7 Change which files --make thinks are 'Haskellish' (#10220)
     3749c05 Reformat build flavours in build.mk.sample (#10223)
     43351ff Filter out `-Rghc-timing` for V=0 builds (#10223)
     f15dbc2 Indentation only.
     0721e55 Fake (->) fixity declaration (#10145)
     9b66a7f Do not set -fasm explicitly in build.mk.sample (#10223)
     4c1e1c8 Disable same warnings for normal builds as for validate (#10223)
     afcfb62 Change 'Tab character' warnings so there is one per file (#9723)
     47f821a libffi: backport noexecstack fix for x86/win32.S
     48977c8 Fix validate linenumber off-by-one
     13a0d5a clarify --no-as-needed is only needed on ELF
     78c79e3 docs: remove unused -ddump flags from users guide
     59f7a7b Restore unwind information generation
     012ea0b parser: allow type-level cons in prefix position
     3541f73 Data.Complex: Derive Generic
     2255c76 Remove an incorrect statement about -fwarn-tabs
     fd1099c Don't `make accept` output of `expect_broken_for` tests
     ab0743f Comments only, mostly typos
     a0c1c96 testsuite: fix failing amd64/Windows perf tests
     54b7dc5 rts/linker: make an error msg a debug msg
     b0ba054 testsuite: skip T10017 on Windows
     89eef44 Whitespace only
     a1404e8 Update hsc2hs submodule
     a838d1f CmmSwitch: Do not trip over a case with no (valid) branches
     8f07092 Test case for #10246
     fef4948 User's guide: .a files can be 2-2.5x larger with -split-objs
     c81e070 Stop profiling output from running together (#8811)
     22eecaf fix '&stg_interp_constr_entry' FFI type to be FunPtr
     7209290 fix typo
     a7ab161 Replace hooks by callbacks in RtsConfig (#8785)
     890461e Add +RTS -O<size> to control the minimum old gen size
     93f3a64 Add -n to the RTS help output
     f745b6e Typechecker: refactoring only
     0622970 testdriver: delete unused ways
     b972de0 Suggest how to fix .ghci when it is group writeable (#8248)
     9f0f99f Fix a long-standing bug in the demand analyser
     547c597 Reduce module qualifiers in pretty-printing
     c897613 Error msg wibbles from reduced module prefixes
     74d2c33 GHC.Prim.Constraint is not built-in syntax
     cfb6042 Do not quantify over the function itself in a RULE
     6ca7b84 Put quotes round a Name in an error message
     8b7ceec More aggressive Given/Wanted overlap check
     553c518 Look inside synonyms for foralls when unifying
     4f8e348 Replace endian test by 64-bit word access in T7600
     ab76b09 rts/Linker.c: distinct between DATA and CODE labels when importing
     cf1d975 Don't repeat package key with -dppr-debug when package info is missing.
     f1a4e42 The production for `pquals` is incorrect; the specifics are in D803.
     cf19640 The production for squals is incorrect; see D806 for specifics.
     eacda92 Test Trac #10148
     e6e0415 More error message wibbles
     a058ad6 Final error message wibble
     a7524ea Support for multiple signature files in scope.
     9e7802f Commit missing T10148 files and ignore the built executable.
     1d5c887 Axe one-shot sig-of
     3c6448c Ignore temporary ./configure files.
     53cc9af Test Trac #8030
     6b96eeb Fixes a compiler error with -DDEBUG (#10265)
     f536d89 Import rand using capi
     2d68aa6 Comments about AnyK
     d9b0be3 Comments in rejigConRes
     702fc77 Comments only
     fa46c59 Make the evidence in a CtGiven into an EvId
     9d16808 Typos in error messages and in comments
     485dba8 configure : LLVM and LD detections improvements (#10234).
     edc059a Fix autoconf's check for create_timer()
     a5745d2 Derive Generic instance for System.Exit.ExitCode
     c327393 Derive Generic instance for Data.Version.Version
     6109b31 use projectVersion from DynFlags rather than cProjectVersion for versionedAppDir
     8aefc9b parser: opt_kind_sig has incorrect SrcSpan
     9eab6fe parser: API Annotations : guardquals1 does not annotate commas properly
     919b511 parser : the API annotation on opt_sig is being discarded
     d261d4c Zap usage info in CSE (Trac #10218)
     25f2d68 Comments only
     a2ce3af Comments and white space only
     7febc2b Add "error:" prefix to error-messages
     79bfe27 Remove LlvmCodeGen panic variants.
     8dc2944 API Annotations : ExprWithTySig processing discards annotated spans
     5fded20 ApiAnnotations : lexer discards comment close in nested comment
     6dd2765 Implement -f[no-]print-unicode-syntax flag for unicode syntax output (#8959)
     7b042d5 Do not allow Typeable on constraints (Trac #9858)
     49d9b00 Fix fundep coverage-condition check for poly-kinds
     a9ca67f Improve Call Arity performance
     9654a7c Call Arity: Trade precision for performance in large mutually recursive groups
     1fb4dd3 Add exception for `KnownNat` and `KnownSymbol` in super classes.
     d8d541d Fixes (hopefully!) T9858
     e68e8ca Fix test output.
     ea579d9 Fix test output
     3b90d8c Rename tests so that they have a unique name.
     51af102 Better hints when RTS options not available (Trac #9579)
     2483644 Documentation for rnImports/rnImportDecl.
     2b3766b Comments only.
     ad6d6a7 Stub out pkgState with non-error, helps with debugging.
     619a324 Make T9579 parallel-safe and add build outputs to .gitignore
     88b8406 Test case for indirect dependencies in ghci linker (#10322)
     4bc925a Update Cabal submodule to 1.22.3.0 release
     d5773a4 Teach DmdAnal that coercions are value arguments!
     3bec1ac Teach DmdAnal about free coercion variables
     d12c7cb Spelling in comment
     f2d1b7f Support unboxing for GADT product types
     5c7e4db Wibble to DmdAnal
     b9f20bd GADTs now are CPR-able
     1e8c9b8 Enable SMP and GHCi support for Aarch64
     0bbc2ac Use the gold linker for aarch64/linux (#9673)
     3b932cc Add a blank line
     9b9fc4c Fix the boot dfun impedence-matching binding
     c0b5adb Do not decompose => (Trac #9858)
     1bb1ff2 Mark T8743 as passing
     1bd1cef Don't use self {-# SOURCE #-} import in test-cases.
     a2f9fef Fix #10182 by disallowing/avoiding self {-# SOURCE #-} imports
     646866f Fix superclass generation in an instance
     9d3bd3d Comments only
     c715166 Improve error reporting for impredicative types
     746f086 Better documetation of higher rank types
     932f086 Test Trac #9858 comment:101
     43d7137 Rename new T9858c to T9858d to avoid test name clash
     a55bfab Rename new T9858d to T9858e to avoid test name clash
     524ddbd Make sure GHC.List.last is memory-efficient
     6ab5da9 Rename role annotations w.r.t only local decls.
     a8d39a7 Fix #10285 by refusing to use NthCo on a newtype.
     414e20b Fix the formal operational semantics (#10121)
     d4cf559 Test #10321 in ghci/scripts/T10321
     dc587fe Test case for #10141
     72a9272 Change default roles in hs-boot files. (#9204)
     bbabb71 Updates to Backpack documentation based on recent visit to MSRC.
     c4e8097 Bump base version to 4.8.2.0
     75adc35 Add missing since-annotations for c024af131b9e2538
     9a0c179 base: Export GHC.Event(.Internal).Lifetime
     5f127fc Flesh out some more Backpack examples in the merging section.
     d0898ca Backpack docs: explain alternate merging scheme.
     541aa7f Full type checking Backpack details.
     21a37ca Backpack docs: merge backpack-shaping into algorithm, sigs no longer provide
     b61562f Seed SpecConstr from local calls
     168c883 A little outright bug in canEqTyVar2
     d9bb0ee Don't print evidence in TcFlatten
     a1275a7 Improve improvement in the constraint solver
     d4a926b Test Trac #10226
     54cefbd Typeset Backpack syntax in a figure
     b83160d Tidy up treatment of FlexibleContexts
     a3f7517 Typo fixes (mostly in comments)
     fe5ccbb Typeset Backpack semantic entities in figure, figure-ify all asides.
     bbfa0ca Comments only
     f6ab0f2 Refactor TyCon to eliminate TupleTyCon
     0d715db Update haddock submodule to track TyCon change
     b626cb0 Make Derived NomEq rewrite only Derived NomEq
     de5d022 Kill off the default types in ghc-prim
     2f6a0ac Move IP, Symbol, Nat to ghc-prim
     4efa421 Permit empty closed type families
     63a10bb arm: Force non-executable stack (#10369)
     f7dfcef Fix safeHaskell test for llvm backend
     bf4f3e6 Give a hint when a TH splice has a bad package key, partially fixes #10279
     cdba973 Documentation for Language.Haskell.TH.Quote.
     1a4374c arm: Force non-executable stack (part 2)
     341a766 Doc: checkCrossStageLifting, RnSplice/TcExpr is untyped/typed brackets (#10384)
     f7daf5a Normalise type families in the type of an expression
     458a97b Fix typo: identifer -> identifier
     03c4893 Retain ic_monad and ic_int_print from external packages after load
     477f514 rts: add "-no-rtsopts-suggestions" option
     fa0474d base: Fix confusing docs typo
     fb54b2c API Annotations : add Locations in hsSyn were layout occurs
     caeae1a Correct parsing of lifted empty list constructor
     15aafc7 ApiAnnotations : quoted type variables missing leading quote
     81030ed ApiAnnotations : Nested forall loses forall annotation
     f34c072 Revert "ApiAnnotations : Nested forall loses forall annotation"
     97d320f Revert "API Annotations : add Locations in hsSyn were layout occurs"
     d1295da Comments only
     931d014 A bit of refactoring RnSplice
     c3e6b3a Regression test for Trac #10390
     5bde9f7 ApiAnnotations : RdrHsSyn.isFunLhs discards parentheses
     cc9b788 Backpack docs: meditate on AvailTC with four examples.
     225df19 ApiAnnotations : AnnComma missing in TupleSection
     7136126 ApiAnnotations: misplaced AnnComma for squals production
     2601a43 Backpack docs: AvailInfo plan, and why selectors are hard.
     28257ca Support stage 1 Template Haskell (non-quasi) quotes, fixes #10382.
     21c72e7 Split off quotes/ from th/ for tests that can be done on stage1 compiler.
     eb0ed40 RnSplice's staging test should be applied for quotes in stage1.
     9a43b2c Always do polymorphic typed quote check, c.f. #10384
     3c70ae0 Quick fix: drop base bound on template-haskell.
     5c459ee Revert stage 1 template-haskell. This is a combination of 5 commits.
     811b72a Api Annotations: RdrHsSyn.mkAtDefault causes annotations to be disconnected.
     e4032b1 ApiAnnotations : mkGadtDecl discards annotations for HsFunTy
     27aa733 IdInfo comment update
     2666ba3 haddock: update submodule to fix #10206
     cf7573b More accurate allocation stats for :set +s
     9736c04 compiler: make sure we reject -O + HscInterpreted
     24707d7 ApiAnnotations : BooleanFormula construction discards original
     f35d621 Fix build breakage from 9736c042
     fe38195 ApiAnnotations : pquals production adds AnnVbar in the wrong place
     ecc3d6b ApiAnnotations : PatBind gives wrong SrcSpan for the pattern.
     f16ddce Support stage 1 Template Haskell (non-quasi) quotes, fixes #10382.
     b0784cc Backpack docs: more carefully describe unification versus unioning.
     b4f6c16 Ignore out and toc files.
     53409a7 Backpack docs: proper discourse on ModIface and ModDetails.
     eecef17 Fix safe haskell bug: instances in safe-inferred
     4fffbc3 New handling of overlapping inst in Safe Haskell
     ef7ed16 Make template-haskell build with GHC 7.6, fixes bootstrap build.
     c119a80 Use fmap instead of <$> (Fixes #10407)
     ca7c855 We need an empty boolFormula.stderr
     f5188f3 Fix weird behavior of -ignore-dot-ghci and -ghci-scipt
     6ee4b6f Turn off warnings when compiling boolFormula
     1b47692 Backpack docs: Consistently italicize metavariables.
     4432863 Update some tests for recent Safe Haskell change.
     a171cc1 Update Safe Haskell documentation.
     4b8b4ce Fix fragile T9579 tests
     8764a7e Revert D727
     8da785d Delete commented-out line
     130e93a Refactor tuple constraints
     5910a1b Change in capitalisation of error msg
     a154944 Two wibbles to fix the build
     a8493e0 Fix imports in HscMain (stage2)
     6e1174d Separate transCloVarSet from fixVarSet
     51cbad1 Update haddock submodule
     ca173aa Add a case to checkValidTyCon
     eb6ca85 Make the "matchable-given" check happen first
     c0aae6f Test Trac #10248
     a9ccd37 Test Trac #10403
     04a484e Test Trac #10359
     3cf8ecd Revert multiple commits
     3ef7fce Do not check dir perms when .ghci doesn't exist
     5972037 Backpack docs: Rewrite type checking section to have a more concrete plan.
     ab45de1 Failing test for #10420 using plugins.
     c256357 Speed up elimCommonBlocks by grouping blocks also by outgoing labels
     8e4dc8f Greatly speed up nativeCodeGen/seqBlocks
     73f836f CmmCommonBlockElim: Improve hash function
     3f42de5 Test Trac #10359
     f1f265d Test Trac #10403
     fa0bdd3 Test Trac #10248
     76024fd Delete commented-out line
     ffc2150 Refactor tuple constraints
     228ddb9 Make the "matchable-given" check happen first
     eaaa38b includes/stg/SMP.h: implement simple load_/store_load_barrier on armv6 and older
     85bf9e4 Add regression test for #10110.
     5cbac88 user guide: correct documentation for -Wall (fixes #10386)
     578d2ba Remove unneeded compatibility with LLVM < 3.6
     b03f074 ghci: Allow :back and :forward to take counts
     b0b11ad In ghci linker, link against all previous temp sos (#10322)
     b199536 compiler: make sure we reject -O + HscInterpreted
     470a949 Revert "In ghci linker, link against all previous temp sos (#10322)"
     753b156 Add a TODO FIXME w.r.t. D894
     fc8c5e7 Test Trac #8799, #8555
     edb8dc5 Revert "compiler: make sure we reject -O + HscInterpreted" (again)
     25d1a71 Fix error messages from open(Binary)TempFileWithDefaultPermissions
     c934914 Backpack docs: Clarifications from today's Skype call.
     9f968e9 Fix binary instance for IfaceLitTy
     c553e98 ApiAnnotations : AST version of nested forall loses forall annotation
     0df14b5 ApiAnnotations : parens around a context with wildcard loses annotations
     c488da8 ApiAnnotatons : AnnDcolon in wrong place for PatBind
     369dd0c White space layout only
     eae703a Reduce magic for seqId
     c89bd68 Fix quadratic behaviour in tidyOccName
     45d9a15 Fix a huge space leak in the mighty Simplifier
     7d519da testsuite: commit missing T4945 stdout
     4d6c0ee compiler: kill a stray pprTrace in OccName
     6694ccf testsuite: handle missing stats files gracefully (#10305)
     c00f051 Update .mailmap
     c04571d rts: Fix typo in comment
     326989e Add missing name for FFI import (fixes #9950)
     70f1ca4 Fix ghci-way tests of -XStaticPointers.
     71d1f01 Omit the static form error for variables not in scope.
     388448b Build system: don't install haddock .t files (#10410)
     c591147 ApiAnnotations tweaks
     ef90466 Testdriver: don't use os.popen in config/ghc
     ce166a3 Testdriver: do not interfer with MinGW path magic (#10449)
     640fe14 Remove unnecessary loadInterface for TH quoted name.
     e28462d base: fix #10298 & #7695
     b0d8ba3 Add liftData function.
     a138fa1 Testsuite: accept new output for T2507 and T8959a
     5ead7d1 Build system: make more targets PHONY
     4c7d177 Build system: remove toplevel target `fast`
     a065a3a Build system: use `mkdir -p` instead of `-mkdir`
     51aacde Build system: allow missing config.mk for target clean_%
     4de8028 Build system: check $CLEANING instead of $MAKECMDGOALS
     47e00ec Build system: don't set CLEANING=NO
     b0885e4 Build system: whitespace and comments only
     cd0e2f5 Build system: prevent "--version: Command not found"
     0bfd05e Build system: prevent "./Setup: Command not found"
     a49070e Build system: time's config files have moved
     48ed2f1 Build system: always allow me to clean haddock
     577d315 Build system: always use `make -r`
     0d20d76 Build system: make clean in utils/ghc-pkg should not delete inplace/lib/bin
     0a159e3 Build system: don't use supposedly local variable inside macro
     018fec0 Build system: also clean the inplace wrapper
     508a3a3 Build system: don't build runghc if GhcWithInterpreter=NO (#10261)
     7db2dec linker_unload working on Windows, fixes #8292.
     5a65da4 Don't run T9330fail on Windows, no clobber occurs. #9930
     94fff17 Travis: use validate --quiet to prevent hitting log file limits
     4756438 Catch canonicalizePath exceptions, fix #10101
     a52f144 In ghci linker, link against all previous temp sos (#10322)
     f5b43ce compiler/specialise: shut match_co up a bit
     f6ca695 rts: Fix aarch64 implementation of xchg
     e00910b ApiAnnotations : rationalise tests
     7dd0ea7 Update binary submodule to 0.7.5.0 release
     e6191d1 ApiAnnotations : strings in warnings do not return SourceText
     e8a7254 Add constraint creation functions to TcPluginM API
     1c38325 Fix dropped event registrations
     928f536 Use seq rather than (==) to force the size
     5eee6a1 Move seqExpr, seqIdInfo etc to CoreUtils
     20d8621 Add some missing seqs to Coercion.seqCo
     d245787 Use named fields in SimplCont.Select constructor
     403cfc9 Comments only
     931268a Replace tabs with spaces.
     98b0b2e Add information about allowed foreign prim args, see #10460.
     e5be846 Typofix: missing period. (#10460)
     a27fb46 Add (failing) test case for #7672.
     f82e866 Newline after type of allocate().
     dfdc50d Don't call DEAD_WEAK finalizer again on shutdown (#7170)
     34dcf8a Re-center perf numbers for T5631
     2f0011a White space only
     11d8f84 Treat pattern-synonym binders more consistently
     9b73cb1 Refactor the GlobalRdrEnv, fixing #7672
     90fde52 Mark sigof02 tests as expect_broken
     1189196 Re-do superclass solving (again); fixes #10423
     b095c97 Improve constraint tuples (Trac #10451)
     dbcdfe2 Set 32-bit perf figure
     d6c01fa Remove redundant import
     b1b2b44 Test Trac #10423
     8a38348 Test Trac #10451
     8e5f8cf Test Trac #10466
     b2b69b2 Test Trac #10438
     091944e compiler: make sure we reject -O + HscInterpreted
     e796026 build: make haddock a bit less chatty
     3758050 Improve FFI error reporting
     5688053 Detabify a programlisting in the User's Guide (#10425)
     942a074 testsuite: mark test T9938 (#9938) as passing again
     7a82b77 newTempName: Do not include pid in basename
     2c4c627 Typofixes
     6adfb88 Suggest -H to improve GC productivity, fixes #10474.
     7b6800c Remove outdated uBackpack docs.
     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
     f61ec3c Merge remote-tracking branch 'origin/master' into wip/orf-reboot
     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
     2c99538 Fix reporting of unused overloaded record fields
     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
     7b8621e Merge remote-tracking branch 'origin/master' into wip/orf-reboot
     87b361c Remove unnecessary Binary instance, since we don't serialize FieldLbl any more
     f8581f1 Get rid of dead code
     b16c3ae Distinguish AllowDuplicateRecordFields from OverloadedRecordFields
     97fd90b Remove unused test file


More information about the ghc-commits mailing list