{-# LANGUAGE LambdaCase #-}
module GHC.CmmToAsm.X86.Ppr (
        pprNatCmmDecl,
        pprData,
        pprInstr,
        pprFormat,
        pprImm,
        pprDataItem,
)
where
import GHC.Prelude
import GHC.Platform
import GHC.Platform.Reg
import GHC.CmmToAsm.X86.Regs
import GHC.CmmToAsm.X86.Instr
import GHC.CmmToAsm.X86.Cond
import GHC.CmmToAsm.Config
import GHC.CmmToAsm.Format
import GHC.CmmToAsm.Types
import GHC.CmmToAsm.Utils
import GHC.CmmToAsm.Ppr
import GHC.Cmm              hiding (topInfoTable)
import GHC.Cmm.Dataflow.Collections
import GHC.Cmm.Dataflow.Label
import GHC.Cmm.BlockId
import GHC.Cmm.CLabel
import GHC.Types.Basic (Alignment, mkAlignment, alignmentBytes)
import GHC.Types.Unique ( pprUniqueAlways )
import GHC.Utils.Outputable
import GHC.Utils.Panic
import Data.Word
pprProcAlignment :: NCGConfig -> SDoc
pprProcAlignment :: NCGConfig -> SDoc
pprProcAlignment NCGConfig
config = SDoc -> (Int -> SDoc) -> Maybe Int -> SDoc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe SDoc
empty (Platform -> Alignment -> SDoc
pprAlign Platform
platform (Alignment -> SDoc) -> (Int -> Alignment) -> Int -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Alignment
mkAlignment) (NCGConfig -> Maybe Int
ncgProcAlignment NCGConfig
config)
   where
      platform :: Platform
platform = NCGConfig -> Platform
ncgPlatform NCGConfig
config
pprNatCmmDecl :: NCGConfig -> NatCmmDecl (Alignment, RawCmmStatics) Instr -> SDoc
pprNatCmmDecl :: NCGConfig -> NatCmmDecl (Alignment, RawCmmStatics) Instr -> SDoc
pprNatCmmDecl NCGConfig
config (CmmData Section
section (Alignment, RawCmmStatics)
dats) =
  NCGConfig -> Section -> SDoc
pprSectionAlign NCGConfig
config Section
section SDoc -> SDoc -> SDoc
$$ NCGConfig -> (Alignment, RawCmmStatics) -> SDoc
pprDatas NCGConfig
config (Alignment, RawCmmStatics)
dats
pprNatCmmDecl NCGConfig
config proc :: NatCmmDecl (Alignment, RawCmmStatics) Instr
proc@(CmmProc LabelMap RawCmmStatics
top_info CLabel
lbl [GlobalReg]
_ (ListGraph [GenBasicBlock Instr]
blocks)) =
  let platform :: Platform
platform = NCGConfig -> Platform
ncgPlatform NCGConfig
config in
  NCGConfig -> SDoc
pprProcAlignment NCGConfig
config SDoc -> SDoc -> SDoc
$$
  case NatCmmDecl (Alignment, RawCmmStatics) Instr -> Maybe RawCmmStatics
forall a i b. GenCmmDecl a (LabelMap i) (ListGraph b) -> Maybe i
topInfoTable NatCmmDecl (Alignment, RawCmmStatics) Instr
proc of
    Maybe RawCmmStatics
Nothing ->
        
        NCGConfig -> Section -> SDoc
pprSectionAlign NCGConfig
config (SectionType -> CLabel -> Section
Section SectionType
Text CLabel
lbl) SDoc -> SDoc -> SDoc
$$
        NCGConfig -> SDoc
pprProcAlignment NCGConfig
config SDoc -> SDoc -> SDoc
$$
        NCGConfig -> CLabel -> SDoc
pprProcLabel NCGConfig
config CLabel
lbl SDoc -> SDoc -> SDoc
$$
        Platform -> CLabel -> SDoc
pprLabel Platform
platform CLabel
lbl SDoc -> SDoc -> SDoc
$$ 
        [SDoc] -> SDoc
vcat ((GenBasicBlock Instr -> SDoc) -> [GenBasicBlock Instr] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (NCGConfig -> LabelMap RawCmmStatics -> GenBasicBlock Instr -> SDoc
pprBasicBlock NCGConfig
config LabelMap RawCmmStatics
top_info) [GenBasicBlock Instr]
blocks) SDoc -> SDoc -> SDoc
$$
        Bool -> SDoc -> SDoc
ppWhen (NCGConfig -> Bool
ncgDwarfEnabled NCGConfig
config) (Platform -> CLabel -> SDoc
pprBlockEndLabel Platform
platform CLabel
lbl SDoc -> SDoc -> SDoc
$$ Platform -> CLabel -> SDoc
pprProcEndLabel Platform
platform CLabel
lbl) SDoc -> SDoc -> SDoc
$$
        Platform -> CLabel -> SDoc
pprSizeDecl Platform
platform CLabel
lbl
    Just (CmmStaticsRaw CLabel
info_lbl [CmmStatic]
_) ->
      NCGConfig -> Section -> SDoc
pprSectionAlign NCGConfig
config (SectionType -> CLabel -> Section
Section SectionType
Text CLabel
info_lbl) SDoc -> SDoc -> SDoc
$$
      NCGConfig -> SDoc
pprProcAlignment NCGConfig
config SDoc -> SDoc -> SDoc
$$
      NCGConfig -> CLabel -> SDoc
pprProcLabel NCGConfig
config CLabel
lbl SDoc -> SDoc -> SDoc
$$
      (if Platform -> Bool
platformHasSubsectionsViaSymbols Platform
platform
          then Platform -> CLabel -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform (CLabel -> CLabel
mkDeadStripPreventer CLabel
info_lbl) SDoc -> SDoc -> SDoc
<> SDoc
colon
          else SDoc
empty) SDoc -> SDoc -> SDoc
$$
      [SDoc] -> SDoc
vcat ((GenBasicBlock Instr -> SDoc) -> [GenBasicBlock Instr] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (NCGConfig -> LabelMap RawCmmStatics -> GenBasicBlock Instr -> SDoc
pprBasicBlock NCGConfig
config LabelMap RawCmmStatics
top_info) [GenBasicBlock Instr]
blocks) SDoc -> SDoc -> SDoc
$$
      Bool -> SDoc -> SDoc
ppWhen (NCGConfig -> Bool
ncgDwarfEnabled NCGConfig
config) (Platform -> CLabel -> SDoc
pprProcEndLabel Platform
platform CLabel
info_lbl) SDoc -> SDoc -> SDoc
$$
      
      
      (if Platform -> Bool
platformHasSubsectionsViaSymbols Platform
platform
       then 
                String -> SDoc
text String
"\t.long "
            SDoc -> SDoc -> SDoc
<+> Platform -> CLabel -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform CLabel
info_lbl
            SDoc -> SDoc -> SDoc
<+> Char -> SDoc
char Char
'-'
            SDoc -> SDoc -> SDoc
<+> Platform -> CLabel -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform (CLabel -> CLabel
mkDeadStripPreventer CLabel
info_lbl)
       else SDoc
empty) SDoc -> SDoc -> SDoc
$$
      Platform -> CLabel -> SDoc
pprSizeDecl Platform
platform CLabel
info_lbl
pprProcLabel :: NCGConfig -> CLabel -> SDoc
pprProcLabel :: NCGConfig -> CLabel -> SDoc
pprProcLabel NCGConfig
config CLabel
lbl
  | NCGConfig -> Bool
ncgExposeInternalSymbols NCGConfig
config
  , Just SDoc
lbl' <- Module -> CLabel -> Maybe SDoc
ppInternalProcLabel (NCGConfig -> Module
ncgThisModule NCGConfig
config) CLabel
lbl
  = SDoc
lbl' SDoc -> SDoc -> SDoc
<> SDoc
colon
  | Bool
otherwise
  = SDoc
empty
pprProcEndLabel :: Platform -> CLabel 
                -> SDoc
pprProcEndLabel :: Platform -> CLabel -> SDoc
pprProcEndLabel Platform
platform CLabel
lbl =
    Platform -> CLabel -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform (CLabel -> CLabel
mkAsmTempProcEndLabel CLabel
lbl) SDoc -> SDoc -> SDoc
<> SDoc
colon
pprBlockEndLabel :: Platform -> CLabel 
                 -> SDoc
pprBlockEndLabel :: Platform -> CLabel -> SDoc
pprBlockEndLabel Platform
platform CLabel
lbl =
    Platform -> CLabel -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform (CLabel -> CLabel
mkAsmTempEndLabel CLabel
lbl) SDoc -> SDoc -> SDoc
<> SDoc
colon
pprSizeDecl :: Platform -> CLabel -> SDoc
pprSizeDecl :: Platform -> CLabel -> SDoc
pprSizeDecl Platform
platform CLabel
lbl
 = if OS -> Bool
osElfTarget (Platform -> OS
platformOS Platform
platform)
   then String -> SDoc
text String
"\t.size" SDoc -> SDoc -> SDoc
<+> Platform -> CLabel -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform CLabel
lbl SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
", .-" SDoc -> SDoc -> SDoc
<> Platform -> CLabel -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform CLabel
lbl
   else SDoc
empty
pprBasicBlock :: NCGConfig -> LabelMap RawCmmStatics -> NatBasicBlock Instr -> SDoc
pprBasicBlock :: NCGConfig -> LabelMap RawCmmStatics -> GenBasicBlock Instr -> SDoc
pprBasicBlock NCGConfig
config LabelMap RawCmmStatics
info_env (BasicBlock BlockId
blockid [Instr]
instrs)
  = SDoc -> SDoc
maybe_infotable (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
    Platform -> CLabel -> SDoc
pprLabel Platform
platform CLabel
asmLbl SDoc -> SDoc -> SDoc
$$
    [SDoc] -> SDoc
vcat ((Instr -> SDoc) -> [Instr] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (Platform -> Instr -> SDoc
pprInstr Platform
platform) [Instr]
instrs) SDoc -> SDoc -> SDoc
$$
    Bool -> SDoc -> SDoc
ppWhen (NCGConfig -> Bool
ncgDwarfEnabled NCGConfig
config) (
      
      
      Platform -> CLabel -> SDoc
pprBlockEndLabel Platform
platform CLabel
asmLbl
      SDoc -> SDoc -> SDoc
<> Platform -> CLabel -> SDoc
pprProcEndLabel Platform
platform CLabel
asmLbl
    )
  where
    asmLbl :: CLabel
asmLbl = BlockId -> CLabel
blockLbl BlockId
blockid
    platform :: Platform
platform = NCGConfig -> Platform
ncgPlatform NCGConfig
config
    maybe_infotable :: SDoc -> SDoc
maybe_infotable SDoc
c = case KeyOf LabelMap -> LabelMap RawCmmStatics -> Maybe RawCmmStatics
forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
mapLookup BlockId
KeyOf LabelMap
blockid LabelMap RawCmmStatics
info_env of
       Maybe RawCmmStatics
Nothing -> SDoc
c
       Just (CmmStaticsRaw CLabel
infoLbl [CmmStatic]
info) ->
           Platform -> SectionType -> SDoc
pprAlignForSection Platform
platform SectionType
Text SDoc -> SDoc -> SDoc
$$
           SDoc
infoTableLoc SDoc -> SDoc -> SDoc
$$
           [SDoc] -> SDoc
vcat ((CmmStatic -> SDoc) -> [CmmStatic] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (NCGConfig -> CmmStatic -> SDoc
pprData NCGConfig
config) [CmmStatic]
info) SDoc -> SDoc -> SDoc
$$
           Platform -> CLabel -> SDoc
pprLabel Platform
platform CLabel
infoLbl SDoc -> SDoc -> SDoc
$$
           SDoc
c SDoc -> SDoc -> SDoc
$$
           Bool -> SDoc -> SDoc
ppWhen (NCGConfig -> Bool
ncgDwarfEnabled NCGConfig
config) (Platform -> CLabel -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform (CLabel -> CLabel
mkAsmTempEndLabel CLabel
infoLbl) SDoc -> SDoc -> SDoc
<> SDoc
colon)
    
    
    infoTableLoc :: SDoc
infoTableLoc = case [Instr]
instrs of
      (l :: Instr
l@LOCATION{} : [Instr]
_) -> Platform -> Instr -> SDoc
pprInstr Platform
platform Instr
l
      [Instr]
_other             -> SDoc
empty
pprDatas :: NCGConfig -> (Alignment, RawCmmStatics) -> SDoc
pprDatas :: NCGConfig -> (Alignment, RawCmmStatics) -> SDoc
pprDatas NCGConfig
config (Alignment
_, 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 -> SDoc
pprGloblDecl (NCGConfig -> Platform
ncgPlatform NCGConfig
config) CLabel
alias
    SDoc -> SDoc -> SDoc
$$ String -> SDoc
text String
".equiv" SDoc -> SDoc -> SDoc
<+> Platform -> CLabel -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc (NCGConfig -> Platform
ncgPlatform NCGConfig
config) CLabel
alias SDoc -> SDoc -> SDoc
<> SDoc
comma SDoc -> SDoc -> SDoc
<> Platform -> CmmLit -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc (NCGConfig -> Platform
ncgPlatform NCGConfig
config) (CLabel -> CmmLit
CmmLabel CLabel
ind')
pprDatas NCGConfig
config (Alignment
align, (CmmStaticsRaw CLabel
lbl [CmmStatic]
dats))
 = [SDoc] -> SDoc
vcat (Platform -> Alignment -> SDoc
pprAlign Platform
platform Alignment
align SDoc -> [SDoc] -> [SDoc]
forall a. a -> [a] -> [a]
: Platform -> CLabel -> SDoc
pprLabel Platform
platform CLabel
lbl SDoc -> [SDoc] -> [SDoc]
forall a. a -> [a] -> [a]
: (CmmStatic -> SDoc) -> [CmmStatic] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (NCGConfig -> CmmStatic -> SDoc
pprData NCGConfig
config) [CmmStatic]
dats)
   where
      platform :: Platform
platform = NCGConfig -> Platform
ncgPlatform NCGConfig
config
pprData :: NCGConfig -> CmmStatic -> SDoc
pprData :: NCGConfig -> CmmStatic -> SDoc
pprData NCGConfig
_config (CmmString ByteString
str) = ByteString -> SDoc
pprString ByteString
str
pprData NCGConfig
_config (CmmFileEmbed String
path) = String -> SDoc
pprFileEmbed String
path
pprData NCGConfig
config (CmmUninitialised Int
bytes)
 = 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 -> SDoc
text String
".space " SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
bytes
         else String -> SDoc
text String
".skip "  SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
bytes
pprData NCGConfig
config (CmmStaticLit CmmLit
lit) = NCGConfig -> CmmLit -> SDoc
pprDataItem NCGConfig
config CmmLit
lit
pprGloblDecl :: Platform -> CLabel -> SDoc
pprGloblDecl :: Platform -> CLabel -> SDoc
pprGloblDecl Platform
platform CLabel
lbl
  | Bool -> Bool
not (CLabel -> Bool
externallyVisibleCLabel CLabel
lbl) = SDoc
empty
  | Bool
otherwise = String -> SDoc
text String
".globl " SDoc -> SDoc -> SDoc
<> Platform -> CLabel -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform CLabel
lbl
pprLabelType' :: Platform -> CLabel -> SDoc
pprLabelType' :: Platform -> CLabel -> SDoc
pprLabelType' Platform
platform CLabel
lbl =
  if CLabel -> Bool
isCFunctionLabel CLabel
lbl Bool -> Bool -> Bool
|| Bool
functionOkInfoTable then
    String -> SDoc
text String
"@function"
  else
    String -> SDoc
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
isConInfoTableLabel CLabel
lbl)
pprTypeDecl :: Platform -> CLabel -> SDoc
pprTypeDecl :: Platform -> CLabel -> SDoc
pprTypeDecl Platform
platform CLabel
lbl
    = if OS -> Bool
osElfTarget (Platform -> OS
platformOS Platform
platform) Bool -> Bool -> Bool
&& CLabel -> Bool
externallyVisibleCLabel CLabel
lbl
      then String -> SDoc
text String
".type " SDoc -> SDoc -> SDoc
<> Platform -> CLabel -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform CLabel
lbl SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
", " SDoc -> SDoc -> SDoc
<> Platform -> CLabel -> SDoc
pprLabelType' Platform
platform CLabel
lbl
      else SDoc
empty
pprLabel :: Platform -> CLabel -> SDoc
pprLabel :: Platform -> CLabel -> SDoc
pprLabel Platform
platform CLabel
lbl =
   Platform -> CLabel -> SDoc
pprGloblDecl Platform
platform CLabel
lbl
   SDoc -> SDoc -> SDoc
$$ Platform -> CLabel -> SDoc
pprTypeDecl Platform
platform CLabel
lbl
   SDoc -> SDoc -> SDoc
$$ (Platform -> CLabel -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform CLabel
lbl SDoc -> SDoc -> SDoc
<> SDoc
colon)
pprAlign :: Platform -> Alignment -> SDoc
pprAlign :: Platform -> Alignment -> SDoc
pprAlign Platform
platform Alignment
alignment
        = String -> SDoc
text String
".align " SDoc -> SDoc -> SDoc
<> Int -> SDoc
int (Platform -> Int
alignmentOn Platform
platform)
  where
        bytes :: Int
bytes = Alignment -> Int
alignmentBytes Alignment
alignment
        alignmentOn :: Platform -> Int
alignmentOn Platform
platform = if Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSDarwin
                               then Int -> Int
log2 Int
bytes
                               else      Int
bytes
        log2 :: Int -> Int  
        log2 :: Int -> Int
log2 Int
1 = Int
0
        log2 Int
2 = Int
1
        log2 Int
4 = Int
2
        log2 Int
8 = Int
3
        log2 Int
n = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int
log2 (Int
n Int -> Int -> Int
forall a. Integral a => a -> a -> a
`quot` Int
2)
pprReg :: Platform -> Format -> Reg -> SDoc
pprReg :: Platform -> Format -> Reg -> SDoc
pprReg Platform
platform Format
f Reg
r
  = case Reg
r of
      RegReal    (RealRegSingle Int
i) ->
          if Platform -> Bool
target32Bit Platform
platform then Format -> Int -> SDoc
ppr32_reg_no Format
f Int
i
                                  else Format -> Int -> SDoc
ppr64_reg_no Format
f Int
i
      RegVirtual (VirtualRegI  Unique
u)  -> String -> SDoc
text String
"%vI_"   SDoc -> SDoc -> SDoc
<> Unique -> SDoc
pprUniqueAlways Unique
u
      RegVirtual (VirtualRegHi Unique
u)  -> String -> SDoc
text String
"%vHi_"  SDoc -> SDoc -> SDoc
<> Unique -> SDoc
pprUniqueAlways Unique
u
      RegVirtual (VirtualRegF  Unique
u)  -> String -> SDoc
text String
"%vF_"   SDoc -> SDoc -> SDoc
<> Unique -> SDoc
pprUniqueAlways Unique
u
      RegVirtual (VirtualRegD  Unique
u)  -> String -> SDoc
text String
"%vD_"   SDoc -> SDoc -> SDoc
<> Unique -> SDoc
pprUniqueAlways Unique
u
  where
    ppr32_reg_no :: Format -> Int -> SDoc
    ppr32_reg_no :: Format -> Int -> SDoc
ppr32_reg_no Format
II8   = Int -> SDoc
ppr32_reg_byte
    ppr32_reg_no Format
II16  = Int -> SDoc
forall a. (Eq a, Num a) => a -> SDoc
ppr32_reg_word
    ppr32_reg_no Format
_     = Int -> SDoc
ppr32_reg_long
    ppr32_reg_byte :: Int -> SDoc
ppr32_reg_byte Int
i =
      case Int
i of {
         Int
0 -> String -> SDoc
text String
"%al";     Int
1 -> String -> SDoc
text String
"%bl";
         Int
2 -> String -> SDoc
text String
"%cl";     Int
3 -> String -> SDoc
text String
"%dl";
        Int
_  -> String -> SDoc
text String
"very naughty I386 byte register: " SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
i
      }
    ppr32_reg_word :: a -> SDoc
ppr32_reg_word a
i =
      case a
i of {
         a
0 -> String -> SDoc
text String
"%ax";     a
1 -> String -> SDoc
text String
"%bx";
         a
2 -> String -> SDoc
text String
"%cx";     a
3 -> String -> SDoc
text String
"%dx";
         a
4 -> String -> SDoc
text String
"%si";     a
5 -> String -> SDoc
text String
"%di";
         a
6 -> String -> SDoc
text String
"%bp";     a
7 -> String -> SDoc
text String
"%sp";
        a
_  -> String -> SDoc
text String
"very naughty I386 word register"
      }
    ppr32_reg_long :: Int -> SDoc
ppr32_reg_long Int
i =
      case Int
i of {
         Int
0 -> String -> SDoc
text String
"%eax";    Int
1 -> String -> SDoc
text String
"%ebx";
         Int
2 -> String -> SDoc
text String
"%ecx";    Int
3 -> String -> SDoc
text String
"%edx";
         Int
4 -> String -> SDoc
text String
"%esi";    Int
5 -> String -> SDoc
text String
"%edi";
         Int
6 -> String -> SDoc
text String
"%ebp";    Int
7 -> String -> SDoc
text String
"%esp";
         Int
_  -> Int -> SDoc
ppr_reg_float Int
i
      }
    ppr64_reg_no :: Format -> Int -> SDoc
    ppr64_reg_no :: Format -> Int -> SDoc
ppr64_reg_no Format
II8   = Int -> SDoc
ppr64_reg_byte
    ppr64_reg_no Format
II16  = Int -> SDoc
forall a. (Eq a, Num a) => a -> SDoc
ppr64_reg_word
    ppr64_reg_no Format
II32  = Int -> SDoc
forall a. (Eq a, Num a) => a -> SDoc
ppr64_reg_long
    ppr64_reg_no Format
_     = Int -> SDoc
ppr64_reg_quad
    ppr64_reg_byte :: Int -> SDoc
ppr64_reg_byte Int
i =
      case Int
i of {
         Int
0 -> String -> SDoc
text String
"%al";      Int
1 -> String -> SDoc
text String
"%bl";
         Int
2 -> String -> SDoc
text String
"%cl";      Int
3 -> String -> SDoc
text String
"%dl";
         Int
4 -> String -> SDoc
text String
"%sil";     Int
5 -> String -> SDoc
text String
"%dil"; 
         Int
6 -> String -> SDoc
text String
"%bpl";     Int
7 -> String -> SDoc
text String
"%spl";
         Int
8 -> String -> SDoc
text String
"%r8b";     Int
9 -> String -> SDoc
text String
"%r9b";
        Int
10 -> String -> SDoc
text String
"%r10b";   Int
11 -> String -> SDoc
text String
"%r11b";
        Int
12 -> String -> SDoc
text String
"%r12b";   Int
13 -> String -> SDoc
text String
"%r13b";
        Int
14 -> String -> SDoc
text String
"%r14b";   Int
15 -> String -> SDoc
text String
"%r15b";
        Int
_  -> String -> SDoc
text String
"very naughty x86_64 byte register: " SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
i
      }
    ppr64_reg_word :: a -> SDoc
ppr64_reg_word a
i =
      case a
i of {
         a
0 -> String -> SDoc
text String
"%ax";      a
1 -> String -> SDoc
text String
"%bx";
         a
2 -> String -> SDoc
text String
"%cx";      a
3 -> String -> SDoc
text String
"%dx";
         a
4 -> String -> SDoc
text String
"%si";      a
5 -> String -> SDoc
text String
"%di";
         a
6 -> String -> SDoc
text String
"%bp";      a
7 -> String -> SDoc
text String
"%sp";
         a
8 -> String -> SDoc
text String
"%r8w";     a
9 -> String -> SDoc
text String
"%r9w";
        a
10 -> String -> SDoc
text String
"%r10w";   a
11 -> String -> SDoc
text String
"%r11w";
        a
12 -> String -> SDoc
text String
"%r12w";   a
13 -> String -> SDoc
text String
"%r13w";
        a
14 -> String -> SDoc
text String
"%r14w";   a
15 -> String -> SDoc
text String
"%r15w";
        a
_  -> String -> SDoc
text String
"very naughty x86_64 word register"
      }
    ppr64_reg_long :: a -> SDoc
ppr64_reg_long a
i =
      case a
i of {
         a
0 -> String -> SDoc
text String
"%eax";    a
1  -> String -> SDoc
text String
"%ebx";
         a
2 -> String -> SDoc
text String
"%ecx";    a
3  -> String -> SDoc
text String
"%edx";
         a
4 -> String -> SDoc
text String
"%esi";    a
5  -> String -> SDoc
text String
"%edi";
         a
6 -> String -> SDoc
text String
"%ebp";    a
7  -> String -> SDoc
text String
"%esp";
         a
8 -> String -> SDoc
text String
"%r8d";    a
9  -> String -> SDoc
text String
"%r9d";
        a
10 -> String -> SDoc
text String
"%r10d";   a
11 -> String -> SDoc
text String
"%r11d";
        a
12 -> String -> SDoc
text String
"%r12d";   a
13 -> String -> SDoc
text String
"%r13d";
        a
14 -> String -> SDoc
text String
"%r14d";   a
15 -> String -> SDoc
text String
"%r15d";
        a
_  -> String -> SDoc
text String
"very naughty x86_64 register"
      }
    ppr64_reg_quad :: Int -> SDoc
ppr64_reg_quad Int
i =
      case Int
i of {
         Int
0 -> String -> SDoc
text String
"%rax";     Int
1 -> String -> SDoc
text String
"%rbx";
         Int
2 -> String -> SDoc
text String
"%rcx";     Int
3 -> String -> SDoc
text String
"%rdx";
         Int
4 -> String -> SDoc
text String
"%rsi";     Int
5 -> String -> SDoc
text String
"%rdi";
         Int
6 -> String -> SDoc
text String
"%rbp";     Int
7 -> String -> SDoc
text String
"%rsp";
         Int
8 -> String -> SDoc
text String
"%r8";      Int
9 -> String -> SDoc
text String
"%r9";
        Int
10 -> String -> SDoc
text String
"%r10";    Int
11 -> String -> SDoc
text String
"%r11";
        Int
12 -> String -> SDoc
text String
"%r12";    Int
13 -> String -> SDoc
text String
"%r13";
        Int
14 -> String -> SDoc
text String
"%r14";    Int
15 -> String -> SDoc
text String
"%r15";
        Int
_  -> Int -> SDoc
ppr_reg_float Int
i
      }
ppr_reg_float :: Int -> SDoc
ppr_reg_float :: Int -> SDoc
ppr_reg_float Int
i = case Int
i of
        Int
16 -> String -> SDoc
text String
"%xmm0" ;   Int
17 -> String -> SDoc
text String
"%xmm1"
        Int
18 -> String -> SDoc
text String
"%xmm2" ;   Int
19 -> String -> SDoc
text String
"%xmm3"
        Int
20 -> String -> SDoc
text String
"%xmm4" ;   Int
21 -> String -> SDoc
text String
"%xmm5"
        Int
22 -> String -> SDoc
text String
"%xmm6" ;   Int
23 -> String -> SDoc
text String
"%xmm7"
        Int
24 -> String -> SDoc
text String
"%xmm8" ;   Int
25 -> String -> SDoc
text String
"%xmm9"
        Int
26 -> String -> SDoc
text String
"%xmm10";   Int
27 -> String -> SDoc
text String
"%xmm11"
        Int
28 -> String -> SDoc
text String
"%xmm12";   Int
29 -> String -> SDoc
text String
"%xmm13"
        Int
30 -> String -> SDoc
text String
"%xmm14";   Int
31 -> String -> SDoc
text String
"%xmm15"
        Int
_  -> String -> SDoc
text String
"very naughty x86 register"
pprFormat :: Format -> SDoc
pprFormat :: Format -> SDoc
pprFormat Format
x = case Format
x of
  Format
II8   -> String -> SDoc
text String
"b"
  Format
II16  -> String -> SDoc
text String
"w"
  Format
II32  -> String -> SDoc
text String
"l"
  Format
II64  -> String -> SDoc
text String
"q"
  Format
FF32  -> String -> SDoc
text String
"ss"      
  Format
FF64  -> String -> SDoc
text String
"sd"      
pprFormat_x87 :: Format -> SDoc
pprFormat_x87 :: Format -> SDoc
pprFormat_x87 Format
x = case Format
x of
  Format
FF32  -> String -> SDoc
text String
"s"
  Format
FF64  -> String -> SDoc
text String
"l"
  Format
_     -> String -> SDoc
forall a. String -> a
panic String
"X86.Ppr.pprFormat_x87"
pprCond :: Cond -> SDoc
pprCond :: Cond -> SDoc
pprCond Cond
c = case Cond
c of {
  Cond
GEU     -> String -> SDoc
text String
"ae";   Cond
LU   -> String -> SDoc
text String
"b";
  Cond
EQQ     -> String -> SDoc
text String
"e";    Cond
GTT  -> String -> SDoc
text String
"g";
  Cond
GE      -> String -> SDoc
text String
"ge";   Cond
GU   -> String -> SDoc
text String
"a";
  Cond
LTT     -> String -> SDoc
text String
"l";    Cond
LE   -> String -> SDoc
text String
"le";
  Cond
LEU     -> String -> SDoc
text String
"be";   Cond
NE   -> String -> SDoc
text String
"ne";
  Cond
NEG     -> String -> SDoc
text String
"s";    Cond
POS  -> String -> SDoc
text String
"ns";
  Cond
CARRY   -> String -> SDoc
text String
"c";   Cond
OFLO  -> String -> SDoc
text String
"o";
  Cond
PARITY  -> String -> SDoc
text String
"p";   Cond
NOTPARITY -> String -> SDoc
text String
"np";
  Cond
ALWAYS  -> String -> SDoc
text String
"mp"}
pprImm :: Platform -> Imm -> SDoc
pprImm :: Platform -> Imm -> SDoc
pprImm Platform
platform = \case
   ImmInt Int
i            -> Int -> SDoc
int Int
i
   ImmInteger Integer
i        -> Integer -> SDoc
integer Integer
i
   ImmCLbl CLabel
l           -> Platform -> CLabel -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform CLabel
l
   ImmIndex CLabel
l Int
i        -> Platform -> CLabel -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform CLabel
l SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'+' SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
i
   ImmLit SDoc
s            -> SDoc
s
   ImmFloat Rational
f          -> Float -> SDoc
float (Float -> SDoc) -> Float -> SDoc
forall a b. (a -> b) -> a -> b
$ Rational -> Float
forall a. Fractional a => Rational -> a
fromRational Rational
f
   ImmDouble Rational
d         -> Double -> SDoc
double (Double -> SDoc) -> Double -> SDoc
forall a b. (a -> b) -> a -> b
$ Rational -> Double
forall a. Fractional a => Rational -> a
fromRational Rational
d
   ImmConstantSum Imm
a Imm
b  -> Platform -> Imm -> SDoc
pprImm Platform
platform Imm
a SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'+' SDoc -> SDoc -> SDoc
<> Platform -> Imm -> SDoc
pprImm Platform
platform Imm
b
   ImmConstantDiff Imm
a Imm
b -> Platform -> Imm -> SDoc
pprImm Platform
platform Imm
a SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'-' SDoc -> SDoc -> SDoc
<> SDoc
lparen SDoc -> SDoc -> SDoc
<> Platform -> Imm -> SDoc
pprImm Platform
platform Imm
b SDoc -> SDoc -> SDoc
<> SDoc
rparen
pprAddr :: Platform -> AddrMode -> SDoc
pprAddr :: Platform -> AddrMode -> SDoc
pprAddr Platform
platform (ImmAddr Imm
imm Int
off)
  = let pp_imm :: SDoc
pp_imm = Platform -> Imm -> SDoc
pprImm Platform
platform Imm
imm
    in
    if (Int
off Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) then
        SDoc
pp_imm
    else if (Int
off Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0) then
        SDoc
pp_imm SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
off
    else
        SDoc
pp_imm SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'+' SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
off
pprAddr Platform
platform (AddrBaseIndex EABase
base EAIndex
index Imm
displacement)
  = let
        pp_disp :: SDoc
pp_disp  = Imm -> SDoc
ppr_disp Imm
displacement
        pp_off :: SDoc -> SDoc
pp_off SDoc
p = SDoc
pp_disp SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'(' SDoc -> SDoc -> SDoc
<> SDoc
p SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
')'
        pp_reg :: Reg -> SDoc
pp_reg Reg
r = Platform -> Format -> Reg -> SDoc
pprReg Platform
platform (Bool -> Format
archWordFormat (Platform -> Bool
target32Bit Platform
platform)) Reg
r
    in
    case (EABase
base, EAIndex
index) of
      (EABase
EABaseNone,  EAIndex
EAIndexNone) -> SDoc
pp_disp
      (EABaseReg Reg
b, EAIndex
EAIndexNone) -> SDoc -> SDoc
pp_off (Reg -> SDoc
pp_reg Reg
b)
      (EABase
EABaseRip,   EAIndex
EAIndexNone) -> SDoc -> SDoc
pp_off (String -> SDoc
text String
"%rip")
      (EABase
EABaseNone,  EAIndex Reg
r Int
i) -> SDoc -> SDoc
pp_off (SDoc
comma SDoc -> SDoc -> SDoc
<> Reg -> SDoc
pp_reg Reg
r SDoc -> SDoc -> SDoc
<> SDoc
comma SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
i)
      (EABaseReg Reg
b, EAIndex Reg
r Int
i) -> SDoc -> SDoc
pp_off (Reg -> SDoc
pp_reg Reg
b SDoc -> SDoc -> SDoc
<> SDoc
comma SDoc -> SDoc -> SDoc
<> Reg -> SDoc
pp_reg Reg
r
                                       SDoc -> SDoc -> SDoc
<> SDoc
comma SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
i)
      (EABase, EAIndex)
_                         -> String -> SDoc
forall a. String -> a
panic String
"X86.Ppr.pprAddr: no match"
  where
    ppr_disp :: Imm -> SDoc
ppr_disp (ImmInt Int
0) = SDoc
empty
    ppr_disp Imm
imm        = Platform -> Imm -> SDoc
pprImm Platform
platform Imm
imm
pprSectionAlign :: NCGConfig -> Section -> SDoc
pprSectionAlign :: NCGConfig -> Section -> SDoc
pprSectionAlign NCGConfig
_config (Section (OtherSection String
_) CLabel
_) =
     String -> SDoc
forall a. String -> a
panic String
"X86.Ppr.pprSectionAlign: unknown section"
pprSectionAlign NCGConfig
config sec :: Section
sec@(Section SectionType
seg CLabel
_) =
    NCGConfig -> Section -> SDoc
pprSectionHeader NCGConfig
config Section
sec SDoc -> SDoc -> SDoc
$$
    Platform -> SectionType -> SDoc
pprAlignForSection (NCGConfig -> Platform
ncgPlatform NCGConfig
config) SectionType
seg
pprAlignForSection :: Platform -> SectionType -> SDoc
pprAlignForSection :: Platform -> SectionType -> SDoc
pprAlignForSection Platform
platform SectionType
seg =
    String -> SDoc
text String
".align " SDoc -> SDoc -> SDoc
<>
    case Platform -> OS
platformOS Platform
platform of
      
      OS
OSDarwin
       | Platform -> Bool
target32Bit Platform
platform ->
          case SectionType
seg of
           SectionType
ReadOnlyData16    -> Int -> SDoc
int Int
4
           SectionType
CString           -> Int -> SDoc
int Int
1
           SectionType
_                 -> Int -> SDoc
int Int
2
       | Bool
otherwise ->
          case SectionType
seg of
           SectionType
ReadOnlyData16    -> Int -> SDoc
int Int
4
           SectionType
CString           -> Int -> SDoc
int Int
1
           SectionType
_                 -> Int -> SDoc
int Int
3
      
      OS
_
       | Platform -> Bool
target32Bit Platform
platform ->
          case SectionType
seg of
           SectionType
Text              -> String -> SDoc
text String
"4,0x90"
           SectionType
ReadOnlyData16    -> Int -> SDoc
int Int
16
           SectionType
CString           -> Int -> SDoc
int Int
1
           SectionType
_                 -> Int -> SDoc
int Int
4
       | Bool
otherwise ->
          case SectionType
seg of
           SectionType
ReadOnlyData16    -> Int -> SDoc
int Int
16
           SectionType
CString           -> Int -> SDoc
int Int
1
           SectionType
_                 -> Int -> SDoc
int Int
8
pprDataItem :: NCGConfig -> CmmLit -> SDoc
pprDataItem :: NCGConfig -> CmmLit -> SDoc
pprDataItem NCGConfig
config CmmLit
lit
  = [SDoc] -> SDoc
vcat (Format -> CmmLit -> [SDoc]
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 -> [SDoc]
ppr_item Format
II8   CmmLit
_ = [String -> SDoc
text String
"\t.byte\t" SDoc -> SDoc -> SDoc
<> Platform -> Imm -> SDoc
pprImm Platform
platform Imm
imm]
        ppr_item Format
II16  CmmLit
_ = [String -> SDoc
text String
"\t.word\t" SDoc -> SDoc -> SDoc
<> Platform -> Imm -> SDoc
pprImm Platform
platform Imm
imm]
        ppr_item Format
II32  CmmLit
_ = [String -> SDoc
text String
"\t.long\t" SDoc -> SDoc -> SDoc
<> Platform -> Imm -> SDoc
pprImm Platform
platform Imm
imm]
        ppr_item Format
FF32 CmmLit
_ = [String -> SDoc
text String
"\t.float\t" SDoc -> SDoc -> SDoc
<> Platform -> Imm -> SDoc
pprImm Platform
platform Imm
imm]
        ppr_item Format
FF64 CmmLit
_ = [String -> SDoc
text String
"\t.double\t" SDoc -> SDoc -> SDoc
<> Platform -> Imm -> SDoc
pprImm Platform
platform Imm
imm]
        ppr_item Format
II64 CmmLit
_
            = case Platform -> OS
platformOS Platform
platform of
              OS
OSDarwin
               | Platform -> Bool
target32Bit Platform
platform ->
                  case CmmLit
lit of
                  CmmInt Integer
x Width
_ ->
                      [String -> SDoc
text String
"\t.long\t"
                          SDoc -> SDoc -> SDoc
<> Int -> SDoc
int (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x :: Word32)),
                       String -> SDoc
text String
"\t.long\t"
                          SDoc -> SDoc -> SDoc
<> Int -> SDoc
int (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
                              (Integer -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
x Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
32) :: Word32))]
                  CmmLit
_ -> String -> [SDoc]
forall a. String -> a
panic String
"X86.Ppr.ppr_item: no match for II64"
               | Bool
otherwise ->
                  [String -> SDoc
text String
"\t.quad\t" SDoc -> SDoc -> SDoc
<> Platform -> Imm -> SDoc
pprImm Platform
platform Imm
imm]
              OS
_
               | Platform -> Bool
target32Bit Platform
platform ->
                  [String -> SDoc
text String
"\t.quad\t" SDoc -> SDoc -> SDoc
<> Platform -> Imm -> SDoc
pprImm Platform
platform Imm
imm]
               | Bool
otherwise ->
                  
                  
                  
                  
                  
                  
                  
                  
                  
                  
                  case CmmLit
lit of
                  
                  CmmLabelDiffOff CLabel
_ CLabel
_ Int
_ Width
_ ->
                      [String -> SDoc
text String
"\t.long\t" SDoc -> SDoc -> SDoc
<> Platform -> Imm -> SDoc
pprImm Platform
platform Imm
imm,
                       String -> SDoc
text String
"\t.long\t0"]
                  CmmLit
_ ->
                      [String -> SDoc
text String
"\t.quad\t" SDoc -> SDoc -> SDoc
<> Platform -> Imm -> SDoc
pprImm Platform
platform Imm
imm]
asmComment :: SDoc -> SDoc
 SDoc
c = SDoc -> SDoc
whenPprDebug (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"# " SDoc -> SDoc -> SDoc
<> SDoc
c
pprInstr :: Platform -> Instr -> SDoc
pprInstr :: Platform -> Instr -> SDoc
pprInstr Platform
platform Instr
i = case Instr
i of
   COMMENT SDoc
s
      -> SDoc -> SDoc
asmComment SDoc
s
   LOCATION Int
file Int
line Int
col String
_name
      -> String -> SDoc
text String
"\t.loc " SDoc -> SDoc -> SDoc
<> Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
file SDoc -> SDoc -> SDoc
<+> Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
line SDoc -> SDoc -> SDoc
<+> Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
col
   DELTA Int
d
      -> SDoc -> SDoc
asmComment (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text (String
"\tdelta = " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
d)
   NEWBLOCK BlockId
_
      -> String -> SDoc
forall a. String -> a
panic String
"pprInstr: NEWBLOCK"
   UNWIND CLabel
lbl UnwindTable
d
      -> SDoc -> SDoc
asmComment (String -> SDoc
text String
"\tunwind = " SDoc -> SDoc -> SDoc
<> Platform -> UnwindTable -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform UnwindTable
d)
         SDoc -> SDoc -> SDoc
$$ Platform -> CLabel -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform CLabel
lbl SDoc -> SDoc -> SDoc
<> SDoc
colon
   LDATA Section
_ (Alignment, RawCmmStatics)
_
      -> String -> SDoc
forall a. String -> a
panic String
"pprInstr: LDATA"
   
   
   MOV Format
format (OpImm (ImmInt Int
0)) dst :: Operand
dst@(OpReg Reg
_)
     -> Platform -> Instr -> SDoc
pprInstr Platform
platform (Format -> Operand -> Operand -> Instr
XOR Format
format' Operand
dst Operand
dst)
        where format' :: Format
format' = case Format
format of
                Format
II64 -> Format
II32          
                Format
_    -> Format
format
   MOV Format
format Operand
src Operand
dst
     -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"mov") Format
format Operand
src Operand
dst
   CMOV Cond
cc Format
format Operand
src Reg
dst
     -> SDoc -> Format -> Cond -> Operand -> Reg -> SDoc
pprCondOpReg (String -> SDoc
text String
"cmov") Format
format Cond
cc Operand
src Reg
dst
   MOVZxL Format
II32 Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"mov") Format
II32 Operand
src Operand
dst
        
        
        
        
   MOVZxL Format
formats Operand
src Operand
dst
      -> SDoc -> Format -> Format -> Operand -> Operand -> SDoc
pprFormatOpOpCoerce (String -> SDoc
text String
"movz") Format
formats Format
II32 Operand
src Operand
dst
        
        
        
   MOVSxL Format
formats Operand
src Operand
dst
      -> SDoc -> Format -> Format -> Operand -> Operand -> SDoc
pprFormatOpOpCoerce (String -> SDoc
text String
"movs") Format
formats (Bool -> Format
archWordFormat (Platform -> Bool
target32Bit Platform
platform)) Operand
src Operand
dst
   
   
   LEA Format
format (OpAddr (AddrBaseIndex (EABaseReg Reg
reg1) (EAIndex Reg
reg2 Int
1) (ImmInt Int
0))) dst :: Operand
dst@(OpReg Reg
reg3)
      | Reg
reg1 Reg -> Reg -> Bool
forall a. Eq a => a -> a -> Bool
== Reg
reg3
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"add") Format
format (Reg -> Operand
OpReg Reg
reg2) Operand
dst
   LEA Format
format (OpAddr (AddrBaseIndex (EABaseReg Reg
reg1) (EAIndex Reg
reg2 Int
1) (ImmInt Int
0))) dst :: Operand
dst@(OpReg Reg
reg3)
      | Reg
reg2 Reg -> Reg -> Bool
forall a. Eq a => a -> a -> Bool
== Reg
reg3
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"add") Format
format (Reg -> Operand
OpReg Reg
reg1) Operand
dst
   LEA Format
