[commit: ghc] wip/names3's head updated: Fix RnModIface (7803d1b)
git at git.haskell.org
git at git.haskell.org
Thu Oct 13 22:34:46 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
Branch 'wip/names3' now includes:
89facad Add T12520 as a test
1766bb3 RtClosureInspect: Fix off-by-one error in cvReconstructType
613d745 Template Haskell support for unboxed sums
7a86f58 Comments only: Refer to actually existing Notes
8d92b88 DmdAnal: Add a final, safe iteration
d6fd2e3 DmdAnal: Testcase about splitFVs and dmdFix abortion
ec7fcfd Degrade "case scrutinee not known to diverge for sure" Lint error to warning
faaf313 WwLib: Add strictness signature to "let x = absentError …"
1083f45 Fix doc build inconsistency
ae66f35 Allow typed holes to be levity-polymorphic
a60ea70 Move import to avoid warning
0050aff Fix scoping of type variables in instances
ca8c0e2 Typofix in docs.
983f660 Template Haskell support for TypeApplications
822af41 Fix broken Haddock comment
f4384ef Remove unused DerivInst constructor for DerivStuff
21c2ebf Missing stderr for T12531.
9d17560 GhcMake: limit Capability count to CPU count in parallel mode
a5d26f2 rts: enable parallel GC scan of large (32M+) allocation area
044e81b OccName: Remove unused DrIFT directive
ff1931e TcGenDeriv: Typofix
d168c41 Fix and complete runghc documentation
6781f37 Clarify pkg selection when multiple versions are available
83b326c Fix binary-trees regression from unnecessary floating in CorePrep.
a25bf26 Tag pointers in interpreted constructors
ef784c5 Fix handling of package-db entries in .ghc.environment files, etc.
2ee1db6 Fixes #12504: Double-escape paths used to build call to hsc_line
28b71c5 users_guide: More capabilities than processors considered harmful
0e74925 GHC: Expose installSignalHandlers, withCleanupSession
3005fa5 iserv: Show usage message on argument parse failure
d790cb9 Bump the default allocation area size to 1MB
d40d6df StgCmmPrim: Add missing MO_WriteBarrier
d1f2239 Clarify scope of `getQ`/`putQ` state.
22259c1 testsuite: Failing testcase for #12091
2d22026 ErrUtils: Expose accessors of ErrDoc and ErrMsg
a07a3ff A failing testcase for T12485
9306db0 TysWiredIn: Use dataConWorkerUnique instead of incrUnique
9cfef16 Add Read1/Read2 methods defined in terms of ReadPrec
1ad770f Add -flocal-ghci-history flag (#9089).
010b07a PPC NCG: Implement minimal stack frame header.
ca6d0eb testsuite: Update bytes allocated of parsing001
75321ff Add -fdefer-out-of-scope-variables flag (#12170).
e9b0bf4 Remove redundant-constraints from -Wall (#10635)
043604c RnExpr: Fix ApplicativeDo desugaring with RebindableSyntax
dad6a88 LoadIFace: Show known names on inconsistent interface file
3fb8f48 Revert "testsuite: Update bytes allocated of parsing001"
a69371c users_guide: Document removal of -Wredundant-constraints from -Wall
ad1e072 users_guide: Move addModFinalizer mention to 8.0.2 release notes
1f5d4a3 users_guide: Move -fdefer-out-of-scope-variables note to 8.0.2 relnotes
da920f6 users_guide: Move initGhcMonad note to 8.0.2 relnotes
a48de37 restore -fmax-worker-args handling (Trac #11565)
1e39c29 Kill vestiages of DEFAULT_TMPDIR
8d35e18 Fix startsVarSym and refactor operator predicates (fixes #4239)
b946cf3 Revert "Fix startsVarSym and refactor operator predicates (fixes #4239)"
f233f00 Fix startsVarSym and refactor operator predicates (fixes #4239)
e5ecb20 Added support for deprecated POSIX functions on Windows.
0cc3931 configure.ac: fix --host= handling
818760d Fix #10923 by fingerprinting optimization level.
36bba47 Typos in notes
33d3527 Protect StablPtr dereference with the StaticPtr table lock.
133a5cc ghc-cabal: accept EXTRA_HC_OPTS make variable
f93c363 extend '-fmax-worker-args' limit to specialiser (Trac #11565)
ac2ded3 Typo in comment
57aa6bb Fix comment about result
f8b139f test #12567: add new testcase with expected plugin behaviour
1805754 accept current (problematic) output
cdbb9da cleanup: drop 11 years old performance hack
71dd6e4 Don't ignore addTopDecls in module finalizers.
6ea6242 Turn divInt# and modInt# into bitwise operations when possible
8d00175 Less scary arity mismatch error message when deriving
4ff4929 Make generated Ord instances smaller (per #10858).
34010db Derive the Generic instance in perf/compiler/T5642
05b497e distrib: Fix libdw bindist check
a7a960e Make the test for #11108 less fragile
dcc4904 Add failing testcase for #12433
feaa31f Remove references to -XRelaxedPolyRec
5eab6a0 Document meaning of order of --package-db flags, fixes #12485.
a8238a4 Update unix submodule to latest HEAD.
65d9597 Add hook for creating ghci external interpreter
1b5f920 Make start address of `osReserveHeapMemory` tunable via command line -xb
7b4bb40 Remove -flocal-ghci-history from default flags
710f21c Add platform warning to Foreign.C.Types
158288b Generalise type of mkMatchGroup to unify with mkMatchGroupName
04184a2 Remove uses of mkMatchGroupName
7b7ea8f Fix derived Ix instances for one-constructor GADTs
0e7ccf6 Fix TH ppr output for list comprehensions with only one Stmt
454033b Add hs_try_putmvar()
03541cb Be less picky about reporing inaccessible code
21d0bfe Remove unused exports
35086d4 users_guide: Fix Docbook remnant
b451fef users_guide: #8761 is now fixed
c6ac1e5 users_guide: TH now partially supports typed holes
6555c6b rts: Disable -hb with multiple capabilities
5eeabe2 Test wibbles for commit 03541cba
ec3edd5 Testsuite wibbles, to the same files
505a518 Comments and white space only
8074e03 Comments and white space only
876b00b Comments and white space
86836a2 Fix codegen bug in PIC version of genSwitch (#12433)
9123845 tryGrabCapability should be using TRY_ACQUIRE_LOCK
626db8f Unify CallStack handling in ghc
a001299 Comments only
a72d798 Comments in TH.Syntax (Trac #12596)
97b47d2 Add test case for #7611
ea310f9 Remove directories from include paths
14c2e8e Codegen for case: Remove redundant void id checks
6886bba Bump Haddock submodule to fix rendering of class methods
8bd3d41 Fix failing test T12504
9cbcdb4 shutdownHaskellAndExit: just do a normal hs_exit() (#5402)
74c4ca0 Expose hs_exit_(rtsFalse) as hs_exit_nowait()
3a17916 Improved documentation for Foreign.Concurrent (#12547)
9766b0c Fix #12442.
d122935 Mark mapUnionFV as INLINABLE rather than INLINE
68f72f1 Replace INLINEABLE by INLINABLE (#12613)
55d92cc Update test output
bc7c730 Pattern Synonyms documentation update
796f0f2 Print foralls in user format
b0ae0dd Remove #ifdef with never fulfilled condition
c36904d Fix layout of MultiWayIf expressions (#10807)
f897b74 TH: Use atomicModifyIORef' for fresh names
0b6024c Comments and manual only: spelling
13d3b53 Test Trac #12634
f21eedb Check.hs: Use actual import lists instead of comments
0b533a2 A bit of tracing about flattening
2fbfbca Fix desugaring of pattern bindings (again)
66a8c19 Fix a bug in occurs checking
3012c43 Add Outputable Report in TcErrors
b612da6 Fix impredicativity (again)
fc4ef66 Comments only
5d473cd Add missing stderr file
3f27237 Make tcrun042 fail
28a00ea Correct spelling in note references
b3d55e2 Document Safe Haskell restrictions on Generic instances
9e86276 Implement deriving strategies
b61b7c2 CodeGen X86: fix unsafe foreign calls wrt inlining
59d7ee5 GHCi: Don't remove shadowed bindings from typechecker scope.
3c17905 Support more than 64 logical processors on Windows
151edd8 Recognise US spelling for specialisation flags.
f869b23 Move -dno-debug-output to the end of the test flags
d1b4fec Mark T11978a as broken due to #12019
1e795a0 Use check stacking on Windows.
c93813d Add NUMA support for Windows
2d6642b Fix interaction of record pattern synonyms and record wildcards
1851349 Don't warn about name shadowing when renaming the patten in a PatSyn decl
ce3370e PPC/CodeGen: fix lwa instruction generation
48ff084 Do not warn about unused underscore-prefixed fields (fixes Trac #12609)
0014fa5 ghc-pkg: Allow unregistering multiple packages in one call
b0d53a8 Turn `__GLASGOW_HASKELL_LLVM__` into an integer again
f547b44 Eliminate some unsafeCoerce#s with deriving strategies
23cf32d Disallow standalone deriving declarations involving unboxed tuples or sums
4d2b15d validate: Add --build-only
42f1d86 runghc: use executeFile to run ghc process on POSIX
3630ad3 Mark #6132 as broken on OS X
8cab9bd Ignore output from derefnull and divbyzero on Darwin
e9104d4 DynFlags: Fix absolute import path to generated header
eda5a4a testsuite: Mark test for #12355 as unbroken on Darwin.
22c6b7f Update Cabal submodule to latest version.
8952cc3 runghc: Fix import of System.Process on Windows
7a6731c genapply: update source file in autogenerated text
c5d6288 Mark zipWithAndUnzipM as INLINABLE rather than INLINE
e4cf962 Bring Note in TcDeriv up to date
465c6c5 Improve error handling in TcRnMonad
58ecdf8 Remove unused T12124.srderr
4a03012 Refactor TcDeriv and TcGenDeriv
a2bedb5 RegAlloc: Make some pattern matched complete
57a207c Remove dead code “mkHsConApp”
cbe11d5 Add compact to packages so it gets cleaned on make clean.
e41b9c6 Fix memory leak from #12664
f3be304 Don't suggest deprecated flags in error messages
76aaa6e Simplify implementation of wWarningFlags
082991a Tc267, tests what happens if you forgot to knot-tie.
3b9e45e Note about external interface changes.
940ded8 Remove reexports from ghc-boot, help bootstrap with GHC 8.
887485a Exclude Cabal PackageTests from gen_contents_index.
00b530d The Backpack patch.
4e8a060 Distinguish between UnitId and InstalledUnitId.
5bd8e8d Make InstalledUnitId be ONLY a FastString.
027a086 Update haddock.Cabal perf for Cabal update.
61b143a Report that we support Backpack in --info.
46b78e6 Cabal submodule update.
e660f4b Rework renaming of children in export lists.
f2d80de Add trailing comma to fix the build.
21647bc Fix build
7b060e1 Generate a unique symbol for signature object stub files, fixes #12673
bcd3445 Do not segfault if no common root can be found
8dc72f3 Cleanup PosixSource.h
6c47f2e Default +RTS -qn to the number of cores
85e81a8 Turn on -n4m with -A16m or greater
1a9705c Escape lambda.
b255ae7 Orient improvement constraints better
b5c8963 Rename a parameter; trivial refactor
88eb773 Delete orphan where clause
76a5477 Move zonking out of tcFamTyPats
cc5ca21 Improved stats for Trac #1969
a6111b8 More tests for Trac #12522
b5be2ec Add test case for #12689
f8d2c20 Add a broken test case for #12689
4fcff2d Unique: Simplify encoding of sum uniques
0dfbea4 Handle deserialization of tuples, etc specifically
38c40f3 Fix some style issues
6a58e04 MkIface: Turn a foldr into a foldl'
7803d1b Fix RnModIface
More information about the ghc-commits
mailing list