ghc-lib-parser-9.4.4.20221225: The GHC API, decoupled from GHC versions
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Cmm.Expr

Synopsis

Documentation

data CmmExpr Source #

Instances

Instances details
Show CmmExpr Source # 
Instance details

Defined in GHC.Cmm.Expr

Eq CmmExpr Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

(==) :: CmmExpr -> CmmExpr -> Bool #

(/=) :: CmmExpr -> CmmExpr -> Bool #

(Ord r, UserOfRegs r CmmReg) => UserOfRegs r CmmExpr Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> r -> b) -> b -> CmmExpr -> b Source #

cmmExprAlignment :: CmmExpr -> Alignment Source #

Returns an alignment in bytes of a CmmExpr when it's a statically known integer constant, otherwise returns an alignment of 1 byte. The caller is responsible for using with a sensible CmmExpr argument.

data CmmReg Source #

Instances

Instances details
Show CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Eq CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

(==) :: CmmReg -> CmmReg -> Bool #

(/=) :: CmmReg -> CmmReg -> Bool #

Ord CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

DefinerOfRegs GlobalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> GlobalReg -> b) -> b -> CmmReg -> b Source #

DefinerOfRegs LocalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> LocalReg -> b) -> b -> CmmReg -> b Source #

UserOfRegs GlobalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> GlobalReg -> b) -> b -> CmmReg -> b Source #

UserOfRegs LocalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> LocalReg -> b) -> b -> CmmReg -> b Source #

data CmmLit Source #

Instances

Instances details
Show CmmLit Source # 
Instance details

Defined in GHC.Cmm.Expr

Outputable CmmLit Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

ppr :: CmmLit -> SDoc Source #

Eq CmmLit Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

(==) :: CmmLit -> CmmLit -> Bool #

(/=) :: CmmLit -> CmmLit -> Bool #

data LocalReg Source #

Constructors

LocalReg !Unique !CmmType

Parameters: 1. Identifier 2. Type

Instances

Instances details
Show LocalReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Uniquable LocalReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Eq LocalReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Ord LocalReg Source # 
Instance details

Defined in GHC.Cmm.Expr

DefinerOfRegs LocalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> LocalReg -> b) -> b -> CmmReg -> b Source #

UserOfRegs LocalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> LocalReg -> b) -> b -> CmmReg -> b Source #

DefinerOfRegs LocalReg (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsDefd :: Platform -> (b -> LocalReg -> b) -> b -> CmmNode e x -> b Source #

UserOfRegs LocalReg (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsUsed :: Platform -> (b -> LocalReg -> b) -> b -> CmmNode e x -> b Source #

data GlobalReg Source #

Instances

Instances details
Show GlobalReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Eq GlobalReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Ord GlobalReg Source # 
Instance details

Defined in GHC.Cmm.Expr

DefinerOfRegs GlobalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> GlobalReg -> b) -> b -> CmmReg -> b Source #

UserOfRegs GlobalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> GlobalReg -> b) -> b -> CmmReg -> b Source #

DefinerOfRegs GlobalReg (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsDefd :: Platform -> (b -> GlobalReg -> b) -> b -> CmmNode e x -> b Source #

UserOfRegs GlobalReg (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsUsed :: Platform -> (b -> GlobalReg -> b) -> b -> CmmNode e x -> b Source #

data VGcPtr Source #

Constructors

VGcPtr 
VNonGcPtr 

Instances

Instances details
Show VGcPtr Source # 
Instance details

Defined in GHC.Cmm.Expr

Eq VGcPtr Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

(==) :: VGcPtr -> VGcPtr -> Bool #

(/=) :: VGcPtr -> VGcPtr -> Bool #

class Ord r => DefinerOfRegs r a Source #

Minimal complete definition

foldRegsDefd

Instances

Instances details
DefinerOfRegs GlobalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> GlobalReg -> b) -> b -> CmmReg -> b Source #

DefinerOfRegs LocalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> LocalReg -> b) -> b -> CmmReg -> b Source #

Ord r => DefinerOfRegs r r Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> r -> b) -> b -> r -> b Source #

DefinerOfRegs r a => DefinerOfRegs r [a] Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsDefd :: Platform -> (b -> r -> b) -> b -> [a] -> b Source #

DefinerOfRegs GlobalReg (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsDefd :: Platform -> (b -> GlobalReg -> b) -> b -> CmmNode e x -> b Source #

DefinerOfRegs LocalReg (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsDefd :: Platform -> (b -> LocalReg -> b) -> b -> CmmNode e x -> b Source #

class Ord r => UserOfRegs r a Source #

Minimal complete definition

foldRegsUsed

Instances

Instances details
UserOfRegs GlobalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> GlobalReg -> b) -> b -> CmmReg -> b Source #

UserOfRegs LocalReg CmmReg Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> LocalReg -> b) -> b -> CmmReg -> b Source #

(Ord r, UserOfRegs r CmmReg) => UserOfRegs r CmmExpr Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> r -> b) -> b -> CmmExpr -> b Source #

(Ord r, UserOfRegs r CmmReg) => UserOfRegs r ForeignTarget Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsUsed :: Platform -> (b -> r -> b) -> b -> ForeignTarget -> b Source #

Ord r => UserOfRegs r r Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> r -> b) -> b -> r -> b Source #

UserOfRegs r a => UserOfRegs r [a] Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

foldRegsUsed :: Platform -> (b -> r -> b) -> b -> [a] -> b Source #

UserOfRegs GlobalReg (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsUsed :: Platform -> (b -> GlobalReg -> b) -> b -> CmmNode e x -> b Source #

UserOfRegs LocalReg (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

Methods

foldRegsUsed :: Platform -> (b -> LocalReg -> b) -> b -> CmmNode e x -> b Source #

foldRegsDefd :: DefinerOfRegs r a => Platform -> (b -> r -> b) -> b -> a -> b Source #

foldRegsUsed :: UserOfRegs r a => Platform -> (b -> r -> b) -> b -> a -> b Source #

foldLocalRegsDefd :: DefinerOfRegs LocalReg a => Platform -> (b -> LocalReg -> b) -> b -> a -> b Source #

foldLocalRegsUsed :: UserOfRegs LocalReg a => Platform -> (b -> LocalReg -> b) -> b -> a -> b Source #

type RegSet r = Set r Source #

Sets of registers

elemRegSet :: Ord r => r -> RegSet r -> Bool Source #

extendRegSet :: Ord r => RegSet r -> r -> RegSet r Source #

mkRegSet :: Ord r => [r] -> RegSet r Source #

plusRegSet :: Ord r => RegSet r -> RegSet r -> RegSet r Source #

minusRegSet :: Ord r => RegSet r -> RegSet r -> RegSet r Source #

timesRegSet :: Ord r => RegSet r -> RegSet r -> RegSet r Source #

data Area Source #

A stack area is either the stack slot where a variable is spilled or the stack space where function arguments and results are passed.

Constructors

Old 
Young !BlockId 

Instances

Instances details
Show Area Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

showsPrec :: Int -> Area -> ShowS #

show :: Area -> String #

showList :: [Area] -> ShowS #

Eq Area Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

(==) :: Area -> Area -> Bool #

(/=) :: Area -> Area -> Bool #

Ord Area Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

compare :: Area -> Area -> Ordering #

(<) :: Area -> Area -> Bool #

(<=) :: Area -> Area -> Bool #

(>) :: Area -> Area -> Bool #

(>=) :: Area -> Area -> Bool #

max :: Area -> Area -> Area #

min :: Area -> Area -> Area #