format (OpAddr (AddrBaseIndex (EABaseReg Reg
reg1) EAIndex
EAIndexNone Imm
displ)) dst :: Operand
dst@(OpReg Reg
reg3)
      | Reg
reg1 Reg -> Reg -> Bool
forall a. Eq a => a -> a -> Bool
== Reg
reg3
      -> Platform -> Instr -> SDoc
pprInstr Platform
platform (Format -> Operand -> Operand -> Instr
ADD Format
format (Imm -> Operand
OpImm Imm
displ) Operand
dst)
   LEA Format
format Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"lea") Format
format Operand
src Operand
dst
   ADD Format
format (OpImm (ImmInt (-1))) Operand
dst
      -> SDoc -> Format -> Operand -> SDoc
pprFormatOp (String -> SDoc
text String
"dec") Format
format Operand
dst
   ADD Format
format (OpImm (ImmInt Int
1)) Operand
dst
      -> SDoc -> Format -> Operand -> SDoc
pprFormatOp (String -> SDoc
text String
"inc") Format
format Operand
dst
   ADD Format
format Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"add") Format
format Operand
src Operand
dst
   ADC Format
format Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"adc") Format
format Operand
src Operand
dst
   SUB Format
format Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"sub") Format
format Operand
src Operand
dst
   SBB Format
format Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"sbb") Format
format Operand
src Operand
dst
   IMUL Format
format Operand
op1 Operand
op2
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"imul") Format
format Operand
op1 Operand
op2
   ADD_CC Format
format Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"add") Format
format Operand
src Operand
dst
   SUB_CC Format
format Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"sub") Format
format Operand
src Operand
dst
   
   
   
   
   AND Format
II64 src :: Operand
src@(OpImm (ImmInteger Integer
mask)) Operand
dst
      | Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
mask Bool -> Bool -> Bool
&& Integer
mask Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0xffffffff
      -> Platform -> Instr -> SDoc
pprInstr Platform
platform (Format -> Operand -> Operand -> Instr
AND Format
II32 Operand
src Operand
dst)
   AND Format
FF32 Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprOpOp (String -> SDoc
text String
"andps") Format
FF32 Operand
src Operand
dst
   AND Format
FF64 Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprOpOp (String -> SDoc
text String
"andpd") Format
FF64 Operand
src Operand
dst
   AND Format
format Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"and") Format
format Operand
src Operand
dst
   OR  Format
format Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"or")  Format
format Operand
src Operand
dst
   XOR Format
FF32 Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprOpOp (String -> SDoc
text String
"xorps") Format
FF32 Operand
src Operand
dst
   XOR Format
FF64 Operand
src Operand
dst
      ->  SDoc -> Format -> Operand -> Operand -> SDoc
