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 CodeGen.Platform
import DynFlags
import Cmm
import PprCmmExpr ()
import Platform

import Outputable
import OrdList

--------------------------------------------------------------------------------
-- | 'InstrBlock's are the insn sequences generated by the insn selectors.
--      They are really trees of insns to facilitate fast appending, where a
--      left-to-right traversal yields the insns in the correct order.
--
type InstrBlock
        = OrdList Instr


-- | Condition codes passed up the tree.
--
data CondCode
        = CondCode Bool Cond InstrBlock


-- | a.k.a "Register64"
--      Reg is the lower 32-bit temporary which contains the result.
--      Use getHiVRegFromLo to find the other VRegUnique.
--
--      Rules of this simplified insn selection game are therefore that
--      the returned Reg may be modified
--
data ChildCode64
   = ChildCode64
        InstrBlock
        Reg


-- | Holds code that references a memory address.
data Amode
        = Amode
                -- the AddrMode we can use in the instruction
                --      that does the real load\/store.
                AddrMode

                -- other setup code we have to run first before we can use the
                --      above AddrMode.
                InstrBlock



--------------------------------------------------------------------------------
-- | Code to produce a result into a register.
--      If the result must go in a specific register, it comes out as Fixed.
--      Otherwise, the parent can decide which register to put it in.
--
data Register
        = Fixed Format Reg InstrBlock
        | Any   Format (Reg -> InstrBlock)


-- | Change the format field in a Register.
setFormatOfRegister
        :: Register -> Format -> Register

setFormatOfRegister :: Register -> Format -> Register
setFormatOfRegister reg :: Register
reg format :: Format
format
 = case Register
reg of
        Fixed _ reg :: Reg
reg code :: InstrBlock
code        -> Format -> Reg -> InstrBlock -> Register
Fixed Format
format Reg
reg InstrBlock
code
        Any _ codefn :: Reg -> InstrBlock
codefn            -> Format -> (Reg -> InstrBlock) -> Register
Any   Format
format Reg -> InstrBlock
codefn


--------------------------------------------------------------------------------
-- | Grab the Reg for a CmmReg
getRegisterReg :: Platform -> CmmReg -> Reg

getRegisterReg :: Platform -> CmmReg -> Reg
getRegisterReg _ (CmmLocal (LocalReg u :: Unique
u pk :: 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
platform (CmmGlobal mid :: GlobalReg
mid)
  = case Platform -> GlobalReg -> Maybe RealReg
globalRegMaybe Platform
platform GlobalReg
mid of
        Just reg :: RealReg
reg -> RealReg -> Reg
RegReal RealReg
reg
        Nothing  -> String -> SDoc -> Reg
forall a. HasCallStack => String -> SDoc -> a
pprPanic
                        "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)


-- Expand CmmRegOff.  ToDo: should we do it this way around, or convert
-- CmmExprs into CmmRegOff?
mangleIndexTree :: DynFlags -> CmmExpr -> CmmExpr

mangleIndexTree :: DynFlags -> CmmExpr -> CmmExpr
mangleIndexTree dflags :: DynFlags
dflags (CmmRegOff reg :: CmmReg
reg off :: 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 _ _
        = String -> CmmExpr
forall a. String -> a
panic "SPARC.CodeGen.Base.mangleIndexTree: no match"