-----------------------------------------------------------------------------
--
-- Pretty-printing assembly language
--
-- (c) The University of Glasgow 1993-2005
--
-----------------------------------------------------------------------------

{-# OPTIONS_GHC -fno-warn-orphans #-}
module PPC.Ppr (pprNatCmmDecl) where

import GhcPrelude

import PPC.Regs
import PPC.Instr
import PPC.Cond
import PprBase
import Instruction
import Format
import Reg
import RegClass
import TargetReg

import Cmm hiding (topInfoTable)
import Hoopl.Collections
import Hoopl.Label

import BlockId
import CLabel
import PprCmmExpr () -- For Outputable instances

import Unique                ( pprUniqueAlways, getUnique )
import GHC.Platform
import FastString
import Outputable
import DynFlags

import Data.Word
import Data.Int
import Data.Bits

-- -----------------------------------------------------------------------------
-- Printing this stuff out

pprNatCmmDecl :: NatCmmDecl CmmStatics Instr -> SDoc
pprNatCmmDecl :: NatCmmDecl CmmStatics Instr -> SDoc
pprNatCmmDecl (CmmData Section
section CmmStatics
dats) =
  Section -> SDoc
pprSectionAlign Section
section SDoc -> SDoc -> SDoc
$$ CmmStatics -> SDoc
pprDatas CmmStatics
dats

pprNatCmmDecl proc :: NatCmmDecl CmmStatics Instr
proc@(CmmProc LabelMap CmmStatics
top_info CLabel
lbl [GlobalReg]
_ (ListGraph [GenBasicBlock Instr]
blocks)) =
  case NatCmmDecl CmmStatics Instr -> Maybe CmmStatics
forall a i b. GenCmmDecl a (LabelMap i) (ListGraph b) -> Maybe i
topInfoTable NatCmmDecl CmmStatics Instr
proc of
    Maybe CmmStatics
Nothing ->
       (Platform -> SDoc) -> SDoc
sdocWithPlatform ((Platform -> SDoc) -> SDoc) -> (Platform -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \Platform
platform ->
         -- special case for code without info table:
         Section -> SDoc
pprSectionAlign (SectionType -> CLabel -> Section
Section SectionType
Text CLabel
lbl) SDoc -> SDoc -> SDoc
$$
         (case Platform -> Arch
platformArch Platform
platform of
            ArchPPC_64 PPC_64ABI
ELF_V1 -> CLabel -> SDoc
pprFunctionDescriptor CLabel
lbl
            ArchPPC_64 PPC_64ABI
ELF_V2 -> CLabel -> SDoc
pprFunctionPrologue CLabel
lbl
            Arch
_ -> CLabel -> SDoc
pprLabel CLabel
lbl) SDoc -> SDoc -> SDoc
$$ -- blocks guaranteed not null,
                                     -- so label needed
         [SDoc] -> SDoc
vcat ((GenBasicBlock Instr -> SDoc) -> [GenBasicBlock Instr] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (LabelMap CmmStatics -> GenBasicBlock Instr -> SDoc
pprBasicBlock LabelMap CmmStatics
top_info) [GenBasicBlock Instr]
blocks)

    Just (Statics CLabel
info_lbl [CmmStatic]
_) ->
      (Platform -> SDoc) -> SDoc
sdocWithPlatform ((Platform -> SDoc) -> SDoc) -> (Platform -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \Platform
platform ->
      Section -> SDoc
pprSectionAlign (SectionType -> CLabel -> Section
Section SectionType
Text CLabel
info_lbl) SDoc -> SDoc -> SDoc
$$
      (if Platform -> Bool
platformHasSubsectionsViaSymbols Platform
platform
          then CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr (CLabel -> CLabel
mkDeadStripPreventer CLabel
info_lbl) SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
':'
          else SDoc
empty) SDoc -> SDoc -> SDoc
$$
      [SDoc] -> SDoc
vcat ((GenBasicBlock Instr -> SDoc) -> [GenBasicBlock Instr] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (LabelMap CmmStatics -> GenBasicBlock Instr -> SDoc
pprBasicBlock LabelMap CmmStatics
top_info) [GenBasicBlock Instr]
blocks) SDoc -> SDoc -> SDoc
$$
      -- above: Even the first block gets a label, because with branch-chain
      -- elimination, it might be the target of a goto.
      (if Platform -> Bool
platformHasSubsectionsViaSymbols Platform
platform
       then
       -- See Note [Subsections Via Symbols] in X86/Ppr.hs
                String -> SDoc
text String
"\t.long "
            SDoc -> SDoc -> SDoc
<+> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
info_lbl
            SDoc -> SDoc -> SDoc
<+> Char -> SDoc
char Char
'-'
            SDoc -> SDoc -> SDoc
<+> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr (CLabel -> CLabel
mkDeadStripPreventer CLabel
info_lbl)
       else SDoc
empty)

pprFunctionDescriptor :: CLabel -> SDoc
pprFunctionDescriptor :: CLabel -> SDoc
pprFunctionDescriptor CLabel
lab = CLabel -> SDoc
pprGloblDecl CLabel
lab
                        SDoc -> SDoc -> SDoc
$$  String -> SDoc
text String
"\t.section \".opd\", \"aw\""
                        SDoc -> SDoc -> SDoc
$$  String -> SDoc
text String
"\t.align 3"
                        SDoc -> SDoc -> SDoc
$$  CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
lab SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
':'
                        SDoc -> SDoc -> SDoc
$$  String -> SDoc
text String
"\t.quad ."
                        SDoc -> SDoc -> SDoc
<>  CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
lab
                        SDoc -> SDoc -> SDoc
<>  String -> SDoc
text String
",.TOC.@tocbase,0"
                        SDoc -> SDoc -> SDoc
$$  String -> SDoc
text String
"\t.previous"
                        SDoc -> SDoc -> SDoc
$$  String -> SDoc
text String
"\t.type"
                        SDoc -> SDoc -> SDoc
<+> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
lab
                        SDoc -> SDoc -> SDoc
<>  String -> SDoc
text String
", @function"
                        SDoc -> SDoc -> SDoc
$$  Char -> SDoc
char Char
'.' SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
lab SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
':'

pprFunctionPrologue :: CLabel ->SDoc
pprFunctionPrologue :: CLabel -> SDoc
pprFunctionPrologue CLabel
lab =  CLabel -> SDoc
pprGloblDecl CLabel
lab
                        SDoc -> SDoc -> SDoc
$$  String -> SDoc
text String
".type "
                        SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
lab
                        SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
", @function"
                        SDoc -> SDoc -> SDoc
$$ CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
lab SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
':'
                        SDoc -> SDoc -> SDoc
$$ String -> SDoc
text String
"0:\taddis\t" SDoc -> SDoc -> SDoc
<> Reg -> SDoc
pprReg Reg
toc
                        SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
",12,.TOC.-0b@ha"
                        SDoc -> SDoc -> SDoc
$$ String -> SDoc
text String
"\taddi\t" SDoc -> SDoc -> SDoc
<> Reg -> SDoc
pprReg Reg
toc
                        SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
',' SDoc -> SDoc -> SDoc
<> Reg -> SDoc
pprReg Reg
toc SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
",.TOC.-0b@l"
                        SDoc -> SDoc -> SDoc
$$ String -> SDoc
text String
"\t.localentry\t" SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
lab
                        SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
",.-" SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
lab

pprBasicBlock :: LabelMap CmmStatics -> NatBasicBlock Instr -> SDoc
pprBasicBlock :: LabelMap CmmStatics -> GenBasicBlock Instr -> SDoc
pprBasicBlock LabelMap CmmStatics
info_env (BasicBlock BlockId
blockid [Instr]
instrs)
  = SDoc
maybe_infotable SDoc -> SDoc -> SDoc
$$
    CLabel -> SDoc
pprLabel (BlockId -> CLabel
blockLbl BlockId
blockid) SDoc -> SDoc -> SDoc
$$
    [SDoc] -> SDoc
vcat ((Instr -> SDoc) -> [Instr] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Instr -> SDoc
pprInstr [Instr]
instrs)
  where
    maybe_infotable :: SDoc
maybe_infotable = case KeyOf LabelMap -> LabelMap CmmStatics -> Maybe CmmStatics
forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
mapLookup KeyOf LabelMap
BlockId
blockid LabelMap CmmStatics
info_env of
       Maybe CmmStatics
Nothing   -> SDoc
empty
       Just (Statics CLabel
info_lbl [CmmStatic]
info) ->
           SectionType -> SDoc
pprAlignForSection SectionType
Text SDoc -> SDoc -> SDoc
$$
           [SDoc] -> SDoc
vcat ((CmmStatic -> SDoc) -> [CmmStatic] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map CmmStatic -> SDoc
pprData [CmmStatic]
info) SDoc -> SDoc -> SDoc
$$
           CLabel -> SDoc
pprLabel CLabel
info_lbl



pprDatas :: CmmStatics -> SDoc
-- See note [emit-time elimination of static indirections] in CLabel.
pprDatas :: CmmStatics -> SDoc
pprDatas (Statics CLabel
alias [CmmStaticLit (CmmLabel CLabel
lbl), CmmStaticLit CmmLit
ind, CmmStatic
_, CmmStatic
_])
  | CLabel
lbl CLabel -> CLabel -> Bool
forall a. Eq a => a -> a -> Bool
== CLabel
mkIndStaticInfoLabel
  , let labelInd :: CmmLit -> Maybe CLabel
labelInd (CmmLabelOff CLabel
l Int
_) = CLabel -> Maybe CLabel
forall a. a -> Maybe a
Just CLabel
l
        labelInd (CmmLabel CLabel
l) = CLabel -> Maybe CLabel
forall a. a -> Maybe a
Just CLabel
l
        labelInd CmmLit
_ = Maybe CLabel
forall a. Maybe a
Nothing
  , Just CLabel
ind' <- CmmLit -> Maybe CLabel
labelInd CmmLit
ind
  , CLabel
alias CLabel -> CLabel -> Bool
`mayRedirectTo` CLabel
ind'
  = CLabel -> SDoc
pprGloblDecl CLabel
alias
    SDoc -> SDoc -> SDoc
$$ String -> SDoc
text String
".equiv" SDoc -> SDoc -> SDoc
<+> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
alias SDoc -> SDoc -> SDoc
<> SDoc
comma SDoc -> SDoc -> SDoc
<> CmmLit -> SDoc
forall a. Outputable a => a -> SDoc
ppr (CLabel -> CmmLit
CmmLabel CLabel
ind')
pprDatas (Statics CLabel
lbl [CmmStatic]
dats) = [SDoc] -> SDoc
vcat (CLabel -> SDoc
pprLabel CLabel
lbl SDoc -> [SDoc] -> [SDoc]
forall a. a -> [a] -> [a]
: (CmmStatic -> SDoc) -> [CmmStatic] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map CmmStatic -> SDoc
pprData [CmmStatic]
dats)

pprData :: CmmStatic -> SDoc
pprData :: CmmStatic -> SDoc
pprData (CmmString ByteString
str)          = ByteString -> SDoc
pprBytes ByteString
str
pprData (CmmUninitialised Int
bytes) = String -> SDoc
text String
".space " SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
bytes
pprData (CmmStaticLit CmmLit
lit)       = CmmLit -> SDoc
pprDataItem CmmLit
lit

pprGloblDecl :: CLabel -> SDoc
pprGloblDecl :: CLabel -> SDoc
pprGloblDecl CLabel
lbl
  | Bool -> Bool
not (CLabel -> Bool
externallyVisibleCLabel CLabel
lbl) = SDoc
empty
  | Bool
otherwise = String -> SDoc
text String
".globl " SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
lbl

pprTypeAndSizeDecl :: CLabel -> SDoc
pprTypeAndSizeDecl :: CLabel -> SDoc
pprTypeAndSizeDecl CLabel
lbl
  = (Platform -> SDoc) -> SDoc
sdocWithPlatform ((Platform -> SDoc) -> SDoc) -> (Platform -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \Platform
platform ->
    if Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSLinux Bool -> Bool -> Bool
&& CLabel -> Bool
externallyVisibleCLabel CLabel
lbl
    then String -> SDoc
text String
".type " SDoc -> SDoc -> SDoc
<>
         CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
", @object"
    else SDoc
empty

pprLabel :: CLabel -> SDoc
pprLabel :: CLabel -> SDoc
pprLabel CLabel
lbl = CLabel -> SDoc
pprGloblDecl CLabel
lbl
            SDoc -> SDoc -> SDoc
$$ CLabel -> SDoc
pprTypeAndSizeDecl CLabel
lbl
            SDoc -> SDoc -> SDoc
$$ (CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
':')

-- -----------------------------------------------------------------------------
-- pprInstr: print an 'Instr'

instance Outputable Instr where
    ppr :: Instr -> SDoc
ppr Instr
instr = Instr -> SDoc
pprInstr Instr
instr


pprReg :: Reg -> SDoc

pprReg :: Reg -> SDoc
pprReg Reg
r
  = case Reg
r of
      RegReal    (RealRegSingle Int
i) -> Int -> SDoc
ppr_reg_no Int
i
      RegReal    (RealRegPair{})   -> String -> SDoc
forall a. String -> a
panic String
"PPC.pprReg: no reg pairs on this arch"
      RegVirtual (VirtualRegI  Unique
u)  -> String -> SDoc
text String
"%vI_"   SDoc -> SDoc -> SDoc
<> Unique -> SDoc
pprUniqueAlways Unique
u
      RegVirtual (VirtualRegHi Unique
u)  -> String -> SDoc
text String
"%vHi_"  SDoc -> SDoc -> SDoc
<> Unique -> SDoc
pprUniqueAlways Unique
u
      RegVirtual (VirtualRegF  Unique
u)  -> String -> SDoc
text String
"%vF_"   SDoc -> SDoc -> SDoc
<> Unique -> SDoc
pprUniqueAlways Unique
u
      RegVirtual (VirtualRegD  Unique
u)  -> String -> SDoc
text String
"%vD_"   SDoc -> SDoc -> SDoc
<> Unique -> SDoc
pprUniqueAlways Unique
u

  where
    ppr_reg_no :: Int -> SDoc
    ppr_reg_no :: Int -> SDoc
ppr_reg_no Int
i
         | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
31   = Int -> SDoc
int Int
i      -- GPRs
         | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
63   = Int -> SDoc
int (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
32) -- FPRs
         | Bool
otherwise = String -> SDoc
text String
"very naughty powerpc register"



pprFormat :: Format -> SDoc
pprFormat :: Format -> SDoc
pprFormat Format
x
 = PtrString -> SDoc
ptext (case Format
x of
                Format
II8  -> String -> PtrString
sLit String
"b"
                Format
II16 -> String -> PtrString
sLit String
"h"
                Format
II32 -> String -> PtrString
sLit String
"w"
                Format
II64 -> String -> PtrString
sLit String
"d"
                Format
FF32 -> String -> PtrString
sLit String
"fs"
                Format
FF64 -> String -> PtrString
sLit String
"fd")


pprCond :: Cond -> SDoc
pprCond :: Cond -> SDoc
pprCond Cond
c
 = PtrString -> SDoc
ptext (case Cond
c of {
                Cond
ALWAYS  -> String -> PtrString
sLit String
"";
                Cond
EQQ     -> String -> PtrString
sLit String
"eq";  Cond
NE    -> String -> PtrString
sLit String
"ne";
                Cond
LTT     -> String -> PtrString
sLit String
"lt";  Cond
GE    -> String -> PtrString
sLit String
"ge";
                Cond
GTT     -> String -> PtrString
sLit String
"gt";  Cond
LE    -> String -> PtrString
sLit String
"le";
                Cond
LU      -> String -> PtrString
sLit String
"lt";  Cond
GEU   -> String -> PtrString
sLit String
"ge";
                Cond
GU      -> String -> PtrString
sLit String
"gt";  Cond
LEU   -> String -> PtrString
sLit String
"le"; })


pprImm :: Imm -> SDoc

pprImm :: Imm -> SDoc
pprImm (ImmInt Int
i)     = Int -> SDoc
int Int
i
pprImm (ImmInteger Integer
i) = Integer -> SDoc
integer Integer
i
pprImm (ImmCLbl CLabel
l)    = CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
l
pprImm (ImmIndex CLabel
l Int
i) = CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
l SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'+' SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
i
pprImm (ImmLit SDoc
s)     = SDoc
s

pprImm (ImmFloat Rational
_)  = String -> SDoc
text String
"naughty float immediate"
pprImm (ImmDouble Rational
_) = String -> SDoc
text String
"naughty double immediate"

pprImm (ImmConstantSum Imm
a Imm
b) = Imm -> SDoc
pprImm Imm
a SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'+' SDoc -> SDoc -> SDoc
<> Imm -> SDoc
pprImm Imm
b
pprImm (ImmConstantDiff Imm
a Imm
b) = Imm -> SDoc
pprImm Imm
a SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'-'
                   SDoc -> SDoc -> SDoc
<> SDoc
lparen SDoc -> SDoc -> SDoc
<> Imm -> SDoc
pprImm Imm
b SDoc -> SDoc -> SDoc
<> SDoc
rparen

pprImm (LO (ImmInt Int
i))     = Imm -> SDoc
pprImm (Imm -> Imm
LO (Integer -> Imm
ImmInteger (Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
i)))
pprImm (LO (ImmInteger Integer
i)) = Imm -> SDoc
pprImm (Integer -> Imm
ImmInteger (Int16 -> Integer
forall a. Integral a => a -> Integer
toInteger Int16
lo16))
  where
    lo16 :: Int16
lo16 = Integer -> Int16
forall a. Num a => Integer -> a
fromInteger (Integer
i Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
.&. Integer
0xffff) :: Int16

pprImm (LO Imm
i)
  = Imm -> SDoc
pprImm Imm
i SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"@l"

pprImm (HI Imm
i)
  = Imm -> SDoc
pprImm Imm
i SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"@h"

pprImm (HA (ImmInt Int
i))     = Imm -> SDoc
pprImm (Imm -> Imm
HA (Integer -> Imm
ImmInteger (Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
i)))
pprImm (HA (ImmInteger Integer
i)) = Imm -> SDoc
pprImm (Integer -> Imm
ImmInteger Integer
ha16)
  where
    ha16 :: Integer
ha16 = if Integer
lo16 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
0x8000 then Integer
hi16Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
1 else Integer
hi16
    hi16 :: Integer
hi16 = (Integer
i Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
16)
    lo16 :: Integer
lo16 = Integer
i Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
.&. Integer
0xffff

pprImm (HA Imm
i)
  = Imm -> SDoc
pprImm Imm
i SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"@ha"

pprImm (HIGHERA Imm
i)
  = Imm -> SDoc
pprImm Imm
i SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"@highera"

pprImm (HIGHESTA Imm
i)
  = Imm -> SDoc
pprImm Imm
i SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"@highesta"


pprAddr :: AddrMode -> SDoc
pprAddr :: AddrMode -> SDoc
pprAddr (AddrRegReg Reg
r1 Reg
r2)
  = Reg -> SDoc
pprReg Reg
r1 SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
',' SDoc -> SDoc -> SDoc
<+> Reg -> SDoc
pprReg Reg
r2
pprAddr (AddrRegImm Reg
r1 (ImmInt Int
i))
  = [SDoc] -> SDoc
hcat [ Int -> SDoc
int Int
i, Char -> SDoc
char Char
'(', Reg -> SDoc
pprReg Reg
r1, Char -> SDoc
char Char
')' ]
pprAddr (AddrRegImm Reg
r1 (ImmInteger Integer
i))
  = [SDoc] -> SDoc
hcat [ Integer -> SDoc
integer Integer
i, Char -> SDoc
char Char
'(', Reg -> SDoc
pprReg Reg
r1, Char -> SDoc
char Char
')' ]
pprAddr (AddrRegImm Reg
r1 Imm
imm)
  = [SDoc] -> SDoc
hcat [ Imm -> SDoc
pprImm Imm
imm, Char -> SDoc
char Char
'(', Reg -> SDoc
pprReg Reg
r1, Char -> SDoc
char Char
')' ]


pprSectionAlign :: Section -> SDoc
pprSectionAlign :: Section -> SDoc
pprSectionAlign sec :: Section
sec@(Section SectionType
seg CLabel
_) =
 (Platform -> SDoc) -> SDoc
sdocWithPlatform ((Platform -> SDoc) -> SDoc) -> (Platform -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \Platform
platform ->
   Platform -> Section -> SDoc
pprSectionHeader Platform
platform Section
sec SDoc -> SDoc -> SDoc
$$
   SectionType -> SDoc
pprAlignForSection SectionType
seg

-- | Print appropriate alignment for the given section type.
pprAlignForSection :: SectionType -> SDoc
pprAlignForSection :: SectionType -> SDoc
pprAlignForSection SectionType
seg =
 (Platform -> SDoc) -> SDoc
sdocWithPlatform ((Platform -> SDoc) -> SDoc) -> (Platform -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \Platform
platform ->
 let ppc64 :: Bool
ppc64    = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Platform -> Bool
target32Bit Platform
platform
 in PtrString -> SDoc
ptext (PtrString -> SDoc) -> PtrString -> SDoc
forall a b. (a -> b) -> a -> b
$ case SectionType
seg of
       SectionType
Text              -> String -> PtrString
sLit String
".align 2"
       SectionType
Data
        | Bool
ppc64          -> String -> PtrString
sLit String
".align 3"
        | Bool
otherwise      -> String -> PtrString
sLit String
".align 2"
       SectionType
ReadOnlyData
        | Bool
ppc64          -> String -> PtrString
sLit String
".align 3"
        | Bool
otherwise      -> String -> PtrString
sLit String
".align 2"
       SectionType
RelocatableReadOnlyData
        | Bool
ppc64          -> String -> PtrString
sLit String
".align 3"
        | Bool
otherwise      -> String -> PtrString
sLit String
".align 2"
       SectionType
UninitialisedData
        | Bool
ppc64          -> String -> PtrString
sLit String
".align 3"
        | Bool
otherwise      -> String -> PtrString
sLit String
".align 2"
       SectionType
ReadOnlyData16    -> String -> PtrString
sLit String
".align 4"
       -- TODO: This is copied from the ReadOnlyData case, but it can likely be
       -- made more efficient.
       SectionType
CString
        | Bool
ppc64          -> String -> PtrString
sLit String
".align 3"
        | Bool
otherwise      -> String -> PtrString
sLit String
".align 2"
       OtherSection String
_    -> String -> PtrString
forall a. String -> a
panic String
"PprMach.pprSectionAlign: unknown section"

pprDataItem :: CmmLit -> SDoc
pprDataItem :: CmmLit -> SDoc
pprDataItem CmmLit
lit
  = (DynFlags -> SDoc) -> SDoc
sdocWithDynFlags ((DynFlags -> SDoc) -> SDoc) -> (DynFlags -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \DynFlags
dflags ->
    [SDoc] -> SDoc
vcat (Format -> CmmLit -> DynFlags -> [SDoc]
ppr_item (CmmType -> Format
cmmTypeFormat (CmmType -> Format) -> CmmType -> Format
forall a b. (a -> b) -> a -> b
$ DynFlags -> CmmLit -> CmmType
cmmLitType DynFlags
dflags CmmLit
lit) CmmLit
lit DynFlags
dflags)
    where
        imm :: Imm
imm = CmmLit -> Imm
litToImm CmmLit
lit
        archPPC_64 :: DynFlags -> Bool
archPPC_64 DynFlags
dflags = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Platform -> Bool
target32Bit (Platform -> Bool) -> Platform -> Bool
forall a b. (a -> b) -> a -> b
$ DynFlags -> Platform
targetPlatform DynFlags
dflags

        ppr_item :: Format -> CmmLit -> DynFlags -> [SDoc]
ppr_item Format
II8   CmmLit
_ DynFlags
_ = [String -> SDoc
text String
"\t.byte\t" SDoc -> SDoc -> SDoc
<> Imm -> SDoc
pprImm Imm
imm]

        ppr_item Format
II32  CmmLit
_ DynFlags
_ = [String -> SDoc
text String
"\t.long\t" SDoc -> SDoc -> SDoc
<> Imm -> SDoc
pprImm Imm
imm]

        ppr_item Format
II64 CmmLit
_ DynFlags
dflags
           | DynFlags -> Bool
archPPC_64 DynFlags
dflags = [String -> SDoc
text String
"\t.quad\t" SDoc -> SDoc -> SDoc
<> Imm -> SDoc
pprImm Imm
imm]


        ppr_item Format
FF32 (CmmFloat Rational
r Width
_) DynFlags
_
           = let bs :: [Int]
bs = Float -> [Int]
floatToBytes (Rational -> Float
forall a. Fractional a => Rational -> a
fromRational Rational
r)
             in  (Int -> SDoc) -> [Int] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (\Int
b -> String -> SDoc
text String
"\t.byte\t" SDoc -> SDoc -> SDoc
<> Imm -> SDoc
pprImm (Int -> Imm
ImmInt Int
b)) [Int]
bs

        ppr_item Format
FF64 (CmmFloat Rational
r Width
_) DynFlags
_
           = let bs :: [Int]
bs = Double -> [Int]
doubleToBytes (Rational -> Double
forall a. Fractional a => Rational -> a
fromRational Rational
r)
             in  (Int -> SDoc) -> [Int] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (\Int
b -> String -> SDoc
text String
"\t.byte\t" SDoc -> SDoc -> SDoc
<> Imm -> SDoc
pprImm (Int -> Imm
ImmInt Int
b)) [Int]
bs

        ppr_item Format
II16 CmmLit
_ DynFlags
_      = [String -> SDoc
text String
"\t.short\t" SDoc -> SDoc -> SDoc
<> Imm -> SDoc
pprImm Imm
imm]

        ppr_item Format
II64 (CmmInt Integer
x Width
_) DynFlags
dflags
           | Bool -> Bool
not(DynFlags -> Bool
archPPC_64 DynFlags
dflags) =
                [String -> SDoc
text String
"\t.long\t"
                    SDoc -> SDoc -> SDoc
<> Int -> SDoc
int (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
                        (Integer -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
x Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
32) :: Word32)),
                 String -> SDoc
text String
"\t.long\t"
                    SDoc -> SDoc -> SDoc
<> Int -> SDoc
int (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x :: Word32))]

        ppr_item Format
_ CmmLit
_ DynFlags
_
                = String -> [SDoc]
forall a. String -> a
panic String
"PPC.Ppr.pprDataItem: no match"


pprInstr :: Instr -> SDoc

pprInstr :: Instr -> SDoc
pprInstr (COMMENT FastString
_) = SDoc
empty -- nuke 'em
{-
pprInstr (COMMENT s) =
     if platformOS platform == OSLinux
     then text "# " <> ftext s
     else text "; " <> ftext s
-}
pprInstr (DELTA Int
d)
   = Instr -> SDoc
pprInstr (FastString -> Instr
COMMENT (String -> FastString
mkFastString (String
"\tdelta = " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
d)))

pprInstr (NEWBLOCK BlockId
_)
   = String -> SDoc
forall a. String -> a
panic String
"PprMach.pprInstr: NEWBLOCK"

pprInstr (LDATA Section
_ CmmStatics
_)
   = String -> SDoc
forall a. String -> a
panic String
"PprMach.pprInstr: LDATA"

{-
pprInstr (SPILL reg slot)
   = hcat [
           text "\tSPILL",
        char '\t',
        pprReg reg,
        comma,
        text "SLOT" <> parens (int slot)]

pprInstr (RELOAD slot reg)
   = hcat [
           text "\tRELOAD",
        char '\t',
        text "SLOT" <> parens (int slot),
        comma,
        pprReg reg]
-}

pprInstr (LD Format
fmt Reg
reg AddrMode
addr) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"l",
        PtrString -> SDoc
ptext (case Format
fmt of
            Format
II8  -> String -> PtrString
sLit String
"bz"
            Format
II16 -> String -> PtrString
sLit String
"hz"
            Format
II32 -> String -> PtrString
sLit String
"wz"
            Format
II64 -> String -> PtrString
sLit String
"d"
            Format
FF32 -> String -> PtrString
sLit String
"fs"
            Format
FF64 -> String -> PtrString
sLit String
"fd"
            ),
        case AddrMode
addr of AddrRegImm Reg
_ Imm
_ -> SDoc
empty
                     AddrRegReg Reg
_ Reg
_ -> Char -> SDoc
char Char
'x',
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg,
        String -> SDoc
text String
", ",
        AddrMode -> SDoc
pprAddr AddrMode
addr
    ]

pprInstr (LDFAR Format
fmt Reg
reg (AddrRegImm Reg
source Imm
off)) =
   (Platform -> SDoc) -> SDoc
sdocWithPlatform ((Platform -> SDoc) -> SDoc) -> (Platform -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \Platform
platform -> [SDoc] -> SDoc
vcat [
         Instr -> SDoc
pprInstr (Reg -> Reg -> Imm -> Instr
ADDIS (Platform -> Reg
tmpReg Platform
platform) Reg
source (Imm -> Imm
HA Imm
off)),
         Instr -> SDoc
pprInstr (Format -> Reg -> AddrMode -> Instr
LD Format
fmt Reg
reg (Reg -> Imm -> AddrMode
AddrRegImm (Platform -> Reg
tmpReg Platform
platform) (Imm -> Imm
LO Imm
off)))
    ]
pprInstr (LDFAR Format
_ Reg
_ AddrMode
_) =
   String -> SDoc
forall a. String -> a
panic String
"PPC.Ppr.pprInstr LDFAR: no match"

pprInstr (LDR Format
fmt Reg
reg1 AddrMode
addr) = [SDoc] -> SDoc
hcat [
  String -> SDoc
text String
"\tl",
  case Format
fmt of
    Format
II32 -> Char -> SDoc
char Char
'w'
    Format
II64 -> Char -> SDoc
char Char
'd'
    Format
_    -> String -> SDoc
forall a. String -> a
panic String
"PPC.Ppr.Instr LDR: no match",
  String -> SDoc
text String
"arx\t",
  Reg -> SDoc
pprReg Reg
reg1,
  String -> SDoc
text String
", ",
  AddrMode -> SDoc
pprAddr AddrMode
addr
  ]

pprInstr (LA Format
fmt Reg
reg AddrMode
addr) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"l",
        PtrString -> SDoc
ptext (case Format
fmt of
            Format
II8  -> String -> PtrString
sLit String
"ba"
            Format
II16 -> String -> PtrString
sLit String
"ha"
            Format
II32 -> String -> PtrString
sLit String
"wa"
            Format
II64 -> String -> PtrString
sLit String
"d"
            Format
FF32 -> String -> PtrString
sLit String
"fs"
            Format
FF64 -> String -> PtrString
sLit String
"fd"
            ),
        case AddrMode
addr of AddrRegImm Reg
_ Imm
_ -> SDoc
empty
                     AddrRegReg Reg
_ Reg
_ -> Char -> SDoc
char Char
'x',
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg,
        String -> SDoc
text String
", ",
        AddrMode -> SDoc
pprAddr AddrMode
addr
    ]
pprInstr (ST Format
fmt Reg
reg AddrMode
addr) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"st",
        Format -> SDoc
pprFormat Format
fmt,
        case AddrMode
addr of AddrRegImm Reg
_ Imm
_ -> SDoc
empty
                     AddrRegReg Reg
_ Reg
_ -> Char -> SDoc
char Char
'x',
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg,
        String -> SDoc
text String
", ",
        AddrMode -> SDoc
pprAddr AddrMode
addr
    ]
pprInstr (STFAR Format
fmt Reg
reg (AddrRegImm Reg
source Imm
off)) =
   (Platform -> SDoc) -> SDoc
sdocWithPlatform ((Platform -> SDoc) -> SDoc) -> (Platform -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \Platform
platform -> [SDoc] -> SDoc
vcat [
         Instr -> SDoc
pprInstr (Reg -> Reg -> Imm -> Instr
ADDIS (Platform -> Reg
tmpReg Platform
platform) Reg
source (Imm -> Imm
HA Imm
off)),
         Instr -> SDoc
pprInstr (Format -> Reg -> AddrMode -> Instr
ST Format
fmt Reg
reg (Reg -> Imm -> AddrMode
AddrRegImm (Platform -> Reg
tmpReg Platform
platform) (Imm -> Imm
LO Imm
off)))
    ]
pprInstr (STFAR Format
_ Reg
_ AddrMode
_) =
   String -> SDoc
forall a. String -> a
panic String
"PPC.Ppr.pprInstr STFAR: no match"
pprInstr (STU Format
fmt Reg
reg AddrMode
addr) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"st",
        Format -> SDoc
pprFormat Format
fmt,
        Char -> SDoc
char Char
'u',
        case AddrMode
addr of AddrRegImm Reg
_ Imm
_ -> SDoc
empty
                     AddrRegReg Reg
_ Reg
_ -> Char -> SDoc
char Char
'x',
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg,
        String -> SDoc
text String
", ",
        AddrMode -> SDoc
pprAddr AddrMode
addr
    ]
pprInstr (STC Format
fmt Reg
reg1 AddrMode
addr) = [SDoc] -> SDoc
hcat [
  String -> SDoc
text String
"\tst",
  case Format
fmt of
    Format
II32 -> Char -> SDoc
char Char
'w'
    Format
II64 -> Char -> SDoc
char Char
'd'
    Format
_    -> String -> SDoc
forall a. String -> a
panic String
"PPC.Ppr.Instr STC: no match",
  String -> SDoc
text String
"cx.\t",
  Reg -> SDoc
pprReg Reg
reg1,
  String -> SDoc
text String
", ",
  AddrMode -> SDoc
pprAddr AddrMode
addr
  ]
pprInstr (LIS Reg
reg Imm
imm) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"lis",
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg,
        String -> SDoc
text String
", ",
        Imm -> SDoc
pprImm Imm
imm
    ]
pprInstr (LI Reg
reg Imm
imm) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"li",
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg,
        String -> SDoc
text String
", ",
        Imm -> SDoc
pprImm Imm
imm
    ]
pprInstr (MR Reg
reg1 Reg
reg2)
    | Reg
reg1 Reg -> Reg -> Bool
forall a. Eq a => a -> a -> Bool
== Reg
reg2 = SDoc
empty
    | Bool
otherwise = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        (Platform -> SDoc) -> SDoc
sdocWithPlatform ((Platform -> SDoc) -> SDoc) -> (Platform -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \Platform
platform ->
        case Platform -> Reg -> RegClass
targetClassOfReg Platform
platform Reg
reg1 of
            RegClass
RcInteger -> String -> SDoc
text String
"mr"
            RegClass
_ -> String -> SDoc
text String
"fmr",
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2
    ]
pprInstr (CMP Format
fmt Reg
reg RI
ri) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        SDoc
op,
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg,
        String -> SDoc
text String
", ",
        RI -> SDoc
pprRI RI
ri
    ]
    where
        op :: SDoc
op = [SDoc] -> SDoc
hcat [
                String -> SDoc
text String
"cmp",
                Format -> SDoc
pprFormat Format
fmt,
                case RI
ri of
                    RIReg Reg
_ -> SDoc
empty
                    RIImm Imm
_ -> Char -> SDoc
char Char
'i'
            ]
pprInstr (CMPL Format
fmt Reg
reg RI
ri) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        SDoc
op,
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg,
        String -> SDoc
text String
", ",
        RI -> SDoc
pprRI RI
ri
    ]
    where
        op :: SDoc
