{-# language CPP #-}
module 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 Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
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 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 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 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 Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.BaseType (bool32ToBool)
import Vulkan.Core10.BaseType (boolToBool32)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.BaseType (Bool32)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceCooperativeMatrixPropertiesNV))
import Vulkan.Core10.Handles (PhysicalDevice)
import Vulkan.Core10.Handles (PhysicalDevice(..))
import Vulkan.Core10.Handles (PhysicalDevice_T)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.ShaderStageFlagBits (ShaderStageFlags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
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))
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

-- | vkGetPhysicalDeviceCooperativeMatrixPropertiesNV - Returns properties
-- describing what cooperative matrix types are supported
--
-- = Description
--
-- If @pProperties@ is @NULL@, then the number of cooperative matrix
-- properties available is returned in @pPropertyCount@. Otherwise,
-- @pPropertyCount@ /must/ point to a variable set by the user to the
-- number of elements in the @pProperties@ array, and on return the
-- variable is overwritten with the number of structures actually written
-- to @pProperties@. If @pPropertyCount@ is less than the number of
-- cooperative matrix properties available, at most @pPropertyCount@
-- structures will be written. If @pPropertyCount@ is smaller than the
-- number of cooperative matrix properties available,
-- 'Vulkan.Core10.Enums.Result.INCOMPLETE' will be returned instead of
-- 'Vulkan.Core10.Enums.Result.SUCCESS', to indicate that not all the
-- available cooperative matrix properties were returned.
--
-- == Valid Usage (Implicit)
--
-- -   @physicalDevice@ /must/ be a valid
--     'Vulkan.Core10.Handles.PhysicalDevice' handle
--
-- -   @pPropertyCount@ /must/ be a valid pointer to a @uint32_t@ value
--
-- -   If the value referenced by @pPropertyCount@ is not @0@, and
--     @pProperties@ is not @NULL@, @pProperties@ /must/ be a valid pointer
--     to an array of @pPropertyCount@ 'CooperativeMatrixPropertiesNV'
--     structures
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.INCOMPLETE'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
-- = See Also
--
-- 'CooperativeMatrixPropertiesNV', 'Vulkan.Core10.Handles.PhysicalDevice'
getPhysicalDeviceCooperativeMatrixPropertiesNV :: forall io
                                                . (MonadIO io)
                                               => -- | @physicalDevice@ is the physical device.
                                                  PhysicalDevice
                                               -> io (Result, ("properties" ::: Vector CooperativeMatrixPropertiesNV))
