module GHC.CmmToAsm.SPARC.Imm (
        
        Imm(..),
        strImmLit,
        litToImm
)
where
import GHC.Prelude
import GHC.Cmm
import GHC.Cmm.CLabel
import GHC.Utils.Outputable
import GHC.Utils.Panic
data Imm
        = ImmInt        Int
        
        | ImmInteger    Integer
        
        | ImmCLbl       CLabel
        
        | ImmLit        SDoc
        | ImmIndex      CLabel Int
        | ImmFloat      Rational
        | ImmDouble     Rational
        | ImmConstantSum  Imm Imm
        | ImmConstantDiff Imm Imm
        | LO    Imm
        | HI    Imm
strImmLit :: String -> Imm
strImmLit :: String -> Imm
strImmLit String
s = SDoc -> Imm
ImmLit (String -> SDoc
text String
s)
litToImm :: CmmLit -> Imm
litToImm :: CmmLit -> Imm
litToImm CmmLit
lit
 = case CmmLit
lit of
        CmmInt Integer
i Width
w              -> Integer -> Imm
ImmInteger (Width -> Integer -> Integer
narrowS Width
w Integer
i)
        CmmFloat Rational
f Width
W32          -> Rational -> Imm
ImmFloat Rational
f
        CmmFloat Rational
f Width
W64          -> Rational -> Imm
ImmDouble Rational
f
        CmmLabel CLabel
l              -> CLabel -> Imm
ImmCLbl CLabel
l
        CmmLabelOff CLabel
l Int
off       -> CLabel -> Int -> Imm
ImmIndex CLabel
l Int
off
        CmmLabelDiffOff CLabel
l1 CLabel
l2 Int
off Width
_
         -> Imm -> Imm -> Imm
ImmConstantSum
                (Imm -> Imm -> Imm
ImmConstantDiff (CLabel -> Imm
ImmCLbl CLabel
l1) (CLabel -> Imm
ImmCLbl CLabel
l2))
                (Int -> Imm
ImmInt Int
off)
        CmmLit
_               -> String -> Imm
forall a. String -> a
panic String
"SPARC.Regs.litToImm: no match"