op = [SDoc] -> SDoc
hcat [
                String -> SDoc
text String
"cmpl",
                Format -> SDoc
pprFormat Format
fmt,
                case RI
ri of
                    RIReg Reg
_ -> SDoc
empty
                    RIImm Imm
_ -> Char -> SDoc
char Char
'i'
            ]
pprInstr (BCC Cond
cond BlockId
blockid Maybe Bool
prediction) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"b",
        Cond -> SDoc
pprCond Cond
cond,
        Maybe Bool -> SDoc
pprPrediction Maybe Bool
prediction,
        Char -> SDoc
char Char
'\t',
        CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
lbl
    ]
    where lbl :: CLabel
lbl = Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
blockid)
          pprPrediction :: Maybe Bool -> SDoc
pprPrediction Maybe Bool
p = case Maybe Bool
p of
            Maybe Bool
Nothing    -> SDoc
empty
            Just Bool
True  -> Char -> SDoc
char Char
'+'
            Just Bool
False -> Char -> SDoc
char Char
'-'

pprInstr (BCCFAR Cond
cond BlockId
blockid Maybe Bool
prediction) = [SDoc] -> SDoc
vcat [
        [SDoc] -> SDoc
hcat [
            String -> SDoc
text String
"\tb",
            Cond -> SDoc
pprCond (Cond -> Cond
condNegate Cond
cond),
            SDoc
neg_prediction,
            String -> SDoc
text String
"\t$+8"
        ],
        [SDoc] -> SDoc
hcat [
            String -> SDoc
text String
"\tb\t",
            CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
lbl
        ]
    ]
    where lbl :: CLabel
