{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
module GHC.Cmm.Expr
( CmmExpr(..), cmmExprType, cmmExprWidth, cmmExprAlignment, maybeInvertCmmExpr
, CmmReg(..), cmmRegType, cmmRegWidth
, CmmLit(..), cmmLitType
, LocalReg(..), localRegType
, GlobalReg(..), isArgReg, globalRegType
, spReg, hpReg, spLimReg, hpLimReg, nodeReg
, currentTSOReg, currentNurseryReg, hpAllocReg, cccsReg
, node, baseReg
, VGcPtr(..)
, DefinerOfRegs, UserOfRegs
, foldRegsDefd, foldRegsUsed
, foldLocalRegsDefd, foldLocalRegsUsed
, RegSet, LocalRegSet, GlobalRegSet
, emptyRegSet, elemRegSet, extendRegSet, deleteFromRegSet, mkRegSet
, plusRegSet, minusRegSet, timesRegSet, sizeRegSet, nullRegSet
, regSetToList
, Area(..)
, module GHC.Cmm.MachOp
, module GHC.Cmm.Type
)
where
import GHC.Prelude
import GHC.Platform
import GHC.Cmm.BlockId
import GHC.Cmm.CLabel
import GHC.Cmm.MachOp
import GHC.Cmm.Type
import GHC.Driver.Session
import GHC.Utils.Outputable (panic)
import GHC.Types.Unique
import Data.Set (Set)
import qualified Data.Set as Set
import GHC.Types.Basic (Alignment, mkAlignment, alignmentOf)
data CmmExpr
= CmmLit CmmLit
| CmmLoad !CmmExpr !CmmType
| CmmReg !CmmReg
| CmmMachOp MachOp [CmmExpr]
| CmmStackSlot Area {-# UNPACK #-} !Int
| CmmRegOff !CmmReg Int
instance Eq CmmExpr where
CmmLit CmmLit
l1 == :: CmmExpr -> CmmExpr -> Bool
== CmmLit CmmLit
l2 = CmmLit
l1CmmLit -> CmmLit -> Bool
forall a. Eq a => a -> a -> Bool
Instance of class: Eq of the constraint type Eq CmmLit
==CmmLit
l2
CmmLoad CmmExpr
e1 CmmType
_ == CmmLoad CmmExpr
e2 CmmType
_ = CmmExpr
e1CmmExpr -> CmmExpr -> Bool
forall a. Eq a => a -> a -> Bool
Instance of class: Eq of the constraint type Eq CmmExpr
==CmmExpr
e2
CmmReg CmmReg
r1 == CmmReg CmmReg
r2 = CmmReg
r1CmmReg -> CmmReg -> Bool
forall a. Eq a => a -> a -> Bool
Instance of class: Eq of the constraint type Eq CmmReg
==CmmReg
r2
CmmRegOff CmmReg
r1 Int
i1 == CmmRegOff CmmReg
r2 Int
i2 = CmmReg
r1CmmReg -> CmmReg -> Bool
forall a. Eq a => a -> a -> Bool
Instance of class: Eq of the constraint type Eq CmmReg
==CmmReg
r2 Bool -> Bool -> Bool
&& Int
i1Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
==Int
i2
CmmMachOp MachOp
op1 [CmmExpr]
es1 == CmmMachOp MachOp
op2 [CmmExpr]
es2 = MachOp
op1MachOp -> MachOp -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq MachOp
==MachOp
op2 Bool -> Bool -> Bool
&& [CmmExpr]
es1[CmmExpr] -> [CmmExpr] -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
Instance of class: Eq of the constraint type Eq CmmExpr
==[CmmExpr]
es2
CmmStackSlot Area
a1 Int
i1 == CmmStackSlot Area
a2 Int
i2 = Area
a1Area -> Area -> Bool
forall a. Eq a => a -> a -> Bool
Instance of class: Eq of the constraint type Eq Area
==Area
a2 Bool -> Bool -> Bool
&& Int
i1Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
==Int
i2
CmmExpr
_e1 == CmmExpr
_e2 = Bool
False
data CmmReg
= CmmLocal {-# UNPACK #-} !LocalReg
| CmmGlobal GlobalReg
deriving( CmmReg -> CmmReg -> Bool
(CmmReg -> CmmReg -> Bool)
-> (CmmReg -> CmmReg -> Bool) -> Eq CmmReg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CmmReg -> CmmReg -> Bool
$c/= :: CmmReg -> CmmReg -> Bool
== :: CmmReg -> CmmReg -> Bool
$c== :: CmmReg -> CmmReg -> Bool
Instance of class: Eq of the constraint type Eq LocalReg
Instance of class: Eq of the constraint type Eq GlobalReg
Eq, Eq CmmReg
Eq CmmReg
-> (CmmReg -> CmmReg -> Ordering)
-> (CmmReg -> CmmReg -> Bool)
-> (CmmReg -> CmmReg -> Bool)
-> (CmmReg -> CmmReg -> Bool)
-> (CmmReg -> CmmReg -> Bool)
-> (CmmReg -> CmmReg -> CmmReg)
-> (CmmReg -> CmmReg -> CmmReg)
-> Ord CmmReg
CmmReg -> CmmReg -> Bool
CmmReg -> CmmReg -> Ordering
CmmReg -> CmmReg -> CmmReg
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CmmReg -> CmmReg -> CmmReg
$cmin :: CmmReg -> CmmReg -> CmmReg
max :: CmmReg -> CmmReg -> CmmReg
$cmax :: CmmReg -> CmmReg -> CmmReg
>= :: CmmReg -> CmmReg -> Bool
$c>= :: CmmReg -> CmmReg -> Bool
> :: CmmReg -> CmmReg -> Bool
$c> :: CmmReg -> CmmReg -> Bool
<= :: CmmReg -> CmmReg -> Bool
$c<= :: CmmReg -> CmmReg -> Bool
< :: CmmReg -> CmmReg -> Bool
$c< :: CmmReg -> CmmReg -> Bool
compare :: CmmReg -> CmmReg -> Ordering
$ccompare :: CmmReg -> CmmReg -> Ordering
Instance of class: Eq of the constraint type Eq CmmReg
Instance of class: Ord of the constraint type Ord LocalReg
Instance of class: Ord of the constraint type Ord GlobalReg
Instance of class: Ord of the constraint type Ord CmmReg
Instance of class: Eq of the constraint type Eq CmmReg
Ord )
data Area
= Old
| Young {-# UNPACK #-} !BlockId
deriving (Area -> Area -> Bool
(Area -> Area -> Bool) -> (Area -> Area -> Bool) -> Eq Area
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Area -> Area -> Bool
$c/= :: Area -> Area -> Bool
== :: Area -> Area -> Bool
$c== :: Area -> Area -> Bool
External instance of the constraint type Eq BlockId
Eq, Eq Area
Eq Area
-> (Area -> Area -> Ordering)
-> (Area -> Area -> Bool)
-> (Area -> Area -> Bool)
-> (Area -> Area -> Bool)
-> (Area -> Area -> Bool)
-> (Area -> Area -> Area)
-> (Area -> Area -> Area)
-> Ord Area
Area -> Area -> Bool
Area -> Area -> Ordering
Area -> Area -> Area
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Area -> Area -> Area
$cmin :: Area -> Area -> Area
max :: Area -> Area -> Area
$cmax :: Area -> Area -> Area
>= :: Area -> Area -> Bool
$c>= :: Area -> Area -> Bool
> :: Area -> Area -> Bool
$c> :: Area -> Area -> Bool
<= :: Area -> Area -> Bool
$c<= :: Area -> Area -> Bool
< :: Area -> Area -> Bool
$c< :: Area -> Area -> Bool
compare :: Area -> Area -> Ordering
$ccompare :: Area -> Area -> Ordering
External instance of the constraint type Ord BlockId
Instance of class: Eq of the constraint type Eq Area
Instance of class: Ord of the constraint type Ord Area
Instance of class: Eq of the constraint type Eq Area
Ord)
data CmmLit
= CmmInt !Integer Width
| CmmFloat Rational Width
| CmmVec [CmmLit]
| CmmLabel CLabel
| CmmLabelOff CLabel Int
| CmmLabelDiffOff CLabel CLabel Int Width
| CmmBlock {-# UNPACK #-} !BlockId
| CmmHighStackMark
deriving CmmLit -> CmmLit -> Bool
(CmmLit -> CmmLit -> Bool)
-> (CmmLit -> CmmLit -> Bool) -> Eq CmmLit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CmmLit -> CmmLit -> Bool
$c/= :: CmmLit -> CmmLit -> Bool
== :: CmmLit -> CmmLit -> Bool
$c== :: CmmLit -> CmmLit -> Bool
External instance of the constraint type Eq Int
External instance of the constraint type Eq CLabel
External instance of the constraint type Eq CLabel
Instance of class: Eq of the constraint type Eq CmmLit
External instance of the constraint type forall a. Eq a => Eq (Ratio a)
External instance of the constraint type Eq Width
External instance of the constraint type Eq Width
External instance of the constraint type Eq Integer
External instance of the constraint type Eq Integer
External instance of the constraint type Eq BlockId
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Int
Instance of class: Eq of the constraint type Eq CmmLit
Eq
cmmExprType :: Platform -> CmmExpr -> CmmType
cmmExprType :: Platform -> CmmExpr -> CmmType
cmmExprType Platform
platform = \case
(CmmLit CmmLit
lit) -> Platform -> CmmLit -> CmmType
cmmLitType Platform
platform CmmLit
lit
(CmmLoad CmmExpr
_ CmmType
rep) -> CmmType
rep
(CmmReg CmmReg
reg) -> Platform -> CmmReg -> CmmType
cmmRegType Platform
platform CmmReg
reg
(CmmMachOp MachOp
op [CmmExpr]
args) -> Platform -> MachOp -> [CmmType] -> CmmType
machOpResultType Platform
platform MachOp
op ((CmmExpr -> CmmType) -> [CmmExpr] -> [CmmType]
forall a b. (a -> b) -> [a] -> [b]
map (Platform -> CmmExpr -> CmmType
cmmExprType Platform
platform) [CmmExpr]
args)
(CmmRegOff CmmReg
reg Int
_) -> Platform -> CmmReg -> CmmType
cmmRegType Platform
platform CmmReg
reg
(CmmStackSlot Area
_ Int
_) -> Platform -> CmmType
bWord Platform
platform
cmmLitType :: Platform -> CmmLit -> CmmType
cmmLitType :: Platform -> CmmLit -> CmmType
cmmLitType Platform
platform = \case
(CmmInt Integer
_ Width
width) -> Width -> CmmType
cmmBits Width
width
(CmmFloat Rational
_ Width
width) -> Width -> CmmType
cmmFloat Width
width
(CmmVec []) -> String -> CmmType
forall a. String -> a
panic String
"cmmLitType: CmmVec []"
(CmmVec (CmmLit
l:[CmmLit]
ls)) -> let ty :: CmmType
ty = Platform -> CmmLit -> CmmType
cmmLitType Platform
platform CmmLit
l
in if (CmmType -> Bool) -> [CmmType] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
External instance of the constraint type Foldable []
all (CmmType -> CmmType -> Bool
`cmmEqType` CmmType
ty) ((CmmLit -> CmmType) -> [CmmLit] -> [CmmType]
forall a b. (a -> b) -> [a] -> [b]
map (Platform -> CmmLit -> CmmType
cmmLitType Platform
platform) [CmmLit]
ls)
then Int -> CmmType -> CmmType
cmmVec (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+[CmmLit] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
External instance of the constraint type Foldable []
length [CmmLit]
ls) CmmType
ty
else String -> CmmType
forall a. String -> a
panic String
"cmmLitType: CmmVec"
(CmmLabel CLabel
lbl) -> Platform -> CLabel -> CmmType
cmmLabelType Platform
platform CLabel
lbl
(CmmLabelOff CLabel
lbl Int
_) -> Platform -> CLabel -> CmmType
cmmLabelType Platform
platform CLabel
lbl
(CmmLabelDiffOff CLabel
_ CLabel
_ Int
_ Width
width) -> Width -> CmmType
cmmBits Width
width
(CmmBlock BlockId
_) -> Platform -> CmmType
bWord Platform
platform
(CmmLit
CmmHighStackMark) -> Platform -> CmmType
bWord Platform
platform
cmmLabelType :: Platform -> CLabel -> CmmType
cmmLabelType :: Platform -> CLabel -> CmmType
cmmLabelType Platform
platform CLabel
lbl
| CLabel -> Bool
isGcPtrLabel CLabel
lbl = Platform -> CmmType
gcWord Platform
platform
| Bool
otherwise = Platform -> CmmType
bWord Platform
platform
cmmExprWidth :: Platform -> CmmExpr -> Width
cmmExprWidth :: Platform -> CmmExpr -> Width
cmmExprWidth Platform
platform CmmExpr
e = CmmType -> Width
typeWidth (Platform -> CmmExpr -> CmmType
cmmExprType Platform
platform CmmExpr
e)
cmmExprAlignment :: CmmExpr -> Alignment
cmmExprAlignment :: CmmExpr -> Alignment
cmmExprAlignment (CmmLit (CmmInt Integer
intOff Width
_)) = Int -> Alignment
alignmentOf (Integer -> Int
forall a. Num a => Integer -> a
External instance of the constraint type Num Int
fromInteger Integer
intOff)
cmmExprAlignment CmmExpr
_ = Int -> Alignment
mkAlignment Int
1
maybeInvertCmmExpr :: CmmExpr -> Maybe CmmExpr
maybeInvertCmmExpr :: CmmExpr -> Maybe CmmExpr
maybeInvertCmmExpr (CmmMachOp MachOp
op [CmmExpr]
args) = do MachOp
op' <- MachOp -> Maybe MachOp
maybeInvertComparison MachOp
op
CmmExpr -> Maybe CmmExpr
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Maybe
return (MachOp -> [CmmExpr] -> CmmExpr
CmmMachOp MachOp
op' [CmmExpr]
args)
maybeInvertCmmExpr CmmExpr
_ = Maybe CmmExpr
forall a. Maybe a
Nothing
data LocalReg
= LocalReg {-# UNPACK #-} !Unique CmmType
instance Eq LocalReg where
(LocalReg Unique
u1 CmmType
_) == :: LocalReg -> LocalReg -> Bool
== (LocalReg Unique
u2 CmmType
_) = Unique
u1 Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Unique
== Unique
u2
instance Ord LocalReg where
compare :: LocalReg -> LocalReg -> Ordering
compare (LocalReg Unique
u1 CmmType
_) (LocalReg Unique
u2 CmmType
_) = Unique -> Unique -> Ordering
nonDetCmpUnique Unique
u1 Unique
u2
instance Uniquable LocalReg where
getUnique :: LocalReg -> Unique
getUnique (LocalReg Unique
uniq CmmType
_) = Unique
uniq
cmmRegType :: Platform -> CmmReg -> CmmType
cmmRegType :: Platform -> CmmReg -> CmmType
cmmRegType Platform
_ (CmmLocal LocalReg
reg) = LocalReg -> CmmType
localRegType LocalReg
reg
cmmRegType Platform
platform (CmmGlobal GlobalReg
reg) = Platform -> GlobalReg -> CmmType
globalRegType Platform
platform GlobalReg
reg
cmmRegWidth :: Platform -> CmmReg -> Width
cmmRegWidth :: Platform -> CmmReg -> Width
cmmRegWidth Platform
platform = CmmType -> Width
typeWidth (CmmType -> Width) -> (CmmReg -> CmmType) -> CmmReg -> Width
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Platform -> CmmReg -> CmmType
cmmRegType Platform
platform
localRegType :: LocalReg -> CmmType
localRegType :: LocalReg -> CmmType
localRegType (LocalReg Unique
_ CmmType
rep) = CmmType
rep
type RegSet r = Set r
type LocalRegSet = RegSet LocalReg
type GlobalRegSet = RegSet GlobalReg
emptyRegSet :: RegSet r
nullRegSet :: RegSet r -> Bool
elemRegSet :: Ord r => r -> RegSet r -> Bool
extendRegSet :: Ord r => RegSet r -> r -> RegSet r
deleteFromRegSet :: Ord r => RegSet r -> r -> RegSet r
mkRegSet :: Ord r => [r] -> RegSet r
minusRegSet, plusRegSet, timesRegSet :: Ord r => RegSet r -> RegSet r -> RegSet r
sizeRegSet :: RegSet r -> Int
regSetToList :: RegSet r -> [r]
emptyRegSet :: RegSet r
emptyRegSet = RegSet r
forall a. Set a
Set.empty
nullRegSet :: RegSet r -> Bool
nullRegSet = RegSet r -> Bool
forall a. Set a -> Bool
Set.null
elemRegSet :: r -> RegSet r -> Bool
elemRegSet = r -> RegSet r -> Bool
forall a. Ord a => a -> Set a -> Bool
Evidence bound by a type signature of the constraint type Ord r
Set.member
extendRegSet :: RegSet r -> r -> RegSet r
extendRegSet = (r -> RegSet r -> RegSet r) -> RegSet r -> r -> RegSet r
forall a b c. (a -> b -> c) -> b -> a -> c
flip r -> RegSet r -> RegSet r
forall a. Ord a => a -> Set a -> Set a
Evidence bound by a type signature of the constraint type Ord r
Set.insert
deleteFromRegSet :: RegSet r -> r -> RegSet r
deleteFromRegSet = (r -> RegSet r -> RegSet r) -> RegSet r -> r -> RegSet r
forall a b c. (a -> b -> c) -> b -> a -> c
flip r -> RegSet r -> RegSet r
forall a. Ord a => a -> Set a -> Set a
Evidence bound by a type signature of the constraint type Ord r
Set.delete
mkRegSet :: [r] -> RegSet r
mkRegSet = [r] -> RegSet r
forall a. Ord a => [a] -> Set a
Evidence bound by a type signature of the constraint type Ord r
Set.fromList
minusRegSet :: RegSet r -> RegSet r -> RegSet r
minusRegSet = RegSet r -> RegSet r -> RegSet r
forall a. Ord a => Set a -> Set a -> Set a
Evidence bound by a type signature of the constraint type Ord r
Set.difference
plusRegSet :: RegSet r -> RegSet r -> RegSet r
plusRegSet = RegSet r -> RegSet r -> RegSet r
forall a. Ord a => Set a -> Set a -> Set a
Evidence bound by a type signature of the constraint type Ord r
Set.union
timesRegSet :: RegSet r -> RegSet r -> RegSet r
timesRegSet = RegSet r -> RegSet r -> RegSet r
forall a. Ord a => Set a -> Set a -> Set a
Evidence bound by a type signature of the constraint type Ord r
Set.intersection
sizeRegSet :: RegSet r -> Int
sizeRegSet = RegSet r -> Int
forall a. Set a -> Int
Set.size
regSetToList :: RegSet r -> [r]
regSetToList = RegSet r -> [r]
forall a. Set a -> [a]
Set.toList
class Ord r => UserOfRegs r a where
foldRegsUsed :: DynFlags -> (b -> r -> b) -> b -> a -> b
foldLocalRegsUsed :: UserOfRegs LocalReg a
=> DynFlags -> (b -> LocalReg -> b) -> b -> a -> b
foldLocalRegsUsed :: DynFlags -> (b -> LocalReg -> b) -> b -> a -> b
foldLocalRegsUsed = DynFlags -> (b -> LocalReg -> b) -> b -> a -> b
forall r a b.
UserOfRegs r a =>
DynFlags -> (b -> r -> b) -> b -> a -> b
Evidence bound by a type signature of the constraint type UserOfRegs LocalReg a
foldRegsUsed
class Ord r => DefinerOfRegs r a where
foldRegsDefd :: DynFlags -> (b -> r -> b) -> b -> a -> b
foldLocalRegsDefd :: DefinerOfRegs LocalReg a
=> DynFlags -> (b -> LocalReg -> b) -> b -> a -> b
foldLocalRegsDefd :: DynFlags -> (b -> LocalReg -> b) -> b -> a -> b
foldLocalRegsDefd = DynFlags -> (b -> LocalReg -> b) -> b -> a -> b
forall r a b.
DefinerOfRegs r a =>
DynFlags -> (b -> r -> b) -> b -> a -> b
Evidence bound by a type signature of the constraint type DefinerOfRegs LocalReg a
foldRegsDefd
instance UserOfRegs LocalReg CmmReg where
foldRegsUsed :: DynFlags -> (b -> LocalReg -> b) -> b -> CmmReg -> b
foldRegsUsed DynFlags
_ b -> LocalReg -> b
f b
z (CmmLocal LocalReg
reg) = b -> LocalReg -> b
f b
z LocalReg
reg
foldRegsUsed DynFlags
_ b -> LocalReg -> b
_ b
z (CmmGlobal GlobalReg
_) = b
z
instance DefinerOfRegs LocalReg CmmReg where
foldRegsDefd :: DynFlags -> (b -> LocalReg -> b) -> b -> CmmReg -> b
foldRegsDefd DynFlags
_ b -> LocalReg -> b
f b
z (CmmLocal LocalReg
reg) = b -> LocalReg -> b
f b
z LocalReg
reg
foldRegsDefd DynFlags
_ b -> LocalReg -> b
_ b
z (CmmGlobal GlobalReg
_) = b
z
instance UserOfRegs GlobalReg CmmReg where
foldRegsUsed :: DynFlags -> (b -> GlobalReg -> b) -> b -> CmmReg -> b
foldRegsUsed DynFlags
_ b -> GlobalReg -> b
_ b
z (CmmLocal LocalReg
_) = b
z
foldRegsUsed DynFlags
_ b -> GlobalReg -> b
f b
z (CmmGlobal GlobalReg
reg) = b -> GlobalReg -> b
f b
z GlobalReg
reg
instance DefinerOfRegs GlobalReg CmmReg where
foldRegsDefd :: DynFlags -> (b -> GlobalReg -> b) -> b -> CmmReg -> b
foldRegsDefd DynFlags
_ b -> GlobalReg -> b
_ b
z (CmmLocal LocalReg
_) = b
z
foldRegsDefd DynFlags
_ b -> GlobalReg -> b
f b
z (CmmGlobal GlobalReg
reg) = b -> GlobalReg -> b
f b
z GlobalReg
reg
instance Ord r => UserOfRegs r r where
foldRegsUsed :: DynFlags -> (b -> r -> b) -> b -> r -> b
foldRegsUsed DynFlags
_ b -> r -> b
f b
z r
r = b -> r -> b
f b
z r
r
instance Ord r => DefinerOfRegs r r where
foldRegsDefd :: DynFlags -> (b -> r -> b) -> b -> r -> b
foldRegsDefd DynFlags
_ b -> r -> b
f b
z r
r = b -> r -> b
f b
z r
r
instance (Ord r, UserOfRegs r CmmReg) => UserOfRegs r CmmExpr where
foldRegsUsed :: DynFlags -> (b -> r -> b) -> b -> CmmExpr -> b
foldRegsUsed DynFlags
dflags b -> r -> b
f !b
z CmmExpr
e = b -> CmmExpr -> b
expr b
z CmmExpr
e
where expr :: b -> CmmExpr -> b
expr b
z (CmmLit CmmLit
_) = b
z
expr b
z (CmmLoad CmmExpr
addr CmmType
_) = DynFlags -> (b -> r -> b) -> b -> CmmExpr -> b
forall r a b.
UserOfRegs r a =>
DynFlags -> (b -> r -> b) -> b -> a -> b
Instance of class: UserOfRegs of the constraint type forall r. (Ord r, UserOfRegs r CmmReg) => UserOfRegs r CmmExpr
Evidence bound by a type signature of the constraint type Ord r
Evidence bound by a type signature of the constraint type UserOfRegs r CmmReg
foldRegsUsed DynFlags
dflags b -> r -> b
f b
z CmmExpr
addr
expr b
z (CmmReg CmmReg
r) = DynFlags -> (b -> r -> b) -> b -> CmmReg -> b
forall r a b.
UserOfRegs r a =>
DynFlags -> (b -> r -> b) -> b -> a -> b
Evidence bound by a type signature of the constraint type UserOfRegs r CmmReg
foldRegsUsed DynFlags
dflags b -> r -> b
f b
z CmmReg
r
expr b
z (CmmMachOp MachOp
_ [CmmExpr]
exprs) = DynFlags -> (b -> r -> b) -> b -> [CmmExpr] -> b
forall r a b.
UserOfRegs r a =>
DynFlags -> (b -> r -> b) -> b -> a -> b
Instance of class: UserOfRegs of the constraint type forall r a. UserOfRegs r a => UserOfRegs r [a]
Instance of class: UserOfRegs of the constraint type forall r. (Ord r, UserOfRegs r CmmReg) => UserOfRegs r CmmExpr
Evidence bound by a type signature of the constraint type Ord r
Evidence bound by a type signature of the constraint type UserOfRegs r CmmReg
foldRegsUsed DynFlags
dflags b -> r -> b
f b
z [CmmExpr]
exprs
expr b
z (CmmRegOff CmmReg
r Int
_) = DynFlags -> (b -> r -> b) -> b -> CmmReg -> b
forall r a b.
UserOfRegs r a =>
DynFlags -> (b -> r -> b) -> b -> a -> b
Evidence bound by a type signature of the constraint type UserOfRegs r CmmReg
foldRegsUsed DynFlags
dflags b -> r -> b
f b
z CmmReg
r
expr b
z (CmmStackSlot Area
_ Int
_) = b
z
instance UserOfRegs r a => UserOfRegs r [a] where
foldRegsUsed :: DynFlags -> (b -> r -> b) -> b -> [a] -> b
foldRegsUsed DynFlags
dflags b -> r -> b
f b
set [a]
as = (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldl' (DynFlags -> (b -> r -> b) -> b -> a -> b
forall r a b.
UserOfRegs r a =>
DynFlags -> (b -> r -> b) -> b -> a -> b
Evidence bound by a type signature of the constraint type UserOfRegs r a
foldRegsUsed DynFlags
dflags b -> r -> b
f) b
set [a]
as
{-# INLINABLE foldRegsUsed #-}
instance DefinerOfRegs r a => DefinerOfRegs r [a] where
foldRegsDefd :: DynFlags -> (b -> r -> b) -> b -> [a] -> b
foldRegsDefd DynFlags
dflags b -> r -> b
f b
set [a]
as = (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldl' (DynFlags -> (b -> r -> b) -> b -> a -> b
forall r a b.
DefinerOfRegs r a =>
DynFlags -> (b -> r -> b) -> b -> a -> b
Evidence bound by a type signature of the constraint type DefinerOfRegs r a
foldRegsDefd DynFlags
dflags b -> r -> b
f) b
set [a]
as
{-# INLINABLE foldRegsDefd #-}
data VGcPtr = VGcPtr | VNonGcPtr deriving( VGcPtr -> VGcPtr -> Bool
(VGcPtr -> VGcPtr -> Bool)
-> (VGcPtr -> VGcPtr -> Bool) -> Eq VGcPtr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VGcPtr -> VGcPtr -> Bool
$c/= :: VGcPtr -> VGcPtr -> Bool
== :: VGcPtr -> VGcPtr -> Bool
$c== :: VGcPtr -> VGcPtr -> Bool
Eq, Int -> VGcPtr -> ShowS
[VGcPtr] -> ShowS
VGcPtr -> String
(Int -> VGcPtr -> ShowS)
-> (VGcPtr -> String) -> ([VGcPtr] -> ShowS) -> Show VGcPtr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VGcPtr] -> ShowS
$cshowList :: [VGcPtr] -> ShowS
show :: VGcPtr -> String
$cshow :: VGcPtr -> String
showsPrec :: Int -> VGcPtr -> ShowS
$cshowsPrec :: Int -> VGcPtr -> ShowS
Show )
data GlobalReg
= VanillaReg
{-# UNPACK #-} !Int
VGcPtr
| FloatReg
{-# UNPACK #-} !Int
| DoubleReg
{-# UNPACK #-} !Int
| LongReg
{-# UNPACK #-} !Int
| XmmReg
{-# UNPACK #-} !Int
| YmmReg
{-# UNPACK #-} !Int
| ZmmReg
{-# UNPACK #-} !Int
| Sp
| SpLim
| Hp
| HpLim
| CCCS
| CurrentTSO
| CurrentNursery
| HpAlloc
| EagerBlackholeInfo
| GCEnter1
| GCFun
| BaseReg
| MachSp
| UnwindReturnReg
| PicBaseReg
deriving( Int -> GlobalReg -> ShowS
[GlobalReg] -> ShowS
GlobalReg -> String
(Int -> GlobalReg -> ShowS)
-> (GlobalReg -> String)
-> ([GlobalReg] -> ShowS)
-> Show GlobalReg
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GlobalReg] -> ShowS
$cshowList :: [GlobalReg] -> ShowS
show :: GlobalReg -> String
$cshow :: GlobalReg -> String
showsPrec :: Int -> GlobalReg -> ShowS
$cshowsPrec :: Int -> GlobalReg -> ShowS
External instance of the constraint type Show Int
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type Show VGcPtr
Show )
instance Eq GlobalReg where
VanillaReg Int
i VGcPtr
_ == :: GlobalReg -> GlobalReg -> Bool
== VanillaReg Int
j VGcPtr
_ = Int
iInt -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
==Int
j
FloatReg Int
i == FloatReg Int
j = Int
iInt -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
==Int
j
DoubleReg Int
i == DoubleReg Int
j = Int
iInt -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
==Int
j
LongReg Int
i == LongReg Int
j = Int
iInt -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
==Int
j
XmmReg Int
i == XmmReg Int
j = Int
iInt -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
==Int
j
YmmReg Int
i == YmmReg Int
j = Int
iInt -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
==Int
j
ZmmReg Int
i == ZmmReg Int
j = Int
iInt -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
==Int
j
GlobalReg
Sp == GlobalReg
Sp = Bool
True
GlobalReg
SpLim == GlobalReg
SpLim = Bool
True
GlobalReg
Hp == GlobalReg
Hp = Bool
True
GlobalReg
HpLim == GlobalReg
HpLim = Bool
True
GlobalReg
CCCS == GlobalReg
CCCS = Bool
True
GlobalReg
CurrentTSO == GlobalReg
CurrentTSO = Bool
True
GlobalReg
CurrentNursery == GlobalReg
CurrentNursery = Bool
True
GlobalReg
HpAlloc == GlobalReg
HpAlloc = Bool
True
GlobalReg
EagerBlackholeInfo == GlobalReg
EagerBlackholeInfo = Bool
True
GlobalReg
GCEnter1 == GlobalReg
GCEnter1 = Bool
True
GlobalReg
GCFun == GlobalReg
GCFun = Bool
True
GlobalReg
BaseReg == GlobalReg
BaseReg = Bool
True
GlobalReg
MachSp == GlobalReg
MachSp = Bool
True
GlobalReg
UnwindReturnReg == GlobalReg
UnwindReturnReg = Bool
True
GlobalReg
PicBaseReg == GlobalReg
PicBaseReg = Bool
True
GlobalReg
_r1 == GlobalReg
_r2 = Bool
False
instance Ord GlobalReg where
compare :: GlobalReg -> GlobalReg -> Ordering
compare (VanillaReg Int
i VGcPtr
_) (VanillaReg Int
j VGcPtr
_) = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
i Int
j
compare (FloatReg Int
i) (FloatReg Int
j) = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
i Int
j
compare (DoubleReg Int
i) (DoubleReg Int
j) = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
i Int
j
compare (LongReg Int
i) (LongReg Int
j) = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
i Int
j
compare (XmmReg Int
i) (XmmReg Int
j) = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
i Int
j
compare (YmmReg Int
i) (YmmReg Int
j) = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
i Int
j
compare (ZmmReg Int
i) (ZmmReg Int
j) = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
i Int
j
compare GlobalReg
Sp GlobalReg
Sp = Ordering
EQ
compare GlobalReg
SpLim GlobalReg
SpLim = Ordering
EQ
compare GlobalReg
Hp GlobalReg
Hp = Ordering
EQ
compare GlobalReg
HpLim GlobalReg
HpLim = Ordering
EQ
compare GlobalReg
CCCS GlobalReg
CCCS = Ordering
EQ
compare GlobalReg
CurrentTSO GlobalReg
CurrentTSO = Ordering
EQ
compare GlobalReg
CurrentNursery GlobalReg
CurrentNursery = Ordering
EQ
compare GlobalReg
HpAlloc GlobalReg
HpAlloc = Ordering
EQ
compare GlobalReg
EagerBlackholeInfo GlobalReg
EagerBlackholeInfo = Ordering
EQ
compare GlobalReg
GCEnter1 GlobalReg
GCEnter1 = Ordering
EQ
compare GlobalReg
GCFun GlobalReg
GCFun = Ordering
EQ
compare GlobalReg
BaseReg GlobalReg
BaseReg = Ordering
EQ
compare GlobalReg
MachSp GlobalReg
MachSp = Ordering
EQ
compare GlobalReg
UnwindReturnReg GlobalReg
UnwindReturnReg = Ordering
EQ
compare GlobalReg
PicBaseReg GlobalReg
PicBaseReg = Ordering
EQ
compare (VanillaReg Int
_ VGcPtr
_) GlobalReg
_ = Ordering
LT
compare GlobalReg
_ (VanillaReg Int
_ VGcPtr
_) = Ordering
GT
compare (FloatReg Int
_) GlobalReg
_ = Ordering
LT
compare GlobalReg
_ (FloatReg Int
_) = Ordering
GT
compare (DoubleReg Int
_) GlobalReg
_ = Ordering
LT
compare GlobalReg
_ (DoubleReg Int
_) = Ordering
GT
compare (LongReg Int
_) GlobalReg
_ = Ordering
LT
compare GlobalReg
_ (LongReg Int
_) = Ordering
GT
compare (XmmReg Int
_) GlobalReg
_ = Ordering
LT
compare GlobalReg
_ (XmmReg Int
_) = Ordering
GT
compare (YmmReg Int
_) GlobalReg
_ = Ordering
LT
compare GlobalReg
_ (YmmReg Int
_) = Ordering
GT
compare (ZmmReg Int
_) GlobalReg
_ = Ordering
LT
compare GlobalReg
_ (ZmmReg Int
_) = Ordering
GT
compare GlobalReg
Sp GlobalReg
_ = Ordering
LT
compare GlobalReg
_ GlobalReg
Sp = Ordering
GT
compare GlobalReg
SpLim GlobalReg
_ = Ordering
LT
compare GlobalReg
_ GlobalReg
SpLim = Ordering
GT
compare GlobalReg
Hp GlobalReg
_ = Ordering
LT
compare GlobalReg
_ GlobalReg
Hp = Ordering
GT
compare GlobalReg
HpLim GlobalReg
_ = Ordering
LT
compare GlobalReg
_ GlobalReg
HpLim = Ordering
GT
compare GlobalReg
CCCS GlobalReg
_ = Ordering
LT
compare GlobalReg
_ GlobalReg
CCCS = Ordering
GT
compare GlobalReg
CurrentTSO GlobalReg
_ = Ordering
LT
compare GlobalReg
_ GlobalReg
CurrentTSO = Ordering
GT
compare GlobalReg
CurrentNursery GlobalReg
_ = Ordering
LT
compare GlobalReg
_ GlobalReg
CurrentNursery = Ordering
GT
compare GlobalReg
HpAlloc GlobalReg
_ = Ordering
LT
compare GlobalReg
_ GlobalReg
HpAlloc = Ordering
GT
compare GlobalReg
GCEnter1 GlobalReg
_ = Ordering
LT
compare GlobalReg
_ GlobalReg
GCEnter1 = Ordering
GT
compare GlobalReg
GCFun GlobalReg
_ = Ordering
LT
compare GlobalReg
_ GlobalReg
GCFun = Ordering
GT
compare GlobalReg
BaseReg GlobalReg
_ = Ordering
LT
compare GlobalReg
_ GlobalReg
BaseReg = Ordering
GT
compare GlobalReg
MachSp GlobalReg
_ = Ordering
LT
compare GlobalReg
_ GlobalReg
MachSp = Ordering
GT
compare GlobalReg
UnwindReturnReg GlobalReg
_ = Ordering
LT
compare GlobalReg
_ GlobalReg
UnwindReturnReg = Ordering
GT
compare GlobalReg
EagerBlackholeInfo GlobalReg
_ = Ordering
LT
compare GlobalReg
_ GlobalReg
EagerBlackholeInfo = Ordering
GT
baseReg, spReg, hpReg, spLimReg, hpLimReg, nodeReg,
currentTSOReg, currentNurseryReg, hpAllocReg, cccsReg :: CmmReg
baseReg :: CmmReg
baseReg = GlobalReg -> CmmReg
CmmGlobal GlobalReg
BaseReg
spReg :: CmmReg
spReg = GlobalReg -> CmmReg
CmmGlobal GlobalReg
Sp
hpReg :: CmmReg
hpReg = GlobalReg -> CmmReg
CmmGlobal GlobalReg
Hp
hpLimReg :: CmmReg
hpLimReg = GlobalReg -> CmmReg
CmmGlobal GlobalReg
HpLim
spLimReg :: CmmReg
spLimReg = GlobalReg -> CmmReg
CmmGlobal GlobalReg
SpLim
nodeReg :: CmmReg
nodeReg = GlobalReg -> CmmReg
CmmGlobal GlobalReg
node
currentTSOReg :: CmmReg
currentTSOReg = GlobalReg -> CmmReg
CmmGlobal GlobalReg
CurrentTSO
currentNurseryReg :: CmmReg
currentNurseryReg = GlobalReg -> CmmReg
CmmGlobal GlobalReg
CurrentNursery
hpAllocReg :: CmmReg
hpAllocReg = GlobalReg -> CmmReg
CmmGlobal GlobalReg
HpAlloc
cccsReg :: CmmReg
cccsReg = GlobalReg -> CmmReg
CmmGlobal GlobalReg
CCCS
node :: GlobalReg
node :: GlobalReg
node = Int -> VGcPtr -> GlobalReg
VanillaReg Int
1 VGcPtr
VGcPtr
globalRegType :: Platform -> GlobalReg -> CmmType
globalRegType :: Platform -> GlobalReg -> CmmType
globalRegType Platform
platform = \case
(VanillaReg Int
_ VGcPtr
VGcPtr) -> Platform -> CmmType
gcWord Platform
platform
(VanillaReg Int
_ VGcPtr
VNonGcPtr) -> Platform -> CmmType
bWord Platform
platform
(FloatReg Int
_) -> Width -> CmmType
cmmFloat Width
W32
(DoubleReg Int
_) -> Width -> CmmType
cmmFloat Width
W64
(LongReg Int
_) -> Width -> CmmType
cmmBits Width
W64
(XmmReg Int
_) -> Int -> CmmType -> CmmType
cmmVec Int
4 (Width -> CmmType
cmmBits Width
W32)
(YmmReg Int
_) -> Int -> CmmType -> CmmType
cmmVec Int
8 (Width -> CmmType
cmmBits Width
W32)
(ZmmReg Int
_) -> Int -> CmmType -> CmmType
cmmVec Int
16 (Width -> CmmType
cmmBits Width
W32)
GlobalReg
Hp -> Platform -> CmmType
gcWord Platform
platform
GlobalReg
_ -> Platform -> CmmType
bWord Platform
platform
isArgReg :: GlobalReg -> Bool
isArgReg :: GlobalReg -> Bool
isArgReg (VanillaReg {}) = Bool
True
isArgReg (FloatReg {}) = Bool
True
isArgReg (DoubleReg {}) = Bool
True
isArgReg (LongReg {}) = Bool
True
isArgReg (XmmReg {}) = Bool
True
isArgReg (YmmReg {}) = Bool
True
isArgReg (ZmmReg {}) = Bool
True
isArgReg GlobalReg
_ = Bool
False