[commit: ghc] ghc-lwc2's head updated: Removes tabs from tab-free files. (d52fcc8)

git at git.haskell.org git at git.haskell.org
Fri Sep 27 20:13:35 CEST 2013


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

Branch 'ghc-lwc2' now includes:

     ade1ae9 Enable -funbox-small-strict-fields by default
     11a85cc extended ticky to also track "let"s that are not conventional closures
     9e390fd Don't suppress foralls in the RHS of a type synonym definition!
     3722f03 Improve documentation of kind polymorphism
     f3472f5 Make isPredTy not use typeKind
     db07129 Eliminate (given) flatten-skolems in favour of user type variables
     7a7530a Fix kind quantification (again)
     d31dd88 In doTopReactDict, try lookup even if fundeps work
     bee30a6 Improve error message for existential newtypes
     ed54858 Do not duplicate work in SpecConstr (fix Trac #7865)
     71aaa3f Fix/update SayAnnNames plugin example code.
     c041b62 Reorganize mk/build.mk.sample a little.
     92191a3 Allow deriving Typeable for more tycons
     ad1bc9d Update the name cache when creating new names via DeriveGeneric
     4be70f9 Treat foreign imported things in CMM as being in this package
     a5a52d7 Fix dynamically linked GHC on Windows
     ba00c33 Fix the name of libffi
     dca18dc Generate dependencies for .cmm files properly
     674cf90 rts_checkSchedStatus: exit the thread, not the process, when Interrupted
     0499eac Make -fno-flat-cache use a dynamic, rather than static, flag
     8241cdd Remove a redundant wrapper function
     3d51be4 Make sure the RTS is built, even when no programs are being built with stage1
     eb569b6 Fix an all-target call in the build system
     315b36b Some build system tweaks
     40cdee7 Modernise code in rename/RnEnv.lhs
     fe427ea Remove an old commented out import
     3a1ecd9 Whitespace only in typecheck/TcHsSyn.lhs
     ee4a534 Remove a "mappM = mapM" wrapper in typecheck/TcHsSyn.lhs
     4e84e51 Remove a "returnM = return" wrapper in typecheck/TcHsSyn.lhs
     a2be710 Modernise some code
     b2cae55 We actually need to use -threaded/-debug when linking /all/ DLLs
     b935841 Remove obsolete documentation.
     b35a6ce More work towards dynamic programs on Windows
     0aae298 Merge win:/cygdrive/c/ghc/git/dt
     9d18aea Merge branch 'master' of http://darcs.haskell.org/ghc
     089cb62 Kill dead code.
     1cc96d5 Remove redundant cmmMakeDynamicReference' wrapper
     7e723a1 Refactor cmmMakeDynamicReference
     58dcced Use NatM_State record fields, rather than matching/constructing the whole type
     b8447a9 Make the current module available to labelDynamic
     c8b7918 Cleaning up ChameneosRedux
     ff1a16a Simplify ghc-cabal
     60b86b0 Fix the GHC package DLL-splitting
     bb2795d Merge branch 'master' of http://darcs.haskell.org/ghc
     69a343a Fix ghci on Windows when GHC is dynamically linked
     f00fac6 schedulePushWork eagerly releases the capability if there are pending upcall actions. Standardized MVar interface in chameneos-redux benchmark -- explicit use of resume tokens and result holes (for takeMVar) does not seem to buy much.
     2c9cb4d Stop excluding the dyn way for the dph packages on Windows
     192c7b7 Define the right RTS config in the Windows dyn wrapper programs
     41e5229 Link to the right RTS whenever we build a .dll on Windows
     8a58851 SpecConstr: seed specialisation of top-level bindings, as with letrecs.
     a91e230 Comments only
     a18ea4f Make 'undefined' have the magical type 'forall (a:OpenKind).a'
     fe389f5 Make splitHsAppTys look through parentheses, fixing Trac #7903
     1d4704d Improve pretty-printing of inline-family pragmas; fixes Trac #7906
     0452021 Fix typechecking of pattern bindings that have type signatures (Trac #7268)
     ca2d30c Comments only
     672553e Make reifyInstances expand type synonyms robustly (Trac #7910)
     efc515a Don't try to build bindist wrappers on Windows
     d533da9 Merge branch 'master' of http://darcs.haskell.org/ghc
     9fc2778 Documentation: use new syntax for record GADTs (#7915)
     c6a05a7 Make dynamic GHC no Windows installable too
     8ed0bda Don't link base/rts/... into C wrapper programs
     a08759d Move the genSym stuff from rts into compiler
     b519e00 Don't try to make windows-installer
     a44978b Update a comment; spotted by Carter Schonwald
     891857a Fix parsing export lists
     a4cc7b1 Remove unused __2Int_encodeDouble
     e20dfbc Expose __word_encode{Float,Double}; fixes integer-simple build
     f7e33ca Add some extra debugging info
     fdd552e Fix a build problem with integer-simple
     bf6854b Fix build problem: Error: junk `.get_pc_thunk.bx' after expression; trac #7799
     6acfc45 We can't use Integer literals when compiling the integer-* package, either
     83a9f4f Refer to the wiki page in the "Make has restarted itself n times" error
     1227600 Need to work around #7799 on all i386 platforms, not just Darwin
     5734f7a Fix -dynamic-too on Windows
     ce89bde Simplify kind generalisation, and fix Trac #7916
     22574cf fix comment (#7907)
     1d3fa86 Fix a problem caused by very large objects (#7919)
     1e2b378 Handle -opt<blah> options more consistently (#7909)
     6cc5bd7 Make AutoDeriveTypeable derive Typeable instances for promoted data constructors
     6806906 Fix #5863
     09b025e Wibbles to yesterday's "Simplify kind generalisation" patch
     b80fcce Comment typo
     ca78233 If the upcall thread is killed, RTS Schedule loop raises exception. Sanitized comments.
     d8dd3cf Fix crash with large objects (#7919)
     6f36790 Add an echo target to the build system
     2ea79ab Revert "Fix -dynamic-too on Windows"
     20d8e8c Don't try to use -dynamic-too on Windows
     cf7e2fa Accept derived Read on an empty data type (Trac #7931)
     3d0d8d0 Do not do an ambiguity check on the type in a GHCi ":kind" command
     b94e98a Print kinds of non-* tyvar binders in pprTyThing
     efc8ad1 Give 'unboundName' a very low binding precedence
     cfb9bee Check for illegal syntax in types (fixes Trac #7943)
     1ed0409 Make 'SPECIALISE instance' work again
     5949ff2 Refine 'type_determines_value' in Specialise.  Fix Trac #7785.
     8d49ef1 Use new TcHsType.zonkSigType to establish Type invariants
     936001c Improve validity check to give better error message
     827cc50 Eta-reduce data/newtype family instance axioms (Trac #4185)
     30059bd Fix Read for empty data types (again; Trac #7931)
     bc5bf1b Remove an out-of-date comment
     ac330cb Add a primitive for coercing values into dictionaries in a special case.
     896d0f1 When verbose, give more information about cache status
     26c7d94 Run ghc-pkg check during validate
     7849266 Merge branch 'master' of http://darcs.haskell.org/ghc
     3d81b68 Define chkAppend, and use it
     d0ecba6 Fix a trailing case in making FamInstTyCon, where the invariant didn't hold, leading to subsequent chaos. Happily an ASSERT caught it.
     192a8f9 set DYNAMIC_GHC_PROGRAMS to NO if platform does not support shared libs
     8e51a7a add arm-unknown-linux to platforms which do not support shared libs
     fc9229d Build statically when using LLVM.
     da345e4 Use the symmetric version of the newtype coercion.
     f83994e Add a comment
     8c4d1ea Fix a comment
     f05cbb1 Untabify
     f39ca29 Untabify
     a740302 Untabify
     9a2f8cc Untabify
     bc44435 Add the ability to customize the continuation prompt.
     22e5b88 Formatting only: fix alignment.
     9ac83e9 Reformat help message for `:show` to fit into 80 cols again.
     cef115f Whitespace only
     d43d63f Fix thunk leak in CoreM's CoreWriter
     2642fe6 Update docs for "set prompt2"
     4770877 Imrove Lint to check unfoldings
     967f746 Fix panic on deriving a nullary typeclass (#7959)
     da4ff65 Comments and white space only
     99d4e5b Implement cardinality analysis
     507c897 Comments about the Name Cache
     6265312 Wibbles (merg-os) to ticky-ticky
     a1a67b5 Add TyCon.checkRecTc, and use in in typeArity
     9b817e5 Remove bogus-looking check, which was causing Trac #7894
     3e7e5ba Use checkRecTc to improve demand analysis slightly
     6673386 Transfer strictness on trivial right-hand sides
     4669c9e Add important missing case for bothCPR
     b2ba8ae Make the simplifier propagate strictness through casts
     9616743 Take proper account of over-saturated functions in CoreUnfold
     7f2a10f Better computeDiscount for ValAppCtxt
     821b077 Traces and comments only
     c0e4eef Whitespace only in compiler/simplCore/CSE.lhs
     cfe92a8 Remove old representation of CSEnv; part of #5996
     a28731b Add --show-options to list all flags (Fixes #7843)
     0d86038 Improve the version numbers generated by the build system
     972c044 use libffi for iOS adjustors; fixes #7718
     16dc39e Outline 7.8.1 release notes.
     1c5b051 Add support for byte endian swapping for Word 16/32/64.
     86ca77e Fix warnings
     6388932 Merge branch 'master' of http://darcs.haskell.org/ghc
     f7c8c3d Whitespace only
     68ba223 Fix a comment
     22690c9 Remove ghc.spec
     96eca81 Change how we check that we have a suitable 'make'
     4c49772 Rarrange the distclean list; part of #7941
     31b2706 Don't create mk/stamp-h
     8c846f7 Fix substitution but in liftCoSubst (Trac #7973)
     0239d78 Fix egregious typo in cmpTypeX
     1cbfddb Make sure we quantify over the context in data constructors
     fc927b3 Trace statements only
     6ecfa98 Actually make the change described in 'Fix egregious typo in cmpTypeX'
     716c2ae Merge branch 'master' of http://darcs.haskell.org/ghc
     57fa437 punctuation in comment
     2f9278d Typo in comment
     91979ed Revert "Add support for byte endian swapping for Word 16/32/64."
     4aa7fc8 Comment out function; consequence of reverting a553f18
     262cab0 Fix the constraint simplifier (Trac #7967)
     355d57a Remove trace that sometimes causes a loop
     289be61 Remove dead code
     db9b631 Avoid generating empty llvm.used definitions.
     a532f40 Typo in hp2ps help output
     2280f96 --show-options lists all flags. Add user documentation for #7843
     5483b14 Cleaning fixes, and other build system tweaks; part of #7941
     9e4348e Whitespace only in rts/storage/SMPClosureOps.h
     5d9e686 Optimization for takeMVar/putMVar when MVar left empty; fixes #7923
     d61c623 Allow multiple C finalizers to be attached to a Weak#
     6770663 Check for a weak pointer being dead before we do any allocation for it
     fe652a8 Maintain per-generation lists of weak pointers (#7847)
     4ca8642 Add braces for clarity
     9a8c20d Whitespace and braces only
     75947bb Optimise lockClosure when n_capabilities == 1; fixes #693
     b097dc9 Fix ghci crash when the user code closes stdin
     71a194d Detect linker information at runtime. Fixes Trac #6063
     6bd6139 Release note blurb for Linker fixes.
     8f2f7a0 Add some missing clang bits to the build system.
     5dc98a0 Work-around clang weirdness by adding a newline.
     4c01e10 Use ideclImplicit to filter out only *implict* Prelude imports (Trac #7963)
     b2cde43 Emit addUsedRdrNames for the datacons in a standalone deriving (Trac #7969)
     73991d6 Remove redundant import, revealed by the fix to #7963
     7b0695a Use assembler-with-cpp mode when running CPP.
     232737a Suppress some more warnings from Clang.
     d8ee2b0 Fix many ASSERT uses under Clang.
     991f285 Fix rts/packages.conf.in ld-options for clang.
     ebf97ad Untabify rts/packages.conf.in
     5dc74f3 Actually fix rts/packages.conf.in ld-options.
     e140837 Fix typo in header guard.
     32edb6e Revert "Actually fix rts/packages.conf.in ld-options."
     0ee9287 Revert "Untabify rts/packages.conf.in"
     1898ea0 Revert "Fix rts/packages.conf.in ld-options for clang."
     2ca4890 Re-untabify rts/packages.conf.in
     f2c477e Fix #7661 regression.
     6ca7525 Support QNXNTO for arm under LLVM
     1a98329 Fix rts/package.conf.in ld-options for Clang.
     3b02251 Document -fwarn-dodgy-imports changes in release notes. Trac #7167.
     e4fc6fd Add release note blurb for Clang support.
     88e97d9 Initialize ptr to NULL to silence Clang warning.
     eeeec4f Don't use -finline-limit with Clang.
     fe6db46 Ensure gc_thread->wakeup is of type StgWord8.
     37e3f3f Ensure gc_type is StgWord8.
     11db9cf Typo in note
     569b265 Revise implementation of overlapping type family instances.
     e381543 Whitespace only in HeaderInfo
     ffe2e22 Fix #8009 : Failure to compile on powerpc64-linux.
     0cb19bc Remove extra dashes in a flag name in the user guide
     74a800b Use consistent dashes in the user guide
     96ca465 The help flag is --help, not -help; fixes #8005
     451e0dd Fix syntax in some code in the user guide; fixes #8007
     f792ba4 Merge branch 'master' of http://darcs.haskell.org/ghc
     3660ef9 Fix build on OS X
     9ffe792 On OS X, fix the path to the libffi dynlib; fixes #7833
     499d698 Run "sh ./configure" rather than "sh configure"; part of #7992
     bdc3775 Add a work-around for #7978.
     92f36df Fix the dynmaic library paths in the libs, as well as in the programs
     7be5b44 Fix dynlib paths in the RTS too; part of #7833
     03fbf8a Merge branch 'master' of http://darcs.haskell.org/ghc
     f81e14b Allow the GHCi messages to be overridden via the GHC API; fixes #7456
     ed341a2 Re-adjust whitespace
     2066702 Break loop in interface typechecking (fixes Trac #8002)
     59d6942 Tidy up the segmentation of mdo expressions
     d2c3630 Make sure that Pretty.text is inlined in stage 0, so that RULE text/str gets a chance to fire (Trac #7995).
     e662c62 Allow associated types as sub-names in an import list (Trac #8011)
     e1cdaf3 White space and ordering only
     e0801a0 Update the package database directory's timestamps when rebuilding the package cache.
     0cb60ce Further fixes in RnNames, to make associated type exports work
     316e8cb Document -XTypeOperators, which had escaped documentation altogether thus far
     57284db Make noteMustPointToIt true of all non-top-level thunks
     aa4c36e Fix typos
     d67b993 Improve "No data constructor has all these fields" message (#7989)
     a7798e9 Comments for Trac #7989
     280a7ec Rework LLVM metadata representation to be more accurate.
     3b1d920 Add ability to call functions with metadata as arguments to LLVM backend.
     12148d9 Iteration on dterei's metadata design
     99d3922 Use SDoc for all LLVM pretty-printing
     720a87c Extend globals to aliases
     8f0ecc0 Rewrite ppLlvmBlock to use standard library "break"
     fa6cbdf Use full contents size for arrays
     a948fe8 Major Llvm refactoring
     fe44d05 LLVM refactor cleanups
     8c5e734 Fix Trac #7939, and add kind inference to closed type families.
     9b456df Fix stale comments around closed type families.
     6a25e92 Update user's guide for kind inference for closed type families.
     01234ec Merge branch 'master' of ssh://darcs.haskell.org/srv/darcs/ghc
     7f65874 Merge TcSMonad.matchClass into TcInteract.matchClassInst
     fb96f13 Fix Trac #8018.
     e56b9d5 Merge branch 'master' of ssh://darcs.haskell.org/srv/darcs/ghc
     1ae72ac Fix #7970, #2161, unfix #551
     98810fe Fix build on Win64
     aec9b2d Fix bumpTickyLitBy[E] on Win64; fixes #7940
     448b981 Track haskeline Win64 fix
     67aacde Fix Trac #8028.
     fdc3761 Do not build dynamic libraries with the perf-llvm BuildFlavour.
     c548fec Change the ranlib detection
     606ec0a Merge branch 'master' of http://darcs.haskell.org/ghc
     a5b7ee5 Comment out a leftover pprTrace
     163de25 include FastString.string_table in CoreMonad.reinitializeGlobals
     279ac9f copy the plugin's FastStringTable changes back into the host compiler
     126285e Fix llvm.prefetch instrinct for old LLVM versions
     a421252 Always have LLVM optimize globals
     405a20c Remove spurious extra brace in LLVM metadata
     a5913a2 Avoid needlessly splitting a UniqSupply when extracting a Unique (#8041)
     60cb478 Fix segfault with STM; fixes #8035. Patch from errge.
     36a5417 emacs-friendly completion command for ghci; part of #5687. Patch from hvr.
     195626f Docs for ghci completion command for ghci; part of #5687. Patch from hvr.
     b16cb73 Alpha rename some functions for consistency
     12ed5c2 Fix build
     08a3862 Disable executable stack for the linker note, fixing #703 (again)
     ca9a431 Merge branch 'master' of http://darcs.haskell.org/ghc
     70e2063 Implement atomicReadMVar, fixing #4001.
     3a8c501 Add LOCK_CLOSURE macro for use in C--, which inlines the capability check.
     190d34a Don't call dirty_MVAR on atomicReadMVar unless we change the MVar.
     db8d4a3 Implement tryAtomicReadMVar#.
     94f2057 Release note for atomicReadMVar and friends.
     f6e9d4f Fix typo in description
     48f462f Rename atomicReadMVar and friends to readMVar.
     4115f23 This reverts commit 163de25813d12764aa5ded1666af7c06fee0d67e and commit 279ac9f66a83203448b279ea478b2cc1dafbd35d.
     193e0ee adding FastString.string_table to the sharedCAF/Globals.c mechanism
     2f99cdb Update docs for readMVar/tryReadMVar.
     18087a1 Add support for byte endian swapping for Word 16/32/64.
     95e6865 Fix bug in readMVar implementation: keep clean MVars clean.
     7cbce1d Sync the list of default warnings with reality; fixes #8060.
     49fc268 On second thoughts, don't document -fwarn-alternative-layout-rule-transitional
     d3e0c76 Document -fwarn-pointless-pragmas; fixes #8049
     9d88904 Add `:show linker` command to `:help` output
     9b8b448 Add `:show imports` to completion table
     e7de764 use prompt2 in `:set +m` mode
     76d0cbc Add final remaining bits to fix #7978.
     be89c67 Temporarily disable common block elimination; fixes #8083 for now
     c234885 Fix a bug in stack layout with safe foreign calls (#8083)
     de0f6c5 Whitespace only in deSugar/Desugar.lhs
     8fe9eff Remove an unnecessary-looking import
     cf8fba9 Some release note additions.
     862b6d0 Use OrdLists when parsing export lists
     75f762c Remove redundant parentheses
     f749f06 Whitespace only in basicTypes/Avail.hs
     0fa7cc9 Whitespace only in basicTypes/BasicTypes.lhs
     fb520bb De-orphan a load of Binary instances
     385055c Beautify a few Binary instances
     ebaa332 Whitespace only in basicTypes/RdrName.lhs
     8f377cc Whitespace only in deSugar/Match.lhs
     b475be3 desugar code even when -fno-code is used; fixes #8101
     9e185cc Remove an out-of-date comment (see #8101)
     9e118d0 Move libffi's tarball into its own repo
     1e25859 Rename doDynamicToo to dynamicTooMkDynamicDynFlags
     e977524 Make sdist make a separate tarball for the Windows tarballs
     a10e199 Change which files --make mode thinks are 'Haskellish'
     0a3663b Added operational semantics to docs/core-spec.
     838e2fd Add strength reduction rules (Fixes #7116)
     4d7c6d0 Fix typos
     5090288 Merge branch 'master' of ssh://darcs.haskell.org/srv/darcs/ghc
     b74c73b Whitespace only in deSugar/MatchLit.lhs
     4e7eb3a Add a warning for overflowing literals; fixes #7895
     ef73963 Add NegativeLiterals extension
     ffd7da3 Document the Negative Literals extension
     02b7c1c Add -XNegativeLiterals to the flag list
     abb3a9f Add a warning for empty enumerations; fixes #7881
     bd0ab6c Fix Trac #8020.
     303d3de Update to Cabal to allow RoleAnnotations
     e8aa8cc Implement "roles" into GHC.
     3cd1360 Refactor checking for GADT-like datacons' return types
     968998e sync-all : Warn on 'pull' operation if not on master branch.
     cda5054 mk/config.mk.in : Add powerpc-unknown-linux to NoSharedLibsPlatformList.
     334131b .gitignore : Add libffi-tarballs.
     9082111 Added support for writing and checking closed type families is hs-boot files.
     0daee29 sync-all : Replace '~~' operator with something supported by older Perl.
     253a5b7 Rename SSE -> XMM for consistency.
     3e598fe Only use real XMM registers when assigning arguments.
     a22e908 Normalize urls for Git submodules
     4f43572 Make `sync-all remote set-url` use normalized `/packages/` urls
     c12df18 sync-all: remove trailing '/' from root-urls in help text
     b264f09 Whitespace change to test Trac/Gitolite.
     c08bf88 Fix typo
     11814a8 GHCi: Implement `%l` prompt substitution for line-number
     94be588 Release notes for #8108.
     e2b72ca Mark retry# as returning bottom.
     789acb2 Fix invalid users guide synax.
     c24ce5a Comments only
     a27895b Add a missing untag to the non-updatable selector thunks (#7978)
     5fb7255 Fix Stage1Only: don't build ghctags.
     288ca49 iOS: generate archive files when compiling.
     efde8ec Bump supported llvm version to 3.4.
     3332737 Don't run the system linker unncessarily.
     6579a6c Comparison primops return Int# (Fixes #6135)
     94c35dd Don't delete HsTimeConfig.h.in during distclean.
     ec621f3 Comments only
     82d5aa0 Comments only
     ac382ab Fix Trac #8138.
     2e41f2f Add support for external repositories to sync-all
     751e38f Eliminate trailing whitespace from Lexer.x
     a6e53ea Eliminate trailing whitespace from Parser.y.pp
     c498062 Remove dead code, fix a typo.
     5d77d8d Dead code elimination.
     96adf0e Improve error when using forall with UnicodeSyntax
     83440fd Comments only
     098c7d1 Add a better implementation of dropTail, and use it
     4d5c9b7 Improve eta-reduction some more, when the function includes casts
     f6ed2f5 Fix Haddock formatting
     2fcc09f Comments only
     c384bb1 Comments only
     4eeccc1 Replace occurences of darcs.haskell.org by git.haskell.org
     6cc7d3f Add note on isSafeOverlap field.
     21db803 Update Win32 submodule.
     9325b18 Comments only
     f661e79 Fix typo
     3f279f3 Trailing whitespaces, code formatting, detabify
     e5374a1 Cleanup StgCmm pass
     6b032db Remove unused module
     388e14e Merge cgTailCall and cgLneJump into one function
     d0b8c46 Comments only
     8d7272b Added bullet in release notes about roles.
     82bbc38 Added paragraph to user's guide about Nominal role for Set
     3ca7ecb add casArray# primop, similar to casMutVar# but for array elements
     1c45d05 Tweak stg_casArrayzh as per Simon Marlow's suggestion.
     4b4c944 Update stg_casArrayzh to conform to new CMM conventions.
     fa27838 Add PrimOp: casIntArray#.  Modify casMutVar# for 'ticketed' style.
     8750d54 Add PrimOp fetchAddIntArray# plus supporting C function atomic_inc_by.
     25ad015 Eliminate atomic_inc_by and instead medofiy atomic_inc.
     b38af65 Detabify
     372053c In the non-threaded RTS, make *_barrier functions EXTERN_INLINE, not #define. (fixes #8077)
     bdfefb3 Really unload object code when it is safe to do so (#8039)
     d060837 Only add -O to C compilations if there was -O on the command line
     4c864e2 Comments only
     c24be4b Update release notes for GHC 7.8
     6fd60b2 minor bugfix to casIntArray# and fetchAddIntArray#
     0717462 Remove DYNAMIC_GHC_PROGRAMS tests in the linker
     306fce6 Strings and comments only: 'to to ' fixes
     cbe3dba Update email addresses
     057628e MkIface: Mention that #include now adds dependent files
     02babd8 MkIface: More specific comment about what forms the interface hash
     4389cbd MkIface: When printing the recomp reason, make clear only mtime is used
     16ae2f0 MkIface: Be consistent with do notation
     677820e Fix interface hashes including time stamp of dependent files.
     7aa922b Fix -Werror failure in Fingerprint.hsc
     5258bff Remove trailing whitespace from MkIface
     726d08a Remove trailing whitespace from HscTypes
     3310068 Remove trailing whitespace from Fingerprint.hsc
     b6a572b Add some more comments to UsageFile.
     15616e7 Actually, split that last comment a bit.
     fba693f Remove dead code.
     d0ed42f Revert "Add support for external repositories to sync-all"
     80ac75f Fix windows detection in ./sync-all.
     48d7b0e Fingerprint: Fix comment typo
     41be8d3 Fingerprint.getFileHash: Fix not reading file at all.
     95ebff9 Fix validation failure in Fingerprint.hsc
     22625f7 Fix build for i386/windows.
     45cdba4 Remove unused ghc-frontpanel.glade file
     27955ff dll-split: Say where to update module list and fix a typo.
     3229ead Fix GHCi macros not shadowing builtins (#8113)
     a54ace7 Fix i386/Linux build.
     6a02f28 Fix build on non-unicode locale
     b7130bf Add support for iOS simulator (issue #8152).
     69d2678 Delete trailing whitespace in mk/config.mk.in
     959d827 Delete trailing whitespace in aclocal.m4
     4b5238a Delete trailing whitespace in LlvmCodeGen/Ppr.hs
     795fe08 Sync Cabal to upstream version 1.18 pre-release
     776cfe2 Properly externalise codegen identifiers (#8166)
     036910a UniqSupply: make mkSplitUniqSupply thread-safe
     b0a20f2 TcRnMonad: make forkM thread-safe
     d295a94 FastString: make the string table thread-safe
     74762a5 SysTools: make various functions thread-safe
     27d189a TidyPgm: Atomically update the NameCache in tidyTopName
     25f8cc8 Binary: Make lazyGet more thread-safe
     db34794 TcEnv: Make mkWrapperName deterministic and thread-safe
     e8d0dc7 Make stdout and stderr line-buffered
     8d9edfe Implement the parallel upsweep (#910)
     e2c0251 Binary: eradicate BinIO handles
     997a8ec Properly handle import loops in the parallel upsweep
     7f33152 Buffer stdout and stderr when we're compiling via GHCi
     6d755c0 Pass a DynFlags argument explicitly to typecheckLoop
     ef01794 Comments only, relating to #8166 fix
     56e28a3 GHCi: Implement new `:show paths` sub-command
     b982ab4 User guide entry for `:shows paths` sub-command
     a499ff7 Make `-ddump-minimal-imports` honour `-dumpdir` flag
     728bd07 Update `-ddump-minimal-imports` entry in user's guide
     382f601 Fix Trac #8186.
     477bc9b Improve error messages for roles by writing role names out
     1effad8 Add check for obsolete `darcs.haskell.org` repo urls
     4652a5d Clarify comments about apartness
     98b0d05 Rework how iOS does linking (#8127)
     9e02b02 Applicative instance for Ghc and GhcT
     a6be6f1 Implement -XNumDecimals (#7266)
     acea949 Detabify RnPat.lhs
     dace02d Document -XNegativeLiterals in the relase notes.
     b94d555 Wibbles.
     30697bf Mention iOS cross compilation in release notes.
     6e5fd38 Wibbles.
     1122f0d Fix validate failure.
     61d2838 More docs for -XNumDecimals
     ef9f994 Update Cabal to 1.18.0 RC2
     c86831b Update `bytestring` library to latest HEAD
     1d1ab12 Whitespaces and comment formatting
     d61c3ac Optimize self-recursive tail calls
     6df7438 Update submodules
     a34300c Revert "Update submodules"
     a1efe57 Display the full type environment when reporting type holes
     f5d148c Improve debug error message for applyTypeToArgs
     ff3d07a Improve TcSimplify.approximateWC, fixing Trac #8155
     04c9c3b Refactor to avoid gratuitous DEBUG warning
     33c880b Improve docs for -XNegativeLiterals
     c080f72 simplified the .hi format and added the -flate-dmd-anal flag (fixes #7782)
     99b58a6 Document :kind! in ghci built-in help
     4886552 Check for integer overflow in osGetMBlocks
     1ce65ed Paranoid integer overflow check in my_mmap
     1247dff Paranoid integer overflow check in osGetMBlocks
     c87c19f Revert "Paranoid integer overflow check in osGetMBlocks"
     d50e7ae Revert "Paranoid integer overflow check in my_mmap"
     29ee739 Revert "Check for integer overflow in osGetMBlocks"
     e4e976c Remove some redundancy.
     8c20f5d Add -fwarn-overloaded-literals to release notes.
     8940dd7 Add release notes about -dynamic-too
     acb91b9 Treat EPERM error from mmap as an OOM (#7500)
     bab28fb Add flag docs for -dynamic-too (#8181)
     099f954 Liberalising IncoherentInstances
     d9f4366 Improve documentation of the new IncoherentInstances behaviour
     f6a3bfe Release note blurb about IncoherentInstances.
     dea53ce Fix minor error regarding NumDecimals.
     d6c4467 Update containers to 0.5.2.1 release
     25f1bda Update binary to 0.7.1.0 release
     064e101 Haddockify documentation in HsBinds and HsExpr
     e87d158 Fix comment typos that interfere with syntax highlighting
     160160f Export languageExtensions as part of the API.
     85c1715 Fix off-by-one error in FastString.getFastStringTable (#8110)
     d55a4f3 Update time to 1.4.1 release
     26bf3dd Merge branch 'master' into ghc-parmake-gsoc
     1c33153 Rename DynFlags.parUpsweepNum to parMakeCount
     685582f Typo in release notes regarding -dynamic-too
     7e91e5b Note unloadObj changes in release notes.
     a2e338f Retain boot modules in getModLoop
     e446551 Update `haskeline` library to latest HEAD
     ea87014 Teach `validate` script how to `--help`
     e251a51 Merge branch 'master' into atomics
     8c99e69 minor: remove tabs from file
     b05caa7 Comment fix
     5f98d44 Explicit import lists for StgCmmProf.
     e4a1d2d Remove the final vestiges of InlineWrappers
     8d7dd54 Make Specialise close over kind variables (fixes Trac #8196)
     d5b81cb Improve documentation for the 7.8 release
     9e2e84e Comments only
     a137827 Extend `packages` by 4th column for upstream repo
     e525547 Patch by lukexi.
     dfa8ef0 Improve Linting in GHCi (fixes Trac #8215)
     32862bf Comment only
     1957fdd Comments and type synonym in CmmSink
     be7f10b Fix #7918
     62d3fde Allow non-Nominal covars (bugfix)
     fc4856f Make validate play nice with clang (for Xcode 5 command line tools)
     5a3918f Hack-fix build breakage on Linux/GCC from fc4856f9
     aa779e0 Don't move Capabilities in setNumCapabilities (#8209)
     356f793 Fix printf formats for pathchar on Windows (where it's wchar_t, not char)
     1fb558d Don't refer to oc->next after freeing oc.
     d3f002c Fix over-eager unpacking in isUnpackableType
     4a0b94b Improve debug tracing a bit
     4db3679 Put the interface-file typechecking of IfUnpackCo inside forkM
     e30c84c Make role inference work on the source type of a data con
     d02a50e Fix definition of DefinerOfRegs for CmmForeignCall
     5335e56 Turn manual Typeable instances into errors; fixes #8132
     32ade41 Add --show-options to --help (#8190)
     d127a69 Merge remote-tracking branch 'origin/master' into ghc-parmake-gsoc
     ba576e5 Remove -fglasgow-exts from --help
     9e133b9 Make sure -fcmm-sink is passed to Parser properly
     6fff216 Add a --no-dph flag to ./validate
     81bafce genSym: atomic_inc() now takes two arguments
     1f5338e Fix bootstrapping of GHC with earlier versions
     34728de documentation and comments for -ffun-to-thunk and -flate-dmd-anal
     8a8cfb2 Update `containers` to 0.5.3.1 release
     eb304bd Update `Cabal` to 1.18.0 final
     0451d85 Fix annoying iOS linker warnings (#8208)
     24b791f Ignore drectve sections, partially fixing #7056
     c1cbda5 docs only: update the release notes with atomic primops
     352a2bf Temporary Haskeline fix for Windows build.
     7e32b2a Windows: load eh_frame as rodata, fixes #8237
     df61477 Fix link to launchbury93natural
     67d1d4e Merge remote-tracking branch 'origin/master' into ghc-parmake-gsoc
     a58ba18 Have `ghc --info` report support for parallel --make
     b372e8e Add basic support for GHCJS
     021b1f8 Fix ghc-pkg list --simple-output not being alphabetical (#8245).
     2757258 Record PAP allocation to CCCS.
     c73d372 resurrected -fdicts-strict, off by default
     d85044f Default to infinite stack size (#8189)
     4129631 Avoid allocating while holding a lock (#8242)
     c798a8c Note infinite stack default in release notes.
     88dba61 Revert "Default to infinite stack size (#8189)"
     2cec084 Revert "Note infinite stack default in release notes."
     783ca39 Merge remote-tracking branch 'origin/master' into ghc-parmake-gsoc
     9fb1584 Remove -fwarn-typeable-instances
     9f8e9d2 Fix optimization of Parser.y.pp
     72ceffe Clarification in formalism concerning roles.
     c62a0b9 Revision to release notes for the new Typeable.
     9c18ad7 Merge branch 'ghc-parmake-gsoc' (#910)
     7740e25 Fix ./validate with GHC 7.6 as bootstrap compiler.
     d290ee5 Add release notes for parallel compilation driver.
     f342512 Typo fix. Spotted by Mikhail Glushenkov.
     80a53aa More release note fixes.
     a8a0764 Remove dead code
     32ee9b3 Improve -flate-dmd-anal documentation
     dc8b06e Comments only
     e365d49 Improve the insolubility check when quantifying
     9039108 Improve error reporting for "relevant bindings" again (Trac #8233)
     850490a factor 'tcRnModuleTcRnM' out of 'tcRnModule' and export it
     ed3c59a Update Git repo URL in `bin-packages-db.cabal`
     43111a0 GHCi: Fix multi-line input line/column-number refs
     bec3c04 Drop proc-points that don't exist in the graph (#8205)
     65e55c6 Update submodule `random` to point to latest HEAD
     1ef941a User guide typo: Missing ) in #language-pragma
     b20cf4e Fix AMP warnings.
     75a9664 Implement the AMP warning (#8004)
     66aa489 Add missing semicolon in rts/Linker.c (#8271)
     ad15c2b Improve sinking pass
     1f77a53 Add support for evaluation of type-level natural numbers.
     f56a787 Fix static GHCi build (#8270)
     6719877 Rename -ddump-cmm-rewrite to -ddump-cmm-sink
     8570fe7 Replace reference to `Data.Generics` with `Data.Data`
     a602fe5 Missing printf path format change
     fccb5c6 Update Cabal to current upstream `1.18` branch tip
     c228418 Release note for new `instance Data Data.Version`
     e239753 Allow primclass and class constraints in primops
     81928d0 Expose more in the TcS monad
     1f17065 Outputable.isOrAre: "is" or "are" for correct grammar
     638da2f Expose tcTyConsOfType as Types.tyConsOfType
     17a868a Introduce coerce :: Coercible a b -> a -> b
     8b9f71e Fix rebase fallout
     291ec13 Implement .init/.init_array support for ELF.
     30bf3ed Implement .ctor support for PEi386.
     e0885ad Implement __mod_init_func for Mach-O. Finishes support for init in #5435.
     9278994 Give language pragma suggestions without -X
     1534b1d Fix links in #special-ids section
     d159446 Mention coerce in the release notes
     57700b9 Fix getPageSize to actually cache the page size.
     d510f5e Nuke tabs in rts/posix/OSMem.c
     bf58295 add stg_MUT_VAR_CLEAN_info and stg_MUT_VAR_DIRTY_info to the symbol table
     81610b0 80 columns
     865956a Cause "make install" to install dynamic libraries (#8194)
     f11289f New primops for byte range copies ByteArray# <-> Addr#
     14677cd Fix freeHaskellFunPtr crash on iOS.
     bb53268 Fix the type signatures of new copy primops.
     769bfc7 Mention new solver for -XTypeNats in release notes.
     ea83174 Distinguish between hs-main cases when giving rtsopts advice.
     85a9e24 Run ctors initializers backwards, see #5435.
     9ef384d Comment typo only
     5f212c8 Release Notes: Document Data.Bool.bool (#8302)
     3ee4700 Make sure type literals aren't negative (#8306)
     7f6518c s/TypeNats/DataKinds/ in release notes.
     2eb4487 Typo in release notes
     9672b08 Further linguistic improvement of that one line
     bfe3c4c Implement ctors support for Linux.
     b647700 Add warning comment about Mach-O section name hack.
     4e2f6c2 Allow branches with / in them (e.g. wip/) in ./sync-all
     96421e0 Release Notes: New printf features in base
     f4046b5 Change role annotation syntax.
     53b2dc8 Suppress unused variable when OS does not support setuid.
     d80bd87 Fix-up Docbook XML broken in f4046b508a5a7
     b6bc326 Limit upper versions of Alex and Happy
     bd42c9d Implement checkable "minimal complete definitions" (#7633)
     b626989 Tweaks to release notes If someone also feels that credits should better go into the release announcement, just nuke the last line of that paragraph.
     7a4c15a Add flag to control loopification
     a5bdc6b A little refactoring
     8cfbdcc Accommodate Derived constraints in two places (fix Trac #8129, #8134)
     62c4058 Optimise (case tagToEnum# x of ..) as in Trac #8317
     03e44ee Tidy up and refactor overflow checking for literals
     6eec7bc Trailing whitespaces
     53948f9 Restore old names of comparison primops
     9078408 Comments only
     de4090b Make Word# a wired-in TyCon (fix Trac #8280)
     07f524c Fix egregious blunder in extractRelevantInerts
     17ba306 Remove trailing whitespaces in flags.xml
     291cb85 Document -floopification flag in user guide
     4916552 Update release notes for new comparison primops
     d85550e Comments only
     d57f2ad Ignore Tickish Breakpoints when serialising Core into interface files
     e17072d Refactor AMP warnings a bit
     3462534 Kill Type.isKindTy in favour of Kind.isKind (same code)
     15dc80e Nuke tc-trace that makes the typechecker loop
     86033a0 Improve error message for deriving polykinded Typeable (Trac #7800)
     d545b46 Comments only
     2fbfa11 Update `Cabal` to 1.18.1 final
     ffa8d22 Typos
     96cfb11 Fix name of vanilla RTS way in the user's guide
     da11bb1 Document more stolen syntax (#4196)
     1320fd2 Add release note entry for `{-# MINIMAL #-}` (#7633)
     efb9e82 Document remaining GHCi commands in users_guide (#7501)
     ea2af9b users_guide/ghci: Whitespace cleanup (#7501)
     6f79989 Restructure compilation pipeline to allow hooks
     6e6e6f5 Release note blurb.
     bdcf210 Ensure that globalRegMaybe returns accurate information for XMM registers.
     e02c506 Do not assume that XMM registers are used to pass floating point arguments.
     0f89b9e Enable passing vector arguments in xmm registers on x86-32.
     da5a647 Do not expose LLVM-only primops in GHC.PrimopWrappers.
     16b350a SIMD primops are now generated using schemas that are polymorphic in width and element type.
     638cd12 Flesh out 128-bit wide SIMD primops.
     0c6cf2a Add support for -mavx and -mavx2 flags.
     9d47e58 Add Cmm support for 256-bit-wide values.
     e074c1c Add support for 256-bit-wide vectors.
     afdb2fc Set LLVM option -stack-alignment=32 when compiling AVX instructions.
     f8c5167 Fixup stack spills when generating AVX instructions.
     0b561f1 Pass 256-bit-wide vectors in registers.
     7624815 Add 256-bit-wide SIMD primitives.
     03e33c9 Add support for -mavx512* flags.
     49f4c12 Add Cmm support for 512-bit-wide values.
     26a960c Add support for 512-bit-wide vectors.
     c5add86 Pass 512-bit-wide vectors in registers.
     7dda67b Add 512-bit-wide SIMD primitives.
     d2b9526 By default, only pass 128-bit SIMD vectors in registers on X86-64.
     1ed36c5 Enable -msse to be specified by itself.
     25eeb67 Check that SIMD vector instructions are compatible with current set of dynamic flags.
     680441d Merge branch 'wip/simd'
     e19ae5d Catch potential garbage after -msse.
     be3b84f Typos
     f5879ac Discard unreachable code in the register allocator (#7574)
     1908195 Fix linker_unload now that we are running constructors in the linker (#8291)
     93a04b4 Remove fglasgow-exts from ghci --help
     84dff71 Fix the definition of cas() on x86 (#8219)
     9c11fdb Fix build when PROF_SPIN is unset
     e2da02d Release notes: mention instance Monad (WrappedMonad m) (#8218)
     5cf3669 Add a type-function for subtraction.
     1c0a8e0 Typo in comment
     94ab5d2 Fix user guide documentation about unboxed values
     8da04f4 Pulling changes from head
     8e119d8 Merge branch 'ghc-lwc2' of /homes/chandras/temp/ghc into lwc-merge
     bd9f907 Minor changes to chameneos to remove the debugging messages. Pulling in newer libraries.
     d52fcc8 Removes tabs from tab-free files.



More information about the ghc-commits mailing list