module GHC.CmmToAsm.LA64.Ppr (pprNatCmmDecl, pprInstr) where
import GHC.Prelude hiding (EQ)
import GHC.CmmToAsm.LA64.Regs
import GHC.CmmToAsm.LA64.Instr
import GHC.CmmToAsm.LA64.Cond
import GHC.CmmToAsm.Config
import GHC.CmmToAsm.Format
import GHC.CmmToAsm.Ppr
import GHC.CmmToAsm.Types
import GHC.CmmToAsm.Utils
import GHC.Cmm hiding (topInfoTable)
import GHC.Cmm.BlockId
import GHC.Cmm.CLabel
import GHC.Cmm.Dataflow.Label
import GHC.Platform
import GHC.Platform.Reg
import GHC.Types.Unique ( pprUniqueAlways, getUnique )
import GHC.Utils.Outputable
import GHC.Types.Basic (Alignment, alignmentBytes, mkAlignment)
import GHC.Utils.Panic
pprNatCmmDecl :: forall doc. (IsDoc doc) => NCGConfig -> NatCmmDecl RawCmmStatics Instr -> doc
pprNatCmmDecl :: forall doc.
IsDoc doc =>
NCGConfig -> NatCmmDecl RawCmmStatics Instr -> doc
pprNatCmmDecl NCGConfig
config (CmmData Section
section RawCmmStatics
dats) =
NCGConfig -> Section -> doc
forall doc. IsDoc doc => NCGConfig -> Section -> doc
pprSectionAlign NCGConfig
config Section
section doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$ NCGConfig -> RawCmmStatics -> doc
forall doc. IsDoc doc => NCGConfig -> RawCmmStatics -> doc
pprDatas NCGConfig
config RawCmmStatics
dats
pprNatCmmDecl NCGConfig
config proc :: NatCmmDecl RawCmmStatics Instr
proc@(CmmProc LabelMap RawCmmStatics
top_info CLabel
lbl [GlobalRegUse]
_ (ListGraph [GenBasicBlock Instr]
blocks)) =
let platform :: Platform
platform = NCGConfig -> Platform
ncgPlatform NCGConfig
config
pprProcAlignment :: doc
pprProcAlignment :: doc
pprProcAlignment = doc -> (Int -> doc) -> Maybe Int -> doc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe doc
forall doc. IsOutput doc => doc
empty (Alignment -> doc
forall doc. IsDoc doc => Alignment -> doc
pprAlign (Alignment -> doc) -> (Int -> Alignment) -> Int -> doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Alignment
mkAlignment) (NCGConfig -> Maybe Int
ncgProcAlignment NCGConfig
config)
in doc
pprProcAlignment
doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$ case NatCmmDecl RawCmmStatics Instr -> Maybe RawCmmStatics
forall a i b. GenCmmDecl a (LabelMap i) (ListGraph b) -> Maybe i
topInfoTable NatCmmDecl RawCmmStatics Instr
proc of
Maybe RawCmmStatics
Nothing ->
NCGConfig -> Section -> doc
forall doc. IsDoc doc => NCGConfig -> Section -> doc
pprSectionAlign NCGConfig
config (SectionType -> CLabel -> Section
Section SectionType
Text CLabel
lbl)
doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$
Platform -> CLabel -> doc
forall doc. IsDoc doc => Platform -> CLabel -> doc
pprLabel Platform
platform CLabel
lbl
doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$ [doc] -> doc
forall doc. IsDoc doc => [doc] -> doc
vcat ((GenBasicBlock Instr -> doc) -> [GenBasicBlock Instr] -> [doc]
forall a b. (a -> b) -> [a] -> [b]
map (NCGConfig -> LabelMap RawCmmStatics -> GenBasicBlock Instr -> doc
forall doc.
IsDoc doc =>
NCGConfig -> LabelMap RawCmmStatics -> GenBasicBlock Instr -> doc
pprBasicBlock NCGConfig
config LabelMap RawCmmStatics
top_info) [GenBasicBlock Instr]
blocks)
doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$ Bool -> doc -> doc
forall doc. IsOutput doc => Bool -> doc -> doc
ppWhen
(NCGConfig -> Bool
ncgDwarfEnabled NCGConfig
config)
(Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprBlockEndLabel Platform
platform CLabel
lbl) doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$ Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprProcEndLabel Platform
platform CLabel
lbl))
doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$ Platform -> CLabel -> doc
forall doc. IsDoc doc => Platform -> CLabel -> doc
pprSizeDecl Platform
platform CLabel
lbl
Just (CmmStaticsRaw CLabel
info_lbl [CmmStatic]
_) ->
NCGConfig -> Section -> doc
forall doc. IsDoc doc => NCGConfig -> Section -> doc
pprSectionAlign NCGConfig
config (SectionType -> CLabel -> Section
Section SectionType
Text CLabel
info_lbl)
doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$
( if Platform -> Bool
platformHasSubsectionsViaSymbols Platform
platform
then Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (CLabel -> CLabel
mkDeadStripPreventer CLabel
info_lbl) Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Char -> Line doc
forall doc. IsLine doc => Char -> doc
char Char
':')
else doc
forall doc. IsOutput doc => doc
empty
)
doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$ [doc] -> doc
forall doc. IsDoc doc => [doc] -> doc
vcat ((GenBasicBlock Instr -> doc) -> [GenBasicBlock Instr] -> [doc]
forall a b. (a -> b) -> [a] -> [b]
map (NCGConfig -> LabelMap RawCmmStatics -> GenBasicBlock Instr -> doc
forall doc.
IsDoc doc =>
NCGConfig -> LabelMap RawCmmStatics -> GenBasicBlock Instr -> doc
pprBasicBlock NCGConfig
config LabelMap RawCmmStatics
top_info) [GenBasicBlock Instr]
blocks)
doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$ Bool -> doc -> doc
forall doc. IsOutput doc => Bool -> doc -> doc
ppWhen (NCGConfig -> Bool
ncgDwarfEnabled NCGConfig
config) (Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprProcEndLabel Platform
platform CLabel
info_lbl))
doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$
( if Platform -> Bool
platformHasSubsectionsViaSymbols Platform
platform
then
Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line
(Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\t.long "
Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
info_lbl
Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Char -> Line doc
forall doc. IsLine doc => Char -> doc
char Char
'-'
Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (CLabel -> CLabel
mkDeadStripPreventer CLabel
info_lbl)
else doc
forall doc. IsOutput doc => doc
empty
)
doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$ Platform -> CLabel -> doc
forall doc. IsDoc doc => Platform -> CLabel -> doc
pprSizeDecl Platform
platform CLabel
info_lbl
{-# SPECIALIZE pprNatCmmDecl :: NCGConfig -> NatCmmDecl RawCmmStatics Instr -> SDoc #-}
{-# SPECIALIZE pprNatCmmDecl :: NCGConfig -> NatCmmDecl RawCmmStatics Instr -> HDoc #-}
pprProcEndLabel :: IsLine doc => Platform -> CLabel
-> doc
pprProcEndLabel :: forall doc. IsLine doc => Platform -> CLabel -> doc
pprProcEndLabel Platform
platform CLabel
lbl =
Platform -> CLabel -> doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (CLabel -> CLabel
mkAsmTempProcEndLabel CLabel
lbl) doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<> doc
forall doc. IsLine doc => doc
colon
pprBlockEndLabel :: IsLine doc => Platform -> CLabel
-> doc
pprBlockEndLabel :: forall doc. IsLine doc => Platform -> CLabel -> doc
pprBlockEndLabel Platform
platform CLabel
lbl =
Platform -> CLabel -> doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (CLabel -> CLabel
mkAsmTempEndLabel CLabel
lbl) doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<> doc
forall doc. IsLine doc => doc
colon
pprLabel :: IsDoc doc => Platform -> CLabel -> doc
pprLabel :: forall doc. IsDoc doc => Platform -> CLabel -> doc
pprLabel Platform
platform CLabel
lbl =
Platform -> CLabel -> doc
forall doc. IsDoc doc => Platform -> CLabel -> doc
pprGloblDecl Platform
platform CLabel
lbl
doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$ Platform -> CLabel -> doc
forall doc. IsDoc doc => Platform -> CLabel -> doc
pprTypeDecl Platform
platform CLabel
lbl
doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$ Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
lbl Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Char -> Line doc
forall doc. IsLine doc => Char -> doc
char Char
':')
pprAlign :: (IsDoc doc) => Alignment -> doc
pprAlign :: forall doc. IsDoc doc => Alignment -> doc
pprAlign Alignment
alignment =
Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\t.balign " Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Int -> Line doc
forall doc. IsLine doc => Int -> doc
int (Alignment -> Int
alignmentBytes Alignment
alignment)
pprAlignForSection :: (IsDoc doc) => SectionType -> doc
pprAlignForSection :: forall doc. IsDoc doc => SectionType -> doc
pprAlignForSection SectionType
_seg = Alignment -> doc
forall doc. IsDoc doc => Alignment -> doc
pprAlign (Alignment -> doc) -> (Int -> Alignment) -> Int -> doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Alignment
mkAlignment (Int -> doc) -> Int -> doc
forall a b. (a -> b) -> a -> b
$ Int
8
pprSectionAlign :: IsDoc doc => NCGConfig -> Section -> doc
pprSectionAlign :: forall doc. IsDoc doc => NCGConfig -> Section -> doc
pprSectionAlign NCGConfig
_config (Section (OtherSection String
_) CLabel
_) =
String -> doc
forall a. HasCallStack => String -> a
panic String
"LA64.Ppr.pprSectionAlign: unknown section"
pprSectionAlign NCGConfig
config sec :: Section
sec@(Section SectionType
seg CLabel
_) =
Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (NCGConfig -> Section -> Line doc
forall doc. IsLine doc => NCGConfig -> Section -> doc
pprSectionHeader NCGConfig
config Section
sec)
doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$ SectionType -> doc
forall doc. IsDoc doc => SectionType -> doc
pprAlignForSection SectionType
seg
pprSizeDecl :: (IsDoc doc) => Platform -> CLabel -> doc
pprSizeDecl :: forall doc. IsDoc doc => Platform -> CLabel -> doc
pprSizeDecl Platform
platform CLabel
lbl
| OS -> Bool
osElfTarget (Platform -> OS
platformOS Platform
platform) =
Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\t.size" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
lbl Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", .-" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
lbl
pprSizeDecl Platform
_ CLabel
_ = doc
forall doc. IsOutput doc => doc
empty
pprBasicBlock ::
(IsDoc doc) =>
NCGConfig ->
LabelMap RawCmmStatics ->
NatBasicBlock Instr ->
doc
pprBasicBlock :: forall doc.
IsDoc doc =>
NCGConfig -> LabelMap RawCmmStatics -> GenBasicBlock Instr -> doc
pprBasicBlock NCGConfig
config LabelMap RawCmmStatics
info_env (BasicBlock BlockId
blockid [Instr]
instrs)
= doc -> doc
maybe_infotable (doc -> doc) -> doc -> doc
forall a b. (a -> b) -> a -> b
$
Platform -> CLabel -> doc
forall doc. IsDoc doc => Platform -> CLabel -> doc
pprLabel Platform
platform CLabel
asmLbl doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$
[doc] -> doc
forall doc. IsDoc doc => [doc] -> doc
vcat ((Instr -> doc) -> [Instr] -> [doc]
forall a b. (a -> b) -> [a] -> [b]
map (Platform -> Instr -> doc
forall doc. IsDoc doc => Platform -> Instr -> doc
pprInstr Platform
platform) ([Instr] -> [Instr]
forall a. a -> a
id [Instr]
optInstrs)) doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$
Bool -> doc -> doc
forall doc. IsOutput doc => Bool -> doc -> doc
ppWhen (NCGConfig -> Bool
ncgDwarfEnabled NCGConfig
config) (
Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprBlockEndLabel Platform
platform CLabel
asmLbl
Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprProcEndLabel Platform
platform CLabel
asmLbl)
)
where
optInstrs :: [Instr]
optInstrs = (Instr -> Bool) -> [Instr] -> [Instr]
forall a. (a -> Bool) -> [a] -> [a]
filter Instr -> Bool
f [Instr]
instrs
where f :: Instr -> Bool
f (MOV Operand
o1 Operand
o2) | Operand
o1 Operand -> Operand -> Bool
forall a. Eq a => a -> a -> Bool
== Operand
o2 = Bool
False
f Instr
_ = Bool
True
asmLbl :: CLabel
asmLbl = BlockId -> CLabel
blockLbl BlockId
blockid
platform :: Platform
platform = NCGConfig -> Platform
ncgPlatform NCGConfig
config
maybe_infotable :: doc -> doc
maybe_infotable doc
c = case BlockId -> LabelMap RawCmmStatics -> Maybe RawCmmStatics
forall a. BlockId -> LabelMap a -> Maybe a
mapLookup BlockId
blockid LabelMap RawCmmStatics
info_env of
Maybe RawCmmStatics
Nothing -> doc
c
Just (CmmStaticsRaw CLabel
info_lbl [CmmStatic]
info) ->
doc
infoTableLoc doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$
[doc] -> doc
forall doc. IsDoc doc => [doc] -> doc
vcat ((CmmStatic -> doc) -> [CmmStatic] -> [doc]
forall a b. (a -> b) -> [a] -> [b]
map (NCGConfig -> CmmStatic -> doc
forall doc. IsDoc doc => NCGConfig -> CmmStatic -> doc
pprData NCGConfig
config) [CmmStatic]
info) doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$
Platform -> CLabel -> doc
forall doc. IsDoc doc => Platform -> CLabel -> doc
pprLabel Platform
platform CLabel
info_lbl doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$
doc
c doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$
Bool -> doc -> doc
forall doc. IsOutput doc => Bool -> doc -> doc
ppWhen (NCGConfig -> Bool
ncgDwarfEnabled NCGConfig
config)
(Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprBlockEndLabel Platform
platform CLabel
info_lbl))
infoTableLoc :: doc
infoTableLoc = case [Instr]
instrs of
(l :: Instr
l@LOCATION{} : [Instr]
_) -> Platform -> Instr -> doc
forall doc. IsDoc doc => Platform -> Instr -> doc
pprInstr Platform
platform Instr
l
[Instr]
_other -> doc
forall doc. IsOutput doc => doc
empty
pprDatas :: IsDoc doc => NCGConfig -> RawCmmStatics -> doc
pprDatas :: forall doc. IsDoc doc => NCGConfig -> RawCmmStatics -> doc
pprDatas NCGConfig
config (CmmStaticsRaw 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'
= Platform -> CLabel -> doc
forall doc. IsDoc doc => Platform -> CLabel -> doc
pprGloblDecl (NCGConfig -> Platform
ncgPlatform NCGConfig
config) CLabel
alias
doc -> doc -> doc
forall doc. IsDoc doc => doc -> doc -> doc
$$ Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
".equiv" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel (NCGConfig -> Platform
ncgPlatform NCGConfig
config) CLabel
alias Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel (NCGConfig -> Platform
ncgPlatform NCGConfig
config) CLabel
ind')
pprDatas NCGConfig
config (CmmStaticsRaw CLabel
lbl [CmmStatic]
dats)
= [doc] -> doc
forall doc. IsDoc doc => [doc] -> doc
vcat (Platform -> CLabel -> doc
forall doc. IsDoc doc => Platform -> CLabel -> doc
pprLabel Platform
platform CLabel
lbl doc -> [doc] -> [doc]
forall a. a -> [a] -> [a]
: (CmmStatic -> doc) -> [CmmStatic] -> [doc]
forall a b. (a -> b) -> [a] -> [b]
map (NCGConfig -> CmmStatic -> doc
forall doc. IsDoc doc => NCGConfig -> CmmStatic -> doc
pprData NCGConfig
config) [CmmStatic]
dats)
where
platform :: Platform
platform = NCGConfig -> Platform
ncgPlatform NCGConfig
config
pprData :: IsDoc doc => NCGConfig -> CmmStatic -> doc
pprData :: forall doc. IsDoc doc => NCGConfig -> CmmStatic -> doc
pprData NCGConfig
_config (CmmString ByteString
str) = Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (ByteString -> Line doc
forall doc. IsLine doc => ByteString -> doc
pprString ByteString
str)
pprData NCGConfig
_config (CmmFileEmbed String
path Int
_) = Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (String -> Line doc
forall doc. IsLine doc => String -> doc
pprFileEmbed String
path)
pprData NCGConfig
config (CmmUninitialised Int
bytes)
= Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ let platform :: Platform
platform = NCGConfig -> Platform
ncgPlatform NCGConfig
config
in if Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSDarwin
then String -> Line doc
forall doc. IsLine doc => String -> doc
text String
".space " Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Int -> Line doc
forall doc. IsLine doc => Int -> doc
int Int
bytes
else String -> Line doc
forall doc. IsLine doc => String -> doc
text String
".skip " Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Int -> Line doc
forall doc. IsLine doc => Int -> doc
int Int
bytes
pprData NCGConfig
config (CmmStaticLit CmmLit
lit) = NCGConfig -> CmmLit -> doc
forall doc. IsDoc doc => NCGConfig -> CmmLit -> doc
pprDataItem NCGConfig
config CmmLit
lit
pprGloblDecl :: IsDoc doc => Platform -> CLabel -> doc
pprGloblDecl :: forall doc. IsDoc doc => Platform -> CLabel -> doc
pprGloblDecl Platform
platform CLabel
lbl
| Bool -> Bool
not (CLabel -> Bool
externallyVisibleCLabel CLabel
lbl) = doc
forall doc. IsOutput doc => doc
empty
| Bool
otherwise = Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\t.globl " Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
lbl)
pprLabelType' :: IsLine doc => Platform -> CLabel -> doc
pprLabelType' :: forall doc. IsLine doc => Platform -> CLabel -> doc
pprLabelType' Platform
platform CLabel
lbl =
if CLabel -> Bool
isCFunctionLabel CLabel
lbl Bool -> Bool -> Bool
|| Bool
functionOkInfoTable
then String -> doc
forall doc. IsLine doc => String -> doc
text String
"@function"
else String -> doc
forall doc. IsLine doc => String -> doc
text String
"@object"
where
functionOkInfoTable :: Bool
functionOkInfoTable = Platform -> Bool
platformTablesNextToCode Platform
platform Bool -> Bool -> Bool
&&
CLabel -> Bool
isInfoTableLabel CLabel
lbl Bool -> Bool -> Bool
&& Bool -> Bool
not (CLabel -> Bool
isCmmInfoTableLabel CLabel
lbl) Bool -> Bool -> Bool
&& Bool -> Bool
not (CLabel -> Bool
isConInfoTableLabel CLabel
lbl)
pprTypeDecl :: IsDoc doc => Platform -> CLabel -> doc
pprTypeDecl :: forall doc. IsDoc doc => Platform -> CLabel -> doc
pprTypeDecl Platform
platform CLabel
lbl
= if OS -> Bool
osElfTarget (Platform -> OS
platformOS Platform
platform) Bool -> Bool -> Bool
&& CLabel -> Bool
externallyVisibleCLabel CLabel
lbl
then Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
".type " Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
lbl Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", " Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprLabelType' Platform
platform CLabel
lbl)
else doc
forall doc. IsOutput doc => doc
empty
pprDataItem :: IsDoc doc => NCGConfig -> CmmLit -> doc
pprDataItem :: forall doc. IsDoc doc => NCGConfig -> CmmLit -> doc
pprDataItem NCGConfig
config CmmLit
lit
= [Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ (Format -> CmmLit -> [Line doc]
ppr_item (CmmType -> Format
cmmTypeFormat (CmmType -> Format) -> CmmType -> Format
forall a b. (a -> b) -> a -> b
$ Platform -> CmmLit -> CmmType
cmmLitType Platform
platform CmmLit
lit) CmmLit
lit)
where
platform :: Platform
platform = NCGConfig -> Platform
ncgPlatform NCGConfig
config
imm :: Imm
imm = CmmLit -> Imm
litToImm CmmLit
lit
ppr_item :: Format -> CmmLit -> [Line doc]
ppr_item Format
II8 CmmLit
_ = [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\t.byte\t" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> Imm -> Line doc
forall doc. IsLine doc => Platform -> Imm -> doc
pprDataImm Platform
platform Imm
imm]
ppr_item Format
II16 CmmLit
_ = [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\t.short\t" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> Imm -> Line doc
forall doc. IsLine doc => Platform -> Imm -> doc
pprDataImm Platform
platform Imm
imm]
ppr_item Format
II32 CmmLit
_ = [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\t.long\t" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> Imm -> Line doc
forall doc. IsLine doc => Platform -> Imm -> doc
pprDataImm Platform
platform Imm
imm]
ppr_item Format
II64 CmmLit
_ = [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\t.quad\t" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> Imm -> Line doc
forall doc. IsLine doc => Platform -> Imm -> doc
pprDataImm Platform
platform Imm
imm]
ppr_item Format
FF32 (CmmFloat Rational
r Width
_)
= let bs :: [Word8]
bs = Float -> [Word8]
floatToBytes (Rational -> Float
forall a. Fractional a => Rational -> a
fromRational Rational
r)
in (Word8 -> Line doc) -> [Word8] -> [Line doc]
forall a b. (a -> b) -> [a] -> [b]
map (\Word8
b -> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\t.byte\t" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Int -> Line doc
forall doc. IsLine doc => Int -> doc
int (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
b)) [Word8]
bs
ppr_item Format
FF64 (CmmFloat Rational
r Width
_)
= let bs :: [Word8]
bs = Double -> [Word8]
doubleToBytes (Rational -> Double
forall a. Fractional a => Rational -> a
fromRational Rational
r)
in (Word8 -> Line doc) -> [Word8] -> [Line doc]
forall a b. (a -> b) -> [a] -> [b]
map (\Word8
b -> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\t.byte\t" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Int -> Line doc
forall doc. IsLine doc => Int -> doc
int (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
b)) [Word8]
bs
ppr_item Format
_ CmmLit
_ = String -> SDoc -> [Line doc]
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"pprDataItem:ppr_item" (String -> SDoc
forall doc. IsLine doc => String -> doc
text (String -> SDoc) -> String -> SDoc
forall a b. (a -> b) -> a -> b
$ CmmLit -> String
forall a. Show a => a -> String
show CmmLit
lit)
pprDataImm :: IsLine doc => Platform -> Imm -> doc
pprDataImm :: forall doc. IsLine doc => Platform -> Imm -> doc
pprDataImm Platform
_ (ImmInt Int
i) = Int -> doc
forall doc. IsLine doc => Int -> doc
int Int
i
pprDataImm Platform
_ (ImmInteger Integer
i) = Integer -> doc
forall doc. IsLine doc => Integer -> doc
integer Integer
i
pprDataImm Platform
p (ImmCLbl CLabel
l) = Platform -> CLabel -> doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
p CLabel
l
pprDataImm Platform
p (ImmIndex CLabel
l Int
i) = Platform -> CLabel -> doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
p CLabel
l doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<> Char -> doc
forall doc. IsLine doc => Char -> doc
char Char
'+' doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<> Int -> doc
forall doc. IsLine doc => Int -> doc
int Int
i
pprDataImm Platform
_ (ImmLit FastString
s) = FastString -> doc
forall doc. IsLine doc => FastString -> doc
ftext FastString
s
pprDataImm Platform
_ (ImmFloat Rational
f) = Float -> doc
forall doc. IsLine doc => Float -> doc
float (Rational -> Float
forall a. Fractional a => Rational -> a
fromRational Rational
f)
pprDataImm Platform
_ (ImmDouble Rational
d) = Double -> doc
forall doc. IsLine doc => Double -> doc
double (Rational -> Double
forall a. Fractional a => Rational -> a
fromRational Rational
d)
pprDataImm Platform
p (ImmConstantSum Imm
a Imm
b) = Platform -> Imm -> doc
forall doc. IsLine doc => Platform -> Imm -> doc
pprDataImm Platform
p Imm
a doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<> Char -> doc
forall doc. IsLine doc => Char -> doc
char Char
'+' doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> Imm -> doc
forall doc. IsLine doc => Platform -> Imm -> doc
pprDataImm Platform
p Imm
b
pprDataImm Platform
p (ImmConstantDiff Imm
a Imm
b) = Platform -> Imm -> doc
forall doc. IsLine doc => Platform -> Imm -> doc
pprDataImm Platform
p Imm
a doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<> Char -> doc
forall doc. IsLine doc => Char -> doc
char Char
'-'
doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<> doc
forall doc. IsLine doc => doc
lparen doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> Imm -> doc
forall doc. IsLine doc => Platform -> Imm -> doc
pprDataImm Platform
p Imm
b doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<> doc
forall doc. IsLine doc => doc
rparen
asmComment :: SDoc -> SDoc
SDoc
c = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"#" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
c
asmDoubleslashComment :: SDoc -> SDoc
SDoc
c = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"//" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
c
asmMultilineComment :: SDoc -> SDoc
SDoc
c = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"/*" SDoc -> SDoc -> SDoc
$+$ SDoc
c SDoc -> SDoc -> SDoc
$+$ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"*/"
pprOpImm :: (IsLine doc) => Platform -> Imm -> doc
pprOpImm :: forall doc. IsLine doc => Platform -> Imm -> doc
pprOpImm Platform
platform Imm
imm = case Imm
imm of
ImmInt Int
i -> Int -> doc
forall doc. IsLine doc => Int -> doc
int Int
i
ImmInteger Integer
i -> Integer -> doc
forall doc. IsLine doc => Integer -> doc
integer Integer
i
ImmCLbl CLabel
l -> Char -> doc
forall doc. IsLine doc => Char -> doc
char Char
'=' doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> CLabel -> doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
l
ImmFloat Rational
f -> Float -> doc
forall doc. IsLine doc => Float -> doc
float (Rational -> Float
forall a. Fractional a => Rational -> a
fromRational Rational
f)
ImmDouble Rational
d -> Double -> doc
forall doc. IsLine doc => Double -> doc
double (Rational -> Double
forall a. Fractional a => Rational -> a
fromRational Rational
d)
Imm
_ -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.Ppr.pprOpImm" (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Unsupported immediate for instruction operands:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (String -> SDoc
forall doc. IsLine doc => String -> doc
text (String -> SDoc) -> (Imm -> String) -> Imm -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Imm -> String
forall a. Show a => a -> String
show) Imm
imm)
negOp :: Operand -> Operand
negOp :: Operand -> Operand
negOp (OpImm (ImmInt Int
i)) = Imm -> Operand
OpImm (Int -> Imm
ImmInt (Int -> Int
forall a. Num a => a -> a
negate Int
i))
negOp (OpImm (ImmInteger Integer
i)) = Imm -> Operand
OpImm (Integer -> Imm
ImmInteger (Integer -> Integer
forall a. Num a => a -> a
negate Integer
i))
negOp Operand
op = String -> SDoc -> Operand
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.negOp" (String -> SDoc
forall doc. IsLine doc => String -> doc
text (String -> SDoc) -> String -> SDoc
forall a b. (a -> b) -> a -> b
$ Operand -> String
forall a. Show a => a -> String
show Operand
op)
pprOp :: IsLine doc => Platform -> Operand -> doc
pprOp :: forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
plat Operand
op = case Operand
op of
OpReg Width
w Reg
r -> Width -> Reg -> doc
forall doc. IsLine doc => Width -> Reg -> doc
pprReg Width
w Reg
r
OpImm Imm
imm -> Platform -> Imm -> doc
forall doc. IsLine doc => Platform -> Imm -> doc
pprOpImm Platform
plat Imm
imm
OpAddr (AddrRegReg Reg
r1 Reg
r2) -> Width -> Reg -> doc
forall doc. IsLine doc => Width -> Reg -> doc
pprReg Width
W64 Reg
r1 doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<> doc
forall doc. IsLine doc => doc
comma doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Width -> Reg -> doc
forall doc. IsLine doc => Width -> Reg -> doc
pprReg Width
W64 Reg
r2
OpAddr (AddrRegImm Reg
r Imm
imm) -> Width -> Reg -> doc
forall doc. IsLine doc => Width -> Reg -> doc
pprReg Width
W64 Reg
r doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<> doc
forall doc. IsLine doc => doc
comma doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Imm -> doc
forall doc. IsLine doc => Platform -> Imm -> doc
pprOpImm Platform
plat Imm
imm
OpAddr (AddrReg Reg
r) -> Width -> Reg -> doc
forall doc. IsLine doc => Width -> Reg -> doc
pprReg Width
W64 Reg
r doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> doc
forall doc. IsLine doc => String -> doc
text String
", 0"
pprReg :: forall doc. IsLine doc => Width -> Reg -> doc
pprReg :: forall doc. IsLine doc => Width -> Reg -> doc
pprReg Width
w Reg
r = case Reg
r of
RegReal (RealRegSingle Int
i) -> Int -> doc
ppr_reg_no Int
i
RegVirtual (VirtualRegI Unique
u) -> String -> doc
forall doc. IsLine doc => String -> doc
text String
"%vI_" doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<> Unique -> doc
forall doc. IsLine doc => Unique -> doc
pprUniqueAlways Unique
u
RegVirtual (VirtualRegD Unique
u) -> String -> doc
forall doc. IsLine doc => String -> doc
text String
"%vD_" doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<> Unique -> doc
forall doc. IsLine doc => Unique -> doc
pprUniqueAlways Unique
u
Reg
_ -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.pprReg" (String -> SDoc
forall doc. IsLine doc => String -> doc
text (Reg -> String
forall a. Show a => a -> String
show Reg
r) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr Width
w)
where
ppr_reg_no :: Int -> doc
ppr_reg_no :: Int -> doc
ppr_reg_no Int
0 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$zero"
ppr_reg_no Int
1 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ra"
ppr_reg_no Int
2 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$tp"
ppr_reg_no Int
3 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$sp"
ppr_reg_no Int
4 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$a0"
ppr_reg_no Int
5 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$a1"
ppr_reg_no Int
6 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$a2"
ppr_reg_no Int
7 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$a3"
ppr_reg_no Int
8 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$a4"
ppr_reg_no Int
9 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$a5"
ppr_reg_no Int
10 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$a6"
ppr_reg_no Int
11 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$a7"
ppr_reg_no Int
12 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$t0"
ppr_reg_no Int
13 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$t1"
ppr_reg_no Int
14 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$t2"
ppr_reg_no Int
15 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$t3"
ppr_reg_no Int
16 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$t4"
ppr_reg_no Int
17 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$t5"
ppr_reg_no Int
18 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$t6"
ppr_reg_no Int
19 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$t7"
ppr_reg_no Int
20 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$t8"
ppr_reg_no Int
21 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$u0"
ppr_reg_no Int
22 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fp"
ppr_reg_no Int
23 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$s0"
ppr_reg_no Int
24 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$s1"
ppr_reg_no Int
25 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$s2"
ppr_reg_no Int
26 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$s3"
ppr_reg_no Int
27 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$s4"
ppr_reg_no Int
28 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$s5"
ppr_reg_no Int
29 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$s6"
ppr_reg_no Int
30 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$s7"
ppr_reg_no Int
31 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$s8"
ppr_reg_no Int
32 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fa0"
ppr_reg_no Int
33 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fa1"
ppr_reg_no Int
34 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fa2"
ppr_reg_no Int
35 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fa3"
ppr_reg_no Int
36 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fa4"
ppr_reg_no Int
37 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fa5"
ppr_reg_no Int
38 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fa6"
ppr_reg_no Int
39 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fa7"
ppr_reg_no Int
40 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ft0"
ppr_reg_no Int
41 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ft1"
ppr_reg_no Int
42 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ft2"
ppr_reg_no Int
43 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ft3"
ppr_reg_no Int
44 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ft4"
ppr_reg_no Int
45 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ft5"
ppr_reg_no Int
46 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ft6"
ppr_reg_no Int
47 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ft7"
ppr_reg_no Int
48 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ft8"
ppr_reg_no Int
49 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ft9"
ppr_reg_no Int
50 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ft10"
ppr_reg_no Int
51 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ft11"
ppr_reg_no Int
52 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ft12"
ppr_reg_no Int
53 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ft13"
ppr_reg_no Int
54 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ft14"
ppr_reg_no Int
55 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$ft15"
ppr_reg_no Int
56 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fs0"
ppr_reg_no Int
57 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fs1"
ppr_reg_no Int
58 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fs2"
ppr_reg_no Int
59 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fs3"
ppr_reg_no Int
60 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fs4"
ppr_reg_no Int
61 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fs5"
ppr_reg_no Int
62 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fs6"
ppr_reg_no Int
63 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"$fs7"
ppr_reg_no Int
i
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"Unexpected register number (min is 0)" (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr Width
w SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Int -> SDoc
forall doc. IsLine doc => Int -> doc
int Int
i)
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
63 = String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"Unexpected register number (max is 63)" (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr Width
w SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Int -> SDoc
forall doc. IsLine doc => Int -> doc
int Int
i)
| Bool
otherwise = String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"Unsupported width in register (max is 64)" (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr Width
w SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Int -> SDoc
forall doc. IsLine doc => Int -> doc
int Int
i)
isSingleOp :: Operand -> Bool
isSingleOp :: Operand -> Bool
isSingleOp (OpReg Width
W32 Reg
_) = Bool
True
isSingleOp Operand
_ = Bool
False
isDoubleOp :: Operand -> Bool
isDoubleOp :: Operand -> Bool
isDoubleOp (OpReg Width
W64 Reg
_) = Bool
True
isDoubleOp Operand
_ = Bool
False
isImmOp :: Operand -> Bool
isImmOp :: Operand -> Bool
isImmOp (OpImm Imm
_) = Bool
True
isImmOp Operand
_ = Bool
False
isImmZero :: Operand -> Bool
isImmZero :: Operand -> Bool
isImmZero (OpImm (ImmFloat Rational
0)) = Bool
True
isImmZero (OpImm (ImmDouble Rational
0)) = Bool
True
isImmZero (OpImm (ImmInt Int
0)) = Bool
True
isImmZero Operand
_ = Bool
False
pprInstr :: IsDoc doc => Platform -> Instr -> doc
pprInstr :: forall doc. IsDoc doc => Platform -> Instr -> doc
pprInstr Platform
platform Instr
instr = case Instr
instr of
COMMENT SDoc
s -> SDoc -> HDoc -> doc
forall doc. IsDoc doc => SDoc -> HDoc -> doc
dualDoc (SDoc -> SDoc
asmComment SDoc
s) HDoc
forall doc. IsOutput doc => doc
empty
MULTILINE_COMMENT SDoc
s -> SDoc -> HDoc -> doc
forall doc. IsDoc doc => SDoc -> HDoc -> doc
dualDoc (SDoc -> SDoc
asmMultilineComment SDoc
s) HDoc
forall doc. IsOutput doc => doc
empty
ANN SDoc
d Instr
i -> SDoc -> HDoc -> doc
forall doc. IsDoc doc => SDoc -> HDoc -> doc
dualDoc (Platform -> Instr -> SDoc
forall doc. IsDoc doc => Platform -> Instr -> doc
pprInstr Platform
platform Instr
i SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
asmDoubleslashComment SDoc
d) (Platform -> Instr -> HDoc
forall doc. IsDoc doc => Platform -> Instr -> doc
pprInstr Platform
platform Instr
i)
LOCATION Int
file Int
line' Int
col LexicalFastString
_name
-> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\t.loc" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Int -> Line doc
forall doc. IsLine doc => Int -> doc
int Int
file Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Int -> Line doc
forall doc. IsLine doc => Int -> doc
int Int
line' Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Int -> Line doc
forall doc. IsLine doc => Int -> doc
int Int
col)
DELTA Int
d -> SDoc -> HDoc -> doc
forall doc. IsDoc doc => SDoc -> HDoc -> doc
dualDoc (SDoc -> SDoc
asmComment (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"\tdelta = " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Int -> SDoc
forall doc. IsLine doc => Int -> doc
int Int
d) HDoc
forall doc. IsOutput doc => doc
empty
NEWBLOCK BlockId
_ -> String -> doc
forall a. HasCallStack => String -> a
panic String
"PprInstr: NEWBLOCK"
LDATA Section
_ RawCmmStatics
_ -> String -> doc
forall a. HasCallStack => String -> a
panic String
"PprInstr: NEWBLOCK"
Instr
PUSH_STACK_FRAME -> [Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.d $sp, $sp, -16"
, String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tst.d $ra, $sp, 8"
, String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tst.d $fp, $sp, 0"
, String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.d $fp, $sp, 16"
]
Instr
POP_STACK_FRAME -> [Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tld.d $fp, $sp, 0"
, String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tld.d $ra, $sp, 8"
, String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.d $sp, $sp, 16"
]
ADD Operand
o1 Operand
o2 Operand
o3
| Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o3 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfadd.s") Operand
o1 Operand
o2 Operand
o3
| Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o3 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfadd.d") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, OpReg Width
W32 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tadd.w") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tadd.d") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, Operand -> Bool
isImmOp Operand
o3, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Int -> Int -> Bool
fitsInNbits Int
12 (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.w") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, Operand -> Bool
isImmOp Operand
o3, (OpImm (ImmInt Int
i)) <- Operand
o3, Int -> Int -> Bool
fitsInNbits Int
12 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.w") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, Operand -> Bool
isImmOp Operand
o3, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Int -> Int -> Bool
fitsInNbits Int
12 (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.d") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, Operand -> Bool
isImmOp Operand
o3, (OpImm (ImmInt Int
i)) <- Operand
o3, Int -> Int -> Bool
fitsInNbits Int
12 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.d") Operand
o1 Operand
o2 Operand
o3
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: ADD error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
SUB Operand
o1 Operand
o2 Operand
o3
| Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o3 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfsub.s") Operand
o1 Operand
o2 Operand
o3
| Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o3 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfsub.d") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, OpReg Width
W32 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsub.w") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsub.d") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, Operand -> Bool
isImmOp Operand
o3, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Int -> Int -> Bool
fitsInNbits Int
12 (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.w") Operand
o1 Operand
o2 (Operand -> Operand
negOp Operand
o3)
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, Operand -> Bool
isImmOp Operand
o3, (OpImm (ImmInt Int
i)) <- Operand
o3, Int -> Int -> Bool
fitsInNbits Int
12 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.w") Operand
o1 Operand
o2 (Operand -> Operand
negOp Operand
o3)
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, Operand -> Bool
isImmOp Operand
o3, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Int -> Int -> Bool
fitsInNbits Int
12 (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.d") Operand
o1 Operand
o2 (Operand -> Operand
negOp Operand
o3)
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, Operand -> Bool
isImmOp Operand
o3, (OpImm (ImmInt Int
i)) <- Operand
o3, Int -> Int -> Bool
fitsInNbits Int
12 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.d") Operand
o1 Operand
o2 (Operand -> Operand
negOp Operand
o3)
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: SUB error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
ALSL Operand
o1 Operand
o2 Operand
o3 Operand
o4
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, OpReg Width
W32 Reg
_ <- Operand
o3, Operand -> Bool
isImmOp Operand
o4 -> Line doc -> Operand -> Operand -> Operand -> Operand -> doc
op4 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\talsl.w") Operand
o1 Operand
o2 Operand
o3 Operand
o4
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3, Operand -> Bool
isImmOp Operand
o4 -> Line doc -> Operand -> Operand -> Operand -> Operand -> doc
op4 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\talsl.d") Operand
o1 Operand
o2 Operand
o3 Operand
o4
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: ALSL error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
ALSLU Operand
o1 Operand
o2 Operand
o3 Operand
o4 -> Line doc -> Operand -> Operand -> Operand -> Operand -> doc
op4 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\talsl.wu") Operand
o1 Operand
o2 Operand
o3 Operand
o4
LU12I Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tlu12i.w") Operand
o1 Operand
o2
LU32I Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tlu32i.d") Operand
o1 Operand
o2
LU52I Operand
o1 Operand
o2 Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tlu52i.d") Operand
o1 Operand
o2 Operand
o3
SSLT Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, Operand -> Bool
isImmOp Operand
o3, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Int -> Int -> Bool
fitsInNbits Int
12 (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tslti") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, Operand -> Bool
isImmOp Operand
o3, (OpImm (ImmInt Int
i)) <- Operand
o3, Int -> Int -> Bool
fitsInNbits Int
12 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tslti") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tslt") Operand
o1 Operand
o2 Operand
o3
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: SSLT error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
SSLTU Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, Operand -> Bool
isImmOp Operand
o3, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Int -> Int -> Bool
fitsInNbits Int
12 (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsltui") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, Operand -> Bool
isImmOp Operand
o3, (OpImm (ImmInt Int
i)) <- Operand
o3, Int -> Int -> Bool
fitsInNbits Int
12 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsltui") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsltu") Operand
o1 Operand
o2 Operand
o3
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: SSLTU error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
PCADDI Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tpcaddi") Operand
o1 Operand
o2
PCADDU12I Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tpcaddu12i") Operand
o1 Operand
o2
PCADDU18I Operand
o1 (OpImm (ImmCLbl CLabel
lbl)) ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tpcaddu18i" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"%call36(" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
lbl Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
")"
]
PCALAU12I Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tpcalau12i") Operand
o1 Operand
o2
AND Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tand") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Int -> Bool
isUnsignOp (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i), Int -> Int -> Bool
fitsInNbits Int
13 (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tandi") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, (OpImm (ImmInt Int
i)) <- Operand
o3, Int -> Bool
isUnsignOp (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i), Int -> Int -> Bool
fitsInNbits Int
13 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tandi") Operand
o1 Operand
o2 Operand
o3
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: AND error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
OR Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tor") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Int -> Bool
isUnsignOp (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i), Int -> Int -> Bool
fitsInNbits Int
13 (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tori") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, (OpImm (ImmInt Int
i)) <- Operand
o3, Int -> Bool
isUnsignOp (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i), Int -> Int -> Bool
fitsInNbits Int
13 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tori") Operand
o1 Operand
o2 Operand
o3
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: OR error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
XOR Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\txor") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Int -> Bool
isUnsignOp (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i), Int -> Int -> Bool
fitsInNbits Int
13 (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\txori") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, (OpImm (ImmInt Int
i)) <- Operand
o3, Int -> Bool
isUnsignOp (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i), Int -> Int -> Bool
fitsInNbits Int
13 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\txori") Operand
o1 Operand
o2 Operand
o3
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: XOR error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
NOR Operand
o1 Operand
o2 Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tnor") Operand
o1 Operand
o2 Operand
o3
ANDN Operand
o1 Operand
o2 Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tandn") Operand
o1 Operand
o2 Operand
o3
ORN Operand
o1 Operand
o2 Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\torn") Operand
o1 Operand
o2 Operand
o3
Instr
NOP -> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tnop"
NEG Operand
o1 Operand
o2
| Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfneg.s") Operand
o1 Operand
o2
| Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfneg.d") Operand
o1 Operand
o2
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsub.w" ) Operand
o1 Operand
zero Operand
o2
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsub.d" ) Operand
o1 Operand
zero Operand
o2
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: NEG error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2)
MOV Operand
o1 Operand
o2
| Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfmov.s") Operand
o1 Operand
o2
| Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfmov.d") Operand
o1 Operand
o2
| Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isImmZero Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o1 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovgr2fr.w") Operand
o1 Operand
zero
| Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isImmZero Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o1 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovgr2fr.d") Operand
o1 Operand
zero
| Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Bool -> Bool
not (Operand -> Bool
isFloatOp Operand
o2) Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o1 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovgr2fr.w") Operand
o1 Operand
o2
| Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Bool -> Bool
not (Operand -> Bool
isFloatOp Operand
o2) Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o1 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovgr2fr.d") Operand
o1 Operand
o2
| Bool -> Bool
not (Operand -> Bool
isFloatOp Operand
o1) Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovfr2gr.s") Operand
o1 Operand
o2
| Bool -> Bool
not (Operand -> Bool
isFloatOp Operand
o1) Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovfr2gr.d") Operand
o1 Operand
o2
| OpReg Width
W64 Reg
_ <- Operand
o1, Operand -> Bool
isImmOp Operand
o2, (OpImm (ImmInteger Integer
i)) <- Operand
o2, Int -> Int -> Bool
fitsInNbits Int
12 (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i) ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
x0 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2]
| OpReg Width
W64 Reg
_ <- Operand
o1, Operand -> Bool
isImmOp Operand
o2, (OpImm (ImmInt Int
i)) <- Operand
o2, Int -> Int -> Bool
fitsInNbits Int
12 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
x0 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2]
| OpReg Width
_ Reg
_ <- Operand
o1, Operand -> Bool
isImmOp Operand
o2, (OpImm (ImmInteger Integer
i)) <- Operand
o2, Int -> Int -> Bool
fitsInNbits Int
12 (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i) ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
x0 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbstrpick.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform (Imm -> Operand
OpImm (Int -> Imm
ImmInt ((Width -> Int
widthToInt (Width -> Int) -> Width -> Int
forall a b. (a -> b) -> a -> b
$ Operand -> Width
widthFromOpReg Operand
o1) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) )) Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", 0"
]
| OpReg Width
_ Reg
_ <- Operand
o1, Operand -> Bool
isImmOp Operand
o2, (OpImm (ImmInt Int
i)) <- Operand
o2, Int -> Int -> Bool
fitsInNbits Int
12 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
x0 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbstrpick.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform (Imm -> Operand
OpImm (Int -> Imm
ImmInt ((Width -> Int
widthToInt (Width -> Int) -> Width -> Int
forall a b. (a -> b) -> a -> b
$ Operand -> Width
widthFromOpReg Operand
o1) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) )) Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", 0"
]
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmove") Operand
o1 Operand
o2
| OpReg Width
_ Reg
_ <- Operand
o1, OpReg Width
_ Reg
_ <- Operand
o2 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbstrpick.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform (Imm -> Operand
OpImm (Int -> Imm
ImmInt ((Width -> Int
widthToInt (Width -> Width -> Width
forall a. Ord a => a -> a -> a
min (Operand -> Width
widthFromOpReg Operand
o1) (Operand -> Width
widthFromOpReg Operand
o2))) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1))) Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", 0"
]
| Operand -> Bool
isImmOp Operand
o2 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tli.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2]
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: MOV error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2)
CSET Cond
cond Operand
dst Operand
o1 Operand
o2 -> case Cond
cond of
Cond
EQ | Operand -> Bool
isIntOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isIntOp Operand
o2 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
Operand -> Operand -> Line doc
subFor Operand
o1 Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsltui" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
1))
]
Cond
EQ | Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o2 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfcmp.seq.d $fcc0," Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovcf2gr" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", $fcc0"
]
Cond
EQ | Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o2 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfcmp.seq.s $fcc0," Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovcf2gr" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", $fcc0"
]
Cond
NE | Operand -> Bool
isIntOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isIntOp Operand
o2 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
Operand -> Operand -> Line doc
subFor Operand
o1 Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsltu" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"$r0" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst
]
Cond
NE | Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o2 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfcmp.cune.d $fcc0," Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovcf2gr" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", $fcc0"
]
Cond
NE | Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o2 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfcmp.cune.s $fcc0," Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovcf2gr" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", $fcc0"
]
Cond
SLT -> [Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [ Operand -> Operand -> Line doc
sltFor Operand
o1 Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 ]
Cond
SLE ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
Operand -> Operand -> Line doc
sltFor Operand
o1 Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\txori" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
1))
]
Cond
SGE ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
Operand -> Operand -> Line doc
sltFor Operand
o1 Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\txori" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
1))
]
Cond
SGT -> [Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [ Operand -> Operand -> Line doc
sltFor Operand
o1 Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 ]
Cond
ULT -> [Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [ Operand -> Operand -> Line doc
sltuFor Operand
o1 Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 ]
Cond
ULE ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
Operand -> Operand -> Line doc
sltuFor Operand
o1 Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\txori" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
1))
]
Cond
UGE ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
Operand -> Operand -> Line doc
sltuFor Operand
o1 Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\txori" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
1))
]
Cond
UGT -> [Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [ Operand -> Operand -> Line doc
sltuFor Operand
o1 Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 ]
Cond
FLT | Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o2 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfcmp.slt.d $fcc0," Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovcf2gr" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", $fcc0"
]
Cond
FLE | Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o2 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfcmp.sle.d $fcc0," Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovcf2gr" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", $fcc0"
]
Cond
FGT | Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o2 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfcmp.slt.d $fcc0," Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovcf2gr" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", $fcc0"
]
Cond
FGE | Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o2 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfcmp.sle.d $fcc0," Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovcf2gr" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", $fcc0"
]
Cond
FLT | Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o2 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfcmp.slt.s $fcc0," Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovcf2gr" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", $fcc0"
]
Cond
FLE | Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o2 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfcmp.sle.s $fcc0," Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovcf2gr" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", $fcc0"
]
Cond
FGT | Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o2 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfcmp.slt.s $fcc0," Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovcf2gr" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", $fcc0"
]
Cond
FGE | Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o2 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfcmp.sle.s $fcc0," Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovcf2gr" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
", $fcc0"
]
Cond
_ -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: CSET error: " (Cond -> SDoc
forall doc. IsLine doc => Cond -> doc
pprCond Cond
cond SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst 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
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2)
where
subFor :: Operand -> Operand -> Line doc
subFor Operand
o1 Operand
o2 | (OpReg Width
W64 Reg
_) <- Operand
dst, (OpReg Width
W64 Reg
_) <- Operand
o1, (OpImm Imm
_) <- Operand
o2 =
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform (Operand -> Operand
negOp Operand
o2)
| (OpReg Width
W64 Reg
_) <- Operand
dst, (OpReg Width
W64 Reg
_) <- Operand
o1,(OpReg Width
W64 Reg
_) <- Operand
o2 =
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsub.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2
| Bool
otherwise = String -> SDoc -> Line doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: unknown subFor format: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
dst)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2)
sltFor :: Operand -> Operand -> Line doc
sltFor Operand
o1 Operand
o2 | (OpReg Width
W64 Reg
_) <- Operand
dst, (OpReg Width
W64 Reg
_) <- Operand
o1, (OpImm Imm
_) <- Operand
o2 = String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tslti"
| (OpReg Width
W64 Reg
_) <- Operand
dst, (OpReg Width
W64 Reg
_) <- Operand
o1, (OpReg Width
W64 Reg
_) <- Operand
o2 = String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tslt"
| Bool
otherwise = String -> SDoc -> Line doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: unknown sltFor format: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
dst)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2)
sltuFor :: Operand -> Operand -> Line doc
sltuFor Operand
o1 Operand
o2 | (OpReg Width
W64 Reg
_) <- Operand
dst, (OpReg Width
W64 Reg
_) <- Operand
o1, (OpImm Imm
_) <- Operand
o2 = String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsltui"
| (OpReg Width
W64 Reg
_) <- Operand
dst, (OpReg Width
W64 Reg
_) <- Operand
o1, (OpReg Width
W64 Reg
_) <- Operand
o2 = String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsltu"
| Bool
otherwise = String -> SDoc -> Line doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: unknown sltuFor format: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
dst)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
dst SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2)
MUL Operand
o1 Operand
o2 Operand
o3
| Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o3 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfmul.s") Operand
o1 Operand
o2 Operand
o3
| Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o3 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfmul.d") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, OpReg Width
W32 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmul.w") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmul.d") Operand
o1 Operand
o2 Operand
o3
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: MUL error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
MULW Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, OpReg Width
W32 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmulw.d.w") Operand
o1 Operand
o2 Operand
o3
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: MULW error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
MULWU Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, OpReg Width
W32 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmulw.d.wu") Operand
o1 Operand
o2 Operand
o3
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: MULWU error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
MULH Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, OpReg Width
W32 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmulh.w") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o2 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmulh.d") Operand
o1 Operand
o2 Operand
o3
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: MULH error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
MULHU Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, OpReg Width
W32 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmulh.wu") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmulh.du") Operand
o1 Operand
o2 Operand
o3
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: MULHU error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
DIV Operand
o1 Operand
o2 Operand
o3
| Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o3 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isSingleOp Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfdiv.s") Operand
o1 Operand
o2 Operand
o3
| Operand -> Bool
isFloatOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isFloatOp Operand
o3 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o1 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o2 Bool -> Bool -> Bool
&& Operand -> Bool
isDoubleOp Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfdiv.d") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, OpReg Width
W32 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tdiv.w") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tdiv.d") Operand
o1 Operand
o2 Operand
o3
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: DIV error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
DIVU Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, OpReg Width
W32 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tdiv.wu") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tdiv.du") Operand
o1 Operand
o2 Operand
o3
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: DIVU error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
MOD Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, OpReg Width
W32 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmod.w") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmod.d") Operand
o1 Operand
o2 Operand
o3
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: MOD error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
MODU Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, OpReg Width
W32 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmod.wu") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmod.du") Operand
o1 Operand
o2 Operand
o3
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: MODU error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
SLL Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, OpReg Width
W32 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsll.w") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsll.d") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
i, Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
32 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tslli.w" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3]
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, (OpImm (ImmInt Int
i)) <- Operand
o3, Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i, Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
32 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tslli.w" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3]
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
i, Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
64 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tslli.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3]
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, (OpImm (ImmInt Int
i)) <- Operand
o3, Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i, Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
64 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tslli.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3]
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: SLL error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
SRL Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, OpReg Width
W32 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsrl.w") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsrl.d") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
i, Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
32 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsrli.w" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3]
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, (OpImm (ImmInt Int
i)) <- Operand
o3, Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i, Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
32 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsrli.w" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3]
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
i, Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
64 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsrli.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3]
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, (OpImm (ImmInt Int
i)) <- Operand
o3, Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i, Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
64 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsrli.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3]
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: SRL error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
SRA Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, OpReg Width
W32 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsra.w") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsra.d") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
i, Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
32 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsrai.w" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3]
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, (OpImm (ImmInt Int
i)) <- Operand
o3, Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i, Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
32 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsrai.w" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3]
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
i, Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
64 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsrai.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3]
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, (OpImm (ImmInt Int
i)) <- Operand
o3, Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i, Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
64 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsrai.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3]
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: SRA error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
ROTR Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, OpReg Width
W32 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\trotr.w") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, OpReg Width
W64 Reg
_ <- Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\trotr.d") Operand
o1 Operand
o2 Operand
o3
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
i, Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
32 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\trotri.w" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3]
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2, (OpImm (ImmInt Int
i)) <- Operand
o3, Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i, Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
32 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\trotri.w" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3]
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, (OpImm (ImmInteger Integer
i)) <- Operand
o3, Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
i, Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
64 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\trotri.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3]
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2, (OpImm (ImmInt Int
i)) <- Operand
o3, Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i, Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
64 ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\trotri.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3]
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: ROTR error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o3)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3)
EXT Operand
o1 Operand
o2
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W8 Reg
_ <- Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\text.w.b") Operand
o1 Operand
o2
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W16 Reg
_ <- Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\text.w.h") Operand
o1 Operand
o2
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: EXT error: " ((Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o1)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Operand -> Width
widthFromOpReg Operand
o2)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2)
CLO Operand
o1 Operand
o2
| OpReg Width
W32 Reg
_ <- Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tclo.w") Operand
o1 Operand
o2
| OpReg Width
W64 Reg
_ <- Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tclo.d") Operand
o1 Operand
o2
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: CLO error" (Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2)
CLZ Operand
o1 Operand
o2
| OpReg Width
W32 Reg
_ <- Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tclz.w") Operand
o1 Operand
o2
| OpReg Width
W64 Reg
_ <- Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tclz.d") Operand
o1 Operand
o2
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: CLZ error" (Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2)
CTO Operand
o1 Operand
o2
| OpReg Width
W32 Reg
_ <- Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tcto.w") Operand
o1 Operand
o2
| OpReg Width
W64 Reg
_ <- Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tcto.d") Operand
o1 Operand
o2
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: CTO error" (Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2)
CTZ Operand
o1 Operand
o2
| OpReg Width
W32 Reg
_ <- Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tctz.w") Operand
o1 Operand
o2
| OpReg Width
W64 Reg
_ <- Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tctz.d") Operand
o1 Operand
o2
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: CTZ error" (Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2)
BYTEPICK Operand
o1 Operand
o2 Operand
o3 Operand
o4
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W32 Reg
_ <- Operand
o2 -> Line doc -> Operand -> Operand -> Operand -> Operand -> doc
op4 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbytepick.w") Operand
o1 Operand
o2 Operand
o3 Operand
o4
| OpReg Width
W64 Reg
_ <- Operand
o1, OpReg Width
W64 Reg
_ <- Operand
o2 -> Line doc -> Operand -> Operand -> Operand -> Operand -> doc
op4 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbytepick.d") Operand
o1 Operand
o2 Operand
o3 Operand
o4
| Bool
otherwise -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.ppr: BYTEPICK error" (Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o4)
REVB2H Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\trevb.2h") Operand
o1 Operand
o2
REVB4H Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\trevb.4h") Operand
o1 Operand
o2
REVB2W Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\trevb.2w") Operand
o1 Operand
o2
REVBD Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\trevb.d") Operand
o1 Operand
o2
REVH2W Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\trevh.2w") Operand
o1 Operand
o2
REVHD Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\trevh.d") Operand
o1 Operand
o2
BITREV4B Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbitrev.4b") Operand
o1 Operand
o2
BITREV8B Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbitrev.8b") Operand
o1 Operand
o2
BITREVW Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbitrev.w") Operand
o1 Operand
o2
BITREVD Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbitrev.d") Operand
o1 Operand
o2
BSTRINS Format
II64 Operand
o1 Operand
o2 Operand
o3 Operand
o4 -> Line doc -> Operand -> Operand -> Operand -> Operand -> doc
op4 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbstrins.d") Operand
o1 Operand
o2 Operand
o3 Operand
o4
BSTRINS Format
II32 Operand
o1 Operand
o2 Operand
o3 Operand
o4 -> Line doc -> Operand -> Operand -> Operand -> Operand -> doc
op4 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbstrins.w") Operand
o1 Operand
o2 Operand
o3 Operand
o4
BSTRPICK Format
II64 Operand
o1 Operand
o2 Operand
o3 Operand
o4 -> Line doc -> Operand -> Operand -> Operand -> Operand -> doc
op4 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbstrpick.d") Operand
o1 Operand
o2 Operand
o3 Operand
o4
BSTRPICK Format
II32 Operand
o1 Operand
o2 Operand
o3 Operand
o4 -> Line doc -> Operand -> Operand -> Operand -> Operand -> doc
op4 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbstrpick.w") Operand
o1 Operand
o2 Operand
o3 Operand
o4
MASKEQZ Operand
o1 Operand
o2 Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmaskeqz") Operand
o1 Operand
o2 Operand
o3
MASKNEZ Operand
o1 Operand
o2 Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmasknez") Operand
o1 Operand
o2 Operand
o3
J (TReg Reg
r) -> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tjirl" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"$r1" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Width -> Reg -> Line doc
forall doc. IsLine doc => Width -> Reg -> doc
pprReg Width
W64 Reg
r Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
" 0"
J_TBL [Maybe BlockId]
_ Maybe CLabel
_ Reg
r -> Platform -> Instr -> doc
forall doc. IsDoc doc => Platform -> Instr -> doc
pprInstr Platform
platform (Target -> Instr
B (Reg -> Target
TReg Reg
r))
B (TBlock BlockId
bid) -> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tb" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
B (TLabel CLabel
lbl) -> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tb" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
lbl
B (TReg Reg
r) -> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tjr" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Width -> Reg -> Line doc
forall doc. IsLine doc => Width -> Reg -> doc
pprReg Width
W64 Reg
r
BL (TBlock BlockId
bid) [Reg]
_ -> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbl" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
BL (TLabel CLabel
lbl) [Reg]
_ -> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbl" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
lbl
BL (TReg Reg
r) [Reg]
_ -> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tjirl" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"$r1" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Width -> Reg -> Line doc
forall doc. IsLine doc => Width -> Reg -> doc
pprReg Width
W64 Reg
r Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
" 0"
CALL36 (TBlock BlockId
bid) -> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tcall36" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
CALL36 (TLabel CLabel
lbl) -> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tcall36" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
lbl
CALL36 Target
_ -> String -> doc
forall a. HasCallStack => String -> a
panic String
"LA64.ppr: CALL36: Unexpected pattern!"
TAIL36 Operand
r (TBlock BlockId
bid) -> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\ttail36" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
r Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
TAIL36 Operand
r (TLabel CLabel
lbl) -> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\ttail36" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
r Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
lbl
TAIL36 Operand
_ Target
_ -> String -> doc
forall a. HasCallStack => String -> a
panic String
"LA64.ppr: TAIL36: Unexpected pattern!"
BCOND Cond
c Operand
j Operand
d (TLabel CLabel
lbl) Operand
_t -> case Cond
c of
Cond
_ -> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\t" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Cond -> Line doc
forall doc. IsLine doc => Cond -> doc
pprBcond Cond
c Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
j Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
d Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
lbl
BCOND Cond
c Operand
j Operand
d (TBlock BlockId
bid) Operand
t -> case Cond
c of
Cond
SLE ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tslt" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
d Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
j,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbeqz" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
]
Cond
SGT ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tslt" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
d Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
j,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbnez" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
]
Cond
ULE ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsltu" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
d Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
j,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbeqz" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
]
Cond
UGT ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsltu" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
d Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
j,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbnez" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
]
Cond
EQ ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsub.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
j Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
d,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbeqz" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
]
Cond
NE ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsub.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
j Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
d,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbnez" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
]
Cond
SLT ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tslt" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
j Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
d,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbnez" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
]
Cond
SGE ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tslt" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
j Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
d,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbeqz" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
]
Cond
ULT ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsltu" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
j Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
d,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbnez" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
]
Cond
UGE ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tsltu" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
j Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
d,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbeqz" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
t Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
]
Cond
_ -> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\t" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Cond -> Line doc
forall doc. IsLine doc => Cond -> doc
pprBcond Cond
c Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
j Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
d Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
BCOND Cond
_ Operand
_ Operand
_ (TReg Reg
_) Operand
_ -> String -> doc
forall a. HasCallStack => String -> a
panic String
"LA64.ppr: BCOND: No conditional branching to registers!"
BEQZ Operand
j (TBlock BlockId
bid) ->
Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbeqz" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
j Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
BEQZ Operand
j (TLabel CLabel
lbl) ->
Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbeqz" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
j Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
lbl
BEQZ Operand
_ (TReg Reg
_) -> String -> doc
forall a. HasCallStack => String -> a
panic String
"LA64.ppr: BEQZ: No conditional branching to registers!"
BNEZ Operand
j (TBlock BlockId
bid) ->
Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbnez" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
j Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform (Unique -> CLabel
mkLocalBlockLabel (BlockId -> Unique
forall a. Uniquable a => a -> Unique
getUnique BlockId
bid))
BNEZ Operand
j (TLabel CLabel
lbl) ->
Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tbnez" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
j Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
lbl
BNEZ Operand
_ (TReg Reg
_) -> String -> doc
forall a. HasCallStack => String -> a
panic String
"LA64.ppr: BNEZ: No conditional branching to registers!"
LD Format
_fmt Operand
o1 (OpImm (ImmIndex CLabel
lbl Int
off)) ->
[Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_ [ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tla.global" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
lbl
, String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\taddi.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Int -> Line doc
forall doc. IsLine doc => Int -> doc
int Int
off
]
LD Format
_fmt Operand
o1 (OpImm (ImmCLbl CLabel
lbl)) ->
Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tla.global" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> CLabel -> Line doc
forall doc. IsLine doc => Platform -> CLabel -> doc
pprAsmLabel Platform
platform CLabel
lbl
LD Format
II8 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tld.b") Operand
o1 Operand
o2
LD Format
II16 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tld.h") Operand
o1 Operand
o2
LD Format
II32 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tld.w") Operand
o1 Operand
o2
LD Format
II64 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tld.d") Operand
o1 Operand
o2
LD Format
FF32 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfld.s") Operand
o1 Operand
o2
LD Format
FF64 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfld.d") Operand
o1 Operand
o2
LDU Format
II8 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tld.bu") Operand
o1 Operand
o2
LDU Format
II16 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tld.hu") Operand
o1 Operand
o2
LDU Format
II32 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tld.wu") Operand
o1 Operand
o2
LDU Format
II64 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tld.d") Operand
o1 Operand
o2
LDU Format
FF32 Operand
o1 o2 :: Operand
o2@(OpAddr (AddrReg Reg
_)) -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfld.s") Operand
o1 Operand
o2
LDU Format
FF32 Operand
o1 o2 :: Operand
o2@(OpAddr (AddrRegImm Reg
_ Imm
_)) -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfld.s") Operand
o1 Operand
o2
LDU Format
FF64 Operand
o1 o2 :: Operand
o2@(OpAddr (AddrReg Reg
_)) -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfld.d") Operand
o1 Operand
o2
LDU Format
FF64 Operand
o1 o2 :: Operand
o2@(OpAddr (AddrRegImm Reg
_ Imm
_)) -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfld.d") Operand
o1 Operand
o2
LDU Format
f Operand
o1 Operand
o2 -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"Unsupported unsigned load" ((String -> SDoc
forall doc. IsLine doc => String -> doc
text(String -> SDoc) -> (Format -> String) -> Format -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Format -> String
forall a. Show a => a -> String
show) Format
f SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2)
ST Format
II8 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tst.b") Operand
o1 Operand
o2
ST Format
II16 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tst.h") Operand
o1 Operand
o2
ST Format
II32 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tst.w") Operand
o1 Operand
o2
ST Format
II64 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tst.d") Operand
o1 Operand
o2
ST Format
FF32 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfst.s") Operand
o1 Operand
o2
ST Format
FF64 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfst.d") Operand
o1 Operand
o2
LDPTR Format
II32 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tldptr.w") Operand
o1 Operand
o2
LDPTR Format
II64 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tldptr.d") Operand
o1 Operand
o2
STPTR Format
II32 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tstptr.w") Operand
o1 Operand
o2
STPTR Format
II64 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tstptr.d") Operand
o1 Operand
o2
LDX Format
II8 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tldx.b") Operand
o1 Operand
o2
LDX Format
II16 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tldx.h") Operand
o1 Operand
o2
LDX Format
II32 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tldx.w") Operand
o1 Operand
o2
LDX Format
II64 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tldx.d") Operand
o1 Operand
o2
LDX Format
FF32 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfldx.s") Operand
o1 Operand
o2
LDX Format
FF64 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfldx.d") Operand
o1 Operand
o2
LDXU Format
II8 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tldx.bu") Operand
o1 Operand
o2
LDXU Format
II16 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tldx.hu") Operand
o1 Operand
o2
LDXU Format
II32 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tldx.wu") Operand
o1 Operand
o2
LDXU Format
II64 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tldx.d") Operand
o1 Operand
o2
STX Format
II8 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tstx.b") Operand
o1 Operand
o2
STX Format
II16 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tstx.h") Operand
o1 Operand
o2
STX Format
II32 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tstx.w") Operand
o1 Operand
o2
STX Format
II64 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tstx.d") Operand
o1 Operand
o2
STX Format
FF32 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfstx.s") Operand
o1 Operand
o2
STX Format
FF64 Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfstx.d") Operand
o1 Operand
o2
DBAR BarrierType
h -> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tdbar" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> BarrierType -> Line doc
forall {doc}. IsLine doc => BarrierType -> doc
pprBarrierType BarrierType
h
IBAR BarrierType
h -> Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tibar" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> BarrierType -> Line doc
forall {doc}. IsLine doc => BarrierType -> doc
pprBarrierType BarrierType
h
FCVT o1 :: Operand
o1@(OpReg Width
W32 Reg
_) o2 :: Operand
o2@(OpReg Width
W64 Reg
_) -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfcvt.s.d") Operand
o1 Operand
o2
FCVT o1 :: Operand
o1@(OpReg Width
W64 Reg
_) o2 :: Operand
o2@(OpReg Width
W32 Reg
_) -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfcvt.d.s") Operand
o1 Operand
o2
FCVT Operand
o1 Operand
o2 -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.pprInstr - impossible float conversion" (SDoc -> doc) -> SDoc -> doc
forall a b. (a -> b) -> a -> b
$
Line SDoc -> SDoc
forall doc. IsDoc doc => Line doc -> doc
line (Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 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
<> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2)
SCVTF o1 :: Operand
o1@(OpReg Width
W32 Reg
_) o2 :: Operand
o2@(OpReg Width
W32 Reg
_) -> [Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_
[
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovgr2fr.w" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tffint.s.w" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1
]
SCVTF o1 :: Operand
o1@(OpReg Width
W32 Reg
_) o2 :: Operand
o2@(OpReg Width
W64 Reg
_) -> [Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_
[
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovgr2fr.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tffint.s.l" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1
]
SCVTF o1 :: Operand
o1@(OpReg Width
W64 Reg
_) o2 :: Operand
o2@(OpReg Width
W32 Reg
_) -> [Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_
[
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovgr2fr.w" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tffint.d.w" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1
]
SCVTF o1 :: Operand
o1@(OpReg Width
W64 Reg
_) o2 :: Operand
o2@(OpReg Width
W64 Reg
_) -> [Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_
[
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovgr2fr.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tffint.d.l" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1
]
SCVTF Operand
o1 Operand
o2 -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.pprInstr - impossible integer to float conversion" (SDoc -> doc) -> SDoc -> doc
forall a b. (a -> b) -> a -> b
$
Line SDoc -> SDoc
forall doc. IsDoc doc => Line doc -> doc
line (Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 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
<> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2)
FCVTZS o1 :: Operand
o1@(OpReg Width
W32 Reg
_) o2 :: Operand
o2@(OpReg Width
W32 Reg
_) o3 :: Operand
o3@(OpReg Width
W32 Reg
_) -> [Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_
[
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfmov.s" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tftintrz.w.s" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovfr2gr.s" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfmov.s" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2
]
FCVTZS o1 :: Operand
o1@(OpReg Width
W32 Reg
_) o2 :: Operand
o2@(OpReg Width
W64 Reg
_) o3 :: Operand
o3@(OpReg Width
W64 Reg
_) -> [Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_
[
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfmov.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tftintrz.w.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovfr2gr.s" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfmov.s" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2
]
FCVTZS o1 :: Operand
o1@(OpReg Width
W64 Reg
_) o2 :: Operand
o2@(OpReg Width
W32 Reg
_) o3 :: Operand
o3@(OpReg Width
W32 Reg
_) -> [Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_
[
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfmov.s" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tftintrz.l.s" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovfr2gr.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfmov.s" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2
]
FCVTZS o1 :: Operand
o1@(OpReg Width
W64 Reg
_) o2 :: Operand
o2@(OpReg Width
W64 Reg
_) o3 :: Operand
o3@(OpReg Width
W64 Reg
_) -> [Line doc] -> doc
forall doc. IsDoc doc => [Line doc] -> doc
lines_
[
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfmov.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tftintrz.l.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tmovfr2gr.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3,
String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfmov.d" Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2
]
FCVTZS Operand
o1 Operand
o2 Operand
o3 -> String -> SDoc -> doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"LA64.pprInstr - impossible float to integer conversion" (SDoc -> doc) -> SDoc -> doc
forall a b. (a -> b) -> a -> b
$
Line SDoc -> SDoc
forall doc. IsDoc doc => Line doc -> doc
line (Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3 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
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"tmpReg:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2)
FMIN Operand
o1 Operand
o2 Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"fmin." Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> if Operand -> Bool
isSingleOp Operand
o2 then String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"s" else String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"d") Operand
o1 Operand
o2 Operand
o3
FMINA Operand
o1 Operand
o2 Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"fmina." Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> if Operand -> Bool
isSingleOp Operand
o2 then String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"s" else String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"d") Operand
o1 Operand
o2 Operand
o3
FMAX Operand
o1 Operand
o2 Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"fmax." Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> if Operand -> Bool
isSingleOp Operand
o2 then String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"s" else String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"d") Operand
o1 Operand
o2 Operand
o3
FMAXA Operand
o1 Operand
o2 Operand
o3 -> Line doc -> Operand -> Operand -> Operand -> doc
op3 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"fmaxa." Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> if Operand -> Bool
isSingleOp Operand
o2 then String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"s" else String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"d") Operand
o1 Operand
o2 Operand
o3
FABS Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"fabs." Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> if Operand -> Bool
isSingleOp Operand
o2 then String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"s" else String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"d") Operand
o1 Operand
o2
FNEG Operand
o1 Operand
o2 -> Line doc -> Operand -> Operand -> doc
op2 (String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"fneg." Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> if Operand -> Bool
isSingleOp Operand
o2 then String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"s" else String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"d") Operand
o1 Operand
o2
FMA FMASign
variant Operand
d Operand
o1 Operand
o2 Operand
o3 ->
let fma :: Line doc
fma = case FMASign
variant of
FMASign
FMAdd -> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfmadd." Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Operand -> Line doc
floatPrecission Operand
d
FMASign
FMSub -> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfmsub." Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Operand -> Line doc
floatPrecission Operand
d
FMASign
FNMAdd -> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfnmadd." Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Operand -> Line doc
floatPrecission Operand
d
FMASign
FNMSub -> String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"\tfnmsub." Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Operand -> Line doc
floatPrecission Operand
d
in Line doc -> Operand -> Operand -> Operand -> Operand -> doc
op4 Line doc
fma Operand
d Operand
o1 Operand
o2 Operand
o3
Instr
instr -> String -> doc
forall a. HasCallStack => String -> a
panic (String -> doc) -> String -> doc
forall a b. (a -> b) -> a -> b
$ String
"LA64.pprInstr - Unknown instruction: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Instr -> String
instrCon Instr
instr)
where op2 :: Line doc -> Operand -> Operand -> doc
op2 Line doc
op Operand
o1 Operand
o2 = Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ Line doc
op Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2
op3 :: Line doc -> Operand -> Operand -> Operand -> doc
op3 Line doc
op Operand
o1 Operand
o2 Operand
o3 = Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ Line doc
op Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3
op4 :: Line doc -> Operand -> Operand -> Operand -> Operand -> doc
op4 Line doc
op Operand
o1 Operand
o2 Operand
o3 Operand
o4 = Line doc -> doc
forall doc. IsDoc doc => Line doc -> doc
line (Line doc -> doc) -> Line doc -> doc
forall a b. (a -> b) -> a -> b
$ Line doc
op Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o1 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o2 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o3 Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<> Line doc
forall doc. IsLine doc => doc
comma Line doc -> Line doc -> Line doc
forall doc. IsLine doc => doc -> doc -> doc
<+> Platform -> Operand -> Line doc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o4
pprBarrierType :: BarrierType -> doc
pprBarrierType BarrierType
Hint0 = String -> doc
forall doc. IsLine doc => String -> doc
text String
"0x0"
floatPrecission :: Operand -> Line doc
floatPrecission Operand
o | Operand -> Bool
isSingleOp Operand
o = String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"s"
| Operand -> Bool
isDoubleOp Operand
o = String -> Line doc
forall doc. IsLine doc => String -> doc
text String
"d"
| Bool
otherwise = String -> SDoc -> Line doc
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"Impossible floating point precission: " (Platform -> Operand -> SDoc
forall doc. IsLine doc => Platform -> Operand -> doc
pprOp Platform
platform Operand
o)
pprBcond :: IsLine doc => Cond -> doc
pprBcond :: forall doc. IsLine doc => Cond -> doc
pprBcond Cond
c = String -> doc
forall doc. IsLine doc => String -> doc
text String
"b" doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<> Cond -> doc
forall doc. IsLine doc => Cond -> doc
pprCond Cond
c
pprCond :: IsLine doc => Cond -> doc
pprCond :: forall doc. IsLine doc => Cond -> doc
pprCond Cond
c = case Cond
c of
Cond
EQ -> String -> doc
forall doc. IsLine doc => String -> doc
text String
"eq"
Cond
NE -> String -> doc
forall doc. IsLine doc => String -> doc
text String
"ne"
Cond
SLT -> String -> doc
forall doc. IsLine doc => String -> doc
text String
"lt"
Cond
SGE -> String -> doc
forall doc. IsLine doc => String -> doc
text String
"ge"
Cond
ULT -> String -> doc
forall doc. IsLine doc => String -> doc
text String
"ltu"
Cond
UGE -> String -> doc
forall doc. IsLine doc => String -> doc
text String
"geu"
Cond
SLE -> String -> doc
forall doc. IsLine doc => String -> doc
text String
"sle->ge"
Cond
SGT -> String -> doc
forall doc. IsLine doc => String -> doc
text String
"sgt->lt"
Cond
ULE -> String -> doc
forall doc. IsLine doc => String -> doc
text String
"ule->geu"
Cond
UGT -> String -> doc
forall doc. IsLine doc => String -> doc
text String
"ugt->ltu"
Cond
_ -> String -> doc
forall a. HasCallStack => String -> a
panic (String -> doc) -> String -> doc
forall a b. (a -> b) -> a -> b
$ String
"LA64.ppr: non-implemented branch condition: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Cond -> String
forall a. Show a => a -> String
show Cond
c