{-# language CPP #-}
module Vulkan.Extensions.VK_NV_cooperative_matrix ( getPhysicalDeviceCooperativeMatrixPropertiesNV
, pattern SCOPE_DEVICE_NV
, pattern SCOPE_WORKGROUP_NV
, pattern SCOPE_SUBGROUP_NV
, pattern SCOPE_QUEUE_FAMILY_NV
, pattern COMPONENT_TYPE_FLOAT16_NV
, pattern COMPONENT_TYPE_FLOAT32_NV
, pattern COMPONENT_TYPE_FLOAT64_NV
, pattern COMPONENT_TYPE_SINT8_NV
, pattern COMPONENT_TYPE_SINT16_NV
, pattern COMPONENT_TYPE_SINT32_NV
, pattern COMPONENT_TYPE_SINT64_NV
, pattern COMPONENT_TYPE_UINT8_NV
, pattern COMPONENT_TYPE_UINT16_NV
, pattern COMPONENT_TYPE_UINT32_NV
, pattern COMPONENT_TYPE_UINT64_NV
, PhysicalDeviceCooperativeMatrixFeaturesNV(..)
, PhysicalDeviceCooperativeMatrixPropertiesNV(..)
, CooperativeMatrixPropertiesNV(..)
, ScopeNV
, ComponentTypeNV
, NV_COOPERATIVE_MATRIX_SPEC_VERSION
, pattern NV_COOPERATIVE_MATRIX_SPEC_VERSION
, NV_COOPERATIVE_MATRIX_EXTENSION_NAME
, pattern NV_COOPERATIVE_MATRIX_EXTENSION_NAME
, ScopeKHR(..)
, ComponentTypeKHR(..)
) where
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ComponentTypeKHR)
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceCooperativeMatrixPropertiesNV))
import Vulkan.Core10.Handles (PhysicalDevice)
import Vulkan.Core10.Handles (PhysicalDevice(..))
import Vulkan.Core10.Handles (PhysicalDevice(PhysicalDevice))
import Vulkan.Core10.Handles (PhysicalDevice_T)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ScopeKHR)
import Vulkan.Core10.Enums.ShaderStageFlagBits (ShaderStageFlags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ComponentTypeKHR(COMPONENT_TYPE_FLOAT16_KHR))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ComponentTypeKHR(COMPONENT_TYPE_FLOAT32_KHR))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ComponentTypeKHR(COMPONENT_TYPE_FLOAT64_KHR))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ComponentTypeKHR(COMPONENT_TYPE_SINT16_KHR))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ComponentTypeKHR(COMPONENT_TYPE_SINT32_KHR))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ComponentTypeKHR(COMPONENT_TYPE_SINT64_KHR))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ComponentTypeKHR(COMPONENT_TYPE_SINT8_KHR))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ComponentTypeKHR(COMPONENT_TYPE_UINT16_KHR))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ComponentTypeKHR(COMPONENT_TYPE_UINT32_KHR))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ComponentTypeKHR(COMPONENT_TYPE_UINT64_KHR))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ComponentTypeKHR(COMPONENT_TYPE_UINT8_KHR))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ScopeKHR(SCOPE_DEVICE_KHR))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ScopeKHR(SCOPE_QUEUE_FAMILY_KHR))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ScopeKHR(SCOPE_SUBGROUP_KHR))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ScopeKHR(SCOPE_WORKGROUP_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_COOPERATIVE_MATRIX_PROPERTIES_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_FEATURES_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_PROPERTIES_NV))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ComponentTypeKHR(..))
import Vulkan.Extensions.VK_KHR_cooperative_matrix (ScopeKHR(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetPhysicalDeviceCooperativeMatrixPropertiesNV
:: FunPtr (Ptr PhysicalDevice_T -> Ptr Word32 -> Ptr CooperativeMatrixPropertiesNV -> IO Result) -> Ptr PhysicalDevice_T -> Ptr Word32 -> Ptr CooperativeMatrixPropertiesNV -> IO Result
getPhysicalDeviceCooperativeMatrixPropertiesNV :: forall io
. (MonadIO io)
=>
PhysicalDevice
-> io (Result, ("properties" ::: Vector CooperativeMatrixPropertiesNV))
getPhysicalDeviceCooperativeMatrixPropertiesNV :: forall (io :: * -> *).
MonadIO io =>
PhysicalDevice
-> io
(Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
getPhysicalDeviceCooperativeMatrixPropertiesNV PhysicalDevice
physicalDevice = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
let vkGetPhysicalDeviceCooperativeMatrixPropertiesNVPtr :: FunPtr
(Ptr PhysicalDevice_T
-> ("pPropertyCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO Result)
vkGetPhysicalDeviceCooperativeMatrixPropertiesNVPtr = InstanceCmds
-> FunPtr
(Ptr PhysicalDevice_T
-> ("pPropertyCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO Result)
pVkGetPhysicalDeviceCooperativeMatrixPropertiesNV (case PhysicalDevice
physicalDevice of PhysicalDevice{InstanceCmds
$sel:instanceCmds:PhysicalDevice :: PhysicalDevice -> InstanceCmds
instanceCmds :: InstanceCmds
instanceCmds} -> InstanceCmds
instanceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr PhysicalDevice_T
-> ("pPropertyCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO Result)
vkGetPhysicalDeviceCooperativeMatrixPropertiesNVPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetPhysicalDeviceCooperativeMatrixPropertiesNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetPhysicalDeviceCooperativeMatrixPropertiesNV' :: Ptr PhysicalDevice_T
-> ("pPropertyCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO Result
vkGetPhysicalDeviceCooperativeMatrixPropertiesNV' = FunPtr
(Ptr PhysicalDevice_T
-> ("pPropertyCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO Result)
-> Ptr PhysicalDevice_T
-> ("pPropertyCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO Result
mkVkGetPhysicalDeviceCooperativeMatrixPropertiesNV FunPtr
(Ptr PhysicalDevice_T
-> ("pPropertyCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO Result)
vkGetPhysicalDeviceCooperativeMatrixPropertiesNVPtr
let physicalDevice' :: Ptr PhysicalDevice_T
physicalDevice' = PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)
"pPropertyCount" ::: Ptr Word32
pPPropertyCount <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @Word32 Int
4) forall a. Ptr a -> IO ()
free
Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetPhysicalDeviceCooperativeMatrixPropertiesNV" (Ptr PhysicalDevice_T
-> ("pPropertyCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO Result
vkGetPhysicalDeviceCooperativeMatrixPropertiesNV'
Ptr PhysicalDevice_T
physicalDevice'
("pPropertyCount" ::: Ptr Word32
pPPropertyCount)
(forall a. Ptr a
nullPtr))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
Word32
pPropertyCount <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @Word32 "pPropertyCount" ::: Ptr Word32
pPPropertyCount
"pProperties" ::: Ptr CooperativeMatrixPropertiesNV
pPProperties <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @CooperativeMatrixPropertiesNV ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPropertyCount)) forall a. Num a => a -> a -> a
* Int
48)) forall a. Ptr a -> IO ()
free
[()]
_ <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\Int
i -> forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => Ptr a -> IO b -> IO b
pokeZeroCStruct ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
pPProperties forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
i forall a. Num a => a -> a -> a
* Int
48) :: Ptr CooperativeMatrixPropertiesNV) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())) [Int
0..(forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPropertyCount)) forall a. Num a => a -> a -> a
- Int
1]
Result
r' <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetPhysicalDeviceCooperativeMatrixPropertiesNV" (Ptr PhysicalDevice_T
-> ("pPropertyCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO Result
vkGetPhysicalDeviceCooperativeMatrixPropertiesNV'
Ptr PhysicalDevice_T
physicalDevice'
("pPropertyCount" ::: Ptr Word32
pPPropertyCount)
(("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
pPProperties)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r' forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r'))
Word32
pPropertyCount' <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @Word32 "pPropertyCount" ::: Ptr Word32
pPPropertyCount
"properties" ::: Vector CooperativeMatrixPropertiesNV
pProperties' <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPropertyCount')) (\Int
i -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @CooperativeMatrixPropertiesNV ((("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
pPProperties) forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
48 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr CooperativeMatrixPropertiesNV)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ((Result
r'), "properties" ::: Vector CooperativeMatrixPropertiesNV
pProperties')
pattern $bSCOPE_DEVICE_NV :: ScopeKHR
$mSCOPE_DEVICE_NV :: forall {r}. ScopeKHR -> ((# #) -> r) -> ((# #) -> r) -> r
SCOPE_DEVICE_NV = SCOPE_DEVICE_KHR
pattern $bSCOPE_WORKGROUP_NV :: ScopeKHR
$mSCOPE_WORKGROUP_NV :: forall {r}. ScopeKHR -> ((# #) -> r) -> ((# #) -> r) -> r
SCOPE_WORKGROUP_NV = SCOPE_WORKGROUP_KHR
pattern $bSCOPE_SUBGROUP_NV :: ScopeKHR
$mSCOPE_SUBGROUP_NV :: forall {r}. ScopeKHR -> ((# #) -> r) -> ((# #) -> r) -> r
SCOPE_SUBGROUP_NV = SCOPE_SUBGROUP_KHR
pattern $bSCOPE_QUEUE_FAMILY_NV :: ScopeKHR
$mSCOPE_QUEUE_FAMILY_NV :: forall {r}. ScopeKHR -> ((# #) -> r) -> ((# #) -> r) -> r
SCOPE_QUEUE_FAMILY_NV = SCOPE_QUEUE_FAMILY_KHR
pattern $bCOMPONENT_TYPE_FLOAT16_NV :: ComponentTypeKHR
$mCOMPONENT_TYPE_FLOAT16_NV :: forall {r}. ComponentTypeKHR -> ((# #) -> r) -> ((# #) -> r) -> r
COMPONENT_TYPE_FLOAT16_NV = COMPONENT_TYPE_FLOAT16_KHR
pattern $bCOMPONENT_TYPE_FLOAT32_NV :: ComponentTypeKHR
$mCOMPONENT_TYPE_FLOAT32_NV :: forall {r}. ComponentTypeKHR -> ((# #) -> r) -> ((# #) -> r) -> r
COMPONENT_TYPE_FLOAT32_NV = COMPONENT_TYPE_FLOAT32_KHR
pattern $bCOMPONENT_TYPE_FLOAT64_NV :: ComponentTypeKHR
$mCOMPONENT_TYPE_FLOAT64_NV :: forall {r}. ComponentTypeKHR -> ((# #) -> r) -> ((# #) -> r) -> r
COMPONENT_TYPE_FLOAT64_NV = COMPONENT_TYPE_FLOAT64_KHR
pattern $bCOMPONENT_TYPE_SINT8_NV :: ComponentTypeKHR
$mCOMPONENT_TYPE_SINT8_NV :: forall {r}. ComponentTypeKHR -> ((# #) -> r) -> ((# #) -> r) -> r
COMPONENT_TYPE_SINT8_NV = COMPONENT_TYPE_SINT8_KHR
pattern $bCOMPONENT_TYPE_SINT16_NV :: ComponentTypeKHR
$mCOMPONENT_TYPE_SINT16_NV :: forall {r}. ComponentTypeKHR -> ((# #) -> r) -> ((# #) -> r) -> r
COMPONENT_TYPE_SINT16_NV = COMPONENT_TYPE_SINT16_KHR
pattern $bCOMPONENT_TYPE_SINT32_NV :: ComponentTypeKHR
$mCOMPONENT_TYPE_SINT32_NV :: forall {r}. ComponentTypeKHR -> ((# #) -> r) -> ((# #) -> r) -> r
COMPONENT_TYPE_SINT32_NV = COMPONENT_TYPE_SINT32_KHR
pattern $bCOMPONENT_TYPE_SINT64_NV :: ComponentTypeKHR
$mCOMPONENT_TYPE_SINT64_NV :: forall {r}. ComponentTypeKHR -> ((# #) -> r) -> ((# #) -> r) -> r
COMPONENT_TYPE_SINT64_NV = COMPONENT_TYPE_SINT64_KHR
pattern $bCOMPONENT_TYPE_UINT8_NV :: ComponentTypeKHR
$mCOMPONENT_TYPE_UINT8_NV :: forall {r}. ComponentTypeKHR -> ((# #) -> r) -> ((# #) -> r) -> r
COMPONENT_TYPE_UINT8_NV = COMPONENT_TYPE_UINT8_KHR
pattern $bCOMPONENT_TYPE_UINT16_NV :: ComponentTypeKHR
$mCOMPONENT_TYPE_UINT16_NV :: forall {r}. ComponentTypeKHR -> ((# #) -> r) -> ((# #) -> r) -> r
COMPONENT_TYPE_UINT16_NV = COMPONENT_TYPE_UINT16_KHR
pattern $bCOMPONENT_TYPE_UINT32_NV :: ComponentTypeKHR
$mCOMPONENT_TYPE_UINT32_NV :: forall {r}. ComponentTypeKHR -> ((# #) -> r) -> ((# #) -> r) -> r
COMPONENT_TYPE_UINT32_NV = COMPONENT_TYPE_UINT32_KHR
pattern $bCOMPONENT_TYPE_UINT64_NV :: ComponentTypeKHR
$mCOMPONENT_TYPE_UINT64_NV :: forall {r}. ComponentTypeKHR -> ((# #) -> r) -> ((# #) -> r) -> r
COMPONENT_TYPE_UINT64_NV = COMPONENT_TYPE_UINT64_KHR
data PhysicalDeviceCooperativeMatrixFeaturesNV = PhysicalDeviceCooperativeMatrixFeaturesNV
{
PhysicalDeviceCooperativeMatrixFeaturesNV -> Bool
cooperativeMatrix :: Bool
,
PhysicalDeviceCooperativeMatrixFeaturesNV -> Bool
cooperativeMatrixRobustBufferAccess :: Bool
}
deriving (Typeable, PhysicalDeviceCooperativeMatrixFeaturesNV
-> PhysicalDeviceCooperativeMatrixFeaturesNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceCooperativeMatrixFeaturesNV
-> PhysicalDeviceCooperativeMatrixFeaturesNV -> Bool
$c/= :: PhysicalDeviceCooperativeMatrixFeaturesNV
-> PhysicalDeviceCooperativeMatrixFeaturesNV -> Bool
== :: PhysicalDeviceCooperativeMatrixFeaturesNV
-> PhysicalDeviceCooperativeMatrixFeaturesNV -> Bool
$c== :: PhysicalDeviceCooperativeMatrixFeaturesNV
-> PhysicalDeviceCooperativeMatrixFeaturesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceCooperativeMatrixFeaturesNV)
#endif
deriving instance Show PhysicalDeviceCooperativeMatrixFeaturesNV
instance ToCStruct PhysicalDeviceCooperativeMatrixFeaturesNV where
withCStruct :: forall b.
PhysicalDeviceCooperativeMatrixFeaturesNV
-> (Ptr PhysicalDeviceCooperativeMatrixFeaturesNV -> IO b) -> IO b
withCStruct PhysicalDeviceCooperativeMatrixFeaturesNV
x Ptr PhysicalDeviceCooperativeMatrixFeaturesNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p PhysicalDeviceCooperativeMatrixFeaturesNV
x (Ptr PhysicalDeviceCooperativeMatrixFeaturesNV -> IO b
f Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
-> PhysicalDeviceCooperativeMatrixFeaturesNV -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p PhysicalDeviceCooperativeMatrixFeaturesNV{Bool
cooperativeMatrixRobustBufferAccess :: Bool
cooperativeMatrix :: Bool
$sel:cooperativeMatrixRobustBufferAccess:PhysicalDeviceCooperativeMatrixFeaturesNV :: PhysicalDeviceCooperativeMatrixFeaturesNV -> Bool
$sel:cooperativeMatrix:PhysicalDeviceCooperativeMatrixFeaturesNV :: PhysicalDeviceCooperativeMatrixFeaturesNV -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_FEATURES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
cooperativeMatrix))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
cooperativeMatrixRobustBufferAccess))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceCooperativeMatrixFeaturesNV -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_FEATURES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceCooperativeMatrixFeaturesNV where
peekCStruct :: Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
-> IO PhysicalDeviceCooperativeMatrixFeaturesNV
peekCStruct Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p = do
Bool32
cooperativeMatrix <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
cooperativeMatrixRobustBufferAccess <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> PhysicalDeviceCooperativeMatrixFeaturesNV
PhysicalDeviceCooperativeMatrixFeaturesNV
(Bool32 -> Bool
bool32ToBool Bool32
cooperativeMatrix)
(Bool32 -> Bool
bool32ToBool Bool32
cooperativeMatrixRobustBufferAccess)
instance Storable PhysicalDeviceCooperativeMatrixFeaturesNV where
sizeOf :: PhysicalDeviceCooperativeMatrixFeaturesNV -> Int
sizeOf ~PhysicalDeviceCooperativeMatrixFeaturesNV
_ = Int
24
alignment :: PhysicalDeviceCooperativeMatrixFeaturesNV -> Int
alignment ~PhysicalDeviceCooperativeMatrixFeaturesNV
_ = Int
8
peek :: Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
-> IO PhysicalDeviceCooperativeMatrixFeaturesNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
-> PhysicalDeviceCooperativeMatrixFeaturesNV -> IO ()
poke Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
ptr PhysicalDeviceCooperativeMatrixFeaturesNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
ptr PhysicalDeviceCooperativeMatrixFeaturesNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceCooperativeMatrixFeaturesNV where
zero :: PhysicalDeviceCooperativeMatrixFeaturesNV
zero = Bool -> Bool -> PhysicalDeviceCooperativeMatrixFeaturesNV
PhysicalDeviceCooperativeMatrixFeaturesNV
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data PhysicalDeviceCooperativeMatrixPropertiesNV = PhysicalDeviceCooperativeMatrixPropertiesNV
{
PhysicalDeviceCooperativeMatrixPropertiesNV -> ShaderStageFlags
cooperativeMatrixSupportedStages :: ShaderStageFlags }
deriving (Typeable, PhysicalDeviceCooperativeMatrixPropertiesNV
-> PhysicalDeviceCooperativeMatrixPropertiesNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceCooperativeMatrixPropertiesNV
-> PhysicalDeviceCooperativeMatrixPropertiesNV -> Bool
$c/= :: PhysicalDeviceCooperativeMatrixPropertiesNV
-> PhysicalDeviceCooperativeMatrixPropertiesNV -> Bool
== :: PhysicalDeviceCooperativeMatrixPropertiesNV
-> PhysicalDeviceCooperativeMatrixPropertiesNV -> Bool
$c== :: PhysicalDeviceCooperativeMatrixPropertiesNV
-> PhysicalDeviceCooperativeMatrixPropertiesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceCooperativeMatrixPropertiesNV)
#endif
deriving instance Show PhysicalDeviceCooperativeMatrixPropertiesNV
instance ToCStruct PhysicalDeviceCooperativeMatrixPropertiesNV where
withCStruct :: forall b.
PhysicalDeviceCooperativeMatrixPropertiesNV
-> (Ptr PhysicalDeviceCooperativeMatrixPropertiesNV -> IO b)
-> IO b
withCStruct PhysicalDeviceCooperativeMatrixPropertiesNV
x Ptr PhysicalDeviceCooperativeMatrixPropertiesNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p PhysicalDeviceCooperativeMatrixPropertiesNV
x (Ptr PhysicalDeviceCooperativeMatrixPropertiesNV -> IO b
f Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> PhysicalDeviceCooperativeMatrixPropertiesNV -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p PhysicalDeviceCooperativeMatrixPropertiesNV{ShaderStageFlags
cooperativeMatrixSupportedStages :: ShaderStageFlags
$sel:cooperativeMatrixSupportedStages:PhysicalDeviceCooperativeMatrixPropertiesNV :: PhysicalDeviceCooperativeMatrixPropertiesNV -> ShaderStageFlags
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_PROPERTIES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ShaderStageFlags)) (ShaderStageFlags
cooperativeMatrixSupportedStages)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceCooperativeMatrixPropertiesNV -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_PROPERTIES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ShaderStageFlags)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PhysicalDeviceCooperativeMatrixPropertiesNV where
peekCStruct :: Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> IO PhysicalDeviceCooperativeMatrixPropertiesNV
peekCStruct Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p = do
ShaderStageFlags
cooperativeMatrixSupportedStages <- forall a. Storable a => Ptr a -> IO a
peek @ShaderStageFlags ((Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ShaderStageFlags))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ShaderStageFlags -> PhysicalDeviceCooperativeMatrixPropertiesNV
PhysicalDeviceCooperativeMatrixPropertiesNV
ShaderStageFlags
cooperativeMatrixSupportedStages
instance Storable PhysicalDeviceCooperativeMatrixPropertiesNV where
sizeOf :: PhysicalDeviceCooperativeMatrixPropertiesNV -> Int
sizeOf ~PhysicalDeviceCooperativeMatrixPropertiesNV
_ = Int
24
alignment :: PhysicalDeviceCooperativeMatrixPropertiesNV -> Int
alignment ~PhysicalDeviceCooperativeMatrixPropertiesNV
_ = Int
8
peek :: Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> IO PhysicalDeviceCooperativeMatrixPropertiesNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> PhysicalDeviceCooperativeMatrixPropertiesNV -> IO ()
poke Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
ptr PhysicalDeviceCooperativeMatrixPropertiesNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
ptr PhysicalDeviceCooperativeMatrixPropertiesNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceCooperativeMatrixPropertiesNV where
zero :: PhysicalDeviceCooperativeMatrixPropertiesNV
zero = ShaderStageFlags -> PhysicalDeviceCooperativeMatrixPropertiesNV
PhysicalDeviceCooperativeMatrixPropertiesNV
forall a. Zero a => a
zero
data CooperativeMatrixPropertiesNV = CooperativeMatrixPropertiesNV
{
CooperativeMatrixPropertiesNV -> Word32
mSize :: Word32
,
CooperativeMatrixPropertiesNV -> Word32
nSize :: Word32
,
CooperativeMatrixPropertiesNV -> Word32
kSize :: Word32
,
CooperativeMatrixPropertiesNV -> ComponentTypeKHR
aType :: ComponentTypeNV
,
CooperativeMatrixPropertiesNV -> ComponentTypeKHR
bType :: ComponentTypeNV
,
CooperativeMatrixPropertiesNV -> ComponentTypeKHR
cType :: ComponentTypeNV
,
CooperativeMatrixPropertiesNV -> ComponentTypeKHR
dType :: ComponentTypeNV
,
CooperativeMatrixPropertiesNV -> ScopeKHR
scope :: ScopeNV
}
deriving (Typeable, CooperativeMatrixPropertiesNV
-> CooperativeMatrixPropertiesNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CooperativeMatrixPropertiesNV
-> CooperativeMatrixPropertiesNV -> Bool
$c/= :: CooperativeMatrixPropertiesNV
-> CooperativeMatrixPropertiesNV -> Bool
== :: CooperativeMatrixPropertiesNV
-> CooperativeMatrixPropertiesNV -> Bool
$c== :: CooperativeMatrixPropertiesNV
-> CooperativeMatrixPropertiesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (CooperativeMatrixPropertiesNV)
#endif
deriving instance Show CooperativeMatrixPropertiesNV
instance ToCStruct CooperativeMatrixPropertiesNV where
withCStruct :: forall b.
CooperativeMatrixPropertiesNV
-> (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV) -> IO b)
-> IO b
withCStruct CooperativeMatrixPropertiesNV
x ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
48 forall a b. (a -> b) -> a -> b
$ \"pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p CooperativeMatrixPropertiesNV
x (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV) -> IO b
f "pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p)
pokeCStruct :: forall b.
("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> CooperativeMatrixPropertiesNV -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p CooperativeMatrixPropertiesNV{Word32
ComponentTypeKHR
ScopeKHR
scope :: ScopeKHR
dType :: ComponentTypeKHR
cType :: ComponentTypeKHR
bType :: ComponentTypeKHR
aType :: ComponentTypeKHR
kSize :: Word32
nSize :: Word32
mSize :: Word32
$sel:scope:CooperativeMatrixPropertiesNV :: CooperativeMatrixPropertiesNV -> ScopeKHR
$sel:dType:CooperativeMatrixPropertiesNV :: CooperativeMatrixPropertiesNV -> ComponentTypeKHR
$sel:cType:CooperativeMatrixPropertiesNV :: CooperativeMatrixPropertiesNV -> ComponentTypeKHR
$sel:bType:CooperativeMatrixPropertiesNV :: CooperativeMatrixPropertiesNV -> ComponentTypeKHR
$sel:aType:CooperativeMatrixPropertiesNV :: CooperativeMatrixPropertiesNV -> ComponentTypeKHR
$sel:kSize:CooperativeMatrixPropertiesNV :: CooperativeMatrixPropertiesNV -> Word32
$sel:nSize:CooperativeMatrixPropertiesNV :: CooperativeMatrixPropertiesNV -> Word32
$sel:mSize:CooperativeMatrixPropertiesNV :: CooperativeMatrixPropertiesNV -> Word32
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COOPERATIVE_MATRIX_PROPERTIES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
mSize)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32)) (Word32
nSize)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (Word32
kSize)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr ComponentTypeNV)) (ComponentTypeKHR
aType)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr ComponentTypeNV)) (ComponentTypeKHR
bType)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr ComponentTypeNV)) (ComponentTypeKHR
cType)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr ComponentTypeNV)) (ComponentTypeKHR
dType)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr ScopeNV)) (ScopeKHR
scope)
IO b
f
cStructSize :: Int
cStructSize = Int
48
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO b -> IO b
pokeZeroCStruct "pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COOPERATIVE_MATRIX_PROPERTIES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr ComponentTypeNV)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr ComponentTypeNV)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr ComponentTypeNV)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr ComponentTypeNV)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr ScopeNV)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct CooperativeMatrixPropertiesNV where
peekCStruct :: ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO CooperativeMatrixPropertiesNV
peekCStruct "pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p = do
Word32
mSize <- forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
Word32
nSize <- forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32))
Word32
kSize <- forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32))
ComponentTypeKHR
aType <- forall a. Storable a => Ptr a -> IO a
peek @ComponentTypeNV (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr ComponentTypeNV))
ComponentTypeKHR
bType <- forall a. Storable a => Ptr a -> IO a
peek @ComponentTypeNV (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr ComponentTypeNV))
ComponentTypeKHR
cType <- forall a. Storable a => Ptr a -> IO a
peek @ComponentTypeNV (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr ComponentTypeNV))
ComponentTypeKHR
dType <- forall a. Storable a => Ptr a -> IO a
peek @ComponentTypeNV (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr ComponentTypeNV))
ScopeKHR
scope <- forall a. Storable a => Ptr a -> IO a
peek @ScopeNV (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr ScopeNV))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word32
-> Word32
-> Word32
-> ComponentTypeKHR
-> ComponentTypeKHR
-> ComponentTypeKHR
-> ComponentTypeKHR
-> ScopeKHR
-> CooperativeMatrixPropertiesNV
CooperativeMatrixPropertiesNV
Word32
mSize Word32
nSize Word32
kSize ComponentTypeKHR
aType ComponentTypeKHR
bType ComponentTypeKHR
cType ComponentTypeKHR
dType ScopeKHR
scope
instance Storable CooperativeMatrixPropertiesNV where
sizeOf :: CooperativeMatrixPropertiesNV -> Int
sizeOf ~CooperativeMatrixPropertiesNV
_ = Int
48
alignment :: CooperativeMatrixPropertiesNV -> Int
alignment ~CooperativeMatrixPropertiesNV
_ = Int
8
peek :: ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO CooperativeMatrixPropertiesNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> CooperativeMatrixPropertiesNV -> IO ()
poke "pProperties" ::: Ptr CooperativeMatrixPropertiesNV
ptr CooperativeMatrixPropertiesNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr CooperativeMatrixPropertiesNV
ptr CooperativeMatrixPropertiesNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero CooperativeMatrixPropertiesNV where
zero :: CooperativeMatrixPropertiesNV
zero = Word32
-> Word32
-> Word32
-> ComponentTypeKHR
-> ComponentTypeKHR
-> ComponentTypeKHR
-> ComponentTypeKHR
-> ScopeKHR
-> CooperativeMatrixPropertiesNV
CooperativeMatrixPropertiesNV
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
type ScopeNV = ScopeKHR
type ComponentTypeNV = ComponentTypeKHR
type NV_COOPERATIVE_MATRIX_SPEC_VERSION = 1
pattern NV_COOPERATIVE_MATRIX_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_COOPERATIVE_MATRIX_SPEC_VERSION :: forall a. Integral a => a
$mNV_COOPERATIVE_MATRIX_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_COOPERATIVE_MATRIX_SPEC_VERSION = 1
type NV_COOPERATIVE_MATRIX_EXTENSION_NAME = "VK_NV_cooperative_matrix"
pattern NV_COOPERATIVE_MATRIX_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_COOPERATIVE_MATRIX_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNV_COOPERATIVE_MATRIX_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_COOPERATIVE_MATRIX_EXTENSION_NAME = "VK_NV_cooperative_matrix"