lbl = Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
blockid)
          neg_prediction :: SDoc
neg_prediction = case Maybe Bool
prediction of
            Maybe Bool
Nothing    -> SDoc
empty
            Just Bool
True  -> Char -> SDoc
char Char
'-'
            Just Bool
False -> Char -> SDoc
char Char
'+'

pprInstr (JMP CLabel
lbl [Reg]
_)
  -- We never jump to ForeignLabels; if we ever do, c.f. handling for "BL"
  | CLabel -> Bool
isForeignLabel CLabel
lbl = String -> SDoc
forall a. String -> a
panic String
"PPC.Ppr.pprInstr: JMP to ForeignLabel"
  | Bool
otherwise =
    [SDoc] -> SDoc
hcat [ -- an alias for b that takes a CLabel
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"b",
        Char -> SDoc
char Char
'\t',
        CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
lbl
    ]

pprInstr (MTCTR Reg
reg) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"mtctr",
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg
    ]
pprInstr (BCTR [Maybe BlockId]
_ Maybe CLabel
_ [Reg]
_) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"bctr"
    ]
pprInstr (BL CLabel
lbl [Reg]
_) = do
    (Platform -> SDoc) -> SDoc
sdocWithPlatform ((Platform -> SDoc) -> SDoc) -> (Platform -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \Platform
platform -> case Platform -> OS
platformOS Platform
platform of
        OS
OSAIX ->
          -- On AIX, "printf" denotes a function-descriptor (for use
          -- by function pointers), whereas the actual entry-code
          -- address is denoted by the dot-prefixed ".printf" label.
          -- Moreover, the PPC NCG only ever emits a BL instruction
          -- for calling C ABI functions. Most of the time these calls
          -- originate from FFI imports and have a 'ForeignLabel',
          -- but when profiling the codegen inserts calls via
          -- 'emitRtsCallGen' which are 'CmmLabel's even though
          -- they'd technically be more like 'ForeignLabel's.
          [SDoc] -> SDoc
hcat [
            String -> SDoc
text String
"\tbl\t.",
            CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
lbl
          ]
        OS
_ ->
          [SDoc] -> SDoc
hcat [
            String -> SDoc
text String
"\tbl\t",
            CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
lbl
          ]
pprInstr (BCTRL [Reg]
_) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"bctrl"
    ]
