[commit: ghc] wip/ext-solver's head updated: Merge branch 'master' into wip/ext-solver (5246346)
git at git.haskell.org
git at git.haskell.org
Sat Jul 19 23:04:54 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
Branch 'wip/ext-solver' now includes:
fa5ac96 Don't require mk/config.mk for all cleanup targets
c4e9f24 Test Trac #9036
0960a37 rm -rf ./docs/comm
ba2e201 Do type-class defaulting even if there are insoluble constraints
ef35d4c Remove the definition of die, which is now provided by System.Exit
7201e2a Update 32-bit perf numbers
3c990bf Start on 7.10.1 release notes
48e475e Fix annotation reification for home package modules
5f5e326 Add a comprehensive test for using Annotations from TH
7b967af tcrun045 should fail (implicit parameter as superclass)
2f3ea95 Print for-alls more often (Trac #9018)
0fe7268 annth_make, annth_compunits: Only run these tests if have_dynamic()
a3896ab Improve implementation of unSubCo_maybe.
ab8bb48 Fix scavenge_stack crash (#9045)
1d0798c Typo in comments
3a5c549 Typo in comment
4539400 rts: Add an initial Coverity model
7400810 Revert "rts: Add an initial Coverity model"
91cc88b Add Note [Role twiddling functions] to Coercion.
275ea0f rts: Add an initial Coverity model
e597f5f rts: Fix leak of file archive handle
b7278d3 rts: Fix memory leak when loading ELF objects
43b3bab Rts: Consistently use StgWord for sizes of bitmaps
05fcc33 Rts: Reuse scavenge_small_bitmap (#8742)
83a003f Don't inline non-register GlobalRegs
34db5cc Replace all #!/usr/bin/perl with #!/usr/bin/env perl
b0534f7 Per-thread allocation counters and limits
a05f8dd Update Haddock submodule ref. Fixes `cabal test'.
5bf22f0 Remove external core
54b31f7 fix rts exported symbols base_GHCziIOziException_allocationLimitExceeded_closure
2e03d86 Update comment now that we have per-gen weak pointer lists.
5141baf Improve docs for array indexing primops
f0fcc41 Revert "Per-thread allocation counters and limits"
9f3e39d Fix over-zealous unused-import warning
1302d50 Add -fno-full-laziness to get consistent profiling output
cdca791 Changed profiling output is fine (according to Simon Marlow)
675c547 Improve comments and tracing in SpecConstr
3c3ce82 Modularise pretty-printing for foralls
5b73dc5 Second go at fixing #9061
13a330e Fix Trac #9071, an egregious bug in TcDeriv.inferConstraints
02227dd Add a bit more typechecker tracing
59b4e6d Adding missing test files for #9071
22ed9ef Update transformers submodule to new v0.4 rel
76820ca Improve tracing in Simplifier
0f978b5 Refactor buildClass and mkDictSelId a bit, to avoid the no_unf argument
4088799 Mark evaluated arguments in dataConInstPat
35be701 Preserve evaluated-ness in CoreTidy
b5ca10c Better error message in vectoriser
12332f1 Error message wibble, presumably due to recent changes in transformers
c302a46 Update .gitignore
2f9a846 testsuite: fix cgrun051 exit code
3ed867f testsuite: fix cc004
3abf949 Require transformers for T5979
fe8a378 Revert output of T5979
2745164 Comments only, on inert_fsks and inert_no_eqs
770e16f In splitHsFunType, take account of prefix (->)
b5cf17f Improve desugaring of lazy pattern match
315fff6 Typo in comment
1f8f927 Typo in note
4cfc1fa Lint should check that TyConAppCo doesn't have a synonym in the tycon position
21f17d0 Fix invariant in mkAppCoFlexible
214ad2d Fix globalRegMaybe for unregisterised build.
3fd7f54 Wibble to 4cfc1fae
b036424 Update Haddock submodule.
0148a1c Add strict ver. of (<$>): (<$!>) to Control.Monad
dd92e21 Set cabal files to default-language:Haskell2010
88c0870 Remove LANGUAGE pragrams implied by Haskell2010
fc0ed8a Add missing stack checks to stg_ap_* functions (#9001)
913b314 Avoid NondecreasingIndentation syntax in ghc-pkg
61fdafc Drop use of CPP in `bin-package-db`
d4aa4e4 Drop default-extensions:CPP in hpc-bin.cabal
2dd80f6 Convert `ghc-bin.cabal` to use others-extensions
e199891 Avoid trivial cases of NondecreasingIndentation
2389244 Add LANGUAGE pragmas to compiler/ source files
9a58cac Express OPTIONS_GHC as LANGUAGE pragmas
022f875 Refactoring around TyCon.isSynTyCon
bc7d49a Only uninstall signal handlers if they were actually installed (#9068)
882978d ghc: Update containers submodule
4dac3a4 base: Document Foreign.ForeignPtr (#8475)
b75d126 rts: remove stable-names from hashtable upon free
39aa1e9 integer-gmp: do not confuse ./configure (#8783)
3df1c51 Extract derived constants from nm output for various OSes differently.
3a61e6d Tighten up wording in the section on let-generalisation and MonoLocalBinds
eab173b Remove the bit about External Core from flags.xml
4117551 Re-add 'classP' with a compatible implementation and a deprecation notice
135489d Provide deprecated backward compatible implementation to 'equalP'
a8cba19 Catch some typos
3a04ce2 Fix below warning by including "unistd.h" also
a15d243 Harden imports in `DeriveConstants.hs` module
7e78faf Coercible: Unwrap newtypes before coercing under tycons
94c5767 Coercible: Test case for now broken(?) corner case
7d958ce Tweaks to note; also fixed unicode quotes
bc58d2e Simple eta reduction in call to adjustMatchResults, just a tidy-up
d8d9711 Make the unifier a fixpoint even for the free kind vars of a tyvar
d41aa76 Better pretty-printing for ClsInst
02437a1 More debug info for failures in typeKind and kindFunResult
427e205 White space only
4dea15a Bump bytes-allocated for T3064
b33f321 Typos in comments
864759c test.mk: Be liberal in accepting GHC_PKG output
b1436f5 Fix yet another bug in 'deriving' for polykinded classes (Trac #7269)
db869e7 Add missing test file T7269
6ed5430 Replace DeriveDataTypeable by AutoDeriveTypeable
ac2796e Store IfExtNames for PatSyn matchers and wrappers in interface file. This way, the Ids for the matchers/wrappers are reused by importing modules, and thus unfoldings are kept.
fb74d71 Assert that matcher-derived PatSyn types match the (redundant) stored types in IfacePatSyn
2745dfb Test Trac #9144
b95dbb5 T4006, environment001, T3307 all work on msys2
8668c54 Use mkTcEqPred rather than mkEqPred in the type checker
3c1f2f7 No need to call defaultKind in mkTcEqPred
e80089e Fix comment typo
a518500 Update Haddock submodule.
dcc6e04 Update T4891, T8639_api to follow 73c08ab10 (GHCi naming changes)
6c5017a Add .gitignore for autogenerated test files.
cd14075 Fix bitrotted GHC API test T6145.
a23f131 Add missing stderr file for tcrun045.
fc6a952 s/implict/implicit/i
a53fc11 Refresh recomp006 error message.
0c1974c Remove obsolete -fno-warn-amp from spec001
723095b Per-capability nursery weak pointer lists, fixes #9075
5a392ca Disable FixEither tests in TcCoercible
a8d81af mkHiPath & mkObjPath didn't need to be in IO
994d5e3 Remove deprecated -optdep options
660c3f9 Just formatting
96a95f0 Fix missing unlockClosure() call in tryReadMVar (#9148)
9e10963 Improve Note [Order of Coercible Instances] about Trac #9117
2da439a fix missing space
09dc9a8 Rename TypeRep.Prec to TypeRep.TyPrec
0ba74f6 Use mkTcEqPred rather than mkEqPred
da64c97 Fix inverted gadt-syntax flag for data families
b4856f9 Do pretty-printing of TyThings via IfaceDecl (Trac #7730)
6e8861c Use IfLclName instead of OccName in IfaceEqSpec
d02cd1a Add :kind test in T7730
dd99434 Comments only (related to Trac #7730)
d7a228b Set/update upstream repo url for haddock
fe59334 Export `TimerManager` from GHC.Event (re #9165)
c63a465 Subsume NullaryTypeClasses by MultiParamTypeClasses (#8993)
0a55a3c Fix egregious instantiation bug in matchOneConLike (fixing Trac #9023)
616f54b Test Trac #9023
3faf83e Add .arcconfig file. Do not use yet.
56ea745 Add ".text.unlikely" to recognized code sections on Windows.
c226d25 Emit error in case of duplicate GRE; fixes #7241
6ad11c4 Fix .arcconfig
9ff32f9 Typo
4627575 Tweak comments
2a463eb Fix compilation of cmm files with -outputdir (Trac #9050)
f9def07 Typo
009e86f Suggest Int when user writes int
ae41a50 Report all possible results from related name spaces
d3cae19 Add testcase for #9177 and adjust test output
6e50553 Update test results (last minuite changes)
3a2b21d Added link ends to role documentation.
6fa7577 Sorted the language options list alphabetically, and added missing options.
57cc003 Prevent line wrapping after the dash of an option.
7ac600d Make the matcher and wrapper Ids in PatSyn into LocalIds, not GlobalIds
63e1f09 Added more option implication documentation.
5c89f88 Merge branch 'master' of git://git.haskell.org/ghc
3bdc78b Make DeriveTraversable imply DeriveFunctor/Foldable
63d7047 Added testcase for #9069
1178fa4 Update mod73 test output
819e1f2 Use UnicodeSyntax when printing
6e4a750 Only use UnicodeSytanx pretty printing if the locale supports it
b021572 Test case: GHCi uses UnicodeSyntax if the loaded file uses it.
e577a52 Fix discarding of unreachable code in the register allocator (#9155)
fbdebd3 supress warning of bang wildcard pattern-binding (i.e. let !_ = rhs). This fixes #9127
ab3f95b s/-hi-diffs/-ddump-hi-diffs/ in docs (#9179)
b36bc2f Test case for #9181 (:browse GHC.TypeLits panic)
96a8980 Pretty-print built in synonym families in interfaces
2f8b4c9 Fix obscure problem with using the system linker (#8935)
9fd507e Raise exceptions when blocked in bad FDs (fixes Trac #4934)
70f58eb Remove unused --run-cps/--run-cpsz options
c025817 Don't use showPass in the backend (#8973)
66bddbb Check that an associated type mentions at least one type variable from the class
aa18a46 Improve documentation for -fwarn-unused-binds
52509d8 Document -fwarn-inline-rule-shadowing (Trac #9166)
59cdb99 Document explicit import/export of data constructors (Trac #8753)
4b4d81a Suggest -fprint-explicit-kinds when only kind variables are ambiguous
877a957 Better warning message for orphan instances (Ticket #9178)
4caadb7 Ship xhtml, terminfo, haskeline (#8919)
25fb4fe Add .arclint file
1946922 Make Ptr's parameter phantom
707bde5 Update test results with new orphan instance warning
f251afe Revert "Make Ptr's parameter phantom"
5bdbd51 Make Ptr's parameter phantom
faddad7 Improve the API doc description of the SmallArray primitive types
f764aac Fire "map/coerce" only in phase 1
fdf370e Forgot to amend before pushing...
0e6bc84 Make better use of the x86 addressing mode
9e6c6b4 Make FunPtr's role be phantom; add comments.
1153194 Clarify error message. See #9167.
8dcfdf9 Add comments about instances of type-level (==).
0f584ae Refine deprecation warnings in template-haskell.
051d694 Fix #9097.
6a1d7f9 Fix #9085.
e79e2c3 Fix #9062.
7b10d01 Test #9097.
9dbf340 Fix #9111.
f502617 Test #9085.
f73d42f Test #9111.
a9ff7d0 Typo in variable name, no functional change
edd5764 Some typos in comments
56f8777 Improve error message in Trac #8883
7817ec1 Comments only explaining the imports for GHC.Integer, GHC.Tuple
748bec4 White space only
e5257f8 Fix tyConToIfaceDecl (Trac #9190)
c8295c0 Simplify variable naming in tcDataKindSig
7d9feb2 Fix a serious, but rare, strictness analyser bug (Trac #9128)
7f467d0 Fix Windows build (wibble to fix for Trac #4934)
165ac4a Catch two typos
a600c91 Improve IfaceSyn a bit further
b60df0f Better debug printing
571f0ad Line up kind and type variables correctly when desugaring TH brackets
b637585 Fix elemLocalRdrEnv (Trac #9160)
970e5d9 Bytes allocated by haddock.base has crept up (again)
632fcf1 Remove forgotten redundant import
ce19d50 Fixes #95 :edit command should jump to the last error
0354fb3 Implement `Typeable` support for type-level literals (#8778).
5ffc68b Fix recomputation of TypeRep in the instance for Typeable (s a) (#9203)
e09be5f Update the incorrect comment on when function was introduced.
836981c Redo instance to be more efficient (see #8778, #9203)
00fc4ba Optimise the Typeable instance for type app a bit, and add a perf test
e38fe3b accept T9181 output
652c9e6 Haddock: haddock-library release and Travis stuff
2ba1a56 Only comments: add notes explaining the various oddities of the `Typeable` implementation for type-level literals.
2a41db3 In progress Backpack implementation docs.
46ec4ae haddock-library: allow 7.4.x building
453e0fd Typo
3d81359 Typos in comments
a52bf96 Finish the rest of the writeup.
b1888aa Typos in comments
b6693d3 A bit more tracing of functional dependencies
0ceb84e Tidy up the printing of single-predicate contexts
cdc7431 Add a new section to the manual about hiding things that a module doesn't export
aec9e75 Improve documentation of defaulting rules with OverloadedStrings
2e362dd Make splitStrProdDmd (and similarly Use) more robust
64224f1 Comment typo
9c621e9 Reject forall types in constraints in signatures
e47baaf More fixes and updates to implementation document
48abb88 Update documentation to follow 2dc3b476aff28
aa3166f Add fake entries into the global kind environment for pattern synonyms.
b6352c9 Simplify package dump for -v4
b847481 Fix #9047
95f95ed Fix up b84748121e777d
446b0e1 arclint: disable Bad Charset lint rule
4612524 sync-all: cleanup
bd07942 sync-all: delete dead code calling gitInitSubmodules
101c3f7 sync-all: die for real when required repo is missing
bdb5809 sync-all: make --no-dph work for all subcommands
9a131dd sync-all: set and check variable $repo_is_submodule
72fe49d sync-all: infer remotepath from .gitmodules file
518ada5 Mark T9208 as broken when debugging is on
7a78374 More updates to Backpack impl docs.
c1035d5 Fix regression in Data.Fixed Read instance (re #9231)
761c4b1 Minor refactoring of interface to extraTyVarInfo
8a0aa19 Comment the expect_broken for Trac #9208
0757831 Add Note [Placeholder PatSyn kinds] in TcBinds
a4a79b5 Describe signature mini-backpack.
d8abf85 Add more primops for atomic ops on byte arrays
ec550e8 Fixup c1035d51e to behave more like in GHC 7.6
db19c66 Convert loose sub-repos into proper submodules (re #8545)
97ac32a Typos in comments
881be80 Fix anchors in Haddock
9833090 Fix few Haddock parser brainfarts
d587ebd The linking restriction, no shaping necessary.
c7dacdb sync-all: Allow - in submodule URLs
c61260e Merge Thomas Miedema’s syn-all improvments
4bf3aa2 Fix sync-all get from a local working copy
bcccadd Fix “Checking for old .. repo” messages
04dd7cb Work around lack of __sync_fetch_and_nand in clang
84d7845 Lots of rewrites to further move toward new world order
950fcae Revert "Add more primops for atomic ops on byte arrays"
22c16eb Update parallel and stm submodules to have .gitignore
5bbbc7d arclint: update rules for xml files
ab105f8 Add new flag -fwrite-interface for -fno-code.
aa4c5e7 Add testsuite-related .gitignore files
af913ad s/KnownLit/KnownSymbol/g and a typo fix
0451f91 More allDistinctTyVars from TcDeriv to Type
2be99d2 In TcValidity.checkAmbiguity, skolemise kind vars that appear free in the kinds of type variables
fe0cbe4 Fix docs typo.
b80d573 Refactor extension-bitmap in Lexer
05120ec Make -fno-write-interface to all modes of GHC, not just -fno-code.
5031772 Revert "Make -fno-write-interface to all modes of GHC, not just -fno-code."
f4766c4 Comments only
1c0b5fd Add -XBinaryLiterals language extension (re #9224)
ec38f4a Minor updates to Backpack docs.
713b271 Whitespace only
4144996 Untabify and M-x whitespace cleanup
0763a2f Fix #9245 by always checking hi-boot for consistency if we find one.
767b9dd Simplify .gitignore files
88d85aa Add BUILD_DPH variable to GHC build-system
9b93ac6 Tyop in comment
dab0fa0 Update Cabal to BinaryLiterals-aware 1.20 version
40ba3da Expect test failure for T8832 on 32bit (re #8832)
f12075d Update 32bit & 64bit performance numbers
26f4192 Promote TcNullaryTC and TcCoercible to fast tests
9982715 Factor-out the `OverlapMode` from `OverlapFlag`.
6290eea Overlapable pragmas for individual instances (#9242)
b7f9b6a Eliminate `Unify.validKindShape` (#9242)
d5c6fd6 Document #8883 in the release notes
abeb2bb Remove dead code. Fix comment typo.
aed1723 Revert "Fix obscure problem with using the system linker (#8935)"
4ee4ab0 Re-add more primops for atomic ops on byte arrays
c44da48 Remove extraneous debugging output (#9071)
b735883 Avoid integer overflow in hp2ps (#9145)
9785bb7 Add a cast to new code in hp2ps
da8baf2 Unbreak TcNullaryTC testcase, by using MPTC
288c21e Replace thenM/thenM_ with do-notation in RnExpr
47bf248 Refactor checkHiBootIface so that TcGblEnv is not necessary.
94c47f5 Update Haddock submodule with Iavor's validate fix.
5f3c538 Partially fix #9003 by reverting bad numbering.
db64180 Check for integer overflow in allocate() (#9172)
d6ee82b Fix demand analyser for unboxed types
127c45e Test Trac #9222
e7b9c41 Fixup nullary typeclasses (Trac #8993)
f5fa0de Backpack docs: Compilation, surface syntax, and package database
70b24c0 Fix variable name in allocate()
f48463e Finish the simple elaboration algo
8afe616 Finish up incomplete sections
34f7e9a Control CPP through settings file (#8683)
b0316cd reading/writing blocking FDs over FD_SETSIZE is broken (Partially Trac #9169)
423caa8 compiler/ghc.mk: restore GhcHcOpts variable handling (Trac #8787)
dd3a724 ghc-pkg register/update --enable-multi-instance
34bae1f includes/stg/SMP.h: use 'NOSMP' instead of never defined 'WITHSMP' (Trac #8789)
b3d9636 remove redundant condition checking in profiling RTS code
5a963b8 Minor edits to Backpack design doc
3285a3d Mark HPC ticks labels as dynamic
23bfa70 Update transformers submodule to 0.4.1.0 release
4c91bc6 PrelNames cleanup
311c55d Update documentation
4b74f6c Update .gitignore
0567a31 Fix windows breakage (fallout from 34f7e9a3c998)
7cf2589 Set mdo in typewriter face
fa8553d Fix imports in GHC.Event.Poll when not HAVE_POLL_H (#9275)
55e7ab1 Do not print the result of 'main' after invoking ':main' (fixes #9086).
1d225d1 Private axiom comment in Backpack
74b6b04 Track gitignore update in submodule unix
ff7aaf5 More testsuite ignores.
7a15a68 Scott's updates to the impl paper.
d68c77b [docs/backpack] Get lint to stop complaining
afe7bc1 Add hyperref package.
a77e079 Start expanding out linking text
bd5f3ef rts: Fix #9003 with an annoying hack
77ecb7b Make the example a little more complex
61cce91 [backpack] Rework definite package compilation
3c9fc10 Avoid unnecessary clock_gettime() syscalls in GC stats.
c80c574 remove SPARC related comment in PPC code generator
e148d7d GHC.Conc: clarify that 'forkOn' binds to capability, not a 'CPU' or 'Task'
2f8d5e2 Fix typos in base documentation.
dbbc1e8 Integrate changelog entries from base-4.7.0.1 rel
8e396b0 Remove unused parameter in rnHsTyVar
edae31a Comments only
441d1b9 Declare official github home of libraries/unix
30518f0 Add a .travis.yml file
6a75bcd M-x untabify
b8b8d19 Activate tab checks
b7b3f01 Fix comment
c70a720 Typoes in comments
d591b19 Rectify some panic messages
31cde29 Fix note spelling
73bb054 Add travis-ci badge
ce4477f testsuite: Tweak T6048 bounds
708062b integer-gmp: tweak gitignore.
47640ca Test case for #9305
8af2f70 Typo in comment
1d71e96 Fix ghci tab completion of duplicate identifiers.
39630ab Avoid deadlock in freeTask (called by forkProcess)
16403f0 Acquire all_tasks_mutex in forkProcess
6da6032 add support for x86_64-solaris2 platform
22e992e Type classes
c85a3b0 Finish TCs section
194107e Update various performance benchmarks
cfeeded New testsuite verbosity level 4
300c721 Give performance benchmark deviation also in percents
4690466 Partially revert 194107ea9333c1d9d61abf307db2da6a699847af
c973c70 Add a clarifying comment about scoping of type variables in associated type decls
f6f4f54 White space only
f692e8e Define PrelNames.allNameStrings and use it in TcHsType
9b8ba62 Entirely re-jig the handling of default type-family instances (fixes Trac #9063)
d761654 Improve documentation of :set/:seti
0fcf060 Improve documentation of overlapping instances (again)
a065f9d Try to explain the applicativity problem
34ec0bd Rewrite coercionRole. (#9233)
5e7406d Optimise optCoercion. (#9233)
3b8b826 Workaround haddock parser error caused by 5e7406d9
da7cfa9 Richards optCoercion improvement made test cases fail the nice way
ef4e8c5 Test Trac #9323
8b6cd6e Include test case name in performance result
13cb4c2 Adjust a few performance numbers
10f3d39 Correctly round when calculating the deviation
612d948 Remove unused parameters in OptCoercion (#9233)
a520072 OK, I think we've finally solved granularity.
b542698 Build on travis with CPUS=2
350ed08 Reduce volume of typechecker trace information
3214ec5 Comments only
4b3df0b Further improvements to floating equalities
af28e61 Update Cabal submodule to HEAD (1.21)
b34fa11 Set i686 as the minimum architecture on 32-bit mingw
c41b716 travis: Install process via cabal
5246346 Merge branch 'master' into wip/ext-solver
More information about the ghc-commits
mailing list