[commit: ghc] simd's head updated: Pass 256-bit-wide vectors in registers. (8fb5fd9)

Geoffrey Mainland gmainlan at ghc.haskell.org
Fri Jul 19 14:17:00 CEST 2013


Repository : http://darcs.haskell.org/ghc.git/

Branch 'simd' now includes:

     d7da7fa Fix building the GHC package DLL on Windows
     9f8ee07 Merge branch 'master' of win:c:/ghc/git/cygwin/.
     b6a11fa Follow changes in Cabal
     56353e3 Finish adding support for 2 DLLs in the ghc package; fixes #5987
     f574b69 Remove tabs and trailing whitespace from TcTyClsDecls
     5319ea7 Implement nullary type classes (#7642)
     b712667 By default, use the dynamic way for programs in the GHC tree
     f5e2cca Set the way to 'dynamic' when running GHCi if GHCi is dynamically linked
     ca39e77 Implement type family instance support for ":info" (#4175)
     39f28cc Partial support for dynamic ghc on Windows
     a272adf Disable DYNAMIC_GHC_PROGRAMS on Windows
     e8459fd A little polishing
     28db4ca Fix searching for object files when doing TH
     ecc1882 Fix the handling of Opt_Static
     d2d71b0 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     1eb5a57 Update Cabal
     c84001d Remove readIface's unused argument
     ae3dcaf Remove a bitrotted hack for OpenBSD and NetBSD regarding the dyn way.
     84df08d Enable Opt_PIC for the dyn way regardless of OSes.
     0374cad Also build the v way when DYNAMIC_GHC_PROGRAMS is YES
     cf403b5 Remove some directories that used to be used by GUM
     c3a9ded Remove a couple of unused make variables
     24be4bc Fix ohi-sanity-check when we have ways other than v and dyn enabled
     eeccce1 Add a kludgy dependency to fix compiling modules that use annotations
     01efdd6 Only steal ~# as a reserved operator when MagicHash is enabled; fixes #7776
     0faa8f5 Remove base 3 support from bin-package-db
     be956c2 Fix stage2 build on ARM.
     c53ea7c Add support for OSX ld's -filelist flag
     effdd65 Merge branch 'master' of mac:ghc/git/val64/.
     ba2c753 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     387c4d1 Optimistically assume that LD_LIBRARY_PATH works for all platforms
     3df97a7 Be more optimistic about which platforms support shared libraries
     d0fc2a6 Fix building when $(CC_STAGE0) contains spaces
     0f49dd6 Remove some commented out build system code
     51bf365 Fix build with non-Linux ELF OSes
     cc097a4 Track subrepos Cabal
     024311c Remove some more old, unused code
     9f03486 Turn object splitting off when we use the dynamic way
     1c0af76 Fix the handling of ways, and in particular Opt_Static and Opt_SplitObjs
     9548ec5 Tweak the _HC_OPTS variables
     f4a2796 Small configure.ac refactoring
     b30015e Change how we handle libffi
     8575d01 Fix the names of the libffi archives
     98267a8 Allow to bootstrap with a compiler from the FreeBSD Ports Collection
     b9d5373 Heap profiling: flush .hp file at the end of each frame
     273183c Comment typo
     1b37a38 Comment only
     54bb2f8 Improve comments about dead code (thanks to Nick Frisby)
     81d55a9 Fix non-termination of SpecConstr (see #5550). ForceSpecConstr will now only specialise recursive types a finite number of times. There is a new option -fspec-constr-recursive, with a default value of 3.
     c7d80c6 improve dead code elimination in CorePrep (fixes #7796)
     460abd7 ticky enhancements
     0b72347 Make sure README.md mentions that make can build in parallel.
     e7ca132 Wibble.
     8ae3675 Revert "Wibble."
     9b4db4b Revert "Make sure README.md mentions that make can build in parallel."
     b4befc0 Make sure README.md mentions that make can build in parallel.
     6b431ab Fix installation
     9d33fc3 In build.mk.sample, include v in GhcLibWays even if DYNAMIC_GHC_PROGRAMS is set
     1128f1e This changes fixes a bad error in canonicalisation, concerning kind equality
     7501a2c Fix Trac #7805: don't allow nested foralls in promoted types
     f3bfbd5 Fix Trac #7804, about floating equalites
     b84da61 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     9b3d4cd Fix typos
     ff59fea When making a DLL, print the number of symbols that are in it
     ba7952b Change the list of modules that are put into a separate DLL on Windows
     9a14de4 Rename the FFI DLL to libffi.dll for consistency
     6534c99 Whitespace only in TysWiredIn
     575cb0c Split off a InteractiveEvalTypes module to remove an import loop
     872f2c8 Whitespace only in Type
     5df7cf3 Detab modules with tabs on 5 lines or fewer
     c0fb187 Derive instance Eq for CmmNode
     78544b7 Build system fix: really print the number of symbols in DLLs
     35a341d Rewrite usingInconsistentPicReg as a table for clarity
     93494bd Remove a redundant build-system hack
     8c2f280 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     d9b57e7 Typos
     444119f Add a check that the Windows DLL split is OK; fixes #7780
     a7b08c0 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     4373e84 Fix installation; fixes #7784
     e3abb5a Propagate ffi includes to compiler/ghci/LibFFI.hsc (Fixes #7686)
     8e02c0a Fix typos
     2e30197 Remove tabs (M-x untabify)
     a443303 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     9e46066 There can be several blocks in a PPC/ELF cmm proc add FETCHPC to all of them (this fixes #7814).
     63f3bd8 Generalise the type of fieldSz and use it more
     91a036f Remove some __HADDOCK__ CPP
     978afe6 Use the standard state monad transformer in GHCi
     75ed401 Remove CPP in ByteCodeItbls
     27cf625 Fix segfaults on SELinux machines; fixes #7629
     155d943 added ticky counters for heap and stack checks
     af12cf6 ignore RealWorld in size_expr; flag to keep w/w from creating sharing
     6afa777 Make explicit that there can be only one entry point per cmm procedure on Darwin/PPC, because of splitting.
     024df66 extended ticky to also track "let"s that are not closures
     37be6f0 Fix type variable scoping in nested pattern type signatures (#7827)
     3fc6ead Tidy up documentation of generalisation
     202f60a Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     d6ceeaa Change wording of "main is not defined in Main" message (Trac #7816)
     bad5783 Revert "extended ticky to also track "let"s that are not closures"
     52efb2c No need to map over all blocks, setting up PIC.
     47556a8 Whitespace only in CmmNode
     b5ac19a Fix the dynflags consistency code
     1aa7ae3 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     58e4f83 Improve the "main is not defined in Main" message a bit further
     29cc690 Make the desugarer a tiny bit cleverer on coercions (fixes Trac #7837)
     a56456d Comments and debug output only
     b088454 Remove accidentally-inserted tabs
     46e204f Allow partial applications of a type synonym in :kind in GHCi (Trac #7586)
     717d4a2 Merge branch 'master' of darcs.haskell.org:/home/darcs/ghc
     78f9189 Fix page numbering in the users guide PDF; fixes #7793
     87baa31 Check to see if TVar's are locked in check_read_only (fixes #7815)
     da65172 Comment only
     24ffa31 Merge branch 'master' of http://darcs.haskell.org/ghc
     5ba23df Remove boot-pkgs from SRC_DIST_GHC_FILES
     d6dd769 Update darcs -> git in a comment
     0ae042d Use a simpler way of finding the current git branch in sync-all
     55c7a0d Some sync-all refactoring
     561d64a Add a 'compare' command to sync-all
     432d104 Small build system refactoring
     54d7902 Small build system refactoring
     db14f97 Some build system refactoring
     9e4e2c2 Remove the Windows installer
     aa06f5d Follow build system changes in integer-gmp
     6579425 Add deriveConstants to the dep files we build in phase 0
     a8de924 Remove ghc-pkg from the list of dep files we build during phase 0
     7631562 Fix haddocking
     b45700c Tweak the bindist comparison tool
     c91c233 Fix typo (spotted by gabor)
     d65a61d Use different exeext variables for each stage; fixes #7709
     157ac08 Fix "make 2" in ghc/
     78d5644 Print details of panic messages raised from GHCi (#7844)
     144db21 Display operators using parentheses/backticks in error messages (#7848)
     310735e Use ffi_prep_closure_loc rather than ffi_prep_closure
     be66c4e Remove some cross-compilation kludges
     e781739 Use a pthread-based implementation of Itimer.c on iOS
     ca33aa8 pass the correct -Dxxx_HOST_ARCH and -Dxxx_HOST_OS to hsc2hs; Fixes #7761.
     2a17985 Update error message text; spotted bu Sergei Trofimovich
     a49fc52 Add stg_sel_n_noupd_info symbols to Linker.c
     72f8eab Add comments to describe AbsBinds
     ffe9a1e Tiny wibble to trace message
     c5f43e5 Comments only
     28c1461 When zonking, get rid of empty implications
     6ebab3d Never unify a SigTyVar with a non-tyvar type (fixes Trac #7786)
     2a7f4de Further wibbbling to type error message reporting
     5724ea0 More accurate cost attribution for stacks.  Fixes #7818.
     15da8ca Typos in comments
     2eea4ac Typo in debug print message
     392924c Comment typo
     ed9895d Comments and debug messages only
     a496e9a Make CmmParse abstract
     b49307f Don't duplicate decls unnecessarily in the environment
     dbd9645 Small refactoring in StgCmmExtCode
     be0b1df In CMM, only allow foreign calls to labels, not arbitrary expressions
     4ff7413 Allow deriving Generic for polykinded phantom types
     9e24b12 Update Makefile in docs/core-spec not to use latexmk
     b1c266c Updated documentation; changed "group" to "branched" in type families
     e83d0da Fixed moer tyops
     b3c0650 Fix the inplace name of ghc-cabal
     3e3707d Add a "Support dynamic-too" field to the --info output
     685f3b0 Whitespace only in StaticFlags
     0947a00 Update Cabal
     c9e7159 Remove some old commented-out code in StaticFlags
     c022831 Update the isStaticFlag predicate
     4d15f23 Mark -dynamic-too as unsupported for now
     ff2b7ad Update Cabal
     4b205b8 We need to setModLocation in the HscOut phase, not the Hsc phase
     25dd77f Fix "-dynamic-too --make"; fixes #7864
     4ae3def "ghc --info" now claims has "Support dynamic-too" as "YES"
     cee55b9 Remove DynFlags's hscOutName field
     da5c9c7 Whitespace only in MkExternalCore
     50ad870 Remove extCoreName from DynFlags
     ebc4305 Update Cabal
     9843083 When linking with $ORIGIN rpaths, use the "-z origin" linker flag too
     ce1094e Use -rpath flags on all Elf OSes, not just Linux
     c47c47a Handle sign bit when generating veneer for ARM Thumb branch relocation
     f6e0dbf Fix mismatched visibility of assembler impls of StgRun
     e5944d9 Don't use getPackageLinkOpts on iOS; fixes #7720.
     8ab3cc1 Set DYNAMIC_GHC_PROGRAMS=NO for FreeBSD because $ORIGIN is not resolved properly (see #7819)
     c797499 Fix linking with binutils 2.22 or later on FreeBSD 9.1, where one should explicitly link against any dependent library
     f6f1252 Fix build on Windows
     2cf5bd3 Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
     a9608cb Record libffi directory in rts package conf; trac #7465
     49e6606 Make "ghc-pkg field pkg field --simple-output" do something useful
     4d8ad58 Remove some old "backwards compatibility" code
     0c3a967 Update Cabal
     7a310c7 Small refactoring in ghc-pkg
     4a55e81 Tidy up some build system code
     23f5080 Add -L flags to libs.depend (fixes #7465)
     50e78da Fix build
     8a1b7eb Fix build on OS X
     d3149f6 Tighten up on the kind checking for foralls
     b988dc3 Suppress a misleading error message (Trac #7869)
     6d8d0dd Exend the "Too few args" message for naked Ids (Trac #7851)
     d75ca39 Fix comment to placate Haddock
     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
     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
     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
     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.
     9f968d4 Add support for -mavx and -mavx=2 flags.
     5401d5d Add Cmm support for 256-bit-wide values.
     f792079 Add support for 256-bit-wide vectors.
     6d51b17 Add DoubleX4# and associated primops.
     7d69e70 Set LLVM option -stack-alignment=32 when compiling AVX instructions.
     a7a9b85 Fixup stack spills when generating AVX instructions.
     8fb5fd9 Pass 256-bit-wide vectors in registers.




More information about the ghc-commits mailing list