pprOpOp (String -> SDoc
text String
"xorpd") Format
FF64 Operand
src Operand
dst
   XOR Format
format Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"xor") Format
format Operand
src Operand
dst
   POPCNT Format
format Operand
src Reg
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprOpOp (String -> SDoc
text String
"popcnt") Format
format Operand
src (Reg -> Operand
OpReg Reg
dst)
   LZCNT Format
format Operand
src Reg
dst
      ->  SDoc -> Format -> Operand -> Operand -> SDoc
pprOpOp (String -> SDoc
text String
"lzcnt") Format
format Operand
src (Reg -> Operand
OpReg Reg
dst)
   TZCNT Format
format Operand
src Reg
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprOpOp (String -> SDoc
text String
"tzcnt") Format
format Operand
src (Reg -> Operand
OpReg Reg
dst)
   BSF Format
format Operand
src Reg
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprOpOp (String -> SDoc
text String
"bsf") Format
format Operand
src (Reg -> Operand
OpReg Reg
dst)
   BSR Format
format Operand
src Reg
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprOpOp (String -> SDoc
text String
"bsr") Format
format Operand
src (Reg -> Operand
OpReg Reg
dst)
   PDEP Format
format Operand
src Operand
mask Reg
dst
      -> SDoc -> Format -> Operand -> Operand -> Reg -> SDoc
