{-# OPTIONS_GHC -fno-warn-orphans #-}
module GHC.CmmToAsm.LA64.Instr where
import GHC.Prelude
import GHC.CmmToAsm.LA64.Cond
import GHC.CmmToAsm.LA64.Regs
import GHC.CmmToAsm.Instr (RegUsage(..))
import GHC.CmmToAsm.Format
import GHC.CmmToAsm.Types
import GHC.CmmToAsm.Utils
import GHC.CmmToAsm.Config
import GHC.Platform.Reg
import GHC.Platform.Regs
import GHC.Platform.Reg.Class.Separate
import GHC.Cmm.BlockId
import GHC.Cmm.Dataflow.Label
import GHC.Cmm
import GHC.Cmm.CLabel
import GHC.Utils.Outputable
import GHC.Platform
import GHC.Types.Unique.DSM
import GHC.Utils.Panic
import Data.Maybe
import GHC.Stack
import GHC.Data.FastString (LexicalFastString)
stackFrameHeaderSize :: Int
= RegNo
2 RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
* RegNo
spillSlotSize
spillSlotSize :: Int
spillSlotSize :: RegNo
spillSlotSize = RegNo
8
stackAlign :: Int
stackAlign :: RegNo
stackAlign = RegNo
16
maxSpillSlots :: NCGConfig -> Int
maxSpillSlots :: NCGConfig -> RegNo
maxSpillSlots NCGConfig
config
= (
(NCGConfig -> RegNo
ncgSpillPreallocSize NCGConfig
config RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
- RegNo
stackFrameHeaderSize)
RegNo -> RegNo -> RegNo
forall a. Integral a => a -> a -> a
`div`
RegNo
spillSlotSize
) RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
- RegNo
1
spillSlotToOffset :: Int -> Int
spillSlotToOffset :: RegNo -> RegNo
spillSlotToOffset RegNo
slot
= RegNo
stackFrameHeaderSize RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
+ RegNo
spillSlotSize RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
* RegNo
slot
instance Outputable RegUsage where
ppr :: RegUsage -> SDoc
ppr (RU [RegWithFormat]
reads [RegWithFormat]
writes) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"RegUsage(reads:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [RegWithFormat] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [RegWithFormat]
reads SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
comma SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"writes:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [RegWithFormat] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [RegWithFormat]
writes SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
')'
regUsageOfInstr :: Platform -> Instr -> RegUsage
regUsageOfInstr :: Platform -> Instr -> RegUsage
regUsageOfInstr Platform
platform Instr
instr = case Instr
instr of
ANN SDoc
_ Instr
i -> Platform -> Instr -> RegUsage
regUsageOfInstr Platform
platform Instr
i
COMMENT{} -> ([Reg], [Reg]) -> RegUsage
usage ([], [])
MULTILINE_COMMENT{} -> ([Reg], [Reg]) -> RegUsage
usage ([], [])
Instr
PUSH_STACK_FRAME -> ([Reg], [Reg]) -> RegUsage
usage ([], [])
Instr
POP_STACK_FRAME -> ([Reg], [Reg]) -> RegUsage
usage ([], [])
DELTA{} -> ([Reg], [Reg]) -> RegUsage
usage ([], [])
LOCATION{} -> ([Reg], [Reg]) -> RegUsage
usage ([], [])
ADD Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
SUB Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
ALSL Operand
dst Operand
src1 Operand
src2 Operand
src3 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src3, Operand -> [Reg]
regOp Operand
dst)
ALSLU Operand
dst Operand
src1 Operand
src2 Operand
src3 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src3, Operand -> [Reg]
regOp Operand
dst)
LU12I Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
LU32I Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
LU52I Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
SSLT Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
SSLTU Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
PCADDI Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
PCADDU12I Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
PCADDU18I Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
PCALAU12I Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
AND Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
OR Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
XOR Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
NOR Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
ANDN Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
ORN Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
MUL Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
MULW Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
MULWU Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
MULH Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
MULHU Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
DIV Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
DIVU Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
MOD Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
MODU Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
SLL Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
SRL Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
SRA Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
ROTR Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
EXT Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
CLO Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
CLZ Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
CTO Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
CTZ Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
BYTEPICK Operand
dst Operand
src1 Operand
src2 Operand
src3 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src3, Operand -> [Reg]
regOp Operand
dst)
REVB2H Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
REVB4H Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
REVB2W Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
REVBD Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
REVH2W Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
REVHD Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
BITREV4B Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
BITREV8B Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
BITREVW Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
BITREVD Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
BSTRINS Format
_ Operand
dst Operand
src1 Operand
src2 Operand
src3 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src3, Operand -> [Reg]
regOp Operand
dst)
BSTRPICK Format
_ Operand
dst Operand
src1 Operand
src2 Operand
src3 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src3, Operand -> [Reg]
regOp Operand
dst)
MASKEQZ Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
MASKNEZ Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
Instr
NOP -> ([Reg], [Reg]) -> RegUsage
usage ([], [])
MOV Operand
dst Operand
src -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src, Operand -> [Reg]
regOp Operand
dst)
NEG Operand
dst Operand
src -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src, Operand -> [Reg]
regOp Operand
dst)
CSET Cond
_cond Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2 , Operand -> [Reg]
regOp Operand
dst)
J Target
t -> ([Reg], [Reg]) -> RegUsage
usage (Target -> [Reg]
regTarget Target
t, [])
J_TBL [Maybe BlockId]
_ Maybe CLabel
_ Reg
t -> ([Reg], [Reg]) -> RegUsage
usage ([Reg
t], [])
B Target
t -> ([Reg], [Reg]) -> RegUsage
usage (Target -> [Reg]
regTarget Target
t, [])
BL Target
t [Reg]
ps -> ([Reg], [Reg]) -> RegUsage
usage (Target -> [Reg]
regTarget Target
t [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ [Reg]
ps, [Reg]
callerSavedRegisters)
CALL36 Target
t -> ([Reg], [Reg]) -> RegUsage
usage (Target -> [Reg]
regTarget Target
t, [])
TAIL36 Operand
r Target
t -> ([Reg], [Reg]) -> RegUsage
usage (Target -> [Reg]
regTarget Target
t, Operand -> [Reg]
regOp Operand
r)
BCOND Cond
_ Operand
j Operand
d Target
t Operand
tmp -> ([Reg], [Reg]) -> RegUsage
usage (Target -> [Reg]
regTarget Target
t [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
j [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
d [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
tmp, Operand -> [Reg]
regOp Operand
tmp)
BEQZ Operand
j Target
t -> ([Reg], [Reg]) -> RegUsage
usage (Target -> [Reg]
regTarget Target
t [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
j, [])
BNEZ Operand
j Target
t -> ([Reg], [Reg]) -> RegUsage
usage (Target -> [Reg]
regTarget Target
t [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
j, [])
LD Format
_ Operand
dst Operand
src -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src, Operand -> [Reg]
regOp Operand
dst)
LDU Format
_ Operand
dst Operand
src -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src, Operand -> [Reg]
regOp Operand
dst)
ST Format
_ Operand
dst Operand
src -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
dst, [])
LDX Format
_ Operand
dst Operand
src -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src, Operand -> [Reg]
regOp Operand
dst)
LDXU Format
_ Operand
dst Operand
src -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src, Operand -> [Reg]
regOp Operand
dst)
STX Format
_ Operand
dst Operand
src -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
dst, [])
LDPTR Format
_ Operand
dst Operand
src -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src, Operand -> [Reg]
regOp Operand
dst)
STPTR Format
_ Operand
dst Operand
src -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
dst, [])
DBAR BarrierType
_hint -> ([Reg], [Reg]) -> RegUsage
usage ([], [])
IBAR BarrierType
_hint -> ([Reg], [Reg]) -> RegUsage
usage ([], [])
FMAX Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
FMIN Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
FMAXA Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
FMINA Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
dst)
FNEG Operand
dst Operand
src1 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1, Operand -> [Reg]
regOp Operand
dst)
FCVT Operand
dst Operand
src -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src, Operand -> [Reg]
regOp Operand
dst)
SCVTF Operand
dst Operand
src -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src, Operand -> [Reg]
regOp Operand
dst)
FCVTZS Operand
dst Operand
src1 Operand
src2 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src2, Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
dst)
FABS Operand
dst Operand
src -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src, Operand -> [Reg]
regOp Operand
dst)
FMA FMASign
_ Operand
dst Operand
src1 Operand
src2 Operand
src3 -> ([Reg], [Reg]) -> RegUsage
usage (Operand -> [Reg]
regOp Operand
src1 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src2 [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ Operand -> [Reg]
regOp Operand
src3, Operand -> [Reg]
regOp Operand
dst)
Instr
_ -> String -> RegUsage
forall a. HasCallStack => String -> a
panic (String -> RegUsage) -> String -> RegUsage
forall a b. (a -> b) -> a -> b
$ String
"regUsageOfInstr: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Instr -> String
instrCon Instr
instr
where
usage :: ([Reg], [Reg]) -> RegUsage
usage :: ([Reg], [Reg]) -> RegUsage
usage ([Reg]
srcRegs, [Reg]
dstRegs) =
[RegWithFormat] -> [RegWithFormat] -> RegUsage
RU
((Reg -> RegWithFormat) -> [Reg] -> [RegWithFormat]
forall a b. (a -> b) -> [a] -> [b]
map Reg -> RegWithFormat
mkFmt ([Reg] -> [RegWithFormat]) -> [Reg] -> [RegWithFormat]
forall a b. (a -> b) -> a -> b
$ (Reg -> Bool) -> [Reg] -> [Reg]
forall a. (a -> Bool) -> [a] -> [a]
filter (Platform -> Reg -> Bool
interesting Platform
platform) [Reg]
srcRegs)
((Reg -> RegWithFormat) -> [Reg] -> [RegWithFormat]
forall a b. (a -> b) -> [a] -> [b]
map Reg -> RegWithFormat
mkFmt ([Reg] -> [RegWithFormat]) -> [Reg] -> [RegWithFormat]
forall a b. (a -> b) -> a -> b
$ (Reg -> Bool) -> [Reg] -> [Reg]
forall a. (a -> Bool) -> [a] -> [a]
filter (Platform -> Reg -> Bool
interesting Platform
platform) [Reg]
dstRegs)
mkFmt :: Reg -> RegWithFormat
mkFmt Reg
r = Reg -> Format -> RegWithFormat
RegWithFormat Reg
r Format
fmt
where
fmt :: Format
fmt = case RegClass
cls of
RegClass
RcInteger -> Format
II64
RegClass
RcFloat -> Format
FF64
RegClass
RcVector -> String -> Format
forall a. HasCallStack => String -> a
sorry String
"The LoongArch64 NCG does not (yet) support vectors; please use -fllvm."
cls :: RegClass
cls = case Reg
r of
RegVirtual VirtualReg
vr -> Arch -> VirtualReg -> RegClass
classOfVirtualReg (Platform -> Arch
platformArch Platform
platform) VirtualReg
vr
RegReal RealReg
rr -> RealReg -> RegClass
classOfRealReg RealReg
rr
regAddr :: AddrMode -> [Reg]
regAddr :: AddrMode -> [Reg]
regAddr (AddrRegReg Reg
r1 Reg
r2) = [Reg
r1, Reg
r2]
regAddr (AddrRegImm Reg
r1 Imm
_) = [Reg
r1]
regAddr (AddrReg Reg
r1) = [Reg
r1]
regOp :: Operand -> [Reg]
regOp :: Operand -> [Reg]
regOp (OpReg Width
_ Reg
r1) = [Reg
r1]
regOp (OpAddr AddrMode
a) = AddrMode -> [Reg]
regAddr AddrMode
a
regOp (OpImm Imm
_) = []
regTarget :: Target -> [Reg]
regTarget :: Target -> [Reg]
regTarget (TBlock BlockId
_) = []
regTarget (TLabel CLabel
_) = []
regTarget (TReg Reg
r1) = [Reg
r1]
interesting :: Platform -> Reg -> Bool
interesting :: Platform -> Reg -> Bool
interesting Platform
_ (RegVirtual VirtualReg
_) = Bool
True
interesting Platform
platform (RegReal (RealRegSingle RegNo
i)) = Platform -> RegNo -> Bool
freeReg Platform
platform RegNo
i
callerSavedRegisters :: [Reg]
callerSavedRegisters :: [Reg]
callerSavedRegisters =
[RegNo -> Reg
regSingle RegNo
1]
[Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ (RegNo -> Reg) -> [RegNo] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map RegNo -> Reg
regSingle [RegNo
4 .. RegNo
11]
[Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ (RegNo -> Reg) -> [RegNo] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map RegNo -> Reg
regSingle [RegNo
12 .. RegNo
20]
[Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ (RegNo -> Reg) -> [RegNo] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map RegNo -> Reg
regSingle [RegNo
32 .. RegNo
39]
[Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ (RegNo -> Reg) -> [RegNo] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map RegNo -> Reg
regSingle [RegNo
40 .. RegNo
55]
patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr
patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr
patchRegsOfInstr Instr
instr Reg -> Reg
env = case Instr
instr of
ANN SDoc
d Instr
i -> SDoc -> Instr -> Instr
ANN SDoc
d (Instr -> (Reg -> Reg) -> Instr
patchRegsOfInstr Instr
i Reg -> Reg
env)
COMMENT{} -> Instr
instr
MULTILINE_COMMENT{} -> Instr
instr
Instr
PUSH_STACK_FRAME -> Instr
instr
Instr
POP_STACK_FRAME -> Instr
instr
DELTA{} -> Instr
instr
LOCATION{} -> Instr
instr
ADD Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
ADD (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
SUB Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
SUB (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
ALSL Operand
o1 Operand
o2 Operand
o3 Operand
o4 -> Operand -> Operand -> Operand -> Operand -> Instr
ALSL (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3) (Operand -> Operand
patchOp Operand
o4)
ALSLU Operand
o1 Operand
o2 Operand
o3 Operand
o4 -> Operand -> Operand -> Operand -> Operand -> Instr
ALSLU (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3) (Operand -> Operand
patchOp Operand
o4)
LU12I Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
LU12I (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
LU32I Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
LU32I (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
LU52I Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
LU52I (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
SSLT Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
SSLT (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
SSLTU Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
SSLTU (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
PCADDI Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
PCADDI (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
PCADDU12I Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
PCADDU12I (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
PCADDU18I Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
PCADDU18I (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
PCALAU12I Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
PCALAU12I (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
AND Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
AND (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
OR Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
OR (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
XOR Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
XOR (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
NOR Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
NOR (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
ANDN Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
ANDN (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
ORN Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
ORN (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
MUL Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
MUL (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
MULW Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
MULW (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
MULWU Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
MULWU (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
MULH Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
MULH (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
MULHU Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
MULHU (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
DIV Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
DIV (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
MOD Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
MOD (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
DIVU Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
DIVU (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
MODU Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
MODU (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
SLL Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
SLL (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
SRL Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
SRL (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
SRA Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
SRA (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
ROTR Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
ROTR (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
EXT Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
EXT (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
CLO Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
CLO (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
CLZ Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
CLZ (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
CTO Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
CTO (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
CTZ Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
CTZ (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
BYTEPICK Operand
o1 Operand
o2 Operand
o3 Operand
o4 -> Operand -> Operand -> Operand -> Operand -> Instr
BYTEPICK (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3) (Operand -> Operand
patchOp Operand
o4)
REVB2H Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
REVB2H (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
REVB4H Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
REVB4H (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
REVB2W Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
REVB2W (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
REVBD Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
REVBD (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
REVH2W Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
REVH2W (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
REVHD Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
REVHD (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
BITREV4B Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
BITREV4B (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
BITREV8B Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
BITREV8B (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
BITREVW Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
BITREVW (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
BITREVD Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
BITREVD (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
BSTRINS Format
f Operand
o1 Operand
o2 Operand
o3 Operand
o4 -> Format -> Operand -> Operand -> Operand -> Operand -> Instr
BSTRINS Format
f (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3) (Operand -> Operand
patchOp Operand
o4)
BSTRPICK Format
f Operand
o1 Operand
o2 Operand
o3 Operand
o4 -> Format -> Operand -> Operand -> Operand -> Operand -> Instr
BSTRPICK Format
f (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3) (Operand -> Operand
patchOp Operand
o4)
MASKEQZ Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
MASKEQZ (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
MASKNEZ Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
MASKNEZ (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
Instr
NOP -> Instr
NOP
MOV Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
MOV (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
NEG Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
NEG (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
CSET Cond
cond Operand
o1 Operand
o2 Operand
o3 -> Cond -> Operand -> Operand -> Operand -> Instr
CSET Cond
cond (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
J Target
t -> Target -> Instr
J (Target -> Target
patchTarget Target
t)
J_TBL [Maybe BlockId]
ids Maybe CLabel
mbLbl Reg
t -> [Maybe BlockId] -> Maybe CLabel -> Reg -> Instr
J_TBL [Maybe BlockId]
ids Maybe CLabel
mbLbl (Reg -> Reg
env Reg
t)
B Target
t -> Target -> Instr
B (Target -> Target
patchTarget Target
t)
BL Target
t [Reg]
ps -> Target -> [Reg] -> Instr
BL (Target -> Target
patchTarget Target
t) [Reg]
ps
CALL36 Target
t -> Target -> Instr
CALL36 (Target -> Target
patchTarget Target
t)
TAIL36 Operand
r Target
t -> Operand -> Target -> Instr
TAIL36 (Operand -> Operand
patchOp Operand
r) (Target -> Target
patchTarget Target
t)
BCOND Cond
c Operand
j Operand
d Target
t Operand
tmp -> Cond -> Operand -> Operand -> Target -> Operand -> Instr
BCOND Cond
c (Operand -> Operand
patchOp Operand
j) (Operand -> Operand
patchOp Operand
d) (Target -> Target
patchTarget Target
t) (Operand -> Operand
patchOp Operand
tmp)
BEQZ Operand
j Target
t -> Operand -> Target -> Instr
BEQZ (Operand -> Operand
patchOp Operand
j) (Target -> Target
patchTarget Target
t)
BNEZ Operand
j Target
t -> Operand -> Target -> Instr
BNEZ (Operand -> Operand
patchOp Operand
j) (Target -> Target
patchTarget Target
t)
LD Format
f Operand
o1 Operand
o2 -> Format -> Operand -> Operand -> Instr
LD Format
f (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
LDU Format
f Operand
o1 Operand
o2 -> Format -> Operand -> Operand -> Instr
LDU Format
f (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
ST Format
f Operand
o1 Operand
o2 -> Format -> Operand -> Operand -> Instr
ST Format
f (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
LDX Format
f Operand
o1 Operand
o2 -> Format -> Operand -> Operand -> Instr
LDX Format
f (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
LDXU Format
f Operand
o1 Operand
o2 -> Format -> Operand -> Operand -> Instr
LDXU Format
f (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
STX Format
f Operand
o1 Operand
o2 -> Format -> Operand -> Operand -> Instr
STX Format
f (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
LDPTR Format
f Operand
o1 Operand
o2 -> Format -> Operand -> Operand -> Instr
LDPTR Format
f (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
STPTR Format
f Operand
o1 Operand
o2 -> Format -> Operand -> Operand -> Instr
STPTR Format
f (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
DBAR BarrierType
o1 -> BarrierType -> Instr
DBAR BarrierType
o1
IBAR BarrierType
o1 -> BarrierType -> Instr
IBAR BarrierType
o1
FCVT Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
FCVT (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
SCVTF Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
SCVTF (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
FCVTZS Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
FCVTZS (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
FMIN Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
FMIN (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
FMAX Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
FMAX (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
FMINA Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
FMINA (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
FMAXA Operand
o1 Operand
o2 Operand
o3 -> Operand -> Operand -> Operand -> Instr
FMAXA (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3)
FNEG Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
FNEG (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
FABS Operand
o1 Operand
o2 -> Operand -> Operand -> Instr
FABS (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2)
FMA FMASign
s Operand
o1 Operand
o2 Operand
o3 Operand
o4 -> FMASign -> Operand -> Operand -> Operand -> Operand -> Instr
FMA FMASign
s (Operand -> Operand
patchOp Operand
o1) (Operand -> Operand
patchOp Operand
o2) (Operand -> Operand
patchOp Operand
o3) (Operand -> Operand
patchOp Operand
o4)
Instr
_ -> String -> Instr
forall a. HasCallStack => String -> a
panic (String -> Instr) -> String -> Instr
forall a b. (a -> b) -> a -> b
$ String
"patchRegsOfInstr: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Instr -> String
instrCon Instr
instr
where
patchOp :: Operand -> Operand
patchOp :: Operand -> Operand
patchOp (OpReg Width
w Reg
r) = Width -> Reg -> Operand
OpReg Width
w (Reg -> Reg
env Reg
r)
patchOp (OpAddr AddrMode
a) = AddrMode -> Operand
OpAddr (AddrMode -> AddrMode
patchAddr AddrMode
a)
patchOp Operand
opImm = Operand
opImm
patchTarget :: Target -> Target
patchTarget :: Target -> Target
patchTarget (TReg Reg
r) = Reg -> Target
TReg (Reg -> Reg
env Reg
r)
patchTarget Target
t = Target
t
patchAddr :: AddrMode -> AddrMode
patchAddr :: AddrMode -> AddrMode
patchAddr (AddrRegReg Reg
r1 Reg
r2) = Reg -> Reg -> AddrMode
AddrRegReg (Reg -> Reg
env Reg
r1) (Reg -> Reg
env Reg
r2)
patchAddr (AddrRegImm Reg
r1 Imm
imm) = Reg -> Imm -> AddrMode
AddrRegImm (Reg -> Reg
env Reg
r1) Imm
imm
patchAddr (AddrReg Reg
r) = Reg -> AddrMode
AddrReg (Reg -> Reg
env Reg
r)
isJumpishInstr :: Instr -> Bool
isJumpishInstr :: Instr -> Bool
isJumpishInstr Instr
instr = case Instr
instr of
ANN SDoc
_ Instr
i -> Instr -> Bool
isJumpishInstr Instr
i
J {} -> Bool
True
J_TBL {} -> Bool
True
B {} -> Bool
True
BL {} -> Bool
True
CALL36 {} -> Bool
True
TAIL36 {} -> Bool
True
BCOND {} -> Bool
True
BEQZ {} -> Bool
True
BNEZ {} -> Bool
True
Instr
_ -> Bool
False
jumpDestsOfInstr :: Instr -> [BlockId]
jumpDestsOfInstr :: Instr -> [BlockId]
jumpDestsOfInstr (ANN SDoc
_ Instr
i) = Instr -> [BlockId]
jumpDestsOfInstr Instr
i
jumpDestsOfInstr (J Target
t) = [BlockId
id | TBlock BlockId
id <- [Target
t]]
jumpDestsOfInstr (J_TBL [Maybe BlockId]
ids Maybe CLabel
_mbLbl Reg
_r) = [Maybe BlockId] -> [BlockId]
forall a. [Maybe a] -> [a]
catMaybes [Maybe BlockId]
ids
jumpDestsOfInstr (B Target
t) = [BlockId
id | TBlock BlockId
id <- [Target
t]]
jumpDestsOfInstr (BL Target
t [Reg]
_) = [BlockId
id | TBlock BlockId
id <- [Target
t]]
jumpDestsOfInstr (CALL36 Target
t) = [BlockId
id | TBlock BlockId
id <- [Target
t]]
jumpDestsOfInstr (TAIL36 Operand
_ Target
t) = [BlockId
id | TBlock BlockId
id <- [Target
t]]
jumpDestsOfInstr (BCOND Cond
_ Operand
_ Operand
_ Target
t Operand
_) = [BlockId
id | TBlock BlockId
id <- [Target
t]]
jumpDestsOfInstr (BEQZ Operand
_ Target
t) = [BlockId
id | TBlock BlockId
id <- [Target
t]]
jumpDestsOfInstr (BNEZ Operand
_ Target
t) = [BlockId
id | TBlock BlockId
id <- [Target
t]]
jumpDestsOfInstr Instr
_ = []
patchJumpInstr :: Instr -> (BlockId -> BlockId) -> Instr
patchJumpInstr :: Instr -> (BlockId -> BlockId) -> Instr
patchJumpInstr Instr
instr BlockId -> BlockId
patchF =
case Instr
instr of
ANN SDoc
d Instr
i -> SDoc -> Instr -> Instr
ANN SDoc
d (Instr -> (BlockId -> BlockId) -> Instr
patchJumpInstr Instr
i BlockId -> BlockId
patchF)
J (TBlock BlockId
bid) -> Target -> Instr
J (BlockId -> Target
TBlock (BlockId -> BlockId
patchF BlockId
bid))
J_TBL [Maybe BlockId]
ids Maybe CLabel
mbLbl Reg
r -> [Maybe BlockId] -> Maybe CLabel -> Reg -> Instr
J_TBL ((Maybe BlockId -> Maybe BlockId)
-> [Maybe BlockId] -> [Maybe BlockId]
forall a b. (a -> b) -> [a] -> [b]
map ((BlockId -> BlockId) -> Maybe BlockId -> Maybe BlockId
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap BlockId -> BlockId
patchF) [Maybe BlockId]
ids) Maybe CLabel
mbLbl Reg
r
B (TBlock BlockId
bid) -> Target -> Instr
B (BlockId -> Target
TBlock (BlockId -> BlockId
patchF BlockId
bid))
BL (TBlock BlockId
bid) [Reg]
ps -> Target -> [Reg] -> Instr
BL (BlockId -> Target
TBlock (BlockId -> BlockId
patchF BlockId
bid)) [Reg]
ps
CALL36 (TBlock BlockId
bid) -> Target -> Instr
CALL36 (BlockId -> Target
TBlock (BlockId -> BlockId
patchF BlockId
bid))
TAIL36 Operand
r (TBlock BlockId
bid) -> Operand -> Target -> Instr
TAIL36 Operand
r (BlockId -> Target
TBlock (BlockId -> BlockId
patchF BlockId
bid))
BCOND Cond
c Operand
o1 Operand
o2 (TBlock BlockId
bid) Operand
tmp -> Cond -> Operand -> Operand -> Target -> Operand -> Instr
BCOND Cond
c Operand
o1 Operand
o2 (BlockId -> Target
TBlock (BlockId -> BlockId
patchF BlockId
bid)) Operand
tmp
BEQZ Operand
j (TBlock BlockId
bid) -> Operand -> Target -> Instr
BEQZ Operand
j (BlockId -> Target
TBlock (BlockId -> BlockId
patchF BlockId
bid))
BNEZ Operand
j (TBlock BlockId
bid) -> Operand -> Target -> Instr
BNEZ Operand
j (BlockId -> Target
TBlock (BlockId -> BlockId
patchF BlockId
bid))
Instr
_ -> String -> Instr
forall a. HasCallStack => String -> a
panic (String -> Instr) -> String -> Instr
forall a b. (a -> b) -> a -> b
$ String
"patchJumpInstr: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Instr -> String
instrCon Instr
instr
mkSpillInstr
:: HasCallStack
=> NCGConfig
-> RegWithFormat
-> Int
-> Int
-> [Instr]
mkSpillInstr :: HasCallStack =>
NCGConfig -> RegWithFormat -> RegNo -> RegNo -> [Instr]
mkSpillInstr NCGConfig
_config (RegWithFormat Reg
reg Format
_fmt) RegNo
delta RegNo
slot =
case RegNo
off RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
- RegNo
delta of
RegNo
imm | RegNo -> RegNo -> Bool
fitsInNbits RegNo
12 RegNo
imm -> [RegNo -> Instr
mkStrSpImm RegNo
imm]
RegNo
imm ->
[ RegNo -> Instr
movImmToIp RegNo
imm,
Instr
addSpToIp,
Instr
mkStrIp
]
where
fmt :: Format
fmt = case Reg
reg of
RegReal (RealRegSingle RegNo
n) | RegNo
n RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
< RegNo
32 -> Format
II64
Reg
_ -> Format
FF64
mkStrSpImm :: RegNo -> Instr
mkStrSpImm RegNo
imm = SDoc -> Instr -> Instr
ANN (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Spill@" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> RegNo -> SDoc
forall doc. IsLine doc => RegNo -> doc
int (RegNo
off RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
- RegNo
delta)) (Instr -> Instr) -> Instr -> Instr
forall a b. (a -> b) -> a -> b
$ Format -> Operand -> Operand -> Instr
ST Format
fmt (Width -> Reg -> Operand
OpReg Width
W64 Reg
reg) (AddrMode -> Operand
OpAddr (Reg -> Imm -> AddrMode
AddrRegImm Reg
spMachReg (RegNo -> Imm
ImmInt RegNo
imm)))
movImmToIp :: RegNo -> Instr
movImmToIp RegNo
imm = SDoc -> Instr -> Instr
ANN (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Spill: TMP <- " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> RegNo -> SDoc
forall doc. IsLine doc => RegNo -> doc
int RegNo
imm) (Instr -> Instr) -> Instr -> Instr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Instr
MOV Operand
tmp (Imm -> Operand
OpImm (RegNo -> Imm
ImmInt RegNo
imm))
addSpToIp :: Instr
addSpToIp = SDoc -> Instr -> Instr
ANN (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Spill: TMP <- SP + TMP ") (Instr -> Instr) -> Instr -> Instr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
ADD Operand
tmp Operand
tmp Operand
sp
mkStrIp :: Instr
mkStrIp = SDoc -> Instr -> Instr
ANN (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Spill@" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> RegNo -> SDoc
forall doc. IsLine doc => RegNo -> doc
int (RegNo
off RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
- RegNo
delta)) (Instr -> Instr) -> Instr -> Instr
forall a b. (a -> b) -> a -> b
$ Format -> Operand -> Operand -> Instr
ST Format
fmt (Width -> Reg -> Operand
OpReg Width
W64 Reg
reg) (AddrMode -> Operand
OpAddr (Reg -> AddrMode
AddrReg Reg
tmpReg))
off :: RegNo
off = RegNo -> RegNo
spillSlotToOffset RegNo
slot
mkLoadInstr
:: NCGConfig
-> RegWithFormat
-> Int
-> Int
-> [Instr]
mkLoadInstr :: NCGConfig -> RegWithFormat -> RegNo -> RegNo -> [Instr]
mkLoadInstr NCGConfig
_config (RegWithFormat Reg
reg Format
_fmt) RegNo
delta RegNo
slot =
case RegNo
off RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
- RegNo
delta of
RegNo
imm | RegNo -> RegNo -> Bool
fitsInNbits RegNo
12 RegNo
imm -> [RegNo -> Instr
mkLdrSpImm RegNo
imm]
RegNo
imm ->
[ RegNo -> Instr
movImmToIp RegNo
imm,
Instr
addSpToIp,
Instr
mkLdrIp
]
where
fmt :: Format
fmt = case Reg
reg of
RegReal (RealRegSingle RegNo
n) | RegNo
n RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
< RegNo
32 -> Format
II64
Reg
_ -> Format
FF64
mkLdrSpImm :: RegNo -> Instr
mkLdrSpImm RegNo
imm = SDoc -> Instr -> Instr
ANN (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Reload@" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> RegNo -> SDoc
forall doc. IsLine doc => RegNo -> doc
int (RegNo
off RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
- RegNo
delta)) (Instr -> Instr) -> Instr -> Instr
forall a b. (a -> b) -> a -> b
$ Format -> Operand -> Operand -> Instr
LD Format
fmt (Width -> Reg -> Operand
OpReg Width
W64 Reg
reg) (AddrMode -> Operand
OpAddr (Reg -> Imm -> AddrMode
AddrRegImm Reg
spMachReg (RegNo -> Imm
ImmInt RegNo
imm)))
movImmToIp :: RegNo -> Instr
movImmToIp RegNo
imm = SDoc -> Instr -> Instr
ANN (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Reload: TMP <- " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> RegNo -> SDoc
forall doc. IsLine doc => RegNo -> doc
int RegNo
imm) (Instr -> Instr) -> Instr -> Instr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Instr
MOV Operand
tmp (Imm -> Operand
OpImm (RegNo -> Imm
ImmInt RegNo
imm))
addSpToIp :: Instr
addSpToIp = SDoc -> Instr -> Instr
ANN (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Reload: TMP <- SP + TMP ") (Instr -> Instr) -> Instr -> Instr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
ADD Operand
tmp Operand
tmp Operand
sp
mkLdrIp :: Instr
mkLdrIp = SDoc -> Instr -> Instr
ANN (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Reload@" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> RegNo -> SDoc
forall doc. IsLine doc => RegNo -> doc
int (RegNo
off RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
- RegNo
delta)) (Instr -> Instr) -> Instr -> Instr
forall a b. (a -> b) -> a -> b
$ Format -> Operand -> Operand -> Instr
LD Format
fmt (Width -> Reg -> Operand
OpReg Width
W64 Reg
reg) (AddrMode -> Operand
OpAddr (Reg -> AddrMode
AddrReg Reg
tmpReg))
off :: RegNo
off = RegNo -> RegNo
spillSlotToOffset RegNo
slot
takeDeltaInstr :: Instr -> Maybe Int
takeDeltaInstr :: Instr -> Maybe RegNo
takeDeltaInstr (ANN SDoc
_ Instr
i) = Instr -> Maybe RegNo
takeDeltaInstr Instr
i
takeDeltaInstr (DELTA RegNo
i) = RegNo -> Maybe RegNo
forall a. a -> Maybe a
Just RegNo
i
takeDeltaInstr Instr
_ = Maybe RegNo
forall a. Maybe a
Nothing
isMetaInstr :: Instr -> Bool
isMetaInstr :: Instr -> Bool
isMetaInstr Instr
instr =
case Instr
instr of
ANN SDoc
_ Instr
i -> Instr -> Bool
isMetaInstr Instr
i
COMMENT {} -> Bool
True
MULTILINE_COMMENT {} -> Bool
True
LOCATION {} -> Bool
True
NEWBLOCK {} -> Bool
True
DELTA {} -> Bool
True
LDATA {} -> Bool
True
Instr
PUSH_STACK_FRAME -> Bool
True
Instr
POP_STACK_FRAME -> Bool
True
Instr
_ -> Bool
False
canFallthroughTo :: Instr -> BlockId -> Bool
canFallthroughTo :: Instr -> BlockId -> Bool
canFallthroughTo Instr
insn BlockId
bid =
case Instr
insn of
J (TBlock BlockId
target) -> BlockId
bid BlockId -> BlockId -> Bool
forall a. Eq a => a -> a -> Bool
== BlockId
target
J_TBL [Maybe BlockId]
targets Maybe CLabel
_ Reg
_ -> (Maybe BlockId -> Bool) -> [Maybe BlockId] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Maybe BlockId -> Bool
isTargetBid [Maybe BlockId]
targets
B (TBlock BlockId
target) -> BlockId
bid BlockId -> BlockId -> Bool
forall a. Eq a => a -> a -> Bool
== BlockId
target
CALL36 (TBlock BlockId
target) -> BlockId
bid BlockId -> BlockId -> Bool
forall a. Eq a => a -> a -> Bool
== BlockId
target
TAIL36 Operand
_ (TBlock BlockId
target) -> BlockId
bid BlockId -> BlockId -> Bool
forall a. Eq a => a -> a -> Bool
== BlockId
target
BCOND Cond
_ Operand
_ Operand
_ (TBlock BlockId
target) Operand
_ -> BlockId
bid BlockId -> BlockId -> Bool
forall a. Eq a => a -> a -> Bool
== BlockId
target
Instr
_ -> Bool
False
where
isTargetBid :: Maybe BlockId -> Bool
isTargetBid Maybe BlockId
target = case Maybe BlockId
target of
Maybe BlockId
Nothing -> Bool
True
Just BlockId
target -> BlockId
target BlockId -> BlockId -> Bool
forall a. Eq a => a -> a -> Bool
== BlockId
bid
mkRegRegMoveInstr :: Reg -> Reg -> Instr
mkRegRegMoveInstr :: Reg -> Reg -> Instr
mkRegRegMoveInstr Reg
src Reg
dst = SDoc -> Instr -> Instr
ANN SDoc
desc Instr
instr
where
desc :: SDoc
desc = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Reg->Reg Move: " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Reg -> SDoc
forall a. Outputable a => a -> SDoc
ppr Reg
src SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
" -> " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Reg -> SDoc
forall a. Outputable a => a -> SDoc
ppr Reg
dst
instr :: Instr
instr = Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
W64 Reg
dst) (Width -> Reg -> Operand
OpReg Width
W64 Reg
src)
takeRegRegMoveInstr :: Instr -> Maybe (Reg, Reg)
takeRegRegMoveInstr :: Instr -> Maybe (Reg, Reg)
takeRegRegMoveInstr (MOV (OpReg Width
width Reg
dst) (OpReg Width
width' Reg
src))
| Width
width Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
width' Bool -> Bool -> Bool
&& (Reg -> Bool
isFloatReg Reg
dst Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Reg -> Bool
isFloatReg Reg
src) = (Reg, Reg) -> Maybe (Reg, Reg)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Reg
src, Reg
dst)
takeRegRegMoveInstr Instr
_ = Maybe (Reg, Reg)
forall a. Maybe a
Nothing
mkJumpInstr :: BlockId -> [Instr]
mkJumpInstr :: BlockId -> [Instr]
mkJumpInstr BlockId
id = [Operand -> Target -> Instr
TAIL36 (Width -> Reg -> Operand
OpReg Width
W64 Reg
tmpReg) (BlockId -> Target
TBlock (BlockId
id))]
mkStackAllocInstr :: Platform -> Int -> [Instr]
mkStackAllocInstr :: Platform -> RegNo -> [Instr]
mkStackAllocInstr Platform
_platform RegNo
n
| RegNo
n RegNo -> RegNo -> Bool
forall a. Eq a => a -> a -> Bool
== RegNo
0 = []
| RegNo
n RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
> RegNo
0 Bool -> Bool -> Bool
&& RegNo -> RegNo -> Bool
fitsInNbits RegNo
12 (RegNo -> RegNo
forall a b. (Integral a, Num b) => a -> b
fromIntegral RegNo
n) =
[ SDoc -> Instr -> Instr
ANN (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Alloc stack") (Instr -> Instr) -> Instr -> Instr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
SUB Operand
sp Operand
sp (Imm -> Operand
OpImm (RegNo -> Imm
ImmInt RegNo
n)) ]
| RegNo
n RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
> RegNo
0 =
[
SDoc -> Instr -> Instr
ANN (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Alloc more stack") (Operand -> Operand -> Instr
MOV Operand
tmp (Imm -> Operand
OpImm (RegNo -> Imm
ImmInt RegNo
n))),
Operand -> Operand -> Operand -> Instr
SUB Operand
sp Operand
sp Operand
tmp
]
mkStackAllocInstr Platform
_platform RegNo
n = String -> SDoc -> [Instr]
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"mkStackAllocInstr" (RegNo -> SDoc
forall doc. IsLine doc => RegNo -> doc
int RegNo
n)
mkStackDeallocInstr :: Platform -> Int -> [Instr]
mkStackDeallocInstr :: Platform -> RegNo -> [Instr]
mkStackDeallocInstr Platform
_platform RegNo
n
| RegNo
n RegNo -> RegNo -> Bool
forall a. Eq a => a -> a -> Bool
== RegNo
0 = []
| RegNo
n RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
> RegNo
0 Bool -> Bool -> Bool
&& RegNo -> RegNo -> Bool
fitsInNbits RegNo
12 (RegNo -> RegNo
forall a b. (Integral a, Num b) => a -> b
fromIntegral RegNo
n) =
[ SDoc -> Instr -> Instr
ANN (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Dealloc stack") (Instr -> Instr) -> Instr -> Instr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
ADD Operand
sp Operand
sp (Imm -> Operand
OpImm (RegNo -> Imm
ImmInt RegNo
n)) ]
| RegNo
n RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
> RegNo
0 =
[
SDoc -> Instr -> Instr
ANN (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Dealloc more stack") (Operand -> Operand -> Instr
MOV Operand
tmp (Imm -> Operand
OpImm (RegNo -> Imm
ImmInt RegNo
n))),
Operand -> Operand -> Operand -> Instr
ADD Operand
sp Operand
sp Operand
tmp
]
mkStackDeallocInstr Platform
_platform RegNo
n = String -> SDoc -> [Instr]
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"mkStackDeallocInstr" (RegNo -> SDoc
forall doc. IsLine doc => RegNo -> doc
int RegNo
n)
allocMoreStack
:: Platform
-> Int
-> NatCmmDecl statics GHC.CmmToAsm.LA64.Instr.Instr
-> UniqDSM (NatCmmDecl statics GHC.CmmToAsm.LA64.Instr.Instr, [(BlockId,BlockId)])
allocMoreStack :: forall statics.
Platform
-> RegNo
-> NatCmmDecl statics Instr
-> UniqDSM (NatCmmDecl statics Instr, [(BlockId, BlockId)])
allocMoreStack Platform
_ RegNo
_ top :: NatCmmDecl statics Instr
top@(CmmData Section
_ statics
_) = (NatCmmDecl statics Instr, [(BlockId, BlockId)])
-> UniqDSM (NatCmmDecl statics Instr, [(BlockId, BlockId)])
forall a. a -> UniqDSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (NatCmmDecl statics Instr
top, [])
allocMoreStack Platform
platform RegNo
slots proc :: NatCmmDecl statics Instr
proc@(CmmProc LabelMap RawCmmStatics
info CLabel
lbl [GlobalRegUse]
live (ListGraph [GenBasicBlock Instr]
code)) = do
let entries :: [BlockId]
entries = NatCmmDecl statics Instr -> [BlockId]
forall a i b. GenCmmDecl a (LabelMap i) (ListGraph b) -> [BlockId]
entryBlocks NatCmmDecl statics Instr
proc
retargetList <- (BlockId -> UniqDSM (BlockId, BlockId))
-> [BlockId] -> UniqDSM [(BlockId, BlockId)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (\BlockId
e -> (BlockId
e,) (BlockId -> (BlockId, BlockId))
-> UniqDSM BlockId -> UniqDSM (BlockId, BlockId)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UniqDSM BlockId
forall (m :: * -> *). MonadGetUnique m => m BlockId
newBlockId) [BlockId]
entries
let
delta = ((RegNo
x RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
+ RegNo
stackAlign RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
- RegNo
1) RegNo -> RegNo -> RegNo
forall a. Integral a => a -> a -> a
`quot` RegNo
stackAlign) RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
* RegNo
stackAlign
where x :: RegNo
x = RegNo
slots RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
* RegNo
spillSlotSize
alloc = Platform -> RegNo -> [Instr]
mkStackAllocInstr Platform
platform RegNo
delta
dealloc = Platform -> RegNo -> [Instr]
mkStackDeallocInstr Platform
platform RegNo
delta
new_blockmap :: LabelMap BlockId
new_blockmap = [(BlockId, BlockId)] -> LabelMap BlockId
forall v. [(BlockId, v)] -> LabelMap v
mapFromList [(BlockId, BlockId)]
retargetList
insert_stack_insn (BasicBlock BlockId
id [Instr]
insns)
| Just BlockId
new_blockid <- BlockId -> LabelMap BlockId -> Maybe BlockId
forall a. BlockId -> LabelMap a -> Maybe a
mapLookup BlockId
id LabelMap BlockId
new_blockmap =
[ BlockId -> [Instr] -> GenBasicBlock Instr
forall i. BlockId -> [i] -> GenBasicBlock i
BasicBlock BlockId
id ([Instr] -> GenBasicBlock Instr) -> [Instr] -> GenBasicBlock Instr
forall a b. (a -> b) -> a -> b
$ [Instr]
alloc [Instr] -> [Instr] -> [Instr]
forall a. [a] -> [a] -> [a]
++ [ Target -> Instr
B (BlockId -> Target
TBlock BlockId
new_blockid) ],
BlockId -> [Instr] -> GenBasicBlock Instr
forall i. BlockId -> [i] -> GenBasicBlock i
BasicBlock BlockId
new_blockid [Instr]
block' ]
| Bool
otherwise =
[ BlockId -> [Instr] -> GenBasicBlock Instr
forall i. BlockId -> [i] -> GenBasicBlock i
BasicBlock BlockId
id [Instr]
block' ]
where
block' :: [Instr]
block' = (Instr -> [Instr] -> [Instr]) -> [Instr] -> [Instr] -> [Instr]
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Instr -> [Instr] -> [Instr]
insert_dealloc [] [Instr]
insns
insert_dealloc Instr
insn [Instr]
r = case Instr
insn of
J {} -> [Instr]
dealloc [Instr] -> [Instr] -> [Instr]
forall a. [a] -> [a] -> [a]
++ (Instr
insn Instr -> [Instr] -> [Instr]
forall a. a -> [a] -> [a]
: [Instr]
r)
J_TBL {} -> [Instr]
dealloc [Instr] -> [Instr] -> [Instr]
forall a. [a] -> [a] -> [a]
++ (Instr
insn Instr -> [Instr] -> [Instr]
forall a. a -> [a] -> [a]
: [Instr]
r)
ANN SDoc
_ Instr
e -> Instr -> [Instr] -> [Instr]
insert_dealloc Instr
e [Instr]
r
Instr
_other | Instr -> [BlockId]
jumpDestsOfInstr Instr
insn [BlockId] -> [BlockId] -> Bool
forall a. Eq a => a -> a -> Bool
/= [] ->
Instr -> (BlockId -> BlockId) -> Instr
patchJumpInstr Instr
insn BlockId -> BlockId
retarget Instr -> [Instr] -> [Instr]
forall a. a -> [a] -> [a]
: [Instr]
r
Instr
_other -> Instr
insn Instr -> [Instr] -> [Instr]
forall a. a -> [a] -> [a]
: [Instr]
r
where retarget :: BlockId -> BlockId
retarget BlockId
b = BlockId -> Maybe BlockId -> BlockId
forall a. a -> Maybe a -> a
fromMaybe BlockId
b (BlockId -> LabelMap BlockId -> Maybe BlockId
forall a. BlockId -> LabelMap a -> Maybe a
mapLookup BlockId
b LabelMap BlockId
new_blockmap)
new_code = (GenBasicBlock Instr -> [GenBasicBlock Instr])
-> [GenBasicBlock Instr] -> [GenBasicBlock Instr]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap GenBasicBlock Instr -> [GenBasicBlock Instr]
insert_stack_insn [GenBasicBlock Instr]
code
return (CmmProc info lbl live (ListGraph new_code), retargetList)
data Instr
= SDoc
| SDoc
| ANN SDoc Instr
| LOCATION Int Int Int LexicalFastString
| NEWBLOCK BlockId
| DELTA Int
| LDATA Section RawCmmStatics
| PUSH_STACK_FRAME
| POP_STACK_FRAME
| ADD Operand Operand Operand
| SUB Operand Operand Operand
| ALSL Operand Operand Operand Operand
| ALSLU Operand Operand Operand Operand
| LU12I Operand Operand
| LU32I Operand Operand
| LU52I Operand Operand Operand
| SSLT Operand Operand Operand
| SSLTU Operand Operand Operand
| PCADDI Operand Operand
| PCADDU12I Operand Operand
| PCADDU18I Operand Operand
| PCALAU12I Operand Operand
| AND Operand Operand Operand
| OR Operand Operand Operand
| XOR Operand Operand Operand
| NOR Operand Operand Operand
| ANDN Operand Operand Operand
| ORN Operand Operand Operand
| MUL Operand Operand Operand
| MULW Operand Operand Operand
| MULWU Operand Operand Operand
| MULH Operand Operand Operand
| MULHU Operand Operand Operand
| DIV Operand Operand Operand
| DIVU Operand Operand Operand
| MOD Operand Operand Operand
| MODU Operand Operand Operand
| SLL Operand Operand Operand
| SRL Operand Operand Operand
| SRA Operand Operand Operand
| ROTR Operand Operand Operand
| EXT Operand Operand
| CLO Operand Operand
| CTO Operand Operand
| CLZ Operand Operand
| CTZ Operand Operand
| BYTEPICK Operand Operand Operand Operand
| REVB2H Operand Operand
| REVB4H Operand Operand
| REVB2W Operand Operand
| REVBD Operand Operand
| REVH2W Operand Operand
| REVHD Operand Operand
| BITREV4B Operand Operand
| BITREV8B Operand Operand
| BITREVW Operand Operand
| BITREVD Operand Operand
| BSTRINS Format Operand Operand Operand Operand
| BSTRPICK Format Operand Operand Operand Operand
| MASKEQZ Operand Operand Operand
| MASKNEZ Operand Operand Operand
| NOP
| MOV Operand Operand
| NEG Operand Operand
| CSET Cond Operand Operand Operand
| J Target
| J_TBL [Maybe BlockId] (Maybe CLabel) Reg
| B Target
| BL Target [Reg]
| CALL36 Target
| TAIL36 Operand Target
| BCOND Cond Operand Operand Target Operand
| BEQZ Operand Target
| BNEZ Operand Target
| LD Format Operand Operand
| LDU Format Operand Operand
| ST Format Operand Operand
| LDX Format Operand Operand
| LDXU Format Operand Operand
| STX Format Operand Operand
| LDPTR Format Operand Operand
| STPTR Format Operand Operand
| DBAR BarrierType
| IBAR BarrierType
| FCVT Operand Operand
| SCVTF Operand Operand
| FCVTZS Operand Operand Operand
| FMAX Operand Operand Operand
| FMIN Operand Operand Operand
| FMAXA Operand Operand Operand
| FMINA Operand Operand Operand
| FNEG Operand Operand
| FABS Operand Operand
| FMA FMASign Operand Operand Operand Operand
data BarrierType = Hint0
instrCon :: Instr -> String
instrCon :: Instr -> String
instrCon Instr
i =
case Instr
i of
COMMENT{} -> String
"COMMENT"
MULTILINE_COMMENT{} -> String
"COMMENT"
ANN{} -> String
"ANN"
LOCATION{} -> String
"LOCATION"
NEWBLOCK{} -> String
"NEWBLOCK"
DELTA{} -> String
"DELTA"
LDATA {} -> String
"LDATA"
PUSH_STACK_FRAME{} -> String
"PUSH_STACK_FRAME"
POP_STACK_FRAME{} -> String
"POP_STACK_FRAME"
ADD{} -> String
"ADD"
SUB{} -> String
"SUB"
ALSL{} -> String
"ALSL"
ALSLU{} -> String
"ALSLU"
LU12I{} -> String
"LU12I"
LU32I{} -> String
"LU32I"
LU52I{} -> String
"LU52I"
SSLT{} -> String
"SSLT"
SSLTU{} -> String
"SSLTU"
PCADDI{} -> String
"PCADDI"
PCADDU12I{} -> String
"PCADDU12I"
PCADDU18I{} -> String
"PCADDU18I"
PCALAU12I{} -> String
"PCALAU12I"
AND{} -> String
"AND"
OR{} -> String
"OR"
XOR{} -> String
"XOR"
NOR{} -> String
"NOR"
ANDN{} -> String
"ANDN"
ORN{} -> String
"ORN"
MUL{} -> String
"MUL"
MULW{} -> String
"MULW"
MULWU{} -> String
"MULWU"
MULH{} -> String
"MULH"
MULHU{} -> String
"MULHU"
DIV{} -> String
"DIV"
MOD{} -> String
"MOD"
DIVU{} -> String
"DIVU"
MODU{} -> String
"MODU"
SLL{} -> String
"SLL"
SRL{} -> String
"SRL"
SRA{} -> String
"SRA"
ROTR{} -> String
"ROTR"
EXT{} -> String
"EXT"
CLO{} -> String
"CLO"
CLZ{} -> String
"CLZ"
CTO{} -> String
"CTO"
CTZ{} -> String
"CTZ"
BYTEPICK{} -> String
"BYTEPICK"
REVB2H{} -> String
"REVB2H"
REVB4H{} -> String
"REVB4H"
REVB2W{} -> String
"REVB2W"
REVBD{} -> String
"REVBD"
REVH2W{} -> String
"REVH2W"
REVHD{} -> String
"REVHD"
BITREV4B{} -> String
"BITREV4B"
BITREV8B{} -> String
"BITREV8B"
BITREVW{} -> String
"BITREVW"
BITREVD{} -> String
"BITREVD"
BSTRINS{} -> String
"BSTRINS"
BSTRPICK{} -> String
"BSTRPICK"
MASKEQZ{} -> String
"MASKEQZ"
MASKNEZ{} -> String
"MASKNEZ"
NOP{} -> String
"NOP"
MOV{} -> String
"MOV"
NEG{} -> String
"NEG"
CSET{} -> String
"CSET"
J{} -> String
"J"
J_TBL{} -> String
"J_TBL"
B{} -> String
"B"
BL{} -> String
"BL"
CALL36{} -> String
"CALL36"
TAIL36{} -> String
"TAIL36"
BCOND{} -> String
"BCOND"
BEQZ{} -> String
"BEQZ"
BNEZ{} -> String
"BNEZ"
LD{} -> String
"LD"
LDU{} -> String
"LDU"
ST{} -> String
"ST"
LDX{} -> String
"LDX"
LDXU{} -> String
"LDXU"
STX{} -> String
"STX"
LDPTR{} -> String
"LDPTR"
STPTR{} -> String
"STPTR"
DBAR{} -> String
"DBAR"
IBAR{} -> String
"IBAR"
FCVT{} -> String
"FCVT"
SCVTF{} -> String
"SCVTF"
FCVTZS{} -> String
"FCVTZS"
FMAX{} -> String
"FMAX"
FMIN{} -> String
"FMIN"
FMAXA{} -> String
"FMAXA"
FMINA{} -> String
"FMINA"
FNEG{} -> String
"FNEG"
FABS{} -> String
"FABS"
FMA FMASign
variant Operand
_ Operand
_ Operand
_ Operand
_ ->
case FMASign
variant of
FMASign
FMAdd -> String
"FMADD"
FMASign
FMSub -> String
"FMSUB"
FMASign
FNMAdd -> String
"FNMADD"
FMASign
FNMSub -> String
"FNMSUB"
data Target
= TBlock BlockId
| TLabel CLabel
| TReg Reg
data Operand
= OpReg Width Reg
| OpImm Imm
| OpAddr AddrMode
deriving (Operand -> Operand -> Bool
(Operand -> Operand -> Bool)
-> (Operand -> Operand -> Bool) -> Eq Operand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Operand -> Operand -> Bool
== :: Operand -> Operand -> Bool
$c/= :: Operand -> Operand -> Bool
/= :: Operand -> Operand -> Bool
Eq, RegNo -> Operand -> String -> String
[Operand] -> String -> String
Operand -> String
(RegNo -> Operand -> String -> String)
-> (Operand -> String)
-> ([Operand] -> String -> String)
-> Show Operand
forall a.
(RegNo -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: RegNo -> Operand -> String -> String
showsPrec :: RegNo -> Operand -> String -> String
$cshow :: Operand -> String
show :: Operand -> String
$cshowList :: [Operand] -> String -> String
showList :: [Operand] -> String -> String
Show)
opReg :: Reg -> Operand
opReg :: Reg -> Operand
opReg = Width -> Reg -> Operand
OpReg Width
W64
opRegNo :: RegNo -> Operand
opRegNo :: RegNo -> Operand
opRegNo = Reg -> Operand
opReg (Reg -> Operand) -> (RegNo -> Reg) -> RegNo -> Operand
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RegNo -> Reg
regSingle
zero, ra, tp, sp, fp, tmp :: Operand
zero :: Operand
zero = Reg -> Operand
opReg Reg
zeroReg
ra :: Operand
ra = Reg -> Operand
opReg Reg
raReg
sp :: Operand
sp = Reg -> Operand
opReg Reg
spMachReg
tp :: Operand
tp = Reg -> Operand
opReg Reg
tpMachReg
fp :: Operand
fp = Reg -> Operand
opReg Reg
fpMachReg
tmp :: Operand
tmp = Reg -> Operand
opReg Reg
tmpReg
x0, x1, x2, x3, x4, x5, x6, x7 :: Operand
x8, x9, x10, x11, x12, x13, x14, x15 :: Operand
x16, x17, x18, x19, x20, x21, x22, x23 :: Operand
x24, x25, x26, x27, x28, x29, x30, x31 :: Operand
x0 :: Operand
x0 = RegNo -> Operand
opRegNo RegNo
0
x1 :: Operand
x1 = RegNo -> Operand
opRegNo RegNo
1
x2 :: Operand
x2 = RegNo -> Operand
opRegNo RegNo
2
x3 :: Operand
x3 = RegNo -> Operand
opRegNo RegNo
3
x4 :: Operand
x4 = RegNo -> Operand
opRegNo RegNo
4
x5 :: Operand
x5 = RegNo -> Operand
opRegNo RegNo
5
x6 :: Operand
x6 = RegNo -> Operand
opRegNo RegNo
6
x7 :: Operand
x7 = RegNo -> Operand
opRegNo RegNo
7
x8 :: Operand
x8 = RegNo -> Operand
opRegNo RegNo
8
x9 :: Operand
x9 = RegNo -> Operand
opRegNo RegNo
9
x10 :: Operand
x10 = RegNo -> Operand
opRegNo RegNo
10
x11 :: Operand
x11 = RegNo -> Operand
opRegNo RegNo
11
x12 :: Operand
x12 = RegNo -> Operand
opRegNo RegNo
12
x13 :: Operand
x13 = RegNo -> Operand
opRegNo RegNo
13
x14 :: Operand
x14 = RegNo -> Operand
opRegNo RegNo
14
x15 :: Operand
x15 = RegNo -> Operand
opRegNo RegNo
15
x16 :: Operand
x16 = RegNo -> Operand
opRegNo RegNo
16
x17 :: Operand
x17 = RegNo -> Operand
opRegNo RegNo
17
x18 :: Operand
x18 = RegNo -> Operand
opRegNo RegNo
18
x19 :: Operand
x19 = RegNo -> Operand
opRegNo RegNo
19
x20 :: Operand
x20 = RegNo -> Operand
opRegNo RegNo
20
x21 :: Operand
x21 = RegNo -> Operand
opRegNo RegNo
21
x22 :: Operand
x22 = RegNo -> Operand
opRegNo RegNo
22
x23 :: Operand
x23 = RegNo -> Operand
opRegNo RegNo
23
x24 :: Operand
x24 = RegNo -> Operand
opRegNo RegNo
24
x25 :: Operand
x25 = RegNo -> Operand
opRegNo RegNo
25
x26 :: Operand
x26 = RegNo -> Operand
opRegNo RegNo
26
x27 :: Operand
x27 = RegNo -> Operand
opRegNo RegNo
27
x28 :: Operand
x28 = RegNo -> Operand
opRegNo RegNo
18
x29 :: Operand
x29 = RegNo -> Operand
opRegNo RegNo
29
x30 :: Operand
x30 = RegNo -> Operand
opRegNo RegNo
30
x31 :: Operand
x31 = RegNo -> Operand
opRegNo RegNo
31
d0, d1, d2, d3, d4, d5, d6, d7 :: Operand
d8, d9, d10, d11, d12, d13, d14, d15 :: Operand
d16, d17, d18, d19, d20, d21, d22, d23 :: Operand
d24, d25, d26, d27, d28, d29, d30, d31 :: Operand
d0 :: Operand
d0 = RegNo -> Operand
opRegNo RegNo
32
d1 :: Operand
d1 = RegNo -> Operand
opRegNo RegNo
33
d2 :: Operand
d2 = RegNo -> Operand
opRegNo RegNo
34
d3 :: Operand
d3 = RegNo -> Operand
opRegNo RegNo
35
d4 :: Operand
d4 = RegNo -> Operand
opRegNo RegNo
36
d5 :: Operand
d5 = RegNo -> Operand
opRegNo RegNo
37
d6 :: Operand
d6 = RegNo -> Operand
opRegNo RegNo
38
d7 :: Operand
d7 = RegNo -> Operand
opRegNo RegNo
39
d8 :: Operand
d8 = RegNo -> Operand
opRegNo RegNo
40
d9 :: Operand
d9 = RegNo -> Operand
opRegNo RegNo
41
d10 :: Operand
d10 = RegNo -> Operand
opRegNo RegNo
42
d11 :: Operand
d11 = RegNo -> Operand
opRegNo RegNo
43
d12 :: Operand
d12 = RegNo -> Operand
opRegNo RegNo
44
d13 :: Operand
d13 = RegNo -> Operand
opRegNo RegNo
45
d14 :: Operand
d14 = RegNo -> Operand
opRegNo RegNo
46
d15 :: Operand
d15 = RegNo -> Operand
opRegNo RegNo
47
d16 :: Operand
d16 = RegNo -> Operand
opRegNo RegNo
48
d17 :: Operand
d17 = RegNo -> Operand
opRegNo RegNo
49
d18 :: Operand
d18 = RegNo -> Operand
opRegNo RegNo
50
d19 :: Operand
d19 = RegNo -> Operand
opRegNo RegNo
51
d20 :: Operand
d20 = RegNo -> Operand
opRegNo RegNo
52
d21 :: Operand
d21 = RegNo -> Operand
opRegNo RegNo
53
d22 :: Operand
d22 = RegNo -> Operand
opRegNo RegNo
54
d23 :: Operand
d23 = RegNo -> Operand
opRegNo RegNo
55
d24 :: Operand
d24 = RegNo -> Operand
opRegNo RegNo
56
d25 :: Operand
d25 = RegNo -> Operand
opRegNo RegNo
57
d26 :: Operand
d26 = RegNo -> Operand
opRegNo RegNo
58
d27 :: Operand
d27 = RegNo -> Operand
opRegNo RegNo
59
d28 :: Operand
d28 = RegNo -> Operand
opRegNo RegNo
60
d29 :: Operand
d29 = RegNo -> Operand
opRegNo RegNo
61
d30 :: Operand
d30 = RegNo -> Operand
opRegNo RegNo
62
d31 :: Operand
d31 = RegNo -> Operand
opRegNo RegNo
63
fitsInNbits :: Int -> Int -> Bool
fitsInNbits :: RegNo -> RegNo -> Bool
fitsInNbits RegNo
n RegNo
i = (-RegNo
1 RegNo -> RegNo -> RegNo
forall a. Bits a => a -> RegNo -> a
`shiftL` (RegNo
n RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
- RegNo
1)) RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
<= RegNo
i Bool -> Bool -> Bool
&& RegNo
i RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
<= (RegNo
1 RegNo -> RegNo -> RegNo
forall a. Bits a => a -> RegNo -> a
`shiftL` (RegNo
n RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
- RegNo
1) RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
- RegNo
1)
isUnsignOp :: Int -> Bool
isUnsignOp :: RegNo -> Bool
isUnsignOp RegNo
i = (RegNo
i RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
>= RegNo
0)
isNbitEncodeable :: Int -> Integer -> Bool
isNbitEncodeable :: RegNo -> Integer -> Bool
isNbitEncodeable RegNo
n Integer
i = let shift :: RegNo
shift = RegNo
n RegNo -> RegNo -> RegNo
forall a. Num a => a -> a -> a
- RegNo
1 in (-Integer
1 Integer -> RegNo -> Integer
forall a. Bits a => a -> RegNo -> a
`shiftL` RegNo
shift) Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
i Bool -> Bool -> Bool
&& Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< (Integer
1 Integer -> RegNo -> Integer
forall a. Bits a => a -> RegNo -> a
`shiftL` RegNo
shift)
isEncodeableInWidth :: Width -> Integer -> Bool
isEncodeableInWidth :: Width -> Integer -> Bool
isEncodeableInWidth = RegNo -> Integer -> Bool
isNbitEncodeable (RegNo -> Integer -> Bool)
-> (Width -> RegNo) -> Width -> Integer -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Width -> RegNo
widthInBits
isIntOp :: Operand -> Bool
isIntOp :: Operand -> Bool
isIntOp = Bool -> Bool
not (Bool -> Bool) -> (Operand -> Bool) -> Operand -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Operand -> Bool
isFloatOp
isFloatOp :: Operand -> Bool
isFloatOp :: Operand -> Bool
isFloatOp (OpReg Width
_ Reg
reg) | Reg -> Bool
isFloatReg Reg
reg = Bool
True
isFloatOp Operand
_ = Bool
False
isFloatReg :: Reg -> Bool
isFloatReg :: Reg -> Bool
isFloatReg (RegReal (RealRegSingle RegNo
i)) | RegNo
i RegNo -> RegNo -> Bool
forall a. Ord a => a -> a -> Bool
> RegNo
31 = Bool
True
isFloatReg (RegVirtual (VirtualRegD Unique
_)) = Bool
True
isFloatReg Reg
_ = Bool
False
widthToInt :: Width -> Int
widthToInt :: Width -> RegNo
widthToInt Width
W8 = RegNo
8
widthToInt Width
W16 = RegNo
16
widthToInt Width
W32 = RegNo
32
widthToInt Width
W64 = RegNo
64
widthToInt Width
_ = RegNo
64
widthFromOpReg :: Operand -> Width
widthFromOpReg :: Operand -> Width
widthFromOpReg (OpReg Width
W8 Reg
_) = Width
W8
widthFromOpReg (OpReg Width
W16 Reg
_) = Width
W16
widthFromOpReg (OpReg Width
W32 Reg
_) = Width
W32
widthFromOpReg (OpReg Width
W64 Reg
_) = Width
W64
widthFromOpReg Operand
_ = Width
W64
lessW64 :: Width -> Bool
lessW64 :: Width -> Bool
lessW64 Width
w | Width
w Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W8 Bool -> Bool -> Bool
|| Width
w Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W16 Bool -> Bool -> Bool
|| Width
w Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W32 = Bool
True
lessW64 Width
_ = Bool
False