{-# OPTIONS_GHC -Wno-unused-imports #-}
{-# OPTIONS_HADDOCK hide, prune, not-home #-}
module MLIR.AST.Dialect.Generated.Shape 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 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 ty0 lhs_ rhs_ = Operation
{ opName = "shape.add"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
add :: () => MonadBlockBuilder m => Type -> Value -> Value -> m Value
add :: Type -> Value -> Value -> m Value
add Type
ty0 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
"shape.add"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, 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 Any :: () => () => Location -> Type -> [operand] -> AbstractOperation operand
pattern $bAny :: Location -> Type -> [operand] -> AbstractOperation operand
$mAny :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> [operand] -> r) -> (Void# -> r) -> r
Any loc ty0 inputs_ = Operation
{ opName = "shape.any"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = inputs_
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
any :: () => MonadBlockBuilder m => Type -> [Value] -> m Value
any :: Type -> [Value] -> m Value
any Type
ty0 [Value]
inputs_ = 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
"shape.any"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = ([Value] -> [Name]
AST.operands [Value]
inputs_)
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern AssumingAll :: () => () => Location -> Type -> [operand] -> AbstractOperation operand
pattern $bAssumingAll :: Location -> Type -> [operand] -> AbstractOperation operand
$mAssumingAll :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> [operand] -> r) -> (Void# -> r) -> r
AssumingAll loc ty0 inputs_ = Operation
{ opName = "shape.assuming_all"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = inputs_
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
assuming_all :: () => MonadBlockBuilder m => Type -> [Value] -> m Value
assuming_all :: Type -> [Value] -> m Value
assuming_all Type
ty0 [Value]
inputs_ = 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
"shape.assuming_all"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = ([Value] -> [Name]
AST.operands [Value]
inputs_)
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
assuming :: () => MonadBlockBuilder m => [Type] -> Value -> RegionBuilderT m () -> m Value
assuming :: [Type] -> Value -> RegionBuilderT m () -> m Value
assuming [Type]
ty0 Value
witness_ RegionBuilderT m ()
doRegion_Builder = do
Region
doRegion_ <- RegionBuilderT m () -> m Region
forall (m :: * -> *). Monad m => RegionBuilderT m () -> m Region
AST.buildRegion RegionBuilderT m ()
doRegion_Builder
([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
"shape.assuming"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit ([Type]
ty0)
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
witness_)]
, opRegions :: [Region]
opRegions = [Region
doRegion_]
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern AssumingYield :: () => () => Location -> [operand] -> AbstractOperation operand
pattern $bAssumingYield :: Location -> [operand] -> AbstractOperation operand
$mAssumingYield :: forall r operand.
AbstractOperation operand
-> (Location -> [operand] -> r) -> (Void# -> r) -> r
AssumingYield loc operands_ = Operation
{ opName = "shape.assuming_yield"
, opLocation = loc
, opResultTypes = Explicit []
, opOperands = operands_
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
assuming_yield :: () => MonadBlockBuilder m => [Value] -> m EndOfBlock
assuming_yield :: [Value] -> m EndOfBlock
assuming_yield [Value]
operands_ = 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
"shape.assuming_yield"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit []
, opOperands :: [Name]
opOperands = ([Value] -> [Name]
AST.operands [Value]
operands_)
, 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 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 InternalBroadcastOpAttributes :: () => () => Maybe BS.ByteString -> NamedAttributes
pattern $bInternalBroadcastOpAttributes :: Maybe Name -> Map Name Attribute
$mInternalBroadcastOpAttributes :: forall r.
Map Name Attribute -> (Maybe Name -> r) -> (Void# -> r) -> r
InternalBroadcastOpAttributes error_ <- ((\m -> (M.lookup "error" m)) -> (OptionalStrAttr error_))
where InternalBroadcastOpAttributes Maybe Name
error_ = [(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
"error",) (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
error_)
pattern Broadcast :: () => () => Location -> Type -> [operand] -> Maybe BS.ByteString -> AbstractOperation operand
pattern $bBroadcast :: Location
-> Type -> [operand] -> Maybe Name -> AbstractOperation operand
$mBroadcast :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> [operand] -> Maybe Name -> r)
-> (Void# -> r)
-> r
Broadcast loc ty0 shapes_ error_ = Operation
{ opName = "shape.broadcast"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = shapes_
, opRegions = []
, opSuccessors = []
, opAttributes = (InternalBroadcastOpAttributes error_)
}
broadcast :: () => MonadBlockBuilder m => Type -> [Value] -> Maybe BS.ByteString -> m Value
broadcast :: Type -> [Value] -> Maybe Name -> m Value
broadcast Type
ty0 [Value]
shapes_ Maybe Name
error_ = 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
"shape.broadcast"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = ([Value] -> [Name]
AST.operands [Value]
shapes_)
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Maybe Name -> Map Name Attribute
InternalBroadcastOpAttributes Maybe Name
error_)
}))
pattern Concat :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bConcat :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mConcat :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
Concat loc ty0 lhs_ rhs_ = Operation
{ opName = "shape.concat"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
concat :: () => MonadBlockBuilder m => Type -> Value -> Value -> m Value
concat :: Type -> Value -> Value -> m Value
concat Type
ty0 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
"shape.concat"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, 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 InternalConstSizeOpAttributes :: () => () => Int -> NamedAttributes
pattern $bInternalConstSizeOpAttributes :: Int -> Map Name Attribute
$mInternalConstSizeOpAttributes :: forall r. Map Name Attribute -> (Int -> r) -> (Void# -> r) -> r
InternalConstSizeOpAttributes value_ <- ((\m -> (M.lookup "value" m)) -> (Just (IntegerAttr IndexType value_)))
where InternalConstSizeOpAttributes Int
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", Type -> Int -> Attribute
IntegerAttr Type
IndexType Int
value_)]
pattern ConstSize :: () => () => Location -> Type -> Int -> AbstractOperation operand
pattern $bConstSize :: Location -> Type -> Int -> AbstractOperation operand
$mConstSize :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> Int -> r) -> (Void# -> r) -> r
ConstSize loc ty0 value_ = Operation
{ opName = "shape.const_size"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = []
, opRegions = []
, opSuccessors = []
, opAttributes = (InternalConstSizeOpAttributes value_)
}
const_size :: () => MonadBlockBuilder m => Type -> Int -> m Value
const_size :: Type -> Int -> m Value
const_size Type
ty0 Int
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
"shape.const_size"
, 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 = (Int -> Map Name Attribute
InternalConstSizeOpAttributes Int
value_)
}))
pattern InternalConstWitnessOpAttributes :: () => () => Bool -> NamedAttributes
pattern $bInternalConstWitnessOpAttributes :: Bool -> Map Name Attribute
$mInternalConstWitnessOpAttributes :: forall r. Map Name Attribute -> (Bool -> r) -> (Void# -> r) -> r
InternalConstWitnessOpAttributes passing_ <- ((\m -> (M.lookup "passing" m)) -> (Just (BoolAttr passing_)))
where InternalConstWitnessOpAttributes Bool
passing_ = [(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
"passing", Bool -> Attribute
BoolAttr Bool
passing_)]
pattern ConstWitness :: () => () => Location -> Type -> Bool -> AbstractOperation operand
pattern $bConstWitness :: Location -> Type -> Bool -> AbstractOperation operand
$mConstWitness :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> Bool -> r) -> (Void# -> r) -> r
ConstWitness loc ty0 passing_ = Operation
{ opName = "shape.const_witness"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = []
, opRegions = []
, opSuccessors = []
, opAttributes = (InternalConstWitnessOpAttributes passing_)
}
const_witness :: () => MonadBlockBuilder m => Type -> Bool -> m Value
const_witness :: Type -> Bool -> m Value
const_witness Type
ty0 Bool
passing_ = 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
"shape.const_witness"
, 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 = (Bool -> Map Name Attribute
InternalConstWitnessOpAttributes Bool
passing_)
}))
pattern CstrBroadcastable :: () => () => Location -> Type -> [operand] -> AbstractOperation operand
pattern $bCstrBroadcastable :: Location -> Type -> [operand] -> AbstractOperation operand
$mCstrBroadcastable :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> [operand] -> r) -> (Void# -> r) -> r
CstrBroadcastable loc ty0 shapes_ = Operation
{ opName = "shape.cstr_broadcastable"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = shapes_
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
cstr_broadcastable :: () => MonadBlockBuilder m => Type -> [Value] -> m Value
cstr_broadcastable :: Type -> [Value] -> m Value
cstr_broadcastable Type
ty0 [Value]
shapes_ = 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
"shape.cstr_broadcastable"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = ([Value] -> [Name]
AST.operands [Value]
shapes_)
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern CstrEq :: () => () => Location -> Type -> [operand] -> AbstractOperation operand
pattern $bCstrEq :: Location -> Type -> [operand] -> AbstractOperation operand
$mCstrEq :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> [operand] -> r) -> (Void# -> r) -> r
CstrEq loc ty0 shapes_ = Operation
{ opName = "shape.cstr_eq"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = shapes_
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
cstr_eq :: () => MonadBlockBuilder m => Type -> [Value] -> m Value
cstr_eq :: Type -> [Value] -> m Value
cstr_eq Type
ty0 [Value]
shapes_ = 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
"shape.cstr_eq"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = ([Value] -> [Name]
AST.operands [Value]
shapes_)
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern InternalCstrRequireOpAttributes :: () => () => BS.ByteString -> NamedAttributes
pattern $bInternalCstrRequireOpAttributes :: Name -> Map Name Attribute
$mInternalCstrRequireOpAttributes :: forall r. Map Name Attribute -> (Name -> r) -> (Void# -> r) -> r
InternalCstrRequireOpAttributes msg_ <- ((\m -> (M.lookup "msg" m)) -> (Just (StringAttr msg_)))
where InternalCstrRequireOpAttributes Name
msg_ = [(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
"msg", Name -> Attribute
StringAttr Name
msg_)]
pattern CstrRequire :: () => () => Location -> Type -> operand -> BS.ByteString -> AbstractOperation operand
pattern $bCstrRequire :: Location -> Type -> operand -> Name -> AbstractOperation operand
$mCstrRequire :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> Name -> r) -> (Void# -> r) -> r
CstrRequire loc ty0 pred_ msg_ = Operation
{ opName = "shape.cstr_require"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [pred_]
, opRegions = []
, opSuccessors = []
, opAttributes = (InternalCstrRequireOpAttributes msg_)
}
cstr_require :: () => MonadBlockBuilder m => Type -> Value -> BS.ByteString -> m Value
cstr_require :: Type -> Value -> Name -> m Value
cstr_require Type
ty0 Value
pred_ Name
msg_ = 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
"shape.cstr_require"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
pred_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Name -> Map Name Attribute
InternalCstrRequireOpAttributes Name
msg_)
}))
pattern DebugPrint :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bDebugPrint :: Location -> Type -> operand -> AbstractOperation operand
$mDebugPrint :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
DebugPrint loc ty0 input_ = Operation
{ opName = "shape.debug_print"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [input_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
debug_print :: () => MonadBlockBuilder m => Type -> Value -> m Value
debug_print :: Type -> Value -> m Value
debug_print Type
ty0 Value
input_ = 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
"shape.debug_print"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
input_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Dim :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bDim :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mDim :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
Dim loc ty0 value_ index_ = Operation
{ opName = "shape.dim"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [value_, index_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
dim :: () => MonadBlockBuilder m => Type -> Value -> Value -> m Value
dim :: Type -> Value -> Value -> m Value
dim Type
ty0 Value
value_ Value
index_ = 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
"shape.dim"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
value_), (Value -> Name
AST.operand Value
index_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Div :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bDiv :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mDiv :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
Div loc ty0 lhs_ rhs_ = Operation
{ opName = "shape.div"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
div :: () => MonadBlockBuilder m => Type -> Value -> Value -> m Value
div :: Type -> Value -> Value -> m Value
div Type
ty0 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
"shape.div"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, 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 FromExtentTensor :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bFromExtentTensor :: Location -> Type -> operand -> AbstractOperation operand
$mFromExtentTensor :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
FromExtentTensor loc ty0 input_ = Operation
{ opName = "shape.from_extent_tensor"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [input_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
from_extent_tensor :: () => MonadBlockBuilder m => Type -> Value -> m Value
from_extent_tensor :: Type -> Value -> m Value
from_extent_tensor Type
ty0 Value
input_ = 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
"shape.from_extent_tensor"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
input_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern FromExtents :: () => () => Location -> Type -> [operand] -> AbstractOperation operand
pattern $bFromExtents :: Location -> Type -> [operand] -> AbstractOperation operand
$mFromExtents :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> [operand] -> r) -> (Void# -> r) -> r
FromExtents loc ty0 extents_ = Operation
{ opName = "shape.from_extents"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = extents_
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
from_extents :: () => MonadBlockBuilder m => Type -> [Value] -> m Value
from_extents :: Type -> [Value] -> m Value
from_extents Type
ty0 [Value]
extents_ = 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
"shape.from_extents"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = ([Value] -> [Name]
AST.operands [Value]
extents_)
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern GetExtent :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bGetExtent :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mGetExtent :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
GetExtent loc ty0 shape_ dim_ = Operation
{ opName = "shape.get_extent"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [shape_, dim_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
get_extent :: () => MonadBlockBuilder m => Type -> Value -> Value -> m Value
get_extent :: Type -> Value -> Value -> m Value
get_extent Type
ty0 Value
shape_ Value
dim_ = 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
"shape.get_extent"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
shape_), (Value -> Name
AST.operand Value
dim_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern IndexToSize :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bIndexToSize :: Location -> Type -> operand -> AbstractOperation operand
$mIndexToSize :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
IndexToSize loc ty0 arg_ = Operation
{ opName = "shape.index_to_size"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
index_to_size :: () => MonadBlockBuilder m => Type -> Value -> m Value
index_to_size :: Type -> Value -> m Value
index_to_size 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
"shape.index_to_size"
, 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 IsBroadcastable :: () => () => Location -> Type -> [operand] -> AbstractOperation operand
pattern $bIsBroadcastable :: Location -> Type -> [operand] -> AbstractOperation operand
$mIsBroadcastable :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> [operand] -> r) -> (Void# -> r) -> r
IsBroadcastable loc ty0 shapes_ = Operation
{ opName = "shape.is_broadcastable"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = shapes_
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
is_broadcastable :: () => MonadBlockBuilder m => Type -> [Value] -> m Value
is_broadcastable :: Type -> [Value] -> m Value
is_broadcastable Type
ty0 [Value]
shapes_ = 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
"shape.is_broadcastable"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = ([Value] -> [Name]
AST.operands [Value]
shapes_)
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Max :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bMax :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mMax :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
Max loc ty0 lhs_ rhs_ = Operation
{ opName = "shape.max"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
max :: () => MonadBlockBuilder m => Type -> Value -> Value -> m Value
max :: Type -> Value -> Value -> m Value
max Type
ty0 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
"shape.max"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, 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 InternalMeetOpAttributes :: () => () => Maybe BS.ByteString -> NamedAttributes
pattern $bInternalMeetOpAttributes :: Maybe Name -> Map Name Attribute
$mInternalMeetOpAttributes :: forall r.
Map Name Attribute -> (Maybe Name -> r) -> (Void# -> r) -> r
InternalMeetOpAttributes error_ <- ((\m -> (M.lookup "error" m)) -> (OptionalStrAttr error_))
where InternalMeetOpAttributes Maybe Name
error_ = [(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
"error",) (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
error_)
pattern Meet :: () => () => Location -> Type -> operand -> operand -> Maybe BS.ByteString -> AbstractOperation operand
pattern $bMeet :: Location
-> Type
-> operand
-> operand
-> Maybe Name
-> AbstractOperation operand
$mMeet :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> Maybe Name -> r)
-> (Void# -> r)
-> r
Meet loc ty0 arg0_ arg1_ error_ = Operation
{ opName = "shape.meet"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg0_, arg1_]
, opRegions = []
, opSuccessors = []
, opAttributes = (InternalMeetOpAttributes error_)
}
meet :: () => MonadBlockBuilder m => Type -> Value -> Value -> Maybe BS.ByteString -> m Value
meet :: Type -> Value -> Value -> Maybe Name -> m Value
meet Type
ty0 Value
arg0_ Value
arg1_ Maybe Name
error_ = 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
"shape.meet"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
arg0_), (Value -> Name
AST.operand Value
arg1_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Maybe Name -> Map Name Attribute
InternalMeetOpAttributes Maybe Name
error_)
}))
pattern Min :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bMin :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mMin :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
Min loc ty0 lhs_ rhs_ = Operation
{ opName = "shape.min"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
min :: () => MonadBlockBuilder m => Type -> Value -> Value -> m Value
min :: Type -> Value -> Value -> m Value
min Type
ty0 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
"shape.min"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, 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 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 ty0 lhs_ rhs_ = Operation
{ opName = "shape.mul"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [lhs_, rhs_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
mul :: () => MonadBlockBuilder m => Type -> Value -> Value -> m Value
mul :: Type -> Value -> Value -> m Value
mul Type
ty0 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
"shape.mul"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, 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 NumElements :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bNumElements :: Location -> Type -> operand -> AbstractOperation operand
$mNumElements :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
NumElements loc ty0 shape_ = Operation
{ opName = "shape.num_elements"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [shape_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
num_elements :: () => MonadBlockBuilder m => Type -> Value -> m Value
num_elements :: Type -> Value -> m Value
num_elements Type
ty0 Value
shape_ = 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
"shape.num_elements"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
shape_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Rank :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bRank :: Location -> Type -> operand -> AbstractOperation operand
$mRank :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
Rank loc ty0 shape_ = Operation
{ opName = "shape.rank"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [shape_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
rank :: () => MonadBlockBuilder m => Type -> Value -> m Value
rank :: Type -> Value -> m Value
rank Type
ty0 Value
shape_ = 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
"shape.rank"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
shape_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
reduce :: () => MonadBlockBuilder m => [Type] -> Value -> [Value] -> RegionBuilderT m () -> m Value
reduce :: [Type] -> Value -> [Value] -> RegionBuilderT m () -> m Value
reduce [Type]
ty0 Value
shape_ [Value]
initVals_ RegionBuilderT m ()
region_Builder = do
Region
region_ <- RegionBuilderT m () -> m Region
forall (m :: * -> *). Monad m => RegionBuilderT m () -> m Region
AST.buildRegion RegionBuilderT m ()
region_Builder
([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
"shape.reduce"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit ([Type]
ty0)
, opOperands :: [Name]
opOperands = ([(Value -> Name
AST.operand Value
shape_)] [Name] -> [Name] -> [Name]
forall a. [a] -> [a] -> [a]
++ ([Value] -> [Name]
AST.operands [Value]
initVals_))
, opRegions :: [Region]
opRegions = [Region
region_]
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Return :: () => () => Location -> [operand] -> AbstractOperation operand
pattern $bReturn :: Location -> [operand] -> AbstractOperation operand
$mReturn :: forall r operand.
AbstractOperation operand
-> (Location -> [operand] -> r) -> (Void# -> r) -> r
Return loc operands_ = Operation
{ opName = "shape.return"
, opLocation = loc
, opResultTypes = Explicit []
, opOperands = operands_
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
return :: () => MonadBlockBuilder m => [Value] -> m EndOfBlock
return :: [Value] -> m EndOfBlock
return [Value]
operands_ = 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
"shape.return"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit []
, opOperands :: [Name]
opOperands = ([Value] -> [Name]
AST.operands [Value]
operands_)
, 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 ShapeEq :: () => () => Location -> Type -> [operand] -> AbstractOperation operand
pattern $bShapeEq :: Location -> Type -> [operand] -> AbstractOperation operand
$mShapeEq :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> [operand] -> r) -> (Void# -> r) -> r
ShapeEq loc ty0 shapes_ = Operation
{ opName = "shape.shape_eq"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = shapes_
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
shape_eq :: () => MonadBlockBuilder m => Type -> [Value] -> m Value
shape_eq :: Type -> [Value] -> m Value
shape_eq Type
ty0 [Value]
shapes_ = 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
"shape.shape_eq"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = ([Value] -> [Name]
AST.operands [Value]
shapes_)
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern ShapeOf :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bShapeOf :: Location -> Type -> operand -> AbstractOperation operand
$mShapeOf :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
ShapeOf loc ty0 arg_ = Operation
{ opName = "shape.shape_of"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
shape_of :: () => MonadBlockBuilder m => Type -> Value -> m Value
shape_of :: Type -> Value -> m Value
shape_of 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
"shape.shape_of"
, 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 SizeToIndex :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bSizeToIndex :: Location -> Type -> operand -> AbstractOperation operand
$mSizeToIndex :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
SizeToIndex loc ty0 arg_ = Operation
{ opName = "shape.size_to_index"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
size_to_index :: () => MonadBlockBuilder m => Type -> Value -> m Value
size_to_index :: Type -> Value -> m Value
size_to_index 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
"shape.size_to_index"
, 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 SplitAt :: () => () => Location -> Type -> Type -> operand -> operand -> AbstractOperation operand
pattern $bSplitAt :: Location
-> Type -> Type -> operand -> operand -> AbstractOperation operand
$mSplitAt :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
SplitAt loc ty0 ty1 operand_ index_ = Operation
{ opName = "shape.split_at"
, opLocation = loc
, opResultTypes = Explicit [ty0, ty1]
, opOperands = [operand_, index_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
split_at :: () => MonadBlockBuilder m => Type -> Type -> Value -> Value -> m [Value]
split_at :: Type -> Type -> Value -> Value -> m [Value]
split_at Type
ty0 Type
ty1 Value
operand_ Value
index_ = do
(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
"shape.split_at"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0, Type
ty1]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
operand_), (Value -> Name
AST.operand Value
index_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern ToExtentTensor :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bToExtentTensor :: Location -> Type -> operand -> AbstractOperation operand
$mToExtentTensor :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
ToExtentTensor loc ty0 input_ = Operation
{ opName = "shape.to_extent_tensor"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [input_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
to_extent_tensor :: () => MonadBlockBuilder m => Type -> Value -> m Value
to_extent_tensor :: Type -> Value -> m Value
to_extent_tensor Type
ty0 Value
input_ = 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
"shape.to_extent_tensor"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
input_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern ValueAsShape :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bValueAsShape :: Location -> Type -> operand -> AbstractOperation operand
$mValueAsShape :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
ValueAsShape loc ty0 arg_ = Operation
{ opName = "shape.value_as_shape"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
value_as_shape :: () => MonadBlockBuilder m => Type -> Value -> m Value
value_as_shape :: Type -> Value -> m Value
value_as_shape 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
"shape.value_as_shape"
, 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 ValueOf :: () => () => Location -> Type -> operand -> AbstractOperation operand
pattern $bValueOf :: Location -> Type -> operand -> AbstractOperation operand
$mValueOf :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> r) -> (Void# -> r) -> r
ValueOf loc ty0 arg_ = Operation
{ opName = "shape.value_of"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
value_of :: () => MonadBlockBuilder m => Type -> Value -> m Value
value_of :: Type -> Value -> m Value
value_of 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
"shape.value_of"
, 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 With :: () => () => Location -> Type -> operand -> operand -> AbstractOperation operand
pattern $bWith :: Location -> Type -> operand -> operand -> AbstractOperation operand
$mWith :: forall r operand.
AbstractOperation operand
-> (Location -> Type -> operand -> operand -> r)
-> (Void# -> r)
-> r
With loc ty0 operand_ shape_ = Operation
{ opName = "shape.with_shape"
, opLocation = loc
, opResultTypes = Explicit [ty0]
, opOperands = [operand_, shape_]
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
with_shape :: () => MonadBlockBuilder m => Type -> Value -> Value -> m Value
with_shape :: Type -> Value -> Value -> m Value
with_shape Type
ty0 Value
operand_ Value
shape_ = 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
"shape.with_shape"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit [Type
ty0]
, opOperands :: [Name]
opOperands = [(Value -> Name
AST.operand Value
operand_), (Value -> Name
AST.operand Value
shape_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [Name]
opSuccessors = []
, opAttributes :: Map Name Attribute
opAttributes = (Map Name Attribute
NoAttrs)
}))
pattern Yield :: () => () => Location -> [operand] -> AbstractOperation operand
pattern $bYield :: Location -> [operand] -> AbstractOperation operand
$mYield :: forall r operand.
AbstractOperation operand
-> (Location -> [operand] -> r) -> (Void# -> r) -> r
Yield loc operands_ = Operation
{ opName = "shape.yield"
, opLocation = loc
, opResultTypes = Explicit []
, opOperands = operands_
, opRegions = []
, opSuccessors = []
, opAttributes = (NoAttrs)
}
yield :: () => MonadBlockBuilder m => [Value] -> m EndOfBlock
yield :: [Value] -> m EndOfBlock
yield [Value]
operands_ = 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
"shape.yield"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit []
, opOperands :: [Name]
opOperands = ([Value] -> [Name]
AST.operands [Value]
operands_)
, 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