pprFormatOpOpReg (String -> SDoc
text String
"pdep") Format
format Operand
src Operand
mask Reg
dst
   PEXT Format
format Operand
src Operand
mask Reg
dst
      -> SDoc -> Format -> Operand -> Operand -> Reg -> SDoc
pprFormatOpOpReg (String -> SDoc
text String
"pext") Format
format Operand
src Operand
mask Reg
dst
   PREFETCH PrefetchVariant
NTA Format
format Operand
src
      -> SDoc -> Format -> Operand -> SDoc
pprFormatOp_ (String -> SDoc
text String
"prefetchnta") Format
format Operand
src
   PREFETCH PrefetchVariant
Lvl0 Format
format Operand
src
      -> SDoc -> Format -> Operand -> SDoc
pprFormatOp_ (String -> SDoc
text String
"prefetcht0") Format
format Operand
src
   PREFETCH PrefetchVariant
Lvl1 Format
format Operand
src
      -> SDoc -> Format -> Operand -> SDoc
pprFormatOp_ (String -> SDoc
text String
"prefetcht1") Format
format Operand
src
   PREFETCH PrefetchVariant
Lvl2 Format
format Operand
src
      -> SDoc -> Format -> Operand -> SDoc
pprFormatOp_ (String -> SDoc
text String
"prefetcht2") Format
format Operand
src
   NOT Format