pprInstr (ADD Reg
reg1 Reg
reg2 RI
ri) = PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic (String -> PtrString
sLit String
"add") Reg
reg1 Reg
reg2 RI
ri
pprInstr (ADDIS Reg
reg1 Reg
reg2 Imm
imm) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"addis",
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2,
        String -> SDoc
text String
", ",
        Imm -> SDoc
pprImm Imm
imm
    ]

pprInstr (ADDO Reg
reg1 Reg
reg2 Reg
reg3) = PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic (String -> PtrString
sLit String
"addo") Reg
reg1 Reg
reg2 (Reg -> RI
RIReg Reg
reg3)
pprInstr (ADDC Reg
reg1 Reg
reg2 Reg
reg3) = PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic (String -> PtrString
sLit String
"addc") Reg
reg1 Reg
reg2 (Reg -> RI
RIReg Reg
reg3)
pprInstr (ADDE Reg
reg1 Reg
reg2 Reg
reg3) = PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic (String -> PtrString
sLit String
"adde") Reg
reg1 Reg
reg2 (Reg -> RI
RIReg Reg
reg3)
pprInstr (ADDZE Reg
reg1 Reg
reg2) = PtrString -> Reg -> Reg -> SDoc
pprUnary (String -> PtrString
sLit String
"addze") Reg
reg1 Reg
reg2
pprInstr (SUBF Reg
reg1 Reg
reg2 Reg
reg3) = PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic (String -> PtrString
sLit String
"subf") Reg
reg1 Reg
reg2 (Reg -> RI
RIReg Reg
reg3)
pprInstr (SUBFO Reg
reg1 Reg
reg2 Reg
reg3) = PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic (String -> PtrString
sLit String
"subfo") Reg
reg1 Reg
reg2 (Reg -> RI
RIReg Reg
reg3)
pprInstr (SUBFC Reg
reg1 Reg
reg2 RI
ri) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"subf",
        case RI
