{-# language CPP #-}
module Graphics.Vulkan.Extensions.VK_NV_cooperative_matrix ( getPhysicalDeviceCooperativeMatrixPropertiesNV
, PhysicalDeviceCooperativeMatrixFeaturesNV(..)
, PhysicalDeviceCooperativeMatrixPropertiesNV(..)
, CooperativeMatrixPropertiesNV(..)
, ScopeNV( SCOPE_DEVICE_NV
, SCOPE_WORKGROUP_NV
, SCOPE_SUBGROUP_NV
, SCOPE_QUEUE_FAMILY_NV
, ..
)
, ComponentTypeNV( COMPONENT_TYPE_FLOAT16_NV
, COMPONENT_TYPE_FLOAT32_NV
, COMPONENT_TYPE_FLOAT64_NV
, COMPONENT_TYPE_SINT8_NV
, COMPONENT_TYPE_SINT16_NV
, COMPONENT_TYPE_SINT32_NV
, COMPONENT_TYPE_SINT64_NV
, COMPONENT_TYPE_UINT8_NV
, COMPONENT_TYPE_UINT16_NV
, COMPONENT_TYPE_UINT32_NV
, COMPONENT_TYPE_UINT64_NV
, ..
)
, NV_COOPERATIVE_MATRIX_SPEC_VERSION
, pattern NV_COOPERATIVE_MATRIX_SPEC_VERSION
, NV_COOPERATIVE_MATRIX_EXTENSION_NAME
, pattern NV_COOPERATIVE_MATRIX_EXTENSION_NAME
) where
import Control.Exception.Base (bracket)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import GHC.Show (showsPrec)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
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 Data.Int (Int32)
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import Data.Word (Word32)
import Text.Read.Lex (Lexeme(Ident))
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Graphics.Vulkan.CStruct.Utils (advancePtrBytes)
import Graphics.Vulkan.Core10.BaseType (bool32ToBool)
import Graphics.Vulkan.Core10.BaseType (boolToBool32)
import Graphics.Vulkan.NamedType ((:::))
import Graphics.Vulkan.Core10.BaseType (Bool32)
import Graphics.Vulkan.CStruct (FromCStruct)
import Graphics.Vulkan.CStruct (FromCStruct(..))
import Graphics.Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceCooperativeMatrixPropertiesNV))
import Graphics.Vulkan.Core10.Handles (PhysicalDevice)
import Graphics.Vulkan.Core10.Handles (PhysicalDevice(..))
import Graphics.Vulkan.Core10.Handles (PhysicalDevice_T)
import Graphics.Vulkan.Core10.Enums.Result (Result)
import Graphics.Vulkan.Core10.Enums.Result (Result(..))
import Graphics.Vulkan.Core10.Enums.ShaderStageFlagBits (ShaderStageFlags)
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType)
import Graphics.Vulkan.CStruct (ToCStruct)
import Graphics.Vulkan.CStruct (ToCStruct(..))
import Graphics.Vulkan.Exception (VulkanException(..))
import Graphics.Vulkan.Zero (Zero)
import Graphics.Vulkan.Zero (Zero(..))
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_COOPERATIVE_MATRIX_PROPERTIES_NV))
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_FEATURES_NV))
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_PROPERTIES_NV))
import Graphics.Vulkan.Core10.Enums.Result (Result(SUCCESS))
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 :: PhysicalDevice -> IO (Result, ("properties" ::: Vector CooperativeMatrixPropertiesNV))
getPhysicalDeviceCooperativeMatrixPropertiesNV physicalDevice = evalContT $ do
let vkGetPhysicalDeviceCooperativeMatrixPropertiesNV' = mkVkGetPhysicalDeviceCooperativeMatrixPropertiesNV (pVkGetPhysicalDeviceCooperativeMatrixPropertiesNV (instanceCmds (physicalDevice :: PhysicalDevice)))
let physicalDevice' = physicalDeviceHandle (physicalDevice)
pPPropertyCount <- ContT $ bracket (callocBytes @Word32 4) free
r <- lift $ vkGetPhysicalDeviceCooperativeMatrixPropertiesNV' physicalDevice' (pPPropertyCount) (nullPtr)
lift $ when (r < SUCCESS) (throwIO (VulkanException r))
pPropertyCount <- lift $ peek @Word32 pPPropertyCount
pPProperties <- ContT $ bracket (callocBytes @CooperativeMatrixPropertiesNV ((fromIntegral (pPropertyCount)) * 48)) free
_ <- traverse (\i -> ContT $ pokeZeroCStruct (pPProperties `advancePtrBytes` (i * 48) :: Ptr CooperativeMatrixPropertiesNV) . ($ ())) [0..(fromIntegral (pPropertyCount)) - 1]
r' <- lift $ vkGetPhysicalDeviceCooperativeMatrixPropertiesNV' physicalDevice' (pPPropertyCount) ((pPProperties))
lift $ when (r' < SUCCESS) (throwIO (VulkanException r'))
pPropertyCount' <- lift $ peek @Word32 pPPropertyCount
pProperties' <- lift $ generateM (fromIntegral (pPropertyCount')) (\i -> peekCStruct @CooperativeMatrixPropertiesNV (((pPProperties) `advancePtrBytes` (48 * (i)) :: Ptr CooperativeMatrixPropertiesNV)))
pure $ ((r'), pProperties')
data PhysicalDeviceCooperativeMatrixFeaturesNV = PhysicalDeviceCooperativeMatrixFeaturesNV
{
cooperativeMatrix :: Bool
,
cooperativeMatrixRobustBufferAccess :: Bool
}
deriving (Typeable)
deriving instance Show PhysicalDeviceCooperativeMatrixFeaturesNV
instance ToCStruct PhysicalDeviceCooperativeMatrixFeaturesNV where
withCStruct x f = allocaBytesAligned 24 8 $ \p -> pokeCStruct p x (f p)
pokeCStruct p PhysicalDeviceCooperativeMatrixFeaturesNV{..} f = do
poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_FEATURES_NV)
poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
poke ((p `plusPtr` 16 :: Ptr Bool32)) (boolToBool32 (cooperativeMatrix))
poke ((p `plusPtr` 20 :: Ptr Bool32)) (boolToBool32 (cooperativeMatrixRobustBufferAccess))
f
cStructSize = 24
cStructAlignment = 8
pokeZeroCStruct p f = do
poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_FEATURES_NV)
poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
poke ((p `plusPtr` 16 :: Ptr Bool32)) (boolToBool32 (zero))
poke ((p `plusPtr` 20 :: Ptr Bool32)) (boolToBool32 (zero))
f
instance FromCStruct PhysicalDeviceCooperativeMatrixFeaturesNV where
peekCStruct p = do
cooperativeMatrix <- peek @Bool32 ((p `plusPtr` 16 :: Ptr Bool32))
cooperativeMatrixRobustBufferAccess <- peek @Bool32 ((p `plusPtr` 20 :: Ptr Bool32))
pure $ PhysicalDeviceCooperativeMatrixFeaturesNV
(bool32ToBool cooperativeMatrix) (bool32ToBool cooperativeMatrixRobustBufferAccess)
instance Storable PhysicalDeviceCooperativeMatrixFeaturesNV where
sizeOf ~_ = 24
alignment ~_ = 8
peek = peekCStruct
poke ptr poked = pokeCStruct ptr poked (pure ())
instance Zero PhysicalDeviceCooperativeMatrixFeaturesNV where
zero = PhysicalDeviceCooperativeMatrixFeaturesNV
zero
zero
data PhysicalDeviceCooperativeMatrixPropertiesNV = PhysicalDeviceCooperativeMatrixPropertiesNV
{
cooperativeMatrixSupportedStages :: ShaderStageFlags }
deriving (Typeable)
deriving instance Show PhysicalDeviceCooperativeMatrixPropertiesNV
instance ToCStruct PhysicalDeviceCooperativeMatrixPropertiesNV where
withCStruct x f = allocaBytesAligned 24 8 $ \p -> pokeCStruct p x (f p)
pokeCStruct p PhysicalDeviceCooperativeMatrixPropertiesNV{..} f = do
poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_PROPERTIES_NV)
poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
poke ((p `plusPtr` 16 :: Ptr ShaderStageFlags)) (cooperativeMatrixSupportedStages)
f
cStructSize = 24
cStructAlignment = 8
pokeZeroCStruct p f = do
poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_PROPERTIES_NV)
poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
poke ((p `plusPtr` 16 :: Ptr ShaderStageFlags)) (zero)
f
instance FromCStruct PhysicalDeviceCooperativeMatrixPropertiesNV where
peekCStruct p = do
cooperativeMatrixSupportedStages <- peek @ShaderStageFlags ((p `plusPtr` 16 :: Ptr ShaderStageFlags))
pure $ PhysicalDeviceCooperativeMatrixPropertiesNV
cooperativeMatrixSupportedStages
instance Storable PhysicalDeviceCooperativeMatrixPropertiesNV where
sizeOf ~_ = 24
alignment ~_ = 8
peek = peekCStruct
poke ptr poked = pokeCStruct ptr poked (pure ())
instance Zero PhysicalDeviceCooperativeMatrixPropertiesNV where
zero = PhysicalDeviceCooperativeMatrixPropertiesNV
zero
data CooperativeMatrixPropertiesNV = CooperativeMatrixPropertiesNV
{
mSize :: Word32
,
nSize :: Word32
,
kSize :: Word32
,
aType :: ComponentTypeNV
,
bType :: ComponentTypeNV
,
cType :: ComponentTypeNV
,
dType :: ComponentTypeNV
,
scope :: ScopeNV
}
deriving (Typeable)
deriving instance Show CooperativeMatrixPropertiesNV
instance ToCStruct CooperativeMatrixPropertiesNV where
withCStruct x f = allocaBytesAligned 48 8 $ \p -> pokeCStruct p x (f p)
pokeCStruct p CooperativeMatrixPropertiesNV{..} f = do
poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_COOPERATIVE_MATRIX_PROPERTIES_NV)
poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
poke ((p `plusPtr` 16 :: Ptr Word32)) (mSize)
poke ((p `plusPtr` 20 :: Ptr Word32)) (nSize)
poke ((p `plusPtr` 24 :: Ptr Word32)) (kSize)
poke ((p `plusPtr` 28 :: Ptr ComponentTypeNV)) (aType)
poke ((p `plusPtr` 32 :: Ptr ComponentTypeNV)) (bType)
poke ((p `plusPtr` 36 :: Ptr ComponentTypeNV)) (cType)
poke ((p `plusPtr` 40 :: Ptr ComponentTypeNV)) (dType)
poke ((p `plusPtr` 44 :: Ptr ScopeNV)) (scope)
f
cStructSize = 48
cStructAlignment = 8
pokeZeroCStruct p f = do
poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_COOPERATIVE_MATRIX_PROPERTIES_NV)
poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
poke ((p `plusPtr` 16 :: Ptr Word32)) (zero)
poke ((p `plusPtr` 20 :: Ptr Word32)) (zero)
poke ((p `plusPtr` 24 :: Ptr Word32)) (zero)
poke ((p `plusPtr` 28 :: Ptr ComponentTypeNV)) (zero)
poke ((p `plusPtr` 32 :: Ptr ComponentTypeNV)) (zero)
poke ((p `plusPtr` 36 :: Ptr ComponentTypeNV)) (zero)
poke ((p `plusPtr` 40 :: Ptr ComponentTypeNV)) (zero)
poke ((p `plusPtr` 44 :: Ptr ScopeNV)) (zero)
f
instance FromCStruct CooperativeMatrixPropertiesNV where
peekCStruct p = do
mSize <- peek @Word32 ((p `plusPtr` 16 :: Ptr Word32))
nSize <- peek @Word32 ((p `plusPtr` 20 :: Ptr Word32))
kSize <- peek @Word32 ((p `plusPtr` 24 :: Ptr Word32))
aType <- peek @ComponentTypeNV ((p `plusPtr` 28 :: Ptr ComponentTypeNV))
bType <- peek @ComponentTypeNV ((p `plusPtr` 32 :: Ptr ComponentTypeNV))
cType <- peek @ComponentTypeNV ((p `plusPtr` 36 :: Ptr ComponentTypeNV))
dType <- peek @ComponentTypeNV ((p `plusPtr` 40 :: Ptr ComponentTypeNV))
scope <- peek @ScopeNV ((p `plusPtr` 44 :: Ptr ScopeNV))
pure $ CooperativeMatrixPropertiesNV
mSize nSize kSize aType bType cType dType scope
instance Storable CooperativeMatrixPropertiesNV where
sizeOf ~_ = 48
alignment ~_ = 8
peek = peekCStruct
poke ptr poked = pokeCStruct ptr poked (pure ())
instance Zero CooperativeMatrixPropertiesNV where
zero = CooperativeMatrixPropertiesNV
zero
zero
zero
zero
zero
zero
zero
zero
newtype ScopeNV = ScopeNV Int32
deriving newtype (Eq, Ord, Storable, Zero)
pattern SCOPE_DEVICE_NV = ScopeNV 1
pattern SCOPE_WORKGROUP_NV = ScopeNV 2
pattern SCOPE_SUBGROUP_NV = ScopeNV 3
pattern SCOPE_QUEUE_FAMILY_NV = ScopeNV 5
{-# complete SCOPE_DEVICE_NV,
SCOPE_WORKGROUP_NV,
SCOPE_SUBGROUP_NV,
SCOPE_QUEUE_FAMILY_NV :: ScopeNV #-}
instance Show ScopeNV where
showsPrec p = \case
SCOPE_DEVICE_NV -> showString "SCOPE_DEVICE_NV"
SCOPE_WORKGROUP_NV -> showString "SCOPE_WORKGROUP_NV"
SCOPE_SUBGROUP_NV -> showString "SCOPE_SUBGROUP_NV"
SCOPE_QUEUE_FAMILY_NV -> showString "SCOPE_QUEUE_FAMILY_NV"
ScopeNV x -> showParen (p >= 11) (showString "ScopeNV " . showsPrec 11 x)
instance Read ScopeNV where
readPrec = parens (choose [("SCOPE_DEVICE_NV", pure SCOPE_DEVICE_NV)
, ("SCOPE_WORKGROUP_NV", pure SCOPE_WORKGROUP_NV)
, ("SCOPE_SUBGROUP_NV", pure SCOPE_SUBGROUP_NV)
, ("SCOPE_QUEUE_FAMILY_NV", pure SCOPE_QUEUE_FAMILY_NV)]
+++
prec 10 (do
expectP (Ident "ScopeNV")
v <- step readPrec
pure (ScopeNV v)))
newtype ComponentTypeNV = ComponentTypeNV Int32
deriving newtype (Eq, Ord, Storable, Zero)
pattern COMPONENT_TYPE_FLOAT16_NV = ComponentTypeNV 0
pattern COMPONENT_TYPE_FLOAT32_NV = ComponentTypeNV 1
pattern COMPONENT_TYPE_FLOAT64_NV = ComponentTypeNV 2
pattern COMPONENT_TYPE_SINT8_NV = ComponentTypeNV 3
pattern COMPONENT_TYPE_SINT16_NV = ComponentTypeNV 4
pattern COMPONENT_TYPE_SINT32_NV = ComponentTypeNV 5
pattern COMPONENT_TYPE_SINT64_NV = ComponentTypeNV 6
pattern COMPONENT_TYPE_UINT8_NV = ComponentTypeNV 7
pattern COMPONENT_TYPE_UINT16_NV = ComponentTypeNV 8
pattern COMPONENT_TYPE_UINT32_NV = ComponentTypeNV 9
pattern COMPONENT_TYPE_UINT64_NV = ComponentTypeNV 10
{-# complete COMPONENT_TYPE_FLOAT16_NV,
COMPONENT_TYPE_FLOAT32_NV,
COMPONENT_TYPE_FLOAT64_NV,
COMPONENT_TYPE_SINT8_NV,
COMPONENT_TYPE_SINT16_NV,
COMPONENT_TYPE_SINT32_NV,
COMPONENT_TYPE_SINT64_NV,
COMPONENT_TYPE_UINT8_NV,
COMPONENT_TYPE_UINT16_NV,
COMPONENT_TYPE_UINT32_NV,
COMPONENT_TYPE_UINT64_NV :: ComponentTypeNV #-}
instance Show ComponentTypeNV where
showsPrec p = \case
COMPONENT_TYPE_FLOAT16_NV -> showString "COMPONENT_TYPE_FLOAT16_NV"
COMPONENT_TYPE_FLOAT32_NV -> showString "COMPONENT_TYPE_FLOAT32_NV"
COMPONENT_TYPE_FLOAT64_NV -> showString "COMPONENT_TYPE_FLOAT64_NV"
COMPONENT_TYPE_SINT8_NV -> showString "COMPONENT_TYPE_SINT8_NV"
COMPONENT_TYPE_SINT16_NV -> showString "COMPONENT_TYPE_SINT16_NV"
COMPONENT_TYPE_SINT32_NV -> showString "COMPONENT_TYPE_SINT32_NV"
COMPONENT_TYPE_SINT64_NV -> showString "COMPONENT_TYPE_SINT64_NV"
COMPONENT_TYPE_UINT8_NV -> showString "COMPONENT_TYPE_UINT8_NV"
COMPONENT_TYPE_UINT16_NV -> showString "COMPONENT_TYPE_UINT16_NV"
COMPONENT_TYPE_UINT32_NV -> showString "COMPONENT_TYPE_UINT32_NV"
COMPONENT_TYPE_UINT64_NV -> showString "COMPONENT_TYPE_UINT64_NV"
ComponentTypeNV x -> showParen (p >= 11) (showString "ComponentTypeNV " . showsPrec 11 x)
instance Read ComponentTypeNV where
readPrec = parens (choose [("COMPONENT_TYPE_FLOAT16_NV", pure COMPONENT_TYPE_FLOAT16_NV)
, ("COMPONENT_TYPE_FLOAT32_NV", pure COMPONENT_TYPE_FLOAT32_NV)
, ("COMPONENT_TYPE_FLOAT64_NV", pure COMPONENT_TYPE_FLOAT64_NV)
, ("COMPONENT_TYPE_SINT8_NV", pure COMPONENT_TYPE_SINT8_NV)
, ("COMPONENT_TYPE_SINT16_NV", pure COMPONENT_TYPE_SINT16_NV)
, ("COMPONENT_TYPE_SINT32_NV", pure COMPONENT_TYPE_SINT32_NV)
, ("COMPONENT_TYPE_SINT64_NV", pure COMPONENT_TYPE_SINT64_NV)
, ("COMPONENT_TYPE_UINT8_NV", pure COMPONENT_TYPE_UINT8_NV)
, ("COMPONENT_TYPE_UINT16_NV", pure COMPONENT_TYPE_UINT16_NV)
, ("COMPONENT_TYPE_UINT32_NV", pure COMPONENT_TYPE_UINT32_NV)
, ("COMPONENT_TYPE_UINT64_NV", pure COMPONENT_TYPE_UINT64_NV)]
+++
prec 10 (do
expectP (Ident "ComponentTypeNV")
v <- step readPrec
pure (ComponentTypeNV v)))
type NV_COOPERATIVE_MATRIX_SPEC_VERSION = 1
pattern NV_COOPERATIVE_MATRIX_SPEC_VERSION :: forall a . Integral a => a
pattern 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 NV_COOPERATIVE_MATRIX_EXTENSION_NAME = "VK_NV_cooperative_matrix"