summaryrefslogtreecommitdiff
path: root/compiler/GHC/CmmToAsm/PPC
Commit message (Collapse)AuthorAgeFilesLines
* PPC NCG: Fix unsigned compare with 16-bit constantsPeter Trommler2021-05-191-1/+2
| | | | Fixes #19852 and #19609
* Cmm: fix sinking after suspendThreadSylvain Henry2021-05-191-0/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Suppose a safe call: myCall(x,y,z) It is lowered into three unsafe calls in Cmm: r = suspendThread(...); myCall(x,y,z); resumeThread(r); Consider the following situation for myCall arguments: x = Sp[..] -- stack y = Hp[..] -- heap z = R1 -- global register r = suspendThread(...); myCall(x,y,z); resumeThread(r); The sink pass assumes that unsafe calls clobber memory (heap and stack), hence x and y assignments are not sunk after `suspendThread`. The sink pass also correctly handles global register clobbering for all unsafe calls, except `suspendThread`! `suspendThread` is special because it releases the capability the thread is running on. Hence the sink pass must also take into account global registers that are mapped into memory (in the capability). In the example above, we could get: r = suspendThread(...); z = R1 myCall(x,y,z); resumeThread(r); But this transformation isn't valid if R1 is (BaseReg->rR1) as BaseReg is invalid between suspendThread and resumeThread. This caused argument corruption at least with the C backend ("unregisterised") in #19237. Fix #19237
* Remove useless {-# LANGUAGE CPP #-} pragmasSylvain Henry2021-05-124-6/+0
|
* Fully remove HsVersions.hSylvain Henry2021-05-124-8/+0
| | | | | | | | | | Replace uses of WARN macro with calls to: warnPprTrace :: Bool -> SDoc -> a -> a Remove the now unused HsVersions.h Bump haddock submodule
* Replace CPP assertions with Haskell functionsSylvain Henry2021-05-121-2/+2
| | | | | | | | | | | | | | | There is no reason to use CPP. __LINE__ and __FILE__ macros are now better replaced with GHC's CallStack. As a bonus, assert error messages now contain more information (function name, column). Here is the mapping table (HasCallStack omitted): * ASSERT: assert :: Bool -> a -> a * MASSERT: massert :: Bool -> m () * ASSERTM: assertM :: m Bool -> m () * ASSERT2: assertPpr :: Bool -> SDoc -> a -> a * MASSERT2: massertPpr :: Bool -> SDoc -> m () * ASSERTM2: assertPprM :: m Bool -> SDoc -> m ()
* Replace (ptext .. sLit) with `text`Sylvain Henry2021-04-292-89/+89
| | | | | | | | | | | | | | | 1. `text` is as efficient as `ptext . sLit` thanks to the rewrite rules 2. `text` is visually nicer than `ptext . sLit` 3. `ptext . sLit` encourages using one `ptext` for several `sLit` as in: ptext $ case xy of ... -> sLit ... ... -> sLit ... which may allocate SDoc's TextBeside constructors at runtime instead of sharing them into CAFs.
* Re-export GHC.Bits from GHC.Prelude with custom shift implementation.Andreas Klebinger2021-04-092-2/+0
| | | | | | | This allows us to use the unsafe shifts in non-debug builds for performance. For older versions of base we instead export Data.Bits See also #19618
* PPC NCG: Fix int to float conversionPeter Trommler2021-03-231-6/+26
| | | | | | | | In commit 540fa6b2 integer to float conversions were changed to round to the nearest even. Implement a special case for 64 bit integer to single precision floating point numbers. Fixes #19563.
* Transfer tickish things to GHC.Types.TickishLuite Stegeman2021-03-201-1/+1
| | | | | Metric Increase: MultiLayerModules
* Save the type of breakpoints in the Breakpoint tick in STGLuite Stegeman2021-03-201-1/+1
| | | | | | | | GHCi needs to know the types of all breakpoints, but it's not possible to get the exprType of any expression in STG. This is preparation for the upcoming change to make GHCi bytecode from STG instead of Core.
* PPC NCG: print procedure end label for debugPeter Trommler2021-02-171-5/+11
| | | | Fixes #19118
* Add the proper HLint rules and remove redundant keywords from compilerHécate2020-11-011-8/+8
|
* Introduce OutputablePSylvain Henry2020-09-171-131/+118
| | | | | | | | | | | | | | | | | | | | | | | | | Some types need a Platform value to be pretty-printed: CLabel, Cmm types, instructions, etc. Before this patch they had an Outputable instance and the Platform value was obtained via sdocWithDynFlags. It meant that the *renderer* of the SDoc was responsible of passing the appropriate Platform value (e.g. via the DynFlags given to showSDoc). It put the burden of passing the Platform value on the renderer while the generator of the SDoc knows the Platform it is generating the SDoc for and there is no point passing a different Platform at rendering time. With this patch, we introduce a new OutputableP class: class OutputableP a where pdoc :: Platform -> a -> SDoc With this class we still have some polymorphism as we have with `ppr` (i.e. we can use `pdoc` on a variety of types instead of having a dedicated `pprXXX` function for each XXX type). One step closer removing `sdocWithDynFlags` (#10143) and supporting several platforms (#14335).
* PPC and X86: Portable printing of IEEE floatsPeter Trommler2020-08-261-10/+4
| | | | | | | | | | | | GNU as and the AIX assembler support floating point literals. SPARC seems to have support too but I cannot test on SPARC. Curiously, `doubleToBytes` is also used in the LLVM backend. To avoid endianness issues when cross-compiling float and double literals are printed as C-style floating point values. The assembler then takes care of memory layout and endianness. This was brought up in #18431 by @hsyl20.
* NCG: Dwarf configurationSylvain Henry2020-08-211-2/+2
| | | | | | * remove references to DynFlags in GHC.CmmToAsm.Dwarf * add specific Dwarf options in NCGConfig instead of directly querying the debug level
* DynFlags: refactor GHC.CmmToAsm (#17957, #10143)Sylvain Henry2020-08-183-74/+68
| | | | | | | | | | | | | | | | | This patch removes the use of `sdocWithDynFlags` from GHC.CmmToAsm.*.Ppr To do that I've had to make some refactoring: * X86' and PPC's `Instr` are no longer `Outputable` as they require a `Platform` argument * `Instruction` class now exposes `pprInstr :: Platform -> instr -> SDoc` * as a consequence, I've refactored some modules to avoid .hs-boot files * added (derived) functor instances for some datatypes parametric in the instruction type. It's useful for pretty-printing as we just have to map `pprInstr` before pretty-printing the container datatype.
* DynFlags: disentangle OutputableSylvain Henry2020-08-124-1/+4
| | | | | | | | | - put panic related functions into GHC.Utils.Panic - put trace related functions using DynFlags in GHC.Driver.Ppr One step closer making Outputable fully independent of DynFlags. Bump haddock submodule
* winio: Add Atomic Exchange PrimOp and implement Atomic Ptr exchanges.Tamar Christina2020-06-141-0/+1
| | | | | | | The initial version was rewritten by Tamar Christina. It was rewritten in large parts by Andreas Klebinger. Co-authored-by: Andreas Klebinger <klebinger.andreas@gmx.at>
* Clarify leaf module names for new module hierarchyTakenobu Tani2020-06-101-1/+1
| | | | | | | | | | | | | | | | | | | | | This updates comments only. This patch replaces leaf module names according to new module hierarchy [1][2] as followings: * Expand leaf names to easily find the module path: for instance, `Id.hs` to `GHC.Types.Id`. * Modify leaf names according to new module hierarchy: for instance, `Convert.hs` to `GHC.ThToHs`. * Fix typo: for instance, `GHC.Core.TyCo.Rep.hs` to `GHC.Core.TyCo.Rep` See also !3375 [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular [2]: https://gitlab.haskell.org/ghc/ghc/issues/13009
* PPC NCG: Fix .size directive on powerpc64 ELF v1Peter Trommler2020-05-301-1/+6
| | | | | | Thanks to Sergei Trofimovich for pointing out the issue. Fixes #18237
* Remove further dead code found by a simple Python script.Brian Foley2020-05-081-16/+0
| | | | | Avoid removing some functions that are part of an API even though they're not used in-tree at the moment.
* Modules: Utils and Data (#13009)Sylvain Henry2020-04-266-17/+17
| | | | | | | Update Haddock submodule Metric Increase: haddock.compiler
* PPC NCG: Add DWARF constants and debug labelsPeter Trommler2020-04-224-9/+50
| | | | Fixes #11261
* CmmToAsm DynFlags refactoring (#17957)Sylvain Henry2020-04-211-47/+39
| | | | | | | | | | | | | * Remove `DynFlags` parameter from `isDynLinkName`: `isDynLinkName` used to test the global `ExternalDynamicRefs` flag. Now we test it outside of `isDynLinkName` * Add new fields into `NCGConfig`: current unit id, sse/bmi versions, externalDynamicRefs, etc. * Replace many uses of `DynFlags` by `NCGConfig` * Moved `BMI/SSE` datatypes into `GHC.Platform`
* Refactor CmmStaticsSylvain Henry2020-04-033-10/+10
| | | | | | | | | | In !2959 we noticed that there was some redundant code (in GHC.Cmm.Utils and GHC.Cmm.StgToCmm.Utils) used to deal with `CmmStatics` datatype (before SRT generation) and `RawCmmStatics` datatype (after SRT generation). This patch removes this redundant code by using a single GADT for (Raw)CmmStatics.
* Move blob handling into StgToCmmSylvain Henry2020-04-031-1/+2
| | | | | | | Move handling of big literal strings from CmmToAsm to StgToCmm. It avoids the use of `sdocWithDynFlags` (cf #10143). We might need to move this handling even higher in the pipeline in the future (cf #17960): this patch will make it easier.
* Modules: Types (#13009)Sylvain Henry2020-03-295-6/+6
| | | | | | | Update Haddock submodule Metric Increase: haddock.compiler
* Refactoring: use Platform instead of DynFlags when possibleSylvain Henry2020-03-192-77/+79
| | | | | | | | Metric Decrease: ManyConstructors T12707 T13035 T1969
* Refactor CmmToAsm (disentangle DynFlags)Sylvain Henry2020-03-154-636/+736
| | | | | | | | | | | | | | | | | | | | | This patch disentangles a bit more DynFlags from the native code generator (CmmToAsm). In more details: - add a new NCGConfig datatype in GHC.CmmToAsm.Config which contains the configuration of a native code generation session - explicitly pass NCGConfig/Platform arguments when necessary - as a consequence `sdocWithPlatform` is gone and there are only a few `sdocWithDynFlags` left - remove the use of `unsafeGlobalDynFlags` from GHC.CmmToAsm.CFG - remove `sdocDebugLevel` (now we pass the debug level via NCGConfig) There are still some places where DynFlags is used, especially because of pretty-printing (CLabel), because of Cmm helpers (such as `cmmExprType`) and because of `Outputable` instance for the instructions. These are left for future refactoring as this patch is already big.
* Modules: CmmToAsm (#13009)Sylvain Henry2020-02-246-0/+4638