ri of
            RIReg Reg
_ -> SDoc
empty
            RIImm Imm
_ -> Char -> SDoc
char Char
'i',
        String -> SDoc
text String
"c\t",
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2,
        String -> SDoc
text String
", ",
        RI -> SDoc
pprRI RI
ri
    ]
pprInstr (SUBFE Reg
reg1 Reg
reg2 Reg
reg3) = PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic (String -> PtrString
sLit String
"subfe") Reg
reg1 Reg
reg2 (Reg -> RI
RIReg Reg
reg3)
pprInstr (MULL Format
fmt Reg
reg1 Reg
reg2 RI
ri) = Format -> Reg -> Reg -> RI -> SDoc
pprMul Format
fmt Reg
reg1 Reg
reg2 RI
ri
pprInstr (MULLO Format
fmt Reg
reg1 Reg
reg2 Reg
reg3) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"mull",
        case Format
fmt of
          Format
II32 -> Char -> SDoc
char Char
'w'
          Format
II64 -> Char -> SDoc
char Char
'd'
          Format
_    -> String -> SDoc
forall a. String -> a
panic String
"PPC: illegal format",
        String -> SDoc
text String
"o\t",
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg3
    ]
pprInstr (MFOV Format
fmt Reg
reg) = [SDoc] -> SDoc
vcat [
        [SDoc] -> SDoc
hcat [
            Char -> SDoc
char Char
'\t',
            String -> SDoc
text String
"mfxer",
            Char -> SDoc
char Char
'\t',
            Reg -> SDoc
pprReg Reg
reg
            ],
        [SDoc] -> SDoc
hcat [
            Char -> SDoc
char Char
'\t',
            String -> SDoc
text String
"extr",
            case Format
fmt of
              Format
II32 -> Char -> SDoc
char Char
'w'
              Format
II64 -> Char -> SDoc
char Char
'd'
              Format
_    -> String -> SDoc
forall a. String -> a
panic String
"PPC: illegal format",
            String -> SDoc
text String
"i\t",
            Reg -> SDoc
pprReg Reg
reg,
            String -> SDoc
text String
", ",
            Reg -> SDoc
pprReg Reg
reg,
            String -> SDoc
text String
", 1, ",
            case Format
fmt of
              Format
II32 -> String -> SDoc
text String
"1"
              Format
II64 -> String -> SDoc
text String
"33"
              Format
_    -> String -> SDoc
forall a. String -> a
panic String
"PPC: illegal format"
            ]
        ]

