{-# LANGUAGE CPP #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE BinaryLiterals #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NumericUnderscores #-}
module GHC.CmmToAsm.AArch64.CodeGen (
cmmTopCodeGen
, generateJumpTableForInstr
)
where
#include "HsVersions.h"
import GHC.Prelude hiding (EQ)
import Data.Word
import GHC.Platform.Regs
import GHC.CmmToAsm.AArch64.Instr
import GHC.CmmToAsm.AArch64.Regs
import GHC.CmmToAsm.AArch64.Cond
import GHC.CmmToAsm.CPrim
import GHC.Cmm.DebugBlock
import GHC.CmmToAsm.Monad
( NatM, getNewRegNat
, getPicBaseMaybeNat, getPlatform, getConfig
, getDebugBlock, getFileId
)
import GHC.CmmToAsm.PIC
import GHC.CmmToAsm.Format
import GHC.CmmToAsm.Config
import GHC.CmmToAsm.Types
import GHC.Platform.Reg
import GHC.Platform
import GHC.Cmm.BlockId
import GHC.Cmm
import GHC.Cmm.Utils
import GHC.Cmm.Switch
import GHC.Cmm.CLabel
import GHC.Cmm.Dataflow.Block
import GHC.Cmm.Dataflow.Graph
import GHC.Types.Tickish ( GenTickish(..) )
import GHC.Types.SrcLoc ( srcSpanFile, srcSpanStartLine, srcSpanStartCol )
import GHC.Data.OrdList
import GHC.Utils.Outputable
import Control.Monad ( mapAndUnzipM, foldM )
import Data.Maybe
import GHC.Float
import GHC.Types.Basic
import GHC.Types.ForeignCall
import GHC.Data.FastString
import GHC.Utils.Misc
import GHC.Utils.Panic
cmmTopCodeGen
:: RawCmmDecl
-> NatM [NatCmmDecl RawCmmStatics Instr]
cmmTopCodeGen :: RawCmmDecl -> NatM [NatCmmDecl RawCmmStatics Instr]
cmmTopCodeGen _cmm :: RawCmmDecl
_cmm@(CmmProc LabelMap RawCmmStatics
info CLabel
lab [GlobalReg]
live CmmGraph
graph) = do
let blocks :: [Block CmmNode C C]
blocks = CmmGraph -> [Block CmmNode C C]
toBlockListEntryFirst CmmGraph
graph
([[NatBasicBlock Instr]]
nat_blocks,[[NatCmmDecl RawCmmStatics Instr]]
statics) <- forall (m :: * -> *) a b c.
Applicative m =>
(a -> m (b, c)) -> [a] -> m ([b], [c])
mapAndUnzipM Block CmmNode C C
-> NatM ([NatBasicBlock Instr], [NatCmmDecl RawCmmStatics Instr])
basicBlockCodeGen [Block CmmNode C C]
blocks
Maybe Reg
picBaseMb <- NatM (Maybe Reg)
getPicBaseMaybeNat
let proc :: NatCmmDecl RawCmmStatics Instr
proc = forall d h g. h -> CLabel -> [GlobalReg] -> g -> GenCmmDecl d h g
CmmProc LabelMap RawCmmStatics
info CLabel
lab [GlobalReg]
live (forall i. [GenBasicBlock i] -> ListGraph i
ListGraph forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[NatBasicBlock Instr]]
nat_blocks)
tops :: [NatCmmDecl RawCmmStatics Instr]
tops = NatCmmDecl RawCmmStatics Instr
proc forall a. a -> [a] -> [a]
: forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[NatCmmDecl RawCmmStatics Instr]]
statics
case Maybe Reg
picBaseMb of
Just Reg
_picBase -> forall a. String -> a
panic String
"AArch64.cmmTopCodeGen: picBase not implemented"
Maybe Reg
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return [NatCmmDecl RawCmmStatics Instr]
tops
cmmTopCodeGen _cmm :: RawCmmDecl
_cmm@(CmmData Section
sec RawCmmStatics
dat) = do
forall (m :: * -> *) a. Monad m => a -> m a
return [forall d h g. Section -> d -> GenCmmDecl d h g
CmmData Section
sec RawCmmStatics
dat]
basicBlockCodeGen
:: Block CmmNode C C
-> NatM ( [NatBasicBlock Instr]
, [NatCmmDecl RawCmmStatics Instr])
basicBlockCodeGen :: Block CmmNode C C
-> NatM ([NatBasicBlock Instr], [NatCmmDecl RawCmmStatics Instr])
basicBlockCodeGen Block CmmNode C C
block = do
NCGConfig
config <- NatM NCGConfig
getConfig
let (CmmNode C O
_, Block CmmNode O O
nodes, CmmNode O C
tail) = forall (n :: Extensibility -> Extensibility -> *).
Block n C C -> (n C O, Block n O O, n O C)
blockSplit Block CmmNode C C
block
id :: Label
id = forall (thing :: Extensibility -> Extensibility -> *)
(x :: Extensibility).
NonLocal thing =>
thing C x -> Label
entryLabel Block CmmNode C C
block
stmts :: [CmmNode O O]
stmts = forall (n :: Extensibility -> Extensibility -> *).
Block n O O -> [n O O]
blockToList Block CmmNode O O
nodes
header_comment_instr :: OrdList Instr
header_comment_instr = forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ SDoc -> Instr
MULTILINE_COMMENT (
String -> SDoc
text String
"-- --------------------------- basicBlockCodeGen --------------------------- --\n"
SDoc -> SDoc -> SDoc
$+$ forall env a. OutputableP env a => env -> a -> SDoc
pdoc (NCGConfig -> Platform
ncgPlatform NCGConfig
config) Block CmmNode C C
block
)
Maybe DebugBlock
dbg <- Label -> NatM (Maybe DebugBlock)
getDebugBlock (forall (thing :: Extensibility -> Extensibility -> *)
(x :: Extensibility).
NonLocal thing =>
thing C x -> Label
entryLabel Block CmmNode C C
block)
OrdList Instr
loc_instrs <- case DebugBlock -> Maybe CmmTickish
dblSourceTick forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe DebugBlock
dbg of
Just (SourceNote RealSrcSpan
span String
name)
-> do Int
fileId <- FastString -> NatM Int
getFileId (RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
span)
let line :: Int
line = RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan
span; col :: Int
col = RealSrcSpan -> Int
srcSpanStartCol RealSrcSpan
span
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> String -> Instr
LOCATION Int
fileId Int
line Int
col String
name
Maybe CmmTickish
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. OrdList a
nilOL
(OrdList Instr
mid_instrs,Label
mid_bid) <- Label -> [CmmNode O O] -> NatM (OrdList Instr, Label)
stmtsToInstrs Label
id [CmmNode O O]
stmts
(!OrdList Instr
tail_instrs,Maybe Label
_) <- forall (e :: Extensibility) (x :: Extensibility).
Label -> CmmNode e x -> NatM (OrdList Instr, Maybe Label)
stmtToInstrs Label
mid_bid CmmNode O C
tail
let instrs :: OrdList Instr
instrs = OrdList Instr
header_comment_instr forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
loc_instrs forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
mid_instrs forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
tail_instrs
let
([Instr]
top,[NatBasicBlock Instr]
other_blocks,[NatCmmDecl RawCmmStatics Instr]
statics) = forall a b. (a -> b -> b) -> b -> OrdList a -> b
foldrOL forall {h} {g}.
Instr
-> ([Instr], [NatBasicBlock Instr], [GenCmmDecl RawCmmStatics h g])
-> ([Instr], [NatBasicBlock Instr], [GenCmmDecl RawCmmStatics h g])
mkBlocks ([],[],[]) OrdList Instr
instrs
mkBlocks :: Instr
-> ([Instr], [NatBasicBlock Instr], [GenCmmDecl RawCmmStatics h g])
-> ([Instr], [NatBasicBlock Instr], [GenCmmDecl RawCmmStatics h g])
mkBlocks (NEWBLOCK Label
id) ([Instr]
instrs,[NatBasicBlock Instr]
blocks,[GenCmmDecl RawCmmStatics h g]
statics)
= ([], forall i. Label -> [i] -> GenBasicBlock i
BasicBlock Label
id [Instr]
instrs forall a. a -> [a] -> [a]
: [NatBasicBlock Instr]
blocks, [GenCmmDecl RawCmmStatics h g]
statics)
mkBlocks (LDATA Section
sec RawCmmStatics
dat) ([Instr]
instrs,[NatBasicBlock Instr]
blocks,[GenCmmDecl RawCmmStatics h g]
statics)
= ([Instr]
instrs, [NatBasicBlock Instr]
blocks, forall d h g. Section -> d -> GenCmmDecl d h g
CmmData Section
sec RawCmmStatics
datforall a. a -> [a] -> [a]
:[GenCmmDecl RawCmmStatics h g]
statics)
mkBlocks Instr
instr ([Instr]
instrs,[NatBasicBlock Instr]
blocks,[GenCmmDecl RawCmmStatics h g]
statics)
= (Instr
instrforall a. a -> [a] -> [a]
:[Instr]
instrs, [NatBasicBlock Instr]
blocks, [GenCmmDecl RawCmmStatics h g]
statics)
forall (m :: * -> *) a. Monad m => a -> m a
return (forall i. Label -> [i] -> GenBasicBlock i
BasicBlock Label
id [Instr]
top forall a. a -> [a] -> [a]
: [NatBasicBlock Instr]
other_blocks, [NatCmmDecl RawCmmStatics Instr]
statics)
ann :: SDoc -> Instr -> Instr
ann :: SDoc -> Instr -> Instr
ann SDoc
doc Instr
instr = SDoc -> Instr -> Instr
ANN SDoc
doc Instr
instr
{-# INLINE ann #-}
annExpr :: CmmExpr -> Instr -> Instr
annExpr :: CmmExpr -> Instr -> Instr
annExpr CmmExpr
e Instr
instr = SDoc -> Instr -> Instr
ANN (String -> SDoc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ CmmExpr
e) Instr
instr
{-# INLINE annExpr #-}
genSwitch :: CmmExpr -> SwitchTargets -> NatM InstrBlock
genSwitch :: CmmExpr -> SwitchTargets -> NatM (OrdList Instr)
genSwitch CmmExpr
expr SwitchTargets
targets = do
(Reg
reg, Format
format, OrdList Instr
code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
expr
let w :: Width
w = Format -> Width
formatToWidth Format
format
let mkbranch :: OrdList Instr -> (Integer, Label) -> NatM (OrdList Instr)
mkbranch OrdList Instr
acc (Integer
key, Label
bid) = do
(Reg
keyReg, Format
_format, OrdList Instr
code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg (CmmLit -> CmmExpr
CmmLit (Integer -> Width -> CmmLit
CmmInt Integer
key Width
w))
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ OrdList Instr
code forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP (Width -> Reg -> Operand
OpReg Width
w Reg
reg) (Width -> Reg -> Operand
OpReg Width
w Reg
keyReg)
, Cond -> Target -> Instr
BCOND Cond
EQ (Label -> Target
TBlock Label
bid)
] forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
acc
def_code :: OrdList Instr
def_code = case SwitchTargets -> Maybe Label
switchTargetsDefault SwitchTargets
targets of
Just Label
bid -> forall a. a -> OrdList a
unitOL (Target -> Instr
B (Label -> Target
TBlock Label
bid))
Maybe Label
Nothing -> forall a. OrdList a
nilOL
OrdList Instr
switch_code <- forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM OrdList Instr -> (Integer, Label) -> NatM (OrdList Instr)
mkbranch forall a. OrdList a
nilOL (SwitchTargets -> [(Integer, Label)]
switchTargetsCases SwitchTargets
targets)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ OrdList Instr
code forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
switch_code forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
def_code
generateJumpTableForInstr :: NCGConfig -> Instr
-> Maybe (NatCmmDecl RawCmmStatics Instr)
generateJumpTableForInstr :: NCGConfig -> Instr -> Maybe (NatCmmDecl RawCmmStatics Instr)
generateJumpTableForInstr NCGConfig
_ Instr
_ = forall a. Maybe a
Nothing
stmtsToInstrs :: BlockId
-> [CmmNode O O]
-> NatM (InstrBlock, BlockId)
stmtsToInstrs :: Label -> [CmmNode O O] -> NatM (OrdList Instr, Label)
stmtsToInstrs Label
bid [CmmNode O O]
stmts =
forall {e :: Extensibility} {x :: Extensibility}.
Label
-> [CmmNode e x] -> OrdList Instr -> NatM (OrdList Instr, Label)
go Label
bid [CmmNode O O]
stmts forall a. OrdList a
nilOL
where
go :: Label
-> [CmmNode e x] -> OrdList Instr -> NatM (OrdList Instr, Label)
go Label
bid [] OrdList Instr
instrs = forall (m :: * -> *) a. Monad m => a -> m a
return (OrdList Instr
instrs,Label
bid)
go Label
bid (CmmNode e x
s:[CmmNode e x]
stmts) OrdList Instr
instrs = do
(OrdList Instr
instrs',Maybe Label
bid') <- forall (e :: Extensibility) (x :: Extensibility).
Label -> CmmNode e x -> NatM (OrdList Instr, Maybe Label)
stmtToInstrs Label
bid CmmNode e x
s
let !newBid :: Label
newBid = forall a. a -> Maybe a -> a
fromMaybe Label
bid Maybe Label
bid'
Label
-> [CmmNode e x] -> OrdList Instr -> NatM (OrdList Instr, Label)
go Label
newBid [CmmNode e x]
stmts (OrdList Instr
instrs forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
instrs')
stmtToInstrs :: BlockId
-> CmmNode e x
-> NatM (InstrBlock, Maybe BlockId)
stmtToInstrs :: forall (e :: Extensibility) (x :: Extensibility).
Label -> CmmNode e x -> NatM (OrdList Instr, Maybe Label)
stmtToInstrs Label
bid CmmNode e x
stmt = do
Platform
platform <- NatM Platform
getPlatform
case CmmNode e x
stmt of
CmmUnsafeForeignCall ForeignTarget
target [CmmFormal]
result_regs [CmmExpr]
args
-> ForeignTarget
-> [CmmFormal]
-> [CmmExpr]
-> Label
-> NatM (OrdList Instr, Maybe Label)
genCCall ForeignTarget
target [CmmFormal]
result_regs [CmmExpr]
args Label
bid
CmmNode e x
_ -> (,forall a. Maybe a
Nothing) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case CmmNode e x
stmt of
CmmComment FastString
s -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> OrdList a
unitOL (SDoc -> Instr
COMMENT (FastString -> SDoc
ftext FastString
s)))
CmmTick {} -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. OrdList a
nilOL
CmmAssign CmmReg
reg CmmExpr
src
| CmmType -> Bool
isFloatType CmmType
ty -> Format -> CmmReg -> CmmExpr -> NatM (OrdList Instr)
assignReg_FltCode Format
format CmmReg
reg CmmExpr
src
| Bool
otherwise -> Format -> CmmReg -> CmmExpr -> NatM (OrdList Instr)
assignReg_IntCode Format
format CmmReg
reg CmmExpr
src
where ty :: CmmType
ty = Platform -> CmmReg -> CmmType
cmmRegType Platform
platform CmmReg
reg
format :: Format
format = CmmType -> Format
cmmTypeFormat CmmType
ty
CmmStore CmmExpr
addr CmmExpr
src AlignmentSpec
_alignment
| CmmType -> Bool
isFloatType CmmType
ty -> Format -> CmmExpr -> CmmExpr -> NatM (OrdList Instr)
assignMem_FltCode Format
format CmmExpr
addr CmmExpr
src
| Bool
otherwise -> Format -> CmmExpr -> CmmExpr -> NatM (OrdList Instr)
assignMem_IntCode Format
format CmmExpr
addr CmmExpr
src
where ty :: CmmType
ty = Platform -> CmmExpr -> CmmType
cmmExprType Platform
platform CmmExpr
src
format :: Format
format = CmmType -> Format
cmmTypeFormat CmmType
ty
CmmBranch Label
id -> Label -> NatM (OrdList Instr)
genBranch Label
id
CmmCondBranch CmmExpr
arg Label
true Label
false Maybe Bool
_prediction ->
Label -> Label -> Label -> CmmExpr -> NatM (OrdList Instr)
genCondBranch Label
bid Label
true Label
false CmmExpr
arg
CmmSwitch CmmExpr
arg SwitchTargets
ids -> CmmExpr -> SwitchTargets -> NatM (OrdList Instr)
genSwitch CmmExpr
arg SwitchTargets
ids
CmmCall { cml_target :: CmmNode O C -> CmmExpr
cml_target = CmmExpr
arg } -> CmmExpr -> NatM (OrdList Instr)
genJump CmmExpr
arg
CmmUnwind [(GlobalReg, Maybe CmmExpr)]
_regs -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. OrdList a
nilOL
CmmNode e x
_ -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"stmtToInstrs: statement should have been cps'd away" (forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
platform CmmNode e x
stmt)
type InstrBlock
= OrdList Instr
data Register
= Fixed Format Reg InstrBlock
| Any Format (Reg -> InstrBlock)
swizzleRegisterRep :: Format -> Register -> Register
swizzleRegisterRep :: Format -> Register -> Register
swizzleRegisterRep Format
format (Fixed Format
_ Reg
reg OrdList Instr
code) = Format -> Reg -> OrdList Instr -> Register
Fixed Format
format Reg
reg OrdList Instr
code
swizzleRegisterRep Format
format (Any Format
_ Reg -> OrdList Instr
codefn) = Format -> (Reg -> OrdList Instr) -> Register
Any Format
format Reg -> OrdList Instr
codefn
getRegisterReg :: Platform -> CmmReg -> Reg
getRegisterReg :: Platform -> CmmReg -> Reg
getRegisterReg Platform
_ (CmmLocal (LocalReg Unique
u CmmType
pk))
= VirtualReg -> Reg
RegVirtual forall a b. (a -> b) -> a -> b
$ Unique -> Format -> VirtualReg
mkVirtualReg Unique
u (CmmType -> Format
cmmTypeFormat CmmType
pk)
getRegisterReg Platform
platform (CmmGlobal GlobalReg
mid)
= case Platform -> GlobalReg -> Maybe RealReg
globalRegMaybe Platform
platform GlobalReg
mid of
Just RealReg
reg -> RealReg -> Reg
RegReal RealReg
reg
Maybe RealReg
Nothing -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegisterReg-memory" (forall a. Outputable a => a -> SDoc
ppr forall a b. (a -> b) -> a -> b
$ GlobalReg -> CmmReg
CmmGlobal GlobalReg
mid)
getSomeReg :: CmmExpr -> NatM (Reg, Format, InstrBlock)
getSomeReg :: CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
expr = do
Register
r <- CmmExpr -> NatM Register
getRegister CmmExpr
expr
case Register
r of
Any Format
rep Reg -> OrdList Instr
code -> do
Reg
tmp <- Format -> NatM Reg
getNewRegNat Format
rep
forall (m :: * -> *) a. Monad m => a -> m a
return (Reg
tmp, Format
rep, Reg -> OrdList Instr
code Reg
tmp)
Fixed Format
rep Reg
reg OrdList Instr
code ->
forall (m :: * -> *) a. Monad m => a -> m a
return (Reg
reg, Format
rep, OrdList Instr
code)
getFloatReg :: HasCallStack => CmmExpr -> NatM (Reg, Format, InstrBlock)
getFloatReg :: HasCallStack => CmmExpr -> NatM (Reg, Format, OrdList Instr)
getFloatReg CmmExpr
expr = do
Register
r <- CmmExpr -> NatM Register
getRegister CmmExpr
expr
case Register
r of
Any Format
rep Reg -> OrdList Instr
code | Format -> Bool
isFloatFormat Format
rep -> do
Reg
tmp <- Format -> NatM Reg
getNewRegNat Format
rep
forall (m :: * -> *) a. Monad m => a -> m a
return (Reg
tmp, Format
rep, Reg -> OrdList Instr
code Reg
tmp)
Any Format
II32 Reg -> OrdList Instr
code -> do
Reg
tmp <- Format -> NatM Reg
getNewRegNat Format
FF32
forall (m :: * -> *) a. Monad m => a -> m a
return (Reg
tmp, Format
FF32, Reg -> OrdList Instr
code Reg
tmp)
Any Format
II64 Reg -> OrdList Instr
code -> do
Reg
tmp <- Format -> NatM Reg
getNewRegNat Format
FF64
forall (m :: * -> *) a. Monad m => a -> m a
return (Reg
tmp, Format
FF64, Reg -> OrdList Instr
code Reg
tmp)
Any Format
_w Reg -> OrdList Instr
_code -> do
NCGConfig
config <- NatM NCGConfig
getConfig
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"can't do getFloatReg on" (forall env a. OutputableP env a => env -> a -> SDoc
pdoc (NCGConfig -> Platform
ncgPlatform NCGConfig
config) CmmExpr
expr)
Fixed Format
rep Reg
reg OrdList Instr
code ->
forall (m :: * -> *) a. Monad m => a -> m a
return (Reg
reg, Format
rep, OrdList Instr
code)
litToImm' :: CmmLit -> NatM (Operand, InstrBlock)
litToImm' :: CmmLit -> NatM (Operand, OrdList Instr)
litToImm' CmmLit
lit = forall (m :: * -> *) a. Monad m => a -> m a
return (Imm -> Operand
OpImm (CmmLit -> Imm
litToImm CmmLit
lit), forall a. OrdList a
nilOL)
getRegister :: CmmExpr -> NatM Register
getRegister :: CmmExpr -> NatM Register
getRegister CmmExpr
e = do
NCGConfig
config <- NatM NCGConfig
getConfig
NCGConfig -> Platform -> CmmExpr -> NatM Register
getRegister' NCGConfig
config (NCGConfig -> Platform
ncgPlatform NCGConfig
config) CmmExpr
e
opRegWidth :: Width -> Width
opRegWidth :: Width -> Width
opRegWidth Width
W64 = Width
W64
opRegWidth Width
W32 = Width
W32
opRegWidth Width
W16 = Width
W32
opRegWidth Width
W8 = Width
W32
opRegWidth Width
w = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"opRegWidth" (String -> SDoc
text String
"Unsupported width" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Width
w)
getRegister' :: NCGConfig -> Platform -> CmmExpr -> NatM Register
getRegister' :: NCGConfig -> Platform -> CmmExpr -> NatM Register
getRegister' NCGConfig
config Platform
plat (CmmMachOp (MO_Add Width
w0) [CmmExpr
x, CmmLit (CmmInt Integer
i Width
w1)]) | Integer
i forall a. Ord a => a -> a -> Bool
< Integer
0
= NCGConfig -> Platform -> CmmExpr -> NatM Register
getRegister' NCGConfig
config Platform
plat (MachOp -> [CmmExpr] -> CmmExpr
CmmMachOp (Width -> MachOp
MO_Sub Width
w0) [CmmExpr
x, CmmLit -> CmmExpr
CmmLit (Integer -> Width -> CmmLit
CmmInt (-Integer
i) Width
w1)])
getRegister' NCGConfig
config Platform
plat (CmmMachOp (MO_Sub Width
w0) [CmmExpr
x, CmmLit (CmmInt Integer
i Width
w1)]) | Integer
i forall a. Ord a => a -> a -> Bool
< Integer
0
= NCGConfig -> Platform -> CmmExpr -> NatM Register
getRegister' NCGConfig
config Platform
plat (MachOp -> [CmmExpr] -> CmmExpr
CmmMachOp (Width -> MachOp
MO_Add Width
w0) [CmmExpr
x, CmmLit -> CmmExpr
CmmLit (Integer -> Width -> CmmLit
CmmInt (-Integer
i) Width
w1)])
getRegister' NCGConfig
config Platform
plat CmmExpr
expr
= case CmmExpr
expr of
CmmReg (CmmGlobal GlobalReg
PicBaseReg)
-> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegisterReg-memory" (forall a. Outputable a => a -> SDoc
ppr forall a b. (a -> b) -> a -> b
$ GlobalReg
PicBaseReg)
CmmLit CmmLit
lit
-> case CmmLit
lit of
CmmInt Integer
i Width
W8 | Integer
i forall a. Ord a => a -> a -> Bool
>= Integer
0 -> do
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
W8) (\Reg
dst -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
W8 Reg
dst) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger (Width -> Integer -> Integer
narrowU Width
W8 Integer
i))))))
CmmInt Integer
i Width
W16 | Integer
i forall a. Ord a => a -> a -> Bool
>= Integer
0 -> do
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
W16) (\Reg
dst -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
W16 Reg
dst) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger (Width -> Integer -> Integer
narrowU Width
W16 Integer
i))))))
CmmInt Integer
i Width
W8 -> do
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
W8) (\Reg
dst -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
W8 Reg
dst) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger (Width -> Integer -> Integer
narrowU Width
W8 Integer
i))))))
CmmInt Integer
i Width
W16 -> do
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
W16) (\Reg
dst -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
W16 Reg
dst) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger (Width -> Integer -> Integer
narrowU Width
W16 Integer
i))))))
CmmInt Integer
i Width
w | Int -> Integer -> Bool
isNbitEncodeable Int
16 Integer
i, Integer
i forall a. Ord a => a -> a -> Bool
>= Integer
0 -> do
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
W16 Reg
dst) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
i)))))
CmmInt Integer
i Width
w | Int -> Integer -> Bool
isNbitEncodeable Int
32 Integer
i, Integer
i forall a. Ord a => a -> a -> Bool
>= Integer
0 -> do
let half0 :: Int
half0 = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i :: Word16)
half1 :: Int
half1 = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
i forall a. Bits a => a -> Int -> a
`shiftR` Int
16) :: Word16)
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> forall a. [a] -> OrdList a
toOL [ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
W32 Reg
dst) (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
half0))
, Operand -> Operand -> Instr
MOVK (Width -> Reg -> Operand
OpReg Width
W32 Reg
dst) (Imm -> ShiftMode -> Int -> Operand
OpImmShift (Int -> Imm
ImmInt Int
half1) ShiftMode
SLSL Int
16)
]))
CmmInt Integer
i Width
W32 -> do
let half0 :: Int
half0 = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i :: Word16)
half1 :: Int
half1 = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
i forall a. Bits a => a -> Int -> a
`shiftR` Int
16) :: Word16)
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
W32) (\Reg
dst -> forall a. [a] -> OrdList a
toOL [ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
W32 Reg
dst) (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
half0))
, Operand -> Operand -> Instr
MOVK (Width -> Reg -> Operand
OpReg Width
W32 Reg
dst) (Imm -> ShiftMode -> Int -> Operand
OpImmShift (Int -> Imm
ImmInt Int
half1) ShiftMode
SLSL Int
16)
]))
CmmInt Integer
i Width
W64 -> do
let half0 :: Int
half0 = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i :: Word16)
half1 :: Int
half1 = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
i forall a. Bits a => a -> Int -> a
`shiftR` Int
16) :: Word16)
half2 :: Int
half2 = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
i forall a. Bits a => a -> Int -> a
`shiftR` Int
32) :: Word16)
half3 :: Int
half3 = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
i forall a. Bits a => a -> Int -> a
`shiftR` Int
48) :: Word16)
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
W64) (\Reg
dst -> forall a. [a] -> OrdList a
toOL [ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
W64 Reg
dst) (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
half0))
, Operand -> Operand -> Instr
MOVK (Width -> Reg -> Operand
OpReg Width
W64 Reg
dst) (Imm -> ShiftMode -> Int -> Operand
OpImmShift (Int -> Imm
ImmInt Int
half1) ShiftMode
SLSL Int
16)
, Operand -> Operand -> Instr
MOVK (Width -> Reg -> Operand
OpReg Width
W64 Reg
dst) (Imm -> ShiftMode -> Int -> Operand
OpImmShift (Int -> Imm
ImmInt Int
half2) ShiftMode
SLSL Int
32)
, Operand -> Operand -> Instr
MOVK (Width -> Reg -> Operand
OpReg Width
W64 Reg
dst) (Imm -> ShiftMode -> Int -> Operand
OpImmShift (Int -> Imm
ImmInt Int
half3) ShiftMode
SLSL Int
48)
]))
CmmInt Integer
_i Width
rep -> do
(Operand
op, OrdList Instr
imm_code) <- CmmLit -> NatM (Operand, OrdList Instr)
litToImm' CmmLit
lit
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
rep) (\Reg
dst -> OrdList Instr
imm_code forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
rep Reg
dst) Operand
op)))
CmmFloat Rational
0 Width
w -> do
(Operand
op, OrdList Instr
imm_code) <- CmmLit -> NatM (Operand, OrdList Instr)
litToImm' CmmLit
lit
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
floatFormat Width
w) (\Reg
dst -> OrdList Instr
imm_code forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
w Reg
dst) Operand
op)))
CmmFloat Rational
_f Width
W8 -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (CmmLit:CmmFloat), no support for bytes" (forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmFloat Rational
_f Width
W16 -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (CmmLit:CmmFloat), no support for halfs" (forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmFloat Rational
f Width
W32 -> do
let word :: Word32
word = Float -> Word32
castFloatToWord32 (forall a. Fractional a => Rational -> a
fromRational Rational
f) :: Word32
half0 :: Int
half0 = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
word :: Word16)
half1 :: Int
half1 = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
word forall a. Bits a => a -> Int -> a
`shiftR` Int
16) :: Word16)
Reg
tmp <- Format -> NatM Reg
getNewRegNat (Width -> Format
intFormat Width
W32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
floatFormat Width
W32) (\Reg
dst -> forall a. [a] -> OrdList a
toOL [ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
W32 Reg
tmp) (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
half0))
, Operand -> Operand -> Instr
MOVK (Width -> Reg -> Operand
OpReg Width
W32 Reg
tmp) (Imm -> ShiftMode -> Int -> Operand
OpImmShift (Int -> Imm
ImmInt Int
half1) ShiftMode
SLSL Int
16)
, Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
W32 Reg
dst) (Width -> Reg -> Operand
OpReg Width
W32 Reg
tmp)
]))
CmmFloat Rational
f Width
W64 -> do
let word :: Word64
word = Double -> Word64
castDoubleToWord64 (forall a. Fractional a => Rational -> a
fromRational Rational
f) :: Word64
half0 :: Int
half0 = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
word :: Word16)
half1 :: Int
half1 = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
word forall a. Bits a => a -> Int -> a
`shiftR` Int
16) :: Word16)
half2 :: Int
half2 = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
word forall a. Bits a => a -> Int -> a
`shiftR` Int
32) :: Word16)
half3 :: Int
half3 = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
word forall a. Bits a => a -> Int -> a
`shiftR` Int
48) :: Word16)
Reg
tmp <- Format -> NatM Reg
getNewRegNat (Width -> Format
intFormat Width
W64)
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
floatFormat Width
W64) (\Reg
dst -> forall a. [a] -> OrdList a
toOL [ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
W64 Reg
tmp) (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
half0))
, Operand -> Operand -> Instr
MOVK (Width -> Reg -> Operand
OpReg Width
W64 Reg
tmp) (Imm -> ShiftMode -> Int -> Operand
OpImmShift (Int -> Imm
ImmInt Int
half1) ShiftMode
SLSL Int
16)
, Operand -> Operand -> Instr
MOVK (Width -> Reg -> Operand
OpReg Width
W64 Reg
tmp) (Imm -> ShiftMode -> Int -> Operand
OpImmShift (Int -> Imm
ImmInt Int
half2) ShiftMode
SLSL Int
32)
, Operand -> Operand -> Instr
MOVK (Width -> Reg -> Operand
OpReg Width
W64 Reg
tmp) (Imm -> ShiftMode -> Int -> Operand
OpImmShift (Int -> Imm
ImmInt Int
half3) ShiftMode
SLSL Int
48)
, Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
W64 Reg
dst) (Width -> Reg -> Operand
OpReg Width
W64 Reg
tmp)
]))
CmmFloat Rational
_f Width
_w -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (CmmLit:CmmFloat), unsupported float lit" (forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmVec [CmmLit]
_ -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (CmmLit:CmmVec): " (forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmLabel CLabel
_lbl -> do
(Operand
op, OrdList Instr
imm_code) <- CmmLit -> NatM (Operand, OrdList Instr)
litToImm' CmmLit
lit
let rep :: CmmType
rep = Platform -> CmmLit -> CmmType
cmmLitType Platform
plat CmmLit
lit
format :: Format
format = CmmType -> Format
cmmTypeFormat CmmType
rep
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any Format
format (\Reg
dst -> OrdList Instr
imm_code forall a. OrdList a -> a -> OrdList a
`snocOL` (CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr forall a b. (a -> b) -> a -> b
$ Format -> Operand -> Operand -> Instr
LDR Format
format (Width -> Reg -> Operand
OpReg (Format -> Width
formatToWidth Format
format) Reg
dst) Operand
op)))
CmmLabelOff CLabel
_lbl Int
off | Int -> Integer -> Bool
isNbitEncodeable Int
12 (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
off) -> do
(Operand
op, OrdList Instr
imm_code) <- CmmLit -> NatM (Operand, OrdList Instr)
litToImm' CmmLit
lit
let rep :: CmmType
rep = Platform -> CmmLit -> CmmType
cmmLitType Platform
plat CmmLit
lit
format :: Format
format = CmmType -> Format
cmmTypeFormat CmmType
rep
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any Format
format (\Reg
dst -> OrdList Instr
imm_code forall a. OrdList a -> a -> OrdList a
`snocOL` Format -> Operand -> Operand -> Instr
LDR Format
format (Width -> Reg -> Operand
OpReg (Format -> Width
formatToWidth Format
format) Reg
dst) Operand
op))
CmmLabelOff CLabel
lbl Int
off -> do
(Operand
op, OrdList Instr
imm_code) <- CmmLit -> NatM (Operand, OrdList Instr)
litToImm' (CLabel -> CmmLit
CmmLabel CLabel
lbl)
let rep :: CmmType
rep = Platform -> CmmLit -> CmmType
cmmLitType Platform
plat CmmLit
lit
format :: Format
format = CmmType -> Format
cmmTypeFormat CmmType
rep
width :: Width
width = CmmType -> Width
typeWidth CmmType
rep
(Reg
off_r, Format
_off_format, OrdList Instr
off_code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg forall a b. (a -> b) -> a -> b
$ CmmLit -> CmmExpr
CmmLit (Integer -> Width -> CmmLit
CmmInt (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
off) Width
width)
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any Format
format (\Reg
dst -> OrdList Instr
imm_code forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
off_code forall a. OrdList a -> a -> OrdList a
`snocOL` Format -> Operand -> Operand -> Instr
LDR Format
format (Width -> Reg -> Operand
OpReg (Format -> Width
formatToWidth Format
format) Reg
dst) Operand
op forall a. OrdList a -> a -> OrdList a
`snocOL` Operand -> Operand -> Operand -> Instr
ADD (Width -> Reg -> Operand
OpReg Width
width Reg
dst) (Width -> Reg -> Operand
OpReg Width
width Reg
dst) (Width -> Reg -> Operand
OpReg Width
width Reg
off_r)))
CmmLabelDiffOff CLabel
_ CLabel
_ Int
_ Width
_ -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (CmmLit:CmmLabelOff): " (forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmBlock Label
_ -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (CmmLit:CmmLabelOff): " (forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmLit
CmmHighStackMark -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (CmmLit:CmmLabelOff): " (forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmLoad CmmExpr
mem CmmType
rep AlignmentSpec
_ -> do
Amode AddrMode
addr OrdList Instr
addr_code <- Platform -> Width -> CmmExpr -> NatM Amode
getAmode Platform
plat (CmmType -> Width
typeWidth CmmType
rep) CmmExpr
mem
let format :: Format
format = CmmType -> Format
cmmTypeFormat CmmType
rep
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any Format
format (\Reg
dst -> OrdList Instr
addr_code forall a. OrdList a -> a -> OrdList a
`snocOL` Format -> Operand -> Operand -> Instr
LDR Format
format (Width -> Reg -> Operand
OpReg (Format -> Width
formatToWidth Format
format) Reg
dst) (AddrMode -> Operand
OpAddr AddrMode
addr)))
CmmStackSlot Area
_ Int
_
-> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (CmmStackSlot): " (forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmReg CmmReg
reg
-> forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> Reg -> OrdList Instr -> Register
Fixed (CmmType -> Format
cmmTypeFormat (Platform -> CmmReg -> CmmType
cmmRegType Platform
plat CmmReg
reg))
(Platform -> CmmReg -> Reg
getRegisterReg Platform
plat CmmReg
reg)
forall a. OrdList a
nilOL)
CmmRegOff CmmReg
reg Int
off | Int -> Integer -> Bool
isNbitEncodeable Int
12 (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
off) -> do
NCGConfig -> Platform -> CmmExpr -> NatM Register
getRegister' NCGConfig
config Platform
plat forall a b. (a -> b) -> a -> b
$
MachOp -> [CmmExpr] -> CmmExpr
CmmMachOp (Width -> MachOp
MO_Add Width
width) [CmmReg -> CmmExpr
CmmReg CmmReg
reg, CmmLit -> CmmExpr
CmmLit (Integer -> Width -> CmmLit
CmmInt (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
off) Width
width)]
where width :: Width
width = CmmType -> Width
typeWidth (Platform -> CmmReg -> CmmType
cmmRegType Platform
plat CmmReg
reg)
CmmRegOff CmmReg
reg Int
off -> do
(Reg
off_r, Format
_off_format, OrdList Instr
off_code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg forall a b. (a -> b) -> a -> b
$ CmmLit -> CmmExpr
CmmLit (Integer -> Width -> CmmLit
CmmInt (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
off) Width
width)
(Reg
reg, Format
_format, OrdList Instr
code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg forall a b. (a -> b) -> a -> b
$ CmmReg -> CmmExpr
CmmReg CmmReg
reg
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
width) (\Reg
dst -> OrdList Instr
off_code forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code forall a. OrdList a -> a -> OrdList a
`snocOL` Operand -> Operand -> Operand -> Instr
ADD (Width -> Reg -> Operand
OpReg Width
width Reg
dst) (Width -> Reg -> Operand
OpReg Width
width Reg
reg) (Width -> Reg -> Operand
OpReg Width
width Reg
off_r))
where width :: Width
width = CmmType -> Width
typeWidth (Platform -> CmmReg -> CmmType
cmmRegType Platform
plat CmmReg
reg)
CmmMachOp MachOp
op [CmmExpr
e] -> do
(Reg
reg, Format
_format, OrdList Instr
code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
e
case MachOp
op of
MO_Not Width
w -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) forall a b. (a -> b) -> a -> b
$ \Reg
dst ->
let w' :: Width
w' = Width -> Width
opRegWidth Width
w
in OrdList Instr
code forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Operand -> Instr
MVN (Width -> Reg -> Operand
OpReg Width
w' Reg
dst) (Width -> Reg -> Operand
OpReg Width
w' Reg
reg) forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
Width -> Width -> Reg -> OrdList Instr
truncateReg Width
w' Width
w Reg
dst
MO_S_Neg Width
w -> forall {m :: * -> *}.
Monad m =>
OrdList Instr -> Width -> Reg -> m Register
negate OrdList Instr
code Width
w Reg
reg
MO_F_Neg Width
w -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
floatFormat Width
w) (\Reg
dst -> OrdList Instr
code forall a. OrdList a -> a -> OrdList a
`snocOL` Operand -> Operand -> Instr
NEG (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg))
MO_SF_Conv Width
from Width
to -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
floatFormat Width
to) (\Reg
dst -> OrdList Instr
code forall a. OrdList a -> a -> OrdList a
`snocOL` Operand -> Operand -> Instr
SCVTF (Width -> Reg -> Operand
OpReg Width
to Reg
dst) (Width -> Reg -> Operand
OpReg Width
from Reg
reg))
MO_FS_Conv Width
from Width
to -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
to) (\Reg
dst -> OrdList Instr
code forall a. OrdList a -> a -> OrdList a
`snocOL` Operand -> Operand -> Instr
FCVTZS (Width -> Reg -> Operand
OpReg Width
to Reg
dst) (Width -> Reg -> Operand
OpReg Width
from Reg
reg))
MO_UU_Conv Width
from Width
to -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
to) (\Reg
dst -> OrdList Instr
code forall a. OrdList a -> a -> OrdList a
`snocOL` Operand -> Operand -> Operand -> Operand -> Instr
UBFM (Width -> Reg -> Operand
OpReg (forall a. Ord a => a -> a -> a
max Width
from Width
to) Reg
dst) (Width -> Reg -> Operand
OpReg (forall a. Ord a => a -> a -> a
max Width
from Width
to) Reg
reg) (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
0)) (Width -> Operand
toImm (forall a. Ord a => a -> a -> a
min Width
from Width
to)))
MO_SS_Conv Width
from Width
to -> forall {m :: * -> *}.
Monad m =>
Width -> Width -> Reg -> OrdList Instr -> m Register
ss_conv Width
from Width
to Reg
reg OrdList Instr
code
MO_FF_Conv Width
from Width
to -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
floatFormat Width
to) (\Reg
dst -> OrdList Instr
code forall a. OrdList a -> a -> OrdList a
`snocOL` Operand -> Operand -> Instr
FCVT (Width -> Reg -> Operand
OpReg Width
to Reg
dst) (Width -> Reg -> Operand
OpReg Width
from Reg
reg))
MO_XX_Conv Width
_from Width
to -> Format -> Register -> Register
swizzleRegisterRep (Width -> Format
intFormat Width
to) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CmmExpr -> NatM Register
getRegister CmmExpr
e
MachOp
_ -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (monadic CmmMachOp):" (forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
where
toImm :: Width -> Operand
toImm Width
W8 = (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
7))
toImm Width
W16 = (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
15))
toImm Width
W32 = (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
31))
toImm Width
W64 = (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
63))
toImm Width
W128 = (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
127))
toImm Width
W256 = (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
255))
toImm Width
W512 = (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
511))
negate :: OrdList Instr -> Width -> Reg -> m Register
negate OrdList Instr
code Width
w Reg
reg = do
let w' :: Width
w' = Width -> Width
opRegWidth Width
w
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) forall a b. (a -> b) -> a -> b
$ \Reg
dst ->
OrdList Instr
code forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
Width -> Width -> Reg -> OrdList Instr
signExtendReg Width
w Width
w' Reg
reg forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Operand -> Instr
NEG (Width -> Reg -> Operand
OpReg Width
w' Reg
dst) (Width -> Reg -> Operand
OpReg Width
w' Reg
reg) forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
Width -> Width -> Reg -> OrdList Instr
truncateReg Width
w' Width
w Reg
dst
ss_conv :: Width -> Width -> Reg -> OrdList Instr -> m Register
ss_conv Width
from Width
to Reg
reg OrdList Instr
code =
let w' :: Width
w' = Width -> Width
opRegWidth (forall a. Ord a => a -> a -> a
max Width
from Width
to)
in forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
to) forall a b. (a -> b) -> a -> b
$ \Reg
dst ->
OrdList Instr
code forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Operand -> Operand -> Operand -> Instr
SBFM (Width -> Reg -> Operand
OpReg Width
w' Reg
dst) (Width -> Reg -> Operand
OpReg Width
w' Reg
reg) (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
0)) (Width -> Operand
toImm (forall a. Ord a => a -> a -> a
min Width
from Width
to)) forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
Width -> Width -> Reg -> OrdList Instr
truncateReg Width
w' Width
to Reg
dst
CmmMachOp (MO_Add Width
_) [expr' :: CmmExpr
expr'@(CmmReg (CmmGlobal GlobalReg
_r)), CmmLit (CmmInt Integer
0 Width
_)] -> NCGConfig -> Platform -> CmmExpr -> NatM Register
getRegister' NCGConfig
config Platform
plat CmmExpr
expr'
CmmMachOp (MO_Sub Width
_) [expr' :: CmmExpr
expr'@(CmmReg (CmmGlobal GlobalReg
_r)), CmmLit (CmmInt Integer
0 Width
_)] -> NCGConfig -> Platform -> CmmExpr -> NatM Register
getRegister' NCGConfig
config Platform
plat CmmExpr
expr'
CmmMachOp (MO_Add Width
w) [(CmmReg CmmReg
reg), CmmLit (CmmInt Integer
n Width
_)]
| Integer
n forall a. Ord a => a -> a -> Bool
> Integer
0 Bool -> Bool -> Bool
&& Integer
n forall a. Ord a => a -> a -> Bool
< Integer
4096 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
d -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Instr
ADD (Width -> Reg -> Operand
OpReg Width
w Reg
d) (Width -> Reg -> Operand
OpReg Width
w' Reg
r') (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
n))))
where w' :: Width
w' = Format -> Width
formatToWidth (CmmType -> Format
cmmTypeFormat (Platform -> CmmReg -> CmmType
cmmRegType Platform
plat CmmReg
reg))
r' :: Reg
r' = Platform -> CmmReg -> Reg
getRegisterReg Platform
plat CmmReg
reg
CmmMachOp (MO_Sub Width
w) [(CmmReg CmmReg
reg), CmmLit (CmmInt Integer
n Width
_)]
| Integer
n forall a. Ord a => a -> a -> Bool
> Integer
0 Bool -> Bool -> Bool
&& Integer
n forall a. Ord a => a -> a -> Bool
< Integer
4096 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
d -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Instr
SUB (Width -> Reg -> Operand
OpReg Width
w Reg
d) (Width -> Reg -> Operand
OpReg Width
w' Reg
r') (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
n))))
where w' :: Width
w' = Format -> Width
formatToWidth (CmmType -> Format
cmmTypeFormat (Platform -> CmmReg -> CmmType
cmmRegType Platform
plat CmmReg
reg))
r' :: Reg
r' = Platform -> CmmReg -> Reg
getRegisterReg Platform
plat CmmReg
reg
CmmMachOp (MO_U_Quot Width
w) [CmmExpr
x, CmmExpr
y] | Width
w forall a. Eq a => a -> a -> Bool
== Width
W8 -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(Reg
reg_y, Format
_format_y, OrdList Instr
code_y) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
y
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Instr
UXTB (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x)) forall a. OrdList a -> a -> OrdList a
`snocOL` (Operand -> Operand -> Instr
UXTB (Width -> Reg -> Operand
OpReg Width
w Reg
reg_y) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_y)) forall a. OrdList a -> a -> OrdList a
`snocOL` (Operand -> Operand -> Operand -> Instr
UDIV (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_y)))
CmmMachOp (MO_U_Quot Width
w) [CmmExpr
x, CmmExpr
y] | Width
w forall a. Eq a => a -> a -> Bool
== Width
W16 -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(Reg
reg_y, Format
_format_y, OrdList Instr
code_y) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
y
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Instr
UXTH (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x)) forall a. OrdList a -> a -> OrdList a
`snocOL` (Operand -> Operand -> Instr
UXTH (Width -> Reg -> Operand
OpReg Width
w Reg
reg_y) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_y)) forall a. OrdList a -> a -> OrdList a
`snocOL` (Operand -> Operand -> Operand -> Instr
UDIV (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_y)))
CmmMachOp (MO_Shl Width
w) [CmmExpr
x, (CmmLit (CmmInt Integer
n Width
_))] | Width
w forall a. Eq a => a -> a -> Bool
== Width
W32, Integer
0 forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n forall a. Ord a => a -> a -> Bool
< Integer
32 -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_x forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Instr
LSL (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
n))))
CmmMachOp (MO_Shl Width
w) [CmmExpr
x, (CmmLit (CmmInt Integer
n Width
_))] | Width
w forall a. Eq a => a -> a -> Bool
== Width
W64, Integer
0 forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n forall a. Ord a => a -> a -> Bool
< Integer
64 -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_x forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Instr
LSL (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
n))))
CmmMachOp (MO_S_Shr Width
w) [CmmExpr
x, (CmmLit (CmmInt Integer
n Width
_))] | Width
w forall a. Eq a => a -> a -> Bool
== Width
W8, Integer
0 forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n forall a. Ord a => a -> a -> Bool
< Integer
8 -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_x forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Operand -> Instr
SBFX (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
n)) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger (Integer
8forall a. Num a => a -> a -> a
-Integer
n)))))
CmmMachOp (MO_S_Shr Width
w) [CmmExpr
x, CmmExpr
y] | Width
w forall a. Eq a => a -> a -> Bool
== Width
W8 -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(Reg
reg_y, Format
_format_y, OrdList Instr
code_y) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
y
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Instr
SXTB (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x)) forall a. OrdList a -> a -> OrdList a
`snocOL` (Operand -> Operand -> Operand -> Instr
ASR (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_y)))
CmmMachOp (MO_S_Shr Width
w) [CmmExpr
x, (CmmLit (CmmInt Integer
n Width
_))] | Width
w forall a. Eq a => a -> a -> Bool
== Width
W16, Integer
0 forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n forall a. Ord a => a -> a -> Bool
< Integer
16 -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_x forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Operand -> Instr
SBFX (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
n)) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger (Integer
16forall a. Num a => a -> a -> a
-Integer
n)))))
CmmMachOp (MO_S_Shr Width
w) [CmmExpr
x, CmmExpr
y] | Width
w forall a. Eq a => a -> a -> Bool
== Width
W16 -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(Reg
reg_y, Format
_format_y, OrdList Instr
code_y) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
y
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Instr
SXTH (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x)) forall a. OrdList a -> a -> OrdList a
`snocOL` (Operand -> Operand -> Operand -> Instr
ASR (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_y)))
CmmMachOp (MO_S_Shr Width
w) [CmmExpr
x, (CmmLit (CmmInt Integer
n Width
_))] | Width
w forall a. Eq a => a -> a -> Bool
== Width
W32, Integer
0 forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n forall a. Ord a => a -> a -> Bool
< Integer
32 -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_x forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Instr
ASR (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
n))))
CmmMachOp (MO_S_Shr Width
w) [CmmExpr
x, (CmmLit (CmmInt Integer
n Width
_))] | Width
w forall a. Eq a => a -> a -> Bool
== Width
W64, Integer
0 forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n forall a. Ord a => a -> a -> Bool
< Integer
64 -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_x forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Instr
ASR (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
n))))
CmmMachOp (MO_U_Shr Width
w) [CmmExpr
x, (CmmLit (CmmInt Integer
n Width
_))] | Width
w forall a. Eq a => a -> a -> Bool
== Width
W8, Integer
0 forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n forall a. Ord a => a -> a -> Bool
< Integer
8 -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_x forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Operand -> Instr
UBFX (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
n)) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger (Integer
8forall a. Num a => a -> a -> a
-Integer
n)))))
CmmMachOp (MO_U_Shr Width
w) [CmmExpr
x, CmmExpr
y] | Width
w forall a. Eq a => a -> a -> Bool
== Width
W8 -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(Reg
reg_y, Format
_format_y, OrdList Instr
code_y) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
y
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Instr
UXTB (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x)) forall a. OrdList a -> a -> OrdList a
`snocOL` (Operand -> Operand -> Operand -> Instr
ASR (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_y)))
CmmMachOp (MO_U_Shr Width
w) [CmmExpr
x, (CmmLit (CmmInt Integer
n Width
_))] | Width
w forall a. Eq a => a -> a -> Bool
== Width
W16, Integer
0 forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n forall a. Ord a => a -> a -> Bool
< Integer
16 -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_x forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Operand -> Instr
UBFX (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
n)) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger (Integer
16forall a. Num a => a -> a -> a
-Integer
n)))))
CmmMachOp (MO_U_Shr Width
w) [CmmExpr
x, CmmExpr
y] | Width
w forall a. Eq a => a -> a -> Bool
== Width
W16 -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(Reg
reg_y, Format
_format_y, OrdList Instr
code_y) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
y
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Instr
UXTH (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x)) forall a. OrdList a -> a -> OrdList a
`snocOL` (Operand -> Operand -> Operand -> Instr
ASR (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_y)))
CmmMachOp (MO_U_Shr Width
w) [CmmExpr
x, (CmmLit (CmmInt Integer
n Width
_))] | Width
w forall a. Eq a => a -> a -> Bool
== Width
W32, Integer
0 forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n forall a. Ord a => a -> a -> Bool
< Integer
32 -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_x forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Instr
LSR (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
n))))
CmmMachOp (MO_U_Shr Width
w) [CmmExpr
x, (CmmLit (CmmInt Integer
n Width
_))] | Width
w forall a. Eq a => a -> a -> Bool
== Width
W64, Integer
0 forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n forall a. Ord a => a -> a -> Bool
< Integer
64 -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_x forall a. OrdList a -> a -> OrdList a
`snocOL` CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Instr
LSR (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
n))))
CmmMachOp (MO_And Width
w) [(CmmReg CmmReg
reg), CmmLit (CmmInt Integer
n Width
_)] | Integer -> Bool
isBitMaskImmediate (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n) ->
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
d -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Instr
AND (Width -> Reg -> Operand
OpReg Width
w Reg
d) (Width -> Reg -> Operand
OpReg Width
w' Reg
r') (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
n))))
where w' :: Width
w' = Format -> Width
formatToWidth (CmmType -> Format
cmmTypeFormat (Platform -> CmmReg -> CmmType
cmmRegType Platform
plat CmmReg
reg))
r' :: Reg
r' = Platform -> CmmReg -> Reg
getRegisterReg Platform
plat CmmReg
reg
CmmMachOp (MO_Or Width
w) [(CmmReg CmmReg
reg), CmmLit (CmmInt Integer
n Width
_)] | Integer -> Bool
isBitMaskImmediate (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n) ->
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
d -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Instr
ORR (Width -> Reg -> Operand
OpReg Width
w Reg
d) (Width -> Reg -> Operand
OpReg Width
w' Reg
r') (Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
n))))
where w' :: Width
w' = Format -> Width
formatToWidth (CmmType -> Format
cmmTypeFormat (Platform -> CmmReg -> CmmType
cmmRegType Platform
plat CmmReg
reg))
r' :: Reg
r' = Platform -> CmmReg -> Reg
getRegisterReg Platform
plat CmmReg
reg
CmmMachOp MachOp
op [CmmExpr
x, CmmExpr
y] -> do
let withTempIntReg :: Width -> (Operand -> NatM b) -> NatM b
withTempIntReg Width
w Operand -> NatM b
op = Width -> Reg -> Operand
OpReg Width
w forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Format -> NatM Reg
getNewRegNat (Width -> Format
intFormat Width
w) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Operand -> NatM b
op
bitOp :: Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
bitOp Width
w Operand -> Operand -> Operand -> OrdList Instr
op = do
(Reg
reg_x, Format
format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(Reg
reg_y, Format
format_y, OrdList Instr
code_y) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
y
MASSERT2(isIntFormat format_x == isIntFormat format_y, text "bitOp: incompatible")
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst ->
OrdList Instr
code_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_y forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
Operand -> Operand -> Operand -> OrdList Instr
op (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_y))
intOp :: Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
is_signed Width
w Operand -> Operand -> Operand -> OrdList Instr
op = do
(Reg
reg_x, Format
format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(Reg
reg_y, Format
format_y, OrdList Instr
code_y) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
y
MASSERT2(isIntFormat format_x && isIntFormat format_y, text "intOp: non-int")
let w' :: Width
w' = Width -> Width
opRegWidth Width
w
signExt :: Reg -> OrdList Instr
signExt Reg
r
| Bool -> Bool
not Bool
is_signed = forall a. OrdList a
nilOL
| Bool
otherwise = Width -> Width -> Reg -> OrdList Instr
signExtendReg Width
w Width
w' Reg
r
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) forall a b. (a -> b) -> a -> b
$ \Reg
dst ->
OrdList Instr
code_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_y forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
Reg -> OrdList Instr
signExt Reg
reg_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
Reg -> OrdList Instr
signExt Reg
reg_y forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
Operand -> Operand -> Operand -> OrdList Instr
op (Width -> Reg -> Operand
OpReg Width
w' Reg
dst) (Width -> Reg -> Operand
OpReg Width
w' Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w' Reg
reg_y) forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
Width -> Width -> Reg -> OrdList Instr
truncateReg Width
w' Width
w Reg
dst
floatOp :: Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
floatOp Width
w Operand -> Operand -> Operand -> OrdList Instr
op = do
(Reg
reg_fx, Format
format_x, OrdList Instr
code_fx) <- HasCallStack => CmmExpr -> NatM (Reg, Format, OrdList Instr)
getFloatReg CmmExpr
x
(Reg
reg_fy, Format
format_y, OrdList Instr
code_fy) <- HasCallStack => CmmExpr -> NatM (Reg, Format, OrdList Instr)
getFloatReg CmmExpr
y
MASSERT2(isFloatFormat format_x && isFloatFormat format_y, text "floatOp: non-float")
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
floatFormat Width
w) (\Reg
dst -> OrdList Instr
code_fx forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_fy forall a. OrdList a -> OrdList a -> OrdList a
`appOL` Operand -> Operand -> Operand -> OrdList Instr
op (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_fx) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_fy))
floatCond :: Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
floatCond Width
w Operand -> Operand -> Operand -> OrdList Instr
op = do
(Reg
reg_fx, Format
format_x, OrdList Instr
code_fx) <- HasCallStack => CmmExpr -> NatM (Reg, Format, OrdList Instr)
getFloatReg CmmExpr
x
(Reg
reg_fy, Format
format_y, OrdList Instr
code_fy) <- HasCallStack => CmmExpr -> NatM (Reg, Format, OrdList Instr)
getFloatReg CmmExpr
y
MASSERT2(isFloatFormat format_x && isFloatFormat format_y, text "floatCond: non-float")
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> OrdList Instr
code_fx forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_fy forall a. OrdList a -> OrdList a -> OrdList a
`appOL` Operand -> Operand -> Operand -> OrdList Instr
op (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_fx) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_fy))
case MachOp
op of
MO_Add Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
False Width
w (\Operand
d Operand
x Operand
y -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Instr
ADD Operand
d Operand
x Operand
y))
MO_Sub Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
False Width
w (\Operand
d Operand
x Operand
y -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Instr
SUB Operand
d Operand
x Operand
y))
MO_Eq Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
bitOp Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
EQ ])
MO_Ne Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
bitOp Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
NE ])
MO_Mul Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
True Width
w (\Operand
d Operand
x Operand
y -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
MUL Operand
d Operand
x Operand
y)
MO_S_MulMayOflo Width
w -> Width -> CmmExpr -> CmmExpr -> NatM Register
do_mul_may_oflo Width
w CmmExpr
x CmmExpr
y
MO_S_Quot Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
True Width
w (\Operand
d Operand
x Operand
y -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
SDIV Operand
d Operand
x Operand
y)
MO_S_Rem Width
w -> forall {b}. Width -> (Operand -> NatM b) -> NatM b
withTempIntReg Width
w forall a b. (a -> b) -> a -> b
$ \Operand
t ->
Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
True Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Operand -> Instr
SDIV Operand
t Operand
x Operand
y, Operand -> Operand -> Operand -> Operand -> Instr
MSUB Operand
d Operand
t Operand
y Operand
x ])
MO_U_MulMayOflo Width
_w -> forall env a b. OutputableP env a => env -> a -> b
unsupportedP Platform
plat CmmExpr
expr
MO_U_Quot Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
False Width
w (\Operand
d Operand
x Operand
y -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
UDIV Operand
d Operand
x Operand
y)
MO_U_Rem Width
w -> forall {b}. Width -> (Operand -> NatM b) -> NatM b
withTempIntReg Width
w forall a b. (a -> b) -> a -> b
$ \Operand
t ->
Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
False Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Operand -> Instr
UDIV Operand
t Operand
x Operand
y, Operand -> Operand -> Operand -> Operand -> Instr
MSUB Operand
d Operand
t Operand
y Operand
x ])
MO_S_Ge Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
True Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
SGE ])
MO_S_Le Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
True Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
SLE ])
MO_S_Gt Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
True Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
SGT ])
MO_S_Lt Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
True Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
SLT ])
MO_U_Ge Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
False Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
UGE ])
MO_U_Le Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
False Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
ULE ])
MO_U_Gt Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
False Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
UGT ])
MO_U_Lt Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
False Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
ULT ])
MO_F_Add Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
floatOp Width
w (\Operand
d Operand
x Operand
y -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
ADD Operand
d Operand
x Operand
y)
MO_F_Sub Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
floatOp Width
w (\Operand
d Operand
x Operand
y -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
SUB Operand
d Operand
x Operand
y)
MO_F_Mul Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
floatOp Width
w (\Operand
d Operand
x Operand
y -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
MUL Operand
d Operand
x Operand
y)
MO_F_Quot Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
floatOp Width
w (\Operand
d Operand
x Operand
y -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
SDIV Operand
d Operand
x Operand
y)
MO_F_Eq Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
floatCond Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
EQ ])
MO_F_Ne Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
floatCond Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
NE ])
MO_F_Ge Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
floatCond Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
OGE ])
MO_F_Le Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
floatCond Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
OLE ])
MO_F_Gt Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
floatCond Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
OGT ])
MO_F_Lt Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
floatCond Width
w (\Operand
d Operand
x Operand
y -> forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
OLT ])
MO_And Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
bitOp Width
w (\Operand
d Operand
x Operand
y -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
AND Operand
d Operand
x Operand
y)
MO_Or Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
bitOp Width
w (\Operand
d Operand
x Operand
y -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
ORR Operand
d Operand
x Operand
y)
MO_Xor Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
bitOp Width
w (\Operand
d Operand
x Operand
y -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
EOR Operand
d Operand
x Operand
y)
MO_Shl Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
False Width
w (\Operand
d Operand
x Operand
y -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
LSL Operand
d Operand
x Operand
y)
MO_U_Shr Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
False Width
w (\Operand
d Operand
x Operand
y -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
LSR Operand
d Operand
x Operand
y)
MO_S_Shr Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
True Width
w (\Operand
d Operand
x Operand
y -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
ASR Operand
d Operand
x Operand
y)
MachOp
op -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (unhandled dyadic CmmMachOp): " forall a b. (a -> b) -> a -> b
$ (MachOp -> SDoc
pprMachOp MachOp
op) SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"in" SDoc -> SDoc -> SDoc
<+> (forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmMachOp MachOp
_op [CmmExpr]
_xs
-> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (variadic CmmMachOp): " (forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
where
unsupportedP :: OutputableP env a => env -> a -> b
unsupportedP :: forall env a b. OutputableP env a => env -> a -> b
unsupportedP env
platform a
op = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"Unsupported op:" (forall env a. OutputableP env a => env -> a -> SDoc
pdoc env
platform a
op)
isNbitEncodeable :: Int -> Integer -> Bool
isNbitEncodeable :: Int -> Integer -> Bool
isNbitEncodeable Int
n Integer
i = let shift :: Int
shift = Int
n forall a. Num a => a -> a -> a
- Int
1 in (-Integer
1 forall a. Bits a => a -> Int -> a
`shiftL` Int
shift) forall a. Ord a => a -> a -> Bool
<= Integer
i Bool -> Bool -> Bool
&& Integer
i forall a. Ord a => a -> a -> Bool
< (Integer
1 forall a. Bits a => a -> Int -> a
`shiftL` Int
shift)
isBitMaskImmediate :: Integer -> Bool
isBitMaskImmediate :: Integer -> Bool
isBitMaskImmediate Integer
i = Integer
i forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Integer
0b0000_0001, Integer
0b0000_0010, Integer
0b0000_0100, Integer
0b0000_1000, Integer
0b0001_0000, Integer
0b0010_0000, Integer
0b0100_0000, Integer
0b1000_0000
,Integer
0b0000_0011, Integer
0b0000_0110, Integer
0b0000_1100, Integer
0b0001_1000, Integer
0b0011_0000, Integer
0b0110_0000, Integer
0b1100_0000
,Integer
0b0000_0111, Integer
0b0000_1110, Integer
0b0001_1100, Integer
0b0011_1000, Integer
0b0111_0000, Integer
0b1110_0000
,Integer
0b0000_1111, Integer
0b0001_1110, Integer
0b0011_1100, Integer
0b0111_1000, Integer
0b1111_0000
,Integer
0b0001_1111, Integer
0b0011_1110, Integer
0b0111_1100, Integer
0b1111_1000
,Integer
0b0011_1111, Integer
0b0111_1110, Integer
0b1111_1100
,Integer
0b0111_1111, Integer
0b1111_1110
,Integer
0b1111_1111]
do_mul_may_oflo :: Width -> CmmExpr -> CmmExpr -> NatM Register
do_mul_may_oflo :: Width -> CmmExpr -> CmmExpr -> NatM Register
do_mul_may_oflo w :: Width
w@Width
W64 CmmExpr
x CmmExpr
y = do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(Reg
reg_y, Format
_format_y, OrdList Instr
code_y) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
y
Reg
lo <- Format -> NatM Reg
getNewRegNat Format
II64
Reg
hi <- Format -> NatM Reg
getNewRegNat Format
II64
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst ->
OrdList Instr
code_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_y forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Operand -> Operand -> Instr
MUL (Width -> Reg -> Operand
OpReg Width
w Reg
lo) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_y) forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Operand -> Operand -> Instr
SMULH (Width -> Reg -> Operand
OpReg Width
w Reg
hi) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_y) forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Operand -> Instr
CMP (Width -> Reg -> Operand
OpReg Width
w Reg
hi) (Width -> Reg -> ShiftMode -> Int -> Operand
OpRegShift Width
w Reg
lo ShiftMode
SASR Int
63) forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Cond -> Instr
CSET (Width -> Reg -> Operand
OpReg Width
w Reg
dst) Cond
NE)
do_mul_may_oflo Width
w CmmExpr
x CmmExpr
y = do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(Reg
reg_y, Format
_format_y, OrdList Instr
code_y) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
y
let tmp_w :: Width
tmp_w = case Width
w of
Width
W32 -> Width
W64
Width
W16 -> Width
W32
Width
W8 -> Width
W32
Width
_ -> forall a. String -> a
panic String
"do_mul_may_oflo: impossible"
Reg
tmp <- Format -> NatM Reg
getNewRegNat (Width -> Format
intFormat Width
tmp_w)
let ext_mode :: ExtMode
ext_mode = case Width
w of
Width
W32 -> ExtMode
ESXTW
Width
W16 -> ExtMode
ESXTH
Width
W8 -> ExtMode
ESXTB
Width
_ -> forall a. String -> a
panic String
"do_mul_may_oflo: impossible"
mul :: Operand -> Operand -> Operand -> Instr
mul = case Width
w of
Width
W32 -> Operand -> Operand -> Operand -> Instr
SMULL
Width
W16 -> Operand -> Operand -> Operand -> Instr
MUL
Width
W8 -> Operand -> Operand -> Operand -> Instr
MUL
Width
_ -> forall a. String -> a
panic String
"do_mul_may_oflo: impossible"
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst ->
OrdList Instr
code_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_y forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Operand -> Operand -> Instr
mul (Width -> Reg -> Operand
OpReg Width
tmp_w Reg
tmp) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_y) forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Operand -> Instr
CMP (Width -> Reg -> Operand
OpReg Width
tmp_w Reg
tmp) (Width -> Reg -> ExtMode -> Int -> Operand
OpRegExt Width
tmp_w Reg
tmp ExtMode
ext_mode Int
0) forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Cond -> Instr
CSET (Width -> Reg -> Operand
OpReg Width
w Reg
dst) Cond
NE)
signExtendReg :: Width -> Width -> Reg -> OrdList Instr
signExtendReg :: Width -> Width -> Reg -> OrdList Instr
signExtendReg Width
w Width
w' Reg
r =
case Width
w of
Width
W64 -> forall a. OrdList a
nilOL
Width
W32
| Width
w' forall a. Eq a => a -> a -> Bool
== Width
W32 -> forall a. OrdList a
nilOL
| Bool
otherwise -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Instr
SXTH (Width -> Reg -> Operand
OpReg Width
w' Reg
r) (Width -> Reg -> Operand
OpReg Width
w' Reg
r)
Width
W16 -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Instr
SXTH (Width -> Reg -> Operand
OpReg Width
w' Reg
r) (Width -> Reg -> Operand
OpReg Width
w' Reg
r)
Width
W8 -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Instr
SXTB (Width -> Reg -> Operand
OpReg Width
w' Reg
r) (Width -> Reg -> Operand
OpReg Width
w' Reg
r)
Width
_ -> forall a. String -> a
panic String
"intOp"
truncateReg :: Width -> Width -> Reg -> OrdList Instr
truncateReg :: Width -> Width -> Reg -> OrdList Instr
truncateReg Width
w Width
w' Reg
r =
case Width
w of
Width
W64 -> forall a. OrdList a
nilOL
Width
W32
| Width
w' forall a. Eq a => a -> a -> Bool
== Width
W32 -> forall a. OrdList a
nilOL
Width
_ -> forall a. a -> OrdList a
unitOL forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Operand -> Instr
UBFM (Width -> Reg -> Operand
OpReg Width
w Reg
r)
(Width -> Reg -> Operand
OpReg Width
w Reg
r)
(Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
0))
(Imm -> Operand
OpImm forall a b. (a -> b) -> a -> b
$ Int -> Imm
ImmInt forall a b. (a -> b) -> a -> b
$ Width -> Int
widthInBits Width
w' forall a. Num a => a -> a -> a
- Int
1)
data Amode = Amode AddrMode InstrBlock
getAmode :: Platform
-> Width
-> CmmExpr
-> NatM Amode
getAmode :: Platform -> Width -> CmmExpr -> NatM Amode
getAmode Platform
platform Width
_ (CmmRegOff CmmReg
reg Int
off) | -Int
256 forall a. Ord a => a -> a -> Bool
<= Int
off, Int
off forall a. Ord a => a -> a -> Bool
<= Int
255
= forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ AddrMode -> OrdList Instr -> Amode
Amode (Reg -> Imm -> AddrMode
AddrRegImm Reg
reg' Imm
off') forall a. OrdList a
nilOL
where reg' :: Reg
reg' = Platform -> CmmReg -> Reg
getRegisterReg Platform
platform CmmReg
reg
off' :: Imm
off' = Int -> Imm
ImmInt Int
off
getAmode Platform
platform Width
W32 (CmmRegOff CmmReg
reg Int
off)
| Int
0 forall a. Ord a => a -> a -> Bool
<= Int
off, Int
off forall a. Ord a => a -> a -> Bool
<= Int
16380, Int
off forall a. Integral a => a -> a -> a
`mod` Int
4 forall a. Eq a => a -> a -> Bool
== Int
0
= forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ AddrMode -> OrdList Instr -> Amode
Amode (Reg -> Imm -> AddrMode
AddrRegImm Reg
reg' Imm
off') forall a. OrdList a
nilOL
where reg' :: Reg
reg' = Platform -> CmmReg -> Reg
getRegisterReg Platform
platform CmmReg
reg
off' :: Imm
off' = Int -> Imm
ImmInt Int
off
getAmode Platform
platform Width
W64 (CmmRegOff CmmReg
reg Int
off)
| Int
0 forall a. Ord a => a -> a -> Bool
<= Int
off, Int
off forall a. Ord a => a -> a -> Bool
<= Int
32760, Int
off forall a. Integral a => a -> a -> a
`mod` Int
8 forall a. Eq a => a -> a -> Bool
== Int
0
= forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ AddrMode -> OrdList Instr -> Amode
Amode (Reg -> Imm -> AddrMode
AddrRegImm Reg
reg' Imm
off') forall a. OrdList a
nilOL
where reg' :: Reg
reg' = Platform -> CmmReg -> Reg
getRegisterReg Platform
platform CmmReg
reg
off' :: Imm
off' = Int -> Imm
ImmInt Int
off
getAmode Platform
_platform Width
_ (CmmMachOp (MO_Add Width
_w) [CmmExpr
expr, CmmLit (CmmInt Integer
off Width
_w')])
| -Integer
256 forall a. Ord a => a -> a -> Bool
<= Integer
off, Integer
off forall a. Ord a => a -> a -> Bool
<= Integer
255
= do (Reg
reg, Format
_format, OrdList Instr
code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
expr
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ AddrMode -> OrdList Instr -> Amode
Amode (Reg -> Imm -> AddrMode
AddrRegImm Reg
reg (Integer -> Imm
ImmInteger Integer
off)) OrdList Instr
code
getAmode Platform
_platform Width
_ (CmmMachOp (MO_Sub Width
_w) [CmmExpr
expr, CmmLit (CmmInt Integer
off Width
_w')])
| -Integer
256 forall a. Ord a => a -> a -> Bool
<= -Integer
off, -Integer
off forall a. Ord a => a -> a -> Bool
<= Integer
255
= do (Reg
reg, Format
_format, OrdList Instr
code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
expr
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ AddrMode -> OrdList Instr -> Amode
Amode (Reg -> Imm -> AddrMode
AddrRegImm Reg
reg (Integer -> Imm
ImmInteger (-Integer
off))) OrdList Instr
code
getAmode Platform
_platform Width
_ CmmExpr
expr
= do (Reg
reg, Format
_format, OrdList Instr
code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
expr
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ AddrMode -> OrdList Instr -> Amode
Amode (Reg -> AddrMode
AddrReg Reg
reg) OrdList Instr
code
assignMem_IntCode :: Format -> CmmExpr -> CmmExpr -> NatM InstrBlock
assignReg_IntCode :: Format -> CmmReg -> CmmExpr -> NatM InstrBlock
assignMem_FltCode :: Format -> CmmExpr -> CmmExpr -> NatM InstrBlock
assignReg_FltCode :: Format -> CmmReg -> CmmExpr -> NatM InstrBlock
assignMem_IntCode :: Format -> CmmExpr -> CmmExpr -> NatM (OrdList Instr)
assignMem_IntCode Format
rep CmmExpr
addrE CmmExpr
srcE
= do
(Reg
src_reg, Format
_format, OrdList Instr
code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
srcE
Platform
platform <- NatM Platform
getPlatform
let w :: Width
w = Format -> Width
formatToWidth Format
rep
Amode AddrMode
addr OrdList Instr
addr_code <- Platform -> Width -> CmmExpr -> NatM Amode
getAmode Platform
platform Width
w CmmExpr
addrE
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ SDoc -> Instr
COMMENT (String -> SDoc
text String
"CmmStore" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (String -> SDoc
text (forall a. Show a => a -> String
show CmmExpr
addrE)) SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (String -> SDoc
text (forall a. Show a => a -> String
show CmmExpr
srcE)))
forall a. a -> OrdList a -> OrdList a
`consOL` (OrdList Instr
code
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
addr_code
forall a. OrdList a -> a -> OrdList a
`snocOL` Format -> Operand -> Operand -> Instr
STR Format
rep (Width -> Reg -> Operand
OpReg Width
w Reg
src_reg) (AddrMode -> Operand
OpAddr AddrMode
addr))
assignReg_IntCode :: Format -> CmmReg -> CmmExpr -> NatM (OrdList Instr)
assignReg_IntCode Format
_ CmmReg
reg CmmExpr
src
= do
Platform
platform <- NatM Platform
getPlatform
let dst :: Reg
dst = Platform -> CmmReg -> Reg
getRegisterReg Platform
platform CmmReg
reg
Register
r <- CmmExpr -> NatM Register
getRegister CmmExpr
src
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Register
r of
Any Format
_ Reg -> OrdList Instr
code -> SDoc -> Instr
COMMENT (String -> SDoc
text String
"CmmAssign" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (String -> SDoc
text (forall a. Show a => a -> String
show CmmReg
reg)) SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (String -> SDoc
text (forall a. Show a => a -> String
show CmmExpr
src))) forall a. a -> OrdList a -> OrdList a
`consOL` Reg -> OrdList Instr
code Reg
dst
Fixed Format
format Reg
freg OrdList Instr
fcode -> SDoc -> Instr
COMMENT (String -> SDoc
text String
"CmmAssign" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (String -> SDoc
text (forall a. Show a => a -> String
show CmmReg
reg)) SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (String -> SDoc
text (forall a. Show a => a -> String
show CmmExpr
src))) forall a. a -> OrdList a -> OrdList a
`consOL` (OrdList Instr
fcode forall a. OrdList a -> a -> OrdList a
`snocOL` Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg (Format -> Width
formatToWidth Format
format) Reg
dst) (Width -> Reg -> Operand
OpReg (Format -> Width
formatToWidth Format
format) Reg
freg))
assignMem_FltCode :: Format -> CmmExpr -> CmmExpr -> NatM (OrdList Instr)
assignMem_FltCode = Format -> CmmExpr -> CmmExpr -> NatM (OrdList Instr)
assignMem_IntCode
assignReg_FltCode :: Format -> CmmReg -> CmmExpr -> NatM (OrdList Instr)
assignReg_FltCode = Format -> CmmReg -> CmmExpr -> NatM (OrdList Instr)
assignReg_IntCode
genJump :: CmmExpr -> NatM InstrBlock
genJump :: CmmExpr -> NatM (OrdList Instr)
genJump expr :: CmmExpr
expr@(CmmLit (CmmLabel CLabel
lbl))
= forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> OrdList a
unitOL (CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Target -> Instr
J (CLabel -> Target
TLabel CLabel
lbl)))
genJump CmmExpr
expr = do
(Reg
target, Format
_format, OrdList Instr
code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
expr
forall (m :: * -> *) a. Monad m => a -> m a
return (OrdList Instr
code forall a. OrdList a -> OrdList a -> OrdList a
`appOL` forall a. a -> OrdList a
unitOL (CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Target -> Instr
J (Reg -> Target
TReg Reg
target))))
genBranch :: BlockId -> NatM InstrBlock
genBranch :: Label -> NatM (OrdList Instr)
genBranch = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> OrdList a
toOL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Label -> [Instr]
mkJumpInstr
genCondJump
:: BlockId
-> CmmExpr
-> NatM InstrBlock
genCondJump :: Label -> CmmExpr -> NatM (OrdList Instr)
genCondJump Label
bid CmmExpr
expr = do
case CmmExpr
expr of
CmmMachOp (MO_Eq Width
w) [CmmExpr
x, CmmLit (CmmInt Integer
0 Width
_)] -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ OrdList Instr
code_x forall a. OrdList a -> a -> OrdList a
`snocOL` (CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Target -> Instr
CBZ (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Label -> Target
TBlock Label
bid)))
CmmMachOp (MO_Ne Width
w) [CmmExpr
x, CmmLit (CmmInt Integer
0 Width
_)] -> do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ OrdList Instr
code_x forall a. OrdList a -> a -> OrdList a
`snocOL` (CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Target -> Instr
CBNZ (Width -> Reg -> Operand
OpReg Width
w Reg
reg_x) (Label -> Target
TBlock Label
bid)))
CmmMachOp MachOp
mop [CmmExpr
x, CmmExpr
y] -> do
let ubcond :: Width -> Cond -> NatM (OrdList Instr)
ubcond Width
w Cond
cmp = do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(Reg
reg_y, Format
_format_y, OrdList Instr
code_y) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
y
let x' :: Operand
x' = Width -> Reg -> Operand
OpReg Width
w Reg
reg_x
y' :: Operand
y' = Width -> Reg -> Operand
OpReg Width
w Reg
reg_y
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Width
w of
Width
W8 -> OrdList Instr
code_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y forall a. OrdList a -> OrdList a -> OrdList a
`appOL` forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
UXTB Operand
x' Operand
x', Operand -> Operand -> Instr
UXTB Operand
y' Operand
y', Operand -> Operand -> Instr
CMP Operand
x' Operand
y', (CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Cond -> Target -> Instr
BCOND Cond
cmp (Label -> Target
TBlock Label
bid))) ]
Width
W16 -> OrdList Instr
code_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y forall a. OrdList a -> OrdList a -> OrdList a
`appOL` forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
UXTH Operand
x' Operand
x', Operand -> Operand -> Instr
UXTH Operand
y' Operand
y', Operand -> Operand -> Instr
CMP Operand
x' Operand
y', (CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Cond -> Target -> Instr
BCOND Cond
cmp (Label -> Target
TBlock Label
bid))) ]
Width
_ -> OrdList Instr
code_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y forall a. OrdList a -> OrdList a -> OrdList a
`appOL` forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x' Operand
y', (CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Cond -> Target -> Instr
BCOND Cond
cmp (Label -> Target
TBlock Label
bid))) ]
sbcond :: Width -> Cond -> NatM (OrdList Instr)
sbcond Width
w Cond
cmp = do
(Reg
reg_x, Format
_format_x, OrdList Instr
code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(Reg
reg_y, Format
_format_y, OrdList Instr
code_y) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
y
let x' :: Operand
x' = Width -> Reg -> Operand
OpReg Width
w Reg
reg_x
y' :: Operand
y' = Width -> Reg -> Operand
OpReg Width
w Reg
reg_y
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Width
w of
Width
W8 -> OrdList Instr
code_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y forall a. OrdList a -> OrdList a -> OrdList a
`appOL` forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
SXTB Operand
x' Operand
x', Operand -> Operand -> Instr
SXTB Operand
y' Operand
y', Operand -> Operand -> Instr
CMP Operand
x' Operand
y', (CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Cond -> Target -> Instr
BCOND Cond
cmp (Label -> Target
TBlock Label
bid))) ]
Width
W16 -> OrdList Instr
code_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y forall a. OrdList a -> OrdList a -> OrdList a
`appOL` forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
SXTH Operand
x' Operand
x', Operand -> Operand -> Instr
SXTH Operand
y' Operand
y', Operand -> Operand -> Instr
CMP Operand
x' Operand
y', (CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Cond -> Target -> Instr
BCOND Cond
cmp (Label -> Target
TBlock Label
bid))) ]
Width
_ -> OrdList Instr
code_x forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y forall a. OrdList a -> OrdList a -> OrdList a
`appOL` forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x' Operand
y', (CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Cond -> Target -> Instr
BCOND Cond
cmp (Label -> Target
TBlock Label
bid))) ]
fbcond :: Width -> Cond -> NatM (OrdList Instr)
fbcond Width
w Cond
cmp = do
(Reg
reg_fx, Format
_format_fx, OrdList Instr
code_fx) <- HasCallStack => CmmExpr -> NatM (Reg, Format, OrdList Instr)
getFloatReg CmmExpr
x
(Reg
reg_fy, Format
_format_fy, OrdList Instr
code_fy) <- HasCallStack => CmmExpr -> NatM (Reg, Format, OrdList Instr)
getFloatReg CmmExpr
y
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ OrdList Instr
code_fx forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_fy forall a. OrdList a -> a -> OrdList a
`snocOL` Operand -> Operand -> Instr
CMP (Width -> Reg -> Operand
OpReg Width
w Reg
reg_fx) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_fy) forall a. OrdList a -> a -> OrdList a
`snocOL` (CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Cond -> Target -> Instr
BCOND Cond
cmp (Label -> Target
TBlock Label
bid)))
case MachOp
mop of
MO_F_Eq Width
w -> Width -> Cond -> NatM (OrdList Instr)
fbcond Width
w Cond
EQ
MO_F_Ne Width
w -> Width -> Cond -> NatM (OrdList Instr)
fbcond Width
w Cond
NE
MO_F_Gt Width
w -> Width -> Cond -> NatM (OrdList Instr)
fbcond Width
w Cond
OGT
MO_F_Ge Width
w -> Width -> Cond -> NatM (OrdList Instr)
fbcond Width
w Cond
OGE
MO_F_Lt Width
w -> Width -> Cond -> NatM (OrdList Instr)
fbcond Width
w Cond
OLT
MO_F_Le Width
w -> Width -> Cond -> NatM (OrdList Instr)
fbcond Width
w Cond
OLE
MO_Eq Width
w -> Width -> Cond -> NatM (OrdList Instr)
sbcond Width
w Cond
EQ
MO_Ne Width
w -> Width -> Cond -> NatM (OrdList Instr)
sbcond Width
w Cond
NE
MO_S_Gt Width
w -> Width -> Cond -> NatM (OrdList Instr)
sbcond Width
w Cond
SGT
MO_S_Ge Width
w -> Width -> Cond -> NatM (OrdList Instr)
sbcond Width
w Cond
SGE
MO_S_Lt Width
w -> Width -> Cond -> NatM (OrdList Instr)
sbcond Width
w Cond
SLT
MO_S_Le Width
w -> Width -> Cond -> NatM (OrdList Instr)
sbcond Width
w Cond
SLE
MO_U_Gt Width
w -> Width -> Cond -> NatM (OrdList Instr)
ubcond Width
w Cond
UGT
MO_U_Ge Width
w -> Width -> Cond -> NatM (OrdList Instr)
ubcond Width
w Cond
UGE
MO_U_Lt Width
w -> Width -> Cond -> NatM (OrdList Instr)
ubcond Width
w Cond
ULT
MO_U_Le Width
w -> Width -> Cond -> NatM (OrdList Instr)
ubcond Width
w Cond
ULE
MachOp
_ -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"AArch64.genCondJump:case mop: " (String -> SDoc
text forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show CmmExpr
expr)
CmmExpr
_ -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"AArch64.genCondJump: " (String -> SDoc
text forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show CmmExpr
expr)
genCondBranch
:: BlockId
-> BlockId
-> BlockId
-> CmmExpr
-> NatM InstrBlock
genCondBranch :: Label -> Label -> Label -> CmmExpr -> NatM (OrdList Instr)
genCondBranch Label
_ Label
true Label
false CmmExpr
expr = do
OrdList Instr
b1 <- Label -> CmmExpr -> NatM (OrdList Instr)
genCondJump Label
true CmmExpr
expr
OrdList Instr
b2 <- Label -> NatM (OrdList Instr)
genBranch Label
false
forall (m :: * -> *) a. Monad m => a -> m a
return (OrdList Instr
b1 forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
b2)
genCCall
:: ForeignTarget
-> [CmmFormal]
-> [CmmActual]
-> BlockId
-> NatM (InstrBlock, Maybe BlockId)
genCCall :: ForeignTarget
-> [CmmFormal]
-> [CmmExpr]
-> Label
-> NatM (OrdList Instr, Maybe Label)
genCCall ForeignTarget
target [CmmFormal]
dest_regs [CmmExpr]
arg_regs Label