getPhysicalDeviceCooperativeMatrixPropertiesNV :: PhysicalDevice
-> io
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
getPhysicalDeviceCooperativeMatrixPropertiesNV physicalDevice :: PhysicalDevice
physicalDevice = IO (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
-> io
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
 -> io
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
-> (ContT
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
      IO
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
    -> IO
         (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
-> io
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
  IO
  (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
-> IO
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
   IO
   (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
 -> io
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
-> io
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
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 (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  IO ()
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
      IO
      ())
-> IO ()
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("pPropertyCount" ::: Ptr Word32)
   -> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
   -> IO Result)
vkGetPhysicalDeviceCooperativeMatrixPropertiesNVPtr FunPtr
  (Ptr PhysicalDevice_T
   -> ("pPropertyCount" ::: Ptr Word32)
   -> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
   -> IO Result)
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pPropertyCount" ::: Ptr Word32)
      -> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> ("pPropertyCount" ::: Ptr Word32)
   -> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetPhysicalDeviceCooperativeMatrixPropertiesNV is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
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 <- ((("pPropertyCount" ::: Ptr Word32)
  -> IO
       (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
 -> IO
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     ("pPropertyCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pPropertyCount" ::: Ptr Word32)
   -> IO
        (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
  -> IO
       (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
 -> ContT
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
      IO
      ("pPropertyCount" ::: Ptr Word32))
-> ((("pPropertyCount" ::: Ptr Word32)
     -> IO
          (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
    -> IO
         (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     ("pPropertyCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO ("pPropertyCount" ::: Ptr Word32)
-> (("pPropertyCount" ::: Ptr Word32) -> IO ())
-> (("pPropertyCount" ::: Ptr Word32)
    -> IO
         (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
-> IO
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pPropertyCount" ::: Ptr Word32)
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) ("pPropertyCount" ::: Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
      IO
      Result)
-> IO Result
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     Result
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pPropertyCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO Result
vkGetPhysicalDeviceCooperativeMatrixPropertiesNV' Ptr PhysicalDevice_T
physicalDevice' ("pPropertyCount" ::: Ptr Word32
pPPropertyCount) ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
forall a. Ptr a
nullPtr)
  IO ()
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
      IO
      ())
-> IO ()
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  Word32
pPropertyCount <- IO Word32
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
 -> ContT
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
      IO
      Word32)
-> IO Word32
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     Word32
forall a b. (a -> b) -> a -> b
$ ("pPropertyCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pPropertyCount" ::: Ptr Word32
pPPropertyCount
  "pProperties" ::: Ptr CooperativeMatrixPropertiesNV
pPProperties <- ((("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
  -> IO
       (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
 -> IO
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
   -> IO
        (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
  -> IO
       (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
 -> ContT
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
      IO
      ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV))
-> ((("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
     -> IO
          (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
    -> IO
         (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
forall a b. (a -> b) -> a -> b
$ IO ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV) -> IO ())
-> (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
    -> IO
         (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
-> IO
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
forall a. Int -> IO (Ptr a)
callocBytes @CooperativeMatrixPropertiesNV ((Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPropertyCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 48)) ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV) -> IO ()
forall a. Ptr a -> IO ()
free
  [()]
_ <- (Int
 -> ContT
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
      IO
      ())
-> [Int]
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     [()]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\i :: Int
i -> ((()
  -> IO
       (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
 -> IO
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((()
   -> IO
        (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
  -> IO
       (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
 -> ContT
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
      IO
      ())
-> ((()
     -> IO
          (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
    -> IO
         (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     ()
forall a b. (a -> b) -> a -> b
$ ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
-> IO
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
forall a b. ToCStruct a => Ptr a -> IO b -> IO b
pokeZeroCStruct ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
pPProperties ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> "pProperties" ::: Ptr CooperativeMatrixPropertiesNV
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* 48) :: Ptr CooperativeMatrixPropertiesNV) (IO (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
 -> IO
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
-> ((()
     -> IO
          (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
    -> IO
         (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
-> (()
    -> IO
         (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
-> IO
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((()
 -> IO
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
-> ()
-> IO
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
forall a b. (a -> b) -> a -> b
$ ())) [0..(Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPropertyCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1]
  Result
r' <- IO Result
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
      IO
      Result)
-> IO Result
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     Result
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pPropertyCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO Result
vkGetPhysicalDeviceCooperativeMatrixPropertiesNV' Ptr PhysicalDevice_T
physicalDevice' ("pPropertyCount" ::: Ptr Word32
pPPropertyCount) (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
pPProperties))
  IO ()
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
      IO
      ())
-> IO ()
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r' Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r'))
  Word32
pPropertyCount' <- IO Word32
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
 -> ContT
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
      IO
      Word32)
-> IO Word32
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     Word32
forall a b. (a -> b) -> a -> b
$ ("pPropertyCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pPropertyCount" ::: Ptr Word32
pPPropertyCount
  "properties" ::: Vector CooperativeMatrixPropertiesNV
pProperties' <- IO ("properties" ::: Vector CooperativeMatrixPropertiesNV)
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     ("properties" ::: Vector CooperativeMatrixPropertiesNV)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("properties" ::: Vector CooperativeMatrixPropertiesNV)
 -> ContT
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
      IO
      ("properties" ::: Vector CooperativeMatrixPropertiesNV))
-> IO ("properties" ::: Vector CooperativeMatrixPropertiesNV)
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     ("properties" ::: Vector CooperativeMatrixPropertiesNV)
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> IO CooperativeMatrixPropertiesNV)
-> IO ("properties" ::: Vector CooperativeMatrixPropertiesNV)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPropertyCount')) (\i :: Int
i -> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO CooperativeMatrixPropertiesNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @CooperativeMatrixPropertiesNV ((("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
pPProperties) ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> "pProperties" ::: Ptr CooperativeMatrixPropertiesNV
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr CooperativeMatrixPropertiesNV)))
  (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
 -> ContT
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
      IO
      (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV))
-> (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
-> ContT
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
     IO
     (Result, "properties" ::: Vector CooperativeMatrixPropertiesNV)
forall a b. (a -> b) -> a -> b
$ ((Result
r'), "properties" ::: Vector CooperativeMatrixPropertiesNV
pProperties')


-- | VkPhysicalDeviceCooperativeMatrixFeaturesNV - Structure describing
-- cooperative matrix features that can be supported by an implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceCooperativeMatrixFeaturesNV' structure
-- describe the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceCooperativeMatrixFeaturesNV' structure is included
-- in the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
-- it is filled with values indicating whether the feature is supported.
-- 'PhysicalDeviceCooperativeMatrixFeaturesNV' /can/ also be included in
-- the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to enable
-- features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.BaseType.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceCooperativeMatrixFeaturesNV = PhysicalDeviceCooperativeMatrixFeaturesNV
  { -- | @cooperativeMatrix@ indicates that the implementation supports the
    -- @CooperativeMatrixNV@ SPIR-V capability.
    PhysicalDeviceCooperativeMatrixFeaturesNV -> Bool
cooperativeMatrix :: Bool
  , -- | @cooperativeMatrixRobustBufferAccess@ indicates that the implementation
    -- supports robust buffer access for SPIR-V @OpCooperativeMatrixLoadNV@ and
    -- @OpCooperativeMatrixStoreNV@ instructions.
    PhysicalDeviceCooperativeMatrixFeaturesNV -> Bool
cooperativeMatrixRobustBufferAccess :: Bool
  }
  deriving (Typeable, PhysicalDeviceCooperativeMatrixFeaturesNV
-> PhysicalDeviceCooperativeMatrixFeaturesNV -> Bool
(PhysicalDeviceCooperativeMatrixFeaturesNV
 -> PhysicalDeviceCooperativeMatrixFeaturesNV -> Bool)
-> (PhysicalDeviceCooperativeMatrixFeaturesNV
    -> PhysicalDeviceCooperativeMatrixFeaturesNV -> Bool)
-> Eq PhysicalDeviceCooperativeMatrixFeaturesNV
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 :: PhysicalDeviceCooperativeMatrixFeaturesNV
-> (Ptr PhysicalDeviceCooperativeMatrixFeaturesNV -> IO b) -> IO b
withCStruct x :: PhysicalDeviceCooperativeMatrixFeaturesNV
x f :: Ptr PhysicalDeviceCooperativeMatrixFeaturesNV -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceCooperativeMatrixFeaturesNV -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV -> IO b) -> IO b)
-> (Ptr PhysicalDeviceCooperativeMatrixFeaturesNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p -> Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
-> PhysicalDeviceCooperativeMatrixFeaturesNV -> IO b -> IO b
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 :: Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
-> PhysicalDeviceCooperativeMatrixFeaturesNV -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p PhysicalDeviceCooperativeMatrixFeaturesNV{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_FEATURES_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p Ptr PhysicalDeviceCooperativeMatrixFeaturesNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
cooperativeMatrix))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p Ptr PhysicalDeviceCooperativeMatrixFeaturesNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
cooperativeMatrixRobustBufferAccess))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceCooperativeMatrixFeaturesNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_FEATURES_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p Ptr PhysicalDeviceCooperativeMatrixFeaturesNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p Ptr PhysicalDeviceCooperativeMatrixFeaturesNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceCooperativeMatrixFeaturesNV where
  peekCStruct :: Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
-> IO PhysicalDeviceCooperativeMatrixFeaturesNV
peekCStruct p :: Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p = do
    Bool32
cooperativeMatrix <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p Ptr PhysicalDeviceCooperativeMatrixFeaturesNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    Bool32
cooperativeMatrixRobustBufferAccess <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
p Ptr PhysicalDeviceCooperativeMatrixFeaturesNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    PhysicalDeviceCooperativeMatrixFeaturesNV
-> IO PhysicalDeviceCooperativeMatrixFeaturesNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceCooperativeMatrixFeaturesNV
 -> IO PhysicalDeviceCooperativeMatrixFeaturesNV)
-> PhysicalDeviceCooperativeMatrixFeaturesNV
-> IO PhysicalDeviceCooperativeMatrixFeaturesNV
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
_ = 24
  alignment :: PhysicalDeviceCooperativeMatrixFeaturesNV -> Int
alignment ~PhysicalDeviceCooperativeMatrixFeaturesNV
_ = 8
  peek :: Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
-> IO PhysicalDeviceCooperativeMatrixFeaturesNV
peek = Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
-> IO PhysicalDeviceCooperativeMatrixFeaturesNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
-> PhysicalDeviceCooperativeMatrixFeaturesNV -> IO ()
poke ptr :: Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
ptr poked :: PhysicalDeviceCooperativeMatrixFeaturesNV
poked = Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
-> PhysicalDeviceCooperativeMatrixFeaturesNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCooperativeMatrixFeaturesNV
ptr PhysicalDeviceCooperativeMatrixFeaturesNV
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDeviceCooperativeMatrixFeaturesNV where
  zero :: PhysicalDeviceCooperativeMatrixFeaturesNV
zero = Bool -> Bool -> PhysicalDeviceCooperativeMatrixFeaturesNV
PhysicalDeviceCooperativeMatrixFeaturesNV
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero


-- | VkPhysicalDeviceCooperativeMatrixPropertiesNV - Structure describing
-- cooperative matrix properties supported by an implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceCooperativeMatrixPropertiesNV'
-- structure describe the following implementation-dependent limits:
--
-- = Description
--
-- If the 'PhysicalDeviceCooperativeMatrixPropertiesNV' structure is
-- included in the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2',
-- it is filled with the implementation-dependent limits.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.ShaderStageFlagBits.ShaderStageFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceCooperativeMatrixPropertiesNV = PhysicalDeviceCooperativeMatrixPropertiesNV
  { -- | @cooperativeMatrixSupportedStages@ is a bitfield of
    -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.ShaderStageFlagBits' describing
    -- the shader stages that cooperative matrix instructions are supported in.
    -- @cooperativeMatrixSupportedStages@ will have the
    -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_COMPUTE_BIT' bit
    -- set if any of the physical device’s queues support
    -- 'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_COMPUTE_BIT'.
    PhysicalDeviceCooperativeMatrixPropertiesNV -> ShaderStageFlags
cooperativeMatrixSupportedStages :: ShaderStageFlags }
  deriving (Typeable, PhysicalDeviceCooperativeMatrixPropertiesNV
-> PhysicalDeviceCooperativeMatrixPropertiesNV -> Bool
(PhysicalDeviceCooperativeMatrixPropertiesNV
 -> PhysicalDeviceCooperativeMatrixPropertiesNV -> Bool)
-> (PhysicalDeviceCooperativeMatrixPropertiesNV
    -> PhysicalDeviceCooperativeMatrixPropertiesNV -> Bool)
-> Eq PhysicalDeviceCooperativeMatrixPropertiesNV
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 :: PhysicalDeviceCooperativeMatrixPropertiesNV
-> (Ptr PhysicalDeviceCooperativeMatrixPropertiesNV -> IO b)
-> IO b
withCStruct x :: PhysicalDeviceCooperativeMatrixPropertiesNV
x f :: Ptr PhysicalDeviceCooperativeMatrixPropertiesNV -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceCooperativeMatrixPropertiesNV -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceCooperativeMatrixPropertiesNV -> IO b) -> IO b)
-> (Ptr PhysicalDeviceCooperativeMatrixPropertiesNV -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p -> Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> PhysicalDeviceCooperativeMatrixPropertiesNV -> IO b -> IO b
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 :: Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> PhysicalDeviceCooperativeMatrixPropertiesNV -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p PhysicalDeviceCooperativeMatrixPropertiesNV{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_PROPERTIES_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ShaderStageFlags -> ShaderStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> Int -> Ptr ShaderStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ShaderStageFlags)) (ShaderStageFlags
cooperativeMatrixSupportedStages)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceCooperativeMatrixPropertiesNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_PROPERTIES_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ShaderStageFlags -> ShaderStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> Int -> Ptr ShaderStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ShaderStageFlags)) (ShaderStageFlags
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceCooperativeMatrixPropertiesNV where
  peekCStruct :: Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> IO PhysicalDeviceCooperativeMatrixPropertiesNV
peekCStruct p :: Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p = do
    ShaderStageFlags
cooperativeMatrixSupportedStages <- Ptr ShaderStageFlags -> IO ShaderStageFlags
forall a. Storable a => Ptr a -> IO a
peek @ShaderStageFlags ((Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
p Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> Int -> Ptr ShaderStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ShaderStageFlags))
    PhysicalDeviceCooperativeMatrixPropertiesNV
-> IO PhysicalDeviceCooperativeMatrixPropertiesNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceCooperativeMatrixPropertiesNV
 -> IO PhysicalDeviceCooperativeMatrixPropertiesNV)
-> PhysicalDeviceCooperativeMatrixPropertiesNV
-> IO PhysicalDeviceCooperativeMatrixPropertiesNV
forall a b. (a -> b) -> a -> b
$ ShaderStageFlags -> PhysicalDeviceCooperativeMatrixPropertiesNV
PhysicalDeviceCooperativeMatrixPropertiesNV
             ShaderStageFlags
cooperativeMatrixSupportedStages

instance Storable PhysicalDeviceCooperativeMatrixPropertiesNV where
  sizeOf :: PhysicalDeviceCooperativeMatrixPropertiesNV -> Int
sizeOf ~PhysicalDeviceCooperativeMatrixPropertiesNV
_ = 24
  alignment :: PhysicalDeviceCooperativeMatrixPropertiesNV -> Int
alignment ~PhysicalDeviceCooperativeMatrixPropertiesNV
_ = 8
  peek :: Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> IO PhysicalDeviceCooperativeMatrixPropertiesNV
peek = Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> IO PhysicalDeviceCooperativeMatrixPropertiesNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> PhysicalDeviceCooperativeMatrixPropertiesNV -> IO ()
poke ptr :: Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
ptr poked :: PhysicalDeviceCooperativeMatrixPropertiesNV
poked = Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
-> PhysicalDeviceCooperativeMatrixPropertiesNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCooperativeMatrixPropertiesNV
ptr PhysicalDeviceCooperativeMatrixPropertiesNV
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDeviceCooperativeMatrixPropertiesNV where
  zero :: PhysicalDeviceCooperativeMatrixPropertiesNV
zero = ShaderStageFlags -> PhysicalDeviceCooperativeMatrixPropertiesNV
PhysicalDeviceCooperativeMatrixPropertiesNV
           ShaderStageFlags
forall a. Zero a => a
zero


-- | VkCooperativeMatrixPropertiesNV - Structure specifying cooperative
-- matrix properties
--
-- = Description
--
-- If some types are preferred over other types (e.g. for performance),
-- they /should/ appear earlier in the list enumerated by
-- 'getPhysicalDeviceCooperativeMatrixPropertiesNV'.
--
-- At least one entry in the list /must/ have power of two values for all
-- of @MSize@, @KSize@, and @NSize@.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'ComponentTypeNV', 'ScopeNV',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getPhysicalDeviceCooperativeMatrixPropertiesNV'
data CooperativeMatrixPropertiesNV = CooperativeMatrixPropertiesNV
  { -- | @MSize@ is the number of rows in matrices A, C, and D.
    CooperativeMatrixPropertiesNV -> Word32
mSize :: Word32
  , -- | @NSize@ is the number of columns in matrices B, C, D.
    CooperativeMatrixPropertiesNV -> Word32
nSize :: Word32
  , -- | @KSize@ is the number of columns in matrix A and rows in matrix B.
    CooperativeMatrixPropertiesNV -> Word32
kSize :: Word32
  , -- | @AType@ is the component type of matrix A, of type 'ComponentTypeNV'.
    --
    -- @AType@ /must/ be a valid 'ComponentTypeNV' value
    CooperativeMatrixPropertiesNV -> ComponentTypeNV
aType :: ComponentTypeNV
  , -- | @BType@ is the component type of matrix B, of type 'ComponentTypeNV'.
    --
    -- @BType@ /must/ be a valid 'ComponentTypeNV' value
    CooperativeMatrixPropertiesNV -> ComponentTypeNV
bType :: ComponentTypeNV
  , -- | @CType@ is the component type of matrix C, of type 'ComponentTypeNV'.
    --
    -- @CType@ /must/ be a valid 'ComponentTypeNV' value
    CooperativeMatrixPropertiesNV -> ComponentTypeNV
cType :: ComponentTypeNV
  , -- | @DType@ is the component type of matrix D, of type 'ComponentTypeNV'.
    --
    -- @DType@ /must/ be a valid 'ComponentTypeNV' value
    CooperativeMatrixPropertiesNV -> ComponentTypeNV
dType :: ComponentTypeNV
  , -- | @scope@ is the scope of all the matrix types, of type 'ScopeNV'.
    --
    -- @scope@ /must/ be a valid 'ScopeNV' value
    CooperativeMatrixPropertiesNV -> ScopeNV
scope :: ScopeNV
  }
  deriving (Typeable, CooperativeMatrixPropertiesNV
-> CooperativeMatrixPropertiesNV -> Bool
(CooperativeMatrixPropertiesNV
 -> CooperativeMatrixPropertiesNV -> Bool)
-> (CooperativeMatrixPropertiesNV
    -> CooperativeMatrixPropertiesNV -> Bool)
-> Eq CooperativeMatrixPropertiesNV
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 :: CooperativeMatrixPropertiesNV
-> (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV) -> IO b)
-> IO b
withCStruct x :: CooperativeMatrixPropertiesNV
x f :: ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV) -> IO b
f = Int
-> Int
-> (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 48 8 ((("pProperties" ::: Ptr CooperativeMatrixPropertiesNV) -> IO b)
 -> IO b)
-> (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p -> ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> CooperativeMatrixPropertiesNV -> IO b -> IO b
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 :: ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> CooperativeMatrixPropertiesNV -> IO b -> IO b
pokeCStruct p :: "pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p CooperativeMatrixPropertiesNV{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COOPERATIVE_MATRIX_PROPERTIES_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ("pPropertyCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> "pPropertyCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
mSize)
    ("pPropertyCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> "pPropertyCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
nSize)
    ("pPropertyCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> "pPropertyCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
kSize)
    Ptr ComponentTypeNV -> ComponentTypeNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr ComponentTypeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ComponentTypeNV)) (ComponentTypeNV
aType)
    Ptr ComponentTypeNV -> ComponentTypeNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr ComponentTypeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr ComponentTypeNV)) (ComponentTypeNV
bType)
    Ptr ComponentTypeNV -> ComponentTypeNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr ComponentTypeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr ComponentTypeNV)) (ComponentTypeNV
cType)
    Ptr ComponentTypeNV -> ComponentTypeNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr ComponentTypeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr ComponentTypeNV)) (ComponentTypeNV
dType)
    Ptr ScopeNV -> ScopeNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr ScopeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr ScopeNV)) (ScopeNV
scope)
    IO b
f
  cStructSize :: Int
cStructSize = 48
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO b -> IO b
pokeZeroCStruct p :: "pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COOPERATIVE_MATRIX_PROPERTIES_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ("pPropertyCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> "pPropertyCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPropertyCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> "pPropertyCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    ("pPropertyCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> "pPropertyCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr ComponentTypeNV -> ComponentTypeNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr ComponentTypeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ComponentTypeNV)) (ComponentTypeNV
forall a. Zero a => a
zero)
    Ptr ComponentTypeNV -> ComponentTypeNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr ComponentTypeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr ComponentTypeNV)) (ComponentTypeNV
forall a. Zero a => a
zero)
    Ptr ComponentTypeNV -> ComponentTypeNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr ComponentTypeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr ComponentTypeNV)) (ComponentTypeNV
forall a. Zero a => a
zero)
    Ptr ComponentTypeNV -> ComponentTypeNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr ComponentTypeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr ComponentTypeNV)) (ComponentTypeNV
forall a. Zero a => a
zero)
    Ptr ScopeNV -> ScopeNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr ScopeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr ScopeNV)) (ScopeNV
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct CooperativeMatrixPropertiesNV where
  peekCStruct :: ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO CooperativeMatrixPropertiesNV
peekCStruct p :: "pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p = do
    Word32
mSize <- ("pPropertyCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> "pPropertyCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    Word32
nSize <- ("pPropertyCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> "pPropertyCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    Word32
kSize <- ("pPropertyCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> "pPropertyCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
    ComponentTypeNV
aType <- Ptr ComponentTypeNV -> IO ComponentTypeNV
forall a. Storable a => Ptr a -> IO a
peek @ComponentTypeNV (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr ComponentTypeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ComponentTypeNV))
    ComponentTypeNV
bType <- Ptr ComponentTypeNV -> IO ComponentTypeNV
forall a. Storable a => Ptr a -> IO a
peek @ComponentTypeNV (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr ComponentTypeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr ComponentTypeNV))
    ComponentTypeNV
cType <- Ptr ComponentTypeNV -> IO ComponentTypeNV
forall a. Storable a => Ptr a -> IO a
peek @ComponentTypeNV (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr ComponentTypeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr ComponentTypeNV))
    ComponentTypeNV
dType <- Ptr ComponentTypeNV -> IO ComponentTypeNV
forall a. Storable a => Ptr a -> IO a
peek @ComponentTypeNV (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr ComponentTypeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr ComponentTypeNV))
    ScopeNV
scope <- Ptr ScopeNV -> IO ScopeNV
forall a. Storable a => Ptr a -> IO a
peek @ScopeNV (("pProperties" ::: Ptr CooperativeMatrixPropertiesNV
p ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> Int -> Ptr ScopeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr ScopeNV))
    CooperativeMatrixPropertiesNV -> IO CooperativeMatrixPropertiesNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CooperativeMatrixPropertiesNV -> IO CooperativeMatrixPropertiesNV)
-> CooperativeMatrixPropertiesNV
-> IO CooperativeMatrixPropertiesNV
forall a b. (a -> b) -> a -> b
$ Word32
-> Word32
-> Word32
-> ComponentTypeNV
-> ComponentTypeNV
-> ComponentTypeNV
-> ComponentTypeNV
-> ScopeNV
-> CooperativeMatrixPropertiesNV
CooperativeMatrixPropertiesNV
             Word32
mSize Word32
nSize Word32
kSize ComponentTypeNV
aType ComponentTypeNV
bType ComponentTypeNV
cType ComponentTypeNV
dType ScopeNV
scope

instance Storable CooperativeMatrixPropertiesNV where
  sizeOf :: CooperativeMatrixPropertiesNV -> Int
sizeOf ~CooperativeMatrixPropertiesNV
_ = 48
  alignment :: CooperativeMatrixPropertiesNV -> Int
alignment ~CooperativeMatrixPropertiesNV
_ = 8
  peek :: ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO CooperativeMatrixPropertiesNV
peek = ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> IO CooperativeMatrixPropertiesNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> CooperativeMatrixPropertiesNV -> IO ()
poke ptr :: "pProperties" ::: Ptr CooperativeMatrixPropertiesNV
ptr poked :: CooperativeMatrixPropertiesNV
poked = ("pProperties" ::: Ptr CooperativeMatrixPropertiesNV)
-> CooperativeMatrixPropertiesNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr CooperativeMatrixPropertiesNV
ptr CooperativeMatrixPropertiesNV
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero CooperativeMatrixPropertiesNV where
  zero :: CooperativeMatrixPropertiesNV
zero = Word32
-> Word32
-> Word32
-> ComponentTypeNV
-> ComponentTypeNV
-> ComponentTypeNV
-> ComponentTypeNV
-> ScopeNV
-> CooperativeMatrixPropertiesNV
CooperativeMatrixPropertiesNV
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           ComponentTypeNV
forall a. Zero a => a
zero
           ComponentTypeNV
forall a. Zero a => a
zero
           ComponentTypeNV
forall a. Zero a => a
zero
           ComponentTypeNV
forall a. Zero a => a
zero
           ScopeNV
forall a. Zero a => a
zero


-- | VkScopeNV - Specify SPIR-V scope
--
-- = Description
--
-- All enum values match the corresponding SPIR-V value.
--
-- = See Also
--
-- 'CooperativeMatrixPropertiesNV'
newtype ScopeNV = ScopeNV Int32
  deriving newtype (ScopeNV -> ScopeNV -> Bool
(ScopeNV -> ScopeNV -> Bool)
-> (ScopeNV -> ScopeNV -> Bool) -> Eq ScopeNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScopeNV -> ScopeNV -> Bool
$c/= :: ScopeNV -> ScopeNV -> Bool
== :: ScopeNV -> ScopeNV -> Bool
$c== :: ScopeNV -> ScopeNV -> Bool
Eq, Eq ScopeNV
Eq ScopeNV =>
(ScopeNV -> ScopeNV -> Ordering)
-> (ScopeNV -> ScopeNV -> Bool)
-> (ScopeNV -> ScopeNV -> Bool)
-> (ScopeNV -> ScopeNV -> Bool)
-> (ScopeNV -> ScopeNV -> Bool)
-> (ScopeNV -> ScopeNV -> ScopeNV)
-> (ScopeNV -> ScopeNV -> ScopeNV)
-> Ord ScopeNV
ScopeNV -> ScopeNV -> Bool
ScopeNV -> ScopeNV -> Ordering
ScopeNV -> ScopeNV -> ScopeNV
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ScopeNV -> ScopeNV -> ScopeNV
$cmin :: ScopeNV -> ScopeNV -> ScopeNV
max :: ScopeNV -> ScopeNV -> ScopeNV
$cmax :: ScopeNV -> ScopeNV -> ScopeNV
>= :: ScopeNV -> ScopeNV -> Bool
$c>= :: ScopeNV -> ScopeNV -> Bool
> :: ScopeNV -> ScopeNV -> Bool
$c> :: ScopeNV -> ScopeNV -> Bool
<= :: ScopeNV -> ScopeNV -> Bool
$c<= :: ScopeNV -> ScopeNV -> Bool
< :: ScopeNV -> ScopeNV -> Bool
$c< :: ScopeNV -> ScopeNV -> Bool
compare :: ScopeNV -> ScopeNV -> Ordering
$ccompare :: ScopeNV -> ScopeNV -> Ordering
$cp1Ord :: Eq ScopeNV
Ord, Ptr b -> Int -> IO ScopeNV
Ptr b -> Int -> ScopeNV -> IO ()
Ptr ScopeNV -> IO ScopeNV
Ptr ScopeNV -> Int -> IO ScopeNV
Ptr ScopeNV -> Int -> ScopeNV -> IO ()
Ptr ScopeNV -> ScopeNV -> IO ()
ScopeNV -> Int
(ScopeNV -> Int)
-> (ScopeNV -> Int)
-> (Ptr ScopeNV -> Int -> IO ScopeNV)
-> (Ptr ScopeNV -> Int -> ScopeNV -> IO ())
-> (forall b. Ptr b -> Int -> IO ScopeNV)
-> (forall b. Ptr b -> Int -> ScopeNV -> IO ())
-> (Ptr ScopeNV -> IO ScopeNV)
-> (Ptr ScopeNV -> ScopeNV -> IO ())
-> Storable ScopeNV
forall b. Ptr b -> Int -> IO ScopeNV
forall b. Ptr b -> Int -> ScopeNV -> 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 ScopeNV -> ScopeNV -> IO ()
$cpoke :: Ptr ScopeNV -> ScopeNV -> IO ()
peek :: Ptr ScopeNV -> IO ScopeNV
$cpeek :: Ptr ScopeNV -> IO ScopeNV
pokeByteOff :: Ptr b -> Int -> ScopeNV -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ScopeNV -> IO ()
peekByteOff :: Ptr b -> Int -> IO ScopeNV
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ScopeNV
pokeElemOff :: Ptr ScopeNV -> Int -> ScopeNV -> IO ()
$cpokeElemOff :: Ptr ScopeNV -> Int -> ScopeNV -> IO ()
peekElemOff :: Ptr ScopeNV -> Int -> IO ScopeNV
$cpeekElemOff :: Ptr ScopeNV -> Int -> IO ScopeNV
alignment :: ScopeNV -> Int
$calignment :: ScopeNV -> Int
sizeOf :: ScopeNV -> Int
$csizeOf :: ScopeNV -> Int
Storable, ScopeNV
ScopeNV -> Zero ScopeNV
forall a. a -> Zero a
zero :: ScopeNV
$czero :: ScopeNV
Zero)
-- Note that the zero instance does not produce a valid value, passing 'zero' to Vulkan will result in an error

-- | 'SCOPE_DEVICE_NV' corresponds to SPIR-V 'Vulkan.Core10.Handles.Device'
-- scope.
pattern $bSCOPE_DEVICE_NV :: ScopeNV
$mSCOPE_DEVICE_NV :: forall r. ScopeNV -> (Void# -> r) -> (Void# -> r) -> r
SCOPE_DEVICE_NV = ScopeNV 1
-- | 'SCOPE_WORKGROUP_NV' corresponds to SPIR-V @Workgroup@ scope.
pattern $bSCOPE_WORKGROUP_NV :: ScopeNV
$mSCOPE_WORKGROUP_NV :: forall r. ScopeNV -> (Void# -> r) -> (Void# -> r) -> r
SCOPE_WORKGROUP_NV = ScopeNV 2
-- | 'SCOPE_SUBGROUP_NV' corresponds to SPIR-V @Subgroup@ scope.
pattern $bSCOPE_SUBGROUP_NV :: ScopeNV
$mSCOPE_SUBGROUP_NV :: forall r. ScopeNV -> (Void# -> r) -> (Void# -> r) -> r
SCOPE_SUBGROUP_NV = ScopeNV 3
-- | 'SCOPE_QUEUE_FAMILY_NV' corresponds to SPIR-V @QueueFamily@ scope.
pattern $bSCOPE_QUEUE_FAMILY_NV :: ScopeNV
$mSCOPE_QUEUE_FAMILY_NV :: forall r. ScopeNV -> (Void# -> r) -> (Void# -> r) -> r
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 :: Int -> ScopeNV -> ShowS
showsPrec p :: Int
p = \case
    SCOPE_DEVICE_NV -> String -> ShowS
showString "SCOPE_DEVICE_NV"
    SCOPE_WORKGROUP_NV -> String -> ShowS
showString "SCOPE_WORKGROUP_NV"
    SCOPE_SUBGROUP_NV -> String -> ShowS
showString "SCOPE_SUBGROUP_NV"
    SCOPE_QUEUE_FAMILY_NV -> String -> ShowS
showString "SCOPE_QUEUE_FAMILY_NV"
    ScopeNV x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "ScopeNV " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read ScopeNV where
  readPrec :: ReadPrec ScopeNV
readPrec = ReadPrec ScopeNV -> ReadPrec ScopeNV
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec ScopeNV)] -> ReadPrec ScopeNV
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("SCOPE_DEVICE_NV", ScopeNV -> ReadPrec ScopeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure ScopeNV
SCOPE_DEVICE_NV)
                            , ("SCOPE_WORKGROUP_NV", ScopeNV -> ReadPrec ScopeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure ScopeNV
SCOPE_WORKGROUP_NV)
                            , ("SCOPE_SUBGROUP_NV", ScopeNV -> ReadPrec ScopeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure ScopeNV
SCOPE_SUBGROUP_NV)
                            , ("SCOPE_QUEUE_FAMILY_NV", ScopeNV -> ReadPrec ScopeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure ScopeNV
SCOPE_QUEUE_FAMILY_NV)]
                     ReadPrec ScopeNV -> ReadPrec ScopeNV -> ReadPrec ScopeNV
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int -> ReadPrec ScopeNV -> ReadPrec ScopeNV
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "ScopeNV")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       ScopeNV -> ReadPrec ScopeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> ScopeNV
ScopeNV Int32
v)))