pprInstr (MULHU Format
fmt Reg
reg1 Reg
reg2 Reg
reg3) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"mulh",
        case Format
fmt of
          Format
II32 -> Char -> SDoc
char Char
'w'
          Format
II64 -> Char -> SDoc
char Char
'd'
          Format
_    -> String -> SDoc
forall a. String -> a
panic String
"PPC: illegal format",
        String -> SDoc
text String
"u\t",
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg3
    ]

pprInstr (DIV Format
fmt Bool
sgn Reg
reg1 Reg
reg2 Reg
reg3) = Format -> Bool -> Reg -> Reg -> Reg -> SDoc
pprDiv Format
fmt Bool
sgn Reg
reg1 Reg
reg2 Reg
reg3

        -- for some reason, "andi" doesn't exist.
        -- we'll use "andi." instead.
pprInstr (AND Reg
reg1 Reg
reg2 (RIImm Imm
imm)) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"andi.",
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2,
        String -> SDoc
text String
", ",
        Imm -> SDoc
pprImm Imm
imm
    ]
pprInstr (AND Reg
reg1 Reg
reg2 RI
ri) = PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic (String -> PtrString
sLit String
"and") Reg
reg1 Reg
reg2 RI
ri
pprInstr (ANDC Reg
reg1 Reg
reg2 Reg
reg3) = PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic (String -> PtrString
sLit String
"andc") Reg
reg1 Reg
reg2 (Reg -> RI
RIReg Reg
reg3)
pprInstr (NAND Reg
reg1 Reg
reg2 Reg
reg3) = PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic (String -> PtrString
sLit String
"nand") Reg
reg1 Reg
reg2 (Reg -> RI
RIReg Reg
reg3)

