summaryrefslogtreecommitdiff
path: root/compiler/llvmGen
Commit message (Collapse)AuthorAgeFilesLines
...
* Revert "Add more primops for atomic ops on byte arrays"Johan Tibell2014-06-263-66/+30
| | | | | | | | This commit caused the register allocator to fail on i386. This reverts commit d8abf85f8ca176854e9d5d0b12371c4bc402aac3 and 04dd7cb3423f1940242fdfe2ea2e3b8abd68a177 (the second being a fix to the first).
* Add more primops for atomic ops on byte arraysJohan Tibell2014-06-243-30/+66
| | | | | | | | | | | | | | | | | | | Summary: Add more primops for atomic ops on byte arrays Adds the following primops: * atomicReadIntArray# * atomicWriteIntArray# * fetchSubIntArray# * fetchOrIntArray# * fetchXorIntArray# * fetchAndIntArray# Makes these pre-existing out-of-line primops inline: * fetchAddIntArray# * casIntArray#
* Some typos in commentsGabor Greif2014-06-111-1/+1
|
* Add LANGUAGE pragmas to compiler/ source filesHerbert Valerio Riedel2014-05-159-7/+16
| | | | | | | | | | | | | | | | | | In some cases, the layout of the LANGUAGE/OPTIONS_GHC lines has been reorganized, while following the convention, to - place `{-# LANGUAGE #-}` pragmas at the top of the source file, before any `{-# OPTIONS_GHC #-}`-lines. - Moreover, if the list of language extensions fit into a single `{-# LANGUAGE ... -#}`-line (shorter than 80 characters), keep it on one line. Otherwise split into `{-# LANGUAGE ... -#}`-lines for each individual language extension. In both cases, try to keep the enumeration alphabetically ordered. (The latter layout is preferable as it's more diff-friendly) While at it, this also replaces obsolete `{-# OPTIONS ... #-}` pragma occurences by `{-# OPTIONS_GHC ... #-}` pragmas.
* Avoid trivial cases of NondecreasingIndentationHerbert Valerio Riedel2014-05-151-2/+2
| | | | | | | This cleanup allows the following refactoring commit to avoid adding a few `{-# LANGUAGE NondecreasingIndentation #-}` pragmas. Signed-off-by: Herbert Valerio Riedel <hvr@gnu.org>
* Validate inferred theta. Fixes #8883Jan Stolarek2014-04-191-0/+1
| | | | | | | This checks that all the required extensions are enabled for the inferred type signature. Updates binary and vector submodules.
* Fix new Haddock doc parse failures.Austin Seipp2014-01-121-7/+6
| | | | Signed-off-by: Austin Seipp <austin@well-typed.com>
* Re-work the naming story for the GHCi prompt (Trac #8649)Simon Peyton Jones2014-01-091-2/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The basic idea here is simple, and described in Note [The interactive package] in HscTypes, which starts thus: Note [The interactive package] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Type and class declarations at the command prompt are treated as if they were defined in modules interactive:Ghci1 interactive:Ghci2 ...etc... with each bunch of declarations using a new module, all sharing a common package 'interactive' (see Module.interactivePackageId, and PrelNames.mkInteractiveModule). This scheme deals well with shadowing. For example: ghci> data T = A ghci> data T = B ghci> :i A data Ghci1.T = A -- Defined at <interactive>:2:10 Here we must display info about constructor A, but its type T has been shadowed by the second declaration. But it has a respectable qualified name (Ghci1.T), and its source location says where it was defined. So the main invariant continues to hold, that in any session an original name M.T only refers to oe unique thing. (In a previous iteration both the T's above were called :Interactive.T, albeit with different uniques, which gave rise to all sorts of trouble.) This scheme deals nicely with the original problem. It allows us to eliminate a couple of grotseque hacks - Note [Outputable Orig RdrName] in HscTypes - Note [interactive name cache] in IfaceEnv (both these comments have gone, because the hacks they describe are no longer necessary). I was also able to simplify Outputable.QueryQualifyName, so that it takes a Module/OccName as args rather than a Name. However, matters are never simple, and this change took me an unreasonably long time to get right. There are some details in Note [The interactive package] in HscTypes.
* Fix validate failure.Austin Seipp2014-01-071-4/+4
| | | | Signed-off-by: Austin Seipp <austin@well-typed.com>
* Remove trailing whitespace.Austin Seipp2014-01-071-3/+2
| | | | Signed-off-by: Austin Seipp <austin@well-typed.com>
* LlvmMangler: Make sure no symbols slip through re-.typingBen Gamari2014-01-071-7/+12
| | | | | | | | | Previously a few symbols weren't flipped from %function to %object as the section splitter was emitting them without processes. This may be a bug in itself but for now let's just work around the issue but rewriting all symbol `.types`. Signed-off-by: Austin Seipp <austin@well-typed.com>
* LlvmMangler: Rewrite @function symbols to @objectBen Gamari2014-01-071-5/+11
| | | | Signed-off-by: Austin Seipp <austin@well-typed.com>
* LLVM mangler: fix AVX instruction rewriter.Austin Seipp2014-01-071-1/+1
| | | | | | | This was pretty badly broken... Authored-by: Ben Gamari <bgamari.foss@gmail.com> Signed-off-by: Austin Seipp <austin@well-typed.com>
* Typo: s/LlVM/LlVM/Joachim Breitner2013-11-171-1/+1
|
* Fix bug in LLVM code generatorBen Lippmeier2013-11-141-1/+5
| | | | The bitcast operation always needs a type for the source.
* Add support for prefetch with locality levels.Austin Seipp2013-10-011-4/+7
| | | | | | | | | | | | | | | | | This patch adds support for several new primitive operations which support using processor-specific instructions to help guide data and cache locality decisions. We have levels ranging from [0..3] For LLVM, we generate llvm.prefetch intrinsics at the proper locality level (similar to GCC.) For x86 we generate prefetch{NTA, t2, t1, t0} instructions. On SPARC and PowerPC, the locality levels are ignored. This closes #8256. Authored-by: Carter Tazio Schonwald <carter.schonwald@gmail.com> Signed-off-by: Austin Seipp <austin@well-typed.com>
* Pass 512-bit-wide vectors in registers.Geoffrey Mainland2013-09-223-0/+9
|
* Pass 256-bit-wide vectors in registers.Geoffrey Mainland2013-09-223-0/+9
|
* Fixup stack spills when generating AVX instructions.Geoffrey Mainland2013-09-221-1/+38
| | | | | | | | | LLVM uses aligned AVX moves to spill values onto the stack, which requires 32-bye aligned stacks. Since the stack in only 16-byte aligned, LLVM inserts extra instructions that munge the stack pointer. This is very very bad for the GHC calling convention, so we tell LLVM to assume the stack is 32-byte aligned. This patch rewrites the spill instructions that LLVM generates so they do not require an aligned stack.
* SIMD primops are now generated using schemas that are polymorphic inGeoffrey Mainland2013-09-221-0/+6
| | | | | | | | | | | | | width and element type. SIMD primops are now polymorphic in vector size and element type, but only internally to the compiler. More specifically, utils/genprimopcode has been extended so that it "knows" about SIMD vectors. This allows us to, for example, write a single definition for the "add two vectors" primop in primops.txt.pp and have it instantiated at many vector types. This generates a primop in GHC.Prim for each vector type at which "add two vectors" is instantiated, but only one data constructor for the PrimOp data type, so the code generator is much, much simpler.
* TyposKrzysztof Gogolewski2013-09-201-2/+2
|
* Fix AMP warnings.Austin Seipp2013-09-111-3/+12
| | | | | Authored-by: David Luposchainsky <dluposchainsky@gmail.com> Signed-off-by: Austin Seipp <austin@well-typed.com>
* Add basic support for GHCJSAustin Seipp2013-09-061-0/+1
| | | | | | | | | | | | | | | | | | | This patch encompasses most of the basic infrastructure for GHCJS. It includes: * A new extension, -XJavaScriptFFI * A new architecture, ArchJavaScript * Parser and lexer support for 'foreign import javascript', only available under -XJavaScriptFFI, using ArchJavaScript. * As a knock-on, there is also a new 'WayCustom' constructor in DynFlags, so clients of the GHC API can add custom 'tags' to their built files. This should be useful for other users as well. The remaining changes are really just the resulting fallout, making sure all the cases are handled appropriately for DynFlags and Platform. Authored-by: Luite Stegeman <stegeman@gmail.com> Signed-off-by: Austin Seipp <aseipp@pobox.com>
* Delete trailing whitespace in LlvmCodeGen/Ppr.hsAustin Seipp2013-08-241-2/+1
| | | | Signed-off-by: Austin Seipp <aseipp@pobox.com>
* Add support for iOS simulator (issue #8152).Austin Seipp2013-08-241-0/+3
| | | | | | | | The iOS simulator is essentially an iOS target but for an x86 machine instead. It doesn't support the native code generator either, though. Authored-by: Stephen Blackheath <...@blacksapphire.com> Signed-off-by: Austin Seipp <aseipp@pobox.com>
* Bump supported llvm version to 3.4.Austin Seipp2013-08-141-1/+1
| | | | | | | The compiler can bootstrap and run all tests fine, given a copy of LLVM built on Jul 27 2013. Signed-off-by: Austin Seipp <aseipp@pobox.com>
* Add support for byte endian swapping for Word 16/32/64.Austin Seipp2013-07-171-26/+35
| | | | | | | | | | | | | * Exposes bSwap{,16,32,64}# primops * Add a new machop: MO_BSwap * Use a Stg implementation (hs_bswap{16,32,64}) for other implementation in NCG. * Generate bswap in X86 NCG for 32 and 64 bits, and for 16 bits, bswap+shr instead of using xchg. * Generate llvm.bswap intrinsics in llvm codegen. Authored-by: Vincent Hanquez <tab@snarc.org> Signed-off-by: Austin Seipp <aseipp@pobox.com>
* Remove spurious extra brace in LLVM metadataPeter Wortmann2013-07-051-1/+1
| | | | | | | This actually caused a segfault in the optimized stage 2 compiler due to wrong TBAA data. Signed-off-by: David Terei <davidterei@gmail.com>
* Fix llvm.prefetch instrinct for old LLVM versionsPeter Wortmann2013-07-051-3/+6
| | | | | | Seems the last parameter to llvm.prefectch was added in LLVM 3.0. Signed-off-by: David Terei <davidterei@gmail.com>
* LLVM refactor cleanupsPeter Wortmann2013-06-273-28/+34
| | | | | Slightly more documentation, removed unused label map (huh), removed MonadIO instance on LlvmM to improve encapsulation.
* Major Llvm refactoringPeter Wortmann2013-06-277-940/+1103
| | | | | | | | | | | | | | | | | | | | | | This combined patch reworks the LLVM backend in a number of ways: 1. Most prominently, we introduce a LlvmM monad carrying the contents of the old LlvmEnv around. This patch completely removes LlvmEnv and refactors towards standard library monad combinators wherever possible. 2. Support for streaming - we can now generate chunks of Llvm for Cmm as it comes in. This might improve our speed. 3. To allow streaming, we need a more flexible way to handle forward references. The solution (getGlobalPtr) unifies LlvmCodeGen.Data and getHsFunc as well. 4. Skip alloca-allocation for registers that are actually never written. LLVM will automatically eliminate these, but output is smaller and friendlier to human eyes this way. 5. We use LlvmM to collect references for llvm.used. This allows places other than cmmProcLlvmGens to generate entries.
* Use full contents size for arraysPeter Wortmann2013-06-271-1/+3
| | | | | | I am not quite sure at what point it makes sense to look at arrays as pointers, but I ran into at least one use case that strongly suggested doing it this way (calculating the actual size of structures, to be exact).
* Rewrite ppLlvmBlock to use standard library "break"Peter Wortmann2013-06-271-13/+8
|
* Extend globals to aliasesPeter Wortmann2013-06-278-37/+43
| | | | | Also give them a proper constructor - getGlobalVar and getGlobalValue map directly to the accessors.
* Use SDoc for all LLVM pretty-printingPeter Wortmann2013-06-276-284/+284
| | | | | | | This patch reworks some parts of the LLVM pretty-printing code that were still using Show and String. Now we should be using SDoc and Outputable throughout. Note that many get*Name functions become pp*Name here as a side-effect.
* Iteration on dterei's metadata designPeter Wortmann2013-06-277-98/+49
| | | | | | | | | | | | | | | | | | | | | - MetaArgs is not needed, as variables are already meta data - Same goes for MetaVal - its only reason for existing seems to be to support LLVM's strange pretty-printing for meta-data annotations, and I feel that is better to keep the data structure clean and handle it in the pretty-printing instead. - Rename "MetaData" to "MetaAnnot". Meta-data is still meta-data when it is not associated with an expression or statement - for example compile unit data for debugging. I feel the old name was a bit misleading. - Make the renamed MetaAnnot a proper data type instead of a type alias for a pair. - Rename "MetaExpr" constructor to "MetaStruct". As the data is much more like a LLVM structure (not array, as it can contain values). - Fix a warning
* Add ability to call functions with metadata as arguments to LLVMDavid Terei2013-06-275-16/+51
| | | | backend.
* Rework LLVM metadata representation to be more accurate.David Terei2013-06-277-85/+167
|
* Support QNXNTO for arm under LLVMStephen Paul Weber2013-06-201-0/+3
| | | | Signed-off-by: Austin Seipp <aseipp@pobox.com>
* Avoid generating empty llvm.used definitions.Geoffrey Mainland2013-06-121-12/+12
| | | | | LLVM 3.3rc3 complains when the llvm.used global is an empty array, so don't define llvm.used at all when it would be empty.
* Comment out function; consequence of reverting a553f18Simon Peyton Jones2013-06-111-2/+2
|
* Revert "Add support for byte endian swapping for Word 16/32/64."Simon Peyton Jones2013-06-111-36/+24
| | | | This reverts commit 1c5b0511a89488f5280523569d45ee61c0d09ffa.
* Fix warningsIan Lynagh2013-06-091-0/+3
|
* Add support for byte endian swapping for Word 16/32/64.Ian Lynagh2013-06-091-24/+36
| | | | | | | | | | | | * Exposes bSwap{,16,32,64}# primops * Add a new machops MO_BSwap * Use a Stg implementation (hs_bswap{16,32,64}) for other implementation in NCG. * Generate bswap in X86 NCG for 32 and 64 bits, and for 16 bits, bswap+shr instead of using xchg. * Generate llvm.bswap intrinsics in llvm codegen. Patch from Vincent Hanquez.
* Fixed moer tyopsGabor Greif2013-04-251-8/+8
|
* Add iOS specific module layout entry to LLVM codegen; fixes #7721Ian Lynagh2013-03-021-0/+3
| | | | Patch from Stephen Blackheath
* Mimic OldCmm basic block ordering in the LLVM backend.Geoffrey Mainland2013-02-011-1/+1
| | | | | | | | | In OldCmm, the false case of a conditional was a fallthrough. In Cmm, conditionals have both true and false successors. When we convert Cmm to LLVM, we now first re-order Cmm blocks so that the false successor of a conditional occurs next in the list of basic blocks, i.e., it is a fallthrough, just like it (necessarily) did in OldCmm. Surprisingly, this can make a big performance difference.
* Add prefetch primops.Geoffrey Mainland2013-02-011-0/+21
|
* Add support for passing SSE vectors in registers.Geoffrey Mainland2013-02-013-37/+102
| | | | | | | This patch adds support for 6 XMM registers on x86-64 which overlap with the F and D registers and may hold 128-bit wide SIMD vectors. Because there is not a good way to attach type information to STG registers, we aggressively bitcast in the LLVM back-end.
* Add the Int32X4# primitive type and associated primops.Paul Monday2013-02-011-0/+23
|