-- | VkComponentTypeNV - Specify SPIR-V cooperative matrix component type
--
-- = See Also
--
-- 'CooperativeMatrixPropertiesNV'
newtype ComponentTypeNV = ComponentTypeNV Int32
  deriving newtype (ComponentTypeNV -> ComponentTypeNV -> Bool
(ComponentTypeNV -> ComponentTypeNV -> Bool)
-> (ComponentTypeNV -> ComponentTypeNV -> Bool)
-> Eq ComponentTypeNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ComponentTypeNV -> ComponentTypeNV -> Bool
$c/= :: ComponentTypeNV -> ComponentTypeNV -> Bool
== :: ComponentTypeNV -> ComponentTypeNV -> Bool
$c== :: ComponentTypeNV -> ComponentTypeNV -> Bool
Eq, Eq ComponentTypeNV
Eq ComponentTypeNV =>
(ComponentTypeNV -> ComponentTypeNV -> Ordering)
-> (ComponentTypeNV -> ComponentTypeNV -> Bool)
-> (ComponentTypeNV -> ComponentTypeNV -> Bool)
-> (ComponentTypeNV -> ComponentTypeNV -> Bool)
-> (ComponentTypeNV -> ComponentTypeNV -> Bool)
-> (ComponentTypeNV -> ComponentTypeNV -> ComponentTypeNV)
-> (ComponentTypeNV -> ComponentTypeNV -> ComponentTypeNV)
-> Ord ComponentTypeNV
ComponentTypeNV -> ComponentTypeNV -> Bool
ComponentTypeNV -> ComponentTypeNV -> Ordering
ComponentTypeNV -> ComponentTypeNV -> ComponentTypeNV
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ComponentTypeNV -> ComponentTypeNV -> ComponentTypeNV
$cmin :: ComponentTypeNV -> ComponentTypeNV -> ComponentTypeNV
max :: ComponentTypeNV -> ComponentTypeNV -> ComponentTypeNV
$cmax :: ComponentTypeNV -> ComponentTypeNV -> ComponentTypeNV
>= :: ComponentTypeNV -> ComponentTypeNV -> Bool
$c>= :: ComponentTypeNV -> ComponentTypeNV -> Bool
> :: ComponentTypeNV -> ComponentTypeNV -> Bool
$c> :: ComponentTypeNV -> ComponentTypeNV -> Bool
<= :: ComponentTypeNV -> ComponentTypeNV -> Bool
$c<= :: ComponentTypeNV -> ComponentTypeNV -> Bool
< :: ComponentTypeNV -> ComponentTypeNV -> Bool
$c< :: ComponentTypeNV -> ComponentTypeNV -> Bool
compare :: ComponentTypeNV -> ComponentTypeNV -> Ordering
$ccompare :: ComponentTypeNV -> ComponentTypeNV -> Ordering
$cp1Ord :: Eq ComponentTypeNV
Ord, Ptr b -> Int -> IO ComponentTypeNV
Ptr b -> Int -> ComponentTypeNV -> IO ()
Ptr ComponentTypeNV -> IO ComponentTypeNV
Ptr ComponentTypeNV -> Int -> IO ComponentTypeNV
Ptr ComponentTypeNV -> Int -> ComponentTypeNV -> IO ()
Ptr ComponentTypeNV -> ComponentTypeNV -> IO ()
ComponentTypeNV -> Int
(ComponentTypeNV -> Int)
-> (ComponentTypeNV -> Int)
-> (Ptr ComponentTypeNV -> Int -> IO ComponentTypeNV)
-> (Ptr ComponentTypeNV -> Int -> ComponentTypeNV -> IO ())
-> (forall b. Ptr b -> Int -> IO ComponentTypeNV)
-> (forall b. Ptr b -> Int -> ComponentTypeNV -> IO ())
-> (Ptr ComponentTypeNV -> IO ComponentTypeNV)
-> (Ptr ComponentTypeNV -> ComponentTypeNV -> IO ())
-> Storable ComponentTypeNV
forall b. Ptr b -> Int -> IO ComponentTypeNV
forall b. Ptr b -> Int -> ComponentTypeNV -> 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 ComponentTypeNV -> ComponentTypeNV -> IO ()
$cpoke :: Ptr ComponentTypeNV -> ComponentTypeNV -> IO ()
peek :: Ptr ComponentTypeNV -> IO ComponentTypeNV
$cpeek :: Ptr ComponentTypeNV -> IO ComponentTypeNV
pokeByteOff :: Ptr b -> Int -> ComponentTypeNV -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ComponentTypeNV -> IO ()
peekByteOff :: Ptr b -> Int -> IO ComponentTypeNV
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ComponentTypeNV
pokeElemOff :: Ptr ComponentTypeNV -> Int -> ComponentTypeNV -> IO ()
$cpokeElemOff :: Ptr ComponentTypeNV -> Int -> ComponentTypeNV -> IO ()
peekElemOff :: Ptr ComponentTypeNV -> Int -> IO ComponentTypeNV
$cpeekElemOff :: Ptr ComponentTypeNV -> Int -> IO ComponentTypeNV
alignment :: ComponentTypeNV -> Int
$calignment :: ComponentTypeNV -> Int
sizeOf :: ComponentTypeNV -> Int
$csizeOf :: ComponentTypeNV -> Int
Storable, ComponentTypeNV
ComponentTypeNV -> Zero ComponentTypeNV
forall a. a -> Zero a
zero :: ComponentTypeNV
$czero :: ComponentTypeNV
Zero)