pprInstr (OR Reg
reg1 Reg
reg2 RI
ri) = PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic (String -> PtrString
sLit String
"or") Reg
reg1 Reg
reg2 RI
ri
pprInstr (XOR Reg
reg1 Reg
reg2 RI
ri) = PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic (String -> PtrString
sLit String
"xor") Reg
reg1 Reg
reg2 RI
ri

pprInstr (ORIS Reg
reg1 Reg
reg2 Imm
imm) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"oris",
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2,
        String -> SDoc
text String
", ",
        Imm -> SDoc
pprImm Imm
imm
    ]

pprInstr (XORIS Reg
reg1 Reg
reg2 Imm
imm) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"xoris",
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2,
        String -> SDoc
text String
", ",
        Imm -> SDoc
pprImm Imm
imm
    ]

pprInstr (EXTS Format
fmt Reg
reg1 Reg
reg2) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"exts",
        Format -> SDoc
pprFormat Format
fmt,
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2
    ]
pprInstr (CNTLZ Format
fmt Reg
reg1 Reg
reg2) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"cntlz",
        case Format
fmt of
          Format
II32 -> Char -> SDoc
char Char
'w'
          Format
II64 -> Char -> SDoc
char Char
'd'
          Format
_    -> String -> SDoc
forall a. String -> a
panic String
"PPC: illegal format",
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2
    ]

pprInstr (NEG Reg
reg1 Reg
reg2) = PtrString -> Reg -> Reg -> SDoc
pprUnary (String -> PtrString
sLit String
"neg") Reg
reg1 Reg
reg2
pprInstr (NOT Reg
reg1 Reg
reg2) = PtrString -> Reg -> Reg -> SDoc
pprUnary (String -> PtrString
sLit String
"not") Reg
reg1 Reg
reg2

pprInstr (SR Format
II32 Reg
reg1 Reg
reg2 (RIImm (ImmInt Int
i))) | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0  Bool -> Bool -> Bool
|| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
31 =
    -- Handle the case where we are asked to shift a 32 bit register by
    -- less than zero or more than 31 bits. We convert this into a clear
    -- of the destination register.
    -- Fixes ticket https://gitlab.haskell.org/ghc/ghc/issues/5900
    Instr -> SDoc
pprInstr (Reg -> Reg -> RI -> Instr
XOR Reg
reg1 Reg
reg2 (Reg -> RI
RIReg Reg
reg2))

pprInstr (SL Format
II32 Reg
reg1 Reg
reg2 (RIImm (ImmInt Int
i))) | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0  Bool -> Bool -> Bool
|| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
31 =
    -- As above for SR, but for left shifts.
    -- Fixes ticket https://gitlab.haskell.org/ghc/ghc/issues/10870
    Instr -> SDoc
pprInstr (Reg -> Reg -> RI -> Instr
XOR Reg
reg1 Reg
reg2 (Reg -> RI
RIReg Reg
reg2))

pprInstr (SRA Format
II32 Reg
reg1 Reg
reg2 (RIImm (ImmInt Int
i))) | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
31 =
    -- PT: I don't know what to do for negative shift amounts:
    -- For now just panic.
    --
    -- For shift amounts greater than 31 set all bit to the
    -- value of the sign bit, this also what sraw does.
    Instr -> SDoc
pprInstr (Format -> Reg -> Reg -> RI -> Instr
SRA Format
II32 Reg
reg1 Reg
reg2 (Imm -> RI
RIImm (Int -> Imm
ImmInt Int
31)))

pprInstr (SL Format
fmt Reg
reg1 Reg
reg2 RI
ri) =
         let op :: String
op = case Format
fmt of
                       Format
II32 -> String
"slw"
                       Format
II64 -> String
"sld"
                       Format
_    -> String -> String
forall a. String -> a
panic String
"PPC.Ppr.pprInstr: shift illegal size"
         in PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic (String -> PtrString
sLit String
op) Reg
reg1 Reg
reg2 (Format -> RI -> RI
limitShiftRI Format
fmt RI
ri)

pprInstr (SR Format
fmt Reg
reg1 Reg
reg2 RI
ri) =
         let op :: String
op = case Format
fmt of
                       Format
II32 -> String
"srw"
                       Format
II64 -> String
"srd"
                       Format
_    -> String -> String
forall a. String -> a
panic String
"PPC.Ppr.pprInstr: shift illegal size"
         in PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic (String -> PtrString
sLit String
op) Reg
reg1 Reg
reg2 (Format -> RI -> RI
limitShiftRI Format
fmt RI
ri)

pprInstr (SRA Format
fmt Reg
reg1 Reg
reg2 RI
ri) =
         let op :: String
op = case Format
fmt of
                       Format
II32 -> String
"sraw"
                       Format
II64 -> String
"srad"
                       Format
_    -> String -> String
forall a. String -> a
panic String
"PPC.Ppr.pprInstr: shift illegal size"
         in PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic (String -> PtrString
sLit String
op) Reg
reg1 Reg
reg2 (Format -> RI -> RI
limitShiftRI Format
fmt RI
ri)

pprInstr (RLWINM Reg
reg1 Reg
reg2 Int
sh Int
mb Int
me) = [SDoc] -> SDoc
hcat [
        String -> SDoc
text String
"\trlwinm\t",
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2,
        String -> SDoc
text String
", ",
        Int -> SDoc
int Int
sh,
        String -> SDoc
text String
", ",
        Int -> SDoc
int Int
mb,
        String -> SDoc
text String
", ",
        Int -> SDoc
int Int
me
    ]

pprInstr (CLRLI Format
fmt Reg
reg1 Reg
reg2 Int
n) = [SDoc] -> SDoc
hcat [
        String -> SDoc
text String
"\tclrl",
        Format -> SDoc
pprFormat Format
fmt,
        String -> SDoc
text String
"i ",
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2,
        String -> SDoc
text String
", ",
        Int -> SDoc
int Int
n
    ]
pprInstr (CLRRI Format
fmt Reg
reg1 Reg
reg2 Int
n) = [SDoc] -> SDoc
hcat [
        String -> SDoc
text String
"\tclrr",
        Format -> SDoc
pprFormat Format
fmt,
        String -> SDoc
text String
"i ",
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2,
        String -> SDoc
text String
", ",
        Int -> SDoc
int Int
n
    ]

pprInstr (FADD Format
fmt Reg
reg1 Reg
reg2 Reg
reg3) = PtrString -> Format -> Reg -> Reg -> Reg -> SDoc
pprBinaryF (String -> PtrString
sLit String
"fadd") Format
fmt Reg
reg1 Reg
reg2 Reg
reg3
pprInstr (FSUB Format
fmt Reg
reg1 Reg
reg2 Reg
reg3) = PtrString -> Format -> Reg -> Reg -> Reg -> SDoc
pprBinaryF (String -> PtrString
sLit String
"fsub") Format
fmt Reg
reg1 Reg
reg2 Reg
reg3
pprInstr (FMUL Format
fmt Reg
reg1 Reg
reg2 Reg
reg3) = PtrString -> Format -> Reg -> Reg -> Reg -> SDoc
pprBinaryF (String -> PtrString
sLit String
"fmul") Format
fmt Reg
reg1 Reg
reg2 Reg
reg3
pprInstr (FDIV Format
fmt Reg
reg1 Reg
reg2 Reg
reg3) = PtrString -> Format -> Reg -> Reg -> Reg -> SDoc
pprBinaryF (String -> PtrString
sLit String
"fdiv") Format
fmt Reg
reg1 Reg
reg2 Reg
reg3
pprInstr (FABS Reg
reg1 Reg
reg2) = PtrString -> Reg -> Reg -> SDoc
pprUnary (String -> PtrString
sLit String
"fabs") Reg
reg1 Reg
reg2
pprInstr (FNEG Reg
reg1 Reg
reg2) = PtrString -> Reg -> Reg -> SDoc
pprUnary (String -> PtrString
sLit String
"fneg") Reg
reg1 Reg
reg2

