[Git][ghc/ghc][wip/supersven/riscv64-ncg] 6 commits: Suppress orphan instance warning
Sven Tennie (@supersven)
gitlab at gitlab.haskell.org
Sun Jan 7 19:00:18 UTC 2024
Sven Tennie pushed to branch wip/supersven/riscv64-ncg at Glasgow Haskell Compiler / GHC
Commits:
f78a1883 by Sven Tennie at 2024-01-07T19:56:54+01:00
Suppress orphan instance warning
Similar to other archs, this seems to be the expected place.
- - - - -
af6771ae by Sven Tennie at 2024-01-07T19:58:08+01:00
Delete commented-out code
- - - - -
cc86c025 by Sven Tennie at 2024-01-07T19:58:52+01:00
Adjust panix message
- - - - -
31b73f19 by Sven Tennie at 2024-01-07T19:59:19+01:00
Add TODOs
- - - - -
cd51abf6 by Sven Tennie at 2024-01-07T19:59:41+01:00
Formatting
- - - - -
86dc6034 by Sven Tennie at 2024-01-07T19:59:52+01:00
Eta reduction
- - - - -
4 changed files:
- compiler/GHC/CmmToAsm/RV64.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToAsm/RV64/Regs.hs
Changes:
=====================================
compiler/GHC/CmmToAsm/RV64.hs
=====================================
@@ -1,3 +1,5 @@
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+
-- | Native code generator for RiscV64 architectures
module GHC.CmmToAsm.RV64
( ncgRV64 )
=====================================
compiler/GHC/CmmToAsm/RV64/CodeGen.hs
=====================================
@@ -544,7 +544,6 @@ getRegister' config plat expr =
(op, imm_code) <- litToImm' lit
let rep = cmmLitType plat lit
format = cmmTypeFormat rep
- -- width = typeWidth rep
return (Any format (\dst -> imm_code `snocOL` LDR format (OpReg (formatToWidth format) dst) op))
CmmLabelOff lbl off -> do
=====================================
compiler/GHC/CmmToAsm/RV64/Ppr.hs
=====================================
@@ -324,9 +324,10 @@ pprReg w r = case r of
RegVirtual (VirtualRegI u) -> text "%vI_" <> pprUniqueAlways u
RegVirtual (VirtualRegF u) -> text "%vF_" <> pprUniqueAlways u
RegVirtual (VirtualRegD u) -> text "%vD_" <> pprUniqueAlways u
- _ -> pprPanic "AArch64.pprReg" (text $ show r)
+ _ -> pprPanic "RiscV64.pprReg" (text $ show r)
where
+ -- TODO: Width is only used in error messages, so we could just remove it.
ppr_reg_no :: Width -> Int -> doc
-- General Purpose Registers
ppr_reg_no _ 0 = text "zero"
=====================================
compiler/GHC/CmmToAsm/RV64/Regs.hs
=====================================
@@ -16,14 +16,15 @@ import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Platform
-allMachRegNos :: [RegNo]
-allMachRegNos = [0..31] ++ [32..63]
+allMachRegNos :: [RegNo]
+allMachRegNos = [0 .. 31] ++ [32 .. 63]
+
-- allocatableRegs is allMachRegNos with the fixed-use regs removed.
-- i.e., these are the regs for which we are prepared to allow the
-- register allocator to attempt to map VRegs to.
allocatableRegs :: Platform -> [RealReg]
allocatableRegs platform
- = let isFree i = freeReg platform i
+ = let isFree = freeReg platform
in map RealRegSingle $ filter isFree allMachRegNos
-- argRegs is the set of regs which are read for an n-argument call to C.
@@ -45,6 +46,7 @@ allFpArgRegs = map regSingle [42..49]
-- addressing modes ------------------------------------------------------------
+-- TODO: AddrRegReg constructor is never used. Remove it?
data AddrMode
= AddrRegReg Reg Reg
| AddrRegImm Reg Imm
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fef187b4b52ac84140b50765301383c72104c8c4...86dc603457e8946c638ac439c4db5eff1f5aca98
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fef187b4b52ac84140b50765301383c72104c8c4...86dc603457e8946c638ac439c4db5eff1f5aca98
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240107/0e85ca1b/attachment-0001.html>
More information about the ghc-commits
mailing list