module SPARC.CodeGen.Base (
InstrBlock,
CondCode(..),
ChildCode64(..),
Amode(..),
Register(..),
setFormatOfRegister,
getRegisterReg,
mangleIndexTree
)
where
import GhcPrelude
import SPARC.Instr
import SPARC.Cond
import SPARC.AddrMode
import SPARC.Regs
import Format
import Reg
import GHC.Platform.Regs
import DynFlags
import Cmm
import PprCmmExpr ()
import GHC.Platform
import Outputable
import OrdList
type InstrBlock
= OrdList Instr
data CondCode
= CondCode Bool Cond InstrBlock
data ChildCode64
= ChildCode64
InstrBlock
Reg
data Amode
= Amode
AddrMode
InstrBlock
data Register
= Fixed Format Reg InstrBlock
| Any Format (Reg -> InstrBlock)
setFormatOfRegister
:: Register -> Format -> Register
setFormatOfRegister :: Register -> Format -> Register
setFormatOfRegister Register
reg Format
format
= case Register
reg of
Fixed Format
_ Reg
reg InstrBlock
code -> Format -> Reg -> InstrBlock -> Register
Fixed Format
format Reg
reg InstrBlock
code
Any Format
_ Reg -> InstrBlock
codefn -> Format -> (Reg -> InstrBlock) -> Register
Any Format
format Reg -> InstrBlock
codefn
getRegisterReg :: Platform -> CmmReg -> Reg
getRegisterReg :: Platform -> CmmReg -> Reg
getRegisterReg Platform
_ (CmmLocal (LocalReg Unique
u CmmType
pk))
= VirtualReg -> Reg
RegVirtual (VirtualReg -> Reg) -> VirtualReg -> Reg
forall a b. (a -> b) -> a -> b
$ Unique -> Format -> VirtualReg
mkVirtualReg Unique
u (CmmType -> Format
cmmTypeFormat CmmType
pk)
getRegisterReg Platform
platform (CmmGlobal GlobalReg
mid)
= case Platform -> GlobalReg -> Maybe RealReg
globalRegMaybe Platform
platform GlobalReg
mid of
Just RealReg
reg -> RealReg -> Reg
RegReal RealReg
reg
Maybe RealReg
Nothing -> String -> SDoc -> Reg
forall a. HasCallStack => String -> SDoc -> a
pprPanic
String
"SPARC.CodeGen.Base.getRegisterReg: global is in memory"
(CmmReg -> SDoc
forall a. Outputable a => a -> SDoc
ppr (CmmReg -> SDoc) -> CmmReg -> SDoc
forall a b. (a -> b) -> a -> b
$ GlobalReg -> CmmReg
CmmGlobal GlobalReg
mid)
mangleIndexTree :: DynFlags -> CmmExpr -> CmmExpr
mangleIndexTree :: DynFlags -> CmmExpr -> CmmExpr
mangleIndexTree DynFlags
dflags (CmmRegOff CmmReg
reg Int
off)
= MachOp -> [CmmExpr] -> CmmExpr
CmmMachOp (Width -> MachOp
MO_Add Width
width) [CmmReg -> CmmExpr
CmmReg CmmReg
reg, CmmLit -> CmmExpr
CmmLit (Integer -> Width -> CmmLit
CmmInt (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
off) Width
width)]
where width :: Width
width = CmmType -> Width
typeWidth (DynFlags -> CmmReg -> CmmType
cmmRegType DynFlags
dflags CmmReg
reg)
mangleIndexTree DynFlags
_ CmmExpr
_
= String -> CmmExpr
forall a. String -> a
panic String
"SPARC.CodeGen.Base.mangleIndexTree: no match"