pprInstr (FCMP Reg
reg1 Reg
reg2) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"fcmpu\t0, ",
            -- Note: we're using fcmpu, not fcmpo
            -- The difference is with fcmpo, compare with NaN is an invalid operation.
            -- We don't handle invalid fp ops, so we don't care.
            -- Morever, we use `fcmpu 0, ...` rather than `fcmpu cr0, ...` for
            -- better portability since some non-GNU assembler (such as
            -- IBM's `as`) tend not to support the symbolic register name cr0.
            -- This matches the syntax that GCC seems to emit for PPC targets.
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2
    ]

pprInstr (FCTIWZ Reg
reg1 Reg
reg2) = PtrString -> Reg -> Reg -> SDoc
pprUnary (String -> PtrString
sLit String
"fctiwz") Reg
reg1 Reg
reg2
pprInstr (FCTIDZ Reg
reg1 Reg
reg2) = PtrString -> Reg -> Reg -> SDoc
pprUnary (String -> PtrString
sLit String
"fctidz") Reg
reg1 Reg
reg2
pprInstr (FCFID Reg
reg1 Reg
reg2) = PtrString -> Reg -> Reg -> SDoc
pprUnary (String -> PtrString
sLit String
"fcfid") Reg
reg1 Reg
reg2
pprInstr (FRSP Reg
reg1 Reg
reg2) = PtrString -> Reg -> Reg -> SDoc
pprUnary (String -> PtrString
sLit String
"frsp") Reg
reg1 Reg
reg2

pprInstr (CRNOR Int
dst Int
src1 Int
src2) = [SDoc] -> SDoc
hcat [
        String -> SDoc
text String
"\tcrnor\t",
        Int -> SDoc
int Int
dst,
        String -> SDoc
text String
", ",
        Int -> SDoc
int Int
src1,
        String -> SDoc
text String
", ",
        Int -> SDoc
int Int
src2
    ]

pprInstr (MFCR Reg
reg) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"mfcr",
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg
    ]

pprInstr (MFLR Reg
reg) = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"mflr",
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg
    ]

pprInstr (FETCHPC Reg
reg) = [SDoc] -> SDoc
vcat [
        String -> SDoc
text String
"\tbcl\t20,31,1f",
        [SDoc] -> SDoc
hcat [ String -> SDoc
text String
"1:\tmflr\t", Reg -> SDoc
pprReg Reg
reg ]
    ]

pprInstr Instr
HWSYNC = String -> SDoc
text String
"\tsync"

pprInstr Instr
ISYNC  = String -> SDoc
text String
"\tisync"

pprInstr Instr
LWSYNC = String -> SDoc
text String
"\tlwsync"

pprInstr Instr
NOP = String -> SDoc
text String
"\tnop"


pprLogic :: PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic :: PtrString -> Reg -> Reg -> RI -> SDoc
pprLogic PtrString
op Reg
reg1 Reg
reg2 RI
ri = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        PtrString -> SDoc
ptext PtrString
op,
        case RI
ri of
            RIReg Reg
_ -> SDoc
empty
            RIImm Imm
_ -> Char -> SDoc
char Char
'i',
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2,
        String -> SDoc
text String
", ",
        RI -> SDoc
pprRI RI
ri
    ]


pprMul :: Format -> Reg -> Reg -> RI -> SDoc
pprMul :: Format -> Reg -> Reg -> RI -> SDoc
pprMul Format
fmt Reg
reg1 Reg
reg2 RI
ri = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"mull",
        case RI
ri of
            RIReg Reg
_ -> case Format
fmt of
              Format
II32 -> Char -> SDoc
char Char
'w'
              Format
II64 -> Char -> SDoc
char Char
'd'
              Format
_    -> String -> SDoc
forall a. String -> a
panic String
"PPC: illegal format"
            RIImm Imm
_ -> Char -> SDoc
char Char
'i',
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2,
        String -> SDoc
text String
", ",
        RI -> SDoc
pprRI RI
ri
    ]


pprDiv :: Format -> Bool -> Reg -> Reg -> Reg -> SDoc
pprDiv :: Format -> Bool -> Reg -> Reg -> Reg -> SDoc
pprDiv Format
fmt Bool
sgn Reg
reg1 Reg
reg2 Reg
reg3 = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        String -> SDoc
text String
"div",
        case Format
fmt of
          Format
II32 -> Char -> SDoc
char Char
'w'
          Format
II64 -> Char -> SDoc
char Char
'd'
          Format
_    -> String -> SDoc
forall a. String -> a
panic String
"PPC: illegal format",
        if Bool
sgn then SDoc
empty else Char -> SDoc
char Char
'u',
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg3
    ]


pprUnary :: PtrString -> Reg -> Reg -> SDoc
pprUnary :: PtrString -> Reg -> Reg -> SDoc
pprUnary PtrString
op Reg
reg1 Reg
reg2 = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        PtrString -> SDoc
ptext PtrString
op,
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2
    ]


pprBinaryF :: PtrString -> Format -> Reg -> Reg -> Reg -> SDoc
pprBinaryF :: PtrString -> Format -> Reg -> Reg -> Reg -> SDoc
pprBinaryF PtrString
op Format
fmt Reg
reg1 Reg
reg2 Reg
reg3 = [SDoc] -> SDoc
hcat [
        Char -> SDoc
char Char
'\t',
        PtrString -> SDoc
ptext PtrString
op,
        Format -> SDoc
pprFFormat Format
fmt,
        Char -> SDoc
char Char
'\t',
        Reg -> SDoc
pprReg Reg
reg1,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg2,
        String -> SDoc
text String
", ",
        Reg -> SDoc
pprReg Reg
reg3
    ]

pprRI :: RI -> SDoc
pprRI :: RI -> SDoc
pprRI (RIReg Reg
r) = Reg -> SDoc
pprReg Reg
r
pprRI (RIImm Imm
r) = Imm -> SDoc
pprImm Imm
r


pprFFormat :: Format -> SDoc
pprFFormat :: Format -> SDoc
pprFFormat Format
FF64     = SDoc
empty
pprFFormat Format
FF32     = Char -> SDoc
char Char
's'
pprFFormat Format
_        = String -> SDoc
forall a. String -> a
panic String
"PPC.Ppr.pprFFormat: no match"

    -- limit immediate argument for shift instruction to range 0..63
    -- for 64 bit size and 0..32 otherwise
limitShiftRI :: Format -> RI -> RI
limitShiftRI :: Format -> RI -> RI
limitShiftRI Format
II64 (RIImm (ImmInt Int
i)) | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
63 Bool -> Bool -> Bool
|| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
  String -> RI
forall a. String -> a
panic (String -> RI) -> String -> RI
forall a b. (a -> b) -> a -> b
$ String
"PPC.Ppr: Shift by " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
i String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" bits is not allowed."
limitShiftRI Format
II32 (RIImm (ImmInt Int
i)) | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
31 Bool -> Bool -> Bool
|| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
  String -> RI
forall a. String -> a
panic (String -> RI) -> String -> RI
forall a b. (a -> b) -> a -> b
$ String
"PPC.Ppr: 32 bit: Shift by " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
i String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" bits is not allowed."
limitShiftRI Format
_ RI
x = RI
x