{-# OPTIONS_HADDOCK hide #-}
module MLIR.Native.FFI where
import Foreign.Ptr
import Foreign.Storable
import qualified Language.C.Inline as C
import qualified Language.C.Types as C
import qualified Language.C.Inline.Context as C.Context
import Text.RawString.QQ
import Data.Int
import Data.Coerce
import qualified Data.Map as Map
C.include "<string.h>"
C.include "<stdlib.h>"
C.include "mlir-c/Support.h"
C.verbatim [r|
void HaskellMlirStringCallback(MlirStringRef ref, void* ctxRaw) {
void** ctx = ctxRaw;
char** data_ptr = ctxRaw;
size_t* size_ptr = ctx[1];
size_t old_size = *size_ptr;
size_t new_size = old_size + ref.length;
if (new_size == 0) return;
*data_ptr = realloc(*data_ptr, new_size);
*size_ptr = new_size;
memcpy((*data_ptr) + old_size, ref.data, ref.length);
}
|]
stringCallbackDecl :: String
stringCallbackDecl :: String
stringCallbackDecl = [r|
void HaskellMlirStringCallback(MlirStringRef ref, void* ctxRaw);
|]
data MlirContextObject
data MlirLocationObject
data MlirModuleObject
data MlirOperationObject
data MlirPassManagerObject
data MlirPassObject
data MlirExecutionEngineObject
data MlirTypeObject
data MlirBlockObject
data MlirRegionObject
data MlirAttributeObject
data MlirValueObject
data MlirIdentifierObject
data MlirAffineExprObject
data MlirAffineMapObject
newtype Context = ContextPtr (Ptr MlirContextObject)
deriving Ptr b -> Int -> IO Context
Ptr b -> Int -> Context -> IO ()
Ptr Context -> IO Context
Ptr Context -> Int -> IO Context
Ptr Context -> Int -> Context -> IO ()
Ptr Context -> Context -> IO ()
Context -> Int
(Context -> Int)
-> (Context -> Int)
-> (Ptr Context -> Int -> IO Context)
-> (Ptr Context -> Int -> Context -> IO ())
-> (forall b. Ptr b -> Int -> IO Context)
-> (forall b. Ptr b -> Int -> Context -> IO ())
-> (Ptr Context -> IO Context)
-> (Ptr Context -> Context -> IO ())
-> Storable Context
forall b. Ptr b -> Int -> IO Context
forall b. Ptr b -> Int -> Context -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr Context -> Context -> IO ()
$cpoke :: Ptr Context -> Context -> IO ()
peek :: Ptr Context -> IO Context
$cpeek :: Ptr Context -> IO Context
pokeByteOff :: Ptr b -> Int -> Context -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Context -> IO ()
peekByteOff :: Ptr b -> Int -> IO Context
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Context
pokeElemOff :: Ptr Context -> Int -> Context -> IO ()
$cpokeElemOff :: Ptr Context -> Int -> Context -> IO ()
peekElemOff :: Ptr Context -> Int -> IO Context
$cpeekElemOff :: Ptr Context -> Int -> IO Context
alignment :: Context -> Int
$calignment :: Context -> Int
sizeOf :: Context -> Int
$csizeOf :: Context -> Int
Storable via (Ptr ())
newtype Pass = PassPtr (Ptr MlirPassObject)
deriving Ptr b -> Int -> IO Pass
Ptr b -> Int -> Pass -> IO ()
Ptr Pass -> IO Pass
Ptr Pass -> Int -> IO Pass
Ptr Pass -> Int -> Pass -> IO ()
Ptr Pass -> Pass -> IO ()
Pass -> Int
(Pass -> Int)
-> (Pass -> Int)
-> (Ptr Pass -> Int -> IO Pass)
-> (Ptr Pass -> Int -> Pass -> IO ())
-> (forall b. Ptr b -> Int -> IO Pass)
-> (forall b. Ptr b -> Int -> Pass -> IO ())
-> (Ptr Pass -> IO Pass)
-> (Ptr Pass -> Pass -> IO ())
-> Storable Pass
forall b. Ptr b -> Int -> IO Pass
forall b. Ptr b -> Int -> Pass -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr Pass -> Pass -> IO ()
$cpoke :: Ptr Pass -> Pass -> IO ()
peek :: Ptr Pass -> IO Pass
$cpeek :: Ptr Pass -> IO Pass
pokeByteOff :: Ptr b -> Int -> Pass -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Pass -> IO ()
peekByteOff :: Ptr b -> Int -> IO Pass
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Pass
pokeElemOff :: Ptr Pass -> Int -> Pass -> IO ()
$cpokeElemOff :: Ptr Pass -> Int -> Pass -> IO ()
peekElemOff :: Ptr Pass -> Int -> IO Pass
$cpeekElemOff :: Ptr Pass -> Int -> IO Pass
alignment :: Pass -> Int
$calignment :: Pass -> Int
sizeOf :: Pass -> Int
$csizeOf :: Pass -> Int
Storable via (Ptr ())
newtype PassManager = PassManagerPtr (Ptr MlirPassManagerObject)
deriving Ptr b -> Int -> IO PassManager
Ptr b -> Int -> PassManager -> IO ()
Ptr PassManager -> IO PassManager
Ptr PassManager -> Int -> IO PassManager
Ptr PassManager -> Int -> PassManager -> IO ()
Ptr PassManager -> PassManager -> IO ()
PassManager -> Int
(PassManager -> Int)
-> (PassManager -> Int)
-> (Ptr PassManager -> Int -> IO PassManager)
-> (Ptr PassManager -> Int -> PassManager -> IO ())
-> (forall b. Ptr b -> Int -> IO PassManager)
-> (forall b. Ptr b -> Int -> PassManager -> IO ())
-> (Ptr PassManager -> IO PassManager)
-> (Ptr PassManager -> PassManager -> IO ())
-> Storable PassManager
forall b. Ptr b -> Int -> IO PassManager
forall b. Ptr b -> Int -> PassManager -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr PassManager -> PassManager -> IO ()
$cpoke :: Ptr PassManager -> PassManager -> IO ()
peek :: Ptr PassManager -> IO PassManager
$cpeek :: Ptr PassManager -> IO PassManager
pokeByteOff :: Ptr b -> Int -> PassManager -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> PassManager -> IO ()
peekByteOff :: Ptr b -> Int -> IO PassManager
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PassManager
pokeElemOff :: Ptr PassManager -> Int -> PassManager -> IO ()
$cpokeElemOff :: Ptr PassManager -> Int -> PassManager -> IO ()
peekElemOff :: Ptr PassManager -> Int -> IO PassManager
$cpeekElemOff :: Ptr PassManager -> Int -> IO PassManager
alignment :: PassManager -> Int
$calignment :: PassManager -> Int
sizeOf :: PassManager -> Int
$csizeOf :: PassManager -> Int
Storable via (Ptr ())
newtype Location = LocationPtr (Ptr MlirLocationObject)
deriving Ptr b -> Int -> IO Location
Ptr b -> Int -> Location -> IO ()
Ptr Location -> IO Location
Ptr Location -> Int -> IO Location
Ptr Location -> Int -> Location -> IO ()
Ptr Location -> Location -> IO ()
Location -> Int
(Location -> Int)
-> (Location -> Int)
-> (Ptr Location -> Int -> IO Location)
-> (Ptr Location -> Int -> Location -> IO ())
-> (forall b. Ptr b -> Int -> IO Location)
-> (forall b. Ptr b -> Int -> Location -> IO ())
-> (Ptr Location -> IO Location)
-> (Ptr Location -> Location -> IO ())
-> Storable Location
forall b. Ptr b -> Int -> IO Location
forall b. Ptr b -> Int -> Location -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr Location -> Location -> IO ()
$cpoke :: Ptr Location -> Location -> IO ()
peek :: Ptr Location -> IO Location
$cpeek :: Ptr Location -> IO Location
pokeByteOff :: Ptr b -> Int -> Location -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Location -> IO ()
peekByteOff :: Ptr b -> Int -> IO Location
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Location
pokeElemOff :: Ptr Location -> Int -> Location -> IO ()
$cpokeElemOff :: Ptr Location -> Int -> Location -> IO ()
peekElemOff :: Ptr Location -> Int -> IO Location
$cpeekElemOff :: Ptr Location -> Int -> IO Location
alignment :: Location -> Int
$calignment :: Location -> Int
sizeOf :: Location -> Int
$csizeOf :: Location -> Int
Storable via (Ptr ())
newtype Operation = OperationPtr (Ptr MlirOperationObject)
deriving Ptr b -> Int -> IO Operation
Ptr b -> Int -> Operation -> IO ()
Ptr Operation -> IO Operation
Ptr Operation -> Int -> IO Operation
Ptr Operation -> Int -> Operation -> IO ()
Ptr Operation -> Operation -> IO ()
Operation -> Int
(Operation -> Int)
-> (Operation -> Int)
-> (Ptr Operation -> Int -> IO Operation)
-> (Ptr Operation -> Int -> Operation -> IO ())
-> (forall b. Ptr b -> Int -> IO Operation)
-> (forall b. Ptr b -> Int -> Operation -> IO ())
-> (Ptr Operation -> IO Operation)
-> (Ptr Operation -> Operation -> IO ())
-> Storable Operation
forall b. Ptr b -> Int -> IO Operation
forall b. Ptr b -> Int -> Operation -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr Operation -> Operation -> IO ()
$cpoke :: Ptr Operation -> Operation -> IO ()
peek :: Ptr Operation -> IO Operation
$cpeek :: Ptr Operation -> IO Operation
pokeByteOff :: Ptr b -> Int -> Operation -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Operation -> IO ()
peekByteOff :: Ptr b -> Int -> IO Operation
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Operation
pokeElemOff :: Ptr Operation -> Int -> Operation -> IO ()
$cpokeElemOff :: Ptr Operation -> Int -> Operation -> IO ()
peekElemOff :: Ptr Operation -> Int -> IO Operation
$cpeekElemOff :: Ptr Operation -> Int -> IO Operation
alignment :: Operation -> Int
$calignment :: Operation -> Int
sizeOf :: Operation -> Int
$csizeOf :: Operation -> Int
Storable via (Ptr ())
newtype Module = ModulePtr (Ptr MlirModuleObject)
deriving Ptr b -> Int -> IO Module
Ptr b -> Int -> Module -> IO ()
Ptr Module -> IO Module
Ptr Module -> Int -> IO Module
Ptr Module -> Int -> Module -> IO ()
Ptr Module -> Module -> IO ()
Module -> Int
(Module -> Int)
-> (Module -> Int)
-> (Ptr Module -> Int -> IO Module)
-> (Ptr Module -> Int -> Module -> IO ())
-> (forall b. Ptr b -> Int -> IO Module)
-> (forall b. Ptr b -> Int -> Module -> IO ())
-> (Ptr Module -> IO Module)
-> (Ptr Module -> Module -> IO ())
-> Storable Module
forall b. Ptr b -> Int -> IO Module
forall b. Ptr b -> Int -> Module -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr Module -> Module -> IO ()
$cpoke :: Ptr Module -> Module -> IO ()
peek :: Ptr Module -> IO Module
$cpeek :: Ptr Module -> IO Module
pokeByteOff :: Ptr b -> Int -> Module -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Module -> IO ()
peekByteOff :: Ptr b -> Int -> IO Module
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Module
pokeElemOff :: Ptr Module -> Int -> Module -> IO ()
$cpokeElemOff :: Ptr Module -> Int -> Module -> IO ()
peekElemOff :: Ptr Module -> Int -> IO Module
$cpeekElemOff :: Ptr Module -> Int -> IO Module
alignment :: Module -> Int
$calignment :: Module -> Int
sizeOf :: Module -> Int
$csizeOf :: Module -> Int
Storable via (Ptr ())
newtype ExecutionEngine = ExecutionEnginePtr (Ptr MlirExecutionEngineObject)
deriving Ptr b -> Int -> IO ExecutionEngine
Ptr b -> Int -> ExecutionEngine -> IO ()
Ptr ExecutionEngine -> IO ExecutionEngine
Ptr ExecutionEngine -> Int -> IO ExecutionEngine
Ptr ExecutionEngine -> Int -> ExecutionEngine -> IO ()
Ptr ExecutionEngine -> ExecutionEngine -> IO ()
ExecutionEngine -> Int
(ExecutionEngine -> Int)
-> (ExecutionEngine -> Int)
-> (Ptr ExecutionEngine -> Int -> IO ExecutionEngine)
-> (Ptr ExecutionEngine -> Int -> ExecutionEngine -> IO ())
-> (forall b. Ptr b -> Int -> IO ExecutionEngine)
-> (forall b. Ptr b -> Int -> ExecutionEngine -> IO ())
-> (Ptr ExecutionEngine -> IO ExecutionEngine)
-> (Ptr ExecutionEngine -> ExecutionEngine -> IO ())
-> Storable ExecutionEngine
forall b. Ptr b -> Int -> IO ExecutionEngine
forall b. Ptr b -> Int -> ExecutionEngine -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr ExecutionEngine -> ExecutionEngine -> IO ()
$cpoke :: Ptr ExecutionEngine -> ExecutionEngine -> IO ()
peek :: Ptr ExecutionEngine -> IO ExecutionEngine
$cpeek :: Ptr ExecutionEngine -> IO ExecutionEngine
pokeByteOff :: Ptr b -> Int -> ExecutionEngine -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ExecutionEngine -> IO ()
peekByteOff :: Ptr b -> Int -> IO ExecutionEngine
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ExecutionEngine
pokeElemOff :: Ptr ExecutionEngine -> Int -> ExecutionEngine -> IO ()
$cpokeElemOff :: Ptr ExecutionEngine -> Int -> ExecutionEngine -> IO ()
peekElemOff :: Ptr ExecutionEngine -> Int -> IO ExecutionEngine
$cpeekElemOff :: Ptr ExecutionEngine -> Int -> IO ExecutionEngine
alignment :: ExecutionEngine -> Int
$calignment :: ExecutionEngine -> Int
sizeOf :: ExecutionEngine -> Int
$csizeOf :: ExecutionEngine -> Int
Storable via (Ptr ())
newtype Type = TypePtr (Ptr MlirTypeObject)
deriving Ptr b -> Int -> IO Type
Ptr b -> Int -> Type -> IO ()
Ptr Type -> IO Type
Ptr Type -> Int -> IO Type
Ptr Type -> Int -> Type -> IO ()
Ptr Type -> Type -> IO ()
Type -> Int
(Type -> Int)
-> (Type -> Int)
-> (Ptr Type -> Int -> IO Type)
-> (Ptr Type -> Int -> Type -> IO ())
-> (forall b. Ptr b -> Int -> IO Type)
-> (forall b. Ptr b -> Int -> Type -> IO ())
-> (Ptr Type -> IO Type)
-> (Ptr Type -> Type -> IO ())
-> Storable Type
forall b. Ptr b -> Int -> IO Type
forall b. Ptr b -> Int -> Type -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr Type -> Type -> IO ()
$cpoke :: Ptr Type -> Type -> IO ()
peek :: Ptr Type -> IO Type
$cpeek :: Ptr Type -> IO Type
pokeByteOff :: Ptr b -> Int -> Type -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Type -> IO ()
peekByteOff :: Ptr b -> Int -> IO Type
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Type
pokeElemOff :: Ptr Type -> Int -> Type -> IO ()
$cpokeElemOff :: Ptr Type -> Int -> Type -> IO ()
peekElemOff :: Ptr Type -> Int -> IO Type
$cpeekElemOff :: Ptr Type -> Int -> IO Type
alignment :: Type -> Int
$calignment :: Type -> Int
sizeOf :: Type -> Int
$csizeOf :: Type -> Int
Storable via (Ptr ())
newtype Block = BlockPtr (Ptr MlirBlockObject)
deriving Ptr b -> Int -> IO Block
Ptr b -> Int -> Block -> IO ()
Ptr Block -> IO Block
Ptr Block -> Int -> IO Block
Ptr Block -> Int -> Block -> IO ()
Ptr Block -> Block -> IO ()
Block -> Int
(Block -> Int)
-> (Block -> Int)
-> (Ptr Block -> Int -> IO Block)
-> (Ptr Block -> Int -> Block -> IO ())
-> (forall b. Ptr b -> Int -> IO Block)
-> (forall b. Ptr b -> Int -> Block -> IO ())
-> (Ptr Block -> IO Block)
-> (Ptr Block -> Block -> IO ())
-> Storable Block
forall b. Ptr b -> Int -> IO Block
forall b. Ptr b -> Int -> Block -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr Block -> Block -> IO ()
$cpoke :: Ptr Block -> Block -> IO ()
peek :: Ptr Block -> IO Block
$cpeek :: Ptr Block -> IO Block
pokeByteOff :: Ptr b -> Int -> Block -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Block -> IO ()
peekByteOff :: Ptr b -> Int -> IO Block
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Block
pokeElemOff :: Ptr Block -> Int -> Block -> IO ()
$cpokeElemOff :: Ptr Block -> Int -> Block -> IO ()
peekElemOff :: Ptr Block -> Int -> IO Block
$cpeekElemOff :: Ptr Block -> Int -> IO Block
alignment :: Block -> Int
$calignment :: Block -> Int
sizeOf :: Block -> Int
$csizeOf :: Block -> Int
Storable via (Ptr ())
newtype Region = RegionPtr (Ptr MlirRegionObject)
deriving Ptr b -> Int -> IO Region
Ptr b -> Int -> Region -> IO ()
Ptr Region -> IO Region
Ptr Region -> Int -> IO Region
Ptr Region -> Int -> Region -> IO ()
Ptr Region -> Region -> IO ()
Region -> Int
(Region -> Int)
-> (Region -> Int)
-> (Ptr Region -> Int -> IO Region)
-> (Ptr Region -> Int -> Region -> IO ())
-> (forall b. Ptr b -> Int -> IO Region)
-> (forall b. Ptr b -> Int -> Region -> IO ())
-> (Ptr Region -> IO Region)
-> (Ptr Region -> Region -> IO ())
-> Storable Region
forall b. Ptr b -> Int -> IO Region
forall b. Ptr b -> Int -> Region -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr Region -> Region -> IO ()
$cpoke :: Ptr Region -> Region -> IO ()
peek :: Ptr Region -> IO Region
$cpeek :: Ptr Region -> IO Region
pokeByteOff :: Ptr b -> Int -> Region -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Region -> IO ()
peekByteOff :: Ptr b -> Int -> IO Region
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Region
pokeElemOff :: Ptr Region -> Int -> Region -> IO ()
$cpokeElemOff :: Ptr Region -> Int -> Region -> IO ()
peekElemOff :: Ptr Region -> Int -> IO Region
$cpeekElemOff :: Ptr Region -> Int -> IO Region
alignment :: Region -> Int
$calignment :: Region -> Int
sizeOf :: Region -> Int
$csizeOf :: Region -> Int
Storable via (Ptr ())
newtype Attribute = AttributePtr (Ptr MlirAttributeObject)
deriving Ptr b -> Int -> IO Attribute
Ptr b -> Int -> Attribute -> IO ()
Ptr Attribute -> IO Attribute
Ptr Attribute -> Int -> IO Attribute
Ptr Attribute -> Int -> Attribute -> IO ()
Ptr Attribute -> Attribute -> IO ()
Attribute -> Int
(Attribute -> Int)
-> (Attribute -> Int)
-> (Ptr Attribute -> Int -> IO Attribute)
-> (Ptr Attribute -> Int -> Attribute -> IO ())
-> (forall b. Ptr b -> Int -> IO Attribute)
-> (forall b. Ptr b -> Int -> Attribute -> IO ())
-> (Ptr Attribute -> IO Attribute)
-> (Ptr Attribute -> Attribute -> IO ())
-> Storable Attribute
forall b. Ptr b -> Int -> IO Attribute
forall b. Ptr b -> Int -> Attribute -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr Attribute -> Attribute -> IO ()
$cpoke :: Ptr Attribute -> Attribute -> IO ()
peek :: Ptr Attribute -> IO Attribute
$cpeek :: Ptr Attribute -> IO Attribute
pokeByteOff :: Ptr b -> Int -> Attribute -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Attribute -> IO ()
peekByteOff :: Ptr b -> Int -> IO Attribute
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Attribute
pokeElemOff :: Ptr Attribute -> Int -> Attribute -> IO ()
$cpokeElemOff :: Ptr Attribute -> Int -> Attribute -> IO ()
peekElemOff :: Ptr Attribute -> Int -> IO Attribute
$cpeekElemOff :: Ptr Attribute -> Int -> IO Attribute
alignment :: Attribute -> Int
$calignment :: Attribute -> Int
sizeOf :: Attribute -> Int
$csizeOf :: Attribute -> Int
Storable via (Ptr ())
newtype Value = ValuePtr (Ptr MlirValueObject)
deriving Ptr b -> Int -> IO Value
Ptr b -> Int -> Value -> IO ()
Ptr Value -> IO Value
Ptr Value -> Int -> IO Value
Ptr Value -> Int -> Value -> IO ()
Ptr Value -> Value -> IO ()
Value -> Int
(Value -> Int)
-> (Value -> Int)
-> (Ptr Value -> Int -> IO Value)
-> (Ptr Value -> Int -> Value -> IO ())
-> (forall b. Ptr b -> Int -> IO Value)
-> (forall b. Ptr b -> Int -> Value -> IO ())
-> (Ptr Value -> IO Value)
-> (Ptr Value -> Value -> IO ())
-> Storable Value
forall b. Ptr b -> Int -> IO Value
forall b. Ptr b -> Int -> Value -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr Value -> Value -> IO ()
$cpoke :: Ptr Value -> Value -> IO ()
peek :: Ptr Value -> IO Value
$cpeek :: Ptr Value -> IO Value
pokeByteOff :: Ptr b -> Int -> Value -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Value -> IO ()
peekByteOff :: Ptr b -> Int -> IO Value
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Value
pokeElemOff :: Ptr Value -> Int -> Value -> IO ()
$cpokeElemOff :: Ptr Value -> Int -> Value -> IO ()
peekElemOff :: Ptr Value -> Int -> IO Value
$cpeekElemOff :: Ptr Value -> Int -> IO Value
alignment :: Value -> Int
$calignment :: Value -> Int
sizeOf :: Value -> Int
$csizeOf :: Value -> Int
Storable via (Ptr ())
newtype Identifier = IdentifierPtr (Ptr MlirIdentifierObject)
deriving Ptr b -> Int -> IO Identifier
Ptr b -> Int -> Identifier -> IO ()
Ptr Identifier -> IO Identifier
Ptr Identifier -> Int -> IO Identifier
Ptr Identifier -> Int -> Identifier -> IO ()
Ptr Identifier -> Identifier -> IO ()
Identifier -> Int
(Identifier -> Int)
-> (Identifier -> Int)
-> (Ptr Identifier -> Int -> IO Identifier)
-> (Ptr Identifier -> Int -> Identifier -> IO ())
-> (forall b. Ptr b -> Int -> IO Identifier)
-> (forall b. Ptr b -> Int -> Identifier -> IO ())
-> (Ptr Identifier -> IO Identifier)
-> (Ptr Identifier -> Identifier -> IO ())
-> Storable Identifier
forall b. Ptr b -> Int -> IO Identifier
forall b. Ptr b -> Int -> Identifier -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr Identifier -> Identifier -> IO ()
$cpoke :: Ptr Identifier -> Identifier -> IO ()
peek :: Ptr Identifier -> IO Identifier
$cpeek :: Ptr Identifier -> IO Identifier
pokeByteOff :: Ptr b -> Int -> Identifier -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Identifier -> IO ()
peekByteOff :: Ptr b -> Int -> IO Identifier
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Identifier
pokeElemOff :: Ptr Identifier -> Int -> Identifier -> IO ()
$cpokeElemOff :: Ptr Identifier -> Int -> Identifier -> IO ()
peekElemOff :: Ptr Identifier -> Int -> IO Identifier
$cpeekElemOff :: Ptr Identifier -> Int -> IO Identifier
alignment :: Identifier -> Int
$calignment :: Identifier -> Int
sizeOf :: Identifier -> Int
$csizeOf :: Identifier -> Int
Storable via (Ptr ())
newtype AffineExpr = AffineExprPtr (Ptr MlirAffineExprObject)
deriving Ptr b -> Int -> IO AffineExpr
Ptr b -> Int -> AffineExpr -> IO ()
Ptr AffineExpr -> IO AffineExpr
Ptr AffineExpr -> Int -> IO AffineExpr
Ptr AffineExpr -> Int -> AffineExpr -> IO ()
Ptr AffineExpr -> AffineExpr -> IO ()
AffineExpr -> Int
(AffineExpr -> Int)
-> (AffineExpr -> Int)
-> (Ptr AffineExpr -> Int -> IO AffineExpr)
-> (Ptr AffineExpr -> Int -> AffineExpr -> IO ())
-> (forall b. Ptr b -> Int -> IO AffineExpr)
-> (forall b. Ptr b -> Int -> AffineExpr -> IO ())
-> (Ptr AffineExpr -> IO AffineExpr)
-> (Ptr AffineExpr -> AffineExpr -> IO ())
-> Storable AffineExpr
forall b. Ptr b -> Int -> IO AffineExpr
forall b. Ptr b -> Int -> AffineExpr -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr AffineExpr -> AffineExpr -> IO ()
$cpoke :: Ptr AffineExpr -> AffineExpr -> IO ()
peek :: Ptr AffineExpr -> IO AffineExpr
$cpeek :: Ptr AffineExpr -> IO AffineExpr
pokeByteOff :: Ptr b -> Int -> AffineExpr -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> AffineExpr -> IO ()
peekByteOff :: Ptr b -> Int -> IO AffineExpr
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AffineExpr
pokeElemOff :: Ptr AffineExpr -> Int -> AffineExpr -> IO ()
$cpokeElemOff :: Ptr AffineExpr -> Int -> AffineExpr -> IO ()
peekElemOff :: Ptr AffineExpr -> Int -> IO AffineExpr
$cpeekElemOff :: Ptr AffineExpr -> Int -> IO AffineExpr
alignment :: AffineExpr -> Int
$calignment :: AffineExpr -> Int
sizeOf :: AffineExpr -> Int
$csizeOf :: AffineExpr -> Int
Storable via (Ptr ())
newtype AffineMap = AffineMapPtr (Ptr MlirAffineMapObject)
deriving Ptr b -> Int -> IO AffineMap
Ptr b -> Int -> AffineMap -> IO ()
Ptr AffineMap -> IO AffineMap
Ptr AffineMap -> Int -> IO AffineMap
Ptr AffineMap -> Int -> AffineMap -> IO ()
Ptr AffineMap -> AffineMap -> IO ()
AffineMap -> Int
(AffineMap -> Int)
-> (AffineMap -> Int)
-> (Ptr AffineMap -> Int -> IO AffineMap)
-> (Ptr AffineMap -> Int -> AffineMap -> IO ())
-> (forall b. Ptr b -> Int -> IO AffineMap)
-> (forall b. Ptr b -> Int -> AffineMap -> IO ())
-> (Ptr AffineMap -> IO AffineMap)
-> (Ptr AffineMap -> AffineMap -> IO ())
-> Storable AffineMap
forall b. Ptr b -> Int -> IO AffineMap
forall b. Ptr b -> Int -> AffineMap -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr AffineMap -> AffineMap -> IO ()
$cpoke :: Ptr AffineMap -> AffineMap -> IO ()
peek :: Ptr AffineMap -> IO AffineMap
$cpeek :: Ptr AffineMap -> IO AffineMap
pokeByteOff :: Ptr b -> Int -> AffineMap -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> AffineMap -> IO ()
peekByteOff :: Ptr b -> Int -> IO AffineMap
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AffineMap
pokeElemOff :: Ptr AffineMap -> Int -> AffineMap -> IO ()
$cpokeElemOff :: Ptr AffineMap -> Int -> AffineMap -> IO ()
peekElemOff :: Ptr AffineMap -> Int -> IO AffineMap
$cpeekElemOff :: Ptr AffineMap -> Int -> IO AffineMap
alignment :: AffineMap -> Int
$calignment :: AffineMap -> Int
sizeOf :: AffineMap -> Int
$csizeOf :: AffineMap -> Int
Storable via (Ptr ())
data NamedAttribute
newtype LogicalResult = UnsafeMkLogicalResult Int8
deriving Ptr b -> Int -> IO LogicalResult
Ptr b -> Int -> LogicalResult -> IO ()
Ptr LogicalResult -> IO LogicalResult
Ptr LogicalResult -> Int -> IO LogicalResult
Ptr LogicalResult -> Int -> LogicalResult -> IO ()
Ptr LogicalResult -> LogicalResult -> IO ()
LogicalResult -> Int
(LogicalResult -> Int)
-> (LogicalResult -> Int)
-> (Ptr LogicalResult -> Int -> IO LogicalResult)
-> (Ptr LogicalResult -> Int -> LogicalResult -> IO ())
-> (forall b. Ptr b -> Int -> IO LogicalResult)
-> (forall b. Ptr b -> Int -> LogicalResult -> IO ())
-> (Ptr LogicalResult -> IO LogicalResult)
-> (Ptr LogicalResult -> LogicalResult -> IO ())
-> Storable LogicalResult
forall b. Ptr b -> Int -> IO LogicalResult
forall b. Ptr b -> Int -> LogicalResult -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr LogicalResult -> LogicalResult -> IO ()
$cpoke :: Ptr LogicalResult -> LogicalResult -> IO ()
peek :: Ptr LogicalResult -> IO LogicalResult
$cpeek :: Ptr LogicalResult -> IO LogicalResult
pokeByteOff :: Ptr b -> Int -> LogicalResult -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> LogicalResult -> IO ()
peekByteOff :: Ptr b -> Int -> IO LogicalResult
$cpeekByteOff :: forall b. Ptr b -> Int -> IO LogicalResult
pokeElemOff :: Ptr LogicalResult -> Int -> LogicalResult -> IO ()
$cpokeElemOff :: Ptr LogicalResult -> Int -> LogicalResult -> IO ()
peekElemOff :: Ptr LogicalResult -> Int -> IO LogicalResult
$cpeekElemOff :: Ptr LogicalResult -> Int -> IO LogicalResult
alignment :: LogicalResult -> Int
$calignment :: LogicalResult -> Int
sizeOf :: LogicalResult -> Int
$csizeOf :: LogicalResult -> Int
Storable via Int8
deriving LogicalResult -> LogicalResult -> Bool
(LogicalResult -> LogicalResult -> Bool)
-> (LogicalResult -> LogicalResult -> Bool) -> Eq LogicalResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogicalResult -> LogicalResult -> Bool
$c/= :: LogicalResult -> LogicalResult -> Bool
== :: LogicalResult -> LogicalResult -> Bool
$c== :: LogicalResult -> LogicalResult -> Bool
Eq
instance Show LogicalResult where
show :: LogicalResult -> String
show LogicalResult
Success = String
"Success"
show LogicalResult
Failure = String
"Failure"
pattern Success :: LogicalResult
pattern $bSuccess :: LogicalResult
$mSuccess :: forall r. LogicalResult -> (Void# -> r) -> (Void# -> r) -> r
Success = UnsafeMkLogicalResult 1
pattern Failure :: LogicalResult
pattern $bFailure :: LogicalResult
$mFailure :: forall r. LogicalResult -> (Void# -> r) -> (Void# -> r) -> r
Failure = UnsafeMkLogicalResult 0
{-# COMPLETE Success, Failure #-}
mlirCtx :: C.Context
mlirCtx :: Context
mlirCtx = Context
forall a. Monoid a => a
mempty {
ctxTypesTable :: TypesTable
C.Context.ctxTypesTable = [(TypeSpecifier, TypeQ)] -> TypesTable
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirContext", [t|Context|])
, (CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirLocation", [t|Location|])
, (CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirModule", [t|Module|])
, (CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirOperation", [t|Operation|])
, (CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirPassManager", [t|PassManager|])
, (CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirPass", [t|Pass|])
, (CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirExecutionEngine", [t|ExecutionEngine|])
, (CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirLogicalResult", [t|LogicalResult|])
, (CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirType", [t|Type|])
, (CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirBlock", [t|Block|])
, (CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirRegion", [t|Region|])
, (CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirAttribute", [t|Attribute|])
, (CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirNamedAttribute", [t|NamedAttribute|])
, (CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirValue", [t|Value|])
, (CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirIdentifier", [t|Identifier|])
, (CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirAffineExpr", [t|AffineExpr|])
, (CIdentifier -> TypeSpecifier
C.TypeName CIdentifier
"MlirAffineMap", [t|AffineMap|])
]
}
nullable :: Coercible a (Ptr ()) => a -> Maybe a
nullable :: a -> Maybe a
nullable a
x = if a -> Ptr Any
coerce a
x Ptr Any -> Ptr Any -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Any
forall a. Ptr a
nullPtr then Maybe a
forall a. Maybe a
Nothing else a -> Maybe a
forall a. a -> Maybe a
Just a
x