{-# language GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
module GHC.CmmToAsm.AArch64.CodeGen (
cmmTopCodeGen
, generateJumpTableForInstr
, makeFarBranches
)
where
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.Label
import GHC.Cmm.Dataflow.Graph
import GHC.Types.Tickish ( GenTickish(..) )
import GHC.Types.SrcLoc ( srcSpanFile, srcSpanStartLine, srcSpanStartCol )
import GHC.Types.Unique.Supply
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
import GHC.Utils.Constants (debugIsOn)
import GHC.Utils.Monad (mapAccumLM)
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
(nat_blocks,statics) <- (Block CmmNode C C
-> NatM ([NatBasicBlock Instr], [NatCmmDecl RawCmmStatics Instr]))
-> [Block CmmNode C C]
-> NatM
([[NatBasicBlock Instr]], [[NatCmmDecl RawCmmStatics Instr]])
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
picBaseMb <- getPicBaseMaybeNat
let proc = LabelMap RawCmmStatics
-> CLabel
-> [GlobalReg]
-> ListGraph Instr
-> NatCmmDecl RawCmmStatics Instr
forall d h g. h -> CLabel -> [GlobalReg] -> g -> GenCmmDecl d h g
CmmProc LabelMap RawCmmStatics
info CLabel
lab [GlobalReg]
live ([NatBasicBlock Instr] -> ListGraph Instr
forall i. [GenBasicBlock i] -> ListGraph i
ListGraph ([NatBasicBlock Instr] -> ListGraph Instr)
-> [NatBasicBlock Instr] -> ListGraph Instr
forall a b. (a -> b) -> a -> b
$ [[NatBasicBlock Instr]] -> [NatBasicBlock Instr]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[NatBasicBlock Instr]]
nat_blocks)
tops = NatCmmDecl RawCmmStatics Instr
proc NatCmmDecl RawCmmStatics Instr
-> [NatCmmDecl RawCmmStatics Instr]
-> [NatCmmDecl RawCmmStatics Instr]
forall a. a -> [a] -> [a]
: [[NatCmmDecl RawCmmStatics Instr]]
-> [NatCmmDecl RawCmmStatics Instr]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[NatCmmDecl RawCmmStatics Instr]]
statics
case picBaseMb of
Just Reg
_picBase -> String -> NatM [NatCmmDecl RawCmmStatics Instr]
forall a. HasCallStack => String -> a
panic String
"AArch64.cmmTopCodeGen: picBase not implemented"
Maybe Reg
Nothing -> [NatCmmDecl RawCmmStatics Instr]
-> NatM [NatCmmDecl RawCmmStatics Instr]
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return [NatCmmDecl RawCmmStatics Instr]
tops
cmmTopCodeGen _cmm :: RawCmmDecl
_cmm@(CmmData Section
sec RawCmmStatics
dat) = do
[NatCmmDecl RawCmmStatics Instr]
-> NatM [NatCmmDecl RawCmmStatics Instr]
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return [Section -> RawCmmStatics -> NatCmmDecl RawCmmStatics Instr
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
config <- NatM NCGConfig
getConfig
let (_, nodes, tail) = blockSplit block
id = Block CmmNode C C -> BlockId
forall (x :: Extensibility). Block CmmNode C x -> BlockId
forall (thing :: Extensibility -> Extensibility -> *)
(x :: Extensibility).
NonLocal thing =>
thing C x -> BlockId
entryLabel Block CmmNode C C
block
stmts = Block CmmNode O O -> [CmmNode O O]
forall (n :: Extensibility -> Extensibility -> *).
Block n O O -> [n O O]
blockToList Block CmmNode O O
nodes
header_comment_instr | Bool
debugIsOn = Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ SDoc -> Instr
MULTILINE_COMMENT (
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"-- --------------------------- basicBlockCodeGen --------------------------- --\n"
SDoc -> SDoc -> SDoc
$+$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultDumpStyle (Platform -> Block CmmNode C C -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc (NCGConfig -> Platform
ncgPlatform NCGConfig
config) Block CmmNode C C
block)
)
| Bool
otherwise = OrdList Instr
forall a. OrdList a
nilOL
dbg <- getDebugBlock (entryLabel block)
loc_instrs <- case dblSourceTick =<< dbg of
Just (SourceNote RealSrcSpan
span (LexicalFastString FastString
name))
-> do fileId <- FastString -> NatM Int
getFileId (RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
span)
let line = RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan
span; col = RealSrcSpan -> Int
srcSpanStartCol RealSrcSpan
span
return $ unitOL $ LOCATION fileId line col (unpackFS name)
Maybe CmmTickish
_ -> OrdList Instr -> NatM (OrdList Instr)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return OrdList Instr
forall a. OrdList a
nilOL
(mid_instrs,mid_bid) <- stmtsToInstrs id stmts
(!tail_instrs,_) <- stmtToInstrs mid_bid tail
let instrs = OrdList Instr
header_comment_instr OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
loc_instrs OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
mid_instrs OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
tail_instrs
let
(top,other_blocks,statics) = foldrOL mkBlocks ([],[],[]) instrs
return (BasicBlock id top : other_blocks, statics)
mkBlocks :: Instr
-> ([Instr], [GenBasicBlock Instr], [GenCmmDecl RawCmmStatics h g])
-> ([Instr], [GenBasicBlock Instr], [GenCmmDecl RawCmmStatics h g])
mkBlocks :: forall h g.
Instr
-> ([Instr], [NatBasicBlock Instr], [GenCmmDecl RawCmmStatics h g])
-> ([Instr], [NatBasicBlock Instr], [GenCmmDecl RawCmmStatics h g])
mkBlocks (NEWBLOCK BlockId
id) ([Instr]
instrs,[NatBasicBlock Instr]
blocks,[GenCmmDecl RawCmmStatics h g]
statics)
= ([], BlockId -> [Instr] -> NatBasicBlock Instr
forall i. BlockId -> [i] -> GenBasicBlock i
BasicBlock BlockId
id [Instr]
instrs NatBasicBlock Instr
-> [NatBasicBlock Instr] -> [NatBasicBlock Instr]
forall a. a -> [a] -> [a]
: [NatBasicBlock Instr]
blocks, [GenCmmDecl RawCmmStatics h g]
statics)
mkBlocks Instr
instr ([Instr]
instrs,[NatBasicBlock Instr]
blocks,[GenCmmDecl RawCmmStatics h g]
statics)
= (Instr
instrInstr -> [Instr] -> [Instr]
forall a. a -> [a] -> [a]
:[Instr]
instrs, [NatBasicBlock Instr]
blocks, [GenCmmDecl RawCmmStatics h g]
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
forall doc. IsLine doc => String -> doc
text (String -> SDoc) -> (CmmExpr -> String) -> CmmExpr -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CmmExpr -> String
forall a. Show a => a -> String
show (CmmExpr -> SDoc) -> CmmExpr -> SDoc
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, format, code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
expr
let w = Format -> Width
formatToWidth Format
format
let mkbranch OrdList Instr
acc (Integer
key, BlockId
bid) = do
(keyReg, _format, code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg (CmmLit -> CmmExpr
CmmLit (Integer -> Width -> CmmLit
CmmInt Integer
key Width
w))
return $ code `appOL`
toOL [ CMP (OpReg w reg) (OpReg w keyReg)
, BCOND EQ (TBlock bid)
] `appOL` acc
def_code = case SwitchTargets -> Maybe BlockId
switchTargetsDefault SwitchTargets
targets of
Just BlockId
bid -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Target -> Instr
B (BlockId -> Target
TBlock BlockId
bid))
Maybe BlockId
Nothing -> OrdList Instr
forall a. OrdList a
nilOL
switch_code <- foldM mkbranch nilOL (switchTargetsCases targets)
return $ code `appOL` switch_code `appOL` def_code
generateJumpTableForInstr :: NCGConfig -> Instr
-> Maybe (NatCmmDecl RawCmmStatics Instr)
generateJumpTableForInstr :: NCGConfig -> Instr -> Maybe (NatCmmDecl RawCmmStatics Instr)
generateJumpTableForInstr NCGConfig
_ Instr
_ = Maybe (NatCmmDecl RawCmmStatics Instr)
forall a. Maybe a
Nothing
stmtsToInstrs :: BlockId
-> [CmmNode O O]
-> NatM (InstrBlock, BlockId)
stmtsToInstrs :: BlockId -> [CmmNode O O] -> NatM (OrdList Instr, BlockId)
stmtsToInstrs BlockId
bid [CmmNode O O]
stmts =
BlockId
-> [CmmNode O O] -> OrdList Instr -> NatM (OrdList Instr, BlockId)
forall {e :: Extensibility} {x :: Extensibility}.
BlockId
-> [CmmNode e x] -> OrdList Instr -> NatM (OrdList Instr, BlockId)
go BlockId
bid [CmmNode O O]
stmts OrdList Instr
forall a. OrdList a
nilOL
where
go :: BlockId
-> [CmmNode e x] -> OrdList Instr -> NatM (OrdList Instr, BlockId)
go BlockId
bid [] OrdList Instr
instrs = (OrdList Instr, BlockId) -> NatM (OrdList Instr, BlockId)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OrdList Instr
instrs,BlockId
bid)
go BlockId
bid (CmmNode e x
s:[CmmNode e x]
stmts) OrdList Instr
instrs = do
(instrs',bid') <- BlockId -> CmmNode e x -> NatM (OrdList Instr, Maybe BlockId)
forall (e :: Extensibility) (x :: Extensibility).
BlockId -> CmmNode e x -> NatM (OrdList Instr, Maybe BlockId)
stmtToInstrs BlockId
bid CmmNode e x
s
let !newBid = BlockId -> Maybe BlockId -> BlockId
forall a. a -> Maybe a -> a
fromMaybe BlockId
bid Maybe BlockId
bid'
go newBid stmts (instrs `appOL` instrs')
stmtToInstrs :: BlockId
-> CmmNode e x
-> NatM (InstrBlock, Maybe BlockId)
stmtToInstrs :: forall (e :: Extensibility) (x :: Extensibility).
BlockId -> CmmNode e x -> NatM (OrdList Instr, Maybe BlockId)
stmtToInstrs BlockId
bid CmmNode e x
stmt = do
platform <- NatM Platform
getPlatform
case stmt of
CmmUnsafeForeignCall ForeignTarget
target [CmmFormal]
result_regs [CmmExpr]
args
-> ForeignTarget
-> [CmmFormal]
-> [CmmExpr]
-> BlockId
-> NatM (OrdList Instr, Maybe BlockId)
genCCall ForeignTarget
target [CmmFormal]
result_regs [CmmExpr]
args BlockId
bid
CmmNode e x
_ -> (,Maybe BlockId
forall a. Maybe a
Nothing) (OrdList Instr -> (OrdList Instr, Maybe BlockId))
-> NatM (OrdList Instr) -> NatM (OrdList Instr, Maybe BlockId)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case CmmNode e x
stmt of
CmmComment FastString
s -> OrdList Instr -> NatM (OrdList Instr)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (SDoc -> Instr
COMMENT (FastString -> SDoc
forall doc. IsLine doc => FastString -> doc
ftext FastString
s)))
CmmTick {} -> OrdList Instr -> NatM (OrdList Instr)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return OrdList Instr
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 = CmmReg -> CmmType
cmmRegType 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 BlockId
id -> BlockId -> NatM (OrdList Instr)
genBranch BlockId
id
CmmCondBranch CmmExpr
arg BlockId
true BlockId
false Maybe Bool
_prediction ->
BlockId -> BlockId -> BlockId -> CmmExpr -> NatM (OrdList Instr)
genCondBranch BlockId
bid BlockId
true BlockId
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 -> OrdList Instr -> NatM (OrdList Instr)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return OrdList Instr
forall a. OrdList a
nilOL
CmmNode e x
_ -> String -> SDoc -> NatM (OrdList Instr)
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"stmtToInstrs: statement should have been cps'd away" (Platform -> CmmNode e x -> SDoc
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 (VirtualReg -> Reg) -> VirtualReg -> Reg
forall a b. (a -> b) -> a -> b
$ Unique -> Format -> VirtualReg
mkVirtualReg Unique
u (CmmType -> Format
cmmTypeFormat CmmType
pk)
getRegisterReg Platform
platform (CmmGlobal reg :: GlobalRegUse
reg@(GlobalRegUse GlobalReg
mid CmmType
_))
= case Platform -> GlobalReg -> Maybe RealReg
globalRegMaybe Platform
platform GlobalReg
mid of
Just RealReg
reg -> RealReg -> Reg
RegReal RealReg
reg
Maybe RealReg
Nothing -> String -> SDoc -> Reg
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegisterReg-memory" (CmmReg -> SDoc
forall a. Outputable a => a -> SDoc
ppr (CmmReg -> SDoc) -> CmmReg -> SDoc
forall a b. (a -> b) -> a -> b
$ GlobalRegUse -> CmmReg
CmmGlobal GlobalRegUse
reg)
getSomeReg :: CmmExpr -> NatM (Reg, Format, InstrBlock)
getSomeReg :: CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
expr = do
r <- CmmExpr -> NatM Register
getRegister CmmExpr
expr
case r of
Any Format
rep Reg -> OrdList Instr
code -> do
tmp <- Format -> NatM Reg
getNewRegNat Format
rep
return (tmp, rep, code tmp)
Fixed Format
rep Reg
reg OrdList Instr
code ->
(Reg, Format, OrdList Instr) -> NatM (Reg, Format, OrdList Instr)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Reg
reg, Format
rep, OrdList Instr
code)
getMovWideImm :: Integer -> Width -> Maybe Operand
getMovWideImm :: Integer -> Width -> Maybe Operand
getMovWideImm Integer
n Width
w
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
0
= Maybe Operand
forall a. Maybe a
Nothing
| Word64
sized_n Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
2Word64 -> Int -> Word64
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
16 :: Int)
= Operand -> Maybe Operand
forall a. a -> Maybe a
Just (Operand -> Maybe Operand) -> Operand -> Maybe Operand
forall a b. (a -> b) -> a -> b
$ Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
truncated)
| Int
trailing_zeros Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
16 Bool -> Bool -> Bool
&& Word64
sized_n Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
2Word64 -> Int -> Word64
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
32 :: Int)
= Operand -> Maybe Operand
forall a. a -> Maybe a
Just (Operand -> Maybe Operand) -> Operand -> Maybe Operand
forall a b. (a -> b) -> a -> b
$ Imm -> ShiftMode -> Int -> Operand
OpImmShift (Integer -> Imm
ImmInteger (Integer -> Imm) -> Integer -> Imm
forall a b. (a -> b) -> a -> b
$ Integer
truncated Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
16) ShiftMode
SLSL Int
16
| Int
trailing_zeros Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
32 Bool -> Bool -> Bool
&& Word64
sized_n Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
2Word64 -> Int -> Word64
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
48 :: Int)
= Operand -> Maybe Operand
forall a. a -> Maybe a
Just (Operand -> Maybe Operand) -> Operand -> Maybe Operand
forall a b. (a -> b) -> a -> b
$ Imm -> ShiftMode -> Int -> Operand
OpImmShift (Integer -> Imm
ImmInteger (Integer -> Imm) -> Integer -> Imm
forall a b. (a -> b) -> a -> b
$ Integer
truncated Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
32) ShiftMode
SLSL Int
32
| Int
trailing_zeros Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
48
= Operand -> Maybe Operand
forall a. a -> Maybe a
Just (Operand -> Maybe Operand) -> Operand -> Maybe Operand
forall a b. (a -> b) -> a -> b
$ Imm -> ShiftMode -> Int -> Operand
OpImmShift (Integer -> Imm
ImmInteger (Integer -> Imm) -> Integer -> Imm
forall a b. (a -> b) -> a -> b
$ Integer
truncated Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
48) ShiftMode
SLSL Int
48
| Bool
otherwise
= Maybe Operand
forall a. Maybe a
Nothing
where
truncated :: Integer
truncated = Width -> Integer -> Integer
narrowU Width
w Integer
n
sized_n :: Word64
sized_n = Integer -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
truncated :: Word64
trailing_zeros :: Int
trailing_zeros = Word64 -> Int
forall b. FiniteBits b => b -> Int
countTrailingZeros Word64
sized_n
getArithImm :: Integer -> Width -> Maybe Operand
getArithImm :: Integer -> Width -> Maybe Operand
getArithImm Integer
n Width
w
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
0
= Maybe Operand
forall a. Maybe a
Nothing
| Word64
sized_n Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
2Word64 -> Int -> Word64
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
12::Int)
= Operand -> Maybe Operand
forall a. a -> Maybe a
Just (Operand -> Maybe Operand) -> Operand -> Maybe Operand
forall a b. (a -> b) -> a -> b
$ Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
truncated)
| Int
trailing_zeros Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
12 Bool -> Bool -> Bool
&& Word64
sized_n Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
2Word64 -> Int -> Word64
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
24::Int)
= Operand -> Maybe Operand
forall a. a -> Maybe a
Just (Operand -> Maybe Operand) -> Operand -> Maybe Operand
forall a b. (a -> b) -> a -> b
$ Imm -> ShiftMode -> Int -> Operand
OpImmShift (Integer -> Imm
ImmInteger (Integer -> Imm) -> Integer -> Imm
forall a b. (a -> b) -> a -> b
$ Integer
truncated Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
12) ShiftMode
SLSL Int
12
| Bool
otherwise
= Maybe Operand
forall a. Maybe a
Nothing
where
sized_n :: Word64
sized_n = Integer -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
truncated :: Word64
truncated :: Integer
truncated = Width -> Integer -> Integer
narrowU Width
w Integer
n
trailing_zeros :: Int
trailing_zeros = Word64 -> Int
forall b. FiniteBits b => b -> Int
countTrailingZeros Word64
sized_n
getBitmaskImm :: Integer -> Width -> Maybe Operand
getBitmaskImm :: Integer -> Width -> Maybe Operand
getBitmaskImm Integer
n Width
w
| Width -> Integer -> Bool
isAArch64Bitmask (Width -> Width
opRegWidth Width
w) Integer
truncated = Operand -> Maybe Operand
forall a. a -> Maybe a
Just (Operand -> Maybe Operand) -> Operand -> Maybe Operand
forall a b. (a -> b) -> a -> b
$ Imm -> Operand
OpImm (Integer -> Imm
ImmInteger Integer
truncated)
| Bool
otherwise = Maybe Operand
forall a. Maybe a
Nothing
where
truncated :: Integer
truncated = Width -> Integer -> Integer
narrowU Width
w Integer
n
isOffsetImm :: Int -> Width -> Bool
isOffsetImm :: Int -> Width -> Bool
isOffsetImm Int
off Width
w
| -Int
256 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
off, Int
off Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
255 = Bool
True
| Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
off, Int
off Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
4096 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
byte_width, Int
off Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
byte_width Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Bool
True
| Bool
otherwise = Bool
False
where
byte_width :: Int
byte_width = Width -> Int
widthInBytes Width
w
getFloatReg :: HasCallStack => CmmExpr -> NatM (Reg, Format, InstrBlock)
getFloatReg :: HasCallStack => CmmExpr -> NatM (Reg, Format, OrdList Instr)
getFloatReg CmmExpr
expr = do
r <- CmmExpr -> NatM Register
getRegister CmmExpr
expr
case r of
Any Format
rep Reg -> OrdList Instr
code | Format -> Bool
isFloatFormat Format
rep -> do
tmp <- Format -> NatM Reg
getNewRegNat Format
rep
return (tmp, rep, code tmp)
Any Format
II32 Reg -> OrdList Instr
code -> do
tmp <- Format -> NatM Reg
getNewRegNat Format
FF32
return (tmp, FF32, code tmp)
Any Format
II64 Reg -> OrdList Instr
code -> do
tmp <- Format -> NatM Reg
getNewRegNat Format
FF64
return (tmp, FF64, code tmp)
Any Format
_w Reg -> OrdList Instr
_code -> do
config <- NatM NCGConfig
getConfig
pprPanic "can't do getFloatReg on" (pdoc (ncgPlatform config) expr)
Fixed Format
rep Reg
reg OrdList Instr
code ->
(Reg, Format, OrdList Instr) -> NatM (Reg, Format, OrdList Instr)
forall a. a -> NatM a
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 = (Operand, OrdList Instr) -> NatM (Operand, OrdList Instr)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Imm -> Operand
OpImm (CmmLit -> Imm
litToImm CmmLit
lit), OrdList Instr
forall a. OrdList a
nilOL)
getRegister :: CmmExpr -> NatM Register
getRegister :: CmmExpr -> NatM Register
getRegister CmmExpr
e = do
config <- NatM NCGConfig
getConfig
getRegister' config (ncgPlatform config) 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 = String -> SDoc -> Width
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"opRegWidth" (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Unsupported width" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Width -> 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 Integer -> Integer -> Bool
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 Integer -> Integer -> Bool
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 (GlobalRegUse GlobalReg
PicBaseReg CmmType
_))
-> String -> SDoc -> NatM Register
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegisterReg-memory" (GlobalReg -> SDoc
forall a. Outputable a => a -> SDoc
ppr (GlobalReg -> SDoc) -> GlobalReg -> SDoc
forall a b. (a -> b) -> a -> b
$ GlobalReg
PicBaseReg)
CmmLit CmmLit
lit
-> case CmmLit
lit of
CmmInt Integer
i Width
W8 | Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
0 -> do
Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
W8) (\Reg
dst -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
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 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
0 -> do
Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
W16) (\Reg
dst -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
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
Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
W8) (\Reg
dst -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
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
Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
W16) (\Reg
dst -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
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 | Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
0
, Just Operand
imm_op <- Integer -> Width -> Maybe Operand
getMovWideImm Integer
i Width
w -> do
Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Instr
MOVZ (Width -> Reg -> Operand
OpReg Width
w Reg
dst) Operand
imm_op)))
CmmInt Integer
i Width
w | Int -> Integer -> Bool
isNbitEncodeable Int
16 Integer
i, Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
0 -> do
Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
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 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
0 -> do
let half0 :: Int
half0 = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i :: Word16)
half1 :: Int
half1 = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
i Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
16) :: Word16)
Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
dst -> [Instr] -> OrdList Instr
forall a. [a] -> OrdList a
toOL [ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr
(Instr -> Instr) -> Instr -> Instr
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 = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i :: Word16)
half1 :: Int
half1 = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
i Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
16) :: Word16)
Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
W32) (\Reg
dst -> [Instr] -> OrdList Instr
forall a. [a] -> OrdList a
toOL [ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr
(Instr -> Instr) -> Instr -> Instr
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 = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i :: Word16)
half1 :: Int
half1 = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
i Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
16) :: Word16)
half2 :: Int
half2 = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
i Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
32) :: Word16)
half3 :: Int
half3 = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
i Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
48) :: Word16)
Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
W64) (\Reg
dst -> [Instr] -> OrdList Instr
forall a. [a] -> OrdList a
toOL [ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr
(Instr -> Instr) -> Instr -> Instr
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
(op, imm_code) <- CmmLit -> NatM (Operand, OrdList Instr)
litToImm' CmmLit
lit
return (Any (intFormat rep) (\Reg
dst -> OrdList Instr
imm_code OrdList Instr -> Instr -> OrdList Instr
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
(op, imm_code) <- CmmLit -> NatM (Operand, OrdList Instr)
litToImm' CmmLit
lit
return (Any (floatFormat w) (\Reg
dst -> OrdList Instr
imm_code OrdList Instr -> Instr -> OrdList Instr
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 -> String -> SDoc -> NatM Register
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (CmmLit:CmmFloat), no support for bytes" (Platform -> CmmExpr -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmFloat Rational
_f Width
W16 -> String -> SDoc -> NatM Register
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (CmmLit:CmmFloat), no support for halfs" (Platform -> CmmExpr -> SDoc
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 (Rational -> Float
forall a. Fractional a => Rational -> a
fromRational Rational
f) :: Word32
half0 :: Int
half0 = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
word :: Word16)
half1 :: Int
half1 = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
word Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftR` Int
16) :: Word16)
tmp <- Format -> NatM Reg
getNewRegNat (Width -> Format
intFormat Width
W32)
return (Any (floatFormat W32) (\Reg
dst -> [Instr] -> OrdList Instr
forall a. [a] -> OrdList a
toOL [ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr
(Instr -> Instr) -> Instr -> Instr
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 (Rational -> Double
forall a. Fractional a => Rational -> a
fromRational Rational
f) :: Word64
half0 :: Int
half0 = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
word :: Word16)
half1 :: Int
half1 = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
word Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
16) :: Word16)
half2 :: Int
half2 = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
word Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
32) :: Word16)
half3 :: Int
half3 = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
word Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
48) :: Word16)
tmp <- Format -> NatM Reg
getNewRegNat (Width -> Format
intFormat Width
W64)
return (Any (floatFormat W64) (\Reg
dst -> [Instr] -> OrdList Instr
forall a. [a] -> OrdList a
toOL [ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr
(Instr -> Instr) -> Instr -> Instr
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 -> String -> SDoc -> NatM Register
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (CmmLit:CmmFloat), unsupported float lit" (Platform -> CmmExpr -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmVec [CmmLit]
_ -> String -> SDoc -> NatM Register
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (CmmLit:CmmVec): " (Platform -> CmmExpr -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmLabel CLabel
_lbl -> do
(op, imm_code) <- CmmLit -> NatM (Operand, OrdList Instr)
litToImm' CmmLit
lit
let rep = Platform -> CmmLit -> CmmType
cmmLitType Platform
plat CmmLit
lit
format = CmmType -> Format
cmmTypeFormat CmmType
rep
return (Any format (\Reg
dst -> OrdList Instr
imm_code OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL` (CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Instr -> Instr) -> Instr -> Instr
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 (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
off) -> do
(op, imm_code) <- CmmLit -> NatM (Operand, OrdList Instr)
litToImm' CmmLit
lit
let rep = Platform -> CmmLit -> CmmType
cmmLitType Platform
plat CmmLit
lit
format = CmmType -> Format
cmmTypeFormat CmmType
rep
return (Any format (\Reg
dst -> OrdList Instr
imm_code OrdList Instr -> Instr -> OrdList Instr
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
(op, imm_code) <- CmmLit -> NatM (Operand, OrdList Instr)
litToImm' (CLabel -> CmmLit
CmmLabel CLabel
lbl)
let rep = Platform -> CmmLit -> CmmType
cmmLitType Platform
plat CmmLit
lit
format = CmmType -> Format
cmmTypeFormat CmmType
rep
width = CmmType -> Width
typeWidth CmmType
rep
(off_r, _off_format, off_code) <- getSomeReg $ CmmLit (CmmInt (fromIntegral off) width)
return (Any format (\Reg
dst -> OrdList Instr
imm_code OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
off_code OrdList Instr -> Instr -> OrdList Instr
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 OrdList Instr -> Instr -> OrdList Instr
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
_ -> String -> SDoc -> NatM Register
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (CmmLit:CmmLabelOff): " (Platform -> CmmExpr -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmBlock BlockId
_ -> String -> SDoc -> NatM Register
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (CmmLit:CmmLabelOff): " (Platform -> CmmExpr -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmLit
CmmHighStackMark -> String -> SDoc -> NatM Register
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (CmmLit:CmmLabelOff): " (Platform -> CmmExpr -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmLoad CmmExpr
mem CmmType
rep AlignmentSpec
_ -> do
Amode addr addr_code <- Platform -> Width -> CmmExpr -> NatM Amode
getAmode Platform
plat (CmmType -> Width
typeWidth CmmType
rep) CmmExpr
mem
let format = CmmType -> Format
cmmTypeFormat CmmType
rep
return (Any format (\Reg
dst -> OrdList Instr
addr_code OrdList Instr -> Instr -> OrdList Instr
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
_
-> String -> SDoc -> NatM Register
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (CmmStackSlot): " (Platform -> CmmExpr -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmReg CmmReg
reg
-> Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Format -> Reg -> OrdList Instr -> Register
Fixed (CmmType -> Format
cmmTypeFormat (CmmReg -> CmmType
cmmRegType CmmReg
reg))
(Platform -> CmmReg -> Reg
getRegisterReg Platform
plat CmmReg
reg)
OrdList Instr
forall a. OrdList a
nilOL)
CmmRegOff CmmReg
reg Int
off ->
let !width :: Width
width = CmmReg -> Width
cmmRegWidth CmmReg
reg
in NCGConfig -> Platform -> CmmExpr -> NatM Register
getRegister' NCGConfig
config Platform
plat (MachOp -> [CmmExpr] -> CmmExpr
CmmMachOp (Width -> MachOp
MO_Add Width
width) [CmmReg -> CmmExpr
CmmReg CmmReg
reg, CmmLit -> CmmExpr
CmmLit (Integer -> Width -> CmmLit
CmmInt (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
off) Width
width)])
CmmMachOp (MO_RelaxedRead Width
w) [CmmExpr
e] ->
CmmExpr -> NatM Register
getRegister (CmmExpr -> CmmType -> AlignmentSpec -> CmmExpr
CmmLoad CmmExpr
e (Width -> CmmType
cmmBits Width
w) AlignmentSpec
NaturallyAligned)
CmmMachOp MachOp
op [CmmExpr
e] -> do
(reg, _format, code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
e
case op of
MO_Not Width
w -> Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Register -> NatM Register) -> Register -> NatM Register
forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) ((Reg -> OrdList Instr) -> Register)
-> (Reg -> OrdList Instr) -> Register
forall a b. (a -> b) -> a -> b
$ \Reg
dst ->
let w' :: Width
w' = Width -> Width
opRegWidth Width
w
in OrdList Instr
code OrdList Instr -> Instr -> OrdList Instr
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) OrdList Instr -> OrdList Instr -> OrdList Instr
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 -> OrdList Instr -> Width -> Reg -> NatM Register
negate OrdList Instr
code Width
w Reg
reg
MO_F_Neg Width
w -> Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Register -> NatM Register) -> Register -> NatM Register
forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
floatFormat Width
w) (\Reg
dst -> OrdList Instr
code OrdList Instr -> Instr -> OrdList Instr
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 -> Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Register -> NatM Register) -> Register -> NatM Register
forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
floatFormat Width
to) (\Reg
dst -> OrdList Instr
code OrdList Instr -> Instr -> OrdList Instr
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 -> Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Register -> NatM Register) -> Register -> NatM Register
forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
to) (\Reg
dst -> OrdList Instr
code OrdList Instr -> Instr -> OrdList Instr
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 -> Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Register -> NatM Register) -> Register -> NatM Register
forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
to) (\Reg
dst -> OrdList Instr
code OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL` Operand -> Operand -> Operand -> Operand -> Instr
UBFM (Width -> Reg -> Operand
OpReg (Width -> Width -> Width
forall a. Ord a => a -> a -> a
max Width
from Width
to) Reg
dst) (Width -> Reg -> Operand
OpReg (Width -> Width -> Width
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 (Width -> Width -> Width
forall a. Ord a => a -> a -> a
min Width
from Width
to)))
MO_SS_Conv Width
from Width
to -> Width -> Width -> Reg -> OrdList Instr -> NatM Register
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 -> Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Register -> NatM Register) -> Register -> NatM Register
forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
floatFormat Width
to) (\Reg
dst -> OrdList Instr
code OrdList Instr -> Instr -> OrdList Instr
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) (Register -> Register) -> NatM Register -> NatM Register
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CmmExpr -> NatM Register
getRegister CmmExpr
e
MachOp
_ -> String -> SDoc -> NatM Register
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (monadic CmmMachOp):" (Platform -> CmmExpr -> SDoc
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 -> NatM Register
negate OrdList Instr
code Width
w Reg
reg = do
let w' :: Width
w' = Width -> Width
opRegWidth Width
w
(reg', code_sx) <- Width -> Width -> Reg -> NatM (Reg, OrdList Instr)
signExtendReg Width
w Width
w' Reg
reg
return $ Any (intFormat w) $ \Reg
dst ->
OrdList Instr
code OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_sx OrdList Instr -> Instr -> OrdList Instr
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') OrdList Instr -> OrdList Instr -> OrdList Instr
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 (Width -> Width -> Width
forall a. Ord a => a -> a -> a
max Width
from Width
to)
in Register -> m Register
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Register -> m Register) -> Register -> m Register
forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
to) ((Reg -> OrdList Instr) -> Register)
-> (Reg -> OrdList Instr) -> Register
forall a b. (a -> b) -> a -> b
$ \Reg
dst ->
OrdList Instr
code OrdList Instr -> Instr -> OrdList Instr
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 (Width -> Width -> Width
forall a. Ord a => a -> a -> a
min Width
from Width
to)) OrdList Instr -> OrdList Instr -> OrdList Instr
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 GlobalRegUse
_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 GlobalRegUse
_r)), CmmLit (CmmInt Integer
0 Width
_)] -> NCGConfig -> Platform -> CmmExpr -> NatM Register
getRegister' NCGConfig
config Platform
plat CmmExpr
expr'
CmmMachOp (MO_U_Quot Width
w) [CmmExpr
x, CmmExpr
y] | Width
w Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W8 -> do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(reg_y, _format_y, code_y) <- getSomeReg y
return $ Any (intFormat w) (\Reg
dst -> OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y OrdList Instr -> Instr -> OrdList Instr
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)) OrdList Instr -> Instr -> OrdList Instr
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)) OrdList Instr -> Instr -> OrdList Instr
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 Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W16 -> do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(reg_y, _format_y, code_y) <- getSomeReg y
return $ Any (intFormat w) (\Reg
dst -> OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y OrdList Instr -> Instr -> OrdList Instr
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)) OrdList Instr -> Instr -> OrdList Instr
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)) OrdList Instr -> Instr -> OrdList Instr
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 Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W32 Bool -> Bool -> Bool
|| Width
w Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W64
, Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Width -> Int
widthInBits Width
w) -> do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
return $ Any (intFormat w) (\Reg
dst -> OrdList Instr
code_x OrdList Instr -> Instr -> OrdList Instr
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 Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W8, Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
8 -> do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
return $ Any (intFormat w) (\Reg
dst -> OrdList Instr
code_x OrdList Instr -> Instr -> OrdList Instr
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
8Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
n)))))
CmmMachOp (MO_S_Shr Width
w) [CmmExpr
x, CmmExpr
y] | Width
w Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W8 -> do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(reg_y, _format_y, code_y) <- getSomeReg y
return $ Any (intFormat w) (\Reg
dst -> OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y OrdList Instr -> Instr -> OrdList Instr
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)) OrdList Instr -> Instr -> OrdList Instr
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 Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W16, Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
16 -> do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
return $ Any (intFormat w) (\Reg
dst -> OrdList Instr
code_x OrdList Instr -> Instr -> OrdList Instr
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
16Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
n)))))
CmmMachOp (MO_S_Shr Width
w) [CmmExpr
x, CmmExpr
y] | Width
w Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W16 -> do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(reg_y, _format_y, code_y) <- getSomeReg y
return $ Any (intFormat w) (\Reg
dst -> OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y OrdList Instr -> Instr -> OrdList Instr
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)) OrdList Instr -> Instr -> OrdList Instr
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 Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W32 Bool -> Bool -> Bool
|| Width
w Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W64
, Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Width -> Int
widthInBits Width
w) -> do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
return $ Any (intFormat w) (\Reg
dst -> OrdList Instr
code_x OrdList Instr -> Instr -> OrdList Instr
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 Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W8, Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
8 -> do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
return $ Any (intFormat w) (\Reg
dst -> OrdList Instr
code_x OrdList Instr -> Instr -> OrdList Instr
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
8Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
n)))))
CmmMachOp (MO_U_Shr Width
w) [CmmExpr
x, CmmExpr
y] | Width
w Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W8 -> do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(reg_y, _format_y, code_y) <- getSomeReg y
return $ Any (intFormat w) (\Reg
dst -> OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y OrdList Instr -> Instr -> OrdList Instr
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)) OrdList Instr -> Instr -> OrdList Instr
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 Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W16, Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
16 -> do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
return $ Any (intFormat w) (\Reg
dst -> OrdList Instr
code_x OrdList Instr -> Instr -> OrdList Instr
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
16Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
n)))))
CmmMachOp (MO_U_Shr Width
w) [CmmExpr
x, CmmExpr
y] | Width
w Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W16 -> do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(reg_y, _format_y, code_y) <- getSomeReg y
return $ Any (intFormat w) (\Reg
dst -> OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y OrdList Instr -> Instr -> OrdList Instr
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))
OrdList Instr -> Instr -> OrdList Instr
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 Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W32 Bool -> Bool -> Bool
|| Width
w Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W64
, Integer
0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
n, Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Width -> Int
widthInBits Width
w) -> do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
return $ Any (intFormat w) (\Reg
dst -> OrdList Instr
code_x OrdList Instr -> Instr -> OrdList Instr
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
_)] | Width -> Integer -> Bool
isAArch64Bitmask (Width -> Width
opRegWidth Width
w') (Integer -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n) ->
Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Register -> NatM Register) -> Register -> NatM Register
forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
d -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
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 (CmmReg -> CmmType
cmmRegType 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
_)] | Width -> Integer -> Bool
isAArch64Bitmask (Width -> Width
opRegWidth Width
w') (Integer -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n) ->
Register -> NatM Register
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Register -> NatM Register) -> Register -> NatM Register
forall a b. (a -> b) -> a -> b
$ Format -> (Reg -> OrdList Instr) -> Register
Any (Width -> Format
intFormat Width
w) (\Reg
d -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
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 (CmmReg -> CmmType
cmmRegType 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 (Reg -> Operand) -> NatM Reg -> NatM Operand
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Format -> NatM Reg
getNewRegNat (Width -> Format
intFormat Width
w) NatM Operand -> (Operand -> NatM b) -> NatM b
forall a b. NatM a -> (a -> NatM b) -> NatM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Operand -> NatM b
op
bitOpImm :: Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> (Integer -> Width -> Maybe Operand)
-> NatM Register
bitOpImm Width
w Operand -> Operand -> Operand -> OrdList Instr
op Integer -> Width -> Maybe Operand
encode_imm = do
(reg_x, format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(op_y, format_y, code_y) <- case y of
CmmLit (CmmInt Integer
n Width
w)
| Just Operand
imm_operand_y <- Integer -> Width -> Maybe Operand
encode_imm Integer
n Width
w
-> (Operand, Format, OrdList Instr)
-> NatM (Operand, Format, OrdList Instr)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Operand
imm_operand_y, Width -> Format
intFormat Width
w, OrdList Instr
forall a. OrdList a
nilOL)
CmmExpr
_ -> do
(reg_y, format_y, code_y) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
y
return (OpReg w reg_y, format_y, code_y)
massertPpr (isIntFormat format_x == isIntFormat format_y) $ text "bitOpImm: incompatible"
return $ Any (intFormat w) (\Reg
dst ->
OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_y OrdList Instr -> OrdList Instr -> OrdList Instr
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) Operand
op_y)
intOpImm :: Bool -> Width -> (Operand -> Operand -> Operand -> OrdList Instr) -> (Integer -> Width -> Maybe Operand) -> NatM (Register)
intOpImm :: Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> (Integer -> Width -> Maybe Operand)
-> NatM Register
intOpImm Bool
True Width
w Operand -> Operand -> Operand -> OrdList Instr
op Integer -> Width -> Maybe Operand
_encode_imm = Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
True Width
w Operand -> Operand -> Operand -> OrdList Instr
op
intOpImm Bool
False Width
w Operand -> Operand -> Operand -> OrdList Instr
op Integer -> Width -> Maybe Operand
encode_imm = do
(reg_x, format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(op_y, format_y, code_y) <- case y of
CmmLit (CmmInt Integer
n Width
w)
| Just Operand
imm_operand_y <- Integer -> Width -> Maybe Operand
encode_imm Integer
n Width
w
-> (Operand, Format, OrdList Instr)
-> NatM (Operand, Format, OrdList Instr)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Operand
imm_operand_y, Width -> Format
intFormat Width
w, OrdList Instr
forall a. OrdList a
nilOL)
CmmExpr
_ -> do
(reg_y, format_y, code_y) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
y
return (OpReg w reg_y, format_y, code_y)
massertPpr (isIntFormat format_x && isIntFormat format_y) $ text "intOp: non-int"
let w' = Width -> Width
opRegWidth Width
w
return $ Any (intFormat w) $ \Reg
dst ->
OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_y OrdList Instr -> OrdList Instr -> OrdList Instr
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) (Operand
op_y) OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
Width -> Width -> Reg -> OrdList Instr
truncateReg Width
w' Width
w Reg
dst
intOp :: Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
is_signed Width
w Operand -> Operand -> Operand -> OrdList Instr
op = do
(reg_x, format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(reg_y, format_y, code_y) <- getSomeReg y
massertPpr (isIntFormat format_x && isIntFormat format_y) $ text "intOp: non-int"
let w' = Width -> Width
opRegWidth Width
w
signExt Reg
r
| Bool -> Bool
not Bool
is_signed = (Reg, OrdList Instr) -> NatM (Reg, OrdList Instr)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Reg
r, OrdList Instr
forall a. OrdList a
nilOL)
| Bool
otherwise = Width -> Width -> Reg -> NatM (Reg, OrdList Instr)
signExtendReg Width
w Width
w' Reg
r
(reg_x_sx, code_x_sx) <- signExt reg_x
(reg_y_sx, code_y_sx) <- signExt reg_y
return $ Any (intFormat w) $ \Reg
dst ->
OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_y OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_x_sx OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_y_sx OrdList Instr -> OrdList Instr -> OrdList Instr
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_sx) (Width -> Reg -> Operand
OpReg Width
w' Reg
reg_y_sx) OrdList Instr -> OrdList Instr -> OrdList Instr
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_fx, format_x, code_fx) <- HasCallStack => CmmExpr -> NatM (Reg, Format, OrdList Instr)
CmmExpr -> NatM (Reg, Format, OrdList Instr)
getFloatReg CmmExpr
x
(reg_fy, format_y, code_fy) <- getFloatReg y
massertPpr (isFloatFormat format_x && isFloatFormat format_y) $ text "floatOp: non-float"
return $ Any (floatFormat w) (\Reg
dst -> OrdList Instr
code_fx OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_fy OrdList Instr -> OrdList Instr -> OrdList Instr
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_fx, format_x, code_fx) <- HasCallStack => CmmExpr -> NatM (Reg, Format, OrdList Instr)
CmmExpr -> NatM (Reg, Format, OrdList Instr)
getFloatReg CmmExpr
x
(reg_fy, format_y, code_fy) <- getFloatReg y
massertPpr (isFloatFormat format_x && isFloatFormat format_y) $ text "floatCond: non-float"
return $ Any (intFormat w) (\Reg
dst -> OrdList Instr
code_fx OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_fy OrdList Instr -> OrdList Instr -> OrdList Instr
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)
-> (Integer -> Width -> Maybe Operand)
-> NatM Register
intOpImm Bool
False Width
w (\Operand
d Operand
x Operand
y -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Instr
ADD Operand
d Operand
x Operand
y)) Integer -> Width -> Maybe Operand
getArithImm
MO_Sub Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> (Integer -> Width -> Maybe Operand)
-> NatM Register
intOpImm Bool
False Width
w (\Operand
d Operand
x Operand
y -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Operand -> Operand -> Operand -> Instr
SUB Operand
d Operand
x Operand
y)) Integer -> Width -> Maybe Operand
getArithImm
MO_Eq Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> (Integer -> Width -> Maybe Operand)
-> NatM Register
bitOpImm Width
w (\Operand
d Operand
x Operand
y -> [Instr] -> OrdList Instr
forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
EQ ]) Integer -> Width -> Maybe Operand
getArithImm
MO_Ne Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> (Integer -> Width -> Maybe Operand)
-> NatM Register
bitOpImm Width
w (\Operand
d Operand
x Operand
y -> [Instr] -> OrdList Instr
forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
NE ]) Integer -> Width -> Maybe Operand
getArithImm
MO_Mul Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
True Width
w (\Operand
d Operand
x Operand
y -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
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 -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
SDIV Operand
d Operand
x Operand
y)
MO_S_Rem Width
w -> Width -> (Operand -> NatM Register) -> NatM Register
forall {b}. Width -> (Operand -> NatM b) -> NatM b
withTempIntReg Width
w ((Operand -> NatM Register) -> NatM Register)
-> (Operand -> NatM Register) -> NatM Register
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 -> [Instr] -> OrdList Instr
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_Quot Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
False Width
w (\Operand
d Operand
x Operand
y -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
UDIV Operand
d Operand
x Operand
y)
MO_U_Rem Width
w -> Width -> (Operand -> NatM Register) -> NatM Register
forall {b}. Width -> (Operand -> NatM b) -> NatM b
withTempIntReg Width
w ((Operand -> NatM Register) -> NatM Register)
-> (Operand -> NatM Register) -> NatM Register
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 -> [Instr] -> OrdList Instr
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 -> [Instr] -> OrdList Instr
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 -> [Instr] -> OrdList Instr
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 -> [Instr] -> OrdList Instr
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 -> [Instr] -> OrdList Instr
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)
-> (Integer -> Width -> Maybe Operand)
-> NatM Register
intOpImm Bool
False Width
w (\Operand
d Operand
x Operand
y -> [Instr] -> OrdList Instr
forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
UGE ]) Integer -> Width -> Maybe Operand
getArithImm
MO_U_Le Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> (Integer -> Width -> Maybe Operand)
-> NatM Register
intOpImm Bool
False Width
w (\Operand
d Operand
x Operand
y -> [Instr] -> OrdList Instr
forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
ULE ]) Integer -> Width -> Maybe Operand
getArithImm
MO_U_Gt Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> (Integer -> Width -> Maybe Operand)
-> NatM Register
intOpImm Bool
False Width
w (\Operand
d Operand
x Operand
y -> [Instr] -> OrdList Instr
forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
UGT ]) Integer -> Width -> Maybe Operand
getArithImm
MO_U_Lt Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> (Integer -> Width -> Maybe Operand)
-> NatM Register
intOpImm Bool
False Width
w (\Operand
d Operand
x Operand
y -> [Instr] -> OrdList Instr
forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Instr
CMP Operand
x Operand
y, Operand -> Cond -> Instr
CSET Operand
d Cond
ULT ]) Integer -> Width -> Maybe Operand
getArithImm
MO_F_Add Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
floatOp Width
w (\Operand
d Operand
x Operand
y -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
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 -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
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 -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
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 -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
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 -> [Instr] -> OrdList Instr
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 -> [Instr] -> OrdList Instr
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 -> [Instr] -> OrdList Instr
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 -> [Instr] -> OrdList Instr
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 -> [Instr] -> OrdList Instr
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 -> [Instr] -> OrdList Instr
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)
-> (Integer -> Width -> Maybe Operand)
-> NatM Register
bitOpImm Width
w (\Operand
d Operand
x Operand
y -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
AND Operand
d Operand
x Operand
y) Integer -> Width -> Maybe Operand
getBitmaskImm
MO_Or Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> (Integer -> Width -> Maybe Operand)
-> NatM Register
bitOpImm Width
w (\Operand
d Operand
x Operand
y -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
ORR Operand
d Operand
x Operand
y) Integer -> Width -> Maybe Operand
getBitmaskImm
MO_Xor Width
w -> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> (Integer -> Width -> Maybe Operand)
-> NatM Register
bitOpImm Width
w (\Operand
d Operand
x Operand
y -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
EOR Operand
d Operand
x Operand
y) Integer -> Width -> Maybe Operand
getBitmaskImm
MO_Shl Width
w -> Bool
-> Width
-> (Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
intOp Bool
False Width
w (\Operand
d Operand
x Operand
y -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
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 -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
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 -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Operand -> Instr
ASR Operand
d Operand
x Operand
y)
MachOp
op -> String -> SDoc -> NatM Register
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (unhandled dyadic CmmMachOp): " (SDoc -> NatM Register) -> SDoc -> NatM Register
forall a b. (a -> b) -> a -> b
$
(MachOp -> SDoc
pprMachOp MachOp
op) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"in" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Platform -> CmmExpr -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
CmmMachOp MachOp
op [CmmExpr
x, CmmExpr
y, CmmExpr
z] ->
case MachOp
op of
MO_FMA FMASign
var Width
w -> case FMASign
var of
FMASign
FMAdd -> Width
-> (Operand -> Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
float3Op Width
w (\Operand
d Operand
n Operand
m Operand
a -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ FMASign -> Operand -> Operand -> Operand -> Operand -> Instr
FMA FMASign
FMAdd Operand
d Operand
n Operand
m Operand
a)
FMASign
FMSub -> Width
-> (Operand -> Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
float3Op Width
w (\Operand
d Operand
n Operand
m Operand
a -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ FMASign -> Operand -> Operand -> Operand -> Operand -> Instr
FMA FMASign
FNMSub Operand
d Operand
n Operand
m Operand
a)
FMASign
FNMAdd -> Width
-> (Operand -> Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
float3Op Width
w (\Operand
d Operand
n Operand
m Operand
a -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ FMASign -> Operand -> Operand -> Operand -> Operand -> Instr
FMA FMASign
FMSub Operand
d Operand
n Operand
m Operand
a)
FMASign
FNMSub -> Width
-> (Operand -> Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
float3Op Width
w (\Operand
d Operand
n Operand
m Operand
a -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ FMASign -> Operand -> Operand -> Operand -> Operand -> Instr
FMA FMASign
FNMAdd Operand
d Operand
n Operand
m Operand
a)
MachOp
_ -> String -> SDoc -> NatM Register
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (unhandled ternary CmmMachOp): " (SDoc -> NatM Register) -> SDoc -> NatM Register
forall a b. (a -> b) -> a -> b
$
(MachOp -> SDoc
pprMachOp MachOp
op) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"in" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Platform -> CmmExpr -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
where
float3Op :: Width
-> (Operand -> Operand -> Operand -> Operand -> OrdList Instr)
-> NatM Register
float3Op Width
w Operand -> Operand -> Operand -> Operand -> OrdList Instr
op = do
(reg_fx, format_x, code_fx) <- HasCallStack => CmmExpr -> NatM (Reg, Format, OrdList Instr)
CmmExpr -> NatM (Reg, Format, OrdList Instr)
getFloatReg CmmExpr
x
(reg_fy, format_y, code_fy) <- getFloatReg y
(reg_fz, format_z, code_fz) <- getFloatReg z
massertPpr (isFloatFormat format_x && isFloatFormat format_y && isFloatFormat format_z) $
text "float3Op: non-float"
return $
Any (floatFormat w) $ \ Reg
dst ->
OrdList Instr
code_fx OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_fy OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_fz OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
Operand -> 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) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_fz)
CmmMachOp MachOp
_op [CmmExpr]
_xs
-> String -> SDoc -> NatM Register
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getRegister' (variadic CmmMachOp): " (Platform -> CmmExpr -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc Platform
plat CmmExpr
expr)
where
isNbitEncodeable :: Int -> Integer -> Bool
isNbitEncodeable :: Int -> Integer -> Bool
isNbitEncodeable Int
n_bits Integer
i = let shift :: Int
shift = Int
n_bits Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1 in (-Integer
1 Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftL` Int
shift) Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
i Bool -> Bool -> Bool
&& Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< (Integer
1 Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftL` Int
shift)
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_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(reg_y, _format_y, code_y) <- getSomeReg y
lo <- getNewRegNat II64
hi <- getNewRegNat II64
return $ Any (intFormat w) (\Reg
dst ->
OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_y OrdList Instr -> Instr -> OrdList Instr
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) OrdList Instr -> Instr -> OrdList Instr
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) OrdList Instr -> Instr -> OrdList Instr
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) OrdList Instr -> Instr -> OrdList Instr
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
W32 CmmExpr
x CmmExpr
y = do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(reg_y, _format_y, code_y) <- getSomeReg y
tmp1 <- getNewRegNat II64
tmp2 <- getNewRegNat II64
return $ Any (intFormat W32) (\Reg
dst ->
OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_y OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Operand -> Operand -> Instr
SMULL (Width -> Reg -> Operand
OpReg Width
W64 Reg
tmp1) (Width -> Reg -> Operand
OpReg Width
W32 Reg
reg_x) (Width -> Reg -> Operand
OpReg Width
W32 Reg
reg_y) OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Operand -> Operand -> Instr
ASR (Width -> Reg -> Operand
OpReg Width
W64 Reg
tmp2) (Width -> Reg -> Operand
OpReg Width
W64 Reg
tmp1) (Imm -> Operand
OpImm (Int -> Imm
ImmInt Int
31)) OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Operand -> Instr
CMP (Width -> Reg -> Operand
OpReg Width
W32 Reg
tmp2) (Width -> Reg -> ShiftMode -> Int -> Operand
OpRegShift Width
W32 Reg
tmp1 ShiftMode
SASR Int
31) OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Cond -> Instr
CSET (Width -> Reg -> Operand
OpReg Width
W32 Reg
dst) Cond
NE)
do_mul_may_oflo Width
w CmmExpr
x CmmExpr
y = do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(reg_y, _format_y, code_y) <- getSomeReg y
tmp1 <- getNewRegNat II32
tmp2 <- getNewRegNat II32
let extend Reg
dst Reg
arg =
case Width
w of
Width
W16 -> Operand -> Operand -> Instr
SXTH (Width -> Reg -> Operand
OpReg Width
W32 Reg
dst) (Width -> Reg -> Operand
OpReg Width
W32 Reg
arg)
Width
W8 -> Operand -> Operand -> Instr
SXTB (Width -> Reg -> Operand
OpReg Width
W32 Reg
dst) (Width -> Reg -> Operand
OpReg Width
W32 Reg
arg)
Width
_ -> String -> Instr
forall a. HasCallStack => String -> a
panic String
"unreachable"
cmp_ext_mode =
case Width
w of
Width
W16 -> ExtMode
EUXTH
Width
W8 -> ExtMode
EUXTB
Width
_ -> String -> ExtMode
forall a. HasCallStack => String -> a
panic String
"unreachable"
width = Width -> Int
widthInBits Width
w
opInt = Imm -> Operand
OpImm (Imm -> Operand) -> (Int -> Imm) -> Int -> Operand
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Imm
ImmInt
return $ Any (intFormat w) (\Reg
dst ->
OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_y OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
Reg -> Reg -> Instr
extend Reg
tmp1 Reg
reg_x OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
Reg -> Reg -> Instr
extend Reg
tmp2 Reg
reg_y OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Operand -> Operand -> Instr
MUL (Width -> Reg -> Operand
OpReg Width
W32 Reg
tmp1) (Width -> Reg -> Operand
OpReg Width
W32 Reg
tmp1) (Width -> Reg -> Operand
OpReg Width
W32 Reg
tmp2) OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Operand -> Operand -> Operand -> Instr
SBFX (Width -> Reg -> Operand
OpReg Width
W64 Reg
tmp2) (Width -> Reg -> Operand
OpReg Width
W64 Reg
tmp1) (Int -> Operand
opInt (Int -> Operand) -> Int -> Operand
forall a b. (a -> b) -> a -> b
$ Int
width Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (Int -> Operand
opInt Int
1) OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Operand -> Operand -> Operand -> Instr
UBFX (Width -> Reg -> Operand
OpReg Width
W32 Reg
tmp1) (Width -> Reg -> Operand
OpReg Width
W32 Reg
tmp1) (Int -> Operand
opInt Int
width) (Int -> Operand
opInt Int
width) OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Operand -> Instr
CMP (Width -> Reg -> Operand
OpReg Width
W32 Reg
tmp1) (Width -> Reg -> ExtMode -> Int -> Operand
OpRegExt Width
W32 Reg
tmp2 ExtMode
cmp_ext_mode Int
0) OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
Operand -> Cond -> Instr
CSET (Width -> Reg -> Operand
OpReg Width
w Reg
dst) Cond
NE)
isAArch64Bitmask :: Width -> Integer -> Bool
isAArch64Bitmask :: Width -> Integer -> Bool
isAArch64Bitmask Width
width Integer
n =
Bool -> Bool -> Bool
forall a. HasCallStack => Bool -> a -> a
assert (Width
width Width -> [Width] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Width
W32,Width
W64]) (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$
case Integer
n of
Integer
0 -> Bool
False
Integer
_ | Integer
n Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Integer
forall a. Bits a => Int -> a
bit (Width -> Int
widthInBits Width
width) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1
-> Bool
False
| Bool
otherwise
-> (Width
width Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W64 Bool -> Bool -> Bool
&& Int -> Bool
check Int
64) Bool -> Bool -> Bool
|| Int -> Bool
check Int
32 Bool -> Bool -> Bool
|| Int -> Bool
check Int
16 Bool -> Bool -> Bool
|| Int -> Bool
check Int
8
where
check :: Int -> Bool
check Int
width
| Word64 -> Bool
hasOneRun Word64
subpat =
let n' :: Integer
n' = Word64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64 -> Word64
mkPat Int
width Word64
subpat)
in Integer
n Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
n'
| Bool
otherwise = Bool
False
where
subpat :: Word64
subpat :: Word64
subpat = Integer -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
n Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
.&. (Int -> Integer
forall a. Bits a => Int -> a
bit Int
width Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1))
mkPat :: Int -> Word64 -> Word64
mkPat :: Int -> Word64 -> Word64
mkPat Int
width Word64
subpat =
(Word64 -> Word64 -> Word64) -> Word64 -> [Word64] -> Word64
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
(.|.) Word64
0 [ Word64
subpat Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` Int
p | Int
p <- [Int
0, Int
width..Int
63] ]
hasOneRun :: Word64 -> Bool
hasOneRun :: Word64 -> Bool
hasOneRun Word64
m =
Int
64 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Word64 -> Int
forall a. Bits a => a -> Int
popCount Word64
m Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Word64 -> Int
forall b. FiniteBits b => b -> Int
countLeadingZeros Word64
m Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Word64 -> Int
forall b. FiniteBits b => b -> Int
countTrailingZeros Word64
m
signExtendReg :: Width -> Width -> Reg -> NatM (Reg, OrdList Instr)
signExtendReg :: Width -> Width -> Reg -> NatM (Reg, OrdList Instr)
signExtendReg Width
w Width
w' Reg
r =
case Width
w of
Width
W64 -> NatM (Reg, OrdList Instr)
noop
Width
W32
| Width
w' Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W32 -> NatM (Reg, OrdList Instr)
noop
| Bool
otherwise -> (Operand -> Operand -> Instr) -> NatM (Reg, OrdList Instr)
extend Operand -> Operand -> Instr
SXTH
Width
W16 -> (Operand -> Operand -> Instr) -> NatM (Reg, OrdList Instr)
extend Operand -> Operand -> Instr
SXTH
Width
W8 -> (Operand -> Operand -> Instr) -> NatM (Reg, OrdList Instr)
extend Operand -> Operand -> Instr
SXTB
Width
_ -> String -> NatM (Reg, OrdList Instr)
forall a. HasCallStack => String -> a
panic String
"intOp"
where
noop :: NatM (Reg, OrdList Instr)
noop = (Reg, OrdList Instr) -> NatM (Reg, OrdList Instr)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Reg
r, OrdList Instr
forall a. OrdList a
nilOL)
extend :: (Operand -> Operand -> Instr) -> NatM (Reg, OrdList Instr)
extend Operand -> Operand -> Instr
instr = do
r' <- Format -> NatM Reg
getNewRegNat Format
II64
return (r', unitOL $ instr (OpReg w' r') (OpReg w' r))
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 -> OrdList Instr
forall a. OrdList a
nilOL
Width
W32
| Width
w' Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
W32 -> OrdList Instr
forall a. OrdList a
nilOL
Width
_ -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
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 (Imm -> Operand) -> Imm -> Operand
forall a b. (a -> b) -> a -> b
$ Int -> Imm
ImmInt (Int -> Imm) -> Int -> Imm
forall a b. (a -> b) -> a -> b
$ Width -> Int
widthInBits Width
w' Int -> Int -> Int
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
w (CmmRegOff CmmReg
reg Int
off)
| Int -> Width -> Bool
isOffsetImm Int
off Width
w
= Amode -> NatM Amode
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Amode -> NatM Amode) -> Amode -> NatM Amode
forall a b. (a -> b) -> a -> b
$ AddrMode -> OrdList Instr -> Amode
Amode (Reg -> Imm -> AddrMode
AddrRegImm Reg
reg' Imm
off') OrdList Instr
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
w (CmmMachOp (MO_Add Width
_w) [CmmExpr
expr, CmmLit (CmmInt Integer
off Width
_w')])
| Int -> Width -> Bool
isOffsetImm (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
off) Width
w
= do (reg, _format, code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
expr
return $ Amode (AddrRegImm reg (ImmInteger off)) code
getAmode Platform
_platform Width
w (CmmMachOp (MO_Sub Width
_w) [CmmExpr
expr, CmmLit (CmmInt Integer
off Width
_w')])
| Int -> Width -> Bool
isOffsetImm (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> Integer -> Int
forall a b. (a -> b) -> a -> b
$ -Integer
off) Width
w
= do (reg, _format, code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
expr
return $ Amode (AddrRegImm reg (ImmInteger $ -off)) code
getAmode Platform
_platform Width
_ CmmExpr
expr
= do (reg, _format, code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
expr
return $ Amode (AddrReg reg) 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
(src_reg, _format, code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
srcE
platform <- getPlatform
let w = Format -> Width
formatToWidth Format
rep
Amode addr addr_code <- getAmode platform w addrE
return $ COMMENT (text "CmmStore" <+> parens (text (show addrE)) <+> parens (text (show srcE)))
`consOL` (code
`appOL` addr_code
`snocOL` STR rep (OpReg w src_reg) (OpAddr addr))
assignReg_IntCode :: Format -> CmmReg -> CmmExpr -> NatM (OrdList Instr)
assignReg_IntCode Format
_ CmmReg
reg CmmExpr
src
= do
platform <- NatM Platform
getPlatform
let dst = Platform -> CmmReg -> Reg
getRegisterReg Platform
platform CmmReg
reg
r <- getRegister src
return $ case r of
Any Format
_ Reg -> OrdList Instr
code -> SDoc -> Instr
COMMENT (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"CmmAssign" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (String -> SDoc
forall doc. IsLine doc => String -> doc
text (CmmReg -> String
forall a. Show a => a -> String
show CmmReg
reg)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (String -> SDoc
forall doc. IsLine doc => String -> doc
text (CmmExpr -> String
forall a. Show a => a -> String
show CmmExpr
src))) Instr -> OrdList Instr -> OrdList Instr
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
forall doc. IsLine doc => String -> doc
text String
"CmmAssign" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (String -> SDoc
forall doc. IsLine doc => String -> doc
text (CmmReg -> String
forall a. Show a => a -> String
show CmmReg
reg)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (String -> SDoc
forall doc. IsLine doc => String -> doc
text (CmmExpr -> String
forall a. Show a => a -> String
show CmmExpr
src))) Instr -> OrdList Instr -> OrdList Instr
forall a. a -> OrdList a -> OrdList a
`consOL` (OrdList Instr
fcode OrdList Instr -> Instr -> OrdList Instr
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))
= OrdList Instr -> NatM (OrdList Instr)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OrdList Instr -> NatM (OrdList Instr))
-> OrdList Instr -> NatM (OrdList Instr)
forall a b. (a -> b) -> a -> b
$ Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (CmmExpr -> Instr -> Instr
annExpr CmmExpr
expr (Target -> Instr
J (CLabel -> Target
TLabel CLabel
lbl)))
genJump CmmExpr
expr = do
(target, _format, code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
expr
return (code `appOL` unitOL (annExpr expr (J (TReg target))))
genBranch :: BlockId -> NatM InstrBlock
genBranch :: BlockId -> NatM (OrdList Instr)
genBranch = OrdList Instr -> NatM (OrdList Instr)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OrdList Instr -> NatM (OrdList Instr))
-> (BlockId -> OrdList Instr) -> BlockId -> NatM (OrdList Instr)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Instr] -> OrdList Instr
forall a. [a] -> OrdList a
toOL ([Instr] -> OrdList Instr)
-> (BlockId -> [Instr]) -> BlockId -> OrdList Instr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockId -> [Instr]
mkJumpInstr
genCondJump
:: BlockId
-> CmmExpr
-> NatM InstrBlock
genCondJump :: BlockId -> CmmExpr -> NatM (OrdList Instr)
genCondJump BlockId
bid CmmExpr
expr = do
case CmmExpr
expr of
CmmMachOp (MO_Eq Width
w) [CmmExpr
x, CmmLit (CmmInt Integer
0 Width
_)] -> do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
return $ code_x `snocOL` (annExpr expr (CBZ (OpReg w reg_x) (TBlock bid)))
CmmMachOp (MO_Ne Width
w) [CmmExpr
x, CmmLit (CmmInt Integer
0 Width
_)] -> do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
return $ code_x `snocOL` (annExpr expr (CBNZ (OpReg w reg_x) (TBlock bid)))
CmmMachOp MachOp
mop [CmmExpr
x, CmmExpr
y] -> do
let ubcond :: Width -> Cond -> NatM (OrdList Instr)
ubcond Width
w Cond
cmp = do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(reg_y, _format_y, code_y) <- getSomeReg y
let x' = Width -> Reg -> Operand
OpReg Width
w Reg
reg_x
y' = Width -> Reg -> Operand
OpReg Width
w Reg
reg_y
return $ case w of
Width
W8 -> OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` [Instr] -> OrdList Instr
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 (BlockId -> Target
TBlock BlockId
bid))) ]
Width
W16 -> OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` [Instr] -> OrdList Instr
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 (BlockId -> Target
TBlock BlockId
bid))) ]
Width
_ -> OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` [Instr] -> OrdList Instr
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 (BlockId -> Target
TBlock BlockId
bid))) ]
sbcond :: Width -> Cond -> NatM (OrdList Instr)
sbcond Width
w Cond
cmp = do
(reg_x, _format_x, code_x) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
x
(reg_y, _format_y, code_y) <- getSomeReg y
let x' = Width -> Reg -> Operand
OpReg Width
w Reg
reg_x
y' = Width -> Reg -> Operand
OpReg Width
w Reg
reg_y
return $ case w of
Width
W8 -> OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` [Instr] -> OrdList Instr
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 (BlockId -> Target
TBlock BlockId
bid))) ]
Width
W16 -> OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` [Instr] -> OrdList Instr
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 (BlockId -> Target
TBlock BlockId
bid))) ]
Width
_ -> OrdList Instr
code_x OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
code_y OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` [Instr] -> OrdList Instr
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 (BlockId -> Target
TBlock BlockId
bid))) ]
fbcond :: Width -> Cond -> NatM (OrdList Instr)
fbcond Width
w Cond
cmp = do
(reg_fx, _format_fx, code_fx) <- HasCallStack => CmmExpr -> NatM (Reg, Format, OrdList Instr)
CmmExpr -> NatM (Reg, Format, OrdList Instr)
getFloatReg CmmExpr
x
(reg_fy, _format_fy, code_fy) <- getFloatReg y
return $ code_fx `appOL` code_fy `snocOL` CMP (OpReg w reg_fx) (OpReg w reg_fy) `snocOL` (annExpr expr (BCOND cmp (TBlock 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
_ -> String -> SDoc -> NatM (OrdList Instr)
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"AArch64.genCondJump:case mop: " (String -> SDoc
forall doc. IsLine doc => String -> doc
text (String -> SDoc) -> String -> SDoc
forall a b. (a -> b) -> a -> b
$ CmmExpr -> String
forall a. Show a => a -> String
show CmmExpr
expr)
CmmExpr
_ -> String -> SDoc -> NatM (OrdList Instr)
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"AArch64.genCondJump: " (String -> SDoc
forall doc. IsLine doc => String -> doc
text (String -> SDoc) -> String -> SDoc
forall a b. (a -> b) -> a -> b
$ CmmExpr -> String
forall a. Show a => a -> String
show CmmExpr
expr)
genCondFarJump :: MonadUnique m => Cond -> Target -> m InstrBlock
genCondFarJump :: forall (m :: * -> *).
MonadUnique m =>
Cond -> Target -> m (OrdList Instr)
genCondFarJump Cond
cond Target
far_target = do
skip_lbl_id <- m BlockId
forall (m :: * -> *). MonadUnique m => m BlockId
newBlockId
jmp_lbl_id <- newBlockId
return $ toOL [ BCOND cond (TBlock jmp_lbl_id)
, B (TBlock skip_lbl_id)
, NEWBLOCK jmp_lbl_id
, B far_target
, NEWBLOCK skip_lbl_id]
genCondBranch
:: BlockId
-> BlockId
-> BlockId
-> CmmExpr
-> NatM InstrBlock
genCondBranch :: BlockId -> BlockId -> BlockId -> CmmExpr -> NatM (OrdList Instr)
genCondBranch BlockId
_ BlockId
true BlockId
false CmmExpr
expr = do
b1 <- BlockId -> CmmExpr -> NatM (OrdList Instr)
genCondJump BlockId
true CmmExpr
expr
b2 <- genBranch false
return (b1 `appOL` b2)
genCCall
:: ForeignTarget
-> [CmmFormal]
-> [CmmActual]
-> BlockId
-> NatM (InstrBlock, Maybe BlockId)
genCCall :: ForeignTarget
-> [CmmFormal]
-> [CmmExpr]
-> BlockId
-> NatM (OrdList Instr, Maybe BlockId)
genCCall ForeignTarget
target [CmmFormal]
dest_regs [CmmExpr]
arg_regs BlockId
bid = do
case ForeignTarget
target of
ForeignTarget CmmExpr
expr ForeignConvention
_cconv -> do
(call_target, call_target_code) <- case CmmExpr
expr of
(CmmLit (CmmLabel CLabel
lbl)) -> (Target, OrdList Instr) -> NatM (Target, OrdList Instr)
forall a. a -> NatM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CLabel -> Target
TLabel CLabel
lbl, OrdList Instr
forall a. OrdList a
nilOL)
CmmExpr
_ -> do (reg, _format, reg_code) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
expr
pure (TReg reg, reg_code)
arg_regs' <- mapM getSomeReg arg_regs
let (_res_hints, arg_hints) = foreignTargetHints target
arg_regs'' = ((Reg, Format, OrdList Instr)
-> ForeignHint -> (Reg, Format, ForeignHint, OrdList Instr))
-> [(Reg, Format, OrdList Instr)]
-> [ForeignHint]
-> [(Reg, Format, ForeignHint, OrdList Instr)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\(Reg
r, Format
f, OrdList Instr
c) ForeignHint
h -> (Reg
r,Format
f,ForeignHint
h,OrdList Instr
c)) [(Reg, Format, OrdList Instr)]
arg_regs' [ForeignHint]
arg_hints
platform <- getPlatform
let packStack = Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSDarwin
(stackSpace', passRegs, passArgumentsCode) <- passArguments packStack allGpArgRegs allFpArgRegs arg_regs'' 0 [] nilOL
let stackSpace = if Int
stackSpace' Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
8 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0
then Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
stackSpace' Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
else Int
stackSpace'
(returnRegs, readResultsCode) <- readResults allGpArgRegs allFpArgRegs dest_regs [] nilOL
let moveStackDown Int
0 = [Instr] -> OrdList Instr
forall a. [a] -> OrdList a
toOL [ Instr
PUSH_STACK_FRAME
, Int -> Instr
DELTA (-Int
16) ]
moveStackDown Int
i | Int -> Bool
forall a. Integral a => a -> Bool
odd Int
i = Int -> OrdList Instr
moveStackDown (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
moveStackDown Int
i = [Instr] -> OrdList Instr
forall a. [a] -> OrdList a
toOL [ Instr
PUSH_STACK_FRAME
, Operand -> Operand -> Operand -> Instr
SUB (Width -> Reg -> Operand
OpReg Width
W64 (Int -> Reg
regSingle Int
31)) (Width -> Reg -> Operand
OpReg Width
W64 (Int -> Reg
regSingle Int
31)) (Imm -> Operand
OpImm (Int -> Imm
ImmInt (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
i)))
, Int -> Instr
DELTA (-Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
16) ]
moveStackUp Int
0 = [Instr] -> OrdList Instr
forall a. [a] -> OrdList a
toOL [ Instr
POP_STACK_FRAME
, Int -> Instr
DELTA Int
0 ]
moveStackUp Int
i | Int -> Bool
forall a. Integral a => a -> Bool
odd Int
i = Int -> OrdList Instr
moveStackUp (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
moveStackUp Int
i = [Instr] -> OrdList Instr
forall a. [a] -> OrdList a
toOL [ Operand -> Operand -> Operand -> Instr
ADD (Width -> Reg -> Operand
OpReg Width
W64 (Int -> Reg
regSingle Int
31)) (Width -> Reg -> Operand
OpReg Width
W64 (Int -> Reg
regSingle Int
31)) (Imm -> Operand
OpImm (Int -> Imm
ImmInt (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
i)))
, Instr
POP_STACK_FRAME
, Int -> Instr
DELTA Int
0 ]
let code = OrdList Instr
call_target_code
OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` Int -> OrdList Instr
moveStackDown (Int
stackSpace Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
8)
OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
passArgumentsCode
OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` (Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ Target -> [Reg] -> [Reg] -> Instr
BL Target
call_target [Reg]
passRegs [Reg]
returnRegs)
OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
readResultsCode
OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` Int -> OrdList Instr
moveStackUp (Int
stackSpace Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
8)
return (code, Nothing)
PrimTarget CallishMachOp
MO_F32_Fabs
| [CmmExpr
arg_reg] <- [CmmExpr]
arg_regs, [CmmFormal
dest_reg] <- [CmmFormal]
dest_regs ->
Width
-> (Operand -> Operand -> OrdList Instr)
-> CmmExpr
-> CmmFormal
-> NatM (OrdList Instr, Maybe BlockId)
forall {a}.
Width
-> (Operand -> Operand -> OrdList Instr)
-> CmmExpr
-> CmmFormal
-> NatM (OrdList Instr, Maybe a)
unaryFloatOp Width
W32 (\Operand
d Operand
x -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Instr
FABS Operand
d Operand
x) CmmExpr
arg_reg CmmFormal
dest_reg
PrimTarget CallishMachOp
MO_F64_Fabs
| [CmmExpr
arg_reg] <- [CmmExpr]
arg_regs, [CmmFormal
dest_reg] <- [CmmFormal]
dest_regs ->
Width
-> (Operand -> Operand -> OrdList Instr)
-> CmmExpr
-> CmmFormal
-> NatM (OrdList Instr, Maybe BlockId)
forall {a}.
Width
-> (Operand -> Operand -> OrdList Instr)
-> CmmExpr
-> CmmFormal
-> NatM (OrdList Instr, Maybe a)
unaryFloatOp Width
W64 (\Operand
d Operand
x -> Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL (Instr -> OrdList Instr) -> Instr -> OrdList Instr
forall a b. (a -> b) -> a -> b
$ Operand -> Operand -> Instr
FABS Operand
d Operand
x) CmmExpr
arg_reg CmmFormal
dest_reg
PrimTarget CallishMachOp
mop -> do
case CallishMachOp
mop of
CallishMachOp
MO_F64_Pwr -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"pow"
CallishMachOp
MO_F64_Sin -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"sin"
CallishMachOp
MO_F64_Cos -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"cos"
CallishMachOp
MO_F64_Tan -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"tan"
CallishMachOp
MO_F64_Sinh -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"sinh"
CallishMachOp
MO_F64_Cosh -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"cosh"
CallishMachOp
MO_F64_Tanh -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"tanh"
CallishMachOp
MO_F64_Asin -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"asin"
CallishMachOp
MO_F64_Acos -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"acos"
CallishMachOp
MO_F64_Atan -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"atan"
CallishMachOp
MO_F64_Asinh -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"asinh"
CallishMachOp
MO_F64_Acosh -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"acosh"
CallishMachOp
MO_F64_Atanh -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"atanh"
CallishMachOp
MO_F64_Log -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"log"
CallishMachOp
MO_F64_Log1P -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"log1p"
CallishMachOp
MO_F64_Exp -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"exp"
CallishMachOp
MO_F64_ExpM1 -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"expm1"
CallishMachOp
MO_F64_Fabs -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"fabs"
CallishMachOp
MO_F64_Sqrt -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"sqrt"
CallishMachOp
MO_F32_Pwr -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"powf"
CallishMachOp
MO_F32_Sin -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"sinf"
CallishMachOp
MO_F32_Cos -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"cosf"
CallishMachOp
MO_F32_Tan -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"tanf"
CallishMachOp
MO_F32_Sinh -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"sinhf"
CallishMachOp
MO_F32_Cosh -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"coshf"
CallishMachOp
MO_F32_Tanh -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"tanhf"
CallishMachOp
MO_F32_Asin -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"asinf"
CallishMachOp
MO_F32_Acos -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"acosf"
CallishMachOp
MO_F32_Atan -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"atanf"
CallishMachOp
MO_F32_Asinh -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"asinhf"
CallishMachOp
MO_F32_Acosh -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"acoshf"
CallishMachOp
MO_F32_Atanh -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"atanhf"
CallishMachOp
MO_F32_Log -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"logf"
CallishMachOp
MO_F32_Log1P -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"log1pf"
CallishMachOp
MO_F32_Exp -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"expf"
CallishMachOp
MO_F32_ExpM1 -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"expm1f"
CallishMachOp
MO_F32_Fabs -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"fabsf"
CallishMachOp
MO_F32_Sqrt -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"sqrtf"
CallishMachOp
MO_I64_ToI -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_int64ToInt"
CallishMachOp
MO_I64_FromI -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_intToInt64"
CallishMachOp
MO_W64_ToW -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_word64ToWord"
CallishMachOp
MO_W64_FromW -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_wordToWord64"
CallishMachOp
MO_x64_Neg -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_neg64"
CallishMachOp
MO_x64_Add -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_add64"
CallishMachOp
MO_x64_Sub -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_sub64"
CallishMachOp
MO_x64_Mul -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_mul64"
CallishMachOp
MO_I64_Quot -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_quotInt64"
CallishMachOp
MO_I64_Rem -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_remInt64"
CallishMachOp
MO_W64_Quot -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_quotWord64"
CallishMachOp
MO_W64_Rem -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_remWord64"
CallishMachOp
MO_x64_And -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_and64"
CallishMachOp
MO_x64_Or -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_or64"
CallishMachOp
MO_x64_Xor -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_xor64"
CallishMachOp
MO_x64_Not -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_not64"
CallishMachOp
MO_x64_Shl -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_uncheckedShiftL64"
CallishMachOp
MO_I64_Shr -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_uncheckedIShiftRA64"
CallishMachOp
MO_W64_Shr -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_uncheckedShiftRL64"
CallishMachOp
MO_x64_Eq -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_eq64"
CallishMachOp
MO_x64_Ne -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_ne64"
CallishMachOp
MO_I64_Ge -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_geInt64"
CallishMachOp
MO_I64_Gt -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_gtInt64"
CallishMachOp
MO_I64_Le -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_leInt64"
CallishMachOp
MO_I64_Lt -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_ltInt64"
CallishMachOp
MO_W64_Ge -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_geWord64"
CallishMachOp
MO_W64_Gt -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_gtWord64"
CallishMachOp
MO_W64_Le -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_leWord64"
CallishMachOp
MO_W64_Lt -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"hs_ltWord64"
MO_UF_Conv Width
w -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall (Width -> FastString
word2FloatLabel Width
w)
MO_S_Mul2 Width
_w -> CallishMachOp -> NatM (OrdList Instr, Maybe BlockId)
forall a b. Show a => a -> b
unsupported CallishMachOp
mop
MO_S_QuotRem Width
_w -> CallishMachOp -> NatM (OrdList Instr, Maybe BlockId)
forall a b. Show a => a -> b
unsupported CallishMachOp
mop
MO_U_QuotRem Width
_w -> CallishMachOp -> NatM (OrdList Instr, Maybe BlockId)
forall a b. Show a => a -> b
unsupported CallishMachOp
mop
MO_U_QuotRem2 Width
_w -> CallishMachOp -> NatM (OrdList Instr, Maybe BlockId)
forall a b. Show a => a -> b
unsupported CallishMachOp
mop
MO_Add2 Width
_w -> CallishMachOp -> NatM (OrdList Instr, Maybe BlockId)
forall a b. Show a => a -> b
unsupported CallishMachOp
mop
MO_AddWordC Width
_w -> CallishMachOp -> NatM (OrdList Instr, Maybe BlockId)
forall a b. Show a => a -> b
unsupported CallishMachOp
mop
MO_SubWordC Width
_w -> CallishMachOp -> NatM (OrdList Instr, Maybe BlockId)
forall a b. Show a => a -> b
unsupported CallishMachOp
mop
MO_AddIntC Width
_w -> CallishMachOp -> NatM (OrdList Instr, Maybe BlockId)
forall a b. Show a => a -> b
unsupported CallishMachOp
mop
MO_SubIntC Width
_w -> CallishMachOp -> NatM (OrdList Instr, Maybe BlockId)
forall a b. Show a => a -> b
unsupported CallishMachOp
mop
MO_U_Mul2 Width
_w -> CallishMachOp -> NatM (OrdList Instr, Maybe BlockId)
forall a b. Show a => a -> b
unsupported CallishMachOp
mop
CallishMachOp
MO_AcquireFence -> (OrdList Instr, Maybe BlockId)
-> NatM (OrdList Instr, Maybe BlockId)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL Instr
DMBISH, Maybe BlockId
forall a. Maybe a
Nothing)
CallishMachOp
MO_ReleaseFence -> (OrdList Instr, Maybe BlockId)
-> NatM (OrdList Instr, Maybe BlockId)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL Instr
DMBISH, Maybe BlockId
forall a. Maybe a
Nothing)
CallishMachOp
MO_SeqCstFence -> (OrdList Instr, Maybe BlockId)
-> NatM (OrdList Instr, Maybe BlockId)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Instr -> OrdList Instr
forall a. a -> OrdList a
unitOL Instr
DMBISH, Maybe BlockId
forall a. Maybe a
Nothing)
CallishMachOp
MO_Touch -> (OrdList Instr, Maybe BlockId)
-> NatM (OrdList Instr, Maybe BlockId)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OrdList Instr
forall a. OrdList a
nilOL, Maybe BlockId
forall a. Maybe a
Nothing)
MO_Prefetch_Data Int
_n -> (OrdList Instr, Maybe BlockId)
-> NatM (OrdList Instr, Maybe BlockId)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OrdList Instr
forall a. OrdList a
nilOL, Maybe BlockId
forall a. Maybe a
Nothing)
MO_Memcpy Int
_align -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"memcpy"
MO_Memset Int
_align -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"memset"
MO_Memmove Int
_align -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"memmove"
MO_Memcmp Int
_align -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"memcmp"
CallishMachOp
MO_SuspendThread -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"suspendThread"
CallishMachOp
MO_ResumeThread -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
"resumeThread"
MO_PopCnt Width
w -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall (Width -> FastString
popCntLabel Width
w)
MO_Pdep Width
w -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall (Width -> FastString
pdepLabel Width
w)
MO_Pext Width
w -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall (Width -> FastString
pextLabel Width
w)
MO_Clz Width
w -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall (Width -> FastString
clzLabel Width
w)
MO_Ctz Width
w -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall (Width -> FastString
ctzLabel Width
w)
MO_BSwap Width
w -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall (Width -> FastString
bSwapLabel Width
w)
MO_BRev Width
w -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall (Width -> FastString
bRevLabel Width
w)
MO_AtomicRead Width
w MemoryOrdering
ord
| [CmmExpr
p_reg] <- [CmmExpr]
arg_regs
, [CmmFormal
dst_reg] <- [CmmFormal]
dest_regs -> do
(p, _fmt_p, code_p) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
p_reg
platform <- getPlatform
let instr = case MemoryOrdering
ord of
MemoryOrdering
MemOrderRelaxed -> Format -> Operand -> Operand -> Instr
LDR
MemoryOrdering
_ -> Format -> Operand -> Operand -> Instr
LDAR
dst = Platform -> CmmReg -> Reg
getRegisterReg Platform
platform (CmmFormal -> CmmReg
CmmLocal CmmFormal
dst_reg)
code =
OrdList Instr
code_p OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
Format -> Operand -> Operand -> Instr
instr (Width -> Format
intFormat Width
w) (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (AddrMode -> Operand
OpAddr (AddrMode -> Operand) -> AddrMode -> Operand
forall a b. (a -> b) -> a -> b
$ Reg -> AddrMode
AddrReg Reg
p)
return (code, Nothing)
| Bool
otherwise -> String -> NatM (OrdList Instr, Maybe BlockId)
forall a. HasCallStack => String -> a
panic String
"mal-formed AtomicRead"
MO_AtomicWrite Width
w MemoryOrdering
ord
| [CmmExpr
p_reg, CmmExpr
val_reg] <- [CmmExpr]
arg_regs -> do
(p, _fmt_p, code_p) <- CmmExpr -> NatM (Reg, Format, OrdList Instr)
getSomeReg CmmExpr
p_reg
(val, fmt_val, code_val) <- getSomeReg val_reg
let instr = case MemoryOrdering
ord of
MemoryOrdering
MemOrderRelaxed -> Format -> Operand -> Operand -> Instr
STR
MemoryOrdering
_ -> Format -> Operand -> Operand -> Instr
STLR
code =
OrdList Instr
code_p OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_val OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
Format -> Operand -> Operand -> Instr
instr Format
fmt_val (Width -> Reg -> Operand
OpReg Width
w Reg
val) (AddrMode -> Operand
OpAddr (AddrMode -> Operand) -> AddrMode -> Operand
forall a b. (a -> b) -> a -> b
$ Reg -> AddrMode
AddrReg Reg
p)
return (code, Nothing)
| Bool
otherwise -> String -> NatM (OrdList Instr, Maybe BlockId)
forall a. HasCallStack => String -> a
panic String
"mal-formed AtomicWrite"
MO_AtomicRMW Width
w AtomicMachOp
amop -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall (Width -> AtomicMachOp -> FastString
atomicRMWLabel Width
w AtomicMachOp
amop)
MO_Cmpxchg Width
w -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall (Width -> FastString
cmpxchgLabel Width
w)
MO_Xchg Width
w -> FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall (Width -> FastString
xchgLabel Width
w)
where
unsupported :: Show a => a -> b
unsupported :: forall a b. Show a => a -> b
unsupported a
mop = String -> b
forall a. HasCallStack => String -> a
panic (String
"outOfLineCmmOp: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
mop
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" not supported here")
mkCCall :: FastString -> NatM (InstrBlock, Maybe BlockId)
mkCCall :: FastString -> NatM (OrdList Instr, Maybe BlockId)
mkCCall FastString
name = do
config <- NatM NCGConfig
getConfig
target <- cmmMakeDynamicReference config CallReference $
mkForeignLabel name Nothing ForeignLabelInThisPackage IsFunction
let cconv = CCallConv
-> [ForeignHint]
-> [ForeignHint]
-> CmmReturnInfo
-> ForeignConvention
ForeignConvention CCallConv
CCallConv [ForeignHint
NoHint] [ForeignHint
NoHint] CmmReturnInfo
CmmMayReturn
genCCall (ForeignTarget target cconv) dest_regs arg_regs bid
passArguments :: Bool -> [Reg] -> [Reg] -> [(Reg, Format, ForeignHint, InstrBlock)] -> Int -> [Reg] -> InstrBlock -> NatM (Int, [Reg], InstrBlock)
passArguments :: Bool
-> [Reg]
-> [Reg]
-> [(Reg, Format, ForeignHint, OrdList Instr)]
-> Int
-> [Reg]
-> OrdList Instr
-> NatM (Int, [Reg], OrdList Instr)
passArguments Bool
_packStack [Reg]
_ [Reg]
_ [] Int
stackSpace [Reg]
accumRegs OrdList Instr
accumCode = (Int, [Reg], OrdList Instr) -> NatM (Int, [Reg], OrdList Instr)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
stackSpace, [Reg]
accumRegs, OrdList Instr
accumCode)
passArguments Bool
pack (Reg
gpReg:[Reg]
gpRegs) [Reg]
fpRegs ((Reg
r, Format
format, ForeignHint
hint, OrdList Instr
code_r):[(Reg, Format, ForeignHint, OrdList Instr)]
args) Int
stackSpace [Reg]
accumRegs OrdList Instr
accumCode | Format -> Bool
isIntFormat Format
format = do
platform <- NatM Platform
getPlatform
let w = Format -> Width
formatToWidth Format
format
mov
| Width
w Width -> Width -> Bool
forall a. Ord a => a -> a -> Bool
< Width
W32
, Platform -> Bool
platformCConvNeedsExtension Platform
platform
, ForeignHint
SignedHint <- ForeignHint
hint
= case Width
w of
Width
W8 -> Operand -> Operand -> Instr
SXTB (Width -> Reg -> Operand
OpReg Width
W64 Reg
gpReg) (Width -> Reg -> Operand
OpReg Width
w Reg
r)
Width
W16 -> Operand -> Operand -> Instr
SXTH (Width -> Reg -> Operand
OpReg Width
W64 Reg
gpReg) (Width -> Reg -> Operand
OpReg Width
w Reg
r)
Width
_ -> String -> Instr
forall a. HasCallStack => String -> a
panic String
"impossible"
| Bool
otherwise
= Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
w Reg
gpReg) (Width -> Reg -> Operand
OpReg Width
w Reg
r)
accumCode' = OrdList Instr
accumCode OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_r OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
SDoc -> Instr -> Instr
ann (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Pass gp argument: " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Reg -> SDoc
forall a. Outputable a => a -> SDoc
ppr Reg
r) Instr
mov
passArguments pack gpRegs fpRegs args stackSpace (gpReg:accumRegs) accumCode'
passArguments Bool
pack [Reg]
gpRegs (Reg
fpReg:[Reg]
fpRegs) ((Reg
r, Format
format, ForeignHint
_hint, OrdList Instr
code_r):[(Reg, Format, ForeignHint, OrdList Instr)]
args) Int
stackSpace [Reg]
accumRegs OrdList Instr
accumCode | Format -> Bool
isFloatFormat Format
format = do
let w :: Width
w = Format -> Width
formatToWidth Format
format
mov :: Instr
mov = Operand -> Operand -> Instr
MOV (Width -> Reg -> Operand
OpReg Width
w Reg
fpReg) (Width -> Reg -> Operand
OpReg Width
w Reg
r)
accumCode' :: OrdList Instr
accumCode' = OrdList Instr
accumCode OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL`
OrdList Instr
code_r OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
SDoc -> Instr -> Instr
ann (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Pass fp argument: " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Reg -> SDoc
forall a. Outputable a => a -> SDoc
ppr Reg
r) Instr
mov
Bool
-> [Reg]
-> [Reg]
-> [(Reg, Format, ForeignHint, OrdList Instr)]
-> Int
-> [Reg]
-> OrdList Instr
-> NatM (Int, [Reg], OrdList Instr)
passArguments Bool
pack [Reg]
gpRegs [Reg]
fpRegs [(Reg, Format, ForeignHint, OrdList Instr)]
args Int
stackSpace (Reg
fpRegReg -> [Reg] -> [Reg]
forall a. a -> [a] -> [a]
:[Reg]
accumRegs) OrdList Instr
accumCode'
passArguments Bool
pack [] [] ((Reg
r, Format
format, ForeignHint
_hint, OrdList Instr
code_r):[(Reg, Format, ForeignHint, OrdList Instr)]
args) Int
stackSpace [Reg]
accumRegs OrdList Instr
accumCode = do
let w :: Width
w = Format -> Width
formatToWidth Format
format
bytes :: Int
bytes = Width -> Int
widthInBits Width
w Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
8
space :: Int
space = if Bool
pack then Int
bytes else Int
8
stackSpace' :: Int
stackSpace' | Bool
pack Bool -> Bool -> Bool
&& Int
stackSpace Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
space Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0 = Int
stackSpace Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
space Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
stackSpace Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
space)
| Bool
otherwise = Int
stackSpace
str :: Instr
str = Format -> Operand -> Operand -> Instr
STR Format
format (Width -> Reg -> Operand
OpReg Width
w Reg
r) (AddrMode -> Operand
OpAddr (Reg -> Imm -> AddrMode
AddrRegImm (Int -> Reg
regSingle Int
31) (Int -> Imm
ImmInt Int
stackSpace')))
stackCode :: OrdList Instr
stackCode = OrdList Instr
code_r OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
SDoc -> Instr -> Instr
ann (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Pass argument (size " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr Width
w SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
") on the stack: " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Reg -> SDoc
forall a. Outputable a => a -> SDoc
ppr Reg
r) Instr
str
Bool
-> [Reg]
-> [Reg]
-> [(Reg, Format, ForeignHint, OrdList Instr)]
-> Int
-> [Reg]
-> OrdList Instr
-> NatM (Int, [Reg], OrdList Instr)
passArguments Bool
pack [] [] [(Reg, Format, ForeignHint, OrdList Instr)]
args (Int
stackSpace'Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
space) [Reg]
accumRegs (OrdList Instr
stackCode OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
accumCode)
passArguments Bool
pack [] [Reg]
fpRegs ((Reg
r, Format
format, ForeignHint
_hint, OrdList Instr
code_r):[(Reg, Format, ForeignHint, OrdList Instr)]
args) Int
stackSpace [Reg]
accumRegs OrdList Instr
accumCode | Format -> Bool
isIntFormat Format
format = do
let w :: Width
w = Format -> Width
formatToWidth Format
format
bytes :: Int
bytes = Width -> Int
widthInBits Width
w Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
8
space :: Int
space = if Bool
pack then Int
bytes else Int
8
stackSpace' :: Int
stackSpace' | Bool
pack Bool -> Bool -> Bool
&& Int
stackSpace Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
space Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0 = Int
stackSpace Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
space Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
stackSpace Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
space)
| Bool
otherwise = Int
stackSpace
str :: Instr
str = Format -> Operand -> Operand -> Instr
STR Format
format (Width -> Reg -> Operand
OpReg Width
w Reg
r) (AddrMode -> Operand
OpAddr (Reg -> Imm -> AddrMode
AddrRegImm (Int -> Reg
regSingle Int
31) (Int -> Imm
ImmInt Int
stackSpace')))
stackCode :: OrdList Instr
stackCode = OrdList Instr
code_r OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
SDoc -> Instr -> Instr
ann (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Pass argument (size " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr Width
w SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
") on the stack: " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Reg -> SDoc
forall a. Outputable a => a -> SDoc
ppr Reg
r) Instr
str
Bool
-> [Reg]
-> [Reg]
-> [(Reg, Format, ForeignHint, OrdList Instr)]
-> Int
-> [Reg]
-> OrdList Instr
-> NatM (Int, [Reg], OrdList Instr)
passArguments Bool
pack [] [Reg]
fpRegs [(Reg, Format, ForeignHint, OrdList Instr)]
args (Int
stackSpace'Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
space) [Reg]
accumRegs (OrdList Instr
stackCode OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
accumCode)
passArguments Bool
pack [Reg]
gpRegs [] ((Reg
r, Format
format, ForeignHint
_hint, OrdList Instr
code_r):[(Reg, Format, ForeignHint, OrdList Instr)]
args) Int
stackSpace [Reg]
accumRegs OrdList Instr
accumCode | Format -> Bool
isFloatFormat Format
format = do
let w :: Width
w = Format -> Width
formatToWidth Format
format
bytes :: Int
bytes = Width -> Int
widthInBits Width
w Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
8
space :: Int
space = if Bool
pack then Int
bytes else Int
8
stackSpace' :: Int
stackSpace' | Bool
pack Bool -> Bool -> Bool
&& Int
stackSpace Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
space Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0 = Int
stackSpace Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
space Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
stackSpace Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
space)
| Bool
otherwise = Int
stackSpace
str :: Instr
str = Format -> Operand -> Operand -> Instr
STR Format
format (Width -> Reg -> Operand
OpReg Width
w Reg
r) (AddrMode -> Operand
OpAddr (Reg -> Imm -> AddrMode
AddrRegImm (Int -> Reg
regSingle Int
31) (Int -> Imm
ImmInt Int
stackSpace')))
stackCode :: OrdList Instr
stackCode = OrdList Instr
code_r OrdList Instr -> Instr -> OrdList Instr
forall a. OrdList a -> a -> OrdList a
`snocOL`
SDoc -> Instr -> Instr
ann (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Pass argument (size " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr Width
w SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
") on the stack: " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Reg -> SDoc
forall a. Outputable a => a -> SDoc
ppr Reg
r) Instr
str
Bool
-> [Reg]
-> [Reg]
-> [(Reg, Format, ForeignHint, OrdList Instr)]
-> Int
-> [Reg]
-> OrdList Instr
-> NatM (Int, [Reg], OrdList Instr)
passArguments Bool
pack [Reg]
gpRegs [] [(Reg, Format, ForeignHint, OrdList Instr)]
args (Int
stackSpace'Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
space) [Reg]
accumRegs (OrdList Instr
stackCode OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Instr
accumCode)
passArguments Bool
_ [Reg]
_ [Reg]
_ [(Reg, Format, ForeignHint, OrdList Instr)]
_ Int
_ [Reg]
_ OrdList Instr
_ = String -> SDoc -> NatM (Int, [Reg], OrdList Instr)
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"passArguments" (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"invalid state")
readResults :: [Reg] -> [Reg] -> [LocalReg] -> [Reg]-> InstrBlock -> NatM ([Reg], InstrBlock)
readResults :: [Reg]
-> [Reg]
-> [CmmFormal]
-> [Reg]
-> OrdList Instr
-> NatM ([Reg], OrdList Instr)
readResults [Reg]
_ [Reg]
_ [] [Reg]
accumRegs OrdList Instr
accumCode = ([Reg], OrdList Instr) -> NatM ([Reg], OrdList Instr)
forall a. a -> NatM a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Reg]
accumRegs, OrdList Instr
accumCode)
readResults [] [Reg]
_ [CmmFormal]
_ [Reg]
_ OrdList Instr
_ = do
platform <- NatM Platform
getPlatform
pprPanic "genCCall, out of gp registers when reading results" (pdoc platform target)
readResults [Reg]
_ [] [CmmFormal]
_ [Reg]
_ OrdList Instr
_ = do
platform <- NatM Platform
getPlatform
pprPanic "genCCall, out of fp registers when reading results" (pdoc platform target)
readResults (Reg
gpReg:[Reg]
gpRegs) (Reg
fpReg:[Reg]
fpRegs) (CmmFormal
dst:[CmmFormal]
dsts) [Reg]
accumRegs OrdList Instr
accumCode = do
platform <- NatM Platform
getPlatform
let rep = CmmReg -> CmmType
cmmRegType (CmmFormal -> CmmReg
CmmLocal CmmFormal
dst)
format = CmmType -> Format
cmmTypeFormat CmmType
rep
w = CmmReg -> Width
cmmRegWidth (CmmFormal -> CmmReg
CmmLocal CmmFormal
dst)
r_dst = Platform -> CmmReg -> Reg
getRegisterReg Platform
platform (CmmFormal -> CmmReg
CmmLocal CmmFormal
dst)
if isFloatFormat format
then readResults (gpReg:gpRegs) fpRegs dsts (fpReg:accumRegs) (accumCode `snocOL` MOV (OpReg w r_dst) (OpReg w fpReg))
else readResults gpRegs (fpReg:fpRegs) dsts (gpReg:accumRegs) (accumCode `snocOL` MOV (OpReg w r_dst) (OpReg w gpReg))
unaryFloatOp :: Width
-> (Operand -> Operand -> OrdList Instr)
-> CmmExpr
-> CmmFormal
-> NatM (OrdList Instr, Maybe a)
unaryFloatOp Width
w Operand -> Operand -> OrdList Instr
op CmmExpr
arg_reg CmmFormal
dest_reg = do
platform <- NatM Platform
getPlatform
(reg_fx, _format_x, code_fx) <- getFloatReg arg_reg
let dst = Platform -> CmmReg -> Reg
getRegisterReg Platform
platform (CmmFormal -> CmmReg
CmmLocal CmmFormal
dest_reg)
let code = OrdList Instr
code_fx OrdList Instr -> OrdList Instr -> OrdList Instr
forall a. OrdList a -> OrdList a -> OrdList a
`appOL` Operand -> Operand -> OrdList Instr
op (Width -> Reg -> Operand
OpReg Width
w Reg
dst) (Width -> Reg -> Operand
OpReg Width
w Reg
reg_fx)
return (code, Nothing)
data BlockInRange = InRange | NotInRange Target
makeFarBranches :: Platform -> LabelMap RawCmmStatics -> [NatBasicBlock Instr]
-> UniqSM [NatBasicBlock Instr]
makeFarBranches :: Platform
-> LabelMap RawCmmStatics
-> [NatBasicBlock Instr]
-> UniqSM [NatBasicBlock Instr]
makeFarBranches Platform
_platform LabelMap RawCmmStatics
statics [NatBasicBlock Instr]
basic_blocks = do
let (Int
func_size, LabelMap Int
lblMap) = ((Int, LabelMap Int) -> NatBasicBlock Instr -> (Int, LabelMap Int))
-> (Int, LabelMap Int)
-> [NatBasicBlock Instr]
-> (Int, LabelMap Int)
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (Int, LabelMap Int) -> NatBasicBlock Instr -> (Int, LabelMap Int)
calc_lbl_positions (Int
0, LabelMap Int
forall v. LabelMap v
mapEmpty) [NatBasicBlock Instr]
basic_blocks
if Int
func_size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
max_jump_dist
then [NatBasicBlock Instr] -> UniqSM [NatBasicBlock Instr]
forall a. a -> UniqSM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [NatBasicBlock Instr]
basic_blocks
else do
(_,blocks) <- (Int -> NatBasicBlock Instr -> UniqSM (Int, [NatBasicBlock Instr]))
-> Int
-> [NatBasicBlock Instr]
-> UniqSM (Int, [[NatBasicBlock Instr]])
forall (m :: * -> *) (t :: * -> *) acc x y.
(Monad m, Traversable t) =>
(acc -> x -> m (acc, y)) -> acc -> t x -> m (acc, t y)
mapAccumLM (LabelMap Int
-> Int
-> NatBasicBlock Instr
-> UniqSM (Int, [NatBasicBlock Instr])
replace_blk LabelMap Int
lblMap) Int
0 [NatBasicBlock Instr]
basic_blocks
pure $ concat blocks
where
max_jump_dist :: Int
max_jump_dist = Int
2Int -> Int -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
18::Int) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1 :: Int
max_info_size :: Int
max_info_size = Int
16 :: Int
long_bc_jump_size :: Int
long_bc_jump_size = Int
3 :: Int
long_bz_jump_size :: Int
long_bz_jump_size = Int
4 :: Int
replace_blk :: LabelMap Int -> Int -> GenBasicBlock Instr -> UniqSM (Int, [GenBasicBlock Instr])
replace_blk :: LabelMap Int
-> Int
-> NatBasicBlock Instr
-> UniqSM (Int, [NatBasicBlock Instr])
replace_blk !LabelMap Int
m !Int
pos (BasicBlock BlockId
lbl [Instr]
instrs) = do
let !block_pos :: Int
block_pos = Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ BlockId -> Int
infoTblSize_maybe BlockId
lbl
(!pos', instrs') <- (Int -> Instr -> UniqSM (Int, [Instr]))
-> Int -> [Instr] -> UniqSM (Int, [[Instr]])
forall (m :: * -> *) (t :: * -> *) acc x y.
(Monad m, Traversable t) =>
(acc -> x -> m (acc, y)) -> acc -> t x -> m (acc, t y)
mapAccumLM (LabelMap Int -> Int -> Instr -> UniqSM (Int, [Instr])
replace_jump LabelMap Int
m) Int
block_pos [Instr]
instrs
let instrs'' = [[Instr]] -> [Instr]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Instr]]
instrs'
let (top, split_blocks, no_data) = foldr mkBlocks ([],[],[]) instrs''
massert (null no_data)
let final_blocks = BlockId -> [Instr] -> NatBasicBlock Instr
forall i. BlockId -> [i] -> GenBasicBlock i
BasicBlock BlockId
lbl [Instr]
top NatBasicBlock Instr
-> [NatBasicBlock Instr] -> [NatBasicBlock Instr]
forall a. a -> [a] -> [a]
: [NatBasicBlock Instr]
split_blocks
pure (pos', final_blocks)
replace_jump :: LabelMap Int -> Int -> Instr -> UniqSM (Int, [Instr])
replace_jump :: LabelMap Int -> Int -> Instr -> UniqSM (Int, [Instr])
replace_jump !LabelMap Int
m !Int
pos Instr
instr = do
case Instr
instr of
ANN SDoc
ann Instr
instr -> do
(idx,instr':instrs') <- LabelMap Int -> Int -> Instr -> UniqSM (Int, [Instr])
replace_jump LabelMap Int
m Int
pos Instr
instr
pure (idx, ANN ann instr':instrs')
BCOND Cond
cond Target
t
-> case LabelMap Int -> Target -> Int -> BlockInRange
target_in_range LabelMap Int
m Target
t Int
pos of
BlockInRange
InRange -> (Int, [Instr]) -> UniqSM (Int, [Instr])
forall a. a -> UniqSM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
posInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
long_bc_jump_size,[Instr
instr])
NotInRange Target
far_target -> do
jmp_code <- Cond -> Target -> UniqSM (OrdList Instr)
forall (m :: * -> *).
MonadUnique m =>
Cond -> Target -> m (OrdList Instr)
genCondFarJump Cond
cond Target
far_target
pure (pos+long_bc_jump_size, fromOL jmp_code)
CBZ Operand
op Target
t -> Operand -> Target -> Cond -> UniqSM (Int, [Instr])
long_zero_jump Operand
op Target
t Cond
EQ
CBNZ Operand
op Target
t -> Operand -> Target -> Cond -> UniqSM (Int, [Instr])
long_zero_jump Operand
op Target
t Cond
NE
Instr
instr
| Instr -> Bool
isMetaInstr Instr
instr -> (Int, [Instr]) -> UniqSM (Int, [Instr])
forall a. a -> UniqSM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
pos,[Instr
instr])
| Bool
otherwise -> (Int, [Instr]) -> UniqSM (Int, [Instr])
forall a. a -> UniqSM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
posInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1, [Instr
instr])
where
long_zero_jump :: Operand -> Target -> Cond -> UniqSM (Int, [Instr])
long_zero_jump Operand
op Target
t Cond
cmp_op =
case LabelMap Int -> Target -> Int -> BlockInRange
target_in_range LabelMap Int
m Target
t Int
pos of
BlockInRange
InRange -> (Int, [Instr]) -> UniqSM (Int, [Instr])
forall a. a -> UniqSM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
posInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
long_bz_jump_size,[Instr
instr])
NotInRange Target
far_target -> do
jmp_code <- Cond -> Target -> UniqSM (OrdList Instr)
forall (m :: * -> *).
MonadUnique m =>
Cond -> Target -> m (OrdList Instr)
genCondFarJump Cond
cmp_op Target
far_target
pure (pos + long_bz_jump_size, CMP op (OpImm (ImmInt 0)) : fromOL jmp_code)
target_in_range :: LabelMap Int -> Target -> Int -> BlockInRange
target_in_range :: LabelMap Int -> Target -> Int -> BlockInRange
target_in_range LabelMap Int
m Target
target Int
src =
case Target
target of
(TReg{}) -> BlockInRange
InRange
(TBlock BlockId
bid) -> LabelMap Int -> Int -> BlockId -> BlockInRange
block_in_range LabelMap Int
m Int
src BlockId
bid
(TLabel CLabel
clbl)
| Just BlockId
bid <- CLabel -> Maybe BlockId
maybeLocalBlockLabel CLabel
clbl
-> LabelMap Int -> Int -> BlockId -> BlockInRange
block_in_range LabelMap Int
m Int
src BlockId
bid
| Bool
otherwise
-> BlockInRange
InRange
block_in_range :: LabelMap Int -> Int -> BlockId -> BlockInRange
block_in_range :: LabelMap Int -> Int -> BlockId -> BlockInRange
block_in_range LabelMap Int
m Int
src_pos BlockId
dest_lbl =
case BlockId -> LabelMap Int -> Maybe Int
forall a. BlockId -> LabelMap a -> Maybe a
mapLookup BlockId
dest_lbl LabelMap Int
m of
Maybe Int
Nothing ->
String -> SDoc -> BlockInRange -> BlockInRange
forall a. String -> SDoc -> a -> a
pprTrace String
"not in range" (BlockId -> SDoc
forall a. Outputable a => a -> SDoc
ppr BlockId
dest_lbl) (BlockInRange -> BlockInRange) -> BlockInRange -> BlockInRange
forall a b. (a -> b) -> a -> b
$
Target -> BlockInRange
NotInRange (BlockId -> Target
TBlock BlockId
dest_lbl)
Just Int
dest_pos -> if Int -> Int
forall a. Num a => a -> a
abs (Int
dest_pos Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
src_pos) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
max_jump_dist
then BlockInRange
InRange
else Target -> BlockInRange
NotInRange (BlockId -> Target
TBlock BlockId
dest_lbl)
calc_lbl_positions :: (Int, LabelMap Int) -> GenBasicBlock Instr -> (Int, LabelMap Int)
calc_lbl_positions :: (Int, LabelMap Int) -> NatBasicBlock Instr -> (Int, LabelMap Int)
calc_lbl_positions (Int
pos, LabelMap Int
m) (BasicBlock BlockId
lbl [Instr]
instrs)
= let !pos' :: Int
pos' = Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ BlockId -> Int
infoTblSize_maybe BlockId
lbl
in ((Int, LabelMap Int) -> Instr -> (Int, LabelMap Int))
-> (Int, LabelMap Int) -> [Instr] -> (Int, LabelMap Int)
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (Int, LabelMap Int) -> Instr -> (Int, LabelMap Int)
instr_pos (Int
pos',BlockId -> Int -> LabelMap Int -> LabelMap Int
forall v. BlockId -> v -> LabelMap v -> LabelMap v
mapInsert BlockId
lbl Int
pos' LabelMap Int
m) [Instr]
instrs
instr_pos :: (Int, LabelMap Int) -> Instr -> (Int, LabelMap Int)
instr_pos :: (Int, LabelMap Int) -> Instr -> (Int, LabelMap Int)
instr_pos (Int
pos, LabelMap Int
m) Instr
instr =
case Instr
instr of
ANN SDoc
_ann Instr
instr -> (Int, LabelMap Int) -> Instr -> (Int, LabelMap Int)
instr_pos (Int
pos, LabelMap Int
m) Instr
instr
NEWBLOCK BlockId
_bid -> String -> (Int, LabelMap Int)
forall a. HasCallStack => String -> a
panic String
"mkFarBranched - unexpected NEWBLOCK"
COMMENT{} -> (Int
pos, LabelMap Int
m)
Instr
instr
| Just Int
jump_size <- Instr -> Maybe Int
is_expandable_jump Instr
instr -> (Int
posInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
jump_size, LabelMap Int
m)
| Bool
otherwise -> (Int
posInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1, LabelMap Int
m)
infoTblSize_maybe :: BlockId -> Int
infoTblSize_maybe BlockId
bid =
case BlockId -> LabelMap RawCmmStatics -> Maybe RawCmmStatics
forall a. BlockId -> LabelMap a -> Maybe a
mapLookup BlockId
bid LabelMap RawCmmStatics
statics of
Maybe RawCmmStatics
Nothing -> Int
0 :: Int
Just RawCmmStatics
_info_static -> Int
max_info_size
is_expandable_jump :: Instr -> Maybe Int
is_expandable_jump Instr
i = case Instr
i of
CBZ{} -> Int -> Maybe Int
forall a. a -> Maybe a
Just Int
long_bz_jump_size
CBNZ{} -> Int -> Maybe Int
forall a. a -> Maybe a
Just Int
long_bz_jump_size
BCOND{} -> Int -> Maybe Int
forall a. a -> Maybe a
Just Int
long_bc_jump_size
Instr
_ -> Maybe Int
forall a. Maybe a
Nothing