-- | 'COMPONENT_TYPE_FLOAT16_NV' corresponds to SPIR-V @OpTypeFloat@ 16.
pattern $bCOMPONENT_TYPE_FLOAT16_NV :: ComponentTypeNV
$mCOMPONENT_TYPE_FLOAT16_NV :: forall r. ComponentTypeNV -> (Void# -> r) -> (Void# -> r) -> r
COMPONENT_TYPE_FLOAT16_NV = ComponentTypeNV 0
-- | 'COMPONENT_TYPE_FLOAT32_NV' corresponds to SPIR-V @OpTypeFloat@ 32.
pattern $bCOMPONENT_TYPE_FLOAT32_NV :: ComponentTypeNV
$mCOMPONENT_TYPE_FLOAT32_NV :: forall r. ComponentTypeNV -> (Void# -> r) -> (Void# -> r) -> r
COMPONENT_TYPE_FLOAT32_NV = ComponentTypeNV 1
-- | 'COMPONENT_TYPE_FLOAT64_NV' corresponds to SPIR-V @OpTypeFloat@ 64.
pattern $bCOMPONENT_TYPE_FLOAT64_NV :: ComponentTypeNV
$mCOMPONENT_TYPE_FLOAT64_NV :: forall r. ComponentTypeNV -> (Void# -> r) -> (Void# -> r) -> r
COMPONENT_TYPE_FLOAT64_NV = ComponentTypeNV 2
-- | 'COMPONENT_TYPE_SINT8_NV' corresponds to SPIR-V @OpTypeInt@ 8 1.
pattern $bCOMPONENT_TYPE_SINT8_NV :: ComponentTypeNV
$mCOMPONENT_TYPE_SINT8_NV :: forall r. ComponentTypeNV -> (Void# -> r) -> (Void# -> r) -> r
COMPONENT_TYPE_SINT8_NV = ComponentTypeNV 3
-- | 'COMPONENT_TYPE_SINT16_NV' corresponds to SPIR-V @OpTypeInt@ 16 1.
pattern $bCOMPONENT_TYPE_SINT16_NV :: ComponentTypeNV
$mCOMPONENT_TYPE_SINT16_NV :: forall r. ComponentTypeNV -> (Void# -> r) -> (Void# -> r) -> r
COMPONENT_TYPE_SINT16_NV = ComponentTypeNV 4
-- | 'COMPONENT_TYPE_SINT32_NV' corresponds to SPIR-V @OpTypeInt@ 32 1.
pattern $bCOMPONENT_TYPE_SINT32_NV :: ComponentTypeNV
$mCOMPONENT_TYPE_SINT32_NV :: forall r. ComponentTypeNV -> (Void# -> r) -> (Void# -> r) -> r
COMPONENT_TYPE_SINT32_NV = ComponentTypeNV 5
-- | 'COMPONENT_TYPE_SINT64_NV' corresponds to SPIR-V @OpTypeInt@ 64 1.
pattern $bCOMPONENT_TYPE_SINT64_NV :: ComponentTypeNV
$mCOMPONENT_TYPE_SINT64_NV :: forall r. ComponentTypeNV -> (Void# -> r) -> (Void# -> r) -> r
COMPONENT_TYPE_SINT64_NV = ComponentTypeNV 6
-- | 'COMPONENT_TYPE_UINT8_NV' corresponds to SPIR-V @OpTypeInt@ 8 0.
pattern $bCOMPONENT_TYPE_UINT8_NV :: ComponentTypeNV
$mCOMPONENT_TYPE_UINT8_NV :: forall r. ComponentTypeNV -> (Void# -> r) -> (Void# -> r) -> r
COMPONENT_TYPE_UINT8_NV = ComponentTypeNV 7
-- | 'COMPONENT_TYPE_UINT16_NV' corresponds to SPIR-V @OpTypeInt@ 16 0.
pattern $bCOMPONENT_TYPE_UINT16_NV :: ComponentTypeNV
$mCOMPONENT_TYPE_UINT16_NV :: forall r. ComponentTypeNV -> (Void# -> r) -> (Void# -> r) -> r
COMPONENT_TYPE_UINT16_NV = ComponentTypeNV 8
-- | 'COMPONENT_TYPE_UINT32_NV' corresponds to SPIR-V @OpTypeInt@ 32 0.
pattern $bCOMPONENT_TYPE_UINT32_NV :: ComponentTypeNV
$mCOMPONENT_TYPE_UINT32_NV :: forall r. ComponentTypeNV -> (Void# -> r) -> (Void# -> r) -> r
COMPONENT_TYPE_UINT32_NV = ComponentTypeNV 9
-- | 'COMPONENT_TYPE_UINT64_NV' corresponds to SPIR-V @OpTypeInt@ 64 0.
pattern $bCOMPONENT_TYPE_UINT64_NV :: ComponentTypeNV
$mCOMPONENT_TYPE_UINT64_NV :: forall r. ComponentTypeNV -> (Void# -> r) -> (Void# -> r) -> r
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 :: Int -> ComponentTypeNV -> ShowS
showsPrec p :: Int
p = \case
    COMPONENT_TYPE_FLOAT16_NV -> String -> ShowS
showString "COMPONENT_TYPE_FLOAT16_NV"
    COMPONENT_TYPE_FLOAT32_NV -> String -> ShowS
showString "COMPONENT_TYPE_FLOAT32_NV"
    COMPONENT_TYPE_FLOAT64_NV -> String -> ShowS
showString "COMPONENT_TYPE_FLOAT64_NV"
    COMPONENT_TYPE_SINT8_NV -> String -> ShowS
showString "COMPONENT_TYPE_SINT8_NV"
    COMPONENT_TYPE_SINT16_NV -> String -> ShowS
showString "COMPONENT_TYPE_SINT16_NV"
    COMPONENT_TYPE_SINT32_NV -> String -> ShowS
showString "COMPONENT_TYPE_SINT32_NV"
    COMPONENT_TYPE_SINT64_NV -> String -> ShowS
showString "COMPONENT_TYPE_SINT64_NV"
    COMPONENT_TYPE_UINT8_NV -> String -> ShowS
showString "COMPONENT_TYPE_UINT8_NV"
    COMPONENT_TYPE_UINT16_NV -> String -> ShowS
showString "COMPONENT_TYPE_UINT16_NV"
    COMPONENT_TYPE_UINT32_NV -> String -> ShowS
showString "COMPONENT_TYPE_UINT32_NV"
    COMPONENT_TYPE_UINT64_NV -> String -> ShowS
showString "COMPONENT_TYPE_UINT64_NV"
    ComponentTypeNV x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "ComponentTypeNV " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read ComponentTypeNV where
  readPrec :: ReadPrec ComponentTypeNV
readPrec = ReadPrec ComponentTypeNV -> ReadPrec ComponentTypeNV
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec ComponentTypeNV)] -> ReadPrec ComponentTypeNV
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("COMPONENT_TYPE_FLOAT16_NV", ComponentTypeNV -> ReadPrec ComponentTypeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure ComponentTypeNV
COMPONENT_TYPE_FLOAT16_NV)
                            , ("COMPONENT_TYPE_FLOAT32_NV", ComponentTypeNV -> ReadPrec ComponentTypeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure ComponentTypeNV
COMPONENT_TYPE_FLOAT32_NV)
                            , ("COMPONENT_TYPE_FLOAT64_NV", ComponentTypeNV -> ReadPrec ComponentTypeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure ComponentTypeNV
COMPONENT_TYPE_FLOAT64_NV)
                            , ("COMPONENT_TYPE_SINT8_NV", ComponentTypeNV -> ReadPrec ComponentTypeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure ComponentTypeNV
COMPONENT_TYPE_SINT8_NV)
                            , ("COMPONENT_TYPE_SINT16_NV", ComponentTypeNV -> ReadPrec ComponentTypeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure ComponentTypeNV
COMPONENT_TYPE_SINT16_NV)
                            , ("COMPONENT_TYPE_SINT32_NV", ComponentTypeNV -> ReadPrec ComponentTypeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure ComponentTypeNV
COMPONENT_TYPE_SINT32_NV)
                            , ("COMPONENT_TYPE_SINT64_NV", ComponentTypeNV -> ReadPrec ComponentTypeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure ComponentTypeNV
COMPONENT_TYPE_SINT64_NV)
                            , ("COMPONENT_TYPE_UINT8_NV", ComponentTypeNV -> ReadPrec ComponentTypeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure ComponentTypeNV
COMPONENT_TYPE_UINT8_NV)
                            , ("COMPONENT_TYPE_UINT16_NV", ComponentTypeNV -> ReadPrec ComponentTypeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure ComponentTypeNV
COMPONENT_TYPE_UINT16_NV)
                            , ("COMPONENT_TYPE_UINT32_NV", ComponentTypeNV -> ReadPrec ComponentTypeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure ComponentTypeNV
COMPONENT_TYPE_UINT32_NV)
                            , ("COMPONENT_TYPE_UINT64_NV", ComponentTypeNV -> ReadPrec ComponentTypeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure ComponentTypeNV
COMPONENT_TYPE_UINT64_NV)]
                     ReadPrec ComponentTypeNV
-> ReadPrec ComponentTypeNV -> ReadPrec ComponentTypeNV
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int -> ReadPrec ComponentTypeNV -> ReadPrec ComponentTypeNV
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "ComponentTypeNV")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       ComponentTypeNV -> ReadPrec ComponentTypeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> ComponentTypeNV
ComponentTypeNV Int32
v)))


type NV_COOPERATIVE_MATRIX_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_NV_COOPERATIVE_MATRIX_SPEC_VERSION"
pattern NV_COOPERATIVE_MATRIX_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_COOPERATIVE_MATRIX_SPEC_VERSION :: a
$mNV_COOPERATIVE_MATRIX_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
NV_COOPERATIVE_MATRIX_SPEC_VERSION = 1


type NV_COOPERATIVE_MATRIX_EXTENSION_NAME = "VK_NV_cooperative_matrix"

-- No documentation found for TopLevel "VK_NV_COOPERATIVE_MATRIX_EXTENSION_NAME"
pattern NV_COOPERATIVE_MATRIX_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_COOPERATIVE_MATRIX_EXTENSION_NAME :: a
$mNV_COOPERATIVE_MATRIX_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_COOPERATIVE_MATRIX_EXTENSION_NAME = "VK_NV_cooperative_matrix"