format Operand
op
      -> SDoc -> Format -> Operand -> SDoc
pprFormatOp (String -> SDoc
text String
"not") Format
format Operand
op
   BSWAP Format
format Reg
op
      -> SDoc -> Format -> Operand -> SDoc
pprFormatOp (String -> SDoc
text String
"bswap") Format
format (Reg -> Operand
OpReg Reg
op)
   NEGI Format
format Operand
op
      -> SDoc -> Format -> Operand -> SDoc
pprFormatOp (String -> SDoc
text String
"neg") Format
format Operand
op
   SHL Format
format Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprShift (String -> SDoc
text String
"shl") Format
format Operand
src Operand
dst
   SAR Format
format Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprShift (String -> SDoc
text String
"sar") Format
format Operand
src Operand
dst
   SHR Format
format Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprShift (String -> SDoc
text String
"shr") Format
format Operand
src Operand
dst
   BT Format
format Imm
imm Operand
src
      -> SDoc -> Format -> Imm -> Operand -> SDoc
pprFormatImmOp (String -> SDoc
text String
"bt") Format
format Imm
imm Operand
src
   CMP Format
format Operand
src Operand
dst
     | Format -> Bool
isFloatFormat Format
format -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"ucomi") Format
format Operand
src Operand
dst 
     | Bool
otherwise            -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"cmp")   Format
format Operand
src Operand
dst
   TEST Format
format Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"test") Format
format' Operand
src Operand
dst
         where
        
        
        
        
        
        
        
        
        
        
          format' :: Format
format' = case (Operand
src,Operand
dst) of
           (OpImm (ImmInteger Integer
mask), OpReg Reg
dstReg)
             | Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
mask Bool -> Bool -> Bool
&& Integer
mask Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
128 -> Platform -> Reg -> Format
minSizeOfReg Platform
platform Reg
dstReg
           (Operand, Operand)
_ -> Format
format
          minSizeOfReg :: Platform -> Reg -> Format
minSizeOfReg Platform
platform (RegReal (RealRegSingle Int
i))
            | Platform -> Bool
target32Bit Platform
platform Bool -> Bool -> Bool
&& Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
3        = Format
II8  
            | Platform -> Bool
target32Bit Platform
platform Bool -> Bool -> Bool
&& Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
7        = Format
II16 
            | Bool -> Bool
not (Platform -> Bool
target32Bit Platform
platform) Bool -> Bool -> Bool
&& Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
15 = Format
II8  
          minSizeOfReg Platform
_ Reg
_ = Format
format                 
   PUSH Format
format Operand
op
      -> SDoc -> Format -> Operand -> SDoc
pprFormatOp (String -> SDoc
text String
"push") Format
format Operand
op
   POP Format
format Operand
op
      -> SDoc -> Format -> Operand -> SDoc
pprFormatOp (String -> SDoc
text String
"pop") Format
format Operand
op
   Instr
NOP
      -> String -> SDoc
text String
"\tnop"
   CLTD Format
II8
      -> String -> SDoc
text String
"\tcbtw"
   CLTD Format
II16
      -> String -> SDoc
text String
"\tcwtd"
   CLTD Format
II32
      -> String -> SDoc
text String
"\tcltd"
   CLTD Format
II64
      -> String -> SDoc
text String
"\tcqto"
   CLTD Format
x
      -> String -> SDoc
forall a. String -> a
panic (String -> SDoc) -> String -> SDoc
forall a b. (a -> b) -> a -> b
$ String
"pprInstr: CLTD " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Format -> String
forall a. Show a => a -> String
show Format
x
   SETCC Cond
cond Operand
op
      -> SDoc -> Cond -> SDoc -> SDoc
pprCondInstr (String -> SDoc
text String
"set") Cond
cond (Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
II8 Operand
op)
   XCHG Format
format Operand
src Reg
val
      -> SDoc -> Format -> Operand -> Reg -> SDoc
pprFormatOpReg (String -> SDoc
text String
"xchg") Format
format Operand
src Reg
val
   JXX Cond
cond BlockId
blockid
      -> SDoc -> Cond -> SDoc -> SDoc
pprCondInstr (String -> SDoc
text String
"j") Cond
cond (Platform -> CLabel -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform CLabel
lab)
         where lab :: CLabel
lab = BlockId -> CLabel
blockLbl BlockId
blockid
   JXX_GBL Cond
cond Imm
imm
      -> SDoc -> Cond -> SDoc -> SDoc
pprCondInstr (String -> SDoc
text String
"j") Cond
cond (Platform -> Imm -> SDoc
pprImm Platform
platform Imm
imm)
   JMP (OpImm Imm
imm) [Reg]
_
      -> String -> SDoc
text String
"\tjmp " SDoc -> SDoc -> SDoc
<> Platform -> Imm -> SDoc
pprImm Platform
platform Imm
imm
   JMP Operand
op [Reg]
_
      -> String -> SDoc
text String
"\tjmp *" SDoc -> SDoc -> SDoc
<> Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform (Bool -> Format
archWordFormat (Platform -> Bool
target32Bit Platform
platform)) Operand
op
   JMP_TBL Operand
op [Maybe JumpDest]
_ Section
_ CLabel
_
      -> Platform -> Instr -> SDoc
pprInstr Platform
platform (Operand -> [Reg] -> Instr
JMP Operand
op [])
   CALL (Left Imm
imm) [Reg]
_
      -> String -> SDoc
text String
"\tcall " SDoc -> SDoc -> SDoc
<> Platform -> Imm -> SDoc
pprImm Platform
platform Imm
imm
   CALL (Right Reg
reg) [Reg]
_
      -> String -> SDoc
text String
"\tcall *" SDoc -> SDoc -> SDoc
<> Platform -> Format -> Reg -> SDoc
pprReg Platform
platform (Bool -> Format
archWordFormat (Platform -> Bool
target32Bit Platform
platform)) Reg
reg
   IDIV Format
fmt Operand
op
      -> SDoc -> Format -> Operand -> SDoc
pprFormatOp (String -> SDoc
text String
"idiv") Format
fmt Operand
op
   DIV Format
fmt Operand
op
      -> SDoc -> Format -> Operand -> SDoc
pprFormatOp (String -> SDoc
text String
"div")  Format
fmt Operand
op
   IMUL2 Format
fmt Operand
op
      -> SDoc -> Format -> Operand -> SDoc
pprFormatOp (String -> SDoc
text String
"imul") Format
fmt Operand
op
   
   MUL Format
format Operand
op1 Operand
op2
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"mul") Format
format Operand
op1 Operand
op2
   MUL2 Format
format Operand
op
      -> SDoc -> Format -> Operand -> SDoc
pprFormatOp (String -> SDoc
text String
"mul") Format
format Operand
op
   FDIV Format
format Operand
op1 Operand
op2
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"div") Format
format Operand
op1 Operand
op2
   SQRT Format
format Operand
op1 Reg
op2
      -> SDoc -> Format -> Operand -> Reg -> SDoc
pprFormatOpReg (String -> SDoc
text String
"sqrt") Format
format Operand
op1 Reg
op2
   CVTSS2SD Reg
from Reg
to
      -> SDoc -> Reg -> Reg -> SDoc
pprRegReg (String -> SDoc
text String
"cvtss2sd") Reg
from Reg
to
   CVTSD2SS Reg
from Reg
to
      -> SDoc -> Reg -> Reg -> SDoc
pprRegReg (String -> SDoc
text String
"cvtsd2ss") Reg
from Reg
to
   CVTTSS2SIQ Format
fmt Operand
from Reg
to
      -> SDoc -> Format -> Format -> Operand -> Reg -> SDoc
pprFormatFormatOpReg (String -> SDoc
text String
"cvttss2si") Format
FF32 Format
fmt Operand
from Reg
to
   CVTTSD2SIQ Format
fmt Operand
from Reg
to
      -> SDoc -> Format -> Format -> Operand -> Reg -> SDoc
pprFormatFormatOpReg (String -> SDoc
text String
"cvttsd2si") Format
FF64 Format
fmt Operand
from Reg
to
   CVTSI2SS Format
fmt Operand
from Reg
to
      -> SDoc -> Format -> Operand -> Reg -> SDoc
pprFormatOpReg (String -> SDoc
text String
"cvtsi2ss") Format
fmt Operand
from Reg
to
   CVTSI2SD Format
fmt Operand
from Reg
to
      -> SDoc -> Format -> Operand -> Reg -> SDoc
pprFormatOpReg (String -> SDoc
text String
"cvtsi2sd") Format
fmt Operand
from Reg
to
       
   FETCHGOT Reg
reg
      -> [SDoc] -> SDoc
vcat [ String -> SDoc
text String
"\tcall 1f",
                [SDoc] -> SDoc
hcat [ String -> SDoc
text String
"1:\tpopl\t", Platform -> Format -> Reg -> SDoc
pprReg Platform
platform Format
II32 Reg
reg ],
                [SDoc] -> SDoc
hcat [ String -> SDoc
text String
"\taddl\t$_GLOBAL_OFFSET_TABLE_+(.-1b), ",
                       Platform -> Format -> Reg -> SDoc
pprReg Platform
platform Format
II32 Reg
reg ]
              ]
    
    
    
    
   FETCHPC Reg
reg
      -> [SDoc] -> SDoc
vcat [ String -> SDoc
text String
"\tcall 1f",
                [SDoc] -> SDoc
hcat [ String -> SDoc
text String
"1:\tpopl\t", Platform -> Format -> Reg -> SDoc
pprReg Platform
platform Format
II32 Reg
reg ]
              ]
   
   
   g :: Instr
g@(X87Store Format
fmt  AddrMode
addr)
      -> Instr -> SDoc -> SDoc
pprX87 Instr
g ([SDoc] -> SDoc
hcat [SDoc
gtab, String -> SDoc
text String
"fstp", Format -> SDoc
pprFormat_x87 Format
fmt, SDoc
gsp, Platform -> AddrMode -> SDoc
pprAddr Platform
platform AddrMode
addr])
   
   LOCK Instr
i
      -> String -> SDoc
text String
"\tlock" SDoc -> SDoc -> SDoc
$$ Platform -> Instr -> SDoc
pprInstr Platform
platform Instr
i
   Instr
MFENCE
      -> String -> SDoc
text String
"\tmfence"
   XADD Format
format Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"xadd") Format
format Operand
src Operand
dst
   CMPXCHG Format
format Operand
src Operand
dst
      -> SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp (String -> SDoc
text String
"cmpxchg") Format
format Operand
src Operand
dst
  where
   gtab :: SDoc
   gtab :: SDoc
gtab  = Char -> SDoc
char Char
'\t'
   gsp :: SDoc
   gsp :: SDoc
gsp   = Char -> SDoc
char Char
' '
   pprX87 :: Instr -> SDoc -> SDoc
   pprX87 :: Instr -> SDoc -> SDoc
pprX87 Instr
fake SDoc
actual
      = (Char -> SDoc
char Char
'#' SDoc -> SDoc -> SDoc
<> Instr -> SDoc
pprX87Instr Instr
fake) SDoc -> SDoc -> SDoc
$$ SDoc
actual
   pprX87Instr :: Instr -> SDoc
   pprX87Instr :: Instr -> SDoc
pprX87Instr (X87Store Format
fmt AddrMode
dst) = SDoc -> Format -> AddrMode -> SDoc
pprFormatAddr (String -> SDoc
text String
"gst") Format
fmt AddrMode
dst
   pprX87Instr Instr
_ = String -> SDoc
forall a. String -> a
panic String
"X86.Ppr.pprX87Instr: no match"
   pprDollImm :: Imm -> SDoc
   pprDollImm :: Imm -> SDoc
pprDollImm Imm
i = String -> SDoc
text String
"$" SDoc -> SDoc -> SDoc
<> Platform -> Imm -> SDoc
pprImm Platform
platform Imm
i
   pprOperand :: Platform -> Format -> Operand -> SDoc
   pprOperand :: Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
f Operand
op = case Operand
op of
      OpReg Reg
r   -> Platform -> Format -> Reg -> SDoc
pprReg Platform
platform Format
f Reg
r
      OpImm Imm
i   -> Imm -> SDoc
pprDollImm Imm
i
      OpAddr AddrMode
ea -> Platform -> AddrMode -> SDoc
pprAddr Platform
platform AddrMode
ea
   pprMnemonic_  :: SDoc -> SDoc
   pprMnemonic_ :: SDoc -> SDoc
pprMnemonic_ SDoc
name =
      Char -> SDoc
char Char
'\t' SDoc -> SDoc -> SDoc
<> SDoc
name SDoc -> SDoc -> SDoc
<> SDoc
space
   pprMnemonic  :: SDoc -> Format -> SDoc
   pprMnemonic :: SDoc -> Format -> SDoc
pprMnemonic SDoc
name Format
format =
      Char -> SDoc
char Char
'\t' SDoc -> SDoc -> SDoc
<> SDoc
name SDoc -> SDoc -> SDoc
<> Format -> SDoc
pprFormat Format
format SDoc -> SDoc -> SDoc
<> SDoc
space
   pprFormatImmOp :: SDoc -> Format -> Imm -> Operand -> SDoc
   pprFormatImmOp :: SDoc -> Format -> Imm -> Operand -> SDoc
pprFormatImmOp SDoc
name Format
format Imm
imm Operand
op1
     = [SDoc] -> SDoc
hcat [
           SDoc -> Format -> SDoc
pprMnemonic SDoc
name Format
format,
           Char -> SDoc
char Char
'$',
           Platform -> Imm -> SDoc
pprImm Platform
platform Imm
imm,
           SDoc
comma,
           Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
format Operand
op1
       ]
   pprFormatOp_ :: SDoc -> Format -> Operand -> SDoc
   pprFormatOp_ :: SDoc -> Format -> Operand -> SDoc
pprFormatOp_ SDoc
name Format
format Operand
op1
     = [SDoc] -> SDoc
hcat [
           SDoc -> SDoc
pprMnemonic_ SDoc
name ,
           Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
format Operand
op1
       ]
   pprFormatOp :: SDoc -> Format -> Operand -> SDoc
   pprFormatOp :: SDoc -> Format -> Operand -> SDoc
pprFormatOp SDoc
name Format
format Operand
op1
     = [SDoc] -> SDoc
hcat [
           SDoc -> Format -> SDoc
pprMnemonic SDoc
name Format
format,
           Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
format Operand
op1
       ]
   pprFormatOpOp :: SDoc -> Format -> Operand -> Operand -> SDoc
   pprFormatOpOp :: SDoc -> Format -> Operand -> Operand -> SDoc
pprFormatOpOp SDoc
name Format
format Operand
op1 Operand
op2
     = [SDoc] -> SDoc
hcat [
           SDoc -> Format -> SDoc
pprMnemonic SDoc
name Format
format,
           Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
format Operand
op1,
           SDoc
comma,
           Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
format Operand
op2
       ]
   pprOpOp :: SDoc -> Format -> Operand -> Operand -> SDoc
   pprOpOp :: SDoc -> Format -> Operand -> Operand -> SDoc
pprOpOp SDoc
name Format
format Operand
op1 Operand
op2
     = [SDoc] -> SDoc
hcat [
           SDoc -> SDoc
pprMnemonic_ SDoc
name,
           Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
format Operand
op1,
           SDoc
comma,
           Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
format Operand
op2
       ]
   pprRegReg :: SDoc -> Reg -> Reg -> SDoc
   pprRegReg :: SDoc -> Reg -> Reg -> SDoc
pprRegReg SDoc
name Reg
reg1 Reg
reg2
     = [SDoc] -> SDoc
hcat [
           SDoc -> SDoc
pprMnemonic_ SDoc
name,
           Platform -> Format -> Reg -> SDoc
pprReg Platform
platform (Bool -> Format
archWordFormat (Platform -> Bool
target32Bit Platform
platform)) Reg
reg1,
           SDoc
comma,
           Platform -> Format -> Reg -> SDoc
pprReg Platform
platform (Bool -> Format
archWordFormat (Platform -> Bool
target32Bit Platform
platform)) Reg
reg2
       ]
   pprFormatOpReg :: SDoc -> Format -> Operand -> Reg -> SDoc
   pprFormatOpReg :: SDoc -> Format -> Operand -> Reg -> SDoc
pprFormatOpReg SDoc
name Format
format Operand
op1 Reg
reg2
     = [SDoc] -> SDoc
hcat [
           SDoc -> Format -> SDoc
pprMnemonic SDoc
name Format
format,
           Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
format Operand
op1,
           SDoc
comma,
           Platform -> Format -> Reg -> SDoc
pprReg Platform
platform (Bool -> Format
archWordFormat (Platform -> Bool
target32Bit Platform
platform)) Reg
reg2
       ]
   pprCondOpReg :: SDoc -> Format -> Cond -> Operand -> Reg -> SDoc
   pprCondOpReg :: SDoc -> Format -> Cond -> Operand -> Reg -> SDoc
pprCondOpReg SDoc
name Format
format Cond
cond Operand
op1 Reg
reg2
     = [SDoc] -> SDoc
hcat [
           Char -> SDoc
char Char
'\t',
           SDoc
name,
           Cond -> SDoc
pprCond Cond
cond,
           SDoc
space,
           Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
format Operand
op1,
           SDoc
comma,
           Platform -> Format -> Reg -> SDoc
pprReg Platform
platform Format
format Reg
reg2
       ]
   pprFormatFormatOpReg :: SDoc -> Format -> Format -> Operand -> Reg -> SDoc
   pprFormatFormatOpReg :: SDoc -> Format -> Format -> Operand -> Reg -> SDoc
pprFormatFormatOpReg SDoc
name Format
format1 Format
format2 Operand
op1 Reg
reg2
     = [SDoc] -> SDoc
hcat [
           SDoc -> Format -> SDoc
pprMnemonic SDoc
name Format
format2,
           Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
format1 Operand
op1,
           SDoc
comma,
           Platform -> Format -> Reg -> SDoc
pprReg Platform
platform Format
format2 Reg
reg2
       ]
   pprFormatOpOpReg :: SDoc -> Format -> Operand -> Operand -> Reg -> SDoc
   pprFormatOpOpReg :: SDoc -> Format -> Operand -> Operand -> Reg -> SDoc
pprFormatOpOpReg SDoc
name Format
format Operand
op1 Operand
op2 Reg
reg3
     = [SDoc] -> SDoc
hcat [
           SDoc -> Format -> SDoc
pprMnemonic SDoc
name Format
format,
           Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
format Operand
op1,
           SDoc
comma,
           Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
format Operand
op2,
           SDoc
comma,
           Platform -> Format -> Reg -> SDoc
pprReg Platform
platform Format
format Reg
reg3
       ]
   pprFormatAddr :: SDoc -> Format -> AddrMode -> SDoc
   pprFormatAddr :: SDoc -> Format -> AddrMode -> SDoc
pprFormatAddr SDoc
name Format
format  AddrMode
op
     = [SDoc] -> SDoc
hcat [
           SDoc -> Format -> SDoc
pprMnemonic SDoc
name Format
format,
           SDoc
comma,
           Platform -> AddrMode -> SDoc
pprAddr Platform
platform AddrMode
op
       ]
   pprShift :: SDoc -> Format -> Operand -> Operand -> SDoc
   pprShift :: SDoc -> Format -> Operand -> Operand -> SDoc
pprShift SDoc
name Format
format Operand
src Operand
dest
     = [SDoc] -> SDoc
hcat [
           SDoc -> Format -> SDoc
pprMnemonic SDoc
name Format
format,
           Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
II8 Operand
src,  
           SDoc
comma,
           Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
format Operand
dest
       ]
   pprFormatOpOpCoerce :: SDoc -> Format -> Format -> Operand -> Operand -> SDoc
   pprFormatOpOpCoerce :: SDoc -> Format -> Format -> Operand -> Operand -> SDoc
pprFormatOpOpCoerce SDoc
name Format
format1 Format
format2 Operand
op1 Operand
op2
     = [SDoc] -> SDoc
hcat [ Char -> SDoc
char Char
'\t', SDoc
name, Format -> SDoc
pprFormat Format
format1, Format -> SDoc
pprFormat Format
format2, SDoc
space,
           Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
format1 Operand
op1,
           SDoc
comma,
           Platform -> Format -> Operand -> SDoc
pprOperand Platform
platform Format
format2 Operand
op2
       ]
   pprCondInstr :: SDoc -> Cond -> SDoc -> SDoc
   pprCondInstr :: SDoc -> Cond -> SDoc -> SDoc
pprCondInstr SDoc
name Cond
cond SDoc
arg
     = [SDoc] -> SDoc
hcat [ Char -> SDoc
char Char
'\t', SDoc
name, Cond -> SDoc
pprCond Cond
cond, SDoc
space, SDoc
arg]