{-# OPTIONS_GHC -Wno-unused-imports #-}
{-# OPTIONS_HADDOCK hide, prune, not-home #-}
module MLIR.AST.Dialect.Generated.LLVM where
import Prelude (Int, Double, Maybe(..), Bool(..), (++), (<$>), ($), (<>), Show)
import qualified Prelude
import Data.Int (Int64)
import qualified Data.Maybe
import Data.Array (Ix)
import qualified Data.Array.IArray as IArray
import qualified Data.ByteString as BS
import qualified Data.Map.Strict as M
import qualified Control.Monad
import MLIR.AST ( Attribute(..), Type(..), AbstractOperation(..), ResultTypes(..)
, Location(..), Signedness(..), DenseElements(..)
, NamedAttributes, Name
, pattern NoAttrs )
import qualified MLIR.AST as AST
import MLIR.AST.Builder (Value, EndOfBlock, MonadBlockBuilder, RegionBuilderT)
import qualified MLIR.AST.Builder as AST
import qualified MLIR.AST.IStorableArray as AST
import qualified MLIR.AST.PatternUtil as PatternUtil
import qualified MLIR.AST.Dialect.Affine as Affine
pattern AShr :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bAShr :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mAShr :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
AShr loc ty lhs_ rhs_ = Operation
{ opName = "llvm.ashr"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
ashr :: () => MonadBlockBuilder m => Value -> Value -> m Value
ashr :: Value -> Value -> m Value
ashr Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.ashr"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Add :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bAdd :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mAdd :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
Add loc ty lhs_ rhs_ = Operation
{ opName = "llvm.add"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
add :: () => MonadBlockBuilder m => Value -> Value -> m Value
add :: Value -> Value -> m Value
add Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.add"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern AddrSpaceCast :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bAddrSpaceCast :: Location -> Type -> operand -> AbstractOperation operand
$mAddrSpaceCast :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
AddrSpaceCast loc ty0 arg_ = Operation
{ opName = "llvm.addrspacecast"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
addrspacecast :: () => MonadBlockBuilder m => Type -> Value -> m Value
addrspacecast :: Type -> Value -> m Value
addrspacecast Type
ty0 Value
arg_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.addrspacecast"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
arg_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern And :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bAnd :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mAnd :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
And loc ty lhs_ rhs_ = Operation
{ opName = "llvm.and"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
and :: () => MonadBlockBuilder m => Value -> Value -> m Value
and :: Value -> Value -> m Value
and Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.and"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Bitcast :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bBitcast :: Location -> Type -> operand -> AbstractOperation operand
$mBitcast :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
Bitcast loc ty0 arg_ = Operation
{ opName = "llvm.bitcast"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
bitcast :: () => MonadBlockBuilder m => Type -> Value -> m Value
bitcast :: Type -> Value -> m Value
bitcast Type
ty0 Value
arg_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.bitcast"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
arg_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern OptionalArrayAttr :: Maybe [Attribute] -> Maybe Attribute
pattern $bOptionalArrayAttr :: Maybe [Attribute] -> Maybe Attribute
$mOptionalArrayAttr :: forall r.
Maybe Attribute -> (Maybe [Attribute] -> r) -> (Void# -> r) -> r
OptionalArrayAttr x <- ((\case Just (ArrayAttr y) -> Just y; Nothing -> Nothing) -> x)
where OptionalArrayAttr Maybe [Attribute]
x = case Maybe [Attribute]
x of Just [Attribute]
y -> Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just ([Attribute] -> Attribute
ArrayAttr [Attribute]
y); Maybe [Attribute]
Nothing -> Maybe Attribute
forall a. Maybe a
Nothing
pattern InternalCallIntrinsicOpAttributes :: () => () => BS.ByteString -> [Int] -> Maybe [Attribute] -> NamedAttributes
pattern $bInternalCallIntrinsicOpAttributes :: Name -> [Int] -> Maybe [Attribute] -> Map Name Attribute
$mInternalCallIntrinsicOpAttributes :: forall r.
Map Name Attribute
-> (Name -> [Int] -> Maybe [Attribute] -> r) -> (Void# -> r) -> r
InternalCallIntrinsicOpAttributes intrin_ op_bundle_sizes_ op_bundle_tags_ <- ((\m -> (M.lookup "intrin" m, M.lookup "op_bundle_sizes" m, M.lookup "op_bundle_tags" m)) -> (Just (StringAttr intrin_), Just (PatternUtil.I32ArrayAttr op_bundle_sizes_), OptionalArrayAttr op_bundle_tags_))
where InternalCallIntrinsicOpAttributes Name
intrin_ [Int]
op_bundle_sizes_ Maybe [Attribute]
op_bundle_tags_ = [(Name, Attribute)] -> Map Name Attribute
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Name, Attribute)] -> Map Name Attribute)
-> [(Name, Attribute)] -> Map Name Attribute
forall a b. (a -> b) -> a -> b
$ [(Name
"intrin", Name -> Attribute
StringAttr Name
intrin_)] [(Name, Attribute)] -> [(Name, Attribute)] -> [(Name, Attribute)]
forall a. [a] -> [a] -> [a]
++ [(Name
"op_bundle_sizes", [Int] -> Attribute
PatternUtil.I32ArrayAttr [Int]
op_bundle_sizes_)] [(Name, Attribute)] -> [(Name, Attribute)] -> [(Name, Attribute)]
forall a. [a] -> [a] -> [a]
++ (Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Maybe (Name, Attribute) -> [(Name, Attribute)])
-> Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a b. (a -> b) -> a -> b
$ (Name
"op_bundle_tags",) (Attribute -> (Name, Attribute))
-> Maybe Attribute -> Maybe (Name, Attribute)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Attribute] -> Maybe Attribute
OptionalArrayAttr Maybe [Attribute]
op_bundle_tags_)
call_intrinsic :: () => MonadBlockBuilder m => Maybe Type -> [Value] -> [Value] -> BS.ByteString -> [Int] -> Maybe [Attribute] -> m Value
call_intrinsic :: Maybe Type
-> [Value]
-> [Value]
-> Name
-> [Int]
-> Maybe [Attribute]
-> m Value
call_intrinsic Maybe Type
ty0 [Value]
args_ [Value]
op_bundle_operands_ Name
intrin_ [Int]
op_bundle_sizes_ Maybe [Attribute]
op_bundle_tags_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.call_intrinsic"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit ((Maybe Type -> [Type]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList Maybe Type
ty0))
, opOperands :: [Name]
opOperands = (([Value] -> [Name]
AST.operands [Value]
args_) [Name] -> [Name] -> [Name]
forall a. [a] -> [a] -> [a]
++ ([Value] -> [Name]
AST.operands [Value]
op_bundle_operands_))
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Name -> [Int] -> Maybe [Attribute] -> Map Name Attribute
InternalCallIntrinsicOpAttributes Name
intrin_ [Int]
op_bundle_sizes_ Maybe [Attribute]
op_bundle_tags_)
Map Name Attribute -> Map Name Attribute -> Map Name Attribute
forall a. Semigroup a => a -> a -> a
<> Name -> Attribute -> Map Name Attribute
AST.namedAttribute Name
"operand_segment_sizes"
(Type -> DenseElements -> Attribute
DenseElementsAttr ([Int] -> Type -> Type
VectorType [Int
2] (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Signedness -> UInt -> Type
IntegerType Signedness
Unsigned UInt
32) (DenseElements -> Attribute) -> DenseElements -> Attribute
forall a b. (a -> b) -> a -> b
$
IStorableArray Int Word32 -> DenseElements
forall i.
(Show i, Ix i) =>
IStorableArray i Word32 -> DenseElements
DenseUInt32 (IStorableArray Int Word32 -> DenseElements)
-> IStorableArray Int Word32 -> DenseElements
forall a b. (a -> b) -> a -> b
$ (Int, Int) -> [Word32] -> IStorableArray Int Word32
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [e] -> a i e
IArray.listArray (Int
1 :: Int, Int
2) ([Word32] -> IStorableArray Int Word32)
-> [Word32] -> IStorableArray Int Word32
forall a b. (a -> b) -> a -> b
$ Int -> Word32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (Int -> Word32) -> [Int] -> [Word32]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[Name] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
Prelude.length ([Value] -> [Name]
AST.operands [Value]
args_), [Name] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
Prelude.length ([Value] -> [Name]
AST.operands [Value]
op_bundle_operands_)])
}))
pattern OptionalDenseI32ArrayAttr :: Maybe [Int] -> Maybe Attribute
pattern $bOptionalDenseI32ArrayAttr :: Maybe [Int] -> Maybe Attribute
$mOptionalDenseI32ArrayAttr :: forall r.
Maybe Attribute -> (Maybe [Int] -> r) -> (Void# -> r) -> r
OptionalDenseI32ArrayAttr x <- ((\case Just (PatternUtil.I32ArrayAttr y) -> Just y; Nothing -> Nothing) -> x)
where OptionalDenseI32ArrayAttr Maybe [Int]
x = case Maybe [Int]
x of Just [Int]
y -> Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just ([Int] -> Attribute
PatternUtil.I32ArrayAttr [Int]
y); Maybe [Int]
Nothing -> Maybe Attribute
forall a. Maybe a
Nothing
pattern InternalCallOpAttributes :: () => () => Maybe [Int] -> [Int] -> Maybe [Attribute] -> NamedAttributes
pattern $bInternalCallOpAttributes :: Maybe [Int] -> [Int] -> Maybe [Attribute] -> Map Name Attribute
$mInternalCallOpAttributes :: forall r.
Map Name Attribute
-> (Maybe [Int] -> [Int] -> Maybe [Attribute] -> r)
-> (Void# -> r)
-> r
InternalCallOpAttributes branch_weights_ op_bundle_sizes_ op_bundle_tags_ <- ((\m -> (M.lookup "branch_weights" m, M.lookup "op_bundle_sizes" m, M.lookup "op_bundle_tags" m)) -> (OptionalDenseI32ArrayAttr branch_weights_, Just (PatternUtil.I32ArrayAttr op_bundle_sizes_), OptionalArrayAttr op_bundle_tags_))
where InternalCallOpAttributes Maybe [Int]
branch_weights_ [Int]
op_bundle_sizes_ Maybe [Attribute]
op_bundle_tags_ = [(Name, Attribute)] -> Map Name Attribute
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Name, Attribute)] -> Map Name Attribute)
-> [(Name, Attribute)] -> Map Name Attribute
forall a b. (a -> b) -> a -> b
$ (Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Maybe (Name, Attribute) -> [(Name, Attribute)])
-> Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a b. (a -> b) -> a -> b
$ (Name
"branch_weights",) (Attribute -> (Name, Attribute))
-> Maybe Attribute -> Maybe (Name, Attribute)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Int] -> Maybe Attribute
OptionalDenseI32ArrayAttr Maybe [Int]
branch_weights_) [(Name, Attribute)] -> [(Name, Attribute)] -> [(Name, Attribute)]
forall a. [a] -> [a] -> [a]
++ [(Name
"op_bundle_sizes", [Int] -> Attribute
PatternUtil.I32ArrayAttr [Int]
op_bundle_sizes_)] [(Name, Attribute)] -> [(Name, Attribute)] -> [(Name, Attribute)]
forall a. [a] -> [a] -> [a]
++ (Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Maybe (Name, Attribute) -> [(Name, Attribute)])
-> Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a b. (a -> b) -> a -> b
$ (Name
"op_bundle_tags",) (Attribute -> (Name, Attribute))
-> Maybe Attribute -> Maybe (Name, Attribute)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Attribute] -> Maybe Attribute
OptionalArrayAttr Maybe [Attribute]
op_bundle_tags_)
call :: () => MonadBlockBuilder m => Maybe Type -> [Value] -> [Value] -> Maybe [Int] -> [Int] -> Maybe [Attribute] -> m Value
call :: Maybe Type
-> [Value]
-> [Value]
-> Maybe [Int]
-> [Int]
-> Maybe [Attribute]
-> m Value
call Maybe Type
ty0 [Value]
callee_operands_ [Value]
op_bundle_operands_ Maybe [Int]
branch_weights_ [Int]
op_bundle_sizes_ Maybe [Attribute]
op_bundle_tags_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.call"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit ((Maybe Type -> [Type]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList Maybe Type
ty0))
, opOperands :: [Name]
opOperands = (([Value] -> [Name]
AST.operands [Value]
callee_operands_) [Name] -> [Name] -> [Name]
forall a. [a] -> [a] -> [a]
++ ([Value] -> [Name]
AST.operands [Value]
op_bundle_operands_))
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Maybe [Int] -> [Int] -> Maybe [Attribute] -> Map Name Attribute
InternalCallOpAttributes Maybe [Int]
branch_weights_ [Int]
op_bundle_sizes_ Maybe [Attribute]
op_bundle_tags_)
Map Name Attribute -> Map Name Attribute -> Map Name Attribute
forall a. Semigroup a => a -> a -> a
<> Name -> Attribute -> Map Name Attribute
AST.namedAttribute Name
"operand_segment_sizes"
(Type -> DenseElements -> Attribute
DenseElementsAttr ([Int] -> Type -> Type
VectorType [Int
2] (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Signedness -> UInt -> Type
IntegerType Signedness
Unsigned UInt
32) (DenseElements -> Attribute) -> DenseElements -> Attribute
forall a b. (a -> b) -> a -> b
$
IStorableArray Int Word32 -> DenseElements
forall i.
(Show i, Ix i) =>
IStorableArray i Word32 -> DenseElements
DenseUInt32 (IStorableArray Int Word32 -> DenseElements)
-> IStorableArray Int Word32 -> DenseElements
forall a b. (a -> b) -> a -> b
$ (Int, Int) -> [Word32] -> IStorableArray Int Word32
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [e] -> a i e
IArray.listArray (Int
1 :: Int, Int
2) ([Word32] -> IStorableArray Int Word32)
-> [Word32] -> IStorableArray Int Word32
forall a b. (a -> b) -> a -> b
$ Int -> Word32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (Int -> Word32) -> [Int] -> [Word32]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[Name] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
Prelude.length ([Value] -> [Name]
AST.operands [Value]
callee_operands_), [Name] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
Prelude.length ([Value] -> [Name]
AST.operands [Value]
op_bundle_operands_)])
}))
pattern InternalCondBrOpAttributes :: () => () => Maybe [Int] -> NamedAttributes
pattern $bInternalCondBrOpAttributes :: Maybe [Int] -> Map Name Attribute
$mInternalCondBrOpAttributes :: forall r.
Map Name Attribute -> (Maybe [Int] -> r) -> (Void# -> r) -> r
InternalCondBrOpAttributes branch_weights_ <- ((\m -> (M.lookup "branch_weights" m)) -> (OptionalDenseI32ArrayAttr branch_weights_))
where InternalCondBrOpAttributes Maybe [Int]
branch_weights_ = [(Name, Attribute)] -> Map Name Attribute
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Name, Attribute)] -> Map Name Attribute)
-> [(Name, Attribute)] -> Map Name Attribute
forall a b. (a -> b) -> a -> b
$ (Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Maybe (Name, Attribute) -> [(Name, Attribute)])
-> Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a b. (a -> b) -> a -> b
$ (Name
"branch_weights",) (Attribute -> (Name, Attribute))
-> Maybe Attribute -> Maybe (Name, Attribute)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Int] -> Maybe Attribute
OptionalDenseI32ArrayAttr Maybe [Int]
branch_weights_)
pattern InternalConstantOpAttributes :: () => () => Attribute -> NamedAttributes
pattern $bInternalConstantOpAttributes :: Attribute -> Map Name Attribute
$mInternalConstantOpAttributes :: forall r.
Map Name Attribute -> (Attribute -> r) -> (Void# -> r) -> r
InternalConstantOpAttributes value_ <- ((\m -> (M.lookup "value" m)) -> (Just (value_)))
where InternalConstantOpAttributes Attribute
value_ = [(Name, Attribute)] -> Map Name Attribute
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Name, Attribute)] -> Map Name Attribute)
-> [(Name, Attribute)] -> Map Name Attribute
forall a b. (a -> b) -> a -> b
$ [(Name
"value", Attribute
value_)]
pattern Constant :: () => () => Location -> Type -> Attribute -> AbstractOperation operand
pattern $bConstant :: Location -> Type -> Attribute -> AbstractOperation operand
$mConstant :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> Attribute -> r) -> (Void# -> r) -> r
Constant loc ty0 value_ = Operation
{ opName = "llvm.mlir.constant"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = []
, opRegions = []
, opSuccessors = []
, opAttributes = (InternalConstantOpAttributes value_)
}
mlir_constant :: () => MonadBlockBuilder m => Type -> Attribute -> m Value
mlir_constant :: Type -> Attribute -> m Value
mlir_constant Type
ty0 Attribute
value_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.mlir.constant"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = []
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Attribute -> Map Name Attribute
InternalConstantOpAttributes Attribute
value_)
}))
pattern ExtractElement :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern loc ty0 vector_ position_ = Operation
{ opName = "llvm.extractelement"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [vector_, position_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
extractelement :: () => MonadBlockBuilder m => Type -> Value -> Value -> m Value
Type
ty0 Value
vector_ Value
position_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.extractelement"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
vector_), (Value -> Name
AST.operand Value
position_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern FAdd :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bFAdd :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mFAdd :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
FAdd loc ty lhs_ rhs_ = Operation
{ opName = "llvm.fadd"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
fadd :: () => MonadBlockBuilder m => Value -> Value -> m Value
fadd :: Value -> Value -> m Value
fadd Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.fadd"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern FDiv :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bFDiv :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mFDiv :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
FDiv loc ty lhs_ rhs_ = Operation
{ opName = "llvm.fdiv"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
fdiv :: () => MonadBlockBuilder m => Value -> Value -> m Value
fdiv :: Value -> Value -> m Value
fdiv Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.fdiv"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern FMul :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bFMul :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mFMul :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
FMul loc ty lhs_ rhs_ = Operation
{ opName = "llvm.fmul"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
fmul :: () => MonadBlockBuilder m => Value -> Value -> m Value
fmul :: Value -> Value -> m Value
fmul Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.fmul"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern FNeg :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bFNeg :: Location -> Type -> operand -> AbstractOperation operand
$mFNeg :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
FNeg loc ty operand_ = Operation
{ opName = "llvm.fneg"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [operand_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
fneg :: () => MonadBlockBuilder m => Value -> m Value
fneg :: Value -> m Value
fneg Value
operand_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.fneg"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
operand_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
operand_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern FPExt :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bFPExt :: Location -> Type -> operand -> AbstractOperation operand
$mFPExt :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
FPExt loc ty0 arg_ = Operation
{ opName = "llvm.fpext"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
fpext :: () => MonadBlockBuilder m => Type -> Value -> m Value
fpext :: Type -> Value -> m Value
fpext Type
ty0 Value
arg_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.fpext"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
arg_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern FPToSI :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bFPToSI :: Location -> Type -> operand -> AbstractOperation operand
$mFPToSI :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
FPToSI loc ty0 arg_ = Operation
{ opName = "llvm.fptosi"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
fptosi :: () => MonadBlockBuilder m => Type -> Value -> m Value
fptosi :: Type -> Value -> m Value
fptosi Type
ty0 Value
arg_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.fptosi"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
arg_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern FPToUI :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bFPToUI :: Location -> Type -> operand -> AbstractOperation operand
$mFPToUI :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
FPToUI loc ty0 arg_ = Operation
{ opName = "llvm.fptoui"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
fptoui :: () => MonadBlockBuilder m => Type -> Value -> m Value
fptoui :: Type -> Value -> m Value
fptoui Type
ty0 Value
arg_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.fptoui"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
arg_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern FPTrunc :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bFPTrunc :: Location -> Type -> operand -> AbstractOperation operand
$mFPTrunc :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
FPTrunc loc ty0 arg_ = Operation
{ opName = "llvm.fptrunc"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
fptrunc :: () => MonadBlockBuilder m => Type -> Value -> m Value
fptrunc :: Type -> Value -> m Value
fptrunc Type
ty0 Value
arg_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.fptrunc"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
arg_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern FRem :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bFRem :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mFRem :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
FRem loc ty lhs_ rhs_ = Operation
{ opName = "llvm.frem"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
frem :: () => MonadBlockBuilder m => Value -> Value -> m Value
frem :: Value -> Value -> m Value
frem Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.frem"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern FSub :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bFSub :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mFSub :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
FSub loc ty lhs_ rhs_ = Operation
{ opName = "llvm.fsub"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
fsub :: () => MonadBlockBuilder m => Value -> Value -> m Value
fsub :: Value -> Value -> m Value
fsub Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.fsub"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Freeze :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bFreeze :: Location -> Type -> operand -> AbstractOperation operand
$mFreeze :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
Freeze loc ty val_ = Operation
{ opName = "llvm.freeze"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [val_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
freeze :: () => MonadBlockBuilder m => Value -> m Value
freeze :: Value -> m Value
freeze Value
val_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.freeze"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
val_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
val_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern InternalInlineAsmOpAttributes :: () => () => BS.ByteString -> BS.ByteString -> Maybe [Attribute] -> NamedAttributes
pattern $bInternalInlineAsmOpAttributes :: Name -> Name -> Maybe [Attribute] -> Map Name Attribute
$mInternalInlineAsmOpAttributes :: forall r.
Map Name Attribute
-> (Name -> Name -> Maybe [Attribute] -> r) -> (Void# -> r) -> r
InternalInlineAsmOpAttributes asm_string_ constraints_ operand_attrs_ <- ((\m -> (M.lookup "asm_string" m, M.lookup "constraints" m, M.lookup "operand_attrs" m)) -> (Just (StringAttr asm_string_), Just (StringAttr constraints_), OptionalArrayAttr operand_attrs_))
where InternalInlineAsmOpAttributes Name
asm_string_ Name
constraints_ Maybe [Attribute]
operand_attrs_ = [(Name, Attribute)] -> Map Name Attribute
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Name, Attribute)] -> Map Name Attribute)
-> [(Name, Attribute)] -> Map Name Attribute
forall a b. (a -> b) -> a -> b
$ [(Name
"asm_string", Name -> Attribute
StringAttr Name
asm_string_)] [(Name, Attribute)] -> [(Name, Attribute)] -> [(Name, Attribute)]
forall a. [a] -> [a] -> [a]
++ [(Name
"constraints", Name -> Attribute
StringAttr Name
constraints_)] [(Name, Attribute)] -> [(Name, Attribute)] -> [(Name, Attribute)]
forall a. [a] -> [a] -> [a]
++ (Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Maybe (Name, Attribute) -> [(Name, Attribute)])
-> Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a b. (a -> b) -> a -> b
$ (Name
"operand_attrs",) (Attribute -> (Name, Attribute))
-> Maybe Attribute -> Maybe (Name, Attribute)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Attribute] -> Maybe Attribute
OptionalArrayAttr Maybe [Attribute]
operand_attrs_)
inline_asm :: () => MonadBlockBuilder m => Maybe Type -> [Value] -> BS.ByteString -> BS.ByteString -> Maybe [Attribute] -> m Value
inline_asm :: Maybe Type
-> [Value] -> Name -> Name -> Maybe [Attribute] -> m Value
inline_asm Maybe Type
ty0 [Value]
operands_ Name
asm_string_ Name
constraints_ Maybe [Attribute]
operand_attrs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.inline_asm"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit ((Maybe Type -> [Type]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList Maybe Type
ty0))
, opOperands :: [Name]
opOperands = ([Value] -> [Name]
AST.operands [Value]
operands_)
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Name -> Name -> Maybe [Attribute] -> Map Name Attribute
InternalInlineAsmOpAttributes Name
asm_string_ Name
constraints_ Maybe [Attribute]
operand_attrs_)
}))
pattern InsertElement :: () => () => Location -> Type -> operand -> operand -> operand -> AbstractOperation operand
pattern $bInsertElement :: Location
-> Type
-> operand
-> operand
-> operand
-> AbstractOperation operand
$mInsertElement :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> operand -> r)
-> (Void# -> r)
-> r
InsertElement loc ty0 vector_ value_ position_ = Operation
{ opName = "llvm.insertelement"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [vector_, value_, position_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
insertelement :: () => MonadBlockBuilder m => Type -> Value -> Value -> Value -> m Value
insertelement :: Type -> Value -> Value -> Value -> m Value
insertelement Type
ty0 Value
vector_ Value
value_ Value
position_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.insertelement"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
vector_), (Value -> Name
AST.operand Value
value_), (Value -> Name
AST.operand Value
position_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern IntToPtr :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bIntToPtr :: Location -> Type -> operand -> AbstractOperation operand
$mIntToPtr :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
IntToPtr loc ty0 arg_ = Operation
{ opName = "llvm.inttoptr"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
inttoptr :: () => MonadBlockBuilder m => Type -> Value -> m Value
inttoptr :: Type -> Value -> m Value
inttoptr Type
ty0 Value
arg_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.inttoptr"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
arg_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern InternalInvokeOpAttributes :: () => () => Maybe [Int] -> [Int] -> Maybe [Attribute] -> NamedAttributes
pattern $bInternalInvokeOpAttributes :: Maybe [Int] -> [Int] -> Maybe [Attribute] -> Map Name Attribute
$mInternalInvokeOpAttributes :: forall r.
Map Name Attribute
-> (Maybe [Int] -> [Int] -> Maybe [Attribute] -> r)
-> (Void# -> r)
-> r
InternalInvokeOpAttributes branch_weights_ op_bundle_sizes_ op_bundle_tags_ <- ((\m -> (M.lookup "branch_weights" m, M.lookup "op_bundle_sizes" m, M.lookup "op_bundle_tags" m)) -> (OptionalDenseI32ArrayAttr branch_weights_, Just (PatternUtil.I32ArrayAttr op_bundle_sizes_), OptionalArrayAttr op_bundle_tags_))
where InternalInvokeOpAttributes Maybe [Int]
branch_weights_ [Int]
op_bundle_sizes_ Maybe [Attribute]
op_bundle_tags_ = [(Name, Attribute)] -> Map Name Attribute
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Name, Attribute)] -> Map Name Attribute)
-> [(Name, Attribute)] -> Map Name Attribute
forall a b. (a -> b) -> a -> b
$ (Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Maybe (Name, Attribute) -> [(Name, Attribute)])
-> Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a b. (a -> b) -> a -> b
$ (Name
"branch_weights",) (Attribute -> (Name, Attribute))
-> Maybe Attribute -> Maybe (Name, Attribute)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Int] -> Maybe Attribute
OptionalDenseI32ArrayAttr Maybe [Int]
branch_weights_) [(Name, Attribute)] -> [(Name, Attribute)] -> [(Name, Attribute)]
forall a. [a] -> [a] -> [a]
++ [(Name
"op_bundle_sizes", [Int] -> Attribute
PatternUtil.I32ArrayAttr [Int]
op_bundle_sizes_)] [(Name, Attribute)] -> [(Name, Attribute)] -> [(Name, Attribute)]
forall a. [a] -> [a] -> [a]
++ (Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Maybe (Name, Attribute) -> [(Name, Attribute)])
-> Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a b. (a -> b) -> a -> b
$ (Name
"op_bundle_tags",) (Attribute -> (Name, Attribute))
-> Maybe Attribute -> Maybe (Name, Attribute)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Attribute] -> Maybe Attribute
OptionalArrayAttr Maybe [Attribute]
op_bundle_tags_)
pattern LShr :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bLShr :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mLShr :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
LShr loc ty lhs_ rhs_ = Operation
{ opName = "llvm.lshr"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
lshr :: () => MonadBlockBuilder m => Value -> Value -> m Value
lshr :: Value -> Value -> m Value
lshr Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.lshr"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Landingpad :: () => () => Location -> Type -> [operand] -> AbstractOperation operand
pattern $bLandingpad :: Location -> Type -> [operand] -> AbstractOperation operand
$mLandingpad :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> [operand] -> r) -> (Void# -> r) -> r
Landingpad loc ty0 _unnamed0_ = Operation
{ opName = "llvm.landingpad"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = _unnamed0_
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
landingpad :: () => MonadBlockBuilder m => Type -> [Value] -> m Value
landingpad :: Type -> [Value] -> m Value
landingpad Type
ty0 [Value]
_unnamed0_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.landingpad"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = ([Value] -> [Name]
AST.operands [Value]
_unnamed0_)
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern OptionalI64Attr :: Maybe Int -> Maybe Attribute
pattern $bOptionalI64Attr :: Maybe Int -> Maybe Attribute
$mOptionalI64Attr :: forall r. Maybe Attribute -> (Maybe Int -> r) -> (Void# -> r) -> r
OptionalI64Attr x <- ((\case Just (IntegerAttr (IntegerType Signless 64) y) -> Just y; Nothing -> Nothing) -> x)
where OptionalI64Attr Maybe Int
x = case Maybe Int
x of Just Int
y -> Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Type -> Int -> Attribute
IntegerAttr (Signedness -> UInt -> Type
IntegerType Signedness
Signless UInt
64) Int
y); Maybe Int
Nothing -> Maybe Attribute
forall a. Maybe a
Nothing
pattern OptionalStrAttr :: Maybe BS.ByteString -> Maybe Attribute
pattern $bOptionalStrAttr :: Maybe Name -> Maybe Attribute
$mOptionalStrAttr :: forall r. Maybe Attribute -> (Maybe Name -> r) -> (Void# -> r) -> r
OptionalStrAttr x <- ((\case Just (StringAttr y) -> Just y; Nothing -> Nothing) -> x)
where OptionalStrAttr Maybe Name
x = case Maybe Name
x of Just Name
y -> Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Name -> Attribute
StringAttr Name
y); Maybe Name
Nothing -> Maybe Attribute
forall a. Maybe a
Nothing
pattern InternalLoadOpAttributes :: () => () => Maybe Int -> Maybe BS.ByteString -> NamedAttributes
pattern $bInternalLoadOpAttributes :: Maybe Int -> Maybe Name -> Map Name Attribute
$mInternalLoadOpAttributes :: forall r.
Map Name Attribute
-> (Maybe Int -> Maybe Name -> r) -> (Void# -> r) -> r
InternalLoadOpAttributes alignment_ syncscope_ <- ((\m -> (M.lookup "alignment" m, M.lookup "syncscope" m)) -> (OptionalI64Attr alignment_, OptionalStrAttr syncscope_))
where InternalLoadOpAttributes Maybe Int
alignment_ Maybe Name
syncscope_ = [(Name, Attribute)] -> Map Name Attribute
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Name, Attribute)] -> Map Name Attribute)
-> [(Name, Attribute)] -> Map Name Attribute
forall a b. (a -> b) -> a -> b
$ (Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Maybe (Name, Attribute) -> [(Name, Attribute)])
-> Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a b. (a -> b) -> a -> b
$ (Name
"alignment",) (Attribute -> (Name, Attribute))
-> Maybe Attribute -> Maybe (Name, Attribute)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int -> Maybe Attribute
OptionalI64Attr Maybe Int
alignment_) [(Name, Attribute)] -> [(Name, Attribute)] -> [(Name, Attribute)]
forall a. [a] -> [a] -> [a]
++ (Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Maybe (Name, Attribute) -> [(Name, Attribute)])
-> Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a b. (a -> b) -> a -> b
$ (Name
"syncscope",) (Attribute -> (Name, Attribute))
-> Maybe Attribute -> Maybe (Name, Attribute)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Name -> Maybe Attribute
OptionalStrAttr Maybe Name
syncscope_)
pattern Load :: () => () => Location -> Type -> operand -> Maybe Int -> Maybe BS.ByteString -> AbstractOperation operand
pattern $bLoad :: Location
-> Type
-> operand
-> Maybe Int
-> Maybe Name
-> AbstractOperation operand
$mLoad :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> Maybe Int -> Maybe Name -> r)
-> (Void# -> r)
-> r
Load loc ty0 addr_ alignment_ syncscope_ = Operation
{ opName = "llvm.load"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [addr_]
, opRegions = []
, opSuccessors = []
, opAttributes = (InternalLoadOpAttributes alignment_ syncscope_)
}
load :: () => MonadBlockBuilder m => Type -> Value -> Maybe Int -> Maybe BS.ByteString -> m Value
load :: Type -> Value -> Maybe Int -> Maybe Name -> m Value
load Type
ty0 Value
addr_ Maybe Int
alignment_ Maybe Name
syncscope_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.load"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
addr_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Maybe Int -> Maybe Name -> Map Name Attribute
InternalLoadOpAttributes Maybe Int
alignment_ Maybe Name
syncscope_)
}))
pattern Mul :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bMul :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mMul :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
Mul loc ty lhs_ rhs_ = Operation
{ opName = "llvm.mul"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
mul :: () => MonadBlockBuilder m => Value -> Value -> m Value
mul :: Value -> Value -> m Value
mul Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.mul"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern NoneToken :: () => () => Location -> Type -> AbstractOperation operand
pattern $bNoneToken :: Location -> Type -> AbstractOperation operand
$mNoneToken :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> r) -> (Void# -> r) -> r
NoneToken loc ty0 = Operation
{ opName = "llvm.mlir.none"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = []
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
mlir_none :: () => MonadBlockBuilder m => Type -> m Value
mlir_none :: Type -> m Value
mlir_none Type
ty0 = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.mlir.none"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = []
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Or :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bOr :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mOr :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
Or loc ty lhs_ rhs_ = Operation
{ opName = "llvm.or"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
or :: () => MonadBlockBuilder m => Value -> Value -> m Value
or :: Value -> Value -> m Value
or Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.or"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Poison :: () => () => Location -> Type -> AbstractOperation operand
pattern $bPoison :: Location -> Type -> AbstractOperation operand
$mPoison :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> r) -> (Void# -> r) -> r
Poison loc ty0 = Operation
{ opName = "llvm.mlir.poison"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = []
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
mlir_poison :: () => MonadBlockBuilder m => Type -> m Value
mlir_poison :: Type -> m Value
mlir_poison Type
ty0 = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.mlir.poison"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = []
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern PtrToInt :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bPtrToInt :: Location -> Type -> operand -> AbstractOperation operand
$mPtrToInt :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
PtrToInt loc ty0 arg_ = Operation
{ opName = "llvm.ptrtoint"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
ptrtoint :: () => MonadBlockBuilder m => Type -> Value -> m Value
ptrtoint :: Type -> Value -> m Value
ptrtoint Type
ty0 Value
arg_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.ptrtoint"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
arg_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Resume :: () => () => Location -> operand -> AbstractOperation operand
pattern $bResume :: Location -> operand -> AbstractOperation operand
$mResume :: forall r operand.
AbstractOperation operand
-> (Location -> operand -> r) -> (Void# -> r) -> r
Resume loc value_ = Operation
{ opName = "llvm.resume"
, opLocation = loc
, opResultTypes = Explicit []
, opOperands = [value_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
resume :: () => MonadBlockBuilder m => Value -> m EndOfBlock
resume :: Value -> m EndOfBlock
resume Value
value_ = do
m [Value] -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Control.Monad.void (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.resume"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit []
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
value_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
m EndOfBlock
forall (m :: * -> *). Monad m => m EndOfBlock
AST.terminateBlock
return :: () => MonadBlockBuilder m => Maybe Value -> m EndOfBlock
return :: Maybe Value -> m EndOfBlock
return Maybe Value
arg_ = do
m [Value] -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Control.Monad.void (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.return"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit []
, opOperands :: [Name]
opOperands = ((Maybe Name -> [Name]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Value -> Name
AST.operand (Value -> Name) -> Maybe Value -> Maybe Name
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Value
arg_)))
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
m EndOfBlock
forall (m :: * -> *). Monad m => m EndOfBlock
AST.terminateBlock
pattern SDiv :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bSDiv :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mSDiv :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
SDiv loc ty lhs_ rhs_ = Operation
{ opName = "llvm.sdiv"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
sdiv :: () => MonadBlockBuilder m => Value -> Value -> m Value
sdiv :: Value -> Value -> m Value
sdiv Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.sdiv"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern SExt :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bSExt :: Location -> Type -> operand -> AbstractOperation operand
$mSExt :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
SExt loc ty0 arg_ = Operation
{ opName = "llvm.sext"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
sext :: () => MonadBlockBuilder m => Type -> Value -> m Value
sext :: Type -> Value -> m Value
sext Type
ty0 Value
arg_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.sext"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
arg_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern SIToFP :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bSIToFP :: Location -> Type -> operand -> AbstractOperation operand
$mSIToFP :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
SIToFP loc ty0 arg_ = Operation
{ opName = "llvm.sitofp"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
sitofp :: () => MonadBlockBuilder m => Type -> Value -> m Value
sitofp :: Type -> Value -> m Value
sitofp Type
ty0 Value
arg_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.sitofp"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
arg_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern SRem :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bSRem :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mSRem :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
SRem loc ty lhs_ rhs_ = Operation
{ opName = "llvm.srem"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
srem :: () => MonadBlockBuilder m => Value -> Value -> m Value
srem :: Value -> Value -> m Value
srem Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.srem"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Select :: () => () => Location -> Type -> operand -> operand -> operand -> AbstractOperation operand
pattern $bSelect :: Location
-> Type
-> operand
-> operand
-> operand
-> AbstractOperation operand
$mSelect :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> operand -> r)
-> (Void# -> r)
-> r
Select loc ty0 condition_ trueValue_ falseValue_ = Operation
{ opName = "llvm.select"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [condition_, trueValue_, falseValue_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
select :: () => MonadBlockBuilder m => Type -> Value -> Value -> Value -> m Value
select :: Type -> Value -> Value -> Value -> m Value
select Type
ty0 Value
condition_ Value
trueValue_ Value
falseValue_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.select"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
condition_), (Value -> Name
AST.operand Value
trueValue_), (Value -> Name
AST.operand Value
falseValue_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Shl :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bShl :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mShl :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
Shl loc ty lhs_ rhs_ = Operation
{ opName = "llvm.shl"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
shl :: () => MonadBlockBuilder m => Value -> Value -> m Value
shl :: Value -> Value -> m Value
shl Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.shl"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern InternalShuffleVectorOpAttributes :: () => () => [Int] -> NamedAttributes
pattern $bInternalShuffleVectorOpAttributes :: [Int] -> Map Name Attribute
$mInternalShuffleVectorOpAttributes :: forall r. Map Name Attribute -> ([Int] -> r) -> (Void# -> r) -> r
InternalShuffleVectorOpAttributes mask_ <- ((\m -> (M.lookup "mask" m)) -> (Just (PatternUtil.I32ArrayAttr mask_)))
where InternalShuffleVectorOpAttributes [Int]
mask_ = [(Name, Attribute)] -> Map Name Attribute
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Name, Attribute)] -> Map Name Attribute)
-> [(Name, Attribute)] -> Map Name Attribute
forall a b. (a -> b) -> a -> b
$ [(Name
"mask", [Int] -> Attribute
PatternUtil.I32ArrayAttr [Int]
mask_)]
pattern ShuffleVector :: () => () => Location -> Type -> operand -> operand -> [Int] -> AbstractOperation operand
pattern $bShuffleVector :: Location
-> Type -> operand -> operand -> [Int] -> AbstractOperation operand
$mShuffleVector :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> [Int] -> r)
-> (Void# -> r)
-> r
ShuffleVector loc ty0 v1_ v2_ mask_ = Operation
{ opName = "llvm.shufflevector"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [v1_, v2_]
, opRegions = []
, opSuccessors = []
, opAttributes = (InternalShuffleVectorOpAttributes mask_)
}
shufflevector :: () => MonadBlockBuilder m => Type -> Value -> Value -> [Int] -> m Value
shufflevector :: Type -> Value -> Value -> [Int] -> m Value
shufflevector Type
ty0 Value
v1_ Value
v2_ [Int]
mask_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.shufflevector"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
v1_), (Value -> Name
AST.operand Value
v2_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = ([Int] -> Map Name Attribute
InternalShuffleVectorOpAttributes [Int]
mask_)
}))
pattern InternalStoreOpAttributes :: () => () => Maybe Int -> Maybe BS.ByteString -> NamedAttributes
pattern $bInternalStoreOpAttributes :: Maybe Int -> Maybe Name -> Map Name Attribute
$mInternalStoreOpAttributes :: forall r.
Map Name Attribute
-> (Maybe Int -> Maybe Name -> r) -> (Void# -> r) -> r
InternalStoreOpAttributes alignment_ syncscope_ <- ((\m -> (M.lookup "alignment" m, M.lookup "syncscope" m)) -> (OptionalI64Attr alignment_, OptionalStrAttr syncscope_))
where InternalStoreOpAttributes Maybe Int
alignment_ Maybe Name
syncscope_ = [(Name, Attribute)] -> Map Name Attribute
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Name, Attribute)] -> Map Name Attribute)
-> [(Name, Attribute)] -> Map Name Attribute
forall a b. (a -> b) -> a -> b
$ (Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Maybe (Name, Attribute) -> [(Name, Attribute)])
-> Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a b. (a -> b) -> a -> b
$ (Name
"alignment",) (Attribute -> (Name, Attribute))
-> Maybe Attribute -> Maybe (Name, Attribute)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int -> Maybe Attribute
OptionalI64Attr Maybe Int
alignment_) [(Name, Attribute)] -> [(Name, Attribute)] -> [(Name, Attribute)]
forall a. [a] -> [a] -> [a]
++ (Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Maybe (Name, Attribute) -> [(Name, Attribute)])
-> Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a b. (a -> b) -> a -> b
$ (Name
"syncscope",) (Attribute -> (Name, Attribute))
-> Maybe Attribute -> Maybe (Name, Attribute)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Name -> Maybe Attribute
OptionalStrAttr Maybe Name
syncscope_)
pattern Store :: () => () => Location -> operand -> operand -> Maybe Int -> Maybe BS.ByteString -> AbstractOperation operand
pattern $bStore :: Location
-> operand
-> operand
-> Maybe Int
-> Maybe Name
-> AbstractOperation operand
$mStore :: forall r operand.
AbstractOperation operand
-> (Location -> operand -> operand -> Maybe Int -> Maybe Name -> r)
-> (Void# -> r)
-> r
Store loc value_ addr_ alignment_ syncscope_ = Operation
{ opName = "llvm.store"
, opLocation = loc
, opResultTypes = Explicit []
, opOperands = [value_, addr_]
, opRegions = []
, opSuccessors = []
, opAttributes = (InternalStoreOpAttributes alignment_ syncscope_)
}
store :: () => MonadBlockBuilder m => Value -> Value -> Maybe Int -> Maybe BS.ByteString -> m ()
store :: Value -> Value -> Maybe Int -> Maybe Name -> m ()
store Value
value_ Value
addr_ Maybe Int
alignment_ Maybe Name
syncscope_ = do
m [Value] -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Control.Monad.void (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.store"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit []
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
value_), (Value -> Name
AST.operand Value
addr_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Maybe Int -> Maybe Name -> Map Name Attribute
InternalStoreOpAttributes Maybe Int
alignment_ Maybe Name
syncscope_)
}))
pattern Sub :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bSub :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mSub :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
Sub loc ty lhs_ rhs_ = Operation
{ opName = "llvm.sub"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
sub :: () => MonadBlockBuilder m => Value -> Value -> m Value
sub :: Value -> Value -> m Value
sub Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.sub"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern InternalSwitchOpAttributes :: () => () => [Int] -> Maybe [Int] -> NamedAttributes
pattern $bInternalSwitchOpAttributes :: [Int] -> Maybe [Int] -> Map Name Attribute
$mInternalSwitchOpAttributes :: forall r.
Map Name Attribute
-> ([Int] -> Maybe [Int] -> r) -> (Void# -> r) -> r
InternalSwitchOpAttributes case_operand_segments_ branch_weights_ <- ((\m -> (M.lookup "case_operand_segments" m, M.lookup "branch_weights" m)) -> (Just (PatternUtil.I32ArrayAttr case_operand_segments_), OptionalDenseI32ArrayAttr branch_weights_))
where InternalSwitchOpAttributes [Int]
case_operand_segments_ Maybe [Int]
branch_weights_ = [(Name, Attribute)] -> Map Name Attribute
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Name, Attribute)] -> Map Name Attribute)
-> [(Name, Attribute)] -> Map Name Attribute
forall a b. (a -> b) -> a -> b
$ [(Name
"case_operand_segments", [Int] -> Attribute
PatternUtil.I32ArrayAttr [Int]
case_operand_segments_)] [(Name, Attribute)] -> [(Name, Attribute)] -> [(Name, Attribute)]
forall a. [a] -> [a] -> [a]
++ (Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a. Maybe a -> [a]
Data.Maybe.maybeToList (Maybe (Name, Attribute) -> [(Name, Attribute)])
-> Maybe (Name, Attribute) -> [(Name, Attribute)]
forall a b. (a -> b) -> a -> b
$ (Name
"branch_weights",) (Attribute -> (Name, Attribute))
-> Maybe Attribute -> Maybe (Name, Attribute)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Int] -> Maybe Attribute
OptionalDenseI32ArrayAttr Maybe [Int]
branch_weights_)
pattern Trunc :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bTrunc :: Location -> Type -> operand -> AbstractOperation operand
$mTrunc :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
Trunc loc ty0 arg_ = Operation
{ opName = "llvm.trunc"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
trunc :: () => MonadBlockBuilder m => Type -> Value -> m Value
trunc :: Type -> Value -> m Value
trunc Type
ty0 Value
arg_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.trunc"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
arg_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern UDiv :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bUDiv :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mUDiv :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
UDiv loc ty lhs_ rhs_ = Operation
{ opName = "llvm.udiv"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
udiv :: () => MonadBlockBuilder m => Value -> Value -> m Value
udiv :: Value -> Value -> m Value
udiv Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.udiv"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern UIToFP :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bUIToFP :: Location -> Type -> operand -> AbstractOperation operand
$mUIToFP :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
UIToFP loc ty0 arg_ = Operation
{ opName = "llvm.uitofp"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
uitofp :: () => MonadBlockBuilder m => Type -> Value -> m Value
uitofp :: Type -> Value -> m Value
uitofp Type
ty0 Value
arg_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.uitofp"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
arg_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern URem :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bURem :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mURem :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
URem loc ty lhs_ rhs_ = Operation
{ opName = "llvm.urem"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
urem :: () => MonadBlockBuilder m => Value -> Value -> m Value
urem :: Value -> Value -> m Value
urem Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.urem"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Undef :: () => () => Location -> Type -> AbstractOperation operand
pattern $bUndef :: Location -> Type -> AbstractOperation operand
$mUndef :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> r) -> (Void# -> r) -> r
Undef loc ty0 = Operation
{ opName = "llvm.mlir.undef"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = []
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
mlir_undef :: () => MonadBlockBuilder m => Type -> m Value
mlir_undef :: Type -> m Value
mlir_undef Type
ty0 = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.mlir.undef"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = []
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Unreachable :: () => () => Location -> AbstractOperation operand
pattern $bUnreachable :: Location -> AbstractOperation operand
$mUnreachable :: forall r operand.
AbstractOperation operand -> (Location -> r) -> (Void# -> r) -> r
Unreachable loc = Operation
{ opName = "llvm.unreachable"
, opLocation = loc
, opResultTypes = Explicit []
, opOperands = []
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
unreachable :: () => MonadBlockBuilder m => m EndOfBlock
unreachable :: m EndOfBlock
unreachable = do
m [Value] -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Control.Monad.void (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.unreachable"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit []
, opOperands :: [Name]
opOperands = []
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
m EndOfBlock
forall (m :: * -> *). Monad m => m EndOfBlock
AST.terminateBlock
pattern VaArg :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bVaArg :: Location -> Type -> operand -> AbstractOperation operand
$mVaArg :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
VaArg loc ty0 arg_ = Operation
{ opName = "llvm.va_arg"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
va_arg :: () => MonadBlockBuilder m => Type -> Value -> m Value
va_arg :: Type -> Value -> m Value
va_arg Type
ty0 Value
arg_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.va_arg"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
arg_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern XOr :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bXOr :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mXOr :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
XOr loc ty lhs_ rhs_ = Operation
{ opName = "llvm.xor"
, opLocation = loc
, opResultTypes = Explicit [ty]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
xor :: () => MonadBlockBuilder m => Value -> Value -> m Value
xor :: Value -> Value -> m Value
xor Value
lhs_ Value
rhs_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.xor"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [(Value -> Type
AST.typeOf Value
lhs_)]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
lhs_), (Value -> Name
AST.operand Value
rhs_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern ZExt :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bZExt :: Location -> Type -> operand -> AbstractOperation operand
$mZExt :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
ZExt loc ty0 arg_ = Operation
{ opName = "llvm.zext"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
zext :: () => MonadBlockBuilder m => Type -> Value -> m Value
zext :: Type -> Value -> m Value
zext Type
ty0 Value
arg_ = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.zext"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
arg_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Zero :: () => () => Location -> Type -> AbstractOperation operand
pattern $bZero :: Location -> Type -> AbstractOperation operand
$mZero :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> r) -> (Void# -> r) -> r
Zero loc ty0 = Operation
{ opName = "llvm.mlir.zero"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = []
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
mlir_zero :: () => MonadBlockBuilder m => Type -> m Value
mlir_zero :: Type -> m Value
mlir_zero Type
ty0 = do
([Value] -> Value) -> m [Value] -> m Value
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
Control.Monad.liftM [Value] -> Value
forall a. [a] -> a
Prelude.head (Operation -> m [Value]
forall (m :: * -> *). MonadBlockBuilder m => Operation -> m [Value]
AST.emitOp (Operation :: forall operand.
Name
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [Name]
-> Map Name Attribute
-> AbstractOperation operand
Operation
{ opName :: Name
opName = Name
"llvm.mlir.zero"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = []
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))