{-# OPTIONS_GHC -Wno-unused-imports #-}
{-# OPTIONS_HADDOCK hide, prune, not-home #-}
module MLIR.AST.Dialect.Generated.ControlFlow 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 InternalAssertOpAttributes :: () => () => BS.ByteString -> NamedAttributes
pattern $bInternalAssertOpAttributes :: ByteString -> NamedAttributes
$mInternalAssertOpAttributes :: forall r. NamedAttributes -> (ByteString -> r) -> (Void# -> r) -> r
InternalAssertOpAttributes msg_ <- ((\m -> (M.lookup "msg" m)) -> (Just (StringAttr msg_)))
where InternalAssertOpAttributes ByteString
msg_ = [(ByteString, Attribute)] -> NamedAttributes
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(ByteString, Attribute)] -> NamedAttributes)
-> [(ByteString, Attribute)] -> NamedAttributes
forall a b. (a -> b) -> a -> b
$ [(ByteString
"msg", ByteString -> Attribute
StringAttr ByteString
msg_)]
pattern Assert :: () => () => Location -> operand -> BS.ByteString -> AbstractOperation operand
pattern $bAssert :: Location -> operand -> ByteString -> AbstractOperation operand
$mAssert :: forall r operand.
AbstractOperation operand
-> (Location -> operand -> ByteString -> r) -> (Void# -> r) -> r
Assert loc arg_ msg_ = Operation
{ opName = "cf.assert"
, opLocation = loc
, opResultTypes = Explicit []
, opOperands = [arg_]
, opRegions = []
, opSuccessors = []
, opAttributes = (InternalAssertOpAttributes msg_)
}
assert :: () => MonadBlockBuilder m => Value -> BS.ByteString -> m ()
assert :: Value -> ByteString -> m ()
assert Value
arg_ ByteString
msg_ = 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.
ByteString
-> Location
-> ResultTypes
-> [operand]
-> [Region]
-> [ByteString]
-> NamedAttributes
-> AbstractOperation operand
Operation
{ opName :: ByteString
opName = ByteString
"cf.assert"
, opLocation :: Location
opLocation = Location
UnknownLocation
, opResultTypes :: ResultTypes
opResultTypes = [Type] -> ResultTypes
Explicit []
, opOperands :: [ByteString]
opOperands = [(Value -> ByteString
AST.operand Value
arg_)]
, opRegions :: [Region]
opRegions = []
, opSuccessors :: [ByteString]
opSuccessors = []
, opAttributes :: NamedAttributes
opAttributes = (ByteString -> NamedAttributes
InternalAssertOpAttributes ByteString
msg_)
}))
pattern InternalSwitchOpAttributes :: () => () => [Int] -> NamedAttributes
pattern $bInternalSwitchOpAttributes :: [Int] -> NamedAttributes
$mInternalSwitchOpAttributes :: forall r. NamedAttributes -> ([Int] -> r) -> (Void# -> r) -> r
InternalSwitchOpAttributes case_operand_segments_ <- ((\m -> (M.lookup "case_operand_segments" m)) -> (Just (PatternUtil.I32ArrayAttr case_operand_segments_)))
where InternalSwitchOpAttributes [Int]
case_operand_segments_ = [(ByteString, Attribute)] -> NamedAttributes
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(ByteString, Attribute)] -> NamedAttributes)
-> [(ByteString, Attribute)] -> NamedAttributes
forall a b. (a -> b) -> a -> b
$ [(ByteString
"case_operand_segments", [Int] -> Attribute
PatternUtil.I32ArrayAttr [Int]